diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/DESCRIPTION b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/DESCRIPTION new file mode 100644 index 0000000..69a2d9a --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/DESCRIPTION @@ -0,0 +1,18 @@ +Package: RBBGCMuso +Title: An R package for BiomeBGC-MuSo ecosystem modelling +Version: 0.7.1 +Authors@R: person("Roland", "Hollo's", , "hollorol@gmail.com", role = c("aut", "cre")) +Description: What the package does (one paragraph). +Depends: R (>= 3.3.2) +License: GPL-2 +NeedsCompilation: no +Packaged: 2023-02-06 09:42:51 UTC; user +Author: Roland Hollo's [aut, cre] +Imports: grDevices, limSolve, stats, utils, graphics, Rcpp, magrittr, + dplyr, ggplot2, rmarkdown, tibble, tidyr, glue, scales, tcltk, + digest, jsonlite, data.table, gridExtra, lubridate, openxlsx, + ncdf4, future, httr, tcltk, Boruta, rpart, rpart.plot +Maintainer: Roland Hollo's +Suggests: knitr, rmarkdown, +VignetteBuilder: knitr +ByteCompile: true diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/NAMESPACE b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/NAMESPACE new file mode 100644 index 0000000..448280f --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/NAMESPACE @@ -0,0 +1,97 @@ +# Generated by roxygen2: do not edit by hand + +export(calibMuso) +export(calibrateMuso) +export(changemulline) +export(checkFileSystem) +export(checkMeteoBGC) +export(cleanupMuso) +export(compareMuso) +export(copyMusoExampleTo) +export(corrigMuso) +export(createSoilFile) +export(flatMuso) +export(getAnnualOutputList) +export(getConstMatrix) +export(getDailyOutputList) +export(getFilePath) +export(getFilesFromIni) +export(getyearlycum) +export(getyearlymax) +export(multiSiteCalib) +export(musoDate) +export(musoGlue) +export(musoMapping) +export(musoMappingFind) +export(musoMonte) +export(musoQuickEffect) +export(musoRand) +export(musoSensi) +export(normalMuso) +export(optiMuso) +export(paramSweep) +export(plotMuso) +export(plotMusoWithData) +export(randEpc) +export(readObservedData) +export(runMuso) +export(rungetMuso) +export(saveAllMusoPlots) +export(setupMuso) +export(spinupMuso) +export(supportedMuso) +export(updateMusoMapping) +import(ggplot2) +import(utils) +importFrom(data.table,':=') +importFrom(data.table,data.table) +importFrom(data.table,fread) +importFrom(digest,digest) +importFrom(dplyr,'%>%') +importFrom(dplyr,filter) +importFrom(dplyr,group_by) +importFrom(dplyr,mutate) +importFrom(dplyr,select) +importFrom(dplyr,summarize) +importFrom(dplyr,tbl_df) +importFrom(future,future) +importFrom(ggplot2,aes) +importFrom(ggplot2,aes_string) +importFrom(ggplot2,element_blank) +importFrom(ggplot2,element_text) +importFrom(ggplot2,facet_wrap) +importFrom(ggplot2,geom_bar) +importFrom(ggplot2,geom_line) +importFrom(ggplot2,geom_point) +importFrom(ggplot2,ggplot) +importFrom(ggplot2,ggsave) +importFrom(ggplot2,ggtitle) +importFrom(ggplot2,labs) +importFrom(ggplot2,scale_y_continuous) +importFrom(ggplot2,theme) +importFrom(ggplot2,theme_classic) +importFrom(ggplot2,xlab) +importFrom(ggplot2,ylab) +importFrom(glue,glue) +importFrom(gridExtra,grid.arrange) +importFrom(httr,GET) +importFrom(httr,config) +importFrom(httr,content) +importFrom(httr,with_config) +importFrom(jsonlite,write_json) +importFrom(limSolve,xsample) +importFrom(lubridate,leap_year) +importFrom(magrittr,'%<>%') +importFrom(magrittr,'%>%') +importFrom(openxlsx,read.xlsx) +importFrom(rmarkdown,pandoc_version) +importFrom(rmarkdown,render) +importFrom(rpart,rpart) +importFrom(rpart,rpart.control) +importFrom(rpart.plot,rpart.plot) +importFrom(scales,percent) +importFrom(stats,approx) +importFrom(tcltk,tk_choose.files) +importFrom(tibble,rownames_to_column) +importFrom(tidyr,gather) +importFrom(tidyr,separate) diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/assistantFunctions.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/assistantFunctions.R new file mode 100644 index 0000000..5cc50af --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/assistantFunctions.R @@ -0,0 +1,188 @@ +#' getLogs +#' +#'This function gives us the muso logfiles with their path +#' +#'@param outputLoc This is the location of the output files. +#'@param outputNames These are the prefixes of the logfiles +#'@return Logfiles with paths +#'@keywords internal + + +getLogs <- function(outputLoc, outputNames, type = "spinup"){ + switch(type, + "spinup" = return(grep(paste0(outputNames[1], ".log"), list.files(outputLoc), value = TRUE)), + "normal" = return(grep(paste0(outputNames[2], ".log"), list.files(outputLoc), value = TRUE)), + "both" = return(sapply(1:2, function (x){grep(paste0(outputNames[x], ".log"), list.files(outputLoc), value = TRUE)}))) +} + + +#' readErrors +#' +#'This function reads the spinup and the normal logfiles and gives back the last line which indicates weather there are any errors during the model execution or not. +#' +#'@param outputLoc This is the location of the output file. +#'@param logfiles These are the names of the logfiles. +#'@return vector with 0 and 1 values, 1, if succed, 0 if not. The first is the spinup run, the second is the normal. +#'@keywords internal + + +readErrors <- function(outputLoc, logfiles, type = "both"){ + + if(length(logfiles)==0){ + if(type=="normal"){ + return(1) + } else { + return(c(0,0)) + } + } + + + switch( type, + "both" = return( + as.numeric( + as.vector( + lapply(paste(outputLoc,logfiles,sep = "/"), + function(x) { + tail(readLines(x,-1),1) + } + ) + ) + ) + ), + "spinup" = print("spinup"), + "normal" = return( + abs(as.numeric(tail(readLines(file.path(outputLoc,logfiles),-1),1))-1) + ) + ) +} + +#' getOutFiles +#' +#'This function gives us the muso output files with their paths +#' +#'@param outputLoc This is the location of the output files. +#'@param outputNames These are the prefixes of the logfiles. +#'@return Output files with their paths. +#'@keywords internal + + +getOutFiles <- function(outputLoc, outputNames){ + + return(grep("out$", grep(paste(paste0(outputNames, "*"), collapse = "|"), list.files(outputLoc), value=TRUE), value = TRUE)) +} + +#' stampAndCopy +#' +#'This function gives us the model output files with their paths +#' +#'@param outputLoc This is the location of the output files. +#'@param outputNames These are the prefixes of the logfiles +#'@return Output files with their paths +#'@keywords internal + +stampAndDir <- function(outputLoc,names,stampDir, wrongDir, type="output", errorsign, logfiles){ + + switch(type, + "output" = ( + file.copy(file.path(outputLoc,names) + ,file.path(stampDir,paste0((stamp(stampDir)+1),"-",names))) ), + "general" = (function (){ + stampnum <- stamp(stampDir) + lapply(names,function (x) file.copy(from = x ,to=paste(stampDir,"/",(stampnum+1),"-", basename(x),sep=""))) + if(errorsign==1){ + lapply(names, function (x) file.copy(from = paste(stampDir,"/",(stampnum+1),"-",basename(x),sep=""), to=wrongDir))}})() + + ) + +} + + + +compareNA <- function(v,a){ + compared<- (v==a) + compared[is.na(compared)] <- FALSE + return(compared) +} + +#' dynRound +#' +#'This function rounds a sequence (definded by its endpoints and the length) optimally +#' +#'@param x The lower end of the sequence +#'@param y The higher end of the sequence +#' @param seqLen The length of the sequence +#'@return rounded sequence +#'@keywords internal + +dynRound <- function(x,y,seqLen){ + digitNum <- 2 + a <- seq(x,y, length = seqLen) + while(length(a) != length(unique(round(a,digitNum)))){ + digitNum <- digitNum +1 + } + + return(round(a,digitNum)) +} + + +readValuesFromFile <- function(epc, linums){ + epcFile <- readLines(epc) + rows <- numeric(2) + values <- sapply(linums, function(x){ + rows[1] <- as.integer(x) + rows[2] <- as.integer(round(100*x)) %% 10 + 1 + epcFile <- readLines(epc) + selRow <- unlist(strsplit(epcFile[rows[1]], split= "[\t ]")) + selRow <- selRow[selRow!=""] + return(as.numeric(selRow[rows[2]])) + + }) + + return(values) +} +#' readMeasuredMuso +#' +#' MuSo data reader +#' @importFrom data.table fread data.table +#' @export + +readObservedData <- function(inFile, + naString = NULL, sep = ",", + leapYearHandling = TRUE, + convert.var = NULL, + convert.scalar = 1, + convert.fun = (function (x) {x * convert.scalar}), + convert.file = NULL, + filterCol = NULL, + filterVal = 1, + selVar = NULL + ){ + + if(!is.null(naString)){ + if(is.numeric(naString)){ + baseData <- fread(file = inFile, sep=sep) + baseData <- as.data.frame(baseData) + baseData[baseData[,selVar] == naString,selVar] <- NA + } else { + baseData <- fread(file = inFile, sep=sep, na.strings = naString) + baseData <- as.data.frame(baseData) + } + + + } else { + + baseData <- fread(file = inFile, sep=sep) + baseData <- as.data.frame(baseData) + } + + if(!is.null(filterCol)){ + filterVar<- colnames(baseData)[filterCol] + baseData[(baseData[,filterVar] == filterVal),selVar] <- NA + } + head(baseData) + if(!is.null(selVar)){ + baseData[,selVar] <-convert.fun(baseData[,selVar]) + } + + return(data.table(baseData)) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/atStart.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/atStart.R new file mode 100644 index 0000000..dae7686 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/atStart.R @@ -0,0 +1,36 @@ +.onLoad <- function(libname,pkgname){ + RMuso_version <- 7 + cat(sprintf("This is RBBGCMuso version 1.0\nDefault Biome-BGCMuSo version: %d", + RMuso_version)) + RMuso_constMatrix <- list(epc=NULL,soil=NULL) + RMuso_varTable <- list() + #___________________________ + sapply(names(RMuso_constMatrix),function(fType){ + sapply(list.files(path=system.file("data",package="RBBGCMuso"), + pattern=sprintf("^%sConstMatrix\\d\\.json$",fType), full.names=TRUE),function(fName){ + constMatrix <- jsonlite::read_json(fName,simplifyVector = TRUE)[,c(1,2,3,4,9,5,6,7,8)] + version <- gsub(".*(\\d)\\.json","\\1",fName) + RMuso_constMatrix[[fType]][[version]] <<- constMatrix + }) + RMuso_constMatrix + # RMuso_constMatrix <<- RMuso_constMatrix + }) + + + sapply(list.files(path=system.file("data",package="RBBGCMuso"), + pattern="^varTable\\d\\.json$", full.names=TRUE),function(fName){ + varTable <- jsonlite::read_json(fName,simplifyVector = TRUE) + version <- gsub(".*(\\d)\\.json","\\1",fName) + RMuso_varTable[[version]] <<- varTable + }) + + RMuso_depTree<- read.csv(file.path(system.file("data",package="RBBGCMuso"),"depTree.csv"), stringsAsFactors=FALSE) + + + options(RMuso_version=RMuso_version, + RMuso_constMatrix=RMuso_constMatrix, + RMuso_varTable=RMuso_varTable, + RMuso_depTree=RMuso_depTree + ) + # getOption("RMuso_constMatrix")$soil[[as.character(getOption("RMuso_version"))]] +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibMuso.R new file mode 100644 index 0000000..f0826f7 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibMuso.R @@ -0,0 +1,368 @@ +#' calibMuso +#' +#' This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a well-structured way. +#' +#' @author Roland Hollos +#' @param settings You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment +#' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet. +#' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles +#' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory. +#' @param export if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv. +#' @param silent If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed. +#' @param aggressive It deletes every possible modell-outputs from the previous modell runs. +#' @param parameters In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4) +#' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter +#' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled. +#' @param keepBinary In default RBBGCMuso to keep working area as clean as possible, deletes all the regular output files. The results are directly printed to the standard output, but you can redirect it, and save it to a variable, or you can export your results to the desired destination in a desired format. Whith this variable you can enable to keep the binary output files. If you want to set the location of the binary output, please take a look at the binaryPlace argument. +#' @param binaryPlace The place of the binary output files. +#' @param fileToChange You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini" +#' @param skipSpinup If TRUE, calibMuso wont do spinup simulation +#' @param prettyOut date ad Date type, separate year, month, day vectors +#' @return No return, outputs are written to file +#' @usage calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, +#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +#' @import utils +#' @export + +calibMuso <- function(settings=setupMuso(), calibrationPar=NULL, + parameters=NULL, outVars = NULL, timee="d", + debugging=FALSE, logfilename=NULL, + keepEpc=FALSE, export=FALSE, + silent=FALSE, aggressive=FALSE, + keepBinary=FALSE, + binaryPlace = "./", fileToChange = "epc", + skipSpinup = TRUE, modifyOriginal = FALSE, prettyOut = FALSE, + postProcString = NULL, + doBackup=TRUE + ){ # +######################################################################## +###########################Set local variables and places############### +######################################################################## + if(doBackup){ + file.copy(eval(parse(text = sprintf("settings$%sInput[2]", fileToChange))),file.path(settings$inputLoc),overwrite=FALSE) + } + + bck <- file.path(settings$inputLoc, "bck", + basename(eval(parse(text = sprintf("settings$%sInput[2]", fileToChange))))) + + if(!silent){ + cat("Biome-BGC simulation started\n") # ZOLI + } + + Linuxp <-(Sys.info()[1]=="Linux") + ##Copy the variables from settings + inputLoc <- settings$inputLoc + outputLoc <- settings$outputLoc + outputNames <- settings$outputNames + executable <- settings$executable + iniInput <- settings$iniInput + epc <- settings$epcInput + + if(is.null(calibrationPar)){ + calibrationPar <- settings$calibrationPar + } + binaryPlace <- normalizePath(binaryPlace) + whereAmI<-getwd() + + + ## Set the working directory to the inputLoc temporarly. + setwd(inputLoc) + + + if(debugging){#If debugging option turned on + #If log or ERROR directory does not exists create it! + dirName<-file.path(inputLoc,"LOG") + dirERROR<-file.path(inputLoc,"ERROR") + + if(!dir.exists(dirName)){ + dir.create(dirName) + } + + if(!dir.exists(dirERROR)){ + dir.create(dirERROR) + } + } + + if(keepEpc) { + epcdir <- dirname(epc[1]) + print(epcdir) + WRONGEPC<-file.path(inputLoc,"WRONGEPC") + EPCS<-file.path(inputLoc,"EPCS") + + if(!dir.exists(WRONGEPC)){ + dir.create(WRONGEPC) + } + + if(!dir.exists(EPCS)){ + dir.create(EPCS) + } + } + +############################################################# +############################spinup run############################ + ########################################################## + + + + + if(aggressive == TRUE){ + cleanupMuso(location = outputLoc,deep = TRUE) + } + + + ##change the epc file if and only if there are given parameters + + if(!is.null(parameters)){ + changemulline(filePaths = epc[2], + calibrationPar = calibrationPar, + contents = parameters, + src = if(file.exists(bck)){ + bck + } else { + NULL + }) + # fileToChange = fileToChange,) + } + + + ##We change the working directory becase of the model, but we want to avoid sideeffects, so we save the current location and after that we will change everything to it. + + if(!skipSpinup) { + + ##Run the model for the spinup run. + + if(silent){#silenc mode + if(Linuxp){ + #In this case, in linux machines + tryCatch(system(paste(executable,iniInput[1],"> /dev/null",sep=" ")), + error= function (e){ + setwd((whereAmI)) + stop("Cannot run the modell-check the executable!")}) + } else { + #In windows machines there is a show.output.on.console option + tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE), + error= function (e){ + setwd((whereAmI)) + stop("Cannot run the modell-check the executable!")}) + } + + } else { + system(paste(executable,iniInput[1],sep=" ")) + } + + + logspinup <- getLogs(outputLoc,outputNames,type="spinup") + ## logspinup <- grep(paste0(outputNames[1],".log"), list.files(outputLoc),value = TRUE) + ## logspinup <- list.files(outputLoc)[grep("log$",list.files(outputLoc))]#load the logfiles + + if(length(logspinup)==0){ + if(keepEpc){ + stampnum<-stamp(EPCS) + lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep=""))) + lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC)) + setwd(whereAmI) + stop("Modell Failure") + } + setwd(whereAmI) + stop("Modell Failure") #in that case the modell did not create even a logfile + } + + if(length(logspinup)>1){ + spincrash<-TRUE + } else { + if(identical(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1),character(0))){ + spincrash<-TRUE + } else { + spincrash <- (tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)!=1) + } + } + } else {spincrash <- FALSE} + #If the last line in the logfile is 0 There are mistakes so the spinup crashes + + if(!spincrash){##If spinup did not crashed, run the normal run. + + ##################################################################### + ###########################normal run######################### + ################################################################# + + ##for the sake of safe we set the location again + setwd(inputLoc) + + if(silent){ + if(Linuxp){ + tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")), + error =function (e){ + setwd((whereAmI)) + stop("Cannot run the modell-check the executable!")}) + } else { + tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE), + error =function (e){ + setwd((whereAmI)) + stop("Cannot run the modell-check the executable!")} ) + } + + } else { + tryCatch(system(paste(executable,iniInput[2],sep=" ")), + error =function (e){ + setwd((whereAmI)) + stop("Cannot run the modell-check the executable!")}) + } + + + ##read the output + + switch(timee, + "d"=(Reva <- tryCatch(getdailyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})), + "m"=(Reva <- tryCatch(getmonthlyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})), + "y"=(Reva <- tryCatch(getyearlyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})) + ) + if(keepBinary){ + possibleNames <- tryCatch(getOutFiles(outputLoc = outputLoc,outputNames = outputNames), + error=function (e){ + setwd((whereAmI)) + stop("Cannot find output files")}) + stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output") + } + } + + + if(skipSpinup){ + logfiles <- tryCatch(getLogs(outputLoc,outputNames,type="normal"), + error = function (e){ + setwd(whereAmI) + stop("Cannot find log files, something went wrong")}) + } else { + logfiles <- tryCatch(getLogs(outputLoc,outputNames,type="both"), + error = function (e){ + setwd(whereAmI) + stop("Cannot find log files, something went wrong")}) + } + ## list.files(outputLoc)[grep("log$",list.files(outputLoc))]#creating a vector for logfilenames + +############################################### +#############LOG SECTION####################### +############################################### + + if(skipSpinup){ + errorsign <- readErrors(outputLoc=outputLoc,logfiles=logfiles,type="normal") + } else { + + perror <- readErrors(outputLoc=outputLoc,logfiles=logfiles) #vector of spinup and normalrun error + + + ##if errorsign is 1 there is error, if it is 0 everything ok + perror[is.na(perror)]<-0 + if(length(perror)>sum(perror)){ + errorsign <- 1 + } else { + if(length(perror)==1){ + errorsign <- 1 + } else { + if(spincrash){ + errorsign <- 1 + } else { + errorsign <- 0 + } } + } + + + + } + + + + + if(keepEpc){#if keepepc option turned on + + if(length(unique(dirname(epc)))>1){ + stop("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?") + } else { + if(skipSpinup){ + stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc[2], type="general", errorsign=errorsign, logfiles=logfiles) + } + stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc, type="general", errorsign=errorsign, logfiles=logfiles) + + } + } + + + + if(debugging){ #debugging is boolean + logfiles <- file.path(outputLoc,logfiles) + + stampAndDir(stampDir=dirName, wrongDir=dirERROR, names=logfiles, type="general",errorsign=errorsign,logfiles=logfiles)} + + + #cleanupMuso(location=outputLoc,deep = FALSE) + if(errorsign==1){ + stop("Modell Failure") + } + + + + + if(timee=="d"){ + if(!prettyOut){ + colnames(Reva) <- unlist(settings$outputVars[[1]]) + } else{ + Reva <- cbind.data.frame( + musoDate(startYear = settings$startYear, + numYears = settings$numYears, + combined = FALSE, prettyOut = TRUE), + Reva) + colnames(Reva) <- as.character(c("date","day","month","year",unlist(settings$outputVars[[1]])) ) + + } + } else { + if(timee=="y") + colnames(Reva) <- unlist(settings$outputVars[[2]]) + } + + if(!is.null(postProcString)){ + Reva <- postProcMuso(Reva,postProcString) + } + + ## if(leapYear){ + ## Reva <- corrigMuso(settings,Reva) + ## if(!prettyOut){ + ## rownames(Reva) <- musoDate(settings$startYear,settings$numYears) + ## } + + ## } else { + ## if(!prettyOut){ + ## rownames(Reva) <- musoDate(settings$startYear, settings$numYears) + ## } + + ## } + + if(!prettyOut){ + rownames(Reva) <- musoDate(settings$startYear, numYears = settings$numYears) + } + + + if(export!=FALSE){ + setwd(whereAmI) + + ## switch(fextension(export), + ## "csv"=(write.csv(Reva,export)), + ## "xlsx"=(), + ## "odt"= + + + ## ) + write.csv(Reva,export) + + } else{ + setwd(whereAmI) + return(Reva) + } +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibrateMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibrateMuso.R new file mode 100644 index 0000000..87a9ee5 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibrateMuso.R @@ -0,0 +1,396 @@ +#' calibrateMuso +#' +#' This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters. +#' @author Roland HOLLOS +#' @importFrom future future +#' @export +calibrateMuso <- function(measuredData, parameters =read.csv("parameters.csv", stringsAsFactor=FALSE), startDate = NULL, + endDate = NULL, formatString = "%Y-%m-%d", + dataVar, outLoc = "./calib", + preTag = "cal-", settings = setupMuso(), + outVars = NULL, iterations = 100, + skipSpinup = TRUE, plotName = "calib.jpg", + modifyOriginal=TRUE, likelihood, uncertainity = NULL, + naVal = NULL, postProcString = NULL, + thread_prefix="thread", numCores = max(c(parallel::detectCores()-1,1)), pb = txtProgressBar(min=0, max=iterations, style=3), + maxLikelihoodEpc=TRUE, + pbUpdate = setTxtProgressBar, outputLoc="./", method="GLUE",lg = FALSE, w=NULL, ...){ + + future::plan(future::multisession) + file.remove(list.files(path = settings$inputLoc, pattern="progress.txt", recursive = TRUE, full.names=TRUE)) + file.remove(list.files(path = settings$inputLoc, pattern="preservedCalib.csv", recursive = TRUE, full.names=TRUE)) + unlink(file.path(settings$inputLoc,"thread"),recursive=TRUE) + + # ____ _ _ _ _ + # / ___|_ __ ___ __ _| |_ ___ | |_| |__ _ __ ___ __ _ __| |___ + # | | | '__/ _ \/ _` | __/ _ \ | __| '_ \| '__/ _ \/ _` |/ _` / __| + # | |___| | | __/ (_| | || __/ | |_| | | | | | __/ (_| | (_| \__ \ + # \____|_| \___|\__,_|\__\___| \__|_| |_|_| \___|\__,_|\__,_|___/ + + + + copyToThreadDirs(thread_prefix, numcores = numCores, runDir = settings$inputLoc) + + # ____ _ _ _ + # | _ \ _ _ _ __ | |_| |__ _ __ ___ __ _ __| |___ + # | |_) | | | | '_ \ | __| '_ \| '__/ _ \/ _` |/ _` / __| + # | _ <| |_| | | | | | |_| | | | | | __/ (_| | (_| \__ \ + # |_| \_\\__,_|_| |_| \__|_| |_|_| \___|\__,_|\__,_|___/ + + threadCount <- distributeCores(iterations, numCores) + + fut <- lapply(1:numCores, function(i) { + # browser() + future({ + tryCatch( + musoSingleThread(measuredData, parameters, startDate, + endDate, formatString, + dataVar, outLoc, + preTag, settings, + outVars, iterations = threadCount[i], + skipSpinup, plotName, + modifyOriginal, likelihood, uncertainity, + naVal, postProcString, i) + , error = function(e){ + writeLines(as.character(iterations),"progress.txt") + }) + + # musoSingleThread(measuredData, parameters, startDate, + # endDate, formatString, + # dataVar, outLoc, + # preTag, settings, + # outVars, iterations = threadCount[i], + # skipSpinup, plotName, + # modifyOriginal, likelihood, uncertainity, + # naVal, postProcString, i) + }) + }) + + # __ ___ _ _ + # \ \ / / |__ __ _| |_ ___| |__ _ __ _ __ ___ ___ ___ ___ ___ + # \ \ /\ / /| '_ \ / _` | __/ __| '_ \ | '_ \| '__/ _ \ / __/ _ \/ __/ __| + # \ V V / | | | | (_| | || (__| | | | | |_) | | | (_) | (_| __/\__ \__ \ + # \_/\_/ |_| |_|\__,_|\__\___|_| |_| | .__/|_| \___/ \___\___||___/___/ + # |_| + + getProgress <- function(){ + # threadfiles <- list.files(settings$inputLoc, pattern="progress.txt", recursive = TRUE) + threadfiles <- list.files(pattern="progress.txt", recursive = TRUE) + if(length(threadfiles)==0){ + return(0) + } else { + sum(sapply(threadfiles, function(x){ + partRes <- readLines(x) + if(length(partRes)==0){ + return(0) + } else { + return(as.numeric(partRes)) + } + + })) + + } + } + + progress <- 0 + while(progress < iterations){ + Sys.sleep(1) + progress <- tryCatch(getProgress(), error=function(e){progress}) + if(is.null(pb)){ + pbUpdate(as.numeric(progress)) + } else { + pbUpdate(pb,as.numeric(progress)) + } + } + if(!is.null(pb)){ + close(pb) + } + + # ____ _ _ + # / ___|___ _ __ ___ | |__ (_)_ __ ___ + # | | / _ \| '_ ` _ \| '_ \| | '_ \ / _ \ + # | |__| (_) | | | | | | |_) | | | | | __/ + # \____\___/|_| |_| |_|_.__/|_|_| |_|\___| + resultFiles <- list.files(pattern="preservedCalib.*csv$",recursive=TRUE) + res0 <- read.csv(grep("thread_1/",resultFiles, value=TRUE),stringsAsFactors=FALSE) + if(numCores==1){ + results <- res0 + } else { + resultFilesSans0 <- grep("thread_1/", resultFiles, value=TRUE, invert=TRUE) + # results <- do.call(rbind,lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE)})) + resultsSans0 <- lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE, header=FALSE)}) + resultsSans0 <- do.call(rbind,resultsSans0) + colnames(resultsSans0) <- colnames(res0) + results <- (rbind(res0,resultsSans0)) + } + + switch(method, + "GLUE"={ + musoGlue(results, parameters=parameters,settings=settings, w=w, lg=lg) + }, + "agromo"={ + liks <- results[,sprintf("%s_likelihood",names(likelihood))] + epcIndexes <- future::value(fut[[1]], stdout = FALSE, signal=FALSE) + epcVals <- results[which.max(liks),1:length(epcIndexes)] + epcPlace <- file.path(dirname(settings$inputFiles),settings$epc)[2] + changemulline(filePaths= epcPlace, epcIndexes, + epcVals, src =epcPlace,# settings$epcInput[2], + outFiles = file.path(outputLoc, "maxLikelihood_epc.epc")) + names(epcVals) <- epcIndexes + xdate <- as.Date(measuredData$date) + meanM <- measuredData[,sprintf("mean.%s", names(likelihood))] + minsd <- meanM - measuredData[,sprintf("sd.%s", names(likelihood)[1])] + maxsd <- meanM + measuredData[,sprintf("sd.%s", names(likelihood)[1])] + minM <- measuredData[,sprintf("min.%s", names(likelihood)[1])] + maxM <- measuredData[,sprintf("max.%s", names(likelihood)[1])] + plot(xdate, minM, type="l", xlab=NA, ylim=c(min(minM)*0.8, max(maxM)*1.1), ylab = names(likelihood)[1]) + lines(xdate, maxM) + polygon(c(xdate,rev(xdate)),c(minM,rev(maxM)), col="gray",border=NA) + lines(xdate, minsd) + lines(xdate, maxsd) + polygon(c(xdate,rev(xdate)),c(minsd,rev(maxsd)), col="gray30",border=NA) + points(xdate,meanM) + + varIndex <- match(as.character(dataVar),settings$dailyVarCodes) + apriori <- calibMuso(settings) + modDates <- as.Date(row.names(apriori), format="%d.%m.%Y") + lines(modDates, apriori[,varIndex],col="brown") + calibrated <- calibMuso(settings, calibrationPar = as.numeric(names(epcVals)), parameters=epcVals) + lines(modDates, calibrated[,varIndex],col="blue") + + }, + stop(sprintf("method: %s not found, please choose from {GLUE, agromo}. See more about this in the documentation of the function!", method)) + ) +} + +copyToThreadDirs <- function(prefix="thread", numcores=parallel::detectCores()-1, runDir="."){ + dir.create(file.path(runDir,prefix), showWarnings=TRUE) + fileNames <- grep(".*thread$", list.files(runDir,full.names=TRUE), value=TRUE, invert=TRUE) + invisible(sapply(1:numcores,function(corenum){ + threadDir <- file.path(runDir,prefix,paste0(prefix,"_",corenum),"") + dir.create(threadDir, showWarnings=FALSE) + file.copy(from=fileNames,to=threadDir, overwrite=FALSE, recursive=TRUE) + })) +} + +musoSingleThread <- function(measuredData, parameters = NULL, startDate = NULL, + endDate = NULL, formatString = "%Y-%m-%d", + dataVar, outLoc = "./calib", + preTag = "cal-", settings = setupMuso(), + outVars = NULL, iterations = 300, + skipSpinup = TRUE, plotName = "calib.jpg", + modifyOriginal=TRUE, likelihood, uncertainity = NULL, + naVal = NULL, postProcString = NULL, threadNumber) { + + setwd(paste0(settings$inputLoc, "/thread/thread_", threadNumber)) + + iniFiles <- file.path(settings$iniInput) + # iniFiles <- list.files(pattern=".*ini") + # if(length(iniFiles)==1){ + # iniFiles <- rep(iniFiles, 2) + # } + settings <- setupMuso(iniInput = iniFiles) + # Exanding likelihood + + likelihoodFull <- as.list(rep(NA,length(dataVar))) + names(likelihoodFull) <- names(dataVar) + if(!missing(likelihood)) { + lapply(names(likelihood),function(x){ + likelihoodFull[[x]] <<- likelihood[[x]] + }) + } + defaultLikelihood <- which(is.na(likelihood)) + if(length(defaultLikelihood)>0){ + likelihoodFull[[defaultLikelihood]] <- (function(x, y){ + exp(-sqrt(mean((x-y)^2))) + }) + } + + mdata <- measuredData + if(is.null(parameters)){ + parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) { + stop("You need to specify a path for the parameters.csv, or a matrix.") + }) + } else { + if((!is.list(parameters)) & (!is.matrix(parameters))){ + parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){ + stop("Cannot find neither parameters file neither the parameters matrix") + }) + }} + + outLoc <- normalizePath(outLoc) + outLocPlain <- basename(outLoc) + currDir <- getwd() + + if(!dir.exists(outLoc)){ + dir.create(outLoc) + warning(paste(outLoc," is not exists, so it was created")) + } + + outLoc <- normalizePath(outLoc) + parameterNames <- parameters[,1] + pretag <- file.path(outLoc,preTag) + ##reading the original epc file at the specified + ## row numbers + print("optiMuso is randomizing the epc parameters now...",quote = FALSE) + if(iterations < 3000){ + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = 3000) + randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] + } else { + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations) + } + + origEpc <- readValuesFromFile(settings$epc[2],randVals[[1]]) + partialResult <- matrix(ncol=length(randVals[[1]])+2*length(dataVar)) + colN <- randVals[[1]] + colN[match(parameters[,2],randVals[[1]])] <- parameters[,1] + colN[match(parameters[,2], randVals[[1]])[!is.na(match(parameters[,2],randVals[[1]]))]] <- parameters[,1] + colnames(partialResult) <- c(colN,sprintf("%s_likelihood",names(dataVar)), + sprintf("%s_rmse",names(dataVar))) + numParameters <- length(colN) + partialResult[1:numParameters] <- origEpc + ## Prepare the preservedCalib matrix for the faster + ## run. + + pretag <- file.path(outLoc,preTag) + + musoCodeToIndex <- sapply(dataVar,function(musoCode){ + settings$dailyOutputTable[settings$dailyOutputTable$code == musoCode,"index"] + }) + resultRange <- (numParameters + 1):(ncol(partialResult)) + ## Creating function for generating separate + ## csv files for each run + + settings$iniInput[2] %>% + (function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>% + unlink + randValues <- randVals[[2]] + + settings$calibrationPar <- randVals[[1]] + + if(!is.null(naVal)){ + measuredData <- as.data.frame(measuredData) + measuredData[measuredData == naVal] <- NA + } + + alignIndexes <- alignMuso(settings,measuredData) + if(!is.null(uncertainity)){ + uncert <- measuredData[alignIndexes$meas,uncertainity] + } else { + uncert <- NULL + } + # browser() + if(threadNumber == 1){ + origModellOut <- calibMuso(settings=settings, silent=TRUE, skipSpinup = skipSpinup, postProcString=postProcString, modifyOriginal=modifyOriginal) + partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar, + mod=origModellOut, + mes=measuredData, + likelihoods=likelihood, + alignIndexes=alignIndexes, + musoCodeToIndex = musoCodeToIndex,uncert=uncert) + write.csv(x=origModellOut, file=paste0(pretag, 1, ".csv")) + write.csv(x=partialResult, file="preservedCalib.csv",row.names=FALSE) + } + print("Running the model with the random epc values...", quote = FALSE) + + # if(!is.null(postProcString)){ + # colNumb <- length(settings$dailyVarCodes) + 1 + # } + + + for(i in 2:(iterations+1)){ + + tmp <- tryCatch(calibMuso(settings = settings, + parameters = randValues[(i-1),], + silent= TRUE, + skipSpinup = skipSpinup, modifyOriginal=modifyOriginal, postProcString = postProcString), error = function (e) NULL) + if(is.null(tmp)){ + partialResult[,resultRange] <- NA + } else { + partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar, + mod=tmp, + mes=measuredData, + likelihoods=likelihood, + alignIndexes=alignIndexes, + musoCodeToIndex = musoCodeToIndex, uncert = uncert) + } + + partialResult[1:numParameters] <- randValues[(i-1),] + write.table(x=partialResult, file="preservedCalib.csv", append=TRUE, row.names=FALSE, + sep=",", col.names=FALSE) + write.csv(x=tmp, file=paste0(pretag, (i+1),".csv")) + writeLines(as.character(i-1),"progress.txt") + } + + if(threadNumber == 1){ + return(randVals[[1]]) + } + +} + +distributeCores <- function(iterations, numCores){ + perProcess<- iterations %/% numCores + numSimu <- rep(perProcess,numCores) + gainers <- sample(1:numCores, iterations %% numCores) + numSimu[gainers] <- numSimu[gainers] + 1 + numSimu +} + +prepareFromAgroMo <- function(fName){ + obs <- read.table(fName, stringsAsFactors=FALSE, sep = ";", header=T) + obs <- reshape(obs, timevar="var_id", idvar = "date", direction = "wide") + dateCols <- apply(do.call(rbind,(strsplit(obs$date, split = "-"))),2,as.numeric) + colnames(dateCols) <- c("year", "month", "day") + cbind.data.frame(dateCols, obs) +} + + +calcLikelihoodsAndRMSE <- function(dataVar, mod, mes, likelihoods, alignIndexes, musoCodeToIndex, uncert){ + + mes <- as.data.frame(mes) + # NOT COMPATIBLE WITH OLD MEASUREMENT DATA, mes have to be a matrix + likelihoodRMSE <- sapply(names(dataVar),function(key){ + modelled <- mod[alignIndexes$mod,musoCodeToIndex[key]] + selected <- grep(sprintf("%s$", key), colnames(mes)) + # browser() + + measured <- mes[alignIndexes$meas,selected] + + if(is.null(dim(measured))){ + notNA <- !is.na(measured) + m <- measured <- measured[notNA] + + } else { + notNA <- sapply(1:nrow(measured), function(x){!any(is.na(measured[x,]))}) + measured <- measured[notNA,] + m <- measured[,grep("^mean", colnames(measured))] + } + modelled <- modelled[notNA] + + # uncert <- uncert[!is.na(measured)] + + # measured <- measured[!is.na(measured)] + res <- c(likelihoods[[key]](modelled, measured), + sqrt(mean((modelled-m)^2)) + ) + # browser() + res + }) + names(likelihoodRMSE) <- c(sprintf("%s_likelihood",dataVar), sprintf("%s_rmse",dataVar)) + return(c(likelihoodRMSE[1,],likelihoodRMSE[2,])) +} + +agroLikelihood <- function(modVector,measured){ + mu <- measured[,grep("mean", colnames(measured))] + stdev <- measured[,grep("^sd", colnames(measured))] + ndata <- nrow(measured) + sum(sapply(1:ndata, function(x){ + dnorm(modVector, mu[x], stdev[x], log = TRUE) + }), na.rm=TRUE) +} + + + +maxLikelihoodAgromo <- function (results, imgPath, varName, ...) { + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibration.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibration.R new file mode 100644 index 0000000..d8f76fd --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/calibration.R @@ -0,0 +1,311 @@ +#' optiMuso +#' +#' This function calculates the -users specified- likelihood for random model input. +#' +#' @author Roland HOLLOS +#' @param measuredDataFile a +#' @param parameters b +#' @param sep c +#' @param startDate d +#' @param endDate e +#' @param formatString a +#' @param filterCol a +#' @param filterVal b +#' @param selVar c +#' @param outLoc c +#' @param pretag a +#' @param calPar a +#' @param skipSpinup a +#' @param iterations c +#' @param constrains d +#' @param likelihood d +#' @param settings e +#' @param leapYear b +#' @param plotName u +#' @importFrom ggplot2 ggplot aes_string geom_point ggsave +#' @importFrom magrittr '%>%' +#' @importFrom gridExtra grid.arrange +#' @export +optiMuso <- function(measuredData, parameters = NULL, startDate = NULL, + endDate = NULL, formatString = "%Y-%m-%d", + dataVar, outLoc = "./calib", + preTag = "cal-", settings = setupMuso(), + outVars = NULL, iterations = 30, + skipSpinup = TRUE, plotName = "calib.jpg", + modifyOriginal=TRUE, likelihood, uncertainity = NULL, + naVal = NULL, postProcString = NULL, w=NULL, lg=FALSE, parallel = TRUE) { + # Exanding likelihood + likelihoodFull <- as.list(rep(NA,length(dataVar))) + names(likelihoodFull) <- names(dataVar) + if(!missing(likelihood)) { + lapply(names(likelihood),function(x){ + likelihoodFull[[x]] <<- likelihood[[x]] + }) + } + defaultLikelihood <- which(is.na(likelihood)) + if(length(defaultLikelihood)>0){ + likelihoodFull[[defaultLikelihood]] <- (function(x, y){ + exp(-sqrt(mean((x-y)^2))) + }) + } + + mdata <- measuredData + if(is.null(parameters)){ + parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) { + stop("You need to specify a path for the parameters.csv, or a matrix.") + }) + } else { + if((!is.list(parameters)) & (!is.matrix(parameters))){ + parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){ + stop("Cannot find neither parameters file neither the parameters matrix") + }) + }} + + outLoc <- normalizePath(outLoc) + outLocPlain <- basename(outLoc) + currDir <- getwd() + + if(!dir.exists(outLoc)){ + dir.create(outLoc) + warning(paste(outLoc," is not exists, so it was created")) + } + + outLoc <- normalizePath(outLoc) + parameterNames <- parameters[,1] + pretag <- file.path(outLoc,preTag) + ##reading the original epc file at the specified + ## row numbers + print("optiMuso is randomizing the epc parameters now...",quote = FALSE) + if(iterations < 3000){ + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = 3000) + randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] + } else { + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations) + } + + origEpc <- readValuesFromFile(settings$epc[2],randVals[[1]]) + partialResult <- matrix(ncol=length(randVals[[1]])+2*length(dataVar)) + colN <- randVals[[1]] + colN[match(parameters[,2],randVals[[1]])] <- parameters[,1] + colnames(partialResult) <- c(colN,sprintf("%s_likelihood",names(dataVar)), + sprintf("%s_rmse",names(dataVar))) + numParameters <- length(colN) + partialResult[1:numParameters] <- origEpc + ## Prepare the preservedCalib matrix for the faster + ## run. + + pretag <- file.path(outLoc,preTag) + + musoCodeToIndex <- sapply(dataVar,function(musoCode){ + settings$dailyOutputTable[settings$dailyOutputTable$code == musoCode,"index"] + }) + resultRange <- (numParameters + 1):(ncol(partialResult)) + ## Creating function for generating separate + ## csv files for each run + + progBar <- txtProgressBar(1,iterations,style=3) + settings$iniInput[2] %>% + (function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>% + unlink + randValues <- randVals[[2]] + + settings$calibrationPar <- randVals[[1]] + + if(!is.null(naVal)){ + measuredData <- as.data.frame(measuredData) + measuredData[measuredData == naVal] <- NA + } + + alignIndexes <- alignMuso(settings,measuredData) + if(!is.null(uncertainity)){ + uncert <- measuredData[alignIndexes$meas,uncertainity] + } else { + uncert <- NULL + } + # browser() + # browser() + origModellOut <- calibMuso(settings=settings, silent=TRUE, skipSpinup = skipSpinup, postProcString=postProcString, modifyOriginal=modifyOriginal) + partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar, + mod=origModellOut, + mes=measuredData, + likelihoods=likelihood, + alignIndexes=alignIndexes, + musoCodeToIndex = musoCodeToIndex,uncert=uncert) + write.csv(x=origModellOut, file=paste0(pretag, 1, ".csv")) + print("Running the model with the random epc values...", quote = FALSE) + + # if(!is.null(postProcString)){ + # colNumb <- length(settings$dailyVarCodes) + 1 + # } + + write.csv(x=partialResult, file="preservedCalib.csv",row.names=FALSE) + for(i in 2:(iterations+1)){ + # browser() + tmp <- tryCatch(calibMuso(settings = settings, + parameters = randValues[(i-1),], + silent= TRUE, + skipSpinup = skipSpinup, modifyOriginal=modifyOriginal, postProcString = postProcString), error = function (e) NULL) + if(is.null(tmp)){ + partialResult[,resultRange] <- NA + } else { + partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar, + mod=tmp, + mes=measuredData, + likelihoods=likelihood, + alignIndexes=alignIndexes, + musoCodeToIndex = musoCodeToIndex, uncert = uncert) + } + + + partialResult[1:numParameters] <- randValues[(i-1),] + write.table(x=partialResult, file="preservedCalib.csv", append=TRUE, row.names=FALSE, + sep=",", col.names=FALSE) + write.csv(x=tmp, file=paste0(pretag, (i+1),".csv")) + setTxtProgressBar(progBar,i) + } + + musoGlue("preservedCalib.csv",w=w, lg = lg) + +} + + + + +alignMuso <- function (settings,measuredData) { + # Have to fix for other starting points also + modelDates <- seq(from= as.Date(sprintf("%s-01-01",settings$startYear)), + by="days", + to=as.Date(sprintf("%s-12-31",settings$startYear+settings$numYears-1))) + modelDates <- grep("-02-29",modelDates,invert=TRUE, value=TRUE) + + measuredDates <- apply(measuredData,1,function(xrow){ + sprintf("%s-%s-%s",xrow[1],xrow[2],xrow[3]) + }) + + modIndex <- match(as.Date(measuredDates), as.Date(modelDates)) + measIndex <- which(!is.na(modIndex)) + modIndex <- modIndex[!is.na(modIndex)] + cbind.data.frame(model=modIndex,meas=measIndex) +} + +# calcLikelihoodsAndRMSE <- function(dataVar, mod, mes, likelihoods, alignIndexes, musoCodeToIndex, uncert){ +# +# likelihoodRMSE <- sapply(names(dataVar),function(key){ +# # browser() +# modelled <- mod[alignIndexes$mod,musoCodeToIndex[key]] +# measured <- mes[alignIndexes$meas,key] +# modelled <- modelled[!is.na(measured)] +# # uncert <- uncert[!is.na(measured)] +# measured <- measured[!is.na(measured)] +# res <- c(likelihoods[[key]](modelled, measured, uncert), +# sqrt(mean((modelled-measured)^2)) +# ) +# res +# }) +# names(likelihoodRMSE) <- c(sprintf("%s_likelihood",dataVar), sprintf("%s_rmse",dataVar)) +# +# return(c(likelihoodRMSE[1,],likelihoodRMSE[2,])) +# } + +#' musoGlue +#' +#' This function calculates the -users specified- likelihood for random model input. +#' +#' @author Roland HOLLOS +#' @param plotName u +#' @export +musoGlue <- function(presCalFile, w, delta = 0.17, settings=setupMuso(), parameters=read.csv("parameters.csv", + stringsAsFactors=FALSE), lg=FALSE){ + if(is.data.frame(presCalFile)){ + preservedCalib <- presCalFile + } else { + preservedCalib <- read.csv(presCalFile) + } + paramIndex <- parameters[(match(colnames(preservedCalib),parameters[,1])),2] + paramIndex <- paramIndex[!is.na(paramIndex)] + paramIndex <- c(paramIndex, + as.numeric(gsub("X","", + grep("X[0-9]{1,}", + colnames(preservedCalib),value=TRUE)))) + preservedCalib <- preservedCalib[-1,] #original + + likeIndexes <- grep("likelihood",colnames(preservedCalib)) + if(!is.null(w)){ + forCombine<- sapply(names(w),function(n){ + grep(sprintf("%s_likelihood",n),colnames(preservedCalib)) + }) + preservedCalib[["combined"]] <- apply(as.data.frame(Map(function(x,y){ + toNormalize <- preservedCalib[,y] + toNormalize <- toNormalize / sqrt(sum(x^2)) + toNormalize * x + + },w,forCombine)), 1, sum) + } else { + preservedCalib[["combined"]] <- preservedCalib[,grep("likelihood",colnames(preservedCalib),value=TRUE)] + } + + parameterIndexes <- 1:(min(likeIndexes)-1) + preservedCalib <- preservedCalib[!is.na(preservedCalib$combined),] + unfilteredLikelihood <- preservedCalib$combined + top5points <- preservedCalib$combined>quantile(preservedCalib$combined,0.95) + preservedCalibtop5 <- preservedCalib[,] + optRanges <-t(apply(preservedCalibtop5,2,function(x) quantile(x,c(0.05,0.5,0.95)))) + pdf("dotplot.pdf") + if(lg){ + plot(Reduce(min, -(unfilteredLikelihood), accumulate=TRUE),type="l", ylab="-log(likelihood)",xlab="iterations") + } else { + plot(Reduce(min, -log(unfilteredLikelihood), accumulate=TRUE),type="l", ylab="-log(likelihood)",xlab="iterations") + } + pari <- par(mfrow=c(1,2)) + for(i in seq_along(colnames(preservedCalib)[parameterIndexes])){ + plot(preservedCalib[,i],preservedCalib[,"combined"],pch=19,cex=.1, ylab="likelihood", + main = colnames(preservedCalib)[i], xlab="") + plot(preservedCalibtop5[,i],preservedCalibtop5[,"combined"],pch=19,cex=.1, ylab="likelihood", + main = paste0(colnames(preservedCalibtop5)[i]," (behav.)"), xlab="") + abline(v=optRanges[i,1],col="blue") + abline(v=optRanges[i,2],col="green") + abline(v=optRanges[i,3],col="red") + + } + + par(pari) + dev.off() + maxParValues <- preservedCalibtop5[which.max(preservedCalibtop5$combined),] + maxParIndexes <- paramIndex + write.csv(cbind.data.frame(calibrationPar=maxParValues,parameters=maxParIndexes),"maxLikelihood.csv") + write.csv(optRanges,"optRanges.csv") + # browser() + # There are some serious problems with this implementation. The uncertainity bouns are not for the parameters, but for the output values. The median is pointwise median for all simulation. + # And the 95 and 5 percentile also. + # dataVec <- preservedCalibtop5$combined + # closestToMedian <- function (dataVec) { + # match(sort(dataVec)[min(which(sort(dataVec)>=median(dataVec)))], dataVec) + # } + # + # while(is.null(optimalEpc)){ + # match(quantile(preservedCalibtop5$combined,0.5), preservedCalibtop5$combined) + # optInterval <-t(apply(preservedCalibtop5,2,function(x) quantile(x,c(0.5-delta,0.5+delta)))) + # optParamRange <- cbind.data.frame(rownames(optInterval)[parameterIndexes],as.numeric(paramIndex),optInterval[parameterIndexes,]) + # optimalEpc <- tryCatch(musoRand(optParamRange,iterations = 2), error=function(e){NULL}) + # delta <- delta*1.05 + # if(delta > 0.5){ + # delta <- 0.5 + # } + # if((delta == 0.5) && is.null(optimalEpc)){ + # stop("cannot find optimal value in the given range") + # } + # } + # print("getOptim") + # optimalEpc[[2]] <- optimalEpc[[2]][1,] + # write.csv(as.data.frame(optimalEpc),"epcOptim.csv") + # print(head(optRanges,n=-2)) + # calibMuso(calibrationPar=optimalEpc[[1]],parameters=optimalEpc[[2]]) + # file.copy(settings$epcInput[2],"epcOptim.epc") +} + +generateOptEpc <- function(optRanges,delta, maxLikelihood=FALSE){ + if(missing(delta)){ + + } + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/changeMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/changeMuso.R new file mode 100644 index 0000000..9a34a0c --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/changeMuso.R @@ -0,0 +1,33 @@ +#' changemulline +#' +#' The function uses the previous changspecline function to operate. +#' +#' @author Roland Hollos +#' @export + +changemulline <- function(filePaths, calibrationPar, contents, src, outFiles=filePaths){ + # browser() + if(is.null(src)){ + src <- filePaths + } + + fileStringVector <- readLines(src) + Map(function(index, content){ + fileStringVector <<- changeByIndex(index, content, fileStringVector) + + }, calibrationPar, contents) + writeLines(fileStringVector, outFiles) + +} + +changeNth <- function (string,place,replacement) { + trimws(gsub(sprintf("^((.*?\\s+){%s})(.*?\\s+)", place), sprintf("\\1%s ", replacement), paste0(string," "), perl=TRUE), + which="right") +} + +changeByIndex <- function (rowIndex, parameter, fileStringVector){ + h <- round((rowIndex*100) %% 10) + i <- as.integer(rowIndex) + fileStringVector[i] <- changeNth(fileStringVector[i], h, parameter) + fileStringVector +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/checkMeteoBGC.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/checkMeteoBGC.R new file mode 100644 index 0000000..1d4c303 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/checkMeteoBGC.R @@ -0,0 +1,103 @@ +#' checkMeteoBGC +#' +#' This function calculates the daily and yearly statistics for a given meteorology file (mtc43). +#' +#' @author Erzsebet Kristof +#' @param settings The output of setupMuso +#' @param metFileName The name of the meteorology file (mtc43). +#' @param skip Number of header lines in meteorology file. +#' @param numericReport If numericReport is set to FALSE, the function returns with a text report. If numericReport is set to TRUE, the function returns with a numeric report. +#' @param type meteorology for spinup or normal run +#' @return It depends on the numericReport parameter. The function returns with a text report, or with a numeric report. +#' @export + +checkMeteoBGC <- function(settings=NULL, skip = 4, numericReport = FALSE,type="normal"){ + + if(is.null(settings)){ + settings <- setupMuso() + } + + metFileName <- settings$metInput[type] + + intMin <- function(x){ + round(min(x,na.rm = TRUE), digits = 1) + } + + intMax <- function(x){ + round(max(x,na.rm = TRUE), digits = 1) + } + + sradAvgShortestDay <- function(x,y){ + round(mean(x[na.omit(y) == min(y, na.rm=TRUE)]), digits=1) + + } + sradAvgLongestDay <- function(x,y){ + round(mean(x[na.omit(y) == max(y, na.rm=TRUE)]), digits=1) + + } + metTable <- tryCatch(read.table(metFileName, skip = skip), error = function(e){ + stop(sprintf("Cannot read or find meteorology file: %s", metFileName)) + }) + + yearlyPrcpSum <- tapply(metTable$V6,list(metTable$V1), sum) + yearlyTempAvg <- tapply(metTable$V5,list(metTable$V1), mean) + yearlyVpdAvg <- tapply(metTable$V7,list(metTable$V1), mean) + + + timeFrame <- range(metTable[,1]) + if(!numericReport){ + cat("Daily and yearly statistics of meteorological data for the time period of", + timeFrame[1], "-", timeFrame[2], ":\n + + Precipitation data: + Minimum and maximum of daily sums:", + intMin(metTable$V6), "cm and", intMax(metTable$V6), "cm. + Minimum and maximum of yearly sums:", + intMin(yearlyPrcpSum), "cm and", intMax(yearlyPrcpSum), "cm.\n + + Temperature data: + Lowest and highest daily temperatures (Tmin and Tmax):", + intMin(metTable$V4), "deg C and", intMax(metTable$V3), "deg C. + Minimum and maximum of yearly averages (based on Tday):", + intMin(yearlyTempAvg), "deg C and", intMax(yearlyTempAvg), "deg C.\n + + Solar radiation data: + Minimum and maximum of daily values:", + intMin(metTable$V8), "W m-2 and", intMax(metTable$V8), "W m-2. + Averages of the shortest and longest days:", + sradAvgShortestDay(metTable$V8, metTable$V9),"W m-2 and", + sradAvgLongestDay(metTable$V8, metTable$V9), "W m-2.\n + + Vapour pressure deficit data: + Minimum and maximum of daily values:", + intMin(metTable$V7), "Pa and", intMax(metTable$V7), "Pa. + Minimum and maximum of yearly averages:", + intMin(yearlyVpdAvg), "Pa and", intMax(yearlyVpdAvg), "Pa.\n") + + } else { + report <- list() + cat("Numeric report:\n") + report["Precipitation"] <- list(data.frame(minimum = c(daily = intMin(metTable$V6), + yearly = intMin(yearlyPrcpSum)), + maximum = c(daily = intMax(metTable$V6), + yearly = intMax(yearlyPrcpSum)))) + + report["Temperature"] <- list(data.frame(minimum = c(daily = intMin(metTable$V4), + yearly = intMin(yearlyTempAvg)), + maximum = c(daily = intMax(metTable$V3), + yearly = intMax(yearlyTempAvg)))) + + report["Solar radiation"] <- list(data.frame(minimum = c(daily = intMin(metTable$V8), + shortest_longest_day = sradAvgShortestDay(metTable$V8, metTable$V9)), + maximum = c(daily = intMax(metTable$V8), + shortest_longest_day = sradAvgLongestDay(metTable$V8, metTable$V9)))) + + report["Vapour pressure deficit"] <- list(data.frame(minimum = c(daily = intMin(metTable$V7), + yearly = intMin(yearlyVpdAvg)), + maximum = c(daily = intMax(metTable$V7), + yearly = intMax(yearlyVpdAvg)))) + + return(report) + } + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/cleanup.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/cleanup.R new file mode 100644 index 0000000..b34edbf --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/cleanup.R @@ -0,0 +1,55 @@ +#'cleanupMuso +#' +#' cleanupMuso can erase all of the unnecessary log and output files. +#' +#' @author Roland HOLLOS +#' @param location This is the place (directory) where your output files are located. +#' @param simplicity TRUE or FALSE. If TRUE cleanupMuso will erase only the log files from the location +#' @param deep If it is TRUE, it will delete every files from the subdirectories also +#' @usage cleanupMuso(location=NULL, simplicity=TRUE,deep=FALSE) +#' @export + + +cleanupMuso <- function(location=NULL, simplicity=TRUE,deep=FALSE){ + + if(is.null(location)){ + location<-"./" + } + + logDir<-file.path(location,"LOG") + errDir<-file.path(location,"ERROR") + epcDir<-file.path(location,"EPCS") + wroDir<-file.path(location,"WRONGEPC") + + if(deep){ + + if(dir.exists(logDir)){ + file.remove( + list.files(logDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE) + ) + } + + if(dir.exists(errDir)){ + file.remove( + list.files(errDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE)) + } + + if(dir.exists(epcDir)){ + file.remove( + list.files(epcDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE)) + } + + if(dir.exists(wroDir)){ + file.remove( + list.files(wroDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE)) + } + + file.remove(list.files(location, pattern="(out$)|(endpoint$)|(log$)",full.names=TRUE))} + + + if(!simplicity){ + file.remove(list.files(location, pattern="(out$)|(endpoint$)|(log$)",full.names=TRUE)) + } else { + file.remove(list.files(location, pattern="log$",full.names=TRUE))} + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/debugMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/debugMuso.R new file mode 100644 index 0000000..0d6c473 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/debugMuso.R @@ -0,0 +1,68 @@ +#'rungetMuso +#' +#' This function runs the Biome-BGCMuSo model and reads its outputfile in a well structured way. +#' +#' @author Roland Hollos +#' @keywords internal +#' +## degubMuso <- function(inputloc,outputloc,debugging,errorsign,){ + + +## if((debugging=="stamplog")|(debugging==TRUE)){#If debugging option turned on +## ##If log or ERROR directory does not exists create it! +## dirName<-paste(inputloc,"LOG",sep="") +## dirERROR<-paste(inputloc,"ERROR",sep="") + +## if(!dir.exists(dirName)){ +## dir.create(dirName) +## } + +## if(!dir.exists(dirERROR)){ +## dir.create(dirERROR) +## } +## } + +## if(debugging=="stamplog"){ +## stampnum<-stamp(dirName) +## if(inputloc==outputloc){ +## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep=""), to=paste(dirName, "/",(stampnum+1),"-",x,sep=""))) + +## } else { +## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep="/"), to=paste(dirName, "/",(stampnum+1),"-",x,sep=""))) +## } + +## if(errorsign==1){ +## lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",(stampnum+1),"-",x,sep=""), to=dirERROR ))} + +## } else { if(debugging){ +## if(is.null(logfilename)){ + +## if(inputloc==outputloc){ +## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep=""), to=paste(dirName,"/", x, sep=""))) +## } else { +## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep="/"), to=paste(dirName,"/", x, sep=""))) +## } + +## if(errorsign==1){ +## lapply( logfiles, function (x) file.rename(from=paste(dirName,"/", x, sep=""), to=dirERROR)) +## } + +## } else { + +## if(inputloc==outputloc){#These are very ugly solutions for a string problem: inputloc: "./", if outputloc equalent of inputloc, it ends with "/", the string manipulation can not handle this. The better solution is easy, but I dont have enough time(Roland Hollo's) +## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep=""), to=paste(dirName, "/",logfilename,"-",x,sep=""))) +## } else { +## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep="/"), to=paste(dirName, "/",logfilename,"-",x,sep=""))) +## } + +## if(errorsign==1){ +## lapply( logfiles, function (x) file.rename(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR)) +## } +## } + +## }} + + +## return(errorsign) + +## } diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/flat.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/flat.R new file mode 100644 index 0000000..0f5fec1 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/flat.R @@ -0,0 +1,267 @@ +getQueue <- function(depTree=options("RMuso_depTree")[[1]], startPoint){ + + if(length(startPoint) == 0){ + return(c()) + } + parent <- depTree[depTree[,"name"] == startPoint,"parent"] + c(getQueue(depTree, depTree[depTree[,"child"] == depTree[depTree[,"name"] == startPoint,"parent"],"name"]),parent) +} + +isRelative <- function(path){ + substr(path,1,1) != '/' +} + +#' getFilePath +#' +#' This function reads the ini file and for a chosen fileType it gives you the filePath +#' @param iniName The name of the ini file +#' @param filetype The type of the choosen file. For options see options("RMuso_depTree")[[1]]$name +#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]] +#' @export + +getFilePath <- function(iniName, fileType, execPath = "./", depTree=options("RMuso_depTree")[[1]]){ + if(!file.exists(iniName) || dir.exists(iniName)){ + stop(sprintf("Cannot find iniFile: %s", iniName)) + } + + startPoint <- fileType + startRow <- depTree[depTree[,"name"] == startPoint,] + startExt <- startRow$child + + parentFile <- Reduce(function(x,y){ + tryCatch(file.path(execPath,gsub(sprintf("\\.%s.*",y), + sprintf("\\.%s",y), + grep(sprintf("\\.%s",y),readLines(x),value=TRUE,perl=TRUE))), error = function(e){ + stop(sprintf("Cannot find %s",x)) + }) + }, + getQueue(depTree,startPoint)[-1], + init=iniName) + if(startRow$mod > 0){ + tryCatch( + gsub(sprintf("\\.%s.*", startExt), + sprintf("\\.%s", startExt), + grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE,perl=TRUE))[startRow$mod] + ,error = function(e){stop(sprintf("Cannot read %s",parentFile))}) + } else { + res <- tryCatch( + gsub(sprintf("\\.%s.*", startExt), + sprintf("\\.%s",startExt), + grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE, perl=TRUE)) + ,error = function(e){stop(sprintf("Cannot read %s", parentFile))}) + unique(gsub(".*\\t","",res)) + } +} + + + +#' getFilesFromIni +#' +#' This function reads the ini file and gives yout back the path of all file involved in model run +#' @param iniName The name of the ini file +#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]] +#' @export + +getFilesFromIni <- function(iniName, execPath = "./", depTree=options("RMuso_depTree")[[1]]){ + res <- lapply(depTree$name,function(x){ + tryCatch(getFilePath(iniName,x,execPath,depTree), error = function(e){ + return(NA); + }) + }) + names(res) <- depTree$name + res +} + +#' flatMuso +#' +#' This function reads the ini file and creates a directory (named after the directory argument) with all the files the modell uses with this file. the directory will be flat. +#' @param iniName The name of the ini file +#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]] +#' @param directory The destination directory for flattening. At default it will be flatdir +#' @export + +flatMuso <- function(iniName, execPath="./", depTree=options("RMuso_depTree")[[1]], directory="flatdir", d=TRUE,outE=TRUE){ + dir.create(directory, showWarnings=FALSE, recursive = TRUE) + files <- getFilesFromIni(iniName,execPath,depTree) + files <- sapply(unlist(files)[!is.na(files)], function(x){ifelse(isRelative(x),file.path(execPath,x),x)}) + file.copy(unlist(files), directory, overwrite=TRUE) + file.copy(iniName, directory, overwrite=TRUE) + + filesByName <- getFilesFromIni(iniName, execPath, depTree) + for(i in seq_along(filesByName)){ + fileLines <- readLines(file.path(directory,list.files(directory, pattern = sprintf("*\\.%s", depTree$parent[i])))[1]) + + sapply(filesByName[[i]],function(origname){ + if(!is.na(origname)){ + fileLines <<- gsub(origname, basename(origname), fileLines, fixed=TRUE) + } + }) + + if(!is.na(filesByName[[i]][1])){ + writeLines(fileLines, file.path(directory,list.files(directory, pattern = sprintf("*\\.%s", depTree$parent[i])))[1]) + } + + } + + iniLines <- readLines(file.path(directory, basename(iniName))) + outPlace <- grep("OUTPUT_CONTROL", iniLines, perl=TRUE)+1 + if(outE){ + iniLines[outPlace] <- tools::file_path_sans_ext(basename(iniName)) + } else { + iniLines[outPlace] <- basename(strsplit(iniLines[outPlace], split = "\\s+")[[1]][1]) + } + if(d){ + iniLines[outPlace + 1] <- 1 + } + writeLines(iniLines, file.path(directory, basename(iniName))) +} + +#' checkFileSystem +#' +#' This function checks the MuSo file system, if it is correct +#' @param iniName The name of the ini file +#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]] +#' @export + +checkFileSystem <- function(iniName,root = ".", depTree = options("RMuso_depTree")[[1]]){ + recoverAfterEval({ + setwd(root) + fileNames <- getFilesFromIni(iniName, depTree) + if(is.na(fileNames$management)){ + fileNames[getLeafs("management")] <- NA + } + fileNames <- fileNames[!is.na(fileNames)] + errorFiles <- fileNames[!file.exists(unlist(fileNames))] + }) + return(errorFiles) +} + +recoverAfterEval <- function(expr){ + wd <- getwd() + tryCatch({ + eval(expr) + setwd(wd) + }, error=function(e){ + setwd(wd) + stop(e) + }) +} + +getLeafs <- function(name, depTree=options("RMuso_depTree")[[1]]){ + + if(length(name) == 0){ + return(NULL) + } + + if(name[1] == "ini"){ + return(getLeafs(depTree$name)) + } + + pname <- depTree[ depTree[,"name"] == name[1] , "child"] + children <- depTree[depTree[,"parent"] == pname,"child"] + + if(length(children)==0){ + if(length(name) == 1){ + return(NULL) + } else{ + apname <- depTree[ depTree[,"name"] == name[2] , "child"] + achildren <- depTree[depTree[,"parent"] == apname,"child"] + if(length(achildren)!=0){ + return(c(name[1],name[2],getLeafs(name[-1]))) + } else{ + return(c(name[1], getLeafs(name[-1]))) + } + + } + } + + childrenLogic <-depTree[,"child"] %in% children + parentLogic <- depTree[,"parent"] ==pname + res <- depTree[childrenLogic & parentLogic, "name"] + getChildelem <- depTree[depTree[,"child"] == intersect(depTree[,"parent"], children), "name"] + unique(c(res,getLeafs(getChildelem))) +} + +getParent <- function (name, depTree=options("RMuso_depTree")[[1]]) { + parentExt <- depTree[depTree$name == name,"parent"] + # if(length(parentExt) == 0){ + # browser() + # } + if(parentExt == "ini"){ + return("iniFile") + } + + depTree[depTree[,"child"] == parentExt,"name"] +} + + + +getFilePath2 <- function(iniName, fileType, depTree=options("RMuso_depTree")[[1]]){ + if(!file.exists(iniName) || dir.exists(iniName)){ + stop(sprintf("Cannot find iniFile: %s", iniName)) + } + + startPoint <- fileType + startRow <- depTree[depTree[,"name"] == startPoint,] + startExt <- startRow$child + + parentFile <- Reduce(function(x,y){ + tryCatch(gsub(sprintf("\\.%s.*",y), + sprintf("\\.%s",y), + grep(sprintf("\\.%s",y),readLines(x),value=TRUE,perl=TRUE)), error = function(e){ + stop(sprintf("Cannot find %s",x)) + }) + }, + getQueue(depTree,startPoint)[-1], + init=iniName) + res <- list() + res["parent"] <- parentFile + if(startRow$mod > 0){ + res["children"] <- tryCatch( + gsub(sprintf("\\.%s.*", startExt), + sprintf("\\.%s", startExt), + grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE,perl=TRUE))[startRow$mod] + ,error = function(e){stop(sprintf("Cannot read %s",parentFile))}) + + } else { + rows <- tryCatch( + gsub(sprintf("\\.%s.*", startExt), + sprintf("\\.%s",startExt), + grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE, perl=TRUE)) + + ,error = function(e){stop(sprintf("Cannot read %s", parentFile))}) + unique(gsub(".*\\t","",res)) + res["children"] <- unique(gsub(".*\\s+(.*\\.epc)","\\1",rows)) + } + res +} + +getFilesFromIni2 <- function(iniName, depTree=options("RMuso_depTree")[[1]]){ + res <- lapply(depTree$name,function(x){ + tryCatch(getFilePath2(iniName,x,depTree), error = function(e){ + return(NA); + }) + }) + names(res) <- depTree$name + res +} + +checkFileSystemForNotif <- function(iniName,root = ".", depTree = options("RMuso_depTree")[[1]]){ + recoverAfterEval({ + setwd(root) + fileNames <- suppressWarnings(getFilesFromIni2(iniName, depTree)) + if(is.atomic(fileNames$management)){ + fileNames[getLeafs("management")] <- NA + } + + hasparent <- sapply(fileNames, function(x){ + !is.atomic(x) + }) + notNA <- ! sapply(fileNames[hasparent], function(x) {is.na(x$children)}) + errorIndex <- ! sapply(fileNames[hasparent & notNA], function(x) file.exists(x$children)) + + }) + return(fileNames[hasparent & notNA][errorIndex]) +} + + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/genEpc.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/genEpc.R new file mode 100644 index 0000000..0543f8e --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/genEpc.R @@ -0,0 +1,35 @@ +#' randEpc +#' +#' randEpc is a random epc creator based on musoMonte +#' @author Roland HOLLOS +#' @param parameterFile parameters.csv file location +#' @param location output location directory +#' @param sourceEpc the original epc file-the template +#' @param iteration the number of iterations +#' @export + +randEpc <- function(parameterFile = "parameters.csv", location = "./epcDir", + sourceEpc = "maize.epc", iterations = 1000, constrains = NULL){ + + if(!dir.exists(location)){ + dir.create(location) + } + sourceEpc <- normalizePath(sourceEpc) + currDir <- getwd() + parameters <- read.csv(parameterFile) + + if(iterations < 3000){ + randVals <- musoRand(parameters = parameters,constrains = constrains, iterations = 3000) + randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] + } else { + randVals <- musoRand(parameters = parameters,constrains = constrains, iterations = iterations) + } + file.copy(sourceEpc,location,overwrite = TRUE) + setwd(location) + for(i in seq(iterations)){ + epcOut <- gsub("\\.",paste0("-",i,"."),basename(sourceEpc)) + changemulline(filePaths = basename(sourceEpc), calibrationPar = randVals[[1]], + contents = randVals[[2]][i,],fileOut = epcOut, fileToChange = "epc") + } + setwd(currDir) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/getOutPutList.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/getOutPutList.R new file mode 100644 index 0000000..e788027 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/getOutPutList.R @@ -0,0 +1,33 @@ +#' getDailyOutputList +#' +#' bla bla +#' @param settings bla +#' @export + + +getDailyOutputList <- function(settings=NULL){ + if(is.null(settings)){ + settings <- setupMuso() + } + varTable <- getOption("RMuso_varTable")$'6' + toPrint <- varTable[match(as.numeric(settings$dailyVarCodes),varTable[,1]),] + toPrint <- cbind.data.frame(index=1:nrow(toPrint),toPrint) + print(toPrint, row.names=FALSE) +} + +#' getAnnualOutputList +#' +#' bla bla +#' @param settings bla +#' @export + + +getAnnualOutputList <- function(settings=NULL){ + if(is.null(settings)){ + settings<- setupMuso() + } + varTable <- getOption("RMuso_varTable")$'6' + toPrint <- varTable[which(varTable$codes %in% as.numeric(settings$annualVarCodes)),] + toPrint <- cbind.data.frame(index=1:nrow(toPrint),toPrint) + print(toPrint, row.names=FALSE) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/getOutput.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/getOutput.R new file mode 100644 index 0000000..ee24515 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/getOutput.R @@ -0,0 +1,44 @@ +getthewholedata<-function(settings){ + f1<-settings$ininput[2] + filename = paste(settings$inputloc,settings$outputname,"_ann.txt",sep="") + alloutput<-read.table(filename,skip=22, header = FALSE) + return(alloutput) +} + +getthespecdata<-function(settings,colnumbers){ + filename<-paste(settings$inputloc,settings$outputname,"_ann.txt",sep="") + specoutput<-read.table(filename,skip=22, header = FALSE)[,colnumbers] + return(specoutput) +} + +getdailyout<-function(settings){ + binaryname<-paste0(settings$outputLoc,"/",settings$outputNames[2],".dayout") + d<-file(binaryname,"rb") + ##leapyear is not implemented yet in this function + dayoutput<-matrix(readBin(d,"double",size=8,n=(settings$numData[1])),(settings$numYears*365),byrow=TRUE) + close(d) + return(dayoutput) +} + +getmonthlyout<-function(settings){ + binaryname<-paste(settings$inputloc,settings$outputname,".monavgout",sep="") + d<-file(binaryname,"rb") + monoutput<-matrix(readBin(d,"double",size=4,n=(settings$numdata[2])),(settings$numyears*12),byrow=TRUE) + close(d) + return(monoutput) +} + +getyearlyout<-function(settings){ + binaryname<-paste0(settings$inputLoc,"/",settings$outputName[2],".annout") + ## d<-file(binaryname,"rb") + ## yearoutput<-matrix(readBin(d,"double",size=4,n=(settings$numData[3])),(settings$numYears),byrow=TRUE) + ## close(d) + ## return(yearoutput) + outPut <- read.table(binaryname,skip = 1) + colnames(outPut) <- c("year", paste0("var_",settings$annualVarCodes)) + outPut +} + + + + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/multiSite.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/multiSite.R new file mode 100644 index 0000000..5627021 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/multiSite.R @@ -0,0 +1,640 @@ +`%between%` <- function(x, y){ + (x <= y[2]) & (x >= y[1]) +} + +annualAggregate <- function(x, aggFun){ + tapply(x, rep(1:(length(x)/365), each=365), aggFun) +} + +SELECT <- function(x, selectPart){ + if(!is.function(selectPart)){ + index <- as.numeric(selectPart) + tapply(x,rep(1:(length(x)/365),each=365), function(y){ + y[index] + }) + } else { + tapply(x,rep(1:(length(x)/365),each=365), selectPart) + } +} + +bVectToInt<- function(bin_vector){ + bin_vector <- rev(as.integer(bin_vector)) + packBits(as.raw(c(bin_vector,numeric(32-length(bin_vector)))),"integer") +} + +constMatToDec <- function(constRes){ + tab <- table(apply(constRes,2,function(x){paste(x,collapse=" ")})) + bitvect <- strsplit(names(tab[which.max(tab)]),split=" ")[[1]] + bVectToInt(bitvect) +} + +compose <- function(expr){ + splt <- strsplit(expr,split="\\|")[[1]] + lhs <- splt[1] + rhs <- splt[2] + penv <- parent.frame() + lhsv <- eval(parse(text=lhs),envir=penv) + penv[["lhsv"]] <- lhsv + place <- regexpr("\\.[^0-9a-zA-Z]",rhs) + + if(place != -1){ + finalExpression <- paste0(substr(rhs, 1, place -1),"lhsv", + substr(rhs, place + 1, nchar(rhs))) + } else { + finalExpression <- paste0(rhs,"(lhsv)") + } + eval(parse(text=finalExpression),envir=penv) +} + +compoVect <- function(mod, constrTable, fileToWrite = "const_results.data"){ + with(as.data.frame(mod), { + nexpr <- nrow(constrTable) + filtered <- numeric(nexpr) + vali <- numeric(nexpr) + for(i in 1:nexpr){ + val <- compose(constrTable[i,1]) + filtered[i] <- (val <= constrTable[i,3]) && + (val >= constrTable[i,2]) + vali[i] <- val + } + + write(paste(vali,collapse=","), fileToWrite, append=TRUE) + filtered + }) +} + +modCont <- function(expr, datf, interval, dumping_factor){ + tryCatch({ + if((with(datf,eval(parse(text=expr))) %between% interval)){ + return(NA) + } else{ + return(dumping_factor) + } + }, + error = function(e){ + stop(sprintf("Cannot find the variable names in the dataframe, detail:\n%s", + e)) + }) +} + +copyToThreadDirs2 <- function(iniSource, thread_prefix = "thread", numCores, execPath="./", + + executable = ifelse(Sys.info()[1]=="Linux", file.path(execPath, "muso"), + file.path(execPath,"muso.exe"))){ + sapply(iniSource, function(x){ + flatMuso(x, execPath, + directory=file.path("tmp", paste0(thread_prefix,"_1"),tools::file_path_sans_ext(basename(x)),""), d =TRUE) + file.copy(executable, + file.path("tmp", paste0(thread_prefix,"_1"),tools::file_path_sans_ext(basename(x)))) + tryCatch(file.copy(file.path(execPath,"cygwin1.dll"), + file.path("tmp", paste0(thread_prefix,"_1"),tools::file_path_sans_ext(basename(x)))), + error = function(e){"If you are in Windows..."}) + }) + sapply(2:numCores,function(thread){ + dir.create(sprintf("tmp/%s_%s",thread_prefix,thread), showWarnings=FALSE) + file.copy(list.files(sprintf("tmp/%s_1",thread_prefix),full.names = TRUE),sprintf("tmp/%s_%s/",thread_prefix,thread), + recursive=TRUE, overwrite = TRUE) + }) + +} + + +#' multiSiteCalib +#' +#' This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution of the random parameters on convex polytopes. +#' @author Roland HOLLOS +#' @importFrom future future +#' @importFrom rpart rpart rpart.control +#' @importFrom rpart.plot rpart.plot +#' @param measuremets The table which contains the measurements +#' @param calTable A dataframe which contantains the ini file locations and the domains they belongs to +#' @param parameters A dataframe with the name, the minimum, and the maximum value for the parameters used in MonteCarlo experiment +#' @param dataVar A named vector where the elements are the MuSo variable codes and the names are the same as provided in measurements and likelihood +#' @param iterations The number of MonteCarlo experiments to be executed +#' @param burnin Currently not used, altought it is the length of burnin period of the MCMC sampling used to generate random parameters +#' @param likelihood A list of likelihood functions which names are linked to dataVar +#' @param execPath If you are running the calibration from different location than the MuSo executable, you have to provide the path +#' @param thread_prefix The prefix of thread directory names in the tmp directory created during the calibrational process +#' @param numCores The number of processes used during the calibration. At default it uses one less than the number of threads available +#' @param pb The progress bar function. If you use (web-)GUI you can provide a different function +#' @param pbUpdate The update function for pb (progress bar) +#' @param copyThread A boolean, recreate tmp directory for calibration or not (case of repeating the calibration) +#' @param contsraints A dataframe containing the constraints logic the minimum and a maximum value for the calibration. +#' @param th A trashold value for multisite calibration. What percentage of the site should satisfy the constraints. +#' @param treeControl A list which controls (maximal complexity, maximal depth) the details of the decession tree making. +#' @export +multiSiteCalib <- function(measurements, + calTable, + parameters, + dataVar, + iterations = 100, + burnin =ifelse(iterations < 3000, 3000, NULL), + likelihood, + execPath, + thread_prefix="thread", + numCores = (parallel::detectCores()-1), + pb = txtProgressBar(min=0, max=iterations, style=3), + pbUpdate = setTxtProgressBar, + copyThread = TRUE, + constraints=NULL, th = 10, treeControl=rpart.control() + ){ + future::plan(future::multisession) + # file.remove(list.files(path = "tmp", pattern="progress.txt", recursive = TRUE, full.names=TRUE)) + # file.remove(list.files(path = "tmp", pattern="preservedCalib.csv", recursive = TRUE, full.names=TRUE)) + + # ____ _ _ _ _ + # / ___|_ __ ___ __ _| |_ ___ | |_| |__ _ __ ___ __ _ __| |___ + # | | | '__/ _ \/ _` | __/ _ \ | __| '_ \| '__/ _ \/ _` |/ _` / __| + # | |___| | | __/ (_| | || __/ | |_| | | | | | __/ (_| | (_| \__ \ + # \____|_| \___|\__,_|\__\___| \__|_| |_|_| \___|\__,_|\__,_|___/ + if(copyThread){ + unlink("tmp",recursive=TRUE) + copyToThreadDirs2(iniSource=calTable$site_id, numCores=numCores, execPath=execPath) + } else { + print("copy skipped") + file.remove(file.path(list.dirs("tmp",recursive=FALSE),"progress.txt")) + file.remove(file.path(list.dirs("tmp", recursive=FALSE), "const_results.data")) + } + + # ____ _ _ _ + # | _ \ _ _ _ __ | |_| |__ _ __ ___ __ _ __| |___ + # | |_) | | | | '_ \ | __| '_ \| '__/ _ \/ _` |/ _` / __| + # | _ <| |_| | | | | | |_| | | | | | __/ (_| | (_| \__ \ + # |_| \_\\__,_|_| |_| \__|_| |_|_| \___|\__,_|\__,_|___/ + + threadCount <- distributeCores(iterations, numCores) + fut <- lapply(1:numCores, function(i) { + future({ + tryCatch( + + { + result <- multiSiteThread(measuredData = measurements, parameters = parameters, calTable=calTable, + dataVar = dataVar, iterations = threadCount[i], + likelihood = likelihood, threadNumber= i, constraints=constraints, th=th) + # setwd("../../") + # return(result) + } + + , error = function(e){ + # browser() + sink("error.txt") + print(e) + sink() + saveRDS(e,"error.RDS") + writeLines(as.character(iterations),"progress.txt") + }) + }) + }) + + # _ _ + # __ ____ _| |_ ___| |__ _ __ _ __ ___ __ _ _ __ ___ ___ ___ + # \ \ /\ / / _` | __/ __| '_ \ | '_ \| '__/ _ \ / _` | '__/ _ \/ __/ __| + # \ V V / (_| | || (__| | | | | |_) | | | (_) | (_| | | | __/\__ \__ \ + # \_/\_/ \__,_|\__\___|_| |_| | .__/|_| \___/ \__, |_| \___||___/___/ + # |_| |___/ + + getProgress <- function(){ + # threadfiles <- list.files(settings$inputLoc, pattern="progress.txt", recursive = TRUE) + threadfiles <- list.files(pattern="progress.txt", recursive = TRUE) + if(length(threadfiles)==0){ + return(0) + } else { + sum(sapply(threadfiles, function(x){ + partRes <- readLines(x) + if(length(partRes)==0){ + return(0) + } else { + return(as.numeric(partRes)) + } + + })) + + } + } + + progress <- 0 + while(progress < iterations){ + Sys.sleep(1) + progress <- tryCatch(getProgress(), error=function(e){progress}) + if(is.null(pb)){ + pbUpdate(as.numeric(progress)) + } else { + pbUpdate(pb,as.numeric(progress)) + } + } + if(!is.null(pb)){ + close(pb) + } + + # ____ _ _ + # / ___|___ _ __ ___ | |__ (_)_ __ ___ + # | | / _ \| '_ ` _ \| '_ \| | '_ \ / _ \ + # | |__| (_) | | | | | | |_) | | | | | __/ + # \____\___/|_| |_| |_|_.__/|_|_| |_|\___| + + if(!is.null(constraints)){ + constRes <- file.path(list.dirs("tmp", recursive=FALSE), "const_results.data") + constRes <- lapply(constRes, function(f){read.csv(f, stringsAsFactors=FALSE, header=FALSE)}) + constRes <- do.call(rbind,constRes) + write.csv(constRes, "constRes.csv") + } + resultFiles <- list.files(pattern="preservedCalib.*csv$",recursive=TRUE) + res0 <- read.csv(grep("thread_1/",resultFiles, value=TRUE),stringsAsFactors=FALSE) + resultFilesSans0 <- grep("thread_1/", resultFiles, value=TRUE, invert=TRUE) + # results <- do.call(rbind,lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE)})) + resultsSans0 <- lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE, header=FALSE)}) + resultsSans0 <- do.call(rbind,resultsSans0) + colnames(resultsSans0) <- colnames(res0) + results <- (rbind(res0,resultsSans0)) + write.csv(results,"result.csv") + calibrationPar <- future::value(fut[[1]], stdout = FALSE, signal=FALSE)[["calibrationPar"]] + if(!is.null(constraints)){ + tryCatch({ + notForTree <- c(seq(from = (length(calibrationPar)+1), length.out=3)) + notForTree <- c(notForTree,which(sapply(seq_along(calibrationPar),function(i){sd(results[,i])==0}))) + treeData <- results[,-notForTree] + treeData["failType"] <- as.factor(results$failType) + if(ncol(treeData) > 4){ + rp <- rpart(failType ~ .,data=treeData,control=treeControl) + svg("treeplot.svg") + rpart.plot(rp) + dev.off() + } + }, error = function(e){ + print(e) + }) + } + origModOut <- future::value(fut[[1]], stdout = FALSE, signal=FALSE)[["origModOut"]] + # Just single objective version TODO:Multiobjective + results <- results[results[,"Const"] == 1,] + if(nrow(results)==0){ + stop("No simulation suitable for constraints\n Please see treeplot.png for explanation, if you have more than four parameters.") + } + bestCase <- which.max(results[,length(calibrationPar) + 1]) + parameters <- results[bestCase,1:length(calibrationPar)] # the last two column is the (log) likelihood and the rmse + #TODO: Have to put that before multiSiteThread, we should not have to calculate it at every iterations + + firstDir <- list.dirs("tmp/thread_1",full.names=TRUE,recursive =FALSE)[1] + epcFile <- list.files(firstDir, pattern = "\\.epc",full.names=TRUE) + settingsProto <- setupMuso(inputLoc = firstDir, + iniInput =rep(list.files(firstDir, pattern = "\\.ini",full.names=TRUE),2)) + alignIndexes <- commonIndexes(settingsProto, measurements) + musoCodeToIndex <- sapply(dataVar,function(musoCode){ + settingsProto$dailyOutputTable[settingsProto$dailyOutputTable$code == musoCode,"index"] + }) + + + setwd("tmp/thread_1") + aposteriori<- spatialRun(settingsProto, calibrationPar, parameters, calTable) + file.copy(list.files(list.dirs(full.names=TRUE, recursive=FALSE)[1], pattern=".*\\.epc", full.names=TRUE), + "../../multiSiteOptim.epc", overwrite=TRUE) + setwd("../../") + #TODO: Have to put that before multiSiteThread, we should not have to calculate it at every iterations + nameGroupTable <- calTable + nameGroupTable[,1] <- tools::file_path_sans_ext(basename(nameGroupTable[,1])) + res <- list() + + res[["calibrationPar"]] <- calibrationPar + res[["parameters"]] <- parameters + # browser() + res[["comparison"]] <- compareCalibratedWithOriginal(key = names(dataVar)[1], modOld=origModOut, modNew=aposteriori, mes=measurements, + + likelihoods = likelihood, + alignIndexes = alignIndexes, + musoCodeToIndex = musoCodeToIndex, + nameGroupTable = nameGroupTable, mean) + res[["likelihood"]] <- results[bestCase,ncol(results)-2] + comp <- res$comparison + res[["originalMAE"]] <- mean(abs((comp[,1]-comp[,3]))) + res[["MAE"]] <- mean(abs((comp[,2]-comp[,3]))) + res[["RMSE"]] <- results[bestCase,ncol(results)-2] + res[["originalRMSE"]] <- sqrt(mean((comp[,1]-comp[,3])^2)) + res[["originalR2"]] <- summary(lm(measured ~ original,data=res$comparison))$r.squared + res[["R2"]] <- summary(lm(measured ~ calibrated, data=res$comparison))$r.squared + saveRDS(res,"results.RDS") + png("calibRes.png") + opar <- par(mar=c(5,5,4,2)+0.1, xpd=FALSE) + with(data=res$comparison, { + plot(measured,original, + ylim=c(min(c(measured,original,calibrated)), + max(c(measured,original,calibrated))), + xlim=c(min(c(measured,original,calibrated)), + max(c(measured,original,calibrated))), + xlab=expression("measured "~(kg[DM]~m^-2)), + ylab=expression("simulated "~(kg[DM]~m^-2)), + cex.lab=1.3, + col="red", + pch=19, + pty="s" + ) + points(measured,calibrated, pch=19, col="blue") + abline(0,1) + legend(x="top", + pch=c(19,19), + col=c("red","blue"), + inset=c(0,-0.1), + legend=c("original","calibrated"), + ncol=2, + box.lty=0, + xpd=TRUE + ) + }) + dev.off() + return(res) +} + +#' multiSiteThread +#' +#' This is an +#' @author Roland HOLLOS + + +multiSiteThread <- function(measuredData, parameters = NULL, startDate = NULL, + endDate = NULL, formatString = "%Y-%m-%d", calTable, + dataVar, outLoc = "./calib", + outVars = NULL, iterations = 300, + skipSpinup = TRUE, plotName = "calib.jpg", + modifyOriginal=TRUE, likelihood, uncertainity = NULL, burnin=NULL, + naVal = NULL, postProcString = NULL, threadNumber, constraints=NULL,th=10) { + + originalRun <- list() + nameGroupTable <- calTable + nameGroupTable[,1] <- tools::file_path_sans_ext(basename(nameGroupTable[,1])) + setwd(paste0("tmp/thread_",threadNumber)) + firstDir <- list.dirs(full.names=FALSE,recursive =FALSE)[1] + epcFile <- list.files(firstDir, pattern = "\\.epc",full.names=TRUE) + settingsProto <- setupMuso(inputLoc = firstDir, + iniInput =rep(list.files(firstDir, pattern = "\\.ini",full.names=TRUE),2)) + + # Exanding likelihood + likelihoodFull <- as.list(rep(NA,length(dataVar))) + names(likelihoodFull) <- names(dataVar) + if(!missing(likelihood)) { + lapply(names(likelihood),function(x){ + likelihoodFull[[x]] <<- likelihood[[x]] + }) + } + + defaultLikelihood <- which(is.na(likelihood)) + if(length(defaultLikelihood)>0){ + likelihoodFull[[defaultLikelihood]] <- (function(x, y){ + exp(-sqrt(mean((x-y)^2))) + }) + } + + mdata <- measuredData + if(is.null(parameters)){ + parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) { + stop("You need to specify a path for the parameters.csv, or a matrix.") + }) + } else { + if((!is.list(parameters)) & (!is.matrix(parameters))){ + parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){ + stop("Cannot find neither parameters file neither the parameters matrix") + }) + }} + + print("optiMuso is randomizing the epc parameters now...",quote = FALSE) + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations) + + origEpc <- readValuesFromFile(epcFile, randVals[[1]]) + partialResult <- matrix(ncol=length(randVals[[1]])+2*length(dataVar) + 2) + colN <- randVals[[1]] + colN[match(parameters[,2],randVals[[1]])] <- parameters[,1] + colN[match(parameters[,2], randVals[[1]])[!is.na(match(parameters[,2],randVals[[1]]))]] <- parameters[,1] + colnames(partialResult) <- c(colN,sprintf("%s_likelihood",names(dataVar)), + sprintf("%s_rmse",names(dataVar)),"Const", "failType") + numParameters <- length(colN) + partialResult[1:numParameters] <- origEpc + ## Prepare the preservedCalib matrix for the faster + ## run. + musoCodeToIndex <- sapply(dataVar,function(musoCode){ + settingsProto$dailyOutputTable[settingsProto$dailyOutputTable$code == musoCode,"index"] + }) + + resultRange <- (numParameters + 1):(ncol(partialResult)) + randValues <- randVals[[2]] + + settingsProto$calibrationPar <- randVals[[1]] + + if(!is.null(naVal)){ + measuredData <- as.data.frame(measuredData) + measuredData[measuredData == naVal] <- NA + } + resIterate <- 1:nrow(calTable) + names(resIterate) <- tools::file_path_sans_ext(basename(calTable[,1])) + alignIndexes <- commonIndexes(settingsProto, measuredData) + if(threadNumber == 1){ + originalRun[["calibrationPar"]] <- randVals[[1]] + + origModOut <- lapply(resIterate, function(i){ + dirName <- tools::file_path_sans_ext(basename(calTable[i,1])) + setwd(dirName) + settings <- settingsProto + settings$outputLoc <- settings$inputLoc <- "./" + settings$iniInput <- settings$inputFiles <- rep(paste0(dirName,".ini"),2) + settings$outputNames <- rep(dirName,2) + settings$executable <- ifelse(Sys.info()[1]=="Linux","./muso","./muso.exe") # set default exe option at start wold be better + res <- tryCatch(calibMuso(settings=settings,parameters =origEpc, silent = TRUE, skipSpinup = TRUE), error=function(e){NA}) + setwd("../") + res + }) + originalRun[["origModOut"]] <- origModOut + + partialResult[,resultRange] <- calcLikelihoodsForGroups(dataVar=dataVar, + mod=origModOut, + mes=measuredData, + likelihoods=likelihood, + alignIndexes=alignIndexes, + musoCodeToIndex = musoCodeToIndex,nameGroupTable = nameGroupTable, groupFun=mean, constraints=constraints,th=th) + + write.csv(x=randVals[[1]],"../randIndexes.csv") + write.csv(x=partialResult, file="preservedCalib.csv",row.names=FALSE) + } + + print("Running the model with the random epc values...", quote = FALSE) + for(i in 2:(iterations+1)){ + tmp <- lapply(resIterate, function(siteI){ + dirName <- tools::file_path_sans_ext(basename(calTable[siteI,1])) + setwd(dirName) + settings <- settingsProto + settings$outputLoc <- settings$inputLoc <- "./" + settings$iniInput <- settings$inputFiles <- rep(paste0(dirName,".ini"),2) + settings$outputNames <- rep(dirName,2) + settings$executable <- ifelse(Sys.info()[1]=="Linux","./muso","./muso.exe") # set default exe option at start wold be better + + res <- tryCatch(calibMuso(settings=settings,parameters=randValues[(i-1),], silent = TRUE, skipSpinup = TRUE), error=function(e){NA}) + setwd("../") + res + }) + + if(is.null(tmp)){ + partialResult[,resultRange] <- NA + } else { + partialResult[,resultRange] <- calcLikelihoodsForGroups(dataVar=dataVar, + mod=tmp, + mes=measuredData, + likelihoods=likelihood, + alignIndexes=alignIndexes, + musoCodeToIndex = musoCodeToIndex,nameGroupTable = nameGroupTable, groupFun=mean, constraints = constraints, th=th) + + + + + + + partialResult[1:numParameters] <- randValues[(i-1),] + write.table(x=partialResult, file="preservedCalib.csv", append=TRUE, row.names=FALSE, + sep=",", col.names=FALSE) + # write.csv(x=tmp, file=paste0(pretag, (i+1),".csv")) + writeLines(as.character(i-1),"progress.txt") #UNCOMMENT IMPORTANT + } + } + + if(threadNumber == 1){ + return(originalRun) + } + + return(0) +} +distributeCores <- function(iterations, numCores){ + perProcess<- iterations %/% numCores + numSimu <- rep(perProcess,numCores) + gainers <- sample(1:numCores, iterations %% numCores) + numSimu[gainers] <- numSimu[gainers] + 1 + numSimu +} + +prepareFromAgroMo <- function(fName){ + obs <- read.table(fName, stringsAsFactors=FALSE, sep = ";", header=T) + obs <- reshape(obs, timevar="var_id", idvar = "date", direction = "wide") + dateCols <- apply(do.call(rbind,(strsplit(obs$date, split = "-"))),2,as.numeric) + colnames(dateCols) <- c("year", "month", "day") + cbind.data.frame(dateCols, obs) +} + +calcLikelihoodsForGroups <- function(dataVar, mod, mes, + likelihoods, alignIndexes, musoCodeToIndex, + nameGroupTable, groupFun, constraints, + th = 10){ + + if(!is.null(constraints)){ + constRes<- sapply(mod,function(m){ + compoVect(m,constraints) + }) + + failType <- constMatToDec(constRes) + } + + likelihoodRMSE <- sapply(names(dataVar),function(key){ + modelled <- as.vector(unlist(sapply(sort(names(alignIndexes)), + function(domain_id){ + apply(do.call(cbind, + lapply(nameGroupTable[,1][nameGroupTable[,2] == domain_id], + function(site){mod[[site]][alignIndexes[[domain_id]]$model,musoCodeToIndex[key]] + })),1,groupFun) + + + + + }))) + + + measuredGroups <- split(mes,mes$domain_id) + measured <- do.call(rbind.data.frame, lapply(names(measuredGroups), function(domain_id){ + measuredGroups[[domain_id]][alignIndexes[[domain_id]]$meas,] + })) + measured <- measured[measured$var_id == key,] + res <- c(likelihoods[[key]](modelled, measured), + sqrt(mean((modelled-measured$mean)^2)) + ) + + + print(abs(mean(modelled)-mean(measured$mean))) + res + }) + + likelihoodRMSE <- c(likelihoodRMSE[1,], likelihoodRMSE[2,], + ifelse((100 * sum(apply(constRes, 2, prod)) / ncol(constRes)) >= th, + 1,0), failType) + names(likelihoodRMSE) <- c(sprintf("%s_likelihood",dataVar), sprintf("%s_rmse",dataVar), "Const", "failType") + return(likelihoodRMSE) +} + +commonIndexes <- function (settings,measuredData) { + # Have to fix for other starting points also + modelDates <- seq(from= as.Date(sprintf("%s-01-01",settings$startYear)), + by="days", + to=as.Date(sprintf("%s-12-31",settings$startYear+settings$numYears-1))) + modelDates <- grep("-02-29",modelDates,invert=TRUE, value=TRUE) + + lapply(split(measuredData,measuredData$domain_id),function(x){ + measuredDates <- x$date + modIndex <- match(as.Date(measuredDates), as.Date(modelDates)) + measIndex <- which(!is.na(modIndex)) + modIndex <- modIndex[!is.na(modIndex)] + cbind.data.frame(model=modIndex,meas=measIndex) + }) +} + +agroLikelihood <- function(modVector,measured){ + mu <- measured[,grep("mean", colnames(measured))] + stdev <- measured[,grep("^sd", colnames(measured))] + ndata <- nrow(measured) + sum(sapply(1:ndata, function(x){ + dnorm(modVector, mu[x], stdev[x], log = TRUE) + }), na.rm=TRUE) +} + + +#' compareCalibratedWithOriginal +#' +#' This functions compareses the likelihood and the RMSE values of the simulations and the measurements +#' @param key +compareCalibratedWithOriginal <- function(key, modOld, modNew, mes, + likelihoods, alignIndexes, musoCodeToIndex, nameGroupTable, + groupFun){ + + original <- as.vector(unlist(sapply(sort(names(alignIndexes)), + function(domain_id){ + apply(do.call(cbind, + lapply(nameGroupTable$site_id[nameGroupTable$domain_id == domain_id], + function(site){ + modOld[[site]][alignIndexes[[domain_id]]$model,musoCodeToIndex[key]] + })),1,groupFun) + }))) + calibrated <- as.vector(unlist(sapply(sort(names(alignIndexes)), + function(domain_id){ + apply(do.call(cbind, + lapply(nameGroupTable$site_id[nameGroupTable$domain_id == domain_id], + function(site){ + modNew[[site]][alignIndexes[[domain_id]]$model,musoCodeToIndex[key]] + })),1,groupFun) + }))) + measuredGroups <- split(mes,mes$domain_id) + measured <- do.call(rbind.data.frame, lapply(names(measuredGroups), function(domain_id){ + measuredGroups[[domain_id]][alignIndexes[[domain_id]]$meas,] + })) + measured <- measured[measured$var_id == key,] + return(data.frame(original = original, calibrated = calibrated,measured=measured$mean)) +} + + +spatialRun <- function(settingsProto,calibrationPar, parameters, calTable){ + resIterate <- 1:nrow(calTable) + names(resIterate) <- tools::file_path_sans_ext(basename(calTable[,1])) + modOut <- lapply(resIterate, function(i){ + dirName <- tools::file_path_sans_ext(basename(calTable[i,1])) + setwd(dirName) + settings <- settingsProto + settings$outputLoc <- settings$inputLoc <- "./" + settings$iniInput <- settings$inputFiles <- rep(paste0(dirName,".ini"),2) + settings$outputNames <- rep(dirName,2) + settings$calibrationPar <- calibrationPar + settings$executable <- ifelse(Sys.info()[1]=="Linux","./muso","./muso.exe") # set default exe option at start wold be better + res <- tryCatch(calibMuso(settings=settings,parameters =parameters, silent = TRUE, skipSpinup = TRUE), error=function(e){NA}) + setwd("../") + res + }) + modOut +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoExample.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoExample.R new file mode 100644 index 0000000..bfdac3b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoExample.R @@ -0,0 +1,56 @@ +#'copyMusoExampleTo +#' +#'This function enables the user to download a complete, working file set to quickly start using Biome-BGCMuSo through RBBGCMuso (or in standalone mode). The user has to specify the target directory for the files. The file set contains the model executable (muso.exe in Windows), the INI files that drive the model, and other files like meteorology input, ecophysiological constants file (EPC), and other ancillary files (CO2 concentration, parameter range definition file called parameters.csv). Note that we strongly recommend to read the User's Guide of Biome-BGCMuSo to clarify the meaning of the input files. The input files (s.ini, n.ini, maize.epc, meteorology files) are simple text files, so the user can read (and modify) them with his/her favourite text editor (like Editpad Lite, vim, emacs). Note that some files use UNIX/Linux style text which means that the text will not be readable using the Windows Notepad. +#' +#'@param example This is the name of the example file. If it is not set then a simple graphical user interface (tcl/tk menu) will open to select the target dataset (which is typically an experimental site). In the list hhs means the Hegyhatsal eddy covariance site in Hungary. +#'@param destination The destination where the example files will be copied. +#'@export + +copyMusoExampleTo <- function(example = NULL, destination = NULL){ + WindowsP <- Sys.info()[1] == "Windows" + + chooseExample <- function(){ + choiceWin <- tcltk::tktoplevel() + tcltk::tclRequire("BWidget") + tcltk::tktitle(choiceWin) <- "Choose an example!" + tcltk::tcl("wm","geometry",choiceWin,"200x50") + tcltk::tcl("wm", "attributes", choiceWin, topmost=TRUE) + choiceValues <- basename(list.dirs(system.file("examples","",package = "RBBGCMuso"),recursive = FALSE)) + choices <- tcltk::tkwidget(choiceWin,"ComboBox", + editable = FALSE, values = choiceValues, + textvariable = tcltk::tclVar(choiceValues[1])) + tcltk::tkpack(choices) + choiceValue <- NA + closeSelection <- tcltk::tkwidget(choiceWin,"button",text ="Select", command =function (){ + choiceValue <<- tcltk::tclvalue(tcltk::tcl(choices,"get")) + tcltk::tkdestroy(choiceWin) + }) + + tcltk::tkpack(closeSelection) + while(as.numeric(tcltk::tclvalue(tcltk::tcl("winfo","exists",choiceWin)))){ + + } + return(choiceValue) + } + + + + if(is.null(example)){ + cExample<-paste0(system.file("examples","",package = "RBBGCMuso"),"/",chooseExample()) + } else { + cExample <- paste0(system.file("examples","",package = "RBBGCMuso"),"/","hhs") + } + + if(is.null(destination)){ + destination<-tcltk::tk_choose.dir(getwd(), "Choose folder to copy the examples!") + } + + currDir <- getwd() + setwd(cExample) + if(!WindowsP){ + file.copy(grep("(exe|dll)$", list.files(), value = TRUE, invert = TRUE),destination) + } else { + file.copy(grep("^muso$", list.files(), value = TRUE, invert = TRUE),destination) + } + setwd(destination) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoMethChanger.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoMethChanger.R new file mode 100644 index 0000000..b2ec51e --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoMethChanger.R @@ -0,0 +1,49 @@ +## library(RBBGCMuso) +## library(BayesianTools) +## library(sensitivity) + +metMusoGet <- function(metFile,skip=4,namerow=3,saveBackup=TRUE, revert=FALSE){ + + + + metData<-read.table(file = metFile,skip=skip) + namesMet <- unlist(read.table(file=metFile,skip = namerow-1,nrows = 1)) + colnames(metData)<-namesMet + + if(revert){ + file.copy(grep(basename(metFile),grep("mbck$",list.files(dirname(metFile)),value=TRUE),value = TRUE), metFile,overwrite = TRUE) + return(cat("Meteorological data is succesfully reverted to backup data")) + } + + if(saveBackup){ + file.copy(metFile,paste(metFile,"mbck",sep = "-")) + } +return(metData) +} + +metMusoSet <- function(metFile,skip=4,namerow=3,saveBackup=TRUE, revert=FALSE,index, changedData){ + + + + metData<-read.table(file = metFile,skip=skip) + namesMet <- unlist(read.table(file=metFile,skip = namerow-1,nrows = 1)) + colnames(metData)<-namesMet + + if(revert){ + file.copy(grep("mbck$",list.files(),value=TRUE), metFile) + } + + if(saveBackup){ + file.copy(metFile,paste(metFile,"mbck",sep = "-")) + } + + if(is.vector(changedData)&(length(metData[,index])==length(changedData))){ + metData[,index]<-changedData + + changedMet<- c(readLines(metFile,-1)[1:skip],apply(metData,1, function (x) paste(x,collapse = " "))) + return(writeLines(changedMet,metFile)) + + }else { + return(cat("\n\tThe changedData is not a vector or not in a same length")) + } +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoMonte.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoMonte.R new file mode 100644 index 0000000..d94abeb --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoMonte.R @@ -0,0 +1,278 @@ +#' musoMonte +#' +#' This function executes the Monte Carlo experiment with Biome-BGCMuSo (musoRand is called by this function). It samples the selected model parameters within user defined ranges from conditional multivariate uniform distribution, and then runs the model for each run. +#' @author Roland HOLLOS +#' @param settings A list of environmental variables for the Monte Carlo experiment. These settings are generated by the setupMuso function. By default the settings parameter is generated automatically. +#' @param parameters This is a dataframe (heterogeneous data-matrix), where the first column is the name of the parameter, the second is a numeric vector of the rownumbers of the given variable in the input EPC file, and the last two columns describe the minimum and the maximum of the parameter (i.e. the parameter ranges), defining the interval for the randomization. +#' @param calibrationPar You might want to change some parameters in your EPC file before you run the modell. You have to select the appropirate model parameters here. You can refer to the parameters by the number of the line in the EPC file where the variables are defined. The indexing of the lines starts at 1, and each line matters (like in any simple text file). You should use a vector for this selection like c(1,5,8) +#' @param inputDir The location of the input directory for the Biome-BGCMuSo model. This directory must contain a viable pack of all input files and the model executable file. +#' @param iterations Number of the Monte Carlo simulations. +#' @param preTag This defines the name of the output files. This tag will be re-used so that the results will be like preTag-1.csv, preTag-2csv... +#' @param outputType This parameter can be "oneCsv", "moreCsv", and "netCDF". If "oneCsv" is chosen the function creates one large csv file for all of the runs. If "moreCsv" is chosen, every model output goes to separate files. If netCDF is selected the output will be stored in a netCDF file. The default value of the outputTypes is "moreCsv". Note that netCDF is not implemented yet. +#' @param fun If you select a variable from the possible outputs (by using the varIndex parameter), you have to provide a function which maps to a subset of real numbers. The most frequent possibilities are: mean, min, max, var, but you can define any function for your needs. +#' @param varIndex This parameter specifies which parameter will be used for the Monte Carlo experiment from the output list of Biome-BGCMuSo (defined by the INI file). You can extract this information from the INI files. At the output parameter specifications, the parameter order will determine this number. For example, if you have set these output parameters: 412, 874, 926, 888, and you want to use 926 for the experiment, you should specify varIndex as 3. +#' @param debugging If you set this parameter, you can save every logfile, and RBBGCMuso will select those which contains errors. This is useful to study why the model crashes with a given parameter set. +#' @param keepEpc If you set keepEpc as TRUE, it will save every selected EPC file, and move the wrong ones into the WRONGEPC directory. +#' @importFrom magrittr '%>%' +#' @export + +musoMonte <- function(settings=NULL, + parameters=NULL, + inputDir = "./", + outLoc = "./calib", + iterations = 10, + preTag = "mont-", + outputType = "moreCsv", + fun=mean, + varIndex = 1, + outVars = NULL, + silent = TRUE, + skipSpinup = TRUE, + debugging = FALSE, + keepEpc = FALSE, + constrains = NULL, + skipZero = TRUE, + postProcString=NULL, + modifyOut=TRUE, + ...){ + + + readValuesFromEpc <- function(epc, linums){ + epcFile <- readLines(epc) + rows <- numeric(2) + values <- sapply(linums, function(x){ + rows[1] <- as.integer(x) + rows[2] <- as.integer(round(100*x)) %% 10 + 1 + epcFile <- readLines(epc) + selRow <- unlist(strsplit(epcFile[rows[1]], split= "[\t ]")) + selRow <- selRow[selRow!=""] + return(as.numeric(selRow[rows[2]])) + + }) + + return(values) + } + + if(is.null(parameters)){ + parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) { + stop("You need to specify a path for the parameters.csv, or a matrix.") + }) + } else { + if((!is.list(parameters)) & (!is.matrix(parameters))){ + parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){ + stop("Cannot find neither parameters file neither the parameters matrix") + }) + }} + + outLocPlain <- basename(outLoc) + currDir <- getwd() + + if(!dir.exists(outLoc)){ + dir.create(outLoc) + warning(paste(outLoc," is not exists, so it was created")) + } + + outLoc <- normalizePath(outLoc) + + if(is.null(settings)){ + settings <- setupMuso() + } + + + + if(is.null(outVars)){ + numVars <- length(settings$outputVars[[1]]) + outVarNames <- settings$outputVars[[1]] + } else { + numVars <- length(outVars) + outVarNames <- sapply(outVars, musoMapping) + } + + if(!is.null(postProcString)){ + outVarNames <- c(outVarNames,gsub("\\s","",unlist(strsplit(procString,"<-"))[1])) + } + + parameterNames <- gsub("([\\s]|\\-epc)","",parameters[,1],perl=TRUE) + # settings$calibrationPar <- A[,1] #:LATER: + pretag <- file.path(outLoc,preTag) + npar <- length(settings$calibrationPar) + + ##reading the original epc file at the specified + ## row numbers + if(iterations < 3000){ + randVals <- musoRand(parameters = parameters,fileType="epc", iterations = 3000) + randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] + } else { + randVals <- musoRand(parameters = parameters,fileType="epc", iterations = iterations) + } + + origEpc <- readValuesFromEpc(settings$epc[2],parameters[,2]) + + ## Prepare the preservedEpc matrix for the faster + ## run. + + pretag <- file.path(outLoc,preTag) + + ## Creating function for generating separate + ## csv files for each run + + progBar <- txtProgressBar(1,iterations,style=3) + + + moreCsv <- function(){ + settings$iniInput[2] %>% + (function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>% + unlink + randValues <- randVals[[2]] + settings$calibrationPar <- randVals[[1]] + ## randValues <- randValues[,randVals[[1]] %in% parameters[,2]][,rank(parameters[,2])] + modellOut <- matrix(ncol = numVars, nrow = iterations + 1) + + + origModellOut <- calibMuso(settings=settings,silent=TRUE) + write.csv(x=origModellOut, file=paste0(pretag,1,".csv")) + + if(!is.list(fun)){ + funct <- rep(list(fun), numVars) + } + + tmp2 <- numeric(numVars) +# browser() + for(j in 1:numVars){ + tmp2[j]<-funct[[j]](origModellOut[,j]) + } + modellOut[1,]<- tmp2 + + for(i in 2:(iterations+1)){ + tmp <- tryCatch(calibMuso(settings = settings, + parameters = randValues[(i-1),], + silent= TRUE, + skipSpinup = skipSpinup, + keepEpc = keepEpc, + debugging = debugging, + modifyOriginal = modifyOut, + outVars = outVars,postProcString=postProcString), error = function (e) NA) + + if(length(dim(tmp))>=1){ + for(j in 1:numVars){ + tmp2[j]<-funct[[j]](tmp[,j]) + } + if(skipZero){ + if(tmp2[j]==0){ + tmp2[j] <- NA + } + } + } else { + for(j in 1:numVars){ + tmp2[j]<-NA + } + } + + + + modellOut[i,]<- tmp2 + write.csv(x=tmp, file=paste0(pretag,(i+1),".csv")) + setTxtProgressBar(progBar,i) + } + + paramLines <- parameters[,2] + paramLines <- order(paramLines) + randInd <- randVals[[1]][(randVals[[1]] %in% parameters[,2])] + randInd <- order(randInd) + + + + # browser() + epcStrip <- rbind(origEpc[order(parameters[,2])], + randValues[,randVals[[1]] %in% parameters[,2]][,randInd]) + + + preservedEpc <- cbind(epcStrip, + modellOut) + colnames(preservedEpc) <- c(parameterNames[paramLines], sapply(outVarNames, function (x) paste0("mod.", x))) + return(preservedEpc) + } + + ## Creating function for generating one + ## csv files for each run + + oneCsv <- function () { + # stop("This function is not implemented yet") + settings$iniInput[2] %>% + (function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>% + unlink + randValues <- randVals[[2]] + settings$calibrationPar <- randVals[[1]] + ## randValues <- randValues[,randVals[[1]] %in% parameters[,2]][,rank(parameters[,2])] + modellOut <- matrix(ncol = numVars, nrow = iterations + 1) + + origModellOut <- calibMuso(settings=settings,silent=TRUE) + write.csv(x=origModellOut, file=paste0(pretag,".csv")) + + if(!is.list(fun)){ + funct <- rep(list(fun), numVars) + } + + tmp2 <- numeric(numVars) + + for(j in 1:numVars){ + tmp2[j]<-funct[[j]](origModellOut[,j]) + } + modellOut[1,]<- tmp2 + + for(i in 2:(iterations+1)){ + tmp <- tryCatch(calibMuso(settings = settings, + parameters = randValues[(i-1),], + silent= TRUE, + skipSpinup = skipSpinup, + keepEpc = keepEpc, + debugging = debugging, + outVars = outVars), error = function (e) NA) + + if(!is.na(tmp)){ + for(j in 1:numVars){ + tmp2[j]<-funct[[j]](tmp[,j]) + } + } else { + for(j in 1:numVars){ + tmp2[j]<-rep(NA,length(settings$outputVars[[1]])) + } + } + + + + modellOut[i,]<- tmp2 + write.table(x=tmp, file=paste0(pretag,".csv"), append = TRUE,col.names = FALSE, sep = ",") + setTxtProgressBar(progBar,i) + } + + paramLines <- parameters[,2] + paramLines <- order(paramLines) + randInd <- randVals[[1]][(randVals[[1]] %in% parameters[,2])] + randInd <- order(randInd) + + + epcStrip <- rbind(origEpc[order(parameters[,2])], + randValues[,randVals[[1]] %in% parameters[,2]][,randInd]) + + + preservedEpc <- cbind(epcStrip, + modellOut) + colnames(preservedEpc) <- c(parameterNames[paramLines], sapply(outVarNames, function (x) paste0("mod.", x))) + return(preservedEpc) + } + + netCDF <- function () { + stop("This function is not inplemented yet") + } + + ## Call one function according to the outputType + switch(outputType, + "oneCsv" = (a <- oneCsv()), + "moreCsv" = (a <- moreCsv()), + "netCDF" = (a <- netCDF())) + write.csv(a,"preservedEpc.csv") + + setwd(currDir) + return(a) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoRand.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoRand.R new file mode 100644 index 0000000..1ed8c3a --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoRand.R @@ -0,0 +1,187 @@ +#' musoRand +#' +#' This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters. +#' @author Roland HOLLOS +#' @param parameters This is a dataframe (heterogeneous data-matrix), where the first column is the name of the parameter, the second is a numeric vector of the rownumbers of the given variable in the input EPC file, and the last two columns describe the minimum and the maximum of the parameter (i.e. the parameter ranges), defining the interval for the randomization. +#' @param constrains This is a matrix wich specify the constrain rules for the sampling. Parameter dependencies are described in the Biome-BGCMuSo User's Guide. Further informations is coming soon. +#' @param iteration The number of samples for the Monte-Carlo experiment. We propose to use at least 3000 iteration because it is generally fast and it can be subsampled later at any time. +#' @importFrom limSolve xsample +#' @export + +musoRand <- function(parameters, iterations=3000, fileType="epc", constrains = NULL, burnin = NULL){ + if(is.null(constrains)){ + constMatrix <- constrains + constMatrix <- getOption("RMuso_constMatrix")[[fileType]][[as.character(getOption("RMuso_version"))]] + } else { + constMatrix <- constrains + } + + parameters <- parameters[,-1] + constMatrix <- constMatrix[,-1] + + depTableMaker <- function(constMatrix,parameters){ + # browser() + parameters <- parameters[order(parameters[,1]),] ## BUG!!! + selectedRows <- constMatrix[,"INDEX"] %in% parameters[,1] + rankList <- rank(constMatrix[selectedRows,2]) + constMatrix[selectedRows,c(5,6)] <- parameters[rankList,c(2,3)] + logiConstrain <- (constMatrix[,"GROUP"] %in% constMatrix[constMatrix[,"INDEX"] %in% parameters[,1],"GROUP"] & + (constMatrix[,"GROUP"]!=0)) | ((constMatrix[,"INDEX"] %in% parameters[,1]) & (constMatrix[,"GROUP"] == 0)) + constMatrix <- constMatrix[logiConstrain,] + constMatrix <- constMatrix[order(apply(constMatrix[,7:8],1,function(x){x[1]/10+abs(x[2])})),] + constMatrix + } + # browser() + genMat0 <- function(dep){ + numberOfVariable <- nrow(dep) + G <- rbind(diag(numberOfVariable), -1*diag(numberOfVariable)) + h <- c(dependences[,5], -1*dependences[,6]) + return(list(G=G,h=h)) + } + + genMat1 <- function(dep, N){ + + ## Range <- sapply(list(min,max),function(x){ + ## x(as.numeric(rownames(dep))) + ## }) It is more elegant, more general, but slower + Range <- (function(x){ + c(min(x), max(x)) + })(as.numeric(dep[,"rowIndex"])) + + numberOfVariables <- nrow(dep) + G<- -1*diag(numberOfVariables) + + for(i in 1:numberOfVariables){ + if(dep[i,4]!=0){ + G[i,dep[i,4]] <- 1 + } + + } +# browser() + G<-G[dep[,4]!=0,] + + if(is.null(nrow(G))){ + G<-t(as.matrix(G)) + } + numRowsInG <- nrow(G) + if(Range[1]==1){ + G<-cbind(G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0)) + } else{ + if(Range[2]==N){ + G<-cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G) + } else { + G <- cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0)) + } + } + return(list(G=-1*G,h=-1*rep(0,nrow(G)))) + } + + genMat2 <- function(dep, N){ + G <- rep(1,nrow(dep)) + + Range <- (function(x){ + c(min(x), max(x)) + })(as.numeric(dep[,"rowIndex"])) + + if(Range[1]==1){ + G<-c(G, numeric(N-Range[2])) + } else{ + if(Range[2]==N){ + G<-c(numeric(Range[1]-1), G) + } else { + G <- c(numeric(Range[1]-1), G, numeric(N-Range[2])) + } + } + + G <- t(matrix(sign(dep[2,4])*G)) + h <- abs(dep[1,4]) + if(dep[1,"TYPE"]==2){ # This is not needed, I'll have to remove the if part, and keep the content + G <- G*(-1) + h <- h*(-1) + } + + return(list(G=G,h=h)) + } + + genMat3 <- function(dep, N){ + Range <- (function(x){ + c(min(x), max(x)) + })(as.numeric(dep[,"rowIndex"])) + + E <- rep(1,nrow(dep)) + + if(Range[1]==1){ + E<-c(E, numeric(N-Range[2])) + } else{ + if(Range[2]==N){ + E<-c(numeric(Range[1]-1), E) + } else { + E <- c(numeric(Range[1]-1), E, numeric(N-Range[2])) + } + } + + + E <- t(matrix(E)) + f <- dep[1,4] + return(list(E=E,f=f)) + } + + + applyRandTypeG <- function(dep,N){ + type <- unique(dep[,"TYPE"]) + minR <- min(dep[,"rowIndex"]) + maxR <- max(dep[,"rowIndex"]) + switch(type, + invisible(Gh <- genMat1(dep, N)), + invisible(Gh <- genMat2(dep, N))) + return(Gh) + } + + applyRandTypeE <- function(dep,N){ + type <- unique(dep[,"TYPE"]) + minR <- min(dep[,"rowIndex"]) + maxR <- max(dep[,"rowIndex"]) + switch(-type, + stop("Not implemented yet"), + stop("Not implemented yet"), + invisible(Ef <- genMat3(dep, N))) + return(Ef) + } + + dependences <- depTableMaker(constMatrix, parameters) + dependences <- cbind(dependences,1:nrow(dependences)) + colnames(dependences)[ncol(dependences)] <- "rowIndex" + # browser() + numberOfVariable <- nrow(dependences) + nonZeroDeps<-dependences[dependences[,"TYPE"]!=0,] + if(nrow(nonZeroDeps)!=0){ + splitedDeps<- split(nonZeroDeps,nonZeroDeps[,"GROUP"]) + Gh <- list() + Ef <- list() + + for(i in 1:length(splitedDeps)){ + print(splitedDeps[[i]][1,"TYPE"]) + if(splitedDeps[[i]][1,"TYPE"]>0){ + Gh[[i]]<-applyRandTypeG(splitedDeps[[i]],nrow(dependences)) + } else { + Ef[[i]] <- applyRandTypeE(splitedDeps[[i]],nrow(dependences)) + } + } + + Gh0<- genMat0(dependences) + G <- do.call(rbind,lapply(Gh,function(x){x$G})) + G<- rbind(Gh0$G,G) + h <- do.call(c,lapply(Gh,function(x){x$h})) + h <- c(Gh0$h,h) + E <- do.call(rbind,lapply(Ef,function(x){x$E})) + f <- do.call(c,lapply(Ef,function(x){x$f})) + # browser() + randVal <- suppressWarnings(limSolve::xsample(G=G,H=h,E=E,F=f,burninlength=burnin, iter = iterations))$X + } else{ + Gh0<-genMat0(dependences) + randVal <- suppressWarnings(xsample(G=Gh0$G,H=Gh0$h, iter = iterations))$X + } + + results <- list(INDEX =dependences$INDEX, randVal=randVal) + return(results) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoSensi.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoSensi.R new file mode 100644 index 0000000..4f4130b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoSensi.R @@ -0,0 +1,121 @@ +#' musoSensi +#' +#' This function does regression based sensitivity analysis based on the output of musoMonte. +#' @param settings A list of montecarlos environmental variables. It is generated by the setupMuso() function. In default the settings parameter is generated automatically. +#' @param parameters This is a dataframe (heterogen data-matrix), which first column is the name of the parameters, the second is a numeric vector of the rownumbers of the given variable in the epc-fie, the last two column consist the endpont of the parameter-ranges, where the parameters will be randomized. +#' @param calibrationPar You may want to change some parameters in your epc file, before you run the modell. You have to select the appropirate modell parameters. You can refence to these with the number of the line in the epc file where the variables are. It indexes from one. You should use a vector for this, like: c(1,5,8) +#' @param inputDir The location of the input directory, this directory must content a viable pack of all inputfiles and the executable file. +#' @param iterations number of the monteCarlo run. +#' @param preTag It will be the name of the output files. For example preTag-1.csv, pretag-2csv... +#' @param outputType This parameter can be "oneCsv", "moreCsv", and "netCDF". If "oneCsv" is choosen the function create 1 big csv file for all of the runs, if "moreCsv" is choosen, every modell output goes to separate files, if netCDF is selected the outputs will be put in a netCDF file. The default value of the outputTypes is "moreCsv". netCDF is not implemented yet. +#' @param fun If you select a variable from the possible outputs (with specify the varIndex parameter), you have to provide a function which maps to a subset of real numbers. The most frequent possibilities are: mean, min, max, var, but you can define any function for your need. +#' @param varIndex This parameter specify which parameter of the output will be used. You can extract this information from the ini-files. At the output parameter specifications, the parameters order will determine this number. For example, if you have set these output parameters: 412, 874, 926, 888, and you want to use 926, you should address varIndex with 3. +#' @param skipSpinup With this parameter, you can turn of the spinup phase after the first spinup. I will decrease the time significantly. +#' @importFrom ggplot2 geom_bar ggplot aes theme element_text xlab ylab ggtitle ggsave scale_y_continuous +#' @importFrom scales percent +#' @export + +musoSensi <- function(monteCarloFile = NULL, + parameters = NULL, + settings = NULL, + inputDir = "./", + outLoc = "./calib", + outVars = NULL, + iterations = 30, + preTag = "mont-", + outputType = "moreCsv", + fun = mean, + varIndex = 1, + outputFile = "sensitivity.csv", + plotName = "sensitivity.png", + plotTitle = "Sensitivity", + skipSpinup = TRUE, + skipZero = TRUE, + postProcString=NULL, + modifyOut=TRUE, + dpi=300){ + + if(is.null(parameters)){ + parameters <- tryCatch(read.csv("parameters.csv",stringsAsFactor=FALSE), error = function (e) { + stop("You need to specify a path for the parameters.csv, or a matrix.") + }) + } else { + if((!is.list(parameters)) & (!is.matrix(parameters))){ + parameters <- tryCatch(read.csv(parameters,stringsAsFactor=FALSE), error = function (e){ + stop("Cannot find neither parameters file neither the parameters matrix") + }) + }} + parameters[,1] <- gsub("([\\s]|\\-epc)","",parameters[,1],perl=TRUE) + doSensi <- function(M){ + # browser() + npar <- ncol(M)-1 + M <- M[which(!is.na(M[,ncol(M)])),] + M <- M[-1,] + y <- M[,(npar+1)] + colnames(M) <- gsub("\\.epc","-epc",colnames(M)) + M <- M[,colnames(M) %in% parameters[,1]] + npar <- ncol(M) + M <- apply(M[,1:npar],2,function(x){x-mean(x)}) + varNames<- colnames(M)[1:npar] + w <- lm(y~M)$coefficients[-1] + Sv <- apply(M,2,var) + overalVar <- sum(Sv*w^2,na.rm = TRUE) + S=numeric(npar) + + for(i in 1:npar){ + S[i] <- ((w[i]^2*Sv[i])/(overalVar))*100 + } + + S <- round(S,digits=2) + names(S)<-varNames + write.csv(file = outputFile, x = S) + + sensiPlot <- ggplot(data.frame(name=varNames,y=S/100),aes(x=name,y=y))+ + geom_bar(stat = 'identity')+ + theme(axis.text.x = element_text(angle = 45, hjust = 1))+ + xlab(NULL)+ + ylab(NULL)+ + ggtitle("Sensitivity")+ + scale_y_continuous(labels = scales::percent,limits=c(0,1)) + print(sensiPlot) + ggsave(plotName,dpi=dpi) + return(S) + } + + + + if(is.null(monteCarloFile)){ + M <- musoMonte(parameters = parameters, + settings = settings, + inputDir = inputDir, + outLoc = outLoc, + iterations = iterations, + preTag = preTag, + outputType = outputType, + outVars = outVars, + fun = fun, + varIndex = varIndex, + skipSpinup = skipSpinup, + skipZero=skipZero, + postProcString=postProcString, + modifyOut=modifyOut + ) + M <- cbind(seq_along(M[,1]),M) + yInd <- grep("mod.", colnames(M))[varIndex] + parNames <- grep("mod.",colnames(M), invert=TRUE, value = TRUE) + M <- M[,c(grep("mod.", colnames(M),invert=TRUE),yInd)] + + return(doSensi(M)) + + } else { + M <- read.csv(monteCarloFile) + yInd <- grep("mod.", colnames(M))[varIndex] + parNames <- grep("mod.",colnames(M), invert=TRUE, value = TRUE) + M <- M[,c(grep("mod.", colnames(M),invert=TRUE),yInd)] + # browser() + return(doSensi(M)) + } +} + + + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoTime.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoTime.R new file mode 100644 index 0000000..28cd2a9 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/musoTime.R @@ -0,0 +1,116 @@ +#' musoDate +#' +#' This function generates MuSo compatibla dates for the data +#' @author Roland HOLLOS +#' @param startYear +#' @param numYears +#' @param timestep +#' @param combined +#' @param corrigated +#' @param format +#' @importFrom lubridate leap_year +#' @export + +musoDate <- function(startYear, endYears = NULL, numYears, combined = TRUE, leapYearHandling = FALSE, prettyOut = FALSE){ + + if(is.null(endYears) & is.null(numYears)){ + stop("You should provide endYears or numYears") + } + + if(is.null(endYears)){ + endYear <- startYear + numYears -1 + } + + dates <- seq(from = as.Date(paste0(startYear,"01","01"),format = "%Y%m%d"), to = as.Date(paste0(endYear,"12","31"),format = "%Y%m%d"), by = "day") + if(leapYearHandling){ + if(prettyOut){ + return(cbind(format(dates,"%d.%m.%Y"), + as.numeric(format(dates,"%d")), + as.numeric(format(dates,"%m")), + as.numeric(format(dates,"%Y"))) ) + } + + if(combined == FALSE){ + return(cbind(format(dates,"%d"),format(dates,"%m"),format(dates,"%Y"))) + } else { + return(format(dates,"%d.%m.%Y")) + } + + } else { + dates <- dates[format(dates,"%m%d")!="0229"] + if(prettyOut){ + return(data.frame(date = format(dates,"%d.%m.%Y"), + day = as.numeric(format(dates,"%d")), + month = as.numeric(format(dates,"%m")), + year = as.numeric(format(dates,"%Y")))) + } + + + if(combined == FALSE){ + return(cbind(format(dates,"%d"),format(dates,"%m"),format(dates,"%Y"))) + } else { + return(format(dates,"%d.%m.%Y")) + } + } + +} +#' alignData +#' +#' This function align the data to the model and the model to the data +#' @importFrom lubridate leap_year +#' @keywords internal +alignData <- function(mdata, dataCol, modellSettings = NULL, startDate=NULL, endDate=NULL, formatString = "%Y-%m-%d", leapYear = TRUE, continious = FALSE){ + + if(continious){ + if((is.null(startDate) | is.null(endDate))){ + stop("If your date is continuous, you have to provide both startDate and endDate. ") + } + startDate <- as.Date(startDate, format = formatString) + endDate <- as.Date(endDate, format = formatString) + } + + if(is.null(modellSettings)){ + modellSettings <- setupMuso() + } + + mdata <- as.data.frame(mdata) + + if(continious){ + dates <- seq(startDate, to = endDate, by= "day") + } else{ + dates <- do.call(c,lapply(seq(nrow(mdata)), function(i){ as.Date(paste0(mdata[i,1],sprintf("%02d",mdata[i,2]),mdata[i,3]),format = "%Y%m%d")})) + } + + ## if(!leapYear){ + ## casualDays <- which(format(dates,"%m%d") != "0229") + ## #mdata <- mdata[casualDays,] + ## dates <- dates[casualDays] + ## } + + mdata <- mdata[dates >= as.Date(paste0(modellSettings$startYear,"01","01"),format = "%Y%m%d"),] + dates <- dates[dates >= as.Date(paste0(modellSettings$startYear,"01","01"),format = "%Y%m%d")] + ## goodInd <- which(!(leap_year(dates)& + ## (format(dates,"%m") == "12")& + ## (format(dates,"%d") == "31"))) + + if(leapYear){ + goodInd <- which(!(leap_year(dates)& + (format(dates,"%m") == "12")& + (format(dates,"%d") == "31"))) + } else { + goodInd <-seq_along(dates) + } + realDate <- dates[which(format(dates,"%m%d") != "0229")] + if(leapYear){ + mdata <- cbind.data.frame(realDate,mdata[goodInd,]) + } else { + mdata <- cbind.data.frame(dates,mdata) + } + modellDates <- as.Date(musoDate(startYear = modellSettings$startYear,numYears = modellSettings$numYears), format = "%d.%m.%Y") + mdata <- mdata[mdata[,1] %in% modellDates,] + nonEmpty <- which(!is.na(mdata[,dataCol+1])) + mdata <- mdata[nonEmpty,] + modIndex <- which(modellDates %in% mdata[,1]) + + list(measuredData = mdata[,dataCol +1], modIndex = modIndex) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/normalMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/normalMuso.R new file mode 100644 index 0000000..db9e53c --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/normalMuso.R @@ -0,0 +1,201 @@ +#' normalMuso +#' +#' This function optionally changes the EPC file and runs the Biome-BGCMuSo model in normal phase and reads its output file in a well-structured way with debugging features. (Execution of spinup phase is possible with spinupMuso.) Prerequisite of normalMuso is the existence of the endpoint file (which is the result of the spinup phase and contains initial conditions for the simulation). +#' +#' @author Roland HOLLOS +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param timee The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet. +#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory and stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved. +#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory. +#' @param export If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv. +#' @param silent If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution. +#' @param aggressive It deletes all previous model-outputs from previous model runs. +#' @param parameters Using normalMuso it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4). +#' @param logfilename If you would like to set a specific name for your logfiles you can set this via the logfile parameter. +#' @param leapYear Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years. +#' @param keepBinary By default RBBGCMuso keeps the working environment as clean as possible, thus deletes all the regular output files. The results are directly written to the standard output (e.g. to the screen), but you can redirect it and save them to a variable. Alternatively, you can export your results to the desired destination in a desired format. Through the keepBinary parameter you can set RBBGCMuso to keep the binary output files. If you would like to set the location of the binary output, please take a look at the binaryPlace argument. +#' @param binaryPlace The directory for the binary output files (see the keepBinary parameter). +#' @param fileToChange You can change any line of the EPC or the INI file prior to model execution. All you need to do is to specify with this variable which file you want to change. Two options possible: "EPC" or "INI" +#' @return The simulation output matrix, where the columns are the chosen variables and each row is a daily/monthly/annual data. +#' @usage normalMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, +#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +#' @import utils +#' @export + +normalMuso<- function(settings=NULL,parameters=NULL,timee="d",debugging=FALSE,logfilename=NULL,keepEpc=FALSE, export=FALSE,silent=FALSE,aggressive=FALSE,leapYear=FALSE, binaryPlace=NULL,fileToChange="epc", keepBinary=FALSE){ + + +########################################################################## +###########################Set local variables######################## +######################################################################## + + if(is.null(settings)){ + settings <- setupMuso() #( :INSIDE: setupMuso.R) + } + # The software works on Linux or Windows, Mac is not implemented yet, so with this simple dichotomy we can determine wich syste is running + Linuxp <-(Sys.info()[1]=="Linux") + ##Copy the variables from settings + inputLoc <- settings$inputLoc + outputLoc <- settings$outputLoc + outputNames <- settings$outputNames + executable <- settings$executable + iniInput <- settings$iniInput + epc <- settings$epcInput + calibrationPar <- settings$calibrationPar + + ## We want to minimize the number of sideeffects so we store the state to restore in the end. + whereAmI<-getwd() + + + ## Optionally the user may want to store the original binary file. At default we set it to the output location. + + if(is.null(binaryPlace)){ + binaryPlace <- outputLoc + } + + ## Now we create a directories for the debugging files if these are not exists, and if debugging or keepEpc options are set to true. + + if(debugging){ #debugging is boolean, so we dont write debugging == TRUE for the sake of faster model run + #If log or ERROR directory does not exists create it! + dirName<-file.path(inputLoc,"LOG") + dirERROR<-file.path(inputLoc,"ERROR") + + if(!dir.exists(dirName)){ + dir.create(dirName) + } + + if(!dir.exists(dirERROR)){ + dir.create(dirERROR) + } + } + + if(keepEpc) {#keepEpc is boolean + epcdir <- dirname(epc[1]) + print(epcdir) + WRONGEPC<-file.path(inputLoc,"WRONGEPC") + EPCS<-file.path(inputLoc,"EPCS") + + if(!dir.exists(WRONGEPC)){ + dir.create(WRONGEPC) + } + + if(!dir.exists(EPCS)){ + dir.create(EPCS) + } + } + + + + + + if(!is.null(parameters)){ + switch(fileToChange, + "epc" = tryCatch(changemulline(filename = epc[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R) + error = function (e) {stop("Cannot change the epc file")}), + "ini" = tryCatch(changemulline(filename = iniInput[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R) + error = function (e) {stop("Cannot change the ini file")}), + "both" = (stop("This option is not implemented yet, please choose epc or ini")) + ) + } + + + + + #normal run + + ## if(silent){ + ## if(Linuxp){ + ## system(paste(executable,iniInput[2],"> /dev/null",sep=" ")) + ## } else { + ## system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE) + ## } + + ## } else { + ## system(paste(executable,iniInput[2],sep=" ")) + ## } + + + + ## system(paste(executable,iniInput[2],sep=" ")) + + ## switch(timee, + ## "d"=(Reva<-getdailyout(settings)), + ## "m"=(Reva<-getmonthlyout(settings)), + ## "y"=(Reva<-getyearlyout(settings)) + ## ) + + + if(silent){ + if(Linuxp){ + tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")), + error =function (e) {stop("Cannot run the modell-check the executable!")}) + } else { + tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE), + error =function (e) {stop("Cannot run the modell-check the executable!")} ) + } + + } else { + tryCatch(system(paste(executable,iniInput[2],sep=" ")), + error =function (e) {stop("Cannot run the modell-check the executable!")}) + } + + + ##read the output + + switch(timee, + "d"=(Reva <- tryCatch(getdailyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})), + "m"=(Reva <- tryCatch(getmonthlyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})), + "y"=(Reva <- tryCatch(getyearlyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})) + ) + + + + if(keepBinary){ + possibleNames <- getOutFiles(outputLoc = outputLoc,outputNames = outputNames) #(:INSIDE: assistantFunctions.R) + stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output") #(:INSIDE: assistantFunctions.R) + } + + + + logfiles <- getLogs(outputLoc,outputNames,type = "normal") #(:INSIDE: assistantFunctions.R) + + +#############LOG SECTION####################### + errorsign <- readErrors(outputLoc = outputLoc,logfiles = logfiles,type="normal") #(:INSIDE: assistantFunctions.R) + + if(keepEpc){#if keepepc option turned on + + if(length(unique(dirname(epc)))>1){ + stop("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?") + } else { + + stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc[2], type="general", errorsign=errorsign, logfiles=logfiles) + + } + } + + + + if(debugging){ #debugging is boolean + logfiles <- file.path(outputLoc,logfiles) + stampAndDir(stampDir=dirName, wrongDir=dirERROR, names=logfiles, type="general",errorsign=errorsign,logfiles=logfiles)} + cleanupMuso() + if(errorsign==1){ + return("Modell Failure") + } + + + + + return(Reva) + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/otherUsefullFunctions.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/otherUsefullFunctions.R new file mode 100644 index 0000000..f70bdff --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/otherUsefullFunctions.R @@ -0,0 +1,185 @@ +#' getyearlycum +#' +#' Funtion for getting cumulative yearly data from observations +#' @author Roland Hollos +#' @param daily_observations vector of the daily observations. +#' @return A vector of yearly data +#' @export + + +getyearlycum<-function(daily_observations){ + number_of_years<-length(daily_observations)/365 + # daily_observations[is.na(daily_observations)]<-0 # 3+NA=NA + fr<-1 + yearlycum<-rep(NA,number_of_years) + for(i in 1:number_of_years){ + to<-i*365 + yearlycum[i]<-sum(daily_observations[fr:to],na.rm = TRUE) + fr<-i*365+1 + } + return(yearlycum) +} + +#' getyearlymax +#' +#' Function for getting the maximum values of the years, from daily data +#' @author Roland Hollos +#' @param daily_observations vector of the daily observations +#' @return A vector of yearly data +#' @usage getyearlymax(daily_observations) +#' @export + +getyearlymax<-function(daily_observations){ + number_of_years<-length(daily_observations)/365 + # daily_observations[is.na(daily_observations)]<-0 # 3+NA=NA + fr<-1 + yearlycum<-rep(NA,number_of_years) + for(i in 1:number_of_years){ + to<-i*365 + yearlymax[i]<-max(daily_observations[fr:to],na.rm=TRUE) + fr<-i*365+1 + } + return(yearlymax) +} + +#' fextension +#' +#' A function for extracting the extension name from the filename string +#' @author Roland Hollos +#' @param filename The string of the filenam +#' @return the extension of the given file +#' @usage fextension(filename) + +fextension <- function(filename){ + #this function gives back the given filenames extension + fextension <- tail(unlist(strsplit(filename,"\\.")),1) + return(fextension) +} + +#'supportedMuso +#' +#' A function for getting the list of the output formats which is supported by RBBGCMuso +#' @author Roland Hollos +#' @param type "outputs" or "message", if you choose "outputs", it gives you a simple vector of the formats, if you choose "message", it gives you a full sentence which contains the same information. +#' @return if you choose "outputs", it gives you a simple vector of the formats, if you choose "message", it gives you a full sentence which contains the same information. +#' @usage supportedMuso(type="outputs") +#' @export + +supportedMuso <- function(type="outputs"){ + supportedFormats <- c("xls","xlsx","odt","csv","txt") + + if(type=="outputs"){ + #If you add new format supports, please expand the lists + return(supportedFormats) + } + if(type=="message"){ + return(cat("Supported formats are ",supportedFormats,"If your fileformat is something else, we automaticle coerced it to csv.\n")) + } +} + +#' corrigMuso +#' +#' This function leapyear-corrigate the output of the modell +#' @author Roland Hollos +#' @param settings This is the output of the setupMuso() function. It contains all of the RBBGCMuso settings +#' @param data the models outputdata +#' @return It returns the modells leapyear-corrigated output data. +#' @export +#' @usage corrigMuso(settings, data) + +corrigMuso <- function(settings, data){ + + insertRow <- function(existingDF, newrow, r){ + nr <- nrow(existingDF) + existingDF <- rbind(existingDF,rep(NA,ncol(existingDF))) + existingDF[seq(r+1,nr+1),] <- existingDF[seq(r,nr),] + existingDF[r,] <- newrow + existingDF + } + + + numdays <- nrow(data) + data <- data + numyears <- settings$numyears + leapyears <- musoLeapYears(settings) + sylvesters <- data[seq(from=365, to=numdays, by=365),] + ind <- 0 + for(i in 1:numyears){ + + if(leapyears[i]){ + data <- insertRow(data,sylvesters[i],i*360+ind) + ind <- ind+1 + } + } + return(data) +} + +## #' file.path2 +## #' +## #' It is an extended file.path function, it can concatenate path where the first ends and the second begins with "/", so +## #' there wont be two slash nearby eachother +## #' @author Roland Hollos +## #' @param str1 This is the first path string +## #' @param str2 This is the second path string +## #' @return A concatenated path +## #' @export +## #' @usage file.path2(str1, str2) + +## file.path2<-function(str1, str2){ +## if(str1==""|str1=="./"){ +## return(str2) +## } +## str1<-file.path(dirname(str1),basename(str1)) +## if(substring(str2,1,1)=="/"){ +## return(paste(str1,str2,sep="")) +## } else{ +## return(file.path(str1,str2)) +## } +## } + +numFactors <- function(x,type="pos"){ + x <- as.integer(abs(x)) + div <- seq_len(x) + posdiv <- div[x%%div==0L] + negdiv <- posdiv*-1 + alldiv <- c(negdiv,posdiv) + switch(type,"pos"=return(posdiv),"neg"=return(negdiv),"all"=return(alldiv)) +} + +niceMatrixLayoutForPlots <- function(n){ + if(n==0){ + return(cat("Ther is nothing to do with 0 graph")) + } + n <- as.integer(n) + factors <- numFactors(n) + if(length(factors)==2){ + return(n)} + sqrtn <- round(sqrt(n)) + num1 <- factors[which(min(abs(factors-sqrtn))==abs(factors-sqrtn))[1]] + num2 <- n/num1 + return(c(num1,num2)) +} + +truncNorm<-function(N,mean, sd, min, max){ +n=0 +randomNorm<-rep(NA,N) +while(n<=N){ + transNorm<-rnorm(1,mean,sd) + if((transNorm>min)&(transNorm%' +#' @importFrom tibble rownames_to_column +#' @importFrom tidyr separate gather +#' @importFrom data.table ':=' data.table +#' @export + +plotMuso <- function(settings = NULL, variable = "all", + ##compare, ##plotname, + timee = "d", silent = TRUE, + calibrationPar = NULL, parameters = NULL, + debugging = FALSE, keepEpc = FALSE, + fileToChange = "epc", logfilename = NULL, + aggressive = FALSE, leapYear = FALSE, + plotName = NULL, plotType = "cts", + layerPlot = FALSE, colour = "blue", + skipSpinup = TRUE, fromData = FALSE, + timeFrame = "day", selectYear = NULL, + groupFun = mean, separateFile = FALSE, dpi=300, postProcString = NULL){ + + if( plotType!="cts" && plotType != "dts"){ + warning(paste0("The plotType ", plotType," is not implemented, plotType is set to cts")) + plotType <- "cts" + } + + if(is.null(settings)){ + settings <- setupMuso() + } + + numberOfYears <- settings$numYears + startYear <- settings$startYear + dailyVarCodes <- settings$dailyVarCodes + groupByTimeFrame <- function(Data, timeFrame, groupFun){ + Data <- data.table(Data) + Data[,c(variable):=groupFun(get(variable)),get(timeFrame)] + Data <- as.data.frame(Data) + Data[,1] <- as.Date(Data[,1],"%d.%m.%Y") + Data + } + + if(fromData){ + Reva <- tryCatch(getdailyout(settings), #(:INSIDE: getOutput.R ) + error = function (e){ + setwd((whereAmI)) + stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")}) + colnames(Reva) <- unlist(settings$outputVars[[1]]) + rownames(Reva) <- NULL + musoData <- cbind(musoDate(startYear = startYear,numYears = numberOfYears,combined = TRUE,corrigated=FALSE), + rep(1:365,numberOfYears), + musoDate(startYear = startYear,numYears = numberOfYears,combined = FALSE,corrigated=FALSE),as.data.frame(Reva)) + colnames(musoData)[1:5]<-c("date","yearDay","year","day","month") + musoData <-musoData %>% + mutate(date=as.Date(as.character(date),"%d.%m.%Y")) + } else { + if(!is.element("cum_yieldC_HRV",unlist(settings$outputVars[[1]]))){ + musoData <- calibMuso(postProcString = postProcString,settings, + calibrationPar=calibrationPar, + parameters = parameters, + silent = TRUE,skipSpinup=skipSpinup,prettyOut = TRUE) + if(!is.null(selectYear)){ + musoData <- musoData %>% filter(year == get("selectYear")) + } + + if(timeFrame!="day"){ + musoData <- tryCatch(groupByTimeFrame(Data=musoData, timeFrame = timeFrame, groupFun = groupFun), + error=function(e){stop("The timeFrame or the groupFun is not found")}) + }} else { + musoData <- calibMuso(postProcString = postProcString,settings,silent = TRUE,skipSpinup=skipSpinup,parameters = parameters, calibrationPar = calibrationPar,fileToChange = fileToChange) %>% + as.data.frame() %>% + rownames_to_column("date") %>% + mutate(date2=date,date=as.Date(date,"%d.%m.%Y"), + yearDay=rep(1:365,numberOfYears), cum_yieldC_HRV=cum_yieldC_HRV*22.22) %>% + separate(date2,c("day","month","year"),sep="\\.") + if(!is.null(selectYear)){ + musoData <- musoData %>% filter(year == get("selectYear")) + } + + + if(timeFrame!="day"){ + musoData <- tryCatch(groupByTimeFrame(data=musoData, timeFrame = timeFrame, groupFun = groupFun), + error=function(e){stop("The timeframe or the gropFun is not found")}) + } + + } + } + + ## numVari <- ncol(musoData) + # numVari <- ncol(musoData)-5 + numVari <- length(settings$dailyVarCodes) + + pointOrLineOrPlot <- function(musoData, variableName, plotType="cts", expandPlot=FALSE, plotName=NULL){ + if(!inherits(musoData$date[1], "Date")){ + musoData$date<- as.Date(as.character(musoData$date),"%d.%m.%Y") + } + if(!expandPlot){ + if(plotType=="cts"){ + if(length(variableName)==1){ + p <- ggplot(musoData,aes_string("date",variableName,group=1))+geom_line(colour=colour)+theme(axis.title.x=element_blank()) + if(!is.null(plotName)){ + ggsave(as.character(plotName), plot = p) + p + } + p + } else { + p <- musoData %>% + select(c("date", variableName))%>% + gather(., key= outputs, value = bla, variableName) %>% + # head %>% + ggplot(aes(x=date,y=bla))+ + facet_wrap(~ outputs, scales = "free_y",ncol=1) + + geom_line(colour=colour)+ + theme( + axis.title.y = element_blank() + ) + if(!is.null(plotName)){ + ggsave(as.character(plotName), plot = p) + } + p + } + } else { + if(length(variableName)==1){ + p <- ggplot(musoData,aes_string("date",variableName))+geom_point(colour=colour)+theme(axis.title.x=element_blank()) + if(!is.null(plotName)){ + ggsave(as.character(plotName),p) + } + p + } else{ + p <- musoData %>% + select(c("date",variableName))%>% + gather(., key= outputs, value = bla,variableName) %>% + # head %>% + ggplot(aes(x=date,y=bla))+ + facet_wrap(~ outputs, scales = "free_y",ncol=1) + + geom_line(colour=colour)+ + theme( + axis.title.y = element_blank() + ) + if(!is.null(plotName)){ + ggsave(as.character(plotName),p) + } + p + + } + } + } else { + if(!is.null(plotName)){ + stop("Cannot save a single plot layer to a graphics device") + } + + if(plotType=="cts"){ + if(length(variableName)==1){ + geom_line(data=musoData, colour=colour, aes_string("date",variableName)) + + } else { + stop("you cannot add layers for multiple plots") + } + } else { + if(length(variableName)==1){ + geom_point(data=musoData, colour=colour, aes_string("date",variableName)) + } else{ + stop("you cannot add layers for multiple plots") + } + } + + } + + } + + + variableName <- as.character(settings$outputVars[[1]])[variable] + if(variable == "all"){ + variableName <- as.character(settings$outputVars[[1]]) + } + if(is.character(variable)){ + + + if(identical(variable,"all")){ + variable <- as.character(settings$outputVars[[1]]) + + } else { + + if(is.element(variable, settings$dailyVarCodes)){ + variable <- settings$outputVars[[1]][match(variable,settings$dailyVarCodes)] + } + + if(identical(character(0),setdiff(variable,as.character(settings$outputVars[[1]])))){ + variableName <- variable + } else { + if(!is.null(postProcString)){ + variableName <- variable + } else { + stop("The symmetric difference of the set of the output variables specified in the ini files and the set specified with your variable parameter is not the empty set.") + } + + } + } + + if(length(variableName)>8){ + warning("Too many variables to plot, the output quality can be poor") + } + + } else { + + if(prod(sapply(variable,function(x){ + return(x >= 0 && x <= numVari) + }))){ + variableName <- as.character(settings$outputVars[[1]])[variable] + } else { + print(numVari) + stop("Not all members of the variable parameter are among the output variables") + }} + + pointOrLineOrPlot(musoData = musoData, + variableName = variableName, + plotType = plotType, + expandPlot = layerPlot, + plotName = plotName) + } + +#'plot the Biome-BGCMuSo model output with observation data +#' +#' This function runs the Biome-BGCMuSo model and reads its output file in a well structured way, and after that it plots the results automatically along with a given measurement dataset provided by the user. plotMusoWithData is a convenient and quick method to create nice graphs from Biome-BGCMuSo output which is quite painful in other environments. +#' +#' @author Roland HOLLOS, Dora HIDY +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param sep This is the separator symbol used in the measurement file (that is supposed to be a delimited text file) +#' @param savePlot It it is specified, the plot will be saved in a graphical format specified by the immanent extension. For example, it the savePlot is set to image01.png then a PNG graphics file will be created. +#' @param variable The name of the output variable to plot +#' @param NACHAR This is not implemented yet +#' @param csvFile This specifies the filename of the measurements. It must contain a header. Typically this is a CSV file. +#' @param calibrationPar You might want to change some parameters in your EPC file before running the model. The function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8) +#' @param parameters Using the function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4). +#' @usage plotMuso(settings, variable, +#' timee="d", silent=TRUE, +#' debugging=FALSE, keepEpc=FALSE, +#' logfilename=NULL, aggressive=FALSE, +#' leapYear=FALSE, export=FALSE) +#' @importFrom ggplot2 ggplot geom_line geom_point aes aes_string labs theme element_blank +#' @export +plotMusoWithData <- function(mdata, plotName=NULL, + startDate = NULL, endDate = NULL, + colour=c("black","blue"), dataVar, modelVar, settings = setupMuso(), silent = TRUE, continious = FALSE, leapYearHandling = FALSE){ + + if(continious & (is.null(startDate) | is.null(endDate))){ + stop("If your date is continuous, you have to provide both startDate and endDate. ") + } + + dataCol<- grep(paste0("^",dataVar,"$"), colnames(mdata)) + selVar <- grep(modelVar,(settings$dailyVarCodes))+4 + + list2env(alignData(mdata, dataCol = dataCol, + modellSettings = settings, + startDate = startDate, + endDate = endDate, leapYear = leapYearHandling, continious = continious),envir=environment()) + mesData <- numeric(settings$numYears*365) + k <- 1 + for(i in seq(mesData)){ + if(i %in% modIndex){ + mesData[i] <- measuredData[k] + k <- k + 1 + } else { + mesData[i] <- NA + } + } + rm(k) + # modIndex and measuredData are created. + ## measuredData is created + ## baseData <- calibMuso(settings = settings, silent = silent, prettyOut = TRUE)[modIndex,] + baseData <- calibMuso(settings = settings, silent = silent, prettyOut = TRUE) + baseData[,1] <- as.Date(baseData[,1],format = "%d.%m.%Y") + selVarName <- colnames(baseData)[selVar] + if(!all.equal(colnames(baseData),unique(colnames(baseData)))){ + notUnique <- setdiff((unlist(settings$dailyVarCodes)),unique(unlist(settings$dailyVarCodes))) + stop(paste0("Error: daily output variable list in the ini file must contain unique numbers. Check your ini files! Not unique codes: ",notUnique)) + } + mesData<-cbind.data.frame(baseData[,1],mesData) + colnames(mesData) <- c("date", "measured") + p <- baseData %>% + ggplot(aes_string("date",selVarName)) + + geom_line(colour=colour[1]) + + geom_point(data = mesData, colour=colour[2], aes(date,measured)) + + labs(y = paste0(selVarName,"_measured"))+ + theme(axis.title.x = element_blank()) + if(!is.null(plotName)){ + ggsave(plotName,p) + return(p) + } else { + return(p) + } + +} + +#' compareMuso +#' +#' This function runs the model, then changes one of its input data, runs it again, and plots both results in one graph. +#' +#' @author Roland HOLLOS +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param parameters Using this function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4). +#' @param variable The name of the output variable to plot +#' @param calibrationPar You might want to change some parameters in your EPC file before running the model. This function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8) +#' @param fileToChange You can change any line of the EPC or the INI file. Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user. +#' @import ggplot2 +#' @export +compareMuso <- function(settings=NULL,parameters, variable=1, calibrationPar=NULL, fileToChange="epc", skipSpinup=TRUE, timeFrame="day"){ + + if(is.null(settings)){ + settings <- setupMuso() + } + + + p1 <- plotMuso(settings = settings,variable = variable,timeFrame = timeFrame) + p2 <- p1+plotMuso(settings = settings,variable = variable, timeFrame = timeFrame,fileToChange=fileToChange,layerPlot=TRUE) + p2 + +} + +#' saveAllMusoPlots +#' +#' This simple function takes the parameters from the ini files and generates graphics for all output variable. +#' +#' @author Roland HOLLOS +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param plotName The basename for the output plots +#' @param destination The destination for the output plots, it not exits the function will create it. +#' @param silent if true do not suspect for printfs... +#' @importFrom ggplot2 theme_classic ggplot geom_line geom_point theme element_blank geom_bar labs aes_string aes ggsave +#' @export + + +saveAllMusoPlots <- function(settings=NULL, plotName = ".png", + silent = TRUE, type = "line", outFile = "annual.csv", + colour = "blue", skipSpinup = FALSE){ + + if(is.null(settings)){ + settings <- setupMuso() + } + + dailyVarCodes <- settings$dailyVarCodes + annualVarCodes <-settings$annualVarCodes + outputVars <- unlist(settings$outputVars[[1]]) + musoData <- calibMuso(settings = settings, prettyOut = TRUE, silent = silent, skipSpinup = skipSpinup) + musoData$date<- as.Date(musoData$date,"%d.%m.%Y") + for(i in seq_along(dailyVarCodes)){ + bases <- ggplot(data = musoData, mapping = aes_string(x = "date", y = outputVars[i])) + object <-ifelse(type == "line",paste0("geom_line(colour = '",colour,"')"), + ifelse(type == "point",paste0("geom_line(colour = ",colour,")"), + stop("The"))) + outPlot <- bases + eval(parse(text = object)) + theme_classic() + theme(axis.title.x=element_blank()) + imName <- paste0("daily-",dailyVarCodes[i],plotName) + cat(sprintf("Saving daily output image of %s as %s\n",outputVars[i],imName)) + suppressMessages(ggsave(imName, outPlot)) + } + if(settings$normOutputFlags["annual"]!=2){ + return("Annual output graphs was not saved (no annual output from the model)") + } + musoYData <- getyearlyout(settings) + write.csv(musoYData,paste0(settings$outputNames[[2]],outFile)) + for(i in seq_along(annualVarCodes)){ + outPlot <- ggplot(data = musoYData, mapping = aes_string(x = "year", y = paste0("var_",annualVarCodes[i])))+ + geom_bar(stat = "identity")+ labs(y = musoMapping(annualVarCodes[i])) + theme_classic() + + theme(axis.title.x=element_blank()) + ggsave(paste0("annual-",annualVarCodes[i],plotName),outPlot) + } + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/postProc.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/postProc.R new file mode 100644 index 0000000..502cece --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/postProc.R @@ -0,0 +1,10 @@ +postProcMuso <- function(modelData, procString){ + cNames <- colnames(modelData) + tocalc <- gsub("(@)(\\d)","modelData[,\\2]",procString) + newVarName <- gsub("\\s","",unlist(strsplit(procString,"<-"))[1]) + assign(newVarName,eval(parse(text = unlist(strsplit(tocalc,"<-"))[2]))) + modelData <- cbind.data.frame(modelData,eval(parse(text = newVarName))) + colnames(modelData) <- c(cNames,newVarName) + modelData +} + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/postProcString.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/postProcString.R new file mode 100644 index 0000000..532ec5b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/postProcString.R @@ -0,0 +1,15 @@ +#' postProcMuso +#' +#' This is a function wich provides some minimal post processing capabilities +#' @keywords internal +postProcMuso <- function(modelData, procString){ + modelDat <- modelData[,-(1:4)] + cNames <- colnames(modelData) + tocalc <- gsub("(@)(\\d)","modelDat[,\\2]",procString) + newVarName <- gsub("\\s","",unlist(strsplit(procString,"<-"))[1]) + assign(newVarName,eval(parse(text = unlist(strsplit(tocalc,"<-"))[2]))) + modelData <- cbind.data.frame(modelData,eval(parse(text = newVarName))) + colnames(modelData) <- c(cNames,newVarName) + modelData +} + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/putOutVars.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/putOutVars.R new file mode 100644 index 0000000..5994048 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/putOutVars.R @@ -0,0 +1,32 @@ +#' putOutVars +#' +#'This function is for adding variables in the inifiles. +#' +#' @author Roland Hollos +#' @param IniFile The name of the normal ini file. +#' @param outputVars List of the output codes +#' @keywords internal +putOutVars <- function(iniFile,outputVars,modifyOriginal = FALSE){ + ini <- readLines(iniFile) + numVarsOriginal <- as.numeric(unlist(strsplit(ini[grep("DAILY_OUTPUT",ini)+1],"[\ \t]"))[1]) + if(!modifyOriginal){ + iniOut <- paste0(tools::file_path_sans_ext(basename(iniFile)),"-tmp.",tools::file_ext(iniFile)) + } else { + iniOut <- iniFile + } + + outNames <- sapply(outputVars,musoMapping) + partOne <- ini[1:grep("DAILY_OUTPUT",ini)] + partTwo <- ini[grep("ANNUAL_OUTPUT",ini):(length(ini))] + numVars <- length(outputVars) + fileContent <- c(partOne, + as.character(numVars), + sapply(outputVars,function (x) { + paste(as.character(x),musoMapping(x),sep = " ") + }), + "", + partTwo) + writeLines(fileContent,iniOut) + return(list(names=outNames,ratio=numVars/numVarsOriginal)) +} + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/quickeffect.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/quickeffect.R new file mode 100644 index 0000000..3c1e2b5 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/quickeffect.R @@ -0,0 +1,86 @@ +#' musoQuickEffect +#' +#' This function changes a chosen parameter from the INI or from the ecophysiological constants file (EPC) within a predefined range (defined by the user), and visualizes the effect of the change on the selected output variable. The user has to specify the parameter, the interval for the parameter effect test, and the number of steps. This function focuses only on one parameter. The so-called paramSweep function can manipulate multiple INI/EPC parameters and visualize the results. +#' @author Roland HOLLOS +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param startVal The initial value of the given parameter. +#' @param endVal The maximum of the given parameter. +#' @param nSteps Number of steps from startVal to endVal. It equals the number of simulations, and number of curves on the final plot. +#' @param fileTochange Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user. +#' @return Graph showing the runs with the selected parameters with color coding. The graph will show data from the last simulation year. +#' @importFrom ggplot2 ggplot aes_string geom_line geom_point aes labs theme ggsave element_blank facet_wrap +#' @importFrom dplyr filter group_by summarize mutate '%>%' tbl_df select +#' @importFrom tibble rownames_to_column +#' @importFrom magrittr '%<>%' +#' @importFrom tidyr separate +#' @export + +musoQuickEffect <- function(settings = setupMuso(), calibrationPar = NULL, startVal, endVal, nSteps = 1, fileToChange="epc",modifyOriginal=TRUE, outVar, parName = "parVal", yearNum=1, year=(settings$startYear + yearNum -1)){ + + if(is.character(outVar)){ + varNames <- as.data.frame(musoMappingFind(outVar)) + if(nrow(varNames)!=1){ + warning("There are more than one output variable in conection with ", outVar, ". The first possibility were choosen.") + print(varNames) + outVarIndex <- unlist(varNames[1,1]) + varNames <- as.character(unlist(varNames[1,2])) + } else { + outVarIndex <- unlist(varNames[1,1]) + varNames <- as.character(unlist(varNames[1,2])) + } + } else { + varNames <- musoMapping(outVar) + outVarIndex<-outVar + } + + if(is.null(calibrationPar)){ + calibrationPar <- settings$calibrationPar + } + + parVals <- seq(startVal, endVal, length = (nSteps + 1)) + parVals <- dynRound(startVal, endVal, seqLen = (nSteps + 1)) + a <- do.call(rbind,lapply(parVals, function(parVal){ + calResult <- tryCatch(calibMuso(settings = settings,calibrationPar = calibrationPar, + modifyOriginal = modifyOriginal, + parameters = parVal, + outVars = outVarIndex, + silent = TRUE, + fileToChange = fileToChange), error = function(e){NULL}) + if(is.null(calResult)){ + b <- cbind(rep(NA,365),parVal) + rownames(b) <- musoDate(startYear = year, numYears = 1) + colnames(b)[1] <- varNames + return(b) + } else { + if(yearNum >=0){ + m <- as.data.frame(calResult[musoDate(startYear = year, numYears = 1),]) + } else{ + m <- as.data.frame(calResult) + } + colnames(m) <- colnames(calResult) + return(cbind(m, parVal)) + } + + })) + a %<>% + tbl_df %>% + mutate(date=as.Date(rownames(a),"%d.%m.%Y")) %>% + select(date,as.character(varNames),parVal) + print(suppressWarnings(ggplot(data = a, aes_string(x= "date", y= varNames))+geom_line(aes(alpha = factor(parVal))) + labs(y=varNames, alpha = parName) + scale_alpha_discrete(range=c(0.25,1)))) +} +# calma <- calibMuso(settings = settings,calibrationPar = calibrationPar, +# modifyOriginal = modifyOriginal, +# parameters = parVal, +# outVars = outVarIndex, +# silent = TRUE, +# fileToChange = fileToChange) +# plot(calma[,1]) +# calma <- calibMuso(settings = settings,calibrationPar = calibrationPar, +# modifyOriginal = modifyOriginal, +# parameters = parVal, +# silent = TRUE, +# fileToChange = fileToChange) +# calm <- calibMuso(calibrationPar=calibrationPar,parameters=parVal,modifyOriginal=TRUE) +# plot(x=as.Date(musoDate(2015,numYears=1),"%d.%m.%Y"),y=calm[musoDate(2015,numYears=1),"daily_gpp"],type="l") +# calibrationPar +# parVal diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/runMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/runMuso.R new file mode 100644 index 0000000..2a77f30 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/runMuso.R @@ -0,0 +1,28 @@ +#' runMuso +#' +#' This function runs the Biome-BGCMuSo model (with option to change the EPC file), then it reads its output file in a well-structured way. As the result is passed to R, the results can be easily post-processed in R environment. +#' +#' @author Roland HOLL\'{O}S +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param timee The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet. +#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory to stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved. +#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory. +#' @param export If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv. +#' @param silent IIf you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution. +#' @param aggressive It deletes all previous model-outputs from previous model runs. +#' @param parameters Using normalMuso it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4). +#' @param logfilename If you would like to set a specific name for your logfiles you can set this via the logfile parameter. +#' @param leapYear Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years. +#' @param keepBinary By default RBBGCMuso keeps the working environment as clean as possible, thus deletes all the regular output files. The results are directly written to the standard output (e.g. to the screen), but you can redirect it and save them to a variable. Alternatively, you can export your results to the desired destination in a desired format. Through the keepBinary parameter you can set RBBGCMuso to keep the binary output files. If you would like to set the location of the binary output, please take a look at the binaryPlace argument. +#' @param binaryPlace The directory for the binary output files (see the keepBinary parameter). +#' @param fileToChange You can change any line of the EPC or the INI file prior to model execution. All you need to do is to specify with this variable which file you want to change. Two options possible: "EPC" or "INI" +#' @param skipSpinup If this is set to TRUE, runMuso will not perform the spinup simulation. This is of course means that the endpoint file (initial conditions) must be available for the normal INI file. This option might be extremely useful to speed up multiple model execution. In cropland related simulations due to site history the EPC file used in the normal phase might differ from the one used in the spinup phase, which means that the spinup is the same even if we change the parameterization for the normal phase. In this situation skipSpinup is really useful. +#' @param prettyOut If this parameter is to TRUE then date will provided as the R-style Date type, and separate year, month and day vectors. In typical cases the user should use this option. +#' @return No return, outputs are written to file +#' @usage calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, +#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +#' @import utils +#' @export +runMuso <- function(...){ + calibMuso(...) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/rungetMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/rungetMuso.R new file mode 100644 index 0000000..07dbc84 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/rungetMuso.R @@ -0,0 +1,278 @@ +#'rungetMuso +#' +#' This function runs the BBGC-MuSo model and reads in its outputfile in a very structured way. +#' +#' @author Roland Hollos +#' @param settings You have to run the setupMuso function before rungetMuso. It is its output which contains all of the necessary system variables. It sets the whole environment +#' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly +#' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles +#' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory. +#' @param export if it is yes or you give a filename here, it converts the output to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv. +#' @param silent If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed. +#' @param aggressive It deletes every possible modell-outputs from the previous modell runs. +#' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled. +#' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter +#' @return It depends on the export parameter. The function returns with a matrix with the modell output, or writes this in a file, which is given previously +#' @usage rungetMuso(settings, timee="d", debugging=FALSE, logfilename=NULL, +#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +#' @import utils +#' @export + + + +rungetMuso <- function(settings, timee="d", debugging=FALSE, logfilename=NULL, keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE){ + + + + +########################################################################## +###########################Set local variables######################## +######################################################################## + + Linuxp <-(Sys.info()[1]=="Linux") + ##Copy the variables from settings + inputLoc <- settings$inputLoc + outputLoc <- settings$outputLoc + executable <- settings$executable + iniInput <- settings$iniInput + epc <- settings$epcInput + calibrationPar <- settings$calibrationPar + whereAmI<-getwd() + +############################################################# +############################spinup run############################ +########################################################## + + + ##Sometimes a bug occure due to logfiles and controlfiles in the input loc directory + + + if(silent!=TRUE){ + if(length(grep("(dayout$)|(log$)",list.files(inputLoc)))>0){ + cat(" \n \n WARMING: there is a log or dayout file nearby the ini files, that may cause problemes. \n \n If you want to avoid that possible problemes, please copy the log or dayout files into a save place, and after do a cleanupMuso(), or delete these manually, or run the rungetMuso(), with the agressive=TRUE parameter \n \n") + + } + + } + + if(aggressive==TRUE){ + cleanupMuso(location=outputLoc, deep=TRUE) + } + + ##We change the working directory becase of the model, but we want to avoid sideeffects, so we save the current location and after that we will change everything to it. + + ## Set the working directory to the inputLoc temporary. + setwd(inputLoc) + + + ##Run the model for the spinup run. + + if(silent){#silenc mode + if(Linuxp){ + #In this case, in linux machines + system(paste(executable,iniInput[1],"> /dev/null",sep=" ")) + } else { + #In windows machines there is a show.output.on.console option + system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE) + } + + } else { + system(paste(executable,iniInput[1],sep=" ")) + } + + + + logspinup<-list.files(outputLoc)[grep("log$",list.files(outputLoc))]#load the logfiles + if(length(logspinup)==0){ + return("Modell Failure")#in that case the modell did not create even a logfile + } + + + if(length(logspinup)>1){ + spincrash<-TRUE + } else { + if(identical(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1),character(0))){ + spincrash<-TRUE + } else { + spincrash<-(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)!=1) + } + } + + + + if(!spincrash){##If spinup did not crashed, run the normal run. + +##################################################################### +###########################normal run######################### +################################################################# + + ##for the sake of safe we set the location again + setwd(inputLoc) + + if(silent){ + if(Linuxp){ + system(paste(executable,iniInput[2],"> /dev/null",sep=" ")) + } else { + system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE) + } + + } else { + system(paste(executable,iniInput[2],sep=" ")) + } + + + ##read the output + + switch(timee, + "d"=(Reva<-getdailyout(settings)), + "m"=(Reva<-getmonthlyout(settings)), + "y"=(Reva<-getyearlyout(settings)) + ) + } + + + logfiles <- list.files(outputLoc)[grep("log$",list.files(outputLoc))]#creating a vector for logfilenames + +############################################### +#############LOG SECTION####################### +############################################### + + perror<-as.numeric(as.vector(lapply(paste(outputLoc,logfiles,sep="/"),function(x) tail(readLines(x,-1),1)))) #vector of spinup and normalrun error + + if((debugging=="stamplog")|(debugging==TRUE)){#If debugging option turned on + ##If log or ERROR directory does not exists create it! + dirName<-paste(inputLoc,"LOG",sep="") + dirERROR<-paste(inputLoc,"ERROR",sep="") + + if(!dir.exists(dirName)){ + dir.create(dirName) + } + + if(!dir.exists(dirERROR)){ + dir.create(dirERROR) + } + } + + ##if errorsign is 1 there is error, if it is 0 everything ok + if(length(perror)>sum(perror)){ + errorsign <- 1 + + } else { + if(spincrash){ + errorsign <- 1 + } else { + errorsign <- 0 + } + } + + + if(keepEpc){#if keepepc option tured on + + if(length(unique(dirname(epc)))>1){ + print("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?") + } else { + epcdir <- dirname(epc[1]) + + WRONGEPC<-paste(inputLoc,"WRONGEPC",sep="") + EPCS<-paste(inputLoc,"EPCS",sep="") + + if(!dir.exists(WRONGEPC)){ + dir.create(WRONGEPC) + } + + if(!dir.exists(EPCS)){ + dir.create(EPCS) + } + + epcfiles <- list.files(epcdir)[grep("epc$",list.files(epcdir))] + stampnum<-stamp(EPCS) + lapply(epcfiles,function (x) file.copy(from = paste(epcdir,"/",x,sep=""),to=paste(EPCS,"/",(stampnum+1),"-",x,sep=""))) + if(errorsign==1){ + lapply(epcfiles,function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",x,sep=""), to=WRONGEPC)) + } + + } + } + + + + + + if(debugging=="stamplog"){ + stampnum<-stamp(dirName) + if(inputLoc==outputLoc){ + lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",(stampnum+1),"-",x,sep=""))) + + } else { + lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",(stampnum+1),"-",x,sep=""))) + } + + if(errorsign==1){ + lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",(stampnum+1),"-",x,sep=""), to=dirERROR ))} + + } else { if(debugging){ + if(is.null(logfilename)){ + + if(inputLoc==outputLoc){ + lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName,"/", x, sep=""))) + } else { + lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName,"/", x, sep=""))) + } + + if(errorsign==1){ + lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR)) + } + + } else { + + if(inputLoc==outputLoc){#These are very ugly solutions for a string problem: inputLoc: "./", if outputLoc equalent of inputLoc, it ends with "/", the string manipulation can not handle this. The better solution is easy, but I dont have enough time(Roland Hollo's) + lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",logfilename,"-",x,sep=""))) + } else { + lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",logfilename,"-",x,sep=""))) + } + + if(errorsign==1){ + lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR)) + } + } + + }} + + cleanupMuso(location=outputLoc) + if(errorsign==1){ + return("Modell Failure") + } + + if(timee=="d"){ + colnames(Reva) <- unlist(settings$outputVars[[1]]) + } else { + if(timee=="y") + colnames(Reva) <- unlist(settings$outputVars[[2]]) + } + + if(leapYear){ + Reva <- corrigMuso(settings,Reva) + rownames(Reva) <- musoDate(settings$startYear, settings$numYears) + } else { + rownames(Reva) <- musoDate(settings$startYear, settings$numYears, corrigated=FALSE) + } + + if(export!=FALSE){ + setwd(whereAmI) + + ## switch(fextension(export), + ## "csv"=(write.csv(Reva,export)), + ## "xlsx"=(), + ## "odt"= + + + ## ) + write.csv(Reva,export) + + } else{ + setwd(whereAmI) + return(Reva)} +} + + + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/setupMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/setupMuso.R new file mode 100644 index 0000000..15892b1 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/setupMuso.R @@ -0,0 +1,354 @@ +#' setupMuso +#' +#' The setupMuso is fundamental for the Biome-BGCMuSo model related other functions like runMuso, spinupMuso, normalMuso, rungetMuso, as it sets the model's environment. The function reads the INI files from a given directory, analyzes them with error checking, and creates a data structure in R that contains the complete information content for the simulation. +#' +#' @author Roland HOLLOS +#' @param parallel Set this variable to TRUE if you would like to implement parallel execution of the model +#' @param executable This parameter stores the location (directory) of the model-executable file. In normal usage, you don't have to set this parameter, because the RBBGCMuso package always contains the latest model executable. In spite of this, if you would like to use this package for model development or just want to use different model version (for example for comparison), you will find this option useful +#' @param calibrationPar You might want to change some parameters in your EPC file before running the model. setupMuso offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8) +#' @param outputLoc With this parameter the user can specify the directory for the model output. The syntax is simple, for example: outputLoc="/place/of/the/outputs/" or outputLoc="C:/my_model_directory/". Note that this output directory is specified by the user within the INI file, which means that the outputLoc parameter overrides the INI settings if specified. +#' @param inputLoc Usually this is the root (or base) directory where the user stores the INI files for the model. If the working directory is set by the user, this parameter can be skipped. +#' @param metInput Via the metInput parameter the user can specify the location of the input meteorological files. By default the package reads this information from the INI files. +#' @param CO2Input Via the CO2Input parameter the user can specify the location of the CO2 data file. By default the package reads this information from the INI files. +#' @param plantInput Via the plantInput parameter, the user can specify the location of the the file that contains the planting information. By default the package reads this information from the INI files. +#' @param thinInput Via the thinInput parameter,the user can specify the location of the file that contains the thinning information. By default the package reads this information from the INI files. +#' @param mowInput Via the mowInput parameter, the user can specify the location of the file that contains the mowing (i.e. grass cutting) information. By default the package reads this information from the INI files. +#' @param grazInput Via the grazInput parameter, the user can specify the location of the file that contains the grazing information. By default the package reads this information from the INI files. +#' @param harvInput Via the harvInput parameter, the user can specify the location of the file that contains the harvesting information. By default the package reads this information from the INI files. +#' @param plougInput Via the plougInput parameter, the user can specify the location of the file that contains the ploughing information. By default the package reads this information from the INI files. +#' @param fertInput Via the fertInput parameter, the user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files. +#' @param irrInput Via the irrInput parameter, the user can specify the location of the file that contains the irrigation information. By default the package reads this information from the INI files. +#' @param nitInput Via the nitInput parameter, the user can specify the location of the file that contains the nitrogen deposition data. By default the package reads this information from the INI files. +#' @param iniInput Via the iniInput parameter, the user can specify the location of the INI files. By default the package reads the INI files from the working directory. +#' @param epcInput Via the epcInput parameter, the user can specify the location of the EPC data file. By default the package reads this information from the INI files. +#' @param modelOutputs This parameter contains the list of the codes that defines the required model output variables. Check the Biome-BGCMuS website for the complete list of possible output variables at http://agromo.agrar.mta.hu/bbgc/download.html +#' @usage setupMuso(executable=NULL, parallel = F, calibrationPar =c(1), +#' outputLoc=NULL, inputLoc=NULL, +#' metInput=NULL, CO2Input=NULL, +#' plantInput=NULL, thinInput=NULL, +#' mowInput=NULL, grazInput=NULL, +#' harvInput=NULL, plougInput=NULL, +#' fertInput=NULL, irrInput=NULL, +#' nitInput=NULL, iniInput=NULL, epcInput=NULL) +#' @return The output is a the model settings list wich contains the following elements: +#' executable, calibrationPar, outputLoc, outputName, inputLoc, iniInput, metInput, epcInput,thinInput,CO2Input, mowInput, grazInput, harvInput, plougInput, fertInput,rrInput, nitInput, inputFiles, numData, startyear, numYears, outputVars +#' @export + +setupMuso <- function(executable=NULL, + parallel = F, + calibrationPar =c(1), + outputLoc=NULL, + modelOutputs=NULL, + inputLoc=NULL, + metInput=NULL, + CO2Input=NULL, + plantInput=NULL, + thinInput=NULL, + mowInput=NULL, + grazInput=NULL, + harvInput=NULL, + plougInput=NULL, + fertInput=NULL, + irrInput=NULL, + nitInput=NULL, + iniInput=NULL, + epcInput=NULL, + mapData=NULL, + leapYear=FALSE, + version=6, + doCopy=TRUE + ){ + + Linuxp <-(Sys.info()[1]=="Linux") + writep <- 0 + + # if(is.null(mapData)&version==4){ + # mData <- mMapping4 + # } + # + + inputParser <- function(string,fileName,counter,value=TRUE){ + unlist(strsplit(grep(string,fileName,value=TRUE, perl = TRUE),"[\ \t]", useBytes = TRUE))[counter] + } + + # outMaker <- function(inputVar,grepString,filep){ + # tempVar <- eval(parse(text=inputVar)) + # if(is.null(tempVar)){ + # writep <<- writep+1 + # if(filep) + # { + # tempVar["spinup"] <- file.path(inputLoc,inputParser(string=grepString,fileName=iniFiles$spinup,counter=1,value=TRUE)) + # tempVar["normal"] <- file.path(inputLoc,inputParser(string=grepString,fileName=iniFiles$normal,counter=1,value=TRUE)) + # } else { + # tempVar["spinup"] <- inputParser(string=grepString,fileName=iniFiles$spinup,counter=1,value=TRUE) + # tempVar["normal"] <- inputParser(string=grepString,fileName=iniFiles$normal,counter=1,value=TRUE) + # + # } + # + # } else { + # iniFiles$spinup[grep(grepString,iniFiles$spinup)] <<- paste0(tempVar[1],"\t ",grepString) + # + # if(length(tempVar)==2){ + # iniFiles$normal[grep(" grepString",iniFiles$normal)] <<- paste0(tempVar[2],"\t ",grepString) + # } + # } + # return(tempVar) + # } + + if(is.null(inputLoc)){ + inputLoc<- normalizePath("./") + } else{ + inputLoc <- normalizePath(inputLoc) + } + + #iniChangedp <- FALSE + + if(is.null(iniInput)){ + spinups<-grep("s.ini$",list.files(inputLoc),value=TRUE, perl = TRUE) + normals<-grep("n.ini$",list.files(inputLoc),value=TRUE, perl = TRUE) + + if(length(spinups)==1){ + iniInput[1] <- file.path(inputLoc,spinups) + } else { + iniInput[1] <- "no spinup" + # stop("There are multiple or no spinup ini files, please choose") + } + + + if(length(normals)==1){ + iniInput[2]<-file.path(inputLoc,normals) + } else {stop("There are multiple or no normal ini files, please choose")} + + } + + ##read the ini files for the further changes + + iniFiles<-lapply(iniInput, function (x) readLines(x,-1)) + iniFiles[[1]] <- gsub("\\\\","/", iniFiles[[1]], perl = TRUE) #replacing \ to / + iniFiles[[2]] <- gsub("\\\\","/", iniFiles[[2]], perl = TRUE) #replacing \ to / + names(iniFiles) <- c("spinup","normal") + + + + # inputs <- lapply(1:nrow(grepHelper), function (x) { + # + # outMaker(grepHelper[x,1],grepHelper[x,2],grepHelper[x,3]) + # + # }) + # names(inputs) <- grepHelper$inputVar + ## grepHelper is in sysdata.rda it is a table like this: + ## + ## inputVar string isFile + ## 1 epcInput EPC file name TRUE + ## 2 metInput met file name TRUE + ## 3 CO2Input CO2 file TRUE + ## 4 nitInput N-dep file TRUE + ## 5 thinInput do THINNING FALSE + ## 6 plantInput do PLANTING FALSE + ## 7 mowInput do MOWING FALSE + ## 8 grazInput do GRAZING FALSE + ## 9 harvInput do HARVESTING FALSE + ## 10 plougInput do PLOUGHING FALSE + ## 11 fertInput do FERTILIZING FALSE + ## 12 irrInput do IRRIGATION FALSE + # return(inputs) debug element + + + # if(is.null(mapData)){ + # + outIndex<-grep("DAILY_OUTPUT",iniFiles[[2]], perl = TRUE)+1 + numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][outIndex],"[\ \t]", useBytes = TRUE))[1]) + dailyVarCodes<-tryCatch(iniFiles[[2]][(outIndex+1):(outIndex+numVar)], + error = function(e){ + stop("Cannot read indexes of output variables from the normal ini file, please make sure you have not skiped a line after the flag: \"DAILY_OUTPUT\"") + }) + + dailyVarCodes<-unlist(lapply(dailyVarCodes, function(x) unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1])) + dailyVarnames<-unlist(lapply(dailyVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1]))) + + outIndex<-grep("ANNUAL_OUTPUT",iniFiles[[2]], perl = TRUE)+1 + numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][outIndex],"[\ \t]", useBytes = TRUE))[1]) + annualVarCodes<-iniFiles[[2]][(outIndex+1):(outIndex+numVar)] + annualVarCodes<-unlist(lapply(annualVarCodes, function(x) unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1])) + annualVarnames<-unlist(lapply(annualVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1]))) + outputVars<-list(dailyVarnames,annualVarnames) + # browser() +# } else { +# +# c<-grep("DAILY_OUTPUT",iniFiles[[2]])+1 +# numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1]) +# dailyVarCodes<-iniFiles[[2]][(c+1):(c+numVar)] +# dailyVarnames<-lapply(dailyVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1],mapData)) +# +# c<-grep("ANNUAL_OUTPUT",iniFiles[[2]])+1 +# numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1]) +# annualVarCodes<-iniFiles[[2]][(c+1):(c+numVar)] +# annualVarnames<-lapply(annualVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1],mapData)) +# outputVars<-list(dailyVarnames,annualVarnames) +# +# +# +# } + + + + if(is.null(executable)){ + if(Linuxp){ + executable<-file.path(inputLoc,"muso") + } else { + executable<-file.path(inputLoc,"muso.exe") + } + } else { + if(doCopy){ + file.copy(executable,inputLoc) + } + + } + + outputName <- character(2) + outputName[1] <- basename(unlist(strsplit(iniFiles[[1]][grep("OUTPUT_CONTROL",iniFiles[[1]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1]) + outputName[2] <- basename(unlist(strsplit(iniFiles[[2]][grep("OUTPUT_CONTROL",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1]) + ## outputName <- unlist(strsplit(grep("output",grep("prefix",iniFiles[[2]],value=TRUE),value=TRUE),"[\ \t]"))[1] + ##THIS IS AN UGLY SOLUTION, WHICH NEEDS AN UPGRADE!!! FiXED (2017.09.11) + ## outputName <- unlist(strsplit(grep("prefix for output files",iniFiles[[2]],value=TRUE),"[\ \t]"))[1] + if(is.null(outputName)){ + stop("I cannot find outputName in your default ini file \n Please make sure that the line wich contains the name also contains the prefix and the output keywords!") + + } + ## outputName<-unlist(read.table(iniInput[2],skip=93,nrows = 1))[1] + + + if(is.null(outputLoc)){ + ## outputLoc<-paste((rev(rev(unlist(strsplit(outputName,"/")))[-1])),collapse="/") + outputLoc <- dirname(unlist(strsplit(iniFiles[[2]][grep("OUTPUT_CONTROL",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1]) + if(substr(outputLoc,start = 1,stop = 1)!="/"){ + ##if the outputName is not absolute path make it absolute + outputLoc <- file.path(inputLoc,outputLoc) + } + } else { + outputLoc <- normalizePath(outputLoc) + } + + + + inputFiles<-c(iniInput,epcInput,metInput) + numData<-rep(NA,3) + numYears <- as.numeric(unlist(strsplit(iniFiles[[2]][grep("TIME_DEFINE",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1]) + ## numYears<-unlist(read.table(iniInput[2],skip = 14,nrows = 1)[1]) + numValues <- as.numeric(unlist(strsplit(iniFiles[[2]][grep("DAILY_OUTPUT",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1]) + ## numValues will be replaced to numVar + ## numValues<-unlist(read.table(iniInput[2],skip=102,nrows = 1)[1]) + startYear <- as.numeric(unlist(strsplit(iniFiles[[2]][grep("TIME_DEFINE",iniFiles[[2]], perl = TRUE)+2],"[\ \t]", useBytes = TRUE))[1]) + numData[1] <- numValues * numYears * 365 # Have to corrigate leapyears + + numData[2] <- numYears * numValues*12 + numData[3] <- numYears * numValues + + ##Writing out changed ini-file + + writeLines(iniFiles[[1]],iniInput[1]) + writeLines(iniFiles[[2]],iniInput[2]) + + if(!is.null(modelOutputs)){ + outVarChanges <- putOutVars(iniFile = iniInput[2],outputVars = modelOutputs, modifyOriginal = TRUE) + numData <- round(numDate*outVarChanges[[2]]) + outputVars[[1]] <-outVarChanges[[1]] + } + + + suppressWarnings(file.remove(paste0(file.path(outputLoc,outputName[1]),".log"))) + ## I use file.path additionally because We do not know if outputLoc ends or not to "/" + suppressWarnings(file.remove(paste0(file.path(outputLoc,outputName[2]),".log"))) + + searchBellow <- function(inFile, key, stringP = TRUE, n=1, management = FALSE){ + + if(stringP){ + unlist(strsplit(inFile[grep(key,inFile, perl=TRUE)+n],split = "\\s+", useBytes = TRUE))[1] + } else { + as.numeric(unlist(strsplit(inFile[grep(key,inFile,perl=TRUE)+n],split = "\\s+", useBytes = TRUE))[1]) + } + } + + normOutputFlags <- c( + daily=searchBellow(iniFiles[[2]], "OUTPUT_CONTROL",stringP=FALSE,n=2), + annual=searchBellow(iniFiles[[2]], "OUTPUT_CONTROL",stringP=FALSE,n=5)) + if(normOutputFlags[1]!=1){ + warning("You should set your daily output flag to 1 (binary) RBBRMuso work only with binary output...") + } + searchBellow(iniFiles[[2]], "OUTPUT_CONTROL",stringP=FALSE,n=5) + soilFile <- NULL + if(version >=6){ + soilFiles <- tryCatch(sapply(iniFiles,function(x){(searchBellow(x,"SOIL_FILE"))}),error = function(e){""}) + } + epcFiles <- tryCatch(sapply(iniFiles,function(x){(searchBellow(x,"EPC_FILE"))}),error = function(e){""}) + metInput <- tryCatch(sapply(iniFiles,function(x){(searchBellow(x,"MET_INPUT"))}),error = function(e){""}) + dailyOutputTable <- cbind.data.frame(seq_along(dailyVarCodes),dailyVarCodes,outputVars[[1]]) + colnames(dailyOutputTable) <- c("index","code","name") + annualOutputTable <- cbind.data.frame(seq_along(annualVarCodes),annualVarCodes,outputVars[[2]]) + colnames(annualOutputTable) <- c("index","code","name") + + settings = list(executable = executable, + calibrationPar = calibrationPar, + outputLoc=outputLoc, + outputNames=outputName, + inputLoc=inputLoc, + iniInput=iniInput, + metInput=metInput, + epcInput=epcFiles, + # thinInput=inputs$thinInput, + # CO2Input=inputs$CO2Input, + # mowInput=inputs$mowInput, + # grazInput=inputs$grazInput, + # harvInput=inputs$harvInput, + # plougInput=inputs$plougInput, + # fertInput=inputs$fertInput, + # irrInput=inputs$irrInput, + # nitInput=inputs$nitInput, + inputFiles=inputFiles, + numData=numData, + startYear=startYear, + numYears=numYears, + outputVars=outputVars, + soilFile=soilFiles, + dailyVarCodes= gsub("\\s.*","",dailyVarCodes), + annualVarCodes = gsub("\\s.*","",annualVarCodes), + dailyOutputTable=dailyOutputTable, + annualOutputTable=annualOutputTable, + normOutputFlags=normOutputFlags + ) + + # if(getOption("RMuso_version")==6){ + # manFile <- scan(iniInput[2],what="",n=1,skip=44,sep=" ") # HARDCODED -> UNTIL JSON VERSION + # mgm <- readLines(manFile) + # mgmConn <- file(manFile,open="r") + # manTypes <- c("planting","thinning","mowing","grazing","harvesting","ploughing","fertilizing","irrigating") + # mgmFiles <- rep("none",length(manTypes)) + # if(scan(mgmConn,skip=3,n=1,what=integer())==1){ + # mgmFiles[1] <- scan(mgmConn,skip=1,n=1,what="", sep = " ") + # } + # for(i in 2:length(mgmFiles)){ + # if(scan(mgmConn,skip=2,n=1,what=integer())==1){ + # mgmFiles[i] <- scan(mgmConn,skip=1,n=1,what="", sep =" " ) + # } else { + # blackhole<-scan(mgmConn,skip =1, n=1,what="") + # } + # } + # names(mgmFiles) <- manTypes + # settings[["management"]] <- mgmFiles + # close(manConn) + # } + + + # if(writep!=nrow(grepHelper)){ + # writeLines(iniFiles[[1]],iniInput[[1]]) + # if(inputs$epcInput[1]!=inputs$epc$Input[2]){ #Change need here + # writeLines(iniFiles[[2]],iniInput[[2]]) + # } + # } + + suppressWarnings(dir.create(file.path(inputLoc,"bck"))) + # sapply(iniFiles,epc) + return(settings) + +} + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/setupMuso6.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/setupMuso6.R new file mode 100644 index 0000000..d6f465b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/setupMuso6.R @@ -0,0 +1,47 @@ +## #' setupMuso6 +## #' +## #' This is the setup function for MuSo version: 6 +## #' +## #' @author Roland HOLLOS +## #' @param setupFile +## #' @export + +## setupMuso6<- function(setupFile){ + +## } + +## ini <- readLines("./hhs_apriori_MuSo6_normal.ini") +## flags <- c("MET_INPUT", +## "RESTART", +## "TIME_DEFINE", +## "CO2_CONTROL", +## "NDEP_CONTROL", +## "SITE", +## "SOILPROP_FILE", +## "EPC_FILE", +## "MANAGEMENT_FILE", +## "SIMULATION_CONTROL", +## "W_STATE", +## "CN_STATE", +## "CLIM_CHANGE", +## "CONDITIONAL_MANAGEMENT_STRATEGIES", +## "OUTPUT_CONTROL", +## "DAILY_OUTPUT", +## "ANNUAL_OUTPUT", +## "END_INIT") +## getSegments <- function(ini, flags){ +## output <- list() +## flagIterator <- 1:(length(flags)-1) +## for(i in flagIterator){ +## output[[flags[i]]] <- lapply(ini[(grep(flags[i],ini)+1):(grep(flags[i+1],ini)-2)], function(x){ +## unlist(strsplit(x,split = "\\["))[1] +## }) +## } +## output +## } +## getSegments(ini,flags) + +## gsub("(.*\\[\\|)([a-zA-Z1-9_]*)","",ini) +## stringi::stri_trim_right("rexamine.com/", "\\[r\\]") +## stri_extract("asdfasdf [|Ezat|]",regex = "\\[\\|*\\]") +## lapply(ini,function(x) gsub("\\s","",(strsplit(x,split= "T]"))[[1]][2])) diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/soilQuery.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/soilQuery.R new file mode 100644 index 0000000..6c4e189 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/soilQuery.R @@ -0,0 +1,73 @@ +#' getSoilDataFull +#' +#' This function collects soil data from a given restapi, de default is soilGrid +#' +#' @author Roland HOLLÓS +#' @name getSoilDataFull +#' @importFrom glue glue +#' @importFrom httr config with_config GET content + +getSoilDataFull <- function(lat, lon, apiURL) { + if(missing(apiURL)){ + apiURL <- "https://81.169.232.36" + } + apiString <- glue("{apiURL}/query?lon={lon}&lat={lat}") + soilREST <- #with_config(config(ssl_verifypeer=0L, ssl_verifyhost=0L), + GET(apiString) # ) # This is temporary solution ssl_verification wont bypass + content(soilREST) +} + +#' createSoilFile +#' +#' This function collects soil data from a given restapi, de default is soilGrid +#' +#' @author Roland HOLLOS +#' @name createSoilFile +#' @importFrom glue glue +#' @importFrom stats approx +#' @importFrom magrittr '%>%' +#' @export + +createSoilFile <- function(lat,lon, + outputFile="recent.soi", + method="constant",apiURL, + template=system.file("examples/hhs/hhs.soi",package="RBBGCMuso")) { + if(missing(apiURL)){ + apiURL <- "https://rest.soilgrids.org/soilgrids/v2.0/properties" + } + outFile <- suppressWarnings(readLines(template)) + outFile[1] <- sprintf("SOILPROP FILE - lat: %s, lon: %s, created in: %s",lat,lon,date()) + musoCenters <- c(1.5,6.5,20.0,45.0,75.0,105.0,135.0,175.0,300.0,700.0) + # soilGridDepths <- c(0,5,15,30,60,100,200) + soilGridDepths <- c(2.5, 10, 22.5, 45, 80, 150) + Reduce(function(x,y){(y-x)/2+x},soilGridDepths,accumulate=TRUE) + rest<- getSoilDataFull(lat,lon, apiURL) + + + createMusoLayers <- function(values,depths=soilGridDepths,centers=musoCenters,intMethod=method){ + approx(x=depths,y=values, xout = centers, method=intMethod,rule=2)$y %>% + paste(.,collapse="\t") %>% paste0(.," ") + } + + soilDepth <- tryCatch(getMeanSoil(rest,"bdod")/100,error=function(e){stop("There is no data for the given coordinates")}) + outFile[55] <- sprintf("%s (%%) percentage of sand by volume in rock free soil", + paste(createMusoLayers(getMeanSoil(rest,"sand")/10), collapse="\t")) + outFile[56] <- sprintf("%s (%%) percentage of silt by volume in rock free soil", + paste(createMusoLayers(getMeanSoil(rest,"silt")/10), collapse="\t")) + outFile[57] <- sprintf("%s (dimless) soil PH", + paste(createMusoLayers(getMeanSoil(rest,"phh2o")/10), collapse="\t")) + # outFile[58] <- sprintf("%s (%%) bulk density",paste(createMusoLayers(soilDepth),collapse="\t")) + writeLines(outFile,outputFile) +} +# createSoilFile(60,50) + +getMeanSoil <- function(rest, name){ + sapply( + rest$properties$layers[sapply(rest$properties$layers,function(x){ + x$name == name + })][[1]]$depths, + function(s){ + s$values$mean + } + ) +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/spinupMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/spinupMuso.R new file mode 100644 index 0000000..3392c97 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/spinupMuso.R @@ -0,0 +1,136 @@ +#' Runs the Biome-BGCMuSo model in spinup phase (execution of normal phase is possible with normalMuso) with debugging features. +#' +#' This function runs the Biome-BGCMuSo model in spinup phase. +#' +#' @author Roland HOLLOS +#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option. +#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory to stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved. +#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory. +#' @param silent If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution. +#' @param aggressive It deletes all previous model-outputs from previous model runs. +#' @param parameters |||| In the parameters variable you have set the row indices of the variables that you wish to change. In this parameter you can provide an exact value for them in a vector form like c(1,2,3,4) +#' @param logfilename If you would like to set a specific name for the logfiles you can set this via the logfilename parameter +#' @return No return, outputs are written to file +#' @usage spinupMuso(settings, parameters=NULL, debugging=FALSE, +#' logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE) +#' @export + +spinupMuso <- function(settings=NULL, parameters=NULL, debugging=FALSE, logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE, fileToChange="epc"){ + +########################################################################## +###########################Set local variables######################## +######################################################################## + + if(is.null(settings)){ + settings <- setupMuso() #(:INSIDE: setupMuso.R) + + } + # The software works on Linux or Windows, Mac is not implemented yet, so with this simple dichotomy we can determine wich system is running + Linuxp <-(Sys.info()[1]=="Linux") + ##Copy the variables from settings for the sake of easy + inputLoc <- settings$inputLoc + outputLoc <- settings$outputLoc + outputNames <- settings$outputNames + executable <- settings$executable + iniInput <- settings$iniInput + epc <- settings$epcInput + calibrationPar <- settings$calibrationPar + + ## We want to minimize the number of sideeffects so we store the state to restore in the end. + whereAmI<-getwd() + + +############################################################# +############################spinup run############################ +########################################################## + + ## obsolete feature, but there can be cases in wich this option is helpfull + if(aggressive==TRUE){ + cleanupMuso(location=outputLoc,deep=TRUE)} #(:INSIDE: cleanup.R) + + ## If parameters given, use changemulline, else leave this steps + + if(!is.null(parameters)){ + switch(fileToChange, + "epc" = tryCatch(changemulline(filename = epc[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R) + error = function (e) {stop("Cannot change the epc file")}), + "ini" = tryCatch(changemulline(filename = iniInput[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R) + error = function (e) {stop("Cannot change the ini file")}), + "both" = (stop("This option is not implemented yet, please choose epc or ini")) + ) + } + + ## Set the working directory to the inputLoc temporary. + setwd(inputLoc) + + + ##Run the spinup modell + + if(silent){#silenc mode + if(Linuxp){ + #In this case, in linux machines + tryCatch(system(paste(executable,iniInput[1],"> /dev/null",sep=" ")), + error= function (e){stop("Cannot run the modell-check the executable!")}) + } else { + #In windows machines there is a show.output.on.console option + tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE), + error= function (e){stop("Cannot run the modell-check the executable!")}) + }} else { + system(paste(executable,iniInput[1],sep=" ")) + } +############################################### +#############LOG SECTION####################### +############################################### + + logspinup <- getLogs(outputLoc,outputNames,type="spinup") #(:INSIDE: assistantFunctions.R) + + if(length(logspinup)==0){ + if(keepEpc){ + stampnum<-stamp(EPCS) + lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep=""))) + lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC)) + setwd(whereAmI) + stop("Modell Failure") + } + setwd(whereAmI) + stop("Modell Failure") #in that case the modell did not create even a logfile + } + + if(length(logspinup)>1){ + spincrash<-TRUE + } else { + if(identical(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1),character(0))){ + spincrash<-TRUE + } else { + spincrash <- (tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)!=1) + } + } + + dirName<-normalizePath(paste(inputLoc,"/LOG",sep="")) + dirERROR<-paste0(inputLoc,"/ERROR") + + if(!dir.exists(dirName)){ + dir.create(dirName)} + + if(!dir.exists(dirERROR)){ + dir.create(dirERROR)} + + if(spincrash){ + errorsign <- 1 + } else { + errorsign <- 0} + + + + if(debugging==TRUE){ + stampAndDir(outputLoc=outputLoc,stampDir=dirName, names=logspinup, type="output") #(:INSIDE: assistantFunctions.R) + } + + + + if(errorsign==1){ + stop("Modell Failure") + } + + +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/stamplog.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/stamplog.R new file mode 100644 index 0000000..b9a8fd9 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/R/stamplog.R @@ -0,0 +1,33 @@ +#' This function returns only the starting numbers of a string +#' +#' This function returns only the starting numbers of a string +#' @author Roland Hollos +#' @keywords internal + +numcut<-function(string){ + #This function returns only the starting numbers of a string + unlist(strsplit(grep("^[0-9]",string,value = TRUE),"[aAzZ-]"))[1] +} + +#' numcutall +#' +#' apply numcut for all elements of a string vector +#' @author Roland Hollos +#' @keywords internal +numcutall<-function(vector){ + #numcall apply numcut for all elements of a string vector +as.numeric(unlist(apply(as.matrix(vector),1,numcut))) +} + +#' It gives back a stamp wich is the maximum number of the output numcall +#' +#' It gives back a stamp wich is the maximum number of the output numcall +#' @author Roland Hollos +#' @keywords internal +stamp<-function(path="./"){ + #It gives back a stamp wich is the maximum number of the output numcall + numbers<-numcutall(list.files(path)) + if(length(numbers)==0){ + return (0)} else { + return(max(numbers))} +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/build/vignette.rds b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/build/vignette.rds new file mode 100644 index 0000000..1ca0eff Binary files /dev/null and b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/build/vignette.rds differ diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/constMatrix5.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/constMatrix5.json new file mode 100644 index 0000000..d691e1b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/constMatrix5.json @@ -0,0 +1 @@ +[{"X":1,"NAME":"yearday to start new growth","INDEX":9,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":2,"NAME":"yearday to end new growth","INDEX":10,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":3,"NAME":"transfer growth period as fraction of growing season","INDEX":11,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":4,"NAME":"litterfall as fraction of growing season","INDEX":12,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":5,"NAME":"base temperature","INDEX":13,"UNIT":"Celsius","MIN":0,"MAX":12,"GROUP":0,"TYPE":0},{"X":6,"NAME":"minimum temperature for growth displayed on current day","INDEX":14,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":1,"TYPE":1},{"X":7,"NAME":"optimal1 temperature for growth displayed on current day","INDEX":15,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":1,"TYPE":1},{"X":8,"NAME":"optimal2 temperature for growth displayed on current day","INDEX":16,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":1,"TYPE":1},{"X":9,"NAME":"maxmimum temperature for growth displayed on current day","INDEX":17,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":1,"TYPE":1},{"X":10,"NAME":"minimum temperature for carbon assimilation displayed on current day","INDEX":18,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":2,"TYPE":1},{"X":11,"NAME":"optimal1 temperature for carbon assimilation displayed on current day","INDEX":19,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":2,"TYPE":1},{"X":12,"NAME":"optimal2 temperature for carbon assimilation displayed on current day","INDEX":20,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":2,"TYPE":1},{"X":13,"NAME":"maxmimum temperature for carbon assimilation displayed on current day","INDEX":21,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":2,"TYPE":1},{"X":14,"NAME":"annual leaf and fine root turnover fraction","INDEX":22,"UNIT":"1/yr","MIN":0.1,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":15,"NAME":"annual live wood turnover fraction","INDEX":23,"UNIT":"1/yr","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":16,"NAME":"annual fire mortality fraction","INDEX":24,"UNIT":"1/yr","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":17,"NAME":"whole-plant mortality paramter for vegetation period","INDEX":25,"UNIT":"1/vegper","MIN":0,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":18,"NAME":"C:N of leaves","INDEX":26,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":10,"MAX":100,"GROUP":0,"TYPE":0},{"X":19,"NAME":"C:N of leaf litter","INDEX":27,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":20,"NAME":"C:N of fine roots","INDEX":28,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":21,"NAME":"C:N of fruit","INDEX":29,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":22,"NAME":"C:N of softstem","INDEX":30,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":23,"NAME":"C:N of live wood","INDEX":31,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":50,"MAX":100,"GROUP":4,"TYPE":1},{"X":24,"NAME":"C:N of dead wood","INDEX":32,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":300,"MAX":800,"GROUP":4,"TYPE":1},{"X":25,"NAME":"dry matter content of leaves","INDEX":33,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":26,"NAME":"dry matter content of leaf litter","INDEX":34,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":27,"NAME":"dry matter content of fine roots","INDEX":35,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":28,"NAME":"dry matter content of fruit","INDEX":36,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":29,"NAME":"dry matter content of softstem","INDEX":37,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":30,"NAME":"dry matter content of live wood","INDEX":38,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":31,"NAME":"dry matter content of dead wood","INDEX":39,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":32,"NAME":"leaf litter labile proportion","INDEX":40,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":33,"NAME":"leaf litter cellulose proportion","INDEX":41,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":34,"NAME":"fine root labile proportion","INDEX":42,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":35,"NAME":"fine root cellulose proportion","INDEX":43,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":36,"NAME":"fruit labile proportion","INDEX":44,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":37,"NAME":"fruit cellulose proportion","INDEX":45,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":38,"NAME":"softstem labile proportion","INDEX":46,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":39,"NAME":"softstem cellulose proportion","INDEX":47,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":40,"NAME":"dead wood cellulose proportion","INDEX":48,"UNIT":"prop","MIN":0.5,"MAX":0.9,"GROUP":0,"TYPE":0},{"X":41,"NAME":"canopy water interception coefficient","INDEX":49,"UNIT":"1/LAI/d","MIN":0.01,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":42,"NAME":"canopy light extinction coefficient","INDEX":50,"UNIT":"dimless","MIN":0.2,"MAX":0.8,"GROUP":0,"TYPE":0},{"X":43,"NAME":"potential radiation use efficiency","INDEX":51,"UNIT":"g/MJ","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":44,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":52,"UNIT":"dimless","MIN":0.781,"MAX":0.781,"GROUP":0,"TYPE":0},{"X":45,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":53,"UNIT":"dimless","MIN":-13.596,"MAX":-13.596,"GROUP":0,"TYPE":0},{"X":46,"NAME":"all-sided to projected leaf area ratio","INDEX":54,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":47,"NAME":"ratio of shaded SLA:sunlit SLA","INDEX":55,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":48,"NAME":"fraction of leaf N in Rubisco","INDEX":56,"UNIT":"dimless","MIN":0.01,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":49,"NAME":"fraction of leaf N in PeP","INDEX":57,"UNIT":"dimless","MIN":0.0424,"MAX":0.0424,"GROUP":0,"TYPE":0},{"X":50,"NAME":"maximum stomatal conductance ","INDEX":58,"UNIT":"m/s","MIN":0.001,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":51,"NAME":"cuticular conductance ","INDEX":59,"UNIT":"m/s","MIN":1e-05,"MAX":0.0001,"GROUP":0,"TYPE":0},{"X":52,"NAME":"boundary layer conductance","INDEX":60,"UNIT":"m/s","MIN":0.01,"MAX":0.09,"GROUP":0,"TYPE":0},{"X":53,"NAME":"maximum height of plant","INDEX":61,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":54,"NAME":"stem weight corresponding to maximum height","INDEX":62,"UNIT":"kgC","MIN":0.1,"MAX":100,"GROUP":0,"TYPE":0},{"X":55,"NAME":"plant height function shape parameter (slope)","INDEX":63,"UNIT":"dimless","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":56,"NAME":"maximum depth of rooting zone","INDEX":64,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":57,"NAME":"root distribution parameter","INDEX":65,"UNIT":"prop","MIN":3.67,"MAX":3.67,"GROUP":0,"TYPE":0},{"X":58,"NAME":"root weight corresponding to max root depth","INDEX":66,"UNIT":"kgC/m2","MIN":0.4,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":59,"NAME":"root depth function shape parameter (slope)","INDEX":67,"UNIT":"prop","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":60,"NAME":"root weight to rooth length conversion factor","INDEX":68,"UNIT":"m/kg","MIN":1000,"MAX":1000,"GROUP":0,"TYPE":0},{"X":61,"NAME":"growth resp per unit of C grown","INDEX":69,"UNIT":"prop","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":62,"NAME":"maintenance respiration in kgC/day per kg of tissue N ","INDEX":70,"UNIT":"kgC/kgN/d","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":63,"NAME":"theoretical maximum prop. of non-structural and structural carbohydrates","INDEX":71,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":64,"NAME":"prop. of non-structural carbohydrates available for maintanance resp","INDEX":72,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":65,"NAME":"symbiotic+asymbiotic fixation of N","INDEX":73,"UNIT":"kgN/m2/yr","MIN":0,"MAX":0.001,"GROUP":0,"TYPE":0},{"X":66,"NAME":"time delay for temperature in photosynthesis acclimation","INDEX":74,"UNIT":"day","MIN":0,"MAX":50,"GROUP":0,"TYPE":0},{"X":67,"NAME":"critical VWCratio (prop. to FC-WP) in germination","INDEX":79,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":68,"NAME":"critical photoslow daylength","INDEX":81,"UNIT":"hour","MIN":14,"MAX":18,"GROUP":0,"TYPE":0},{"X":69,"NAME":"slope of relative photoslow development rate ","INDEX":82,"UNIT":"dimless","MIN":0.005,"MAX":0.005,"GROUP":0,"TYPE":0},{"X":70,"NAME":"critical vernalization temperature 1","INDEX":84,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":9,"TYPE":1},{"X":71,"NAME":"critical vernalization temperature 2","INDEX":85,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":9,"TYPE":1},{"X":72,"NAME":"critical vernalization temperature 3","INDEX":86,"UNIT":"Celsius","DEPENDENCE":2,"MIN":5,"MAX":15,"GROUP":9,"TYPE":1},{"X":73,"NAME":"critical vernalization temperature 4","INDEX":87,"UNIT":"Celsius","DEPENDENCE":3,"MIN":10,"MAX":20,"GROUP":9,"TYPE":1},{"X":74,"NAME":"slope of relative vernalization development rate ","INDEX":88,"UNIT":"dimless","MIN":0.04,"MAX":0.04,"GROUP":0,"TYPE":0},{"X":75,"NAME":"required vernalization days (in vernalization development rate)","INDEX":89,"UNIT":"dimless","MIN":30,"MAX":70,"GROUP":0,"TYPE":0},{"X":76,"NAME":"critical flowering heat stress temperature 1","INDEX":91,"UNIT":"Celsius","DEPENDENCE":0,"MIN":30,"MAX":40,"GROUP":10,"TYPE":1},{"X":77,"NAME":"critical flowering heat stress temperature 2","INDEX":92,"UNIT":"Celsius","DEPENDENCE":1,"MIN":30,"MAX":50,"GROUP":10,"TYPE":1},{"X":78,"NAME":"theoretical maximum of flowering thermal stress mortality","INDEX":93,"UNIT":"prop","MIN":0,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":79,"NAME":"VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)","INDEX":96,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":80,"NAME":"VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)","INDEX":97,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":81,"NAME":"minimum of soil moisture limit2 multiplicator (full anoxic stress value)","INDEX":98,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":82,"NAME":"vapor pressure deficit: start of conductance reduction","INDEX":99,"UNIT":"Pa","MIN":500,"MAX":1500,"GROUP":0,"TYPE":0},{"X":83,"NAME":"vapor pressure deficit: complete conductance reduction","INDEX":100,"UNIT":"Pa","MIN":1500,"MAX":3500,"GROUP":0,"TYPE":0},{"X":84,"NAME":"maximum senescence mortality coefficient of aboveground plant material","INDEX":101,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":85,"NAME":"maximum senescence mortality coefficient of belowground plant material","INDEX":102,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":86,"NAME":"maximum senescence mortality coefficient of non-structured plant material","INDEX":103,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":87,"NAME":"lower limit extreme high temperature effect on senescence mortality","INDEX":104,"UNIT":"Celsius","MIN":30,"MAX":40,"GROUP":0,"TYPE":0},{"X":88,"NAME":"upper limit extreme high temperature effect on senescence mortality","INDEX":105,"UNIT":"Celsius","MIN":30,"MAX":50,"GROUP":0,"TYPE":0},{"X":89,"NAME":"turnover rate of wilted standing biomass to litter","INDEX":106,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":90,"NAME":"turnover rate of cut-down non-woody biomass to litter","INDEX":107,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":91,"NAME":"turnover rate of cut-down woody biomass to litter","INDEX":108,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":92,"NAME":"drought tolerance parameter (critical value of day since water stress)","INDEX":109,"UNIT":"n_day","MIN":0,"MAX":100,"GROUP":0,"TYPE":0},{"X":93,"NAME":"crit. amount of snow limiting photosyn.","INDEX":112,"UNIT":"kg/m2","MIN":0,"MAX":20,"GROUP":0,"TYPE":0},{"X":94,"NAME":"limit1 (under:full constrained) of HEATSUM index","INDEX":113,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":50,"GROUP":11,"TYPE":1},{"X":95,"NAME":"limit2 (above:unconstrained) of HEATSUM index","INDEX":114,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":100,"GROUP":11,"TYPE":1},{"X":96,"NAME":"limit1 (under:full constrained) of TMIN index","INDEX":115,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":12,"TYPE":1},{"X":97,"NAME":"limit2 (above:unconstrained) of TMIN index","INDEX":116,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":12,"TYPE":1},{"X":98,"NAME":"limit1 (above:full constrained) of VPD index","INDEX":117,"UNIT":"Pa","DEPENDENCE":0,"MIN":2000,"MAX":600,"GROUP":13,"TYPE":1},{"X":99,"NAME":"limit2 (under:unconstrained) of VPD index","INDEX":118,"UNIT":"Pa","DEPENDENCE":1,"MIN":500,"MAX":1500,"GROUP":13,"TYPE":1},{"X":100,"NAME":"limit1 (under:full constrained) of DAYLENGTH index","INDEX":119,"UNIT":"s","DEPENDENCE":0,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":101,"NAME":"limit2 (above:unconstrained) of DAYLENGTH index","INDEX":120,"UNIT":"s","DEPENDENCE":1,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":102,"NAME":"moving average (to avoid the effects of extreme events)","INDEX":121,"UNIT":"n_day","MIN":2,"MAX":20,"GROUP":0,"TYPE":0},{"X":103,"NAME":"GSI limit1 (greater that limit -> start of vegper)","INDEX":122,"UNIT":"dimless","MIN":0,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":104,"NAME":"GSI limit2 (less that limit -> end of vegper)","INDEX":123,"UNIT":"dimless","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":105,"NAME":"length of phenophase (GDD)","INDEX":127,"UNIT":"Celsius","MIN":0,"MAX":10000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -0","INDEX":128.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-0","INDEX":129.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -0","INDEX":130.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-0","INDEX":131.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -0","INDEX":132.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -0","INDEX":133.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-0","INDEX":134.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -0","INDEX":135.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-0","INDEX":136.6,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-0","INDEX":137.6,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-0","INDEX":138.6,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -1","INDEX":128.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-1","INDEX":129.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -1","INDEX":130.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-1","INDEX":131.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -1","INDEX":132.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -1","INDEX":133.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-1","INDEX":134.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -1","INDEX":135.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-1","INDEX":136.61,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-1","INDEX":137.61,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-1","INDEX":138.61,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -2","INDEX":128.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-2","INDEX":129.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -2","INDEX":130.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-2","INDEX":131.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -2","INDEX":132.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -2","INDEX":133.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-2","INDEX":134.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -2","INDEX":135.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-2","INDEX":136.62,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-2","INDEX":137.62,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-2","INDEX":138.62,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -3","INDEX":128.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-3","INDEX":129.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -3","INDEX":130.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-3","INDEX":131.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -3","INDEX":132.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -3","INDEX":133.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-3","INDEX":134.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -3","INDEX":135.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-3","INDEX":136.63,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-3","INDEX":137.63,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-3","INDEX":138.63,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -4","INDEX":128.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-4","INDEX":129.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -4","INDEX":130.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-4","INDEX":131.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -4","INDEX":132.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -4","INDEX":133.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-4","INDEX":134.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -4","INDEX":135.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-4","INDEX":136.64,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-4","INDEX":137.64,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-4","INDEX":138.64,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -5","INDEX":128.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-5","INDEX":129.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -5","INDEX":130.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-5","INDEX":131.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -5","INDEX":132.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -5","INDEX":133.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-5","INDEX":134.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -5","INDEX":135.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-5","INDEX":136.65,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-5","INDEX":137.65,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-5","INDEX":138.65,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -6","INDEX":128.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-6","INDEX":129.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -6","INDEX":130.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-6","INDEX":131.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -6","INDEX":132.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -6","INDEX":133.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-6","INDEX":134.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -6","INDEX":135.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-6","INDEX":136.66,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-6","INDEX":137.66,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-6","INDEX":138.66,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0}] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/constMatrix6.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/constMatrix6.json new file mode 100644 index 0000000..6fcfe03 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/constMatrix6.json @@ -0,0 +1,190 @@ +[ + {"X": "1", "NAME": "yearday to start new growth", "INDEX": "9", "UNIT": "yday", "MIN": "0", "MAX": "364", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "2", "NAME": "yearday to end new growth", "INDEX": "10", "UNIT": "yday", "MIN": "0", "MAX": "364", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "3", "NAME": "transfer growth period as fraction of growing season", "INDEX": "11", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "4", "NAME": "litterfall as fraction of growing season", "INDEX": "12", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "5", "NAME": "base temperature", "INDEX": "13", "UNIT": "Celsius", "MIN": "0", "MAX": "12", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "6", "NAME": "minimum temperature for growth displayed on current day", "INDEX": "14", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "0", "GROUP": "1", "TYPE": "1"}, + {"X": "7", "NAME": "optimal1 temperature for growth displayed on current day", "INDEX": "15", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "1", "GROUP": "1", "TYPE": "1"}, + {"X": "8", "NAME": "optimal2 temperature for growth displayed on current day", "INDEX": "16", "UNIT": "Celsius", "MIN": "20", "MAX": "40", "DEPENDENCE": "2", "GROUP": "1", "TYPE": "1"}, + {"X": "9", "NAME": "maxmimum temperature for growth displayed on current day", "INDEX": "17", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "3", "GROUP": "1", "TYPE": "1"}, + {"X": "10", "NAME": "minimum temperature for carbon assimilation displayed on current day", "INDEX": "18", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "0", "GROUP": "2", "TYPE": "1"}, + {"X": "11", "NAME": "optimal1 temperature for carbon assimilation displayed on current day", "INDEX": "19", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "1", "GROUP": "2", "TYPE": "1"}, + {"X": "12", "NAME": "optimal2 temperature for carbon assimilation displayed on current day", "INDEX": "20", "UNIT": "Celsius", "MIN": "20", "MAX": "40", "DEPENDENCE": "2", "GROUP": "2", "TYPE": "1"}, + {"X": "13", "NAME": "maxmimum temperature for carbon assimilation displayed on current day", "INDEX": "21", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "3", "GROUP": "2", "TYPE": "1"}, + {"X": "14", "NAME": "annual leaf and fine root turnover fraction", "INDEX": "22", "UNIT": "1/yr", "MIN": "0.1", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "15", "NAME": "annual live wood turnover fraction", "INDEX": "23", "UNIT": "1/yr", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "16", "NAME": "annual fire mortality fraction", "INDEX": "24", "UNIT": "1/yr", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "17", "NAME": "whole-plant mortality paramter for vegetation period", "INDEX": "25", "UNIT": "1/vegper", "MIN": "0", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "18", "NAME": "C:N of leaves", "INDEX": "26", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "100", "DEPENDENCE": "0", "GROUP": "3", "TYPE": "1"}, + {"X": "19", "NAME": "C:N of leaf litter", "INDEX": "27", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "20", "NAME": "C:N of fine roots", "INDEX": "28", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "21", "NAME": "C:N of fruit", "INDEX": "29", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "22", "NAME": "C:N of softstem", "INDEX": "30", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "23", "NAME": "C:N of live wood", "INDEX": "31", "UNIT": "kgC/kgN", "MIN": "50", "MAX": "100", "DEPENDENCE": "0", "GROUP": "4", "TYPE": "1"}, + {"X": "24", "NAME": "C:N of dead wood", "INDEX": "32", "UNIT": "kgC/kgN", "MIN": "300", "MAX": "800", "DEPENDENCE": "1", "GROUP": "4", "TYPE": "1"}, + {"X": "25", "NAME": "dry matter content of leaves", "INDEX": "33", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "26", "NAME": "dry matter content of leaf litter", "INDEX": "34", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "27", "NAME": "dry matter content of fine roots", "INDEX": "35", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "28", "NAME": "dry matter content of fruit", "INDEX": "36", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "29", "NAME": "dry matter content of softstem", "INDEX": "37", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "30", "NAME": "dry matter content of live wood", "INDEX": "38", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "31", "NAME": "dry matter content of dead wood", "INDEX": "39", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "32", "NAME": "leaf litter labile proportion", "INDEX": "40", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "5", "TYPE": "2"}, + {"X": "33", "NAME": "leaf litter cellulose proportion", "INDEX": "41", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "5", "TYPE": "2"}, + {"X": "34", "NAME": "fine root labile proportion", "INDEX": "42", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "6", "TYPE": "2"}, + {"X": "35", "NAME": "fine root cellulose proportion", "INDEX": "43", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "6", "TYPE": "2"}, + {"X": "36", "NAME": "fruit labile proportion", "INDEX": "44", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "7", "TYPE": "2"}, + {"X": "37", "NAME": "fruit cellulose proportion", "INDEX": "45", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "7", "TYPE": "2"}, + {"X": "38", "NAME": "softstem labile proportion", "INDEX": "46", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "8", "TYPE": "2"}, + {"X": "39", "NAME": "softstem cellulose proportion", "INDEX": "47", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "8", "TYPE": "2"}, + {"X": "40", "NAME": "dead wood cellulose proportion", "INDEX": "48", "UNIT": "prop", "MIN": "0.5", "MAX": "0.9", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "41", "NAME": "canopy water interception coefficient", "INDEX": "49", "UNIT": "1/LAI/d", "MIN": "0.01", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "42", "NAME": "canopy light extinction coefficient", "INDEX": "50", "UNIT": "dimless", "MIN": "0.2", "MAX": "0.8", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "43", "NAME": "potential radiation use efficiency", "INDEX": "51", "UNIT": "g/MJ", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "44", "NAME": "radiation parameter1 (Jiang et al.2015)", "INDEX": "52", "UNIT": "dimless", "MIN": "0.781", "MAX": "0.781", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "45", "NAME": "radiation parameter1 (Jiang et al.2015)", "INDEX": "53", "UNIT": "dimless", "MIN": "-13.596", "MAX": "-13.596", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "46", "NAME": "all-sided to projected leaf area ratio", "INDEX": "54", "UNIT": "dimless", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "47", "NAME": "ratio of shaded SLA:sunlit SLA", "INDEX": "55", "UNIT": "dimless", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "48", "NAME": "fraction of leaf N in Rubisco", "INDEX": "56", "UNIT": "dimless", "MIN": "0.01", "MAX": "0.2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "49", "NAME": "fraction of leaf N in PeP", "INDEX": "57", "UNIT": "dimless", "MIN": "0.0424", "MAX": "0.0424", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "50", "NAME": "maximum stomatal conductance", "INDEX": "58", "UNIT": "m/s", "MIN": "0.001", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "51", "NAME": "cuticular conductance", "INDEX": "59", "UNIT": "m/s", "MIN": "1E-05", "MAX": "0.0001", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "52", "NAME": "boundary layer conductance", "INDEX": "60", "UNIT": "m/s", "MIN": "0.01", "MAX": "0.09", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "53", "NAME": "maximum height of plant", "INDEX": "61", "UNIT": "m", "MIN": "0.1", "MAX": "10", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "54", "NAME": "stem weight corresponding to maximum height", "INDEX": "62", "UNIT": "kgC", "MIN": "0.1", "MAX": "100", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "55", "NAME": "plant height function shape parameter (slope)", "INDEX": "63", "UNIT": "dimless", "MIN": "0.5", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "56", "NAME": "maximum depth of rooting zone", "INDEX": "64", "UNIT": "m", "MIN": "0.1", "MAX": "10", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "57", "NAME": "root distribution parameter", "INDEX": "65", "UNIT": "prop", "MIN": "3.67", "MAX": "3.67", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "58", "NAME": "root weight corresponding to max root depth", "INDEX": "66", "UNIT": "kgC/m2", "MIN": "0.4", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "59", "NAME": "root depth function shape parameter (slope)", "INDEX": "67", "UNIT": "prop", "MIN": "0.5", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "60", "NAME": "root weight to rooth length conversion factor", "INDEX": "68", "UNIT": "m/kg", "MIN": "1000", "MAX": "1000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "61", "NAME": "growth resp per unit of C grown", "INDEX": "69", "UNIT": "prop", "MIN": "0.1", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "62", "NAME": "maintenance respiration in kgC/day per kg of tissue N", "INDEX": "70", "UNIT": "kgC/kgN/d", "MIN": "0.1", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "63", "NAME": "theoretical maximum prop. of non-structural and structural carbohydrates", "INDEX": "71", "UNIT": "dimless", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "64", "NAME": "prop. of non-structural carbohydrates available for maintanance resp", "INDEX": "72", "UNIT": "dimless", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "65", "NAME": "symbiotic+asymbiotic fixation of N", "INDEX": "73", "UNIT": "kgN/m2/yr", "MIN": "0", "MAX": "0.001", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "66", "NAME": "time delay for temperature in photosynthesis acclimation", "INDEX": "74", "UNIT": "day", "MIN": "0", "MAX": "50", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "67", "NAME": "critical VWCratio (prop. to FC-WP) in germination", "INDEX": "79", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "68", "NAME": "critical photoslow daylength", "INDEX": "81", "UNIT": "hour", "MIN": "14", "MAX": "18", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "69", "NAME": "slope of relative photoslow development rate", "INDEX": "82", "UNIT": "dimless", "MIN": "0.005", "MAX": "0.005", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "70", "NAME": "critical vernalization temperature 1", "INDEX": "84", "UNIT": "Celsius", "MIN": "-5", "MAX": "5", "DEPENDENCE": "0", "GROUP": "9", "TYPE": "1"}, + {"X": "71", "NAME": "critical vernalization temperature 2", "INDEX": "85", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "1", "GROUP": "9", "TYPE": "1"}, + {"X": "72", "NAME": "critical vernalization temperature 3", "INDEX": "86", "UNIT": "Celsius", "MIN": "5", "MAX": "15", "DEPENDENCE": "2", "GROUP": "9", "TYPE": "1"}, + {"X": "73", "NAME": "critical vernalization temperature 4", "INDEX": "87", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "3", "GROUP": "9", "TYPE": "1"}, + {"X": "74", "NAME": "slope of relative vernalization development rate", "INDEX": "88", "UNIT": "dimless", "MIN": "0.04", "MAX": "0.04", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "75", "NAME": "required vernalization days (in vernalization development rate)", "INDEX": "89", "UNIT": "dimless", "MIN": "30", "MAX": "70", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "76", "NAME": "critical flowering heat stress temperature 1", "INDEX": "91", "UNIT": "Celsius", "MIN": "30", "MAX": "40", "DEPENDENCE": "0", "GROUP": "10", "TYPE": "1"}, + {"X": "77", "NAME": "critical flowering heat stress temperature 2", "INDEX": "92", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "1", "GROUP": "10", "TYPE": "1"}, + {"X": "78", "NAME": "theoretical maximum of flowering thermal stress mortality", "INDEX": "93", "UNIT": "prop", "MIN": "0", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "79", "NAME": "VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)", "INDEX": "96", "UNIT": "prop", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "80", "NAME": "VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)", "INDEX": "97", "UNIT": "prop", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "81", "NAME": "minimum of soil moisture limit2 multiplicator (full anoxic stress value)", "INDEX": "98", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "82", "NAME": "vapor pressure deficit: start of conductance reduction", "INDEX": "99", "UNIT": "Pa", "MIN": "500", "MAX": "1500", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "83", "NAME": "vapor pressure deficit: complete conductance reduction", "INDEX": "100", "UNIT": "Pa", "MIN": "1500", "MAX": "3500", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "84", "NAME": "maximum senescence mortality coefficient of aboveground plant material", "INDEX": "101", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "85", "NAME": "maximum senescence mortality coefficient of belowground plant material", "INDEX": "102", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "86", "NAME": "maximum senescence mortality coefficient of non-structured plant material", "INDEX": "103", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "87", "NAME": "lower limit extreme high temperature effect on senescence mortality", "INDEX": "104", "UNIT": "Celsius", "MIN": "30", "MAX": "40", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "88", "NAME": "upper limit extreme high temperature effect on senescence mortality", "INDEX": "105", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "89", "NAME": "turnover rate of wilted standing biomass to litter", "INDEX": "106", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "90", "NAME": "turnover rate of cut-down non-woody biomass to litter", "INDEX": "107", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "91", "NAME": "turnover rate of cut-down woody biomass to litter", "INDEX": "108", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "92", "NAME": "drought tolerance parameter (critical value of day since water stress)", "INDEX": "109", "UNIT": "n_day", "MIN": "0", "MAX": "100", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "93", "NAME": "crit. amount of snow limiting photosyn.", "INDEX": "112", "UNIT": "kg/m2", "MIN": "0", "MAX": "20", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "94", "NAME": "limit1 (under:full constrained) of HEATSUM index", "INDEX": "113", "UNIT": "Celsius", "MIN": "0", "MAX": "50", "DEPENDENCE": "0", "GROUP": "11", "TYPE": "1"}, + {"X": "95", "NAME": "limit2 (above:unconstrained) of HEATSUM index", "INDEX": "114", "UNIT": "Celsius", "MIN": "0", "MAX": "100", "DEPENDENCE": "1", "GROUP": "11", "TYPE": "1"}, + {"X": "96", "NAME": "limit1 (under:full constrained) of TMIN index", "INDEX": "115", "UNIT": "Celsius", "MIN": "-5", "MAX": "5", "DEPENDENCE": "0", "GROUP": "12", "TYPE": "1"}, + {"X": "97", "NAME": "limit2 (above:unconstrained) of TMIN index", "INDEX": "116", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "1", "GROUP": "12", "TYPE": "1"}, + {"X": "98", "NAME": "limit1 (above:full constrained) of VPD index", "INDEX": "117", "UNIT": "Pa", "MIN": "2000", "MAX": "600", "DEPENDENCE": "0", "GROUP": "13", "TYPE": "1"}, + {"X": "99", "NAME": "limit2 (under:unconstrained) of VPD index", "INDEX": "118", "UNIT": "Pa", "MIN": "500", "MAX": "1500", "DEPENDENCE": "1", "GROUP": "13", "TYPE": "1"}, + {"X": "100", "NAME": "limit1 (under:full constrained) of DAYLENGTH index", "INDEX": "119", "UNIT": "s", "MIN": "0", "MAX": "0", "DEPENDENCE": "0", "GROUP": "14", "TYPE": "1"}, + {"X": "101", "NAME": "limit2 (above:unconstrained) of DAYLENGTH index", "INDEX": "120", "UNIT": "s", "MIN": "0", "MAX": "0", "DEPENDENCE": "1", "GROUP": "14", "TYPE": "1"}, + {"X": "102", "NAME": "moving average (to avoid the effects of extreme events)", "INDEX": "121", "UNIT": "n_day", "MIN": "2", "MAX": "20", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "103", "NAME": "GSI limit1 (greater that limit -> start of vegper)", "INDEX": "122", "UNIT": "dimless", "MIN": "0", "MAX": "0.2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "104", "NAME": "GSI limit2 (less that limit -> end of vegper)", "INDEX": "123", "UNIT": "dimless", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-0", "INDEX": "127.6", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -0", "INDEX": "128.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-0", "INDEX": "129.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -0", "INDEX": "130.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-0", "INDEX": "131.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -0", "INDEX": "132.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -0", "INDEX": "133.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-0", "INDEX": "134.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -0", "INDEX": "135.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-0", "INDEX": "136.6", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-0", "INDEX": "137.6", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-0", "INDEX": "138.6", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-1", "INDEX": "127.61", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -1", "INDEX": "128.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-1", "INDEX": "129.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -1", "INDEX": "130.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-1", "INDEX": "131.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -1", "INDEX": "132.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -1", "INDEX": "133.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-1", "INDEX": "134.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -1", "INDEX": "135.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-1", "INDEX": "136.61", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-1", "INDEX": "137.61", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-1", "INDEX": "138.61", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-2", "INDEX": "127.62", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -2", "INDEX": "128.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-2", "INDEX": "129.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -2", "INDEX": "130.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-2", "INDEX": "131.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -2", "INDEX": "132.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -2", "INDEX": "133.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-2", "INDEX": "134.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -2", "INDEX": "135.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-2", "INDEX": "136.62", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-2", "INDEX": "137.62", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-2", "INDEX": "138.62", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-3", "INDEX": "127.63", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -3", "INDEX": "128.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-3", "INDEX": "129.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -3", "INDEX": "130.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-3", "INDEX": "131.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -3", "INDEX": "132.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -3", "INDEX": "133.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-3", "INDEX": "134.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -3", "INDEX": "135.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-3", "INDEX": "136.63", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-3", "INDEX": "137.63", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-3", "INDEX": "138.63", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-4", "INDEX": "127.64", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -4", "INDEX": "128.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-4", "INDEX": "129.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -4", "INDEX": "130.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-4", "INDEX": "131.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -4", "INDEX": "132.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -4", "INDEX": "133.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-4", "INDEX": "134.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -4", "INDEX": "135.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-4", "INDEX": "136.64", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-4", "INDEX": "137.64", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-4", "INDEX": "138.64", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-5", "INDEX": "127.65", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -5", "INDEX": "128.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-5", "INDEX": "129.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -5", "INDEX": "130.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-5", "INDEX": "131.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -5", "INDEX": "132.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -5", "INDEX": "133.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-5", "INDEX": "134.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -5", "INDEX": "135.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-5", "INDEX": "136.65", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-5", "INDEX": "137.65", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-5", "INDEX": "138.65", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-6", "INDEX": "127.6", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -6", "INDEX": "128.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-6", "INDEX": "129.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -6", "INDEX": "130.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-6", "INDEX": "131.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -6", "INDEX": "132.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -6", "INDEX": "133.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-6", "INDEX": "134.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -6", "INDEX": "135.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-6", "INDEX": "136.66", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-6", "INDEX": "137.66", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-6", "INDEX": "138.66", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"} +] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/depTree.csv b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/depTree.csv new file mode 100644 index 0000000..afa513a --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/depTree.csv @@ -0,0 +1,18 @@ +"child","parent","mod","name" +"wth","ini",1,"weather" +"endpoint","ini",1,"endpointIn" +"endpoint","ini",2,"endpointOut" +"txt","ini",1,"co2" +"txt","ini",2,"nitrogen" +"soi","ini",1,"soil" +"epc","ini",1,"startEpc" +"mgm","ini",1,"management" +"plt","mgm",1,"planting" +"thn","mgm",1,"thining" +"mow","mgm",1,"mowing" +"grz","mgm",1,"grazing" +"hrv","mgm",1,"harvest" +"cul","mgm",1,"cultivation" +"frz","mgm",1,"fertilization" +"irr","mgm",1,"irrigation" +"epc","plt",0,"plantEpc" diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/epcConstMatrix5.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/epcConstMatrix5.json new file mode 100644 index 0000000..d691e1b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/epcConstMatrix5.json @@ -0,0 +1 @@ +[{"X":1,"NAME":"yearday to start new growth","INDEX":9,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":2,"NAME":"yearday to end new growth","INDEX":10,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":3,"NAME":"transfer growth period as fraction of growing season","INDEX":11,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":4,"NAME":"litterfall as fraction of growing season","INDEX":12,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":5,"NAME":"base temperature","INDEX":13,"UNIT":"Celsius","MIN":0,"MAX":12,"GROUP":0,"TYPE":0},{"X":6,"NAME":"minimum temperature for growth displayed on current day","INDEX":14,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":1,"TYPE":1},{"X":7,"NAME":"optimal1 temperature for growth displayed on current day","INDEX":15,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":1,"TYPE":1},{"X":8,"NAME":"optimal2 temperature for growth displayed on current day","INDEX":16,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":1,"TYPE":1},{"X":9,"NAME":"maxmimum temperature for growth displayed on current day","INDEX":17,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":1,"TYPE":1},{"X":10,"NAME":"minimum temperature for carbon assimilation displayed on current day","INDEX":18,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":2,"TYPE":1},{"X":11,"NAME":"optimal1 temperature for carbon assimilation displayed on current day","INDEX":19,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":2,"TYPE":1},{"X":12,"NAME":"optimal2 temperature for carbon assimilation displayed on current day","INDEX":20,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":2,"TYPE":1},{"X":13,"NAME":"maxmimum temperature for carbon assimilation displayed on current day","INDEX":21,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":2,"TYPE":1},{"X":14,"NAME":"annual leaf and fine root turnover fraction","INDEX":22,"UNIT":"1/yr","MIN":0.1,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":15,"NAME":"annual live wood turnover fraction","INDEX":23,"UNIT":"1/yr","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":16,"NAME":"annual fire mortality fraction","INDEX":24,"UNIT":"1/yr","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":17,"NAME":"whole-plant mortality paramter for vegetation period","INDEX":25,"UNIT":"1/vegper","MIN":0,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":18,"NAME":"C:N of leaves","INDEX":26,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":10,"MAX":100,"GROUP":0,"TYPE":0},{"X":19,"NAME":"C:N of leaf litter","INDEX":27,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":20,"NAME":"C:N of fine roots","INDEX":28,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":21,"NAME":"C:N of fruit","INDEX":29,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":22,"NAME":"C:N of softstem","INDEX":30,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":23,"NAME":"C:N of live wood","INDEX":31,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":50,"MAX":100,"GROUP":4,"TYPE":1},{"X":24,"NAME":"C:N of dead wood","INDEX":32,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":300,"MAX":800,"GROUP":4,"TYPE":1},{"X":25,"NAME":"dry matter content of leaves","INDEX":33,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":26,"NAME":"dry matter content of leaf litter","INDEX":34,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":27,"NAME":"dry matter content of fine roots","INDEX":35,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":28,"NAME":"dry matter content of fruit","INDEX":36,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":29,"NAME":"dry matter content of softstem","INDEX":37,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":30,"NAME":"dry matter content of live wood","INDEX":38,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":31,"NAME":"dry matter content of dead wood","INDEX":39,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":32,"NAME":"leaf litter labile proportion","INDEX":40,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":33,"NAME":"leaf litter cellulose proportion","INDEX":41,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":34,"NAME":"fine root labile proportion","INDEX":42,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":35,"NAME":"fine root cellulose proportion","INDEX":43,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":36,"NAME":"fruit labile proportion","INDEX":44,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":37,"NAME":"fruit cellulose proportion","INDEX":45,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":38,"NAME":"softstem labile proportion","INDEX":46,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":39,"NAME":"softstem cellulose proportion","INDEX":47,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":40,"NAME":"dead wood cellulose proportion","INDEX":48,"UNIT":"prop","MIN":0.5,"MAX":0.9,"GROUP":0,"TYPE":0},{"X":41,"NAME":"canopy water interception coefficient","INDEX":49,"UNIT":"1/LAI/d","MIN":0.01,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":42,"NAME":"canopy light extinction coefficient","INDEX":50,"UNIT":"dimless","MIN":0.2,"MAX":0.8,"GROUP":0,"TYPE":0},{"X":43,"NAME":"potential radiation use efficiency","INDEX":51,"UNIT":"g/MJ","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":44,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":52,"UNIT":"dimless","MIN":0.781,"MAX":0.781,"GROUP":0,"TYPE":0},{"X":45,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":53,"UNIT":"dimless","MIN":-13.596,"MAX":-13.596,"GROUP":0,"TYPE":0},{"X":46,"NAME":"all-sided to projected leaf area ratio","INDEX":54,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":47,"NAME":"ratio of shaded SLA:sunlit SLA","INDEX":55,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":48,"NAME":"fraction of leaf N in Rubisco","INDEX":56,"UNIT":"dimless","MIN":0.01,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":49,"NAME":"fraction of leaf N in PeP","INDEX":57,"UNIT":"dimless","MIN":0.0424,"MAX":0.0424,"GROUP":0,"TYPE":0},{"X":50,"NAME":"maximum stomatal conductance ","INDEX":58,"UNIT":"m/s","MIN":0.001,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":51,"NAME":"cuticular conductance ","INDEX":59,"UNIT":"m/s","MIN":1e-05,"MAX":0.0001,"GROUP":0,"TYPE":0},{"X":52,"NAME":"boundary layer conductance","INDEX":60,"UNIT":"m/s","MIN":0.01,"MAX":0.09,"GROUP":0,"TYPE":0},{"X":53,"NAME":"maximum height of plant","INDEX":61,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":54,"NAME":"stem weight corresponding to maximum height","INDEX":62,"UNIT":"kgC","MIN":0.1,"MAX":100,"GROUP":0,"TYPE":0},{"X":55,"NAME":"plant height function shape parameter (slope)","INDEX":63,"UNIT":"dimless","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":56,"NAME":"maximum depth of rooting zone","INDEX":64,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":57,"NAME":"root distribution parameter","INDEX":65,"UNIT":"prop","MIN":3.67,"MAX":3.67,"GROUP":0,"TYPE":0},{"X":58,"NAME":"root weight corresponding to max root depth","INDEX":66,"UNIT":"kgC/m2","MIN":0.4,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":59,"NAME":"root depth function shape parameter (slope)","INDEX":67,"UNIT":"prop","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":60,"NAME":"root weight to rooth length conversion factor","INDEX":68,"UNIT":"m/kg","MIN":1000,"MAX":1000,"GROUP":0,"TYPE":0},{"X":61,"NAME":"growth resp per unit of C grown","INDEX":69,"UNIT":"prop","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":62,"NAME":"maintenance respiration in kgC/day per kg of tissue N ","INDEX":70,"UNIT":"kgC/kgN/d","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":63,"NAME":"theoretical maximum prop. of non-structural and structural carbohydrates","INDEX":71,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":64,"NAME":"prop. of non-structural carbohydrates available for maintanance resp","INDEX":72,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":65,"NAME":"symbiotic+asymbiotic fixation of N","INDEX":73,"UNIT":"kgN/m2/yr","MIN":0,"MAX":0.001,"GROUP":0,"TYPE":0},{"X":66,"NAME":"time delay for temperature in photosynthesis acclimation","INDEX":74,"UNIT":"day","MIN":0,"MAX":50,"GROUP":0,"TYPE":0},{"X":67,"NAME":"critical VWCratio (prop. to FC-WP) in germination","INDEX":79,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":68,"NAME":"critical photoslow daylength","INDEX":81,"UNIT":"hour","MIN":14,"MAX":18,"GROUP":0,"TYPE":0},{"X":69,"NAME":"slope of relative photoslow development rate ","INDEX":82,"UNIT":"dimless","MIN":0.005,"MAX":0.005,"GROUP":0,"TYPE":0},{"X":70,"NAME":"critical vernalization temperature 1","INDEX":84,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":9,"TYPE":1},{"X":71,"NAME":"critical vernalization temperature 2","INDEX":85,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":9,"TYPE":1},{"X":72,"NAME":"critical vernalization temperature 3","INDEX":86,"UNIT":"Celsius","DEPENDENCE":2,"MIN":5,"MAX":15,"GROUP":9,"TYPE":1},{"X":73,"NAME":"critical vernalization temperature 4","INDEX":87,"UNIT":"Celsius","DEPENDENCE":3,"MIN":10,"MAX":20,"GROUP":9,"TYPE":1},{"X":74,"NAME":"slope of relative vernalization development rate ","INDEX":88,"UNIT":"dimless","MIN":0.04,"MAX":0.04,"GROUP":0,"TYPE":0},{"X":75,"NAME":"required vernalization days (in vernalization development rate)","INDEX":89,"UNIT":"dimless","MIN":30,"MAX":70,"GROUP":0,"TYPE":0},{"X":76,"NAME":"critical flowering heat stress temperature 1","INDEX":91,"UNIT":"Celsius","DEPENDENCE":0,"MIN":30,"MAX":40,"GROUP":10,"TYPE":1},{"X":77,"NAME":"critical flowering heat stress temperature 2","INDEX":92,"UNIT":"Celsius","DEPENDENCE":1,"MIN":30,"MAX":50,"GROUP":10,"TYPE":1},{"X":78,"NAME":"theoretical maximum of flowering thermal stress mortality","INDEX":93,"UNIT":"prop","MIN":0,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":79,"NAME":"VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)","INDEX":96,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":80,"NAME":"VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)","INDEX":97,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":81,"NAME":"minimum of soil moisture limit2 multiplicator (full anoxic stress value)","INDEX":98,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":82,"NAME":"vapor pressure deficit: start of conductance reduction","INDEX":99,"UNIT":"Pa","MIN":500,"MAX":1500,"GROUP":0,"TYPE":0},{"X":83,"NAME":"vapor pressure deficit: complete conductance reduction","INDEX":100,"UNIT":"Pa","MIN":1500,"MAX":3500,"GROUP":0,"TYPE":0},{"X":84,"NAME":"maximum senescence mortality coefficient of aboveground plant material","INDEX":101,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":85,"NAME":"maximum senescence mortality coefficient of belowground plant material","INDEX":102,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":86,"NAME":"maximum senescence mortality coefficient of non-structured plant material","INDEX":103,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":87,"NAME":"lower limit extreme high temperature effect on senescence mortality","INDEX":104,"UNIT":"Celsius","MIN":30,"MAX":40,"GROUP":0,"TYPE":0},{"X":88,"NAME":"upper limit extreme high temperature effect on senescence mortality","INDEX":105,"UNIT":"Celsius","MIN":30,"MAX":50,"GROUP":0,"TYPE":0},{"X":89,"NAME":"turnover rate of wilted standing biomass to litter","INDEX":106,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":90,"NAME":"turnover rate of cut-down non-woody biomass to litter","INDEX":107,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":91,"NAME":"turnover rate of cut-down woody biomass to litter","INDEX":108,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":92,"NAME":"drought tolerance parameter (critical value of day since water stress)","INDEX":109,"UNIT":"n_day","MIN":0,"MAX":100,"GROUP":0,"TYPE":0},{"X":93,"NAME":"crit. amount of snow limiting photosyn.","INDEX":112,"UNIT":"kg/m2","MIN":0,"MAX":20,"GROUP":0,"TYPE":0},{"X":94,"NAME":"limit1 (under:full constrained) of HEATSUM index","INDEX":113,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":50,"GROUP":11,"TYPE":1},{"X":95,"NAME":"limit2 (above:unconstrained) of HEATSUM index","INDEX":114,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":100,"GROUP":11,"TYPE":1},{"X":96,"NAME":"limit1 (under:full constrained) of TMIN index","INDEX":115,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":12,"TYPE":1},{"X":97,"NAME":"limit2 (above:unconstrained) of TMIN index","INDEX":116,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":12,"TYPE":1},{"X":98,"NAME":"limit1 (above:full constrained) of VPD index","INDEX":117,"UNIT":"Pa","DEPENDENCE":0,"MIN":2000,"MAX":600,"GROUP":13,"TYPE":1},{"X":99,"NAME":"limit2 (under:unconstrained) of VPD index","INDEX":118,"UNIT":"Pa","DEPENDENCE":1,"MIN":500,"MAX":1500,"GROUP":13,"TYPE":1},{"X":100,"NAME":"limit1 (under:full constrained) of DAYLENGTH index","INDEX":119,"UNIT":"s","DEPENDENCE":0,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":101,"NAME":"limit2 (above:unconstrained) of DAYLENGTH index","INDEX":120,"UNIT":"s","DEPENDENCE":1,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":102,"NAME":"moving average (to avoid the effects of extreme events)","INDEX":121,"UNIT":"n_day","MIN":2,"MAX":20,"GROUP":0,"TYPE":0},{"X":103,"NAME":"GSI limit1 (greater that limit -> start of vegper)","INDEX":122,"UNIT":"dimless","MIN":0,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":104,"NAME":"GSI limit2 (less that limit -> end of vegper)","INDEX":123,"UNIT":"dimless","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":105,"NAME":"length of phenophase (GDD)","INDEX":127,"UNIT":"Celsius","MIN":0,"MAX":10000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -0","INDEX":128.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-0","INDEX":129.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -0","INDEX":130.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-0","INDEX":131.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -0","INDEX":132.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -0","INDEX":133.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-0","INDEX":134.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -0","INDEX":135.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-0","INDEX":136.6,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-0","INDEX":137.6,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-0","INDEX":138.6,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -1","INDEX":128.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-1","INDEX":129.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -1","INDEX":130.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-1","INDEX":131.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -1","INDEX":132.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -1","INDEX":133.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-1","INDEX":134.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -1","INDEX":135.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-1","INDEX":136.61,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-1","INDEX":137.61,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-1","INDEX":138.61,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -2","INDEX":128.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-2","INDEX":129.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -2","INDEX":130.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-2","INDEX":131.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -2","INDEX":132.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -2","INDEX":133.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-2","INDEX":134.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -2","INDEX":135.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-2","INDEX":136.62,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-2","INDEX":137.62,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-2","INDEX":138.62,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -3","INDEX":128.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-3","INDEX":129.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -3","INDEX":130.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-3","INDEX":131.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -3","INDEX":132.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -3","INDEX":133.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-3","INDEX":134.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -3","INDEX":135.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-3","INDEX":136.63,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-3","INDEX":137.63,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-3","INDEX":138.63,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -4","INDEX":128.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-4","INDEX":129.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -4","INDEX":130.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-4","INDEX":131.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -4","INDEX":132.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -4","INDEX":133.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-4","INDEX":134.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -4","INDEX":135.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-4","INDEX":136.64,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-4","INDEX":137.64,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-4","INDEX":138.64,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -5","INDEX":128.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-5","INDEX":129.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -5","INDEX":130.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-5","INDEX":131.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -5","INDEX":132.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -5","INDEX":133.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-5","INDEX":134.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -5","INDEX":135.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-5","INDEX":136.65,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-5","INDEX":137.65,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-5","INDEX":138.65,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -6","INDEX":128.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-6","INDEX":129.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -6","INDEX":130.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-6","INDEX":131.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -6","INDEX":132.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -6","INDEX":133.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-6","INDEX":134.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -6","INDEX":135.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-6","INDEX":136.66,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-6","INDEX":137.66,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-6","INDEX":138.66,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0}] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/epcConstMatrix6.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/epcConstMatrix6.json new file mode 100644 index 0000000..337faac --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/epcConstMatrix6.json @@ -0,0 +1,1987 @@ +[ + { + "X": 1, + "NAME": "yearday to start new growth", + "INDEX": 9, + "UNIT": "yday", + "MIN": 0, + "MAX": 364, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 2, + "NAME": "yearday to end new growth", + "INDEX": 10, + "UNIT": "yday", + "MIN": 0, + "MAX": 364, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 3, + "NAME": "transfer growth period as fraction of growing season", + "INDEX": 11, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 4, + "NAME": "litterfall as fraction of growing season", + "INDEX": 12, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 5, + "NAME": "base temperature", + "INDEX": 13, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 12, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 6, + "NAME": "minimum temperature for growth displayed on current day", + "INDEX": 14, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 0, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 7, + "NAME": "optimal1 temperature for growth displayed on current day", + "INDEX": 15, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 1, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 8, + "NAME": "optimal2 temperature for growth displayed on current day", + "INDEX": 16, + "UNIT": "Celsius", + "MIN": 20, + "MAX": 40, + "DEPENDENCE": 2, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 9, + "NAME": "maxmimum temperature for growth displayed on current day", + "INDEX": 17, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 3, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 10, + "NAME": "minimum temperature for carbon assimilation displayed on current day", + "INDEX": 18, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 0, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 11, + "NAME": "optimal1 temperature for carbon assimilation displayed on current day", + "INDEX": 19, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 1, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 12, + "NAME": "optimal2 temperature for carbon assimilation displayed on current day", + "INDEX": 20, + "UNIT": "Celsius", + "MIN": 20, + "MAX": 40, + "DEPENDENCE": 2, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 13, + "NAME": "maxmimum temperature for carbon assimilation displayed on current day", + "INDEX": 21, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 3, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 14, + "NAME": "annual leaf and fine root turnover fraction", + "INDEX": 22, + "UNIT": "1/yr", + "MIN": 0.1, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 15, + "NAME": "annual live wood turnover fraction", + "INDEX": 23, + "UNIT": "1/yr", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 16, + "NAME": "annual fire mortality fraction", + "INDEX": 24, + "UNIT": "1/yr", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 17, + "NAME": "whole-plant mortality paramter for vegetation period", + "INDEX": 25, + "UNIT": "1/vegper", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 18, + "NAME": "C:N of leaves", + "INDEX": 26, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 100, + "DEPENDENCE": 0, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 19, + "NAME": "C:N of leaf litter", + "INDEX": 27, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 20, + "NAME": "C:N of fine roots", + "INDEX": 28, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 21, + "NAME": "C:N of fruit", + "INDEX": 29, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 22, + "NAME": "C:N of softstem", + "INDEX": 30, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 23, + "NAME": "C:N of live wood", + "INDEX": 31, + "UNIT": "kgC/kgN", + "MIN": 50, + "MAX": 100, + "DEPENDENCE": 0, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 24, + "NAME": "C:N of dead wood", + "INDEX": 32, + "UNIT": "kgC/kgN", + "MIN": 300, + "MAX": 800, + "DEPENDENCE": 1, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 25, + "NAME": "dry matter content of leaves", + "INDEX": 33, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 26, + "NAME": "dry matter content of leaf litter", + "INDEX": 34, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 27, + "NAME": "dry matter content of fine roots", + "INDEX": 35, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 28, + "NAME": "dry matter content of fruit", + "INDEX": 36, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 29, + "NAME": "dry matter content of softstem", + "INDEX": 37, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 30, + "NAME": "dry matter content of live wood", + "INDEX": 38, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 31, + "NAME": "dry matter content of dead wood", + "INDEX": 39, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 32, + "NAME": "leaf litter labile proportion", + "INDEX": 40, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 33, + "NAME": "leaf litter cellulose proportion", + "INDEX": 41, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 34, + "NAME": "fine root labile proportion", + "INDEX": 42, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 6, + "TYPE": 2 + }, + { + "X": 35, + "NAME": "fine root cellulose proportion", + "INDEX": 43, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 6, + "TYPE": 2 + }, + { + "X": 36, + "NAME": "fruit labile proportion", + "INDEX": 44, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 37, + "NAME": "fruit cellulose proportion", + "INDEX": 45, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 38, + "NAME": "softstem labile proportion", + "INDEX": 46, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 8, + "TYPE": 2 + }, + { + "X": 39, + "NAME": "softstem cellulose proportion", + "INDEX": 47, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 8, + "TYPE": 2 + }, + { + "X": 40, + "NAME": "dead wood cellulose proportion", + "INDEX": 48, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 0.9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 41, + "NAME": "canopy water interception coefficient", + "INDEX": 49, + "UNIT": "1/LAI/d", + "MIN": 0.01, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 42, + "NAME": "canopy light extinction coefficient", + "INDEX": 50, + "UNIT": "dimless", + "MIN": 0.2, + "MAX": 0.8, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 43, + "NAME": "potential radiation use efficiency", + "INDEX": 51, + "UNIT": "g/MJ", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "radiation parameter1 (Jiang et al.2015)", + "INDEX": 52, + "UNIT": "dimless", + "MIN": 0.781, + "MAX": 0.781, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 45, + "NAME": "radiation parameter1 (Jiang et al.2015)", + "INDEX": 53, + "UNIT": "dimless", + "MIN": -13.596, + "MAX": -13.596, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 46, + "NAME": "all-sided to projected leaf area ratio", + "INDEX": 54, + "UNIT": "dimless", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "ratio of shaded SLA:sunlit SLA", + "INDEX": 55, + "UNIT": "dimless", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "fraction of leaf N in Rubisco", + "INDEX": 56, + "UNIT": "dimless", + "MIN": 0.01, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 49, + "NAME": "fraction of leaf N in PeP", + "INDEX": 57, + "UNIT": "dimless", + "MIN": 0.0424, + "MAX": 0.0424, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 50, + "NAME": "maximum stomatal conductance", + "INDEX": 58, + "UNIT": "m/s", + "MIN": 0.001, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 51, + "NAME": "cuticular conductance", + "INDEX": 59, + "UNIT": "m/s", + "MIN": 1e-05, + "MAX": 0.0001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 52, + "NAME": "boundary layer conductance", + "INDEX": 60, + "UNIT": "m/s", + "MIN": 0.01, + "MAX": 0.09, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "maximum height of plant", + "INDEX": 61, + "UNIT": "m", + "MIN": 0.1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 54, + "NAME": "stem weight corresponding to maximum height", + "INDEX": 62, + "UNIT": "kgC", + "MIN": 0.1, + "MAX": 100, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 55, + "NAME": "plant height function shape parameter (slope)", + "INDEX": 63, + "UNIT": "dimless", + "MIN": 0.5, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 56, + "NAME": "maximum depth of rooting zone", + "INDEX": 64, + "UNIT": "m", + "MIN": 0.1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 57, + "NAME": "root distribution parameter", + "INDEX": 65, + "UNIT": "prop", + "MIN": 3.67, + "MAX": 3.67, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 58, + "NAME": "root weight corresponding to max root depth", + "INDEX": 66, + "UNIT": "kgC/m2", + "MIN": 0.4, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 59, + "NAME": "root depth function shape parameter (slope)", + "INDEX": 67, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 60, + "NAME": "root weight to rooth length conversion factor", + "INDEX": 68, + "UNIT": "m/kg", + "MIN": 1000, + "MAX": 1000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 61, + "NAME": "growth resp per unit of C grown", + "INDEX": 69, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 62, + "NAME": "maintenance respiration in kgC/day per kg of tissue N", + "INDEX": 70, + "UNIT": "kgC/kgN/d", + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 63, + "NAME": "theoretical maximum prop. of non-structural and structural carbohydrates", + "INDEX": 71, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 64, + "NAME": "prop. of non-structural carbohydrates available for maintanance resp", + "INDEX": 72, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 65, + "NAME": "symbiotic+asymbiotic fixation of N", + "INDEX": 73, + "UNIT": "kgN/m2/yr", + "MIN": 0, + "MAX": 0.001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 66, + "NAME": "time delay for temperature in photosynthesis acclimation", + "INDEX": 74, + "UNIT": "day", + "MIN": 0, + "MAX": 50, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 67, + "NAME": "critical VWCratio (prop. to FC-WP) in germination", + "INDEX": 79, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 68, + "NAME": "critical photoslow daylength", + "INDEX": 81, + "UNIT": "hour", + "MIN": 14, + "MAX": 18, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 69, + "NAME": "slope of relative photoslow development rate", + "INDEX": 82, + "UNIT": "dimless", + "MIN": 0.005, + "MAX": 0.005, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 70, + "NAME": "critical vernalization temperature 1", + "INDEX": 84, + "UNIT": "Celsius", + "MIN": -5, + "MAX": 5, + "DEPENDENCE": 0, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 71, + "NAME": "critical vernalization temperature 2", + "INDEX": 85, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 1, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 72, + "NAME": "critical vernalization temperature 3", + "INDEX": 86, + "UNIT": "Celsius", + "MIN": 5, + "MAX": 15, + "DEPENDENCE": 2, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 73, + "NAME": "critical vernalization temperature 4", + "INDEX": 87, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 3, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 74, + "NAME": "slope of relative vernalization development rate", + "INDEX": 88, + "UNIT": "dimless", + "MIN": 0.04, + "MAX": 0.04, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 75, + "NAME": "required vernalization days (in vernalization development rate)", + "INDEX": 89, + "UNIT": "dimless", + "MIN": 30, + "MAX": 70, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 76, + "NAME": "critical flowering heat stress temperature 1", + "INDEX": 91, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 40, + "DEPENDENCE": 0, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 77, + "NAME": "critical flowering heat stress temperature 2", + "INDEX": 92, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 1, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 78, + "NAME": "theoretical maximum of flowering thermal stress mortality", + "INDEX": 93, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 79, + "NAME": "VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)", + "INDEX": 96, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 80, + "NAME": "VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)", + "INDEX": 97, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 81, + "NAME": "minimum of soil moisture limit2 multiplicator (full anoxic stress value)", + "INDEX": 98, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 82, + "NAME": "vapor pressure deficit: start of conductance reduction", + "INDEX": 99, + "UNIT": "Pa", + "MIN": 500, + "MAX": 1500, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 83, + "NAME": "vapor pressure deficit: complete conductance reduction", + "INDEX": 100, + "UNIT": "Pa", + "MIN": 1500, + "MAX": 3500, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 84, + "NAME": "maximum senescence mortality coefficient of aboveground plant material", + "INDEX": 101, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "DEPENDENCE": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 85, + "NAME": "maximum senescence mortality coefficient of belowground plant material", + "INDEX": 102, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "DEPENDENCE": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 86, + "NAME": "maximum senescence mortality coefficient of non-structured plant material", + "INDEX": 103, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 87, + "NAME": "lower limit extreme high temperature effect on senescence mortality", + "INDEX": 104, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 88, + "NAME": "upper limit extreme high temperature effect on senescence mortality", + "INDEX": 105, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 89, + "NAME": "turnover rate of wilted standing biomass to litter", + "INDEX": 106, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 90, + "NAME": "turnover rate of cut-down non-woody biomass to litter", + "INDEX": 107, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 91, + "NAME": "turnover rate of cut-down woody biomass to litter", + "INDEX": 108, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 92, + "NAME": "drought tolerance parameter (critical value of day since water stress)", + "INDEX": 109, + "UNIT": "n_day", + "MIN": 0, + "MAX": 100, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 93, + "NAME": "effect of soilstress factor on photosynthesis", + "INDEX": 110, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 94, + "NAME": "crit. amount of snow limiting photosyn.", + "INDEX": 113, + "UNIT": "kg/m2", + "MIN": 0, + "MAX": 20, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 95, + "NAME": "limit1 (under:full constrained) of HEATSUM index", + "INDEX": 114, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 50, + "DEPENDENCE": 0, + "GROUP": 11, + "TYPE": 1 + }, + { + "X": 96, + "NAME": "limit2 (above:unconstrained) of HEATSUM index", + "INDEX": 115, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 100, + "DEPENDENCE": 1, + "GROUP": 11, + "TYPE": 1 + }, + { + "X": 97, + "NAME": "limit1 (under:full constrained) of TMIN index", + "INDEX": 116, + "UNIT": "Celsius", + "MIN": -5, + "MAX": 5, + "DEPENDENCE": 0, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 98, + "NAME": "limit2 (above:unconstrained) of TMIN index", + "INDEX": 117, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 1, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 99, + "NAME": "limit1 (above:full constrained) of VPD index", + "INDEX": 118, + "UNIT": "Pa", + "MIN": 2000, + "MAX": 600, + "DEPENDENCE": 0, + "GROUP": 13, + "TYPE": 1 + }, + { + "X": 100, + "NAME": "limit2 (under:unconstrained) of VPD index", + "INDEX": 119, + "UNIT": "Pa", + "MIN": 500, + "MAX": 1500, + "DEPENDENCE": 1, + "GROUP": 13, + "TYPE": 1 + }, + { + "X": 101, + "NAME": "limit1 (under:full constrained) of DAYLENGTH index", + "INDEX": 120, + "UNIT": "s", + "MIN": 0, + "MAX": 0, + "DEPENDENCE": 0, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 102, + "NAME": "limit2 (above:unconstrained) of DAYLENGTH index", + "INDEX": 121, + "UNIT": "s", + "MIN": 0, + "MAX": 0, + "DEPENDENCE": 1, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 103, + "NAME": "moving average (to avoid the effects of extreme events)", + "INDEX": 122, + "UNIT": "n_day", + "MIN": 2, + "MAX": 20, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 104, + "NAME": "GSI limit1 (greater that limit -> start of vegper)", + "INDEX": 123, + "UNIT": "dimless", + "MIN": 0, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 105, + "NAME": "GSI limit2 (less that limit -> end of vegper)", + "INDEX": 124, + "UNIT": "dimless", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-0", + "INDEX": 128.6, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -0", + "INDEX": 129.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-0", + "INDEX": 130.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -0", + "INDEX": 131.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-0", + "INDEX": 132.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -0", + "INDEX": 133.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -0", + "INDEX": 134.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-0", + "INDEX": 135.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -0", + "INDEX": 136.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-0", + "INDEX": 137.6, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-0", + "INDEX": 138.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-0", + "INDEX": 139.6, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-1", + "INDEX": 128.61, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -1", + "INDEX": 129.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-1", + "INDEX": 130.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -1", + "INDEX": 131.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-1", + "INDEX": 132.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -1", + "INDEX": 133.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -1", + "INDEX": 134.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-1", + "INDEX": 135.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -1", + "INDEX": 136.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-1", + "INDEX": 137.61, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-1", + "INDEX": 138.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-1", + "INDEX": 139.61, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-2", + "INDEX": 128.62, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -2", + "INDEX": 129.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-2", + "INDEX": 130.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -2", + "INDEX": 131.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-2", + "INDEX": 132.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -2", + "INDEX": 133.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -2", + "INDEX": 134.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-2", + "INDEX": 135.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -2", + "INDEX": 136.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-2", + "INDEX": 137.62, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-2", + "INDEX": 138.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-2", + "INDEX": 139.62, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-3", + "INDEX": 128.63, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -3", + "INDEX": 129.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-3", + "INDEX": 130.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -3", + "INDEX": 131.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-3", + "INDEX": 132.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -3", + "INDEX": 133.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -3", + "INDEX": 134.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-3", + "INDEX": 135.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -3", + "INDEX": 136.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-3", + "INDEX": 137.63, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-3", + "INDEX": 138.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-3", + "INDEX": 139.63, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-4", + "INDEX": 128.64, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -4", + "INDEX": 129.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-4", + "INDEX": 130.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -4", + "INDEX": 131.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-4", + "INDEX": 132.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -4", + "INDEX": 133.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -4", + "INDEX": 134.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-4", + "INDEX": 135.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -4", + "INDEX": 136.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-4", + "INDEX": 137.64, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-4", + "INDEX": 138.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-4", + "INDEX": 139.64, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-5", + "INDEX": 128.65, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -5", + "INDEX": 129.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-5", + "INDEX": 130.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -5", + "INDEX": 131.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-5", + "INDEX": 132.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -5", + "INDEX": 133.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -5", + "INDEX": 134.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-5", + "INDEX": 135.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -5", + "INDEX": 136.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-5", + "INDEX": 137.65, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-5", + "INDEX": 138.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-5", + "INDEX": 139.65, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-6", + "INDEX": 128.66, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -6", + "INDEX": 129.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-6", + "INDEX": 130.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -6", + "INDEX": 131.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-6", + "INDEX": 132.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -6", + "INDEX": 133.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -6", + "INDEX": 134.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-6", + "INDEX": 135.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -6", + "INDEX": 136.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-6", + "INDEX": 137.66, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-6", + "INDEX": 138.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-6", + "INDEX": 139.66, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + } +] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/soilConstMatrix5.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/soilConstMatrix5.json new file mode 100644 index 0000000..d691e1b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/soilConstMatrix5.json @@ -0,0 +1 @@ +[{"X":1,"NAME":"yearday to start new growth","INDEX":9,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":2,"NAME":"yearday to end new growth","INDEX":10,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":3,"NAME":"transfer growth period as fraction of growing season","INDEX":11,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":4,"NAME":"litterfall as fraction of growing season","INDEX":12,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":5,"NAME":"base temperature","INDEX":13,"UNIT":"Celsius","MIN":0,"MAX":12,"GROUP":0,"TYPE":0},{"X":6,"NAME":"minimum temperature for growth displayed on current day","INDEX":14,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":1,"TYPE":1},{"X":7,"NAME":"optimal1 temperature for growth displayed on current day","INDEX":15,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":1,"TYPE":1},{"X":8,"NAME":"optimal2 temperature for growth displayed on current day","INDEX":16,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":1,"TYPE":1},{"X":9,"NAME":"maxmimum temperature for growth displayed on current day","INDEX":17,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":1,"TYPE":1},{"X":10,"NAME":"minimum temperature for carbon assimilation displayed on current day","INDEX":18,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":2,"TYPE":1},{"X":11,"NAME":"optimal1 temperature for carbon assimilation displayed on current day","INDEX":19,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":2,"TYPE":1},{"X":12,"NAME":"optimal2 temperature for carbon assimilation displayed on current day","INDEX":20,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":2,"TYPE":1},{"X":13,"NAME":"maxmimum temperature for carbon assimilation displayed on current day","INDEX":21,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":2,"TYPE":1},{"X":14,"NAME":"annual leaf and fine root turnover fraction","INDEX":22,"UNIT":"1/yr","MIN":0.1,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":15,"NAME":"annual live wood turnover fraction","INDEX":23,"UNIT":"1/yr","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":16,"NAME":"annual fire mortality fraction","INDEX":24,"UNIT":"1/yr","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":17,"NAME":"whole-plant mortality paramter for vegetation period","INDEX":25,"UNIT":"1/vegper","MIN":0,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":18,"NAME":"C:N of leaves","INDEX":26,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":10,"MAX":100,"GROUP":0,"TYPE":0},{"X":19,"NAME":"C:N of leaf litter","INDEX":27,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":20,"NAME":"C:N of fine roots","INDEX":28,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":21,"NAME":"C:N of fruit","INDEX":29,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":22,"NAME":"C:N of softstem","INDEX":30,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":23,"NAME":"C:N of live wood","INDEX":31,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":50,"MAX":100,"GROUP":4,"TYPE":1},{"X":24,"NAME":"C:N of dead wood","INDEX":32,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":300,"MAX":800,"GROUP":4,"TYPE":1},{"X":25,"NAME":"dry matter content of leaves","INDEX":33,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":26,"NAME":"dry matter content of leaf litter","INDEX":34,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":27,"NAME":"dry matter content of fine roots","INDEX":35,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":28,"NAME":"dry matter content of fruit","INDEX":36,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":29,"NAME":"dry matter content of softstem","INDEX":37,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":30,"NAME":"dry matter content of live wood","INDEX":38,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":31,"NAME":"dry matter content of dead wood","INDEX":39,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":32,"NAME":"leaf litter labile proportion","INDEX":40,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":33,"NAME":"leaf litter cellulose proportion","INDEX":41,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":34,"NAME":"fine root labile proportion","INDEX":42,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":35,"NAME":"fine root cellulose proportion","INDEX":43,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":36,"NAME":"fruit labile proportion","INDEX":44,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":37,"NAME":"fruit cellulose proportion","INDEX":45,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":38,"NAME":"softstem labile proportion","INDEX":46,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":39,"NAME":"softstem cellulose proportion","INDEX":47,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":40,"NAME":"dead wood cellulose proportion","INDEX":48,"UNIT":"prop","MIN":0.5,"MAX":0.9,"GROUP":0,"TYPE":0},{"X":41,"NAME":"canopy water interception coefficient","INDEX":49,"UNIT":"1/LAI/d","MIN":0.01,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":42,"NAME":"canopy light extinction coefficient","INDEX":50,"UNIT":"dimless","MIN":0.2,"MAX":0.8,"GROUP":0,"TYPE":0},{"X":43,"NAME":"potential radiation use efficiency","INDEX":51,"UNIT":"g/MJ","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":44,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":52,"UNIT":"dimless","MIN":0.781,"MAX":0.781,"GROUP":0,"TYPE":0},{"X":45,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":53,"UNIT":"dimless","MIN":-13.596,"MAX":-13.596,"GROUP":0,"TYPE":0},{"X":46,"NAME":"all-sided to projected leaf area ratio","INDEX":54,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":47,"NAME":"ratio of shaded SLA:sunlit SLA","INDEX":55,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":48,"NAME":"fraction of leaf N in Rubisco","INDEX":56,"UNIT":"dimless","MIN":0.01,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":49,"NAME":"fraction of leaf N in PeP","INDEX":57,"UNIT":"dimless","MIN":0.0424,"MAX":0.0424,"GROUP":0,"TYPE":0},{"X":50,"NAME":"maximum stomatal conductance ","INDEX":58,"UNIT":"m/s","MIN":0.001,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":51,"NAME":"cuticular conductance ","INDEX":59,"UNIT":"m/s","MIN":1e-05,"MAX":0.0001,"GROUP":0,"TYPE":0},{"X":52,"NAME":"boundary layer conductance","INDEX":60,"UNIT":"m/s","MIN":0.01,"MAX":0.09,"GROUP":0,"TYPE":0},{"X":53,"NAME":"maximum height of plant","INDEX":61,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":54,"NAME":"stem weight corresponding to maximum height","INDEX":62,"UNIT":"kgC","MIN":0.1,"MAX":100,"GROUP":0,"TYPE":0},{"X":55,"NAME":"plant height function shape parameter (slope)","INDEX":63,"UNIT":"dimless","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":56,"NAME":"maximum depth of rooting zone","INDEX":64,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":57,"NAME":"root distribution parameter","INDEX":65,"UNIT":"prop","MIN":3.67,"MAX":3.67,"GROUP":0,"TYPE":0},{"X":58,"NAME":"root weight corresponding to max root depth","INDEX":66,"UNIT":"kgC/m2","MIN":0.4,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":59,"NAME":"root depth function shape parameter (slope)","INDEX":67,"UNIT":"prop","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":60,"NAME":"root weight to rooth length conversion factor","INDEX":68,"UNIT":"m/kg","MIN":1000,"MAX":1000,"GROUP":0,"TYPE":0},{"X":61,"NAME":"growth resp per unit of C grown","INDEX":69,"UNIT":"prop","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":62,"NAME":"maintenance respiration in kgC/day per kg of tissue N ","INDEX":70,"UNIT":"kgC/kgN/d","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":63,"NAME":"theoretical maximum prop. of non-structural and structural carbohydrates","INDEX":71,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":64,"NAME":"prop. of non-structural carbohydrates available for maintanance resp","INDEX":72,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":65,"NAME":"symbiotic+asymbiotic fixation of N","INDEX":73,"UNIT":"kgN/m2/yr","MIN":0,"MAX":0.001,"GROUP":0,"TYPE":0},{"X":66,"NAME":"time delay for temperature in photosynthesis acclimation","INDEX":74,"UNIT":"day","MIN":0,"MAX":50,"GROUP":0,"TYPE":0},{"X":67,"NAME":"critical VWCratio (prop. to FC-WP) in germination","INDEX":79,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":68,"NAME":"critical photoslow daylength","INDEX":81,"UNIT":"hour","MIN":14,"MAX":18,"GROUP":0,"TYPE":0},{"X":69,"NAME":"slope of relative photoslow development rate ","INDEX":82,"UNIT":"dimless","MIN":0.005,"MAX":0.005,"GROUP":0,"TYPE":0},{"X":70,"NAME":"critical vernalization temperature 1","INDEX":84,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":9,"TYPE":1},{"X":71,"NAME":"critical vernalization temperature 2","INDEX":85,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":9,"TYPE":1},{"X":72,"NAME":"critical vernalization temperature 3","INDEX":86,"UNIT":"Celsius","DEPENDENCE":2,"MIN":5,"MAX":15,"GROUP":9,"TYPE":1},{"X":73,"NAME":"critical vernalization temperature 4","INDEX":87,"UNIT":"Celsius","DEPENDENCE":3,"MIN":10,"MAX":20,"GROUP":9,"TYPE":1},{"X":74,"NAME":"slope of relative vernalization development rate ","INDEX":88,"UNIT":"dimless","MIN":0.04,"MAX":0.04,"GROUP":0,"TYPE":0},{"X":75,"NAME":"required vernalization days (in vernalization development rate)","INDEX":89,"UNIT":"dimless","MIN":30,"MAX":70,"GROUP":0,"TYPE":0},{"X":76,"NAME":"critical flowering heat stress temperature 1","INDEX":91,"UNIT":"Celsius","DEPENDENCE":0,"MIN":30,"MAX":40,"GROUP":10,"TYPE":1},{"X":77,"NAME":"critical flowering heat stress temperature 2","INDEX":92,"UNIT":"Celsius","DEPENDENCE":1,"MIN":30,"MAX":50,"GROUP":10,"TYPE":1},{"X":78,"NAME":"theoretical maximum of flowering thermal stress mortality","INDEX":93,"UNIT":"prop","MIN":0,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":79,"NAME":"VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)","INDEX":96,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":80,"NAME":"VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)","INDEX":97,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":81,"NAME":"minimum of soil moisture limit2 multiplicator (full anoxic stress value)","INDEX":98,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":82,"NAME":"vapor pressure deficit: start of conductance reduction","INDEX":99,"UNIT":"Pa","MIN":500,"MAX":1500,"GROUP":0,"TYPE":0},{"X":83,"NAME":"vapor pressure deficit: complete conductance reduction","INDEX":100,"UNIT":"Pa","MIN":1500,"MAX":3500,"GROUP":0,"TYPE":0},{"X":84,"NAME":"maximum senescence mortality coefficient of aboveground plant material","INDEX":101,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":85,"NAME":"maximum senescence mortality coefficient of belowground plant material","INDEX":102,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":86,"NAME":"maximum senescence mortality coefficient of non-structured plant material","INDEX":103,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":87,"NAME":"lower limit extreme high temperature effect on senescence mortality","INDEX":104,"UNIT":"Celsius","MIN":30,"MAX":40,"GROUP":0,"TYPE":0},{"X":88,"NAME":"upper limit extreme high temperature effect on senescence mortality","INDEX":105,"UNIT":"Celsius","MIN":30,"MAX":50,"GROUP":0,"TYPE":0},{"X":89,"NAME":"turnover rate of wilted standing biomass to litter","INDEX":106,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":90,"NAME":"turnover rate of cut-down non-woody biomass to litter","INDEX":107,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":91,"NAME":"turnover rate of cut-down woody biomass to litter","INDEX":108,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":92,"NAME":"drought tolerance parameter (critical value of day since water stress)","INDEX":109,"UNIT":"n_day","MIN":0,"MAX":100,"GROUP":0,"TYPE":0},{"X":93,"NAME":"crit. amount of snow limiting photosyn.","INDEX":112,"UNIT":"kg/m2","MIN":0,"MAX":20,"GROUP":0,"TYPE":0},{"X":94,"NAME":"limit1 (under:full constrained) of HEATSUM index","INDEX":113,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":50,"GROUP":11,"TYPE":1},{"X":95,"NAME":"limit2 (above:unconstrained) of HEATSUM index","INDEX":114,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":100,"GROUP":11,"TYPE":1},{"X":96,"NAME":"limit1 (under:full constrained) of TMIN index","INDEX":115,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":12,"TYPE":1},{"X":97,"NAME":"limit2 (above:unconstrained) of TMIN index","INDEX":116,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":12,"TYPE":1},{"X":98,"NAME":"limit1 (above:full constrained) of VPD index","INDEX":117,"UNIT":"Pa","DEPENDENCE":0,"MIN":2000,"MAX":600,"GROUP":13,"TYPE":1},{"X":99,"NAME":"limit2 (under:unconstrained) of VPD index","INDEX":118,"UNIT":"Pa","DEPENDENCE":1,"MIN":500,"MAX":1500,"GROUP":13,"TYPE":1},{"X":100,"NAME":"limit1 (under:full constrained) of DAYLENGTH index","INDEX":119,"UNIT":"s","DEPENDENCE":0,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":101,"NAME":"limit2 (above:unconstrained) of DAYLENGTH index","INDEX":120,"UNIT":"s","DEPENDENCE":1,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":102,"NAME":"moving average (to avoid the effects of extreme events)","INDEX":121,"UNIT":"n_day","MIN":2,"MAX":20,"GROUP":0,"TYPE":0},{"X":103,"NAME":"GSI limit1 (greater that limit -> start of vegper)","INDEX":122,"UNIT":"dimless","MIN":0,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":104,"NAME":"GSI limit2 (less that limit -> end of vegper)","INDEX":123,"UNIT":"dimless","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":105,"NAME":"length of phenophase (GDD)","INDEX":127,"UNIT":"Celsius","MIN":0,"MAX":10000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -0","INDEX":128.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-0","INDEX":129.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -0","INDEX":130.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-0","INDEX":131.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -0","INDEX":132.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -0","INDEX":133.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-0","INDEX":134.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -0","INDEX":135.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-0","INDEX":136.6,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-0","INDEX":137.6,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-0","INDEX":138.6,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -1","INDEX":128.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-1","INDEX":129.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -1","INDEX":130.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-1","INDEX":131.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -1","INDEX":132.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -1","INDEX":133.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-1","INDEX":134.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -1","INDEX":135.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-1","INDEX":136.61,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-1","INDEX":137.61,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-1","INDEX":138.61,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -2","INDEX":128.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-2","INDEX":129.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -2","INDEX":130.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-2","INDEX":131.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -2","INDEX":132.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -2","INDEX":133.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-2","INDEX":134.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -2","INDEX":135.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-2","INDEX":136.62,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-2","INDEX":137.62,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-2","INDEX":138.62,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -3","INDEX":128.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-3","INDEX":129.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -3","INDEX":130.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-3","INDEX":131.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -3","INDEX":132.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -3","INDEX":133.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-3","INDEX":134.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -3","INDEX":135.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-3","INDEX":136.63,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-3","INDEX":137.63,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-3","INDEX":138.63,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -4","INDEX":128.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-4","INDEX":129.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -4","INDEX":130.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-4","INDEX":131.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -4","INDEX":132.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -4","INDEX":133.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-4","INDEX":134.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -4","INDEX":135.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-4","INDEX":136.64,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-4","INDEX":137.64,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-4","INDEX":138.64,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -5","INDEX":128.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-5","INDEX":129.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -5","INDEX":130.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-5","INDEX":131.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -5","INDEX":132.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -5","INDEX":133.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-5","INDEX":134.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -5","INDEX":135.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-5","INDEX":136.65,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-5","INDEX":137.65,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-5","INDEX":138.65,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -6","INDEX":128.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-6","INDEX":129.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -6","INDEX":130.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-6","INDEX":131.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -6","INDEX":132.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -6","INDEX":133.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-6","INDEX":134.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -6","INDEX":135.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-6","INDEX":136.66,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-6","INDEX":137.66,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-6","INDEX":138.66,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0}] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/soilConstMatrix6.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/soilConstMatrix6.json new file mode 100644 index 0000000..891f0f1 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/soilConstMatrix6.json @@ -0,0 +1,1495 @@ +[ + { + "X": 1, + "NAME": "denitrification rate per g of CO2 respiration of SOM", + "INDEX": 4, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 2, + "NAME": "nitrification coefficient 1 ", + "INDEX": 5, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 3, + "NAME": "nitrification coefficient 2", + "INDEX": 6, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 4, + "NAME": "coefficient of N2O emission of nitrification", + "INDEX": 7, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 5, + "NAME": "NH4 mobilen proportion", + "INDEX": 8, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 6, + "NAME": "NO3 mobilen proportion", + "INDEX": 9, + "UNIT": "prop", + "MIN": 0.8, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 7, + "NAME": "e-folding depth of decomposition rate's depth scalar", + "INDEX": 10, + "UNIT": "m", + "MIN": 6, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 8, + "NAME": "fraction of dissolved part of SOIL1 organic matter", + "INDEX": 11, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 9, + "NAME": "fraction of dissolved part of SOIL2 organic matter", + "INDEX": 12, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 10, + "NAME": "fraction of dissolved part of SOIL3organic matter", + "INDEX": 13, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 11, + "NAME": "fraction of dissolved part of SOIL4 organic matter", + "INDEX": 14, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 12, + "NAME": "minimum WFPS for scalar of nitrification calculation", + "INDEX": 15, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 0, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 13, + "NAME": "lower optimum WFPS for scalar of nitrification calculation", + "INDEX": 16, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 14, + "NAME": "higher optimum WFPS for scalar of nitrification calculation", + "INDEX": 17, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 2, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 15, + "NAME": "minimum value for saturated WFPS scalar of nitrification calculation", + "INDEX": 18, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 16, + "NAME": "critical value of dissolved N and C in bottom (inactive layer)", + "INDEX": 19, + "UNIT": "ppm", + "MIN": 0, + "MAX": 1000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 17, + "NAME": "respiration fractions for fluxes between compartments (l1s1)", + "INDEX": 22, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 18, + "NAME": "respiration fractions for fluxes between compartments (l2s2)", + "INDEX": 23, + "UNIT": "prop", + "MIN": 0.55, + "MAX": 0.55, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 19, + "NAME": "respiration fractions for fluxes between compartments (l4s3)", + "INDEX": 24, + "UNIT": "prop", + "MIN": 0.29, + "MAX": 0.29, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 20, + "NAME": "respiration fractions for fluxes between compartments (s1s2)", + "INDEX": 25, + "UNIT": "prop", + "MIN": 0.28, + "MAX": 0.28, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 21, + "NAME": "respiration fractions for fluxes between compartments (s2s3)", + "INDEX": 26, + "UNIT": "prop", + "MIN": 0.46, + "MAX": 0.46, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 22, + "NAME": "respiration fractions for fluxes between compartments (s3s4)", + "INDEX": 27, + "UNIT": "prop", + "MIN": 0.55, + "MAX": 0.55, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 23, + "NAME": "rate constant scalar of labile litter pool", + "INDEX": 28, + "UNIT": "1/day", + "MIN": 0.7, + "MAX": 0.7, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 24, + "NAME": "rate constant scalar of cellulose litter pool", + "INDEX": 29, + "UNIT": "1/day", + "MIN": 0.07, + "MAX": 0.07, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 25, + "NAME": "rate constant scalar of lignin litter pool", + "INDEX": 30, + "UNIT": "1/day", + "MIN": 0.014, + "MAX": 0.014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 26, + "NAME": "rate constant scalar of fast microbial recycling pool", + "INDEX": 31, + "UNIT": "1/day", + "MIN": 0.07, + "MAX": 0.07, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 27, + "NAME": "rate constant scalar of medium microbial recycling pool", + "INDEX": 32, + "UNIT": "1/day", + "MIN": 0.014, + "MAX": 0.014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 28, + "NAME": "rate constant scalar of slow microbial recycling pool", + "INDEX": 33, + "UNIT": "1/day", + "MIN": 0.0014, + "MAX": 0.0014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 29, + "NAME": "rate constant scalar of recalcitrant SOM (humus) pool", + "INDEX": 34, + "UNIT": "1/day", + "MIN": 0.0001, + "MAX": 0.0001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 30, + "NAME": "rate constant scalar of physical fragmentation of coarse woody debris", + "INDEX": 35, + "UNIT": "1/day", + "MIN": 0.001, + "MAX": 0.001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 31, + "NAME": "param1 for CH4 calculations (empirical function of BD)", + "INDEX": 38, + "UNIT": "dimless", + "MIN": 212.5, + "MAX": 212.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 32, + "NAME": "param2 for CH4 calculations (empirical function of BD)", + "INDEX": 39, + "UNIT": "dimless", + "MIN": 1.81, + "MAX": 1.81, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 33, + "NAME": "param1 for CH4 calculations (empirical function of VWC)", + "INDEX": 40, + "UNIT": "dimless", + "MIN": -1.353, + "MAX": -1.353, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 34, + "NAME": "param2 for CH4 calculations (empirical function of VWC)", + "INDEX": 41, + "UNIT": "dimless", + "MIN": 0.2, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 35, + "NAME": "param3 for CH4 calculations (empirical function of VWC)", + "INDEX": 42, + "UNIT": "dimless", + "MIN": 1.781, + "MAX": 1.781, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 36, + "NAME": "param4 for CH4 calculations (empirical function of VWC)", + "INDEX": 43, + "UNIT": "dimless", + "MIN": 6.786, + "MAX": 6.786, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 37, + "NAME": "param1 for CH4 calculations (empirical function of Tsoil)", + "INDEX": 44, + "UNIT": "dimless", + "MIN": 0.01, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 38, + "NAME": "depth of soil", + "INDEX": 47, + "UNIT": "m", + "MIN": 1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 39, + "NAME": "limit of first stage evaporation", + "INDEX": 48, + "UNIT": "prop", + "MIN": 1, + "MAX": 9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 40, + "NAME": "maximum height of pond water", + "INDEX": 49, + "UNIT": "mm", + "MIN": 0, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 41, + "NAME": "curvature of soil stress functionr", + "INDEX": 50, + "UNIT": "dimless", + "MIN": 0.1, + "MAX": 5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 42, + "NAME": "runoff curve parameter", + "INDEX": 51, + "UNIT": "dimless", + "MIN": 10, + "MAX": 90, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 43, + "NAME": "aerodynamic resistance", + "INDEX": 52, + "UNIT": "s/m", + "MIN": 60, + "MAX": 200, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-0", + "INDEX": 55.9, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 1, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-0", + "INDEX": 56.9, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 1, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-0", + "INDEX": 57.9, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-0", + "INDEX": 58.9, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-0", + "INDEX": 59.9, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-0", + "INDEX": 60.9, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-0", + "INDEX": 61.9, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-0", + "INDEX": 62.9, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-0", + "INDEX": 63.9, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-0", + "INDEX": 64.9, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-1", + "INDEX": 55.91, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 3, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-1", + "INDEX": 56.91, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 3, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-1", + "INDEX": 57.91, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-1", + "INDEX": 58.91, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-1", + "INDEX": 59.91, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-1", + "INDEX": 60.91, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-1", + "INDEX": 61.91, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-1", + "INDEX": 62.91, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-1", + "INDEX": 63.91, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-1", + "INDEX": 64.91, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-2", + "INDEX": 55.92, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-2", + "INDEX": 56.92, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-2", + "INDEX": 57.92, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-2", + "INDEX": 58.92, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-2", + "INDEX": 59.92, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-2", + "INDEX": 60.92, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-2", + "INDEX": 61.92, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-2", + "INDEX": 62.92, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-2", + "INDEX": 63.92, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-2", + "INDEX": 64.92, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-3", + "INDEX": 55.93, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-3", + "INDEX": 56.93, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-3", + "INDEX": 57.93, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-3", + "INDEX": 58.93, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-3", + "INDEX": 59.93, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-3", + "INDEX": 60.93, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-3", + "INDEX": 61.93, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-3", + "INDEX": 62.93, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-3", + "INDEX": 63.93, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-3", + "INDEX": 64.93, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-4", + "INDEX": 55.94, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 9, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-4", + "INDEX": 56.94, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 9, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-4", + "INDEX": 57.94, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-4", + "INDEX": 58.94, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-4", + "INDEX": 59.94, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-4", + "INDEX": 60.94, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-4", + "INDEX": 61.94, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-4", + "INDEX": 62.94, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-4", + "INDEX": 63.94, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-4", + "INDEX": 64.94, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-5", + "INDEX": 55.95, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 11, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-5", + "INDEX": 56.95, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 11, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-5", + "INDEX": 57.95, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-5", + "INDEX": 58.95, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-5", + "INDEX": 59.95, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-5", + "INDEX": 60.95, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-5", + "INDEX": 61.95, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-5", + "INDEX": 62.95, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-5", + "INDEX": 63.95, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-5", + "INDEX": 64.95, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-6", + "INDEX": 55.96, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 13, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-6", + "INDEX": 56.96, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 13, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-6", + "INDEX": 57.96, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-6", + "INDEX": 58.96, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-6", + "INDEX": 59.96, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-6", + "INDEX": 60.96, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-6", + "INDEX": 61.96, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-6", + "INDEX": 62.96, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-6", + "INDEX": 63.96, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-6", + "INDEX": 64.96, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-7", + "INDEX": 55.97, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 15, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-7", + "INDEX": 56.97, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 15, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-7", + "INDEX": 57.97, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-7", + "INDEX": 58.97, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-7", + "INDEX": 59.97, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-7", + "INDEX": 60.97, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-7", + "INDEX": 61.97, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-7", + "INDEX": 62.97, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-7", + "INDEX": 63.97, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-7", + "INDEX": 64.97, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-8", + "INDEX": 55.98, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 17, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-8", + "INDEX": 56.98, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 17, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-8", + "INDEX": 57.98, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-8", + "INDEX": 58.98, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-8", + "INDEX": 59.98, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-8", + "INDEX": 60.98, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-8", + "INDEX": 61.98, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-8", + "INDEX": 62.98, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-8", + "INDEX": 63.98, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-8", + "INDEX": 64.98, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-9", + "INDEX": 55.99, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 19, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-9", + "INDEX": 56.99, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 19, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-9", + "INDEX": 57.99, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-9", + "INDEX": 58.99, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-9", + "INDEX": 59.99, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-9", + "INDEX": 60.99, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-9", + "INDEX": 61.99, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-9", + "INDEX": 62.99, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-9", + "INDEX": 63.99, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-9", + "INDEX": 64.99, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + } +] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/varTable6.json b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/varTable6.json new file mode 100644 index 0000000..1900b6f --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/data/varTable6.json @@ -0,0 +1,15770 @@ +[ + { + "codes": 0, + "names": "remdays_curgrowth", + "units": "n", + "descriptions": "Remaining days current growth season" + }, + { + "codes": 1, + "names": "remdays_transfer", + "units": "n", + "descriptions": "Remaining days transfer period" + }, + { + "codes": 2, + "names": "remdays_litfall", + "units": "n", + "descriptions": "Remaining days litterfall" + }, + { + "codes": 3, + "names": "predays_transfer", + "units": "n", + "descriptions": "Previous days transfer period" + }, + { + "codes": 4, + "names": "predays_litfall", + "units": "n", + "descriptions": "Previous days litterfall" + }, + { + "codes": 5, + "names": "n_growthday", + "units": "n", + "descriptions": "Number of growing days" + }, + { + "codes": 6, + "names": "n_transferday", + "units": "n", + "descriptions": "Number of transfer days" + }, + { + "codes": 7, + "names": "n_litfallday", + "units": "n", + "descriptions": "Number of litterfall days" + }, + { + "codes": 8, + "names": "yday_total", + "units": "dimless", + "descriptions": "Counter for simdays of the whole simulation" + }, + { + "codes": 9, + "names": "phpsl_dev_rate", + "units": "dimless", + "descriptions": "Photoslowing effect rel. development" + }, + { + "codes": 10, + "names": "vern_dev_rate", + "units": "dimless", + "descriptions": "Vernalization rel. development" + }, + { + "codes": 11, + "names": "vern_days", + "units": "n", + "descriptions": "Vernalization days" + }, + { + "codes": 12, + "names": "GDD_limit", + "units": "degree", + "descriptions": "Lower limit of GDD in given phen.phase" + }, + { + "codes": 13, + "names": "GDD_crit[0]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 1" + }, + { + "codes": 14, + "names": "GDD_crit[1]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 2" + }, + { + "codes": 15, + "names": "GDD_crit[2]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 3" + }, + { + "codes": 16, + "names": "GDD_crit[3]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 4" + }, + { + "codes": 17, + "names": "GDD_crit[4]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 5" + }, + { + "codes": 18, + "names": "GDD_crit[5]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 6" + }, + { + "codes": 19, + "names": "GDD_crit[6]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 7" + }, + { + "codes": 20, + "names": "GDD_emergSTART", + "units": "degree", + "descriptions": "GDD at start of emergence period" + }, + { + "codes": 21, + "names": "GDD_emergEND", + "units": "degree", + "descriptions": "GDD at end of emergence period" + }, + { + "codes": 22, + "names": "onday", + "units": "dimless", + "descriptions": "Actual onday value" + }, + { + "codes": 23, + "names": "offday", + "units": "dimless", + "descriptions": "Actual offday value" + }, + { + "codes": 24, + "names": "planttype", + "units": "dimless", + "descriptions": "Plant type (maize:1,wheat:2,barley:3,...)" + }, + { + "codes": 40, + "names": "tACCLIM", + "units": "degree", + "descriptions": "Acclimation temperature" + }, + { + "codes": 41, + "names": "tnight", + "units": "degree", + "descriptions": "Nighttime temperature" + }, + { + "codes": 42, + "names": "tavg11_ra", + "units": "degree", + "descriptions": "11-day running average temperature" + }, + { + "codes": 43, + "names": "tavg10_ra", + "units": "degree", + "descriptions": "10-day running average temperature" + }, + { + "codes": 44, + "names": "tavg30_ra", + "units": "degree", + "descriptions": "30-day running average temperature" + }, + { + "codes": 45, + "names": "F_temprad", + "units": "dimless", + "descriptions": "Soil temperature factor (air temperature and radiation)" + }, + { + "codes": 46, + "names": "F_temprad_ra", + "units": "dimless", + "descriptions": "5-day running average soil temperature factor" + }, + { + "codes": 47, + "names": "tsoil_surface", + "units": "degree", + "descriptions": "Soil surface temperature" + }, + { + "codes": 48, + "names": "tsoil_surface_pre", + "units": "degree", + "descriptions": "Soil surface temperature of previous day" + }, + { + "codes": 49, + "names": "tsoil_avg", + "units": "degree", + "descriptions": "Average soil temperature" + }, + { + "codes": 50, + "names": "tsoil[0]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 1 (0 - 2 cm)" + }, + { + "codes": 51, + "names": "tsoil[1]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 2 (3 - 10 cm)" + }, + { + "codes": 52, + "names": "tsoil[2]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 3 (10 - 30 cm)" + }, + { + "codes": 53, + "names": "tsoil[3]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 4 (30 - 60 cm)" + }, + { + "codes": 54, + "names": "tsoil[4]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 5 (60 - 90 cm)" + }, + { + "codes": 55, + "names": "tsoil[5]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 6 (90 - 120 cm)" + }, + { + "codes": 56, + "names": "tsoil[6]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 7 (120 - 150 cm)" + }, + { + "codes": 57, + "names": "tsoil[7]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 8 (150 - 200 cm)" + }, + { + "codes": 58, + "names": "tsoil[8]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 9 (200 - 400 cm)" + }, + { + "codes": 59, + "names": "tsoil[9]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 60, + "names": "swRADnet", + "units": "Wm-2", + "descriptions": "Net shortwave radiation" + }, + { + "codes": 61, + "names": "lwRADnet", + "units": "Wm-2", + "descriptions": "Net outgoing longwave radiation" + }, + { + "codes": 62, + "names": "RADnet", + "units": "Wm-2", + "descriptions": "Daylight average net radiation flux" + }, + { + "codes": 63, + "names": "RADnet_per_plaisun", + "units": "Wm-2", + "descriptions": "Daylight avg. net radiation flux sunshade proj. leaf area index" + }, + { + "codes": 64, + "names": "RADnet_per_plaishade", + "units": "Wm-2", + "descriptions": "Daylight avg. net radiation flux sunlit proj. leaf area index" + }, + { + "codes": 65, + "names": "swavgfd", + "units": "Wm-2", + "descriptions": "Daylight average shortwave flux" + }, + { + "codes": 66, + "names": "swabs", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux" + }, + { + "codes": 67, + "names": "swtrans", + "units": "Wm-2", + "descriptions": "Transmitted shortwave flux" + }, + { + "codes": 68, + "names": "swabs_per_plaisun", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux sunlit prof. leaf area index" + }, + { + "codes": 69, + "names": "swabs_per_plaishade", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux sunshade prof. leaf area index" + }, + { + "codes": 70, + "names": "ppfd_per_plaisun", + "units": "µmolm-2s-1", + "descriptions": "PPFD sunlit proj. leaf area index" + }, + { + "codes": 71, + "names": "ppfd_per_plaishade", + "units": "µmolm-2s-1", + "descriptions": "PPFD sunshade proj. leaf area index" + }, + { + "codes": 72, + "names": "parabs", + "units": "Wm-2", + "descriptions": "Canopy absorbed PAR" + }, + { + "codes": 73, + "names": "parabs_plaisun", + "units": "Wm-2", + "descriptions": "PAR absorbed by sunlit canopy fraction" + }, + { + "codes": 74, + "names": "parabs_plaishade", + "units": "Wm-2", + "descriptions": "PAR absorbed by sunshade canopy fraction" + }, + { + "codes": 75, + "names": "GDD", + "units": "degree", + "descriptions": "GDD" + }, + { + "codes": 76, + "names": "GDD_wMOD", + "units": "degree", + "descriptions": "GDD modified by vern. and photop. effect" + }, + { + "codes": 77, + "names": "GDDpre", + "units": "degree", + "descriptions": "GDD previous day" + }, + { + "codes": 78, + "names": "pa", + "units": "Pa", + "descriptions": "Atmospheric pressure" + }, + { + "codes": 80, + "names": "soilw[0]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 1 (0 - 2 cm)" + }, + { + "codes": 81, + "names": "soilw[1]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 2 (3 - 10 cm)" + }, + { + "codes": 82, + "names": "soilw[2]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 3 (10 - 30 cm)" + }, + { + "codes": 83, + "names": "soilw[3]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 4 (30 - 60 cm)" + }, + { + "codes": 84, + "names": "soilw[4]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 5 (60 - 90 cm)" + }, + { + "codes": 85, + "names": "soilw[5]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 6 (90 - 120 cm)" + }, + { + "codes": 86, + "names": "soilw[6]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 7 (120 - 150 cm)" + }, + { + "codes": 87, + "names": "soilw[7]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 8 (150 - 200 cm)" + }, + { + "codes": 88, + "names": "soilw[8]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 9 (200 - 400 cm)" + }, + { + "codes": 89, + "names": "soilw[9]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 90, + "names": "soilw_SUM", + "units": "kgH2O m-2", + "descriptions": "SWC" + }, + { + "codes": 91, + "names": "pond_water", + "units": "kgH2O m-2", + "descriptions": "Pond water" + }, + { + "codes": 92, + "names": "snoww", + "units": "kgH2O m-2", + "descriptions": "Snow water" + }, + { + "codes": 93, + "names": "canopyw", + "units": "kgH2O m-2", + "descriptions": "Canopy water" + }, + { + "codes": 94, + "names": "prcp_src", + "units": "kgH2O m-2", + "descriptions": "Precipitation" + }, + { + "codes": 95, + "names": "soilevap_snk", + "units": "kgH2O m-2", + "descriptions": "Soil water evaporation" + }, + { + "codes": 96, + "names": "snowsubl_snk", + "units": "kgH2O m-2", + "descriptions": "Snow sublimation" + }, + { + "codes": 97, + "names": "canopyevap_snk", + "units": "kgH2O m-2", + "descriptions": "Canopy evaporation" + }, + { + "codes": 98, + "names": "pondwevap_snk", + "units": "kgH2O m-2", + "descriptions": "Pond water evaporation" + }, + { + "codes": 99, + "names": "trans_snk", + "units": "kgH2O m-2", + "descriptions": "Transpiration" + }, + { + "codes": 100, + "names": "runoff_snk", + "units": "kgH2O m-2", + "descriptions": "Runoff" + }, + { + "codes": 101, + "names": "deeppercolation_snk", + "units": "kgH2O m-2", + "descriptions": "Deep percolation" + }, + { + "codes": 102, + "names": "groundwater_src", + "units": "kgH2O m-2", + "descriptions": "Water plus from groundwater" + }, + { + "codes": 103, + "names": "canopyw_THNsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss thinning" + }, + { + "codes": 104, + "names": "canopyw_MOWsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss mowing" + }, + { + "codes": 105, + "names": "canopyw_HRVsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss harvesting" + }, + { + "codes": 106, + "names": "canopyw_PLGsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss ploughing" + }, + { + "codes": 107, + "names": "canopyw_GRZsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss grazing" + }, + { + "codes": 108, + "names": "IRGsrc_W", + "units": "kgH2O m-2", + "descriptions": "Water income from irrigation" + }, + { + "codes": 109, + "names": "FRZsrc_W", + "units": "kgH2O m-2", + "descriptions": "Water income from fertilizers" + }, + { + "codes": 110, + "names": "WbalanceERR", + "units": "kgH2O m-2", + "descriptions": "Water balance error" + }, + { + "codes": 111, + "names": "inW", + "units": "kgH2O m-2", + "descriptions": "SUM of water input" + }, + { + "codes": 112, + "names": "outW", + "units": "kgH2O m-2", + "descriptions": "SUM of water output" + }, + { + "codes": 113, + "names": "storeW", + "units": "kgH2O m-2", + "descriptions": "SUM of water storage" + }, + { + "codes": 114, + "names": "soil_evapCUM1", + "units": "kgH2O m-2", + "descriptions": "Cumulated soil evaporation in first evaporation phase (no limit)" + }, + { + "codes": 115, + "names": "soil_evapCUM2", + "units": "kgH2O m-2", + "descriptions": "Cumulated soil evaporation in second evaporation phase (dsr limit)" + }, + { + "codes": 116, + "names": "soilw_2 m", + "units": "kgH2O m-2", + "descriptions": "SWC in 0-2 m" + }, + { + "codes": 117, + "names": "soilw_RZ", + "units": "kgH2O m-2", + "descriptions": "SWC in rootzone" + }, + { + "codes": 118, + "names": "soilw_RZ_avail", + "units": "kgH2O m-2", + "descriptions": "SWC in rootzone available for plants" + }, + { + "codes": 119, + "names": "soilw_avail[0]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 2 (0 - 3 cm)" + }, + { + "codes": 120, + "names": "soilw_avail[1]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 2 (3 - 10 cm)" + }, + { + "codes": 121, + "names": "soilw_avail[2]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 3 (10 - 30 cm)" + }, + { + "codes": 122, + "names": "soilw_avail[3]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 4 (30 - 60 cm)" + }, + { + "codes": 123, + "names": "soilw_avail[4]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 5 (60 - 90 cm)" + }, + { + "codes": 124, + "names": "soilw_avail[5]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 6 (90 - 120 cm)" + }, + { + "codes": 125, + "names": "soilw_avail[6]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 7 (120 - 150 cm)" + }, + { + "codes": 126, + "names": "soilw_avail[7]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 8 (150 - 200 cm)" + }, + { + "codes": 127, + "names": "soilw_avail[8]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 9 (200 - 400 cm)" + }, + { + "codes": 128, + "names": "soilw_avail[9]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 10 (400 - 1000 cm)" + }, + { + "codes": 150, + "names": "prcp_to_canopyw", + "units": "kgH2O m-2 day-1", + "descriptions": "Interception on canopy" + }, + { + "codes": 151, + "names": "prcp_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Precipitation entering soilwater pool" + }, + { + "codes": 152, + "names": "prcp_to_snoww", + "units": "kgH2O m-2 day-1", + "descriptions": "Snowpack accumulation" + }, + { + "codes": 153, + "names": "prcp_to_runoff", + "units": "kgH2O m-2 day-1", + "descriptions": "Runoff flux" + }, + { + "codes": 154, + "names": "canopyw_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Evaporation from canopy" + }, + { + "codes": 155, + "names": "canopyw_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy drip and stemflow" + }, + { + "codes": 156, + "names": "pondw_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Pond water evaporation" + }, + { + "codes": 157, + "names": "snoww_subl", + "units": "kgH2O m-2 day-1", + "descriptions": "Sublimation from snowpack" + }, + { + "codes": 158, + "names": "snoww_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Melt from snowpack" + }, + { + "codes": 159, + "names": "soilw_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Evaporation from soil" + }, + { + "codes": 160, + "names": "soilw_trans[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 1 (0 - 2 cm)" + }, + { + "codes": 161, + "names": "soilw_trans[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 2 (3 - 10 cm)" + }, + { + "codes": 162, + "names": "soilw_trans[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 3 (10 - 30 cm)" + }, + { + "codes": 163, + "names": "soilw_trans[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 4 (30 - 60 cm)" + }, + { + "codes": 164, + "names": "soilw_trans[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 5 (60 - 90 cm)" + }, + { + "codes": 165, + "names": "soilw_trans[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 6 (90 - 120 cm)" + }, + { + "codes": 166, + "names": "soilw_trans[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 7 (120 - 150 cm)" + }, + { + "codes": 167, + "names": "soilw_trans[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 8 (150 - 200 cm)" + }, + { + "codes": 168, + "names": "soilw_trans[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 9 (200 - 400 cm)" + }, + { + "codes": 169, + "names": "soilw_trans[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 170, + "names": "soilw_trans_SUM", + "units": "kgH2O m-2 day-1", + "descriptions": "SUM of transpiration from the soil layers" + }, + { + "codes": 171, + "names": "evapotransp", + "units": "kgH2O m-2 day-1", + "descriptions": "Evapotranspiration (evap+transp+subl)" + }, + { + "codes": 172, + "names": "pondw_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Water flux from pond to soil" + }, + { + "codes": 173, + "names": "soilw_to_pondw", + "units": "kgH2O m-2 day-1", + "descriptions": "Water flux from soil to pond" + }, + { + "codes": 174, + "names": "soilw_percolated[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 1 (0-3 cm)" + }, + { + "codes": 175, + "names": "soilw_percolated[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 2 (3-10 cm)" + }, + { + "codes": 176, + "names": "soilw_percolated[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 3 (10-30 cm)" + }, + { + "codes": 177, + "names": "soilw_percolated[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 4 (30-60 cm)" + }, + { + "codes": 178, + "names": "soilw_percolated[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 5 (60-90 cm)" + }, + { + "codes": 179, + "names": "soilw_percolated[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 6 (90-120 cm)" + }, + { + "codes": 180, + "names": "soilw_percolated[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 7 (120-150 cm)" + }, + { + "codes": 181, + "names": "soilw_percolated[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 8 (150-200 cm)" + }, + { + "codes": 182, + "names": "soilw_percolated[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 9 (200-400 cm)" + }, + { + "codes": 183, + "names": "soilw_percolated[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 184, + "names": "soilw_diffused[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 1 (0-3 cm)" + }, + { + "codes": 185, + "names": "soilw_diffused[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 2 (3-10 cm)" + }, + { + "codes": 186, + "names": "soilw_diffused[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 3 (10-30 cm)" + }, + { + "codes": 187, + "names": "soilw_diffused[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 4 (30-60 cm)" + }, + { + "codes": 188, + "names": "soilw_diffused[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 5 (60-90 cm)" + }, + { + "codes": 189, + "names": "soilw_diffused[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 6 (90-120 cm)" + }, + { + "codes": 190, + "names": "soilw_diffused[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 7 (120-150 cm)" + }, + { + "codes": 191, + "names": "soilw_diffused[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 8 (150-200 cm)" + }, + { + "codes": 192, + "names": "soilw_diffused[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 9 (200-400 cm)" + }, + { + "codes": 193, + "names": "soilw_diffused[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 10 (400-1000 cm)" + }, + { + "codes": 194, + "names": "soilw_from_GW[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 1 (0-3 cm)" + }, + { + "codes": 195, + "names": "soilw_from_GW[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 2 (3-10 cm)" + }, + { + "codes": 196, + "names": "soilw_from_GW[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 3 (10-30 cm)" + }, + { + "codes": 197, + "names": "soilw_from_GW[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 4 (30-60 cm)" + }, + { + "codes": 198, + "names": "soilw_from_GW[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 5 (60-90 cm)" + }, + { + "codes": 199, + "names": "soilw_from_GW[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 6 (90-120 cm)" + }, + { + "codes": 200, + "names": "soilw_from_GW[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 7 (120-150 cm)" + }, + { + "codes": 201, + "names": "soilw_from_GW[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 8 (150-200 cm)" + }, + { + "codes": 202, + "names": "soilw_from_GW[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 9 (200-400 cm)" + }, + { + "codes": 203, + "names": "soilw_from_GW[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 10 (400-1000 cm)" + }, + { + "codes": 204, + "names": "soilw_leached_RZ", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water leached from rootzone (perc+diff)" + }, + { + "codes": 205, + "names": "canopyw_to_THN", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss thinning" + }, + { + "codes": 206, + "names": "canopyw_to_MOW", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss mowing" + }, + { + "codes": 207, + "names": "canopyw_to_HRV", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss harvesting" + }, + { + "codes": 208, + "names": "canopyw_to_PLG", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss ploughing" + }, + { + "codes": 209, + "names": "canopyw_to_GRZ", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss grazing" + }, + { + "codes": 210, + "names": "IRG_to_prcp", + "units": "kgH2O m-2 day-1", + "descriptions": "Irrigated water amount" + }, + { + "codes": 211, + "names": "FRZ_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Water flux from fertilization" + }, + { + "codes": 212, + "names": "pot_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential evaporation" + }, + { + "codes": 213, + "names": "pot_infilt", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential infiltration" + }, + { + "codes": 214, + "names": "soilw_transDEMAND[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 1 (0 - 2 cm)" + }, + { + "codes": 215, + "names": "soilw_transDEMAND[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 2 (3 - 10 cm)" + }, + { + "codes": 216, + "names": "soilw_transDEMAND[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 3 (10 - 30 cm)" + }, + { + "codes": 217, + "names": "soilw_transDEMAND[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 4 (30 - 60 cm)" + }, + { + "codes": 218, + "names": "soilw_transDEMAND[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 5 (60 - 90 cm)" + }, + { + "codes": 219, + "names": "soilw_transDEMAND[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 6 (90 - 120 cm)" + }, + { + "codes": 220, + "names": "soilw_transDEMAND[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 7 (120 - 150 cm)" + }, + { + "codes": 221, + "names": "soilw_transDEMAND[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 8 (150 - 200 cm)" + }, + { + "codes": 222, + "names": "soilw_transDEMAND[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 9 (200 - 400 cm)" + }, + { + "codes": 223, + "names": "soilw_transDEMAND[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 224, + "names": "soilw_transDEMAND_SUM", + "units": "kgH2O m-2 day-1", + "descriptions": "Sum of transpiration demand" + }, + { + "codes": 225, + "names": "soilw_transPOT", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential transpiration (no SWC limit)" + }, + { + "codes": 226, + "names": "PET", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential evapotranspiration" + }, + { + "codes": 300, + "names": "leafcSUM_phenphase[0]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 1" + }, + { + "codes": 301, + "names": "leafcSUM_phenphase[1]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 2" + }, + { + "codes": 302, + "names": "leafcSUM_phenphase[2]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 3" + }, + { + "codes": 303, + "names": "leafcSUM_phenphase[3]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 4" + }, + { + "codes": 304, + "names": "leafcSUM_phenphase[4]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 5" + }, + { + "codes": 305, + "names": "leafcSUM_phenphase[5]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 6" + }, + { + "codes": 306, + "names": "leafcSUM_phenphase[6]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 7" + }, + { + "codes": 307, + "names": "leafc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of leaf pool" + }, + { + "codes": 308, + "names": "leafc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of leaf storage pool" + }, + { + "codes": 309, + "names": "leafc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of leaf transfer pool" + }, + { + "codes": 310, + "names": "frootc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of fine root pool" + }, + { + "codes": 311, + "names": "frootc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of fine root storage pool" + }, + { + "codes": 312, + "names": "frootc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of fine root storage pool" + }, + { + "codes": 313, + "names": "fruitc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of fruit pool" + }, + { + "codes": 314, + "names": "fruitc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of fruit storage pool" + }, + { + "codes": 315, + "names": "fruitc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of fruit transfer pool" + }, + { + "codes": 316, + "names": "softstemc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of softstem pool" + }, + { + "codes": 317, + "names": "softstemc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of softstem storage pool" + }, + { + "codes": 318, + "names": "softstemc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of softstem transfer pool" + }, + { + "codes": 319, + "names": "livestemc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of live stem pool" + }, + { + "codes": 320, + "names": "livestemc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of live stem storage pool" + }, + { + "codes": 321, + "names": "livestemc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of live stem transfer pool" + }, + { + "codes": 322, + "names": "deadstemc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of dead stem pool" + }, + { + "codes": 323, + "names": "deadstemc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of dead stem storage pool" + }, + { + "codes": 324, + "names": "deadstemc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of dead stem transfer pool" + }, + { + "codes": 325, + "names": "livecrootc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of live coarse root pool" + }, + { + "codes": 326, + "names": "livecrootc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of live coarse root storge pool" + }, + { + "codes": 327, + "names": "livecrootc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of live coarse root transfer pool" + }, + { + "codes": 328, + "names": "deadcrootc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of dead coarse root pool" + }, + { + "codes": 329, + "names": "deadcrootc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of dead coarse root storage pool" + }, + { + "codes": 330, + "names": "deadcrootc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of dead coarse root transfer pool" + }, + { + "codes": 331, + "names": "gresp_storage", + "units": "kgC m-2", + "descriptions": "Growth respiration storage pool" + }, + { + "codes": 332, + "names": "gresp_transfer", + "units": "kgC m-2", + "descriptions": "Growth respiration transfer pool" + }, + { + "codes": 333, + "names": "nsc_w", + "units": "kgC m-2", + "descriptions": "Non-structured woody carbohydrate pool" + }, + { + "codes": 334, + "names": "nsc_nw", + "units": "kgC m-2", + "descriptions": "Non-structured non-woody carbohydrate pool" + }, + { + "codes": 335, + "names": "sc_w", + "units": "kgC m-2", + "descriptions": "Structured woody carbohydrate pool" + }, + { + "codes": 336, + "names": "sc_nw", + "units": "kgC m-2", + "descriptions": "Structured non-woody carbohydrate pool" + }, + { + "codes": 337, + "names": "cwdc[0]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 1 (0-3 cm)" + }, + { + "codes": 338, + "names": "cwdc[1]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 2 (3-10 cm)" + }, + { + "codes": 339, + "names": "cwdc[2]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 3 (10-30 cm)" + }, + { + "codes": 340, + "names": "cwdc[3]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 4 (30-60 cm)" + }, + { + "codes": 341, + "names": "cwdc[4]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 5 (60-90 cm)" + }, + { + "codes": 342, + "names": "cwdc[5]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 6 (90-120 cm)" + }, + { + "codes": 343, + "names": "cwdc[6]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 7 (120-150 cm)" + }, + { + "codes": 344, + "names": "cwdc[7]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 8 (150-200 cm)" + }, + { + "codes": 345, + "names": "cwdc[8]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 9 (200-400 cm)" + }, + { + "codes": 346, + "names": "cwdc[9]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 10 (400-1000 cm)" + }, + { + "codes": 347, + "names": "litr1c[0]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 348, + "names": "litr1c[1]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 349, + "names": "litr1c[2]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 350, + "names": "litr1c[3]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 351, + "names": "litr1c[4]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 352, + "names": "litr1c[5]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 353, + "names": "litr1c[6]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 354, + "names": "litr1c[7]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 355, + "names": "litr1c[8]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 356, + "names": "litr1c[9]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 357, + "names": "litr2c[0]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 358, + "names": "litr2c[1]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 359, + "names": "litr2c[2]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 360, + "names": "litr2c[3]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 361, + "names": "litr2c[4]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 362, + "names": "litr2c[5]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 363, + "names": "litr2c[6]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 364, + "names": "litr2c[7]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 365, + "names": "litr2c[8]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 366, + "names": "litr2c[9]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 367, + "names": "litr3c[0]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 368, + "names": "litr3c[1]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 369, + "names": "litr3c[2]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 370, + "names": "litr3c[3]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 371, + "names": "litr3c[4]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 372, + "names": "litr3c[5]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 373, + "names": "litr3c[6]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 374, + "names": "litr3c[7]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 375, + "names": "litr3c[8]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 376, + "names": "litr3c[9]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 377, + "names": "litr4c[0]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 378, + "names": "litr4c[1]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 379, + "names": "litr4c[2]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 380, + "names": "litr4c[3]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 381, + "names": "litr4c[4]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 382, + "names": "litr4c[5]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 383, + "names": "litr4c[6]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 384, + "names": "litr4c[7]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 385, + "names": "litr4c[8]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 386, + "names": "litr4c[9]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 387, + "names": "litrC[0]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 1 (0-3 cm)" + }, + { + "codes": 388, + "names": "litrC[1]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 2 (3-10 cm)" + }, + { + "codes": 389, + "names": "litrC[2]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 3 (10-30 cm)" + }, + { + "codes": 390, + "names": "litrC[3]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 4 (30-60 cm)" + }, + { + "codes": 391, + "names": "litrC[4]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 5 (60-90 cm)" + }, + { + "codes": 392, + "names": "litrC[5]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 6 (90-120 cm)" + }, + { + "codes": 393, + "names": "litrC[6]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 7 (120-150 cm)" + }, + { + "codes": 394, + "names": "litrC[7]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 8 (150-200 cm)" + }, + { + "codes": 395, + "names": "litrC[8]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 9 (200-400 cm)" + }, + { + "codes": 396, + "names": "litrC[9]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 10 (400-1000 cm)" + }, + { + "codes": 397, + "names": "litr1c_total", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter" + }, + { + "codes": 398, + "names": "litr2c_total", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter" + }, + { + "codes": 399, + "names": "litr3c_total", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter" + }, + { + "codes": 400, + "names": "litr4c_total", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter" + }, + { + "codes": 401, + "names": "cwdc_total", + "units": "kgC m-2", + "descriptions": "Total carbon content of coarse woody debris" + }, + { + "codes": 402, + "names": "STDBc_leaf", + "units": "kgC m-2", + "descriptions": "Wilted leaf biomass" + }, + { + "codes": 403, + "names": "STDBc_froot", + "units": "kgC m-2", + "descriptions": "Wilted fine root biomass" + }, + { + "codes": 404, + "names": "STDBc_fruit", + "units": "kgC m-2", + "descriptions": "Wilted fruit biomass" + }, + { + "codes": 405, + "names": "STDBc_softstem", + "units": "kgC m-2", + "descriptions": "Wilted softstem biomass" + }, + { + "codes": 406, + "names": "STDBc_nsc", + "units": "kgC m-2", + "descriptions": "Wilted non-stuctured carbohydrate biomass" + }, + { + "codes": 407, + "names": "STDBc_above", + "units": "kgC m-2", + "descriptions": "Wilted aboveground plant biomass" + }, + { + "codes": 408, + "names": "STDBc_below", + "units": "kgC m-2", + "descriptions": "Wilted belowground plant biomass" + }, + { + "codes": 409, + "names": "CTDBc_leaf", + "units": "kgC m-2", + "descriptions": "Cut-down leaf biomass" + }, + { + "codes": 410, + "names": "CTDBc_froot", + "units": "kgC m-2", + "descriptions": "Cut-down fineroot biomass" + }, + { + "codes": 411, + "names": "CTDBc_fruit", + "units": "kgC m-2", + "descriptions": "Cut-down fruit biomass" + }, + { + "codes": 412, + "names": "CTDBc_softstem", + "units": "kgC m-2", + "descriptions": "Cut-down softstem biomass" + }, + { + "codes": 413, + "names": "CTDBc_nsc", + "units": "kgC m-2", + "descriptions": "Cut-down non-structured biomass" + }, + { + "codes": 414, + "names": "CTDBc_cstem", + "units": "kgC m-2", + "descriptions": "Cut-down coarse stem biomass" + }, + { + "codes": 415, + "names": "CTDBc_croot", + "units": "kgC m-2", + "descriptions": "Cut-down coarse root biomass" + }, + { + "codes": 416, + "names": "CTDBc_above", + "units": "kgC m-2", + "descriptions": "Cut-down aboveground plant biomass" + }, + { + "codes": 417, + "names": "CTDBc_below", + "units": "kgC m-2", + "descriptions": "Cut-down belowground plant biomass" + }, + { + "codes": 418, + "names": "soil1c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 419, + "names": "soil1c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 420, + "names": "soil1c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 421, + "names": "soil1c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 422, + "names": "soil1c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 423, + "names": "soil1c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 424, + "names": "soil1c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 425, + "names": "soil1c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 426, + "names": "soil1c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 427, + "names": "soil1c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 428, + "names": "soil2c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 429, + "names": "soil2c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 430, + "names": "soil2c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 431, + "names": "soil2c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 432, + "names": "soil2c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 433, + "names": "soil2c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 434, + "names": "soil2c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 435, + "names": "soil2c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 436, + "names": "soil2c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 437, + "names": "soil2c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 438, + "names": "soil3c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 439, + "names": "soil3c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 440, + "names": "soil3c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 441, + "names": "soil3c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 442, + "names": "soil3c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 443, + "names": "soil3c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 444, + "names": "soil3c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 445, + "names": "soil3c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 446, + "names": "soil3c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 447, + "names": "soil3c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 448, + "names": "soil4c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 449, + "names": "soil4c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 450, + "names": "soil4c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 451, + "names": "soil4c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 452, + "names": "soil4c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 453, + "names": "soil4c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 454, + "names": "soil4c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 455, + "names": "soil4c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 456, + "names": "soil4c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 457, + "names": "soil4c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 458, + "names": "soilC[0]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 1 (0-3 cm)" + }, + { + "codes": 459, + "names": "soilC[1]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 2 (3-10 cm)" + }, + { + "codes": 460, + "names": "soilC[2]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 3 (10-30 cm)" + }, + { + "codes": 461, + "names": "soilC[3]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 4 (30-60 cm)" + }, + { + "codes": 462, + "names": "soilC[4]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 5 (60-90 cm)" + }, + { + "codes": 463, + "names": "soilC[5]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 6 (90-120 cm)" + }, + { + "codes": 464, + "names": "soilC[6]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 7 (120-150 cm)" + }, + { + "codes": 465, + "names": "soilC[7]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 8 (150-200 cm)" + }, + { + "codes": 466, + "names": "soilC[8]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 9 (200-400 cm)" + }, + { + "codes": 467, + "names": "soilC[9]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 468, + "names": "soil1_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 469, + "names": "soil1_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 470, + "names": "soil1_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 471, + "names": "soil1_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 472, + "names": "soil1_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 473, + "names": "soil1_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 474, + "names": "soil1_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 475, + "names": "soil1_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 476, + "names": "soil1_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 477, + "names": "soil1_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 478, + "names": "soil2_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 479, + "names": "soil2_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 480, + "names": "soil2_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 481, + "names": "soil2_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 482, + "names": "soil2_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 483, + "names": "soil2_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 484, + "names": "soil2_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 485, + "names": "soil2_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 486, + "names": "soil2_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 487, + "names": "soil2_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 488, + "names": "soil3_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 489, + "names": "soil3_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 490, + "names": "soil3_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 491, + "names": "soil3_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 492, + "names": "soil3_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 493, + "names": "soil3_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 494, + "names": "soil3_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 495, + "names": "soil3_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 496, + "names": "soil3_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 497, + "names": "soil3_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 498, + "names": "soil4_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 499, + "names": "soil4_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 500, + "names": "soil4_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 501, + "names": "soil4_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 502, + "names": "soil4_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 503, + "names": "soil4_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 504, + "names": "soil4_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 505, + "names": "soil4_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 506, + "names": "soil4_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 507, + "names": "soil4_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 508, + "names": "soil_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 509, + "names": "soil_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 510, + "names": "soil_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 511, + "names": "soil_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 512, + "names": "soil_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 513, + "names": "soil_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 514, + "names": "soil_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 515, + "names": "soil_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 516, + "names": "soil_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 517, + "names": "soil_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 518, + "names": "soil1c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (labile)" + }, + { + "codes": 519, + "names": "soil2c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (fast)" + }, + { + "codes": 520, + "names": "soil3c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (slow)" + }, + { + "codes": 521, + "names": "soil4c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (stable)" + }, + { + "codes": 522, + "names": "cpool", + "units": "kgC m-2", + "descriptions": "Temporary photosynthate C pool" + }, + { + "codes": 523, + "names": "psnsun_src", + "units": "kgC m-2", + "descriptions": "Gross photosynthesis from sunlit canopy" + }, + { + "codes": 524, + "names": "psnshade_src", + "units": "kgC m-2", + "descriptions": "Gross photosynthesis from shaded canopy" + }, + { + "codes": 525, + "names": "NSC_mr_snk", + "units": "kgC m-2", + "descriptions": "Non-structured carbohydrate MR loss" + }, + { + "codes": 526, + "names": "actC_mr_snk", + "units": "kgC m-2", + "descriptions": "MR loss from actual carbon pool" + }, + { + "codes": 527, + "names": "leaf_mr_snk", + "units": "kgC m-2", + "descriptions": "Leaf maintenance respiration" + }, + { + "codes": 528, + "names": "froot_mr_snk", + "units": "kgC m-2", + "descriptions": "Fine root maintenance respiration" + }, + { + "codes": 529, + "names": "fruit_mr_snk", + "units": "kgC m-2", + "descriptions": "Fruit maintenance respiration" + }, + { + "codes": 530, + "names": "softstem_mr_snk", + "units": "kgC m-2", + "descriptions": "Softstem maintenance respiration" + }, + { + "codes": 531, + "names": "livestem_mr_snk", + "units": "kgC m-2", + "descriptions": "Live stem maintenance respiration" + }, + { + "codes": 532, + "names": "livecroot_mr_snk", + "units": "kgC m-2", + "descriptions": "Live coarse root maintenance respiration" + }, + { + "codes": 533, + "names": "leaf_gr_snk", + "units": "kgC m-2", + "descriptions": "Leaf growth respiration" + }, + { + "codes": 534, + "names": "froot_gr_snk", + "units": "kgC m-2", + "descriptions": "Fine root growth respiration" + }, + { + "codes": 535, + "names": "fruit_gr_snk", + "units": "kgC m-2", + "descriptions": "Fruit growth respiration" + }, + { + "codes": 536, + "names": "softstem_gr_snk", + "units": "kgC m-2", + "descriptions": "Softstem growth respiration" + }, + { + "codes": 537, + "names": "livestem_gr_snk", + "units": "kgC m-2", + "descriptions": "Live stem growth respiration" + }, + { + "codes": 538, + "names": "livecroot_gr_snk", + "units": "kgC m-2", + "descriptions": "Live coarse root growth respiration" + }, + { + "codes": 539, + "names": "deadstem_gr_snk", + "units": "kgC m-2", + "descriptions": "Dead stem growth respiration" + }, + { + "codes": 540, + "names": "deadcroot_gr_snk", + "units": "kgC m-2", + "descriptions": "Dead coarse root growth respiration" + }, + { + "codes": 541, + "names": "litr1_hr_snk", + "units": "kgC m-2", + "descriptions": "Labile litter microbial respiration" + }, + { + "codes": 542, + "names": "litr2_hr_snk", + "units": "kgC m-2", + "descriptions": "Cellulose litter microbial respiration" + }, + { + "codes": 543, + "names": "litr4_hr_snk", + "units": "kgC m-2", + "descriptions": "Lignin litter microbial respiration" + }, + { + "codes": 544, + "names": "soil1_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of labile SOM" + }, + { + "codes": 545, + "names": "soil2_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of fast SOM" + }, + { + "codes": 546, + "names": "soil3_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of slow SOM" + }, + { + "codes": 547, + "names": "soil4_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of stable SOM" + }, + { + "codes": 548, + "names": "FIREsnk_C", + "units": "kgC m-2", + "descriptions": "Fire C losses" + }, + { + "codes": 549, + "names": "SNSCsnk_C", + "units": "kgC m-2", + "descriptions": "Senescence C losses" + }, + { + "codes": 550, + "names": "PLTsrc_C", + "units": "kgC m-2", + "descriptions": "C content of planted plant material" + }, + { + "codes": 551, + "names": "THN_transportC", + "units": "kgC m-2", + "descriptions": "C content of thinned and transported plant material" + }, + { + "codes": 552, + "names": "HRV_transportC", + "units": "kgC m-2", + "descriptions": "C content of harvested and transported plant material" + }, + { + "codes": 553, + "names": "MOW_transportC", + "units": "kgC m-2", + "descriptions": "C content of mowed and transported plant material" + }, + { + "codes": 554, + "names": "GRZsnk_C", + "units": "kgC m-2", + "descriptions": "C content of grazed leaf" + }, + { + "codes": 555, + "names": "GRZsrc_C", + "units": "kgC m-2", + "descriptions": "Added C from fertilizer" + }, + { + "codes": 556, + "names": "FRZsrc_C", + "units": "kgC m-2", + "descriptions": "C content of fertilizer return to the litter pool" + }, + { + "codes": 557, + "names": "fruitC_HRV", + "units": "kgC m-2", + "descriptions": "C content of havested fruit in a year" + }, + { + "codes": 558, + "names": "vegC_HRV", + "units": "kgC m-2", + "descriptions": "C content of havested plant (leaf+stem+fruit) in a year" + }, + { + "codes": 559, + "names": "CbalanceERR", + "units": "kgC m-2", + "descriptions": "Carbon balance error" + }, + { + "codes": 560, + "names": "inC", + "units": "kgC m-2", + "descriptions": "Carbon input" + }, + { + "codes": 561, + "names": "outC", + "units": "kgC m-2", + "descriptions": "Carbon output" + }, + { + "codes": 562, + "names": "storeC", + "units": "kgC m-2", + "descriptions": "Carbon store" + }, + { + "codes": 563, + "names": "Cdeepleach_snk", + "units": "kgC m-2", + "descriptions": "SUM of C deep leaching" + }, + { + "codes": 564, + "names": "cwdc_above", + "units": "kgC m-2", + "descriptions": "Aboveground cwdc" + }, + { + "codes": 565, + "names": "litrc_above", + "units": "kgC m-2", + "descriptions": "Aboveground litrc" + }, + { + "codes": 566, + "names": "CNratioERR", + "units": "kgC m-2", + "descriptions": "CN ratio error" + }, + { + "codes": 567, + "names": "flowHSsnk_C", + "units": "kgC m-2", + "descriptions": "C loss due to flower heat stress" + }, + { + "codes": 600, + "names": "m_leafc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to labile C portion of litter" + }, + { + "codes": 601, + "names": "m_leafc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to unshielded cellulose portion of litter" + }, + { + "codes": 602, + "names": "m_leafc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to shielded cellulose portion of litter" + }, + { + "codes": 603, + "names": "m_leafc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to lignin portion of litter" + }, + { + "codes": 604, + "names": "m_frootc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to labile litter" + }, + { + "codes": 605, + "names": "m_frootc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 606, + "names": "m_frootc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 607, + "names": "m_frootc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to lignin portion of litter" + }, + { + "codes": 608, + "names": "m_fruitc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to labile litter" + }, + { + "codes": 609, + "names": "m_fruitc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to unshielded cellulose portion of litter" + }, + { + "codes": 610, + "names": "m_fruitc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to shielded cellulose portion of litter" + }, + { + "codes": 611, + "names": "m_fruitc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to lignin portion of litter" + }, + { + "codes": 612, + "names": "m_softstemc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to labile litter" + }, + { + "codes": 613, + "names": "m_softstemc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 614, + "names": "m_softstemc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 615, + "names": "m_softstemc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to lignin portion of litter" + }, + { + "codes": 616, + "names": "m_leafc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf storage pool to labile litter" + }, + { + "codes": 617, + "names": "m_frootc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root storage pool to labile litter" + }, + { + "codes": 618, + "names": "m_softstemc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem storage pool to labile litter" + }, + { + "codes": 619, + "names": "m_fruitc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit storage pool to labile litter" + }, + { + "codes": 620, + "names": "m_livestemc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live stem storage pool to labile litter" + }, + { + "codes": 621, + "names": "m_deadstemc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead stem storage pool to labile litter" + }, + { + "codes": 622, + "names": "m_livecrootc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live coarse root storage pool to labile litter" + }, + { + "codes": 623, + "names": "m_deadcrootc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead coarse root storage pool to labile litter" + }, + { + "codes": 624, + "names": "m_leafc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf transfer pool to labile litter" + }, + { + "codes": 625, + "names": "m_frootc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root transfer pool to labile litter" + }, + { + "codes": 626, + "names": "m_fruitc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit transfer pool to labile litter" + }, + { + "codes": 627, + "names": "m_softstemc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem transfer pool to labile litter" + }, + { + "codes": 628, + "names": "m_livestemc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live stem transfer pool to labile litter" + }, + { + "codes": 629, + "names": "m_deadstemc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead stem transfer pool to labile litter" + }, + { + "codes": 630, + "names": "m_livecrootc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live coarse root transfer pool to labile litter" + }, + { + "codes": 631, + "names": "m_deadcrootc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead coarse root transfer pool to labile litter" + }, + { + "codes": 632, + "names": "m_livestemc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Moartality C flux from live stem to coarse woody debris" + }, + { + "codes": 633, + "names": "m_deadstemc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead stem to coarse woody debris" + }, + { + "codes": 634, + "names": "m_livecrootc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live coarse root to coarse woody debris" + }, + { + "codes": 635, + "names": "m_deadcrootc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Moartality C flux from dead coarse root to coarse woody debris" + }, + { + "codes": 636, + "names": "m_gresp_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from growth respiration storage pool to labile litter" + }, + { + "codes": 637, + "names": "m_gresp_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from growth respiration transfer pool to labile litter" + }, + { + "codes": 638, + "names": "m_leafc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Leaf fire C flux" + }, + { + "codes": 639, + "names": "m_frootc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fine root fire C flux" + }, + { + "codes": 640, + "names": "m_fruitc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fruit fire C flux" + }, + { + "codes": 641, + "names": "m_softstemc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Softstem fire C flux" + }, + { + "codes": 642, + "names": "m_STDBc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Wilted plant biomass fire C flux" + }, + { + "codes": 643, + "names": "m_CTDBc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down plant biomass fire C flux" + }, + { + "codes": 644, + "names": "m_leafc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Leaf storage pool fire C flux" + }, + { + "codes": 645, + "names": "m_frootc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fine root storage pool fire C flux" + }, + { + "codes": 646, + "names": "m_fruitc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fruit storage pool fire C flux" + }, + { + "codes": 647, + "names": "m_softstemc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Softstem storage pool fire C flux" + }, + { + "codes": 648, + "names": "m_livestemc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live stem storage pool fire C flux" + }, + { + "codes": 649, + "names": "m_deadstemc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead stem storage pool fire C flux" + }, + { + "codes": 650, + "names": "m_livecrootc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root storage pool fire C flux" + }, + { + "codes": 651, + "names": "m_deadcrootc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead coarse root storage pool fire C flux" + }, + { + "codes": 652, + "names": "m_leafc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Leaf transfer pool fire C flux" + }, + { + "codes": 653, + "names": "m_frootc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fine root transfer pool fire C flux" + }, + { + "codes": 654, + "names": "m_fruitc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fruit transfer pool fire C flux" + }, + { + "codes": 655, + "names": "m_softstemc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Softstem transfer pool fire C flux" + }, + { + "codes": 656, + "names": "m_livestemc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live stem transfer pool fire C flux" + }, + { + "codes": 657, + "names": "m_deadstemc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead stem transfer pool fire C flux" + }, + { + "codes": 658, + "names": "m_livecrootc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root transfer pool fire C flux" + }, + { + "codes": 659, + "names": "m_deadcrootc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead coarse root transfer pool fire C flux" + }, + { + "codes": 660, + "names": "m_livestemc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live stem fire C flux" + }, + { + "codes": 661, + "names": "m_deadstemc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead stem fire C flux" + }, + { + "codes": 662, + "names": "m_livecrootc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root fire C flux" + }, + { + "codes": 663, + "names": "m_deadcrootc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead coarse root fire C flux" + }, + { + "codes": 664, + "names": "m_gresp_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration storage pool fire C flux" + }, + { + "codes": 665, + "names": "m_gresp_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration transfer pool fire C flux" + }, + { + "codes": 666, + "names": "m_litr1c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "labile litter fire C flux" + }, + { + "codes": 667, + "names": "m_litr2c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Unshielded cellulose portion of litter fire C flux" + }, + { + "codes": 668, + "names": "m_litr3c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Shielded cellulose portion of litter fire C flux" + }, + { + "codes": 669, + "names": "m_litr4c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Lignin portion of litter fire C flux" + }, + { + "codes": 670, + "names": "m_cwdc_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Coarse woody debris fire C flux" + }, + { + "codes": 671, + "names": "m_vegc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Total vegetation senescence C flux" + }, + { + "codes": 672, + "names": "m_leafc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Leaf senescence C flux" + }, + { + "codes": 673, + "names": "m_leafc_to_SNSCgenprog", + "units": "kgC m-2 day-1", + "descriptions": "Leaf gen. prog. scenescene C flux" + }, + { + "codes": 674, + "names": "m_frootc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fine root senescene C flux" + }, + { + "codes": 675, + "names": "m_fruitc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fruit senescence C flux" + }, + { + "codes": 676, + "names": "m_softstemc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Softstem senescence C flux" + }, + { + "codes": 677, + "names": "m_leafc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Leaf storage pool senescence C flux" + }, + { + "codes": 678, + "names": "m_frootc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fine root storage pool senescence C flux" + }, + { + "codes": 679, + "names": "m_leafc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Leaf transfer pool senescence C flux" + }, + { + "codes": 680, + "names": "m_frootc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fine root transfer pool senescence C flux" + }, + { + "codes": 681, + "names": "m_fruitc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fruit storage pool senescence C flux" + }, + { + "codes": 682, + "names": "m_fruitc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fruit transfer pool senescence C flux" + }, + { + "codes": 683, + "names": "m_softstemc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Softstem storage pool senescence C flux" + }, + { + "codes": 684, + "names": "m_softstemc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Softstem transfer pool senescence C flux" + }, + { + "codes": 685, + "names": "m_gresp_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration storage pool senescence C flux" + }, + { + "codes": 686, + "names": "m_gresp_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration transfer pool senescence C flux" + }, + { + "codes": 687, + "names": "HRV_leafc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested leaf storage pool senescence C flux" + }, + { + "codes": 688, + "names": "HRV_leafc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested leaf transfer pool senescence C flux" + }, + { + "codes": 689, + "names": "HRV_fruitc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fruit storage pool senescence C flux" + }, + { + "codes": 690, + "names": "HRV_fruitc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fruit transfer pool senescence C flux" + }, + { + "codes": 691, + "names": "HRV_frootc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fine root senescence C flux" + }, + { + "codes": 692, + "names": "HRV_softstemc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested softstem senscence C flux" + }, + { + "codes": 693, + "names": "HRV_frootc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fine root storage senescence C flux" + }, + { + "codes": 694, + "names": "HRV_frootc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fine root transfer senescence C flux" + }, + { + "codes": 695, + "names": "HRV_softstemc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested softstem storage senescence C flux" + }, + { + "codes": 696, + "names": "HRV_softstemc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested softstem transfer senescence C flux" + }, + { + "codes": 697, + "names": "HRV_gresp_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested growth respiration storage pool senescence C flux" + }, + { + "codes": 698, + "names": "HRV_gresp_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested growth respiration transfer pool senescence C flux" + }, + { + "codes": 699, + "names": "fruitc_to_flowHS", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit flowering heat stress" + }, + { + "codes": 700, + "names": "STDBc_leaf_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Leaf standing dead biomass C flux to litter" + }, + { + "codes": 701, + "names": "STDBc_froot_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Fine root standing dead biomass C flux to litter" + }, + { + "codes": 702, + "names": "STDBc_fruit_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Fruit standing dead biomass C flux to litter" + }, + { + "codes": 703, + "names": "STDBc_softstem_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Softstem standing dead biomass C flux to litter" + }, + { + "codes": 704, + "names": "STDBc_nsc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Standing dead biomass non-structured pool C flux to litter" + }, + { + "codes": 705, + "names": "STDBc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Standing dead biomass C flux to litter" + }, + { + "codes": 706, + "names": "CTDBc_leaf_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down leaf dead biomass C flux to litter" + }, + { + "codes": 707, + "names": "CTDBc_froot_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down fine root dead biomass C flux to litter" + }, + { + "codes": 708, + "names": "CTDBc_fruit_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down fruit dead biomass C flux to litter" + }, + { + "codes": 709, + "names": "CTDBc_softstem_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down softstem dead biomass C flux to litter" + }, + { + "codes": 710, + "names": "CTDBc_nsc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down dead biomass non-structured pool C flux to litter" + }, + { + "codes": 711, + "names": "CTDBc_cstem_to_cwd", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down coarse stem dead biomass C flux to coarse woody debris" + }, + { + "codes": 712, + "names": "CTDBc_croot_to_cwd", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down coarse root dead biomass C flux to coarse woody debris" + }, + { + "codes": 713, + "names": "CTDBc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down dead biomass C flux to litter" + }, + { + "codes": 714, + "names": "leafc_transfer_to_leafc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from leaf transfer pool to leaf" + }, + { + "codes": 715, + "names": "frootc_transfer_to_frootc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from fine root transfer pool to fine root" + }, + { + "codes": 716, + "names": "fruitc_transfer_to_fruitc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from fruit transfer pool to fruit" + }, + { + "codes": 717, + "names": "softstemc_transfer_to_softstemc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from softstem transfer pool to softstem" + }, + { + "codes": 718, + "names": "livestemc_transfer_to_livestemc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from live stem transfer pool to live stem" + }, + { + "codes": 719, + "names": "deadstemc_transfer_to_deadstemc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from dead stem transfer to dead stem" + }, + { + "codes": 720, + "names": "livecrootc_transfer_to_livecrootc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from live coarse root transfer pool to live coarse root" + }, + { + "codes": 721, + "names": "deadcrootc_transfer_to_deadcrootc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from dead coarse root transfer pool to dead coarse root" + }, + { + "codes": 722, + "names": "leafc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to labile litter" + }, + { + "codes": 723, + "names": "leafc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to unshielded cellulose portion of litter" + }, + { + "codes": 724, + "names": "leafc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to shielded cellulose portion of litter" + }, + { + "codes": 725, + "names": "leafc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to lignin portion of litter" + }, + { + "codes": 726, + "names": "frootc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to labile litter" + }, + { + "codes": 727, + "names": "frootc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 728, + "names": "frootc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 729, + "names": "frootc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to lignin portion of litter" + }, + { + "codes": 730, + "names": "fruitc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to labile litter" + }, + { + "codes": 731, + "names": "fruitc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to unshielded cellulose portion of litter" + }, + { + "codes": 732, + "names": "fruitc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to shielded cellulose portion of litter" + }, + { + "codes": 733, + "names": "fruitc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to lignin portion of litter" + }, + { + "codes": 734, + "names": "softstemc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to labile litter" + }, + { + "codes": 735, + "names": "softstemc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 736, + "names": "softstemc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 737, + "names": "softstemc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to lignin portion of litter" + }, + { + "codes": 738, + "names": "leaf_day_mr", + "units": "kgC m-2 day-1", + "descriptions": "Leaf daylight maintenance respiration" + }, + { + "codes": 739, + "names": "leaf_night_mr", + "units": "kgC m-2 day-1", + "descriptions": "Leaf night maintenance respiration" + }, + { + "codes": 740, + "names": "froot_mr", + "units": "kgC m-2 day-1", + "descriptions": "Fine root maintenance respiration" + }, + { + "codes": 741, + "names": "fruit_mr", + "units": "kgC m-2 day-1", + "descriptions": "Fruit maintenance repsiration" + }, + { + "codes": 742, + "names": "softstem_mr", + "units": "kgC m-2 day-1", + "descriptions": "Softstem maintenance respiration" + }, + { + "codes": 743, + "names": "livestem_mr", + "units": "kgC m-2 day-1", + "descriptions": "Live stem maintenance respiration" + }, + { + "codes": 744, + "names": "livecroot_mr", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root maintenance respiration" + }, + { + "codes": 745, + "names": "psnsun_to_cpool", + "units": "kgC m-2 day-1", + "descriptions": "C flux to temporary photosynthate C pool by sunlight" + }, + { + "codes": 746, + "names": "psnshade_to_cpool", + "units": "kgC m-2 day-1", + "descriptions": "C flux to temporary photosynthate C pool by sunshade" + }, + { + "codes": 747, + "names": "cwdc_to_litr2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose part of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 748, + "names": "cwdc_to_litr2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 749, + "names": "cwdc_to_litr2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 750, + "names": "cwdc_to_litr2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 751, + "names": "cwdc_to_litr2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 752, + "names": "cwdc_to_litr2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 753, + "names": "cwdc_to_litr2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 754, + "names": "cwdc_to_litr2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 755, + "names": "cwdc_to_litr2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 756, + "names": "cwdc_to_litr2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 757, + "names": "cwdc_to_litr3c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 758, + "names": "cwdc_to_litr3c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 759, + "names": "cwdc_to_litr3c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 760, + "names": "cwdc_to_litr3c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 761, + "names": "cwdc_to_litr3c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 762, + "names": "cwdc_to_litr3c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 763, + "names": "cwdc_to_litr3c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 764, + "names": "cwdc_to_litr3c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 765, + "names": "cwdc_to_litr3c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 766, + "names": "cwdc_to_litr3c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 767, + "names": "cwdc_to_litr4c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 768, + "names": "cwdc_to_litr4c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 769, + "names": "cwdc_to_litr4c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 770, + "names": "cwdc_to_litr4c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 771, + "names": "cwdc_to_litr4c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 772, + "names": "cwdc_to_litr4c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 773, + "names": "cwdc_to_litr4c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 774, + "names": "cwdc_to_litr4c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 775, + "names": "cwdc_to_litr4c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 776, + "names": "cwdc_to_litr4c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 777, + "names": "litr1_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 778, + "names": "litr1_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 779, + "names": "litr1_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 780, + "names": "litr1_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 781, + "names": "litr1_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 782, + "names": "litr1_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 783, + "names": "litr1_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 784, + "names": "litr1_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 785, + "names": "litr1_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 786, + "names": "litr1_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 787, + "names": "litr1c_to_soil1c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 788, + "names": "litr1c_to_soil1c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 789, + "names": "litr1c_to_soil1c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 790, + "names": "litr1c_to_soil1c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 791, + "names": "litr1c_to_soil1c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 792, + "names": "litr1c_to_soil1c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 793, + "names": "litr1c_to_soil1c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 794, + "names": "litr1c_to_soil1c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 795, + "names": "litr1c_to_soil1c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 796, + "names": "litr1c_to_soil1c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 797, + "names": "litr2_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose soil layer 1 (0-3 cm)" + }, + { + "codes": 798, + "names": "litr2_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 2 (3-10 cm)" + }, + { + "codes": 799, + "names": "litr2_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 3 (10-30 cm)" + }, + { + "codes": 800, + "names": "litr2_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 4 (30-60 cm)" + }, + { + "codes": 801, + "names": "litr2_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 5 (60-90 cm)" + }, + { + "codes": 802, + "names": "litr2_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 6 (90-120 cm)" + }, + { + "codes": 803, + "names": "litr2_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 7 (120-150 cm)" + }, + { + "codes": 804, + "names": "litr2_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 8 (150-200 cm)" + }, + { + "codes": 805, + "names": "litr2_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 9 (200-400 cm)" + }, + { + "codes": 806, + "names": "litr2_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 10 (400-1000 cm)" + }, + { + "codes": 807, + "names": "litr2c_to_soil2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 808, + "names": "litr2c_to_soil2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 809, + "names": "litr2c_to_soil2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 810, + "names": "litr2c_to_soil2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 811, + "names": "litr2c_to_soil2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 812, + "names": "litr2c_to_soil2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 813, + "names": "litr2c_to_soil2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 814, + "names": "litr2c_to_soil2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 815, + "names": "litr2c_to_soil2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 816, + "names": "litr2c_to_soil2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 817, + "names": "litr3c_to_litr2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 818, + "names": "litr3c_to_litr2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 819, + "names": "litr3c_to_litr2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 820, + "names": "litr3c_to_litr2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 821, + "names": "litr3c_to_litr2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 822, + "names": "litr3c_to_litr2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 823, + "names": "litr3c_to_litr2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 824, + "names": "litr3c_to_litr2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 825, + "names": "litr3c_to_litr2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 826, + "names": "litr3c_to_litr2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 827, + "names": "litr4_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 828, + "names": "litr4_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 828, + "names": "litr4_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 830, + "names": "litr4_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 831, + "names": "litr4_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 832, + "names": "litr4_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 833, + "names": "litr4_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 834, + "names": "litr4_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 835, + "names": "litr4_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 836, + "names": "litr4_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 837, + "names": "litr4c_to_soil3c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 838, + "names": "litr4c_to_soil3c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 839, + "names": "litr4c_to_soil3c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 840, + "names": "litr4c_to_soil3c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 841, + "names": "litr4c_to_soil3c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 842, + "names": "litr4c_to_soil3c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 843, + "names": "litr4c_to_soil3c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 844, + "names": "litr4c_to_soil3c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 845, + "names": "litr4c_to_soil3c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 846, + "names": "litr4c_to_soil3c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 847, + "names": "soil1_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 848, + "names": "soil1_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 849, + "names": "soil1_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 850, + "names": "soil1_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 851, + "names": "soil1_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 852, + "names": "soil1_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 853, + "names": "soil1_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 854, + "names": "soil1_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 855, + "names": "soil1_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 856, + "names": "soil1_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 857, + "names": "soil1c_to_soil2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 858, + "names": "soil1c_to_soil2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 859, + "names": "soil1c_to_soil2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 860, + "names": "soil1c_to_soil2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 861, + "names": "soil1c_to_soil2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 862, + "names": "soil1c_to_soil2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 863, + "names": "soil1c_to_soil2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 864, + "names": "soil1c_to_soil2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 865, + "names": "soil1c_to_soil2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 866, + "names": "soil1c_to_soil2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 867, + "names": "soil2_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 868, + "names": "soil2_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer (3-10 cm)" + }, + { + "codes": 869, + "names": "soil2_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 870, + "names": "soil2_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 871, + "names": "soil2_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 872, + "names": "soil2_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 873, + "names": "soil2_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 874, + "names": "soil2_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 875, + "names": "soil2_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 876, + "names": "soil2_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 1 (400-1000 cm)" + }, + { + "codes": 877, + "names": "soil2c_to_soil3c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 878, + "names": "soil2c_to_soil3c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 879, + "names": "soil2c_to_soil3c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 880, + "names": "soil2c_to_soil3c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 881, + "names": "soil2c_to_soil3c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 882, + "names": "soil2c_to_soil3c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 883, + "names": "soil2c_to_soil3c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 884, + "names": "soil2c_to_soil3c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 885, + "names": "soil2c_to_soil3c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 886, + "names": "soil2c_to_soil3c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 887, + "names": "soil3_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 888, + "names": "soil3_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer (3-10 cm)" + }, + { + "codes": 889, + "names": "soil3_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 890, + "names": "soil3_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 891, + "names": "soil3_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 892, + "names": "soil3_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 893, + "names": "soil3_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 894, + "names": "soil3_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 895, + "names": "soil3_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 896, + "names": "soil3_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 897, + "names": "soil3c_to_soil4c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 898, + "names": "soil3c_to_soil4c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 2 (3-10 cm)" + }, + { + "codes": 899, + "names": "soil3c_to_soil4c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 3 (10-30 cm)" + }, + { + "codes": 900, + "names": "soil3c_to_soil4c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 4 (30-60 cm)" + }, + { + "codes": 901, + "names": "soil3c_to_soil4c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 5 (60-90 cm)" + }, + { + "codes": 902, + "names": "soil3c_to_soil4c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 6 (90-120 cm)" + }, + { + "codes": 903, + "names": "soil3c_to_soil4c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 7 (120-150 cm)" + }, + { + "codes": 904, + "names": "soil3c_to_soil4c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 8 (150-200 cm)" + }, + { + "codes": 905, + "names": "soil3c_to_soil4c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 9 (200-400 cm)" + }, + { + "codes": 906, + "names": "soil3c_to_soil4c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 10 (400-1000 cm)" + }, + { + "codes": 907, + "names": "soil4_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 1 (0-3 cm)" + }, + { + "codes": 908, + "names": "soil4_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 2 (3-10 cm)" + }, + { + "codes": 909, + "names": "soil4_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 3 (10-30 cm)" + }, + { + "codes": 910, + "names": "soil4_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 4 (30-60 cm)" + }, + { + "codes": 911, + "names": "soil4_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 5 (60-90 cm)" + }, + { + "codes": 912, + "names": "soil4_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 6 (90-120 cm)" + }, + { + "codes": 913, + "names": "soil4_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 7 (120-150 cm)" + }, + { + "codes": 914, + "names": "soil4_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 8 (150-200 cm)" + }, + { + "codes": 915, + "names": "soil4_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 9 (200-400 cm)" + }, + { + "codes": 916, + "names": "soil4_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 917, + "names": "soil1_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 918, + "names": "soil1_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 919, + "names": "soil1_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 920, + "names": "soil1_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 921, + "names": "soil1_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 922, + "names": "soil1_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 923, + "names": "soil1_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 924, + "names": "soil1_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 925, + "names": "soil1_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 926, + "names": "soil1_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 927, + "names": "soil2_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 928, + "names": "soil2_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 929, + "names": "soil2_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 930, + "names": "soil2_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 931, + "names": "soil2_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 932, + "names": "soil2_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 933, + "names": "soil2_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 934, + "names": "soil2_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 935, + "names": "soil2_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 936, + "names": "soil2_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 937, + "names": "soil3_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 938, + "names": "soil3_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 939, + "names": "soil3_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 940, + "names": "soil3_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 941, + "names": "soil3_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 942, + "names": "soil3_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 943, + "names": "soil3_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 944, + "names": "soil3_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 945, + "names": "soil3_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 946, + "names": "soil3_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 947, + "names": "soil4_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 948, + "names": "soil4_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 949, + "names": "soil4_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 950, + "names": "soil4_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 951, + "names": "soil4_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 952, + "names": "soil4_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 953, + "names": "soil4_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 954, + "names": "soil4_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 955, + "names": "soil4_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 956, + "names": "soil4_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 957, + "names": "soil1_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 958, + "names": "soil1_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 959, + "names": "soil1_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 960, + "names": "soil1_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 961, + "names": "soil1_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 962, + "names": "soil1_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 963, + "names": "soil1_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 964, + "names": "soil1_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 965, + "names": "soil1_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 966, + "names": "soil1_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 967, + "names": "soil2_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 968, + "names": "soil2_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 969, + "names": "soil2_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 970, + "names": "soil2_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 971, + "names": "soil2_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 972, + "names": "soil2_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 973, + "names": "soil2_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 974, + "names": "soil2_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 975, + "names": "soil2_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 976, + "names": "soil2_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 977, + "names": "soil3_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 978, + "names": "soil3_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 979, + "names": "soil3_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 980, + "names": "soil3_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 981, + "names": "soil3_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 982, + "names": "soil3_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 983, + "names": "soil3_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 984, + "names": "soil3_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 985, + "names": "soil3_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 986, + "names": "soil3_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 987, + "names": "soil4_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 988, + "names": "soil4_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 989, + "names": "soil4_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 990, + "names": "soil4_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 991, + "names": "soil4_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 992, + "names": "soil4_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 993, + "names": "soil4_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 994, + "names": "soil4_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 995, + "names": "soil4_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 996, + "names": "soil4_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 997, + "names": "DOC_leached_RZ", + "units": "kgC m-2 day-1", + "descriptions": "Leached DOC from rootzone" + }, + { + "codes": 998, + "names": "cpool_to_leafc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to leaf" + }, + { + "codes": 999, + "names": "cpool_to_leafc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Dail allocation C flux from current GPP to leaf storage pool" + }, + { + "codes": 1000, + "names": "cpool_to_frootc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fine root" + }, + { + "codes": 1001, + "names": "cpool_to_frootc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fine root storage pool" + }, + { + "codes": 1002, + "names": "cpool_to_fruitc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fruit" + }, + { + "codes": 1003, + "names": "cpool_to_fruitc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fruit storage pool" + }, + { + "codes": 1004, + "names": "cpool_to_softstemc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to softstem" + }, + { + "codes": 1005, + "names": "cpool_to_softstemc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to softstem storage pool" + }, + { + "codes": 1006, + "names": "cpool_to_livestemc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live stem" + }, + { + "codes": 1007, + "names": "cpool_to_livestemc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily alloaction C flux from current GPP to live stem storage pool" + }, + { + "codes": 1008, + "names": "cpool_to_deadstemc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead stem" + }, + { + "codes": 1009, + "names": "cpool_to_deadstemc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead stem storage pool" + }, + { + "codes": 1010, + "names": "cpool_to_livecrootc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live coarse root" + }, + { + "codes": 1011, + "names": "cpool_to_livecrootc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live coarse root storage pool" + }, + { + "codes": 1012, + "names": "cpool_to_deadcrootc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead coarse root" + }, + { + "codes": 1013, + "names": "cpool_to_deadcrootc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead coarse root storage pool" + }, + { + "codes": 1014, + "names": "cpool_to_gresp_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to growth respiration storage pool" + }, + { + "codes": 1015, + "names": "cpool_leaf_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily leaf growth respiration flux" + }, + { + "codes": 1016, + "names": "cpool_leaf_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily leaf storage pool growth respiration flux" + }, + { + "codes": 1017, + "names": "transfer_leaf_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily leaf transfer pool respiration flux" + }, + { + "codes": 1018, + "names": "cpool_froot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fine root growth respiration flux" + }, + { + "codes": 1019, + "names": "cpool_froot_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fine root storage pool growth respiration flux" + }, + { + "codes": 1020, + "names": "transfer_froot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fine root transfer pool growth respiration flux" + }, + { + "codes": 1021, + "names": "cpool_fruit_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fruit growth respiration flux" + }, + { + "codes": 1022, + "names": "cpool_fruit_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fruit storage pool growth respiration flux" + }, + { + "codes": 1023, + "names": "transfer_fruit_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fruit transfer pool gowth respiration flux" + }, + { + "codes": 1024, + "names": "cpool_softstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily softstem growth respiration flux" + }, + { + "codes": 1025, + "names": "cpool_softstem_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily softstem storage pool growth respiration flux" + }, + { + "codes": 1026, + "names": "transfer_softstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily softstem transfer pool growth respiration flux" + }, + { + "codes": 1027, + "names": "cpool_livestem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live stem growth respiration flux" + }, + { + "codes": 1028, + "names": "cpool_livestem_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live stem storage pool growth respiration flux" + }, + { + "codes": 1029, + "names": "transfer_livestem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live stem transfer pool growth respiration flux" + }, + { + "codes": 1030, + "names": "cpool_deadstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead stem growth respiration flux" + }, + { + "codes": 1031, + "names": "cpool_deadstem_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead stem storage pool growth respiration flux" + }, + { + "codes": 1032, + "names": "transfer_deadstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead stem transfer pool growth respiration flux" + }, + { + "codes": 1033, + "names": "cpool_livecroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live coarse root growth respiration flux" + }, + { + "codes": 1034, + "names": "cpool_livecroot_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live coarse root storage pool growth respiration flux" + }, + { + "codes": 1035, + "names": "transfer_livecroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live coarse root transfer pool growth respiration flux" + }, + { + "codes": 1036, + "names": "cpool_deadcroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead coarse root growth respiration flux" + }, + { + "codes": 1037, + "names": "cpool_deadcroot_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead coarse root storage pool respiration flux" + }, + { + "codes": 1038, + "names": "transfer_deadcroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead coarse root transfer pool respiration flux" + }, + { + "codes": 1039, + "names": "leafc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf storage pool" + }, + { + "codes": 1040, + "names": "frootc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root storage pool" + }, + { + "codes": 1041, + "names": "fruitc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fruit storage pool" + }, + { + "codes": 1042, + "names": "softstemc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem storage pool" + }, + { + "codes": 1043, + "names": "livestemc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem storage pool" + }, + { + "codes": 1044, + "names": "livecrootc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root storage pool" + }, + { + "codes": 1045, + "names": "deadstemc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead stem storage pool" + }, + { + "codes": 1046, + "names": "deadcrootc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead coarse root storage pool" + }, + { + "codes": 1047, + "names": "leafc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf transfer pool" + }, + { + "codes": 1048, + "names": "frootc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root transfer pool" + }, + { + "codes": 1049, + "names": "fruitc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fruit transfer pool" + }, + { + "codes": 1050, + "names": "softstemc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem transfer pool" + }, + { + "codes": 1051, + "names": "livestemc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem transfer pool" + }, + { + "codes": 1052, + "names": "livecrootc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root transfer pool" + }, + { + "codes": 1053, + "names": "deadstemc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead stem transfer pool" + }, + { + "codes": 1054, + "names": "deadcrootc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead coarse root transfer pool" + }, + { + "codes": 1055, + "names": "leafc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf" + }, + { + "codes": 1056, + "names": "frootc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root" + }, + { + "codes": 1057, + "names": "fruitc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fruit" + }, + { + "codes": 1058, + "names": "softstemc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem" + }, + { + "codes": 1059, + "names": "livestemc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem" + }, + { + "codes": 1060, + "names": "livecrootc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root" + }, + { + "codes": 1061, + "names": "NSC_nw_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-structured non-woody carbohydrates" + }, + { + "codes": 1062, + "names": "actC_nw_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-woody portion ofactual C pool" + }, + { + "codes": 1063, + "names": "NSC_w_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-structured woody carbohydrates" + }, + { + "codes": 1064, + "names": "actC_w_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from woody portion ofactual C pool" + }, + { + "codes": 1065, + "names": "leafc_storage_to_leafc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of leaf storage to transfer pool" + }, + { + "codes": 1066, + "names": "frootc_storage_to_frootc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of fine root storage to transfer pool" + }, + { + "codes": 1067, + "names": "fruitc_storage_to_fruitc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of fruit storage to transfer pool" + }, + { + "codes": 1068, + "names": "softstemc_storage_to_softstemc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of softstem storage to transfer pool" + }, + { + "codes": 1069, + "names": "livestemc_storage_to_livestemc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live stem storage to transfer pool" + }, + { + "codes": 1070, + "names": "deadstemc_storage_to_deadstemc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of dead stem storage to transfer pool" + }, + { + "codes": 1071, + "names": "livecrootc_storage_to_livecrootc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live coarse root storage to transfer pool" + }, + { + "codes": 1072, + "names": "deadcrootc_storage_to_deadcrootc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of dead coarse root storage to transfer pool" + }, + { + "codes": 1073, + "names": "gresp_storage_to_gresp_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of growth respiration storage to transfer pool" + }, + { + "codes": 1074, + "names": "livestemc_to_deadstemc", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live stem to dead stem" + }, + { + "codes": 1075, + "names": "livecrootc_to_deadcrootc", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live coarse root to dead coarse root" + }, + { + "codes": 1076, + "names": "leafc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Leaf transfer pool C flux from planting" + }, + { + "codes": 1077, + "names": "frootc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Fine root transfer pool C flux from planting" + }, + { + "codes": 1078, + "names": "fruitc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Fruit transfer pool C flux from planting" + }, + { + "codes": 1079, + "names": "softstemc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Softstem transfer pool C flux from planting" + }, + { + "codes": 1080, + "names": "leafc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from leaf" + }, + { + "codes": 1081, + "names": "leafc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from leaf storage pool" + }, + { + "codes": 1082, + "names": "leafc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from leaf transfer pool" + }, + { + "codes": 1083, + "names": "fruitc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from fruit" + }, + { + "codes": 1084, + "names": "fruitc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from fruit storage pool" + }, + { + "codes": 1085, + "names": "fruitc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from fruit transfer pool" + }, + { + "codes": 1086, + "names": "livestemc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from live stem" + }, + { + "codes": 1087, + "names": "livestemc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from live stem storage pool" + }, + { + "codes": 1088, + "names": "livestemc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from live stem transfer pool" + }, + { + "codes": 1089, + "names": "deadstemc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from dead stem" + }, + { + "codes": 1090, + "names": "deadstemc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from dead stem storage pool" + }, + { + "codes": 1091, + "names": "deadstemc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from dead stem transfer pool" + }, + { + "codes": 1092, + "names": "gresp_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from growth respiration storage pool" + }, + { + "codes": 1093, + "names": "gresp_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from growth respiration transfer pool" + }, + { + "codes": 1094, + "names": "THN_to_CTDBc_leaf", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down leaf biomass" + }, + { + "codes": 1095, + "names": "THN_to_CTDBc_fruit", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down fruit biomass" + }, + { + "codes": 1096, + "names": "THN_to_CTDBc_nsc", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down plant biomass non-structured pool" + }, + { + "codes": 1097, + "names": "THN_to_CTDBc_cstem", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down coarse stem biomass" + }, + { + "codes": 1098, + "names": "STDBc_leaf_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from wilted leaf biomass" + }, + { + "codes": 1099, + "names": "STDBc_fruit_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from wilted fruit biomass" + }, + { + "codes": 1100, + "names": "STDBc_nsc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1101, + "names": "leafc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from leaf" + }, + { + "codes": 1102, + "names": "leafc_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from leaf storage pool" + }, + { + "codes": 1103, + "names": "leafc_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from leaf transfer pool" + }, + { + "codes": 1104, + "names": "fruitc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from fruit" + }, + { + "codes": 1105, + "names": "fruitc_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from fruit storage pool" + }, + { + "codes": 1106, + "names": "fruitc_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from fruit transfer pool" + }, + { + "codes": 1107, + "names": "softstemc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from softstem" + }, + { + "codes": 1108, + "names": "softstemc_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from softstem storage pool" + }, + { + "codes": 1109, + "names": "softstemc_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from softstem transfer pool" + }, + { + "codes": 1110, + "names": "gresp_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from growth respiration storage pool" + }, + { + "codes": 1111, + "names": "gresp_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from growth respiration transfer pool" + }, + { + "codes": 1112, + "names": "MOW_to_CTDBc_leaf", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down leaf biomass" + }, + { + "codes": 1113, + "names": "MOW_to_CTDBc_fruit", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down fruit biomass" + }, + { + "codes": 1114, + "names": "MOW_to_CTDBc_softstem", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down softstem biomass" + }, + { + "codes": 1115, + "names": "MOW_to_CTDBc_nsc", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down biomass non-structured pool" + }, + { + "codes": 1116, + "names": "STDBc_leaf_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted leaf biomass" + }, + { + "codes": 1117, + "names": "STDBc_fruit_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted fruit biomass" + }, + { + "codes": 1118, + "names": "STDBc_softstem_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted softstem biomass" + }, + { + "codes": 1119, + "names": "STDBc_nsc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1120, + "names": "leafc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from leaf" + }, + { + "codes": 1121, + "names": "leafc_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from leaf storage pool" + }, + { + "codes": 1122, + "names": "leafc_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from leaf transfer pool" + }, + { + "codes": 1123, + "names": "fruitc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from fruit" + }, + { + "codes": 1124, + "names": "fruitc_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from fruit storage pool" + }, + { + "codes": 1125, + "names": "fruitc_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from fruit transfer pool" + }, + { + "codes": 1126, + "names": "softstemc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from softstem" + }, + { + "codes": 1127, + "names": "softstemc_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from softstem storage pool" + }, + { + "codes": 1128, + "names": "softstemc_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from softstem transfer pool" + }, + { + "codes": 1129, + "names": "gresp_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from growth respiration storage pool" + }, + { + "codes": 1130, + "names": "gresp_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from growth respiration transfer pool" + }, + { + "codes": 1131, + "names": "HRV_to_CTDBc_leaf", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down leaf biomass" + }, + { + "codes": 1132, + "names": "HRV_to_CTDBc_fruit", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down fruit biomass" + }, + { + "codes": 1133, + "names": "HRV_to_CTDBc_softstem", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down softstem biomass" + }, + { + "codes": 1134, + "names": "HRV_to_CTDBc_nsc", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down biomass non-structured pool" + }, + { + "codes": 1135, + "names": "STDBc_leaf_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted leaf biomass" + }, + { + "codes": 1136, + "names": "STDBc_fruit_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted fruit biomass" + }, + { + "codes": 1137, + "names": "STDBc_softstem_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted softstem biomass" + }, + { + "codes": 1138, + "names": "STDBc_nsc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1139, + "names": "leafc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from leaf" + }, + { + "codes": 1140, + "names": "leafc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from leaf storage pool" + }, + { + "codes": 1141, + "names": "leafc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from leaf transfer pool" + }, + { + "codes": 1142, + "names": "frootc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fine root" + }, + { + "codes": 1143, + "names": "frootc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fine root storage pool" + }, + { + "codes": 1144, + "names": "frootc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fine root transfer pool" + }, + { + "codes": 1145, + "names": "fruitc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fruit" + }, + { + "codes": 1146, + "names": "fruitc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fruit storage pool" + }, + { + "codes": 1147, + "names": "fruitc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fruit transfer pool" + }, + { + "codes": 1148, + "names": "softstemc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from softstem" + }, + { + "codes": 1149, + "names": "softstemc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from softstem storage pool" + }, + { + "codes": 1150, + "names": "softstemc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from softstem transfer pool" + }, + { + "codes": 1151, + "names": "gresp_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from growth respiration storage pool" + }, + { + "codes": 1152, + "names": "gresp_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from growth respiration transfer pool" + }, + { + "codes": 1153, + "names": "STDBc_leaf_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted leaf biomass" + }, + { + "codes": 1154, + "names": "STDBc_froot_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted fine root biomass" + }, + { + "codes": 1155, + "names": "STDBc_fruit_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted fruit biomass" + }, + { + "codes": 1156, + "names": "STDBc_softstem_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted softstem biomass" + }, + { + "codes": 1157, + "names": "STDBc_nsc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1158, + "names": "CTDBc_leaf_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from cut-down leaf biomass" + }, + { + "codes": 1159, + "names": "CTDBc_fruit_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from cut-down fruit biomass" + }, + { + "codes": 1160, + "names": "CTDBc_softstem_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from cut-down softstem biomass" + }, + { + "codes": 1161, + "names": "leafc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from leaf" + }, + { + "codes": 1162, + "names": "leafc_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazig C flux from leaf storage pool" + }, + { + "codes": 1163, + "names": "leafc_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux fromleaf transfer pool" + }, + { + "codes": 1164, + "names": "fruitc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from fruit" + }, + { + "codes": 1165, + "names": "fruitc_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from fruit storage pool" + }, + { + "codes": 1166, + "names": "fruitc_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from fruit transfer pool" + }, + { + "codes": 1167, + "names": "softstemc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from softstem" + }, + { + "codes": 1168, + "names": "softstemc_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from softstem storage pool" + }, + { + "codes": 1169, + "names": "softstemc_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from softstem transfer pool" + }, + { + "codes": 1170, + "names": "gresp_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from growth respiration storage pool" + }, + { + "codes": 1171, + "names": "gresp_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from growth respiration transfer pool" + }, + { + "codes": 1172, + "names": "STDBc_leaf_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from wilted leaf biomass" + }, + { + "codes": 1173, + "names": "STDBc_fruit_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from wilted fruit biomass" + }, + { + "codes": 1174, + "names": "STDBc_softstem_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing flux from wilted softstem biomass" + }, + { + "codes": 1175, + "names": "STDBc_nsc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1176, + "names": "GRZ_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to labile litter" + }, + { + "codes": 1177, + "names": "GRZ_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to unshielded cellulose portion of litter" + }, + { + "codes": 1178, + "names": "GRZ_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to shielded cellulose portion of litter" + }, + { + "codes": 1179, + "names": "GRZ_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to lignin portion of litter" + }, + { + "codes": 1180, + "names": "FRZ_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to labile litter" + }, + { + "codes": 1181, + "names": "FRZ_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to unshielded cellulose portion of litter" + }, + { + "codes": 1182, + "names": "FRZ_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to shielded cellulose portion of litter" + }, + { + "codes": 1183, + "names": "FRZ_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to lignin portion of litter" + }, + { + "codes": 1184, + "names": "CH4_flux_soil", + "units": "kgC m-2 day-1", + "descriptions": "Estimated CH4 flux from soil" + }, + { + "codes": 1185, + "names": "CH4_flux_MANURE", + "units": "kgC m-2 day-1", + "descriptions": "Estimated CH4 flux from manure" + }, + { + "codes": 1186, + "names": "CH4_flux_ANIMAL", + "units": "kgC m-2 day-1", + "descriptions": "Estimated CH4 flux from animals" + }, + { + "codes": 1300, + "names": "leafn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of leaf pool" + }, + { + "codes": 1301, + "names": "leafn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of leaf storage pool" + }, + { + "codes": 1302, + "names": "leafn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of leaf transfer pool" + }, + { + "codes": 1303, + "names": "frootn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of fine root pool" + }, + { + "codes": 1304, + "names": "frootn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fine root storage pool" + }, + { + "codes": 1305, + "names": "frootn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fine root storage pool" + }, + { + "codes": 1306, + "names": "fruitn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of fruit pool" + }, + { + "codes": 1307, + "names": "fruitn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fruit storage pool" + }, + { + "codes": 1308, + "names": "fruitn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fruit transfer pool" + }, + { + "codes": 1309, + "names": "softstemn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of softstem pool" + }, + { + "codes": 1310, + "names": "softstemn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of softstem storage pool" + }, + { + "codes": 1311, + "names": "softstemn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of softstem transfer pool" + }, + { + "codes": 1312, + "names": "livestemn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of live stem pool" + }, + { + "codes": 1313, + "names": "livestemn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live stem storage pool" + }, + { + "codes": 1314, + "names": "livestemn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live stem transfer pool" + }, + { + "codes": 1315, + "names": "deadstemn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of dead stem pool" + }, + { + "codes": 1316, + "names": "deadstemn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead stem storage pool" + }, + { + "codes": 1317, + "names": "deadstemn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead stem transfer pool" + }, + { + "codes": 1318, + "names": "livecrootn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of live coarse root pool" + }, + { + "codes": 1319, + "names": "livecrootn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live coarse root storage pool" + }, + { + "codes": 1320, + "names": "livecrootn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live coarse root transfer pool" + }, + { + "codes": 1321, + "names": "deadcrootn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of dead coarse root pool" + }, + { + "codes": 1322, + "names": "deadcrootn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead coarse root storage pool" + }, + { + "codes": 1323, + "names": "deadcrootn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead coarse root transfer pool" + }, + { + "codes": 1324, + "names": "npool", + "units": "kgN m-2", + "descriptions": "Temporary plant N pool" + }, + { + "codes": 1325, + "names": "cwdn[0]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 1 (0-3 cm)" + }, + { + "codes": 1326, + "names": "cwdn[1]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 2 (3-10 cm)" + }, + { + "codes": 1327, + "names": "cwdn[2]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 3 (10-30 cm)" + }, + { + "codes": 1328, + "names": "cwdn[3]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 4 (30-60 cm)" + }, + { + "codes": 1329, + "names": "cwdn[4]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 5 (60-90 cm)" + }, + { + "codes": 1330, + "names": "cwdn[5]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 6 (90-120 cm)" + }, + { + "codes": 1331, + "names": "cwdn[6]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 7 (120-150 cm)" + }, + { + "codes": 1332, + "names": "cwdn[7]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 8 (150-200 cm)" + }, + { + "codes": 1333, + "names": "cwdn[8]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 9 (200-400 cm)" + }, + { + "codes": 1334, + "names": "cwdn[9]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1335, + "names": "litr1n[0]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1336, + "names": "litr1n[1]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1337, + "names": "litr1n[2]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1338, + "names": "litr1n[3]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1339, + "names": "litr1n[4]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1340, + "names": "litr1n[5]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1341, + "names": "litr1n[6]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1342, + "names": "litr1n[7]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1343, + "names": "litr1n[8]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1344, + "names": "litr1n[9]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1345, + "names": "litr2n[0]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1346, + "names": "litr2n[1]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1347, + "names": "litr2n[2]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1348, + "names": "litr2n[3]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1349, + "names": "litr2n[4]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1350, + "names": "litr2n[5]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1351, + "names": "litr2n[6]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1352, + "names": "litr2n[7]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1353, + "names": "litr2n[8]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1354, + "names": "litr2n[9]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1355, + "names": "litr3n[0]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1356, + "names": "litr3n[1]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1357, + "names": "litr3n[2]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1358, + "names": "litr3n[3]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1359, + "names": "litr3n[4]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1360, + "names": "litr3n[5]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1361, + "names": "litr3n[6]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1362, + "names": "litr3n[7]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1363, + "names": "litr3n[8]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1364, + "names": "litr3n[9]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1365, + "names": "litr4n[0]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1366, + "names": "litr4n[1]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1367, + "names": "litr4n[2]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1368, + "names": "litr4n[3]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1369, + "names": "litr4n[4]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1370, + "names": "litr4n[5]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1371, + "names": "litr4n[6]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1372, + "names": "litr4n[7]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1373, + "names": "litr4n[8]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1374, + "names": "litr4n[9]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1375, + "names": "litrN[0]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1376, + "names": "litrN[1]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1377, + "names": "litrN[2]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1378, + "names": "litrN[3]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1379, + "names": "litrN[4]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1380, + "names": "litrN[5]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1381, + "names": "litrN[6]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1382, + "names": "litrN[7]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1383, + "names": "litrN[8]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1384, + "names": "litrN[9]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1385, + "names": "litr1n_total", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter" + }, + { + "codes": 1386, + "names": "litr2n_total", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter" + }, + { + "codes": 1387, + "names": "litr3n_total", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter" + }, + { + "codes": 1388, + "names": "litr4n_total", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter" + }, + { + "codes": 1389, + "names": "cwdn_total", + "units": "kgN m-2", + "descriptions": "Total nitrogen content of coarse woody debris" + }, + { + "codes": 1390, + "names": "STDBn_leaf", + "units": "kgN m-2", + "descriptions": "N content of wilted leaf biomass" + }, + { + "codes": 1391, + "names": "STDBn_froot", + "units": "kgN m-2", + "descriptions": "N content of wilted fine root biomass" + }, + { + "codes": 1392, + "names": "STDBn_fruit", + "units": "kgN m-2", + "descriptions": "N content of wilted fruit biomass" + }, + { + "codes": 1393, + "names": "STDBn_softstem", + "units": "kgN m-2", + "descriptions": "N content of wilted softstem biomass" + }, + { + "codes": 1394, + "names": "STDBn_nsc", + "units": "kgN m-2", + "descriptions": "N content of wilted non-structured biomass" + }, + { + "codes": 1395, + "names": "STDBn_above", + "units": "kgN m-2", + "descriptions": "N content of wilted aboveground plant biomass" + }, + { + "codes": 1396, + "names": "STDBn_below", + "units": "kgN m-2", + "descriptions": "N content of wilted belowground plant biomass" + }, + { + "codes": 1397, + "names": "CTDBn_leaf", + "units": "kgN m-2", + "descriptions": "N content of cut-down leaf biomass" + }, + { + "codes": 1398, + "names": "CTDBn_froot", + "units": "kgN m-2", + "descriptions": "N content of cut-down fineroot biomass" + }, + { + "codes": 1399, + "names": "CTDBn_fruit", + "units": "kgN m-2", + "descriptions": "N content of cut-down fruit biomass" + }, + { + "codes": 1400, + "names": "CTDBn_softstem", + "units": "kgN m-2", + "descriptions": "N content of cut-down softstem biomass" + }, + { + "codes": 1401, + "names": "CTDBn_nsc", + "units": "kgN m-2", + "descriptions": "N content of cut-down non-structured biomass" + }, + { + "codes": 1402, + "names": "CTDBn_cstem", + "units": "kgN m-2", + "descriptions": "N content of cut-down coarse stem biomass" + }, + { + "codes": 1403, + "names": "CTDBn_croot", + "units": "kgN m-2", + "descriptions": "N content of cut-down coarse root biomass" + }, + { + "codes": 1404, + "names": "CTDBn_above", + "units": "kgN m-2", + "descriptions": "N content of cut-down aboveground plant biomass" + }, + { + "codes": 1405, + "names": "CTDBn_below", + "units": "kgN m-2", + "descriptions": "N content of cut-down belowground plant biomass" + }, + { + "codes": 1406, + "names": "soil1n[0]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 1407, + "names": "soil1n[1]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 1408, + "names": "soil1n[2]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 1409, + "names": "soil1n[3]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 1410, + "names": "soil1n[4]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 1411, + "names": "soil1n[5]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 1412, + "names": "soil1n[6]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 1413, + "names": "soil1n[7]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 1414, + "names": "soil1n[8]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 1415, + "names": "soil1n[9]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 1416, + "names": "soil2n[0]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 1417, + "names": "soil2n[1]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 1418, + "names": "soil2n[2]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 1419, + "names": "soil2n[3]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 1420, + "names": "soil2n[4]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 1421, + "names": "soil2n[5]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 1422, + "names": "soil2n[6]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 1423, + "names": "soil2n[7]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 1424, + "names": "soil2n[8]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 1425, + "names": "soil2n[9]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 1426, + "names": "soil3n[0]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 1427, + "names": "soil3n[1]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 1428, + "names": "soil3n[2]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 1429, + "names": "soil3n[3]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 1430, + "names": "soil3n[4]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 1431, + "names": "soil3n[5]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 1432, + "names": "soil3n[6]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 1433, + "names": "soil3n[7]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 1434, + "names": "soil3n[8]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 1435, + "names": "soil3n[9]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 1436, + "names": "soil4n[0]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 1437, + "names": "soil4n[1]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 1438, + "names": "soil4n[2]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 1439, + "names": "soil4n[3]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 1440, + "names": "soil4n[4]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 1441, + "names": "soil4n[5]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 1442, + "names": "soil4n[6]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 1443, + "names": "soil4n[7]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 1444, + "names": "soil4n[8]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 1445, + "names": "soil4n[9]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 1446, + "names": "soilN[0]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1447, + "names": "soilN[1]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1448, + "names": "soilN[2]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1449, + "names": "soilN[3]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1450, + "names": "soilN[4]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1451, + "names": "soilN[5]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1452, + "names": "soilN[6]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1453, + "names": "soilN[7]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1454, + "names": "soilN[8]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1455, + "names": "soilN[9]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1456, + "names": "soil1_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 1457, + "names": "soil1_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 1458, + "names": "soil1_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 1459, + "names": "soil1_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 1460, + "names": "soil1_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 1461, + "names": "soil1_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 1462, + "names": "soil1_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 1463, + "names": "soil1_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 1464, + "names": "soil1_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 1465, + "names": "soil1_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 1466, + "names": "soil2_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 1467, + "names": "soil2_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 1468, + "names": "soil2_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 1469, + "names": "soil2_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 1470, + "names": "soil2_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 1471, + "names": "soil2_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 1472, + "names": "soil2_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 1473, + "names": "soil2_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 1474, + "names": "soil2_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 1475, + "names": "soil2_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 1476, + "names": "soil3_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 1477, + "names": "soil3_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 1478, + "names": "soil3_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 1479, + "names": "soil3_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 1480, + "names": "soil3_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 1481, + "names": "soil3_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 1482, + "names": "soil3_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 1483, + "names": "soil3_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 1484, + "names": "soil3_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 1485, + "names": "soil3_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 1486, + "names": "soil4_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 1487, + "names": "soil4_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 1488, + "names": "soil4_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 1489, + "names": "soil4_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 1490, + "names": "soil4_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 1491, + "names": "soil4_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 1492, + "names": "soil4_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 1493, + "names": "soil4_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 1494, + "names": "soil4_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 1495, + "names": "soil4_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 1496, + "names": "soil_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1497, + "names": "soil_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1498, + "names": "soil_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1499, + "names": "soil_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1500, + "names": "soil_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1501, + "names": "soil_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1502, + "names": "soil_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1503, + "names": "soil_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1504, + "names": "soil_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1505, + "names": "soil_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1506, + "names": "soil1n_total", + "units": "kgN m-2", + "descriptions": "Labile SOM nitrogen pool" + }, + { + "codes": 1507, + "names": "soil2n_total", + "units": "kgN m-2", + "descriptions": "Fast decomposing SOM nitrogen pool (fast)" + }, + { + "codes": 1508, + "names": "soil3n_total", + "units": "kgN m-2", + "descriptions": "Slow decomposing SOM nitrogen pool" + }, + { + "codes": 1509, + "names": "soil4n_total", + "units": "kgN m-2", + "descriptions": "Stable SOM nitrogen pool" + }, + { + "codes": 1510, + "names": "retransn", + "units": "kgN m-2", + "descriptions": "Plant pool of retranslocated N" + }, + { + "codes": 1511, + "names": "sminNH4[0]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1512, + "names": "sminNH4[1]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1513, + "names": "sminNH4[2]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1514, + "names": "sminNH4[3]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1515, + "names": "sminNH4[4]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1516, + "names": "sminNH4[5]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1517, + "names": "sminNH4[6]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1518, + "names": "sminNH4[7]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1519, + "names": "sminNH4[8]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1520, + "names": "sminNH4[9]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1521, + "names": "sminNO3[0]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1522, + "names": "sminNO3[1]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1523, + "names": "sminNO3[2]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1524, + "names": "sminNO3[3]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1525, + "names": "sminNO3[4]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1526, + "names": "sminNO3[5]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1527, + "names": "sminNO3[6]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1528, + "names": "sminNO3[7]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1529, + "names": "sminNO3[8]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1530, + "names": "sminNO3[9]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1531, + "names": "sminNH4_total", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil" + }, + { + "codes": 1532, + "names": "sminNO3_total", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil" + }, + { + "codes": 1533, + "names": "Nfix_src", + "units": "kgN m-2", + "descriptions": "SUM of biological N fixation" + }, + { + "codes": 1534, + "names": "Ndep_src", + "units": "kgN m-2", + "descriptions": "SUM of N deposition inputs" + }, + { + "codes": 1535, + "names": "Ndeepleach_snk", + "units": "kgN m-2", + "descriptions": "SUM of N deep leaching" + }, + { + "codes": 1536, + "names": "Nvol_snk", + "units": "kgN m-2", + "descriptions": "SUM of N lost to volatilization" + }, + { + "codes": 1537, + "names": "FIREsnk_N", + "units": "kgN m-2", + "descriptions": "SUM of N lost to fire" + }, + { + "codes": 1538, + "names": "Nprec_snk", + "units": "kgN m-2", + "descriptions": "SUM of N lost to precision control" + }, + { + "codes": 1539, + "names": "SNSCsnk_N", + "units": "kgN m-2", + "descriptions": "SUM of senescence N losses" + }, + { + "codes": 1540, + "names": "FRZsrc_N", + "units": "kgN m-2", + "descriptions": "SUM of N fertilization inputs" + }, + { + "codes": 1541, + "names": "PLTsrc_N", + "units": "kgN m-2", + "descriptions": "SUM of planted leaf N" + }, + { + "codes": 1542, + "names": "THN_transportN", + "units": "kgN m-2", + "descriptions": "SUM N content of thinned and transported plant material" + }, + { + "codes": 1543, + "names": "HRV_transportN", + "units": "kgN m-2", + "descriptions": "SUM of N content of harvested and transported plant material" + }, + { + "codes": 1544, + "names": "MOW_transportN", + "units": "kgN m-2", + "descriptions": "SUM of N content of mowed and transported plant material" + }, + { + "codes": 1545, + "names": "GRZsnk_N", + "units": "kgN m-2", + "descriptions": "SUM of grazed leaf N content" + }, + { + "codes": 1546, + "names": "GRZsrc_N", + "units": "kgN m-2", + "descriptions": "SUM of leaf N from grazing" + }, + { + "codes": 1548, + "names": "SPINUPsrc", + "units": "kgN m-2", + "descriptions": "SUM of leaf N from spinup" + }, + { + "codes": 1550, + "names": "NbalanceERR", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen balance error" + }, + { + "codes": 1551, + "names": "inN", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen input" + }, + { + "codes": 1552, + "names": "outN", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen output" + }, + { + "codes": 1553, + "names": "storeN", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen store" + }, + { + "codes": 1700, + "names": "m_leafn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to labile N portion of litter" + }, + { + "codes": 1701, + "names": "m_leafn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to unshielded cellulose N portion of litter" + }, + { + "codes": 1702, + "names": "m_leafn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to shielded cellulose N portion of litter" + }, + { + "codes": 1703, + "names": "m_leafn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to lignin N portion of litter" + }, + { + "codes": 1704, + "names": "m_frootn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to labile N portion of litter" + }, + { + "codes": 1705, + "names": "m_frootn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to unshielded cellulose N portion of litter" + }, + { + "codes": 1706, + "names": "m_frootn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to shielded cellulose portion N of litter" + }, + { + "codes": 1707, + "names": "m_frootn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to lignin N portion of litter" + }, + { + "codes": 1708, + "names": "m_fruitn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to labile N portion of litter" + }, + { + "codes": 1709, + "names": "m_fruitn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to unshielded cellulose N portion of litter" + }, + { + "codes": 1710, + "names": "m_fruitn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to shielded cellulose N portion of litter" + }, + { + "codes": 1711, + "names": "m_fruitn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to lignin N portion of litter" + }, + { + "codes": 1712, + "names": "m_softstemn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to labile N portion of litter" + }, + { + "codes": 1713, + "names": "m_softstemn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to unshielded cellulose N portion of litter" + }, + { + "codes": 1714, + "names": "m_softstemn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to shielded cellulose N portion of litter" + }, + { + "codes": 1715, + "names": "m_softstemn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to lignin N portion of litter" + }, + { + "codes": 1716, + "names": "m_leafn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf storage pool to labile N portion of litter" + }, + { + "codes": 1717, + "names": "m_frootn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root storage pool to labile N portion of litter" + }, + { + "codes": 1718, + "names": "m_fruitn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit storage pool to labile N portion of litter" + }, + { + "codes": 1719, + "names": "m_fruitn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit transfer pool to labile N portion of litter" + }, + { + "codes": 1720, + "names": "m_softstemn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem storage pool to labile N portion of litter" + }, + { + "codes": 1721, + "names": "m_softstemn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem transfer pool to labile N portion of litter" + }, + { + "codes": 1722, + "names": "m_livestemn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem storage pool to labile N portion of litter" + }, + { + "codes": 1723, + "names": "m_deadstemn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead stem storage pool to labile N portion of litter" + }, + { + "codes": 1724, + "names": "m_livecrootn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root storage pool to labile N portion of litter" + }, + { + "codes": 1725, + "names": "m_deadcrootn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead coarse root storage pool to labile N portion of litter" + }, + { + "codes": 1726, + "names": "m_leafn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf transfer pool to labile N portion of litter" + }, + { + "codes": 1727, + "names": "m_frootn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root transfer pool to labile N portion of litter" + }, + { + "codes": 1728, + "names": "m_livestemn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem transfer pool to labile N portion of litter" + }, + { + "codes": 1729, + "names": "m_deadstemn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead stem transfer pool to labile N portion of litter" + }, + { + "codes": 1730, + "names": "m_livecrootn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root transfer pool to labile N portion of litter" + }, + { + "codes": 1731, + "names": "m_deadcrootn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead coarse root transfer pool to labile N portion of litter" + }, + { + "codes": 1732, + "names": "m_livestemn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem to labile N portion of litter" + }, + { + "codes": 1733, + "names": "m_livestemn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem to coarse woody debris" + }, + { + "codes": 1734, + "names": "m_deadstemn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead stem to coarse woody debris" + }, + { + "codes": 1735, + "names": "m_livecrootn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root ro labile N portion of litter" + }, + { + "codes": 1736, + "names": "m_livecrootn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root to coarse woody debris" + }, + { + "codes": 1737, + "names": "m_deadcrootn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead coarse root to coarse woody debris" + }, + { + "codes": 1738, + "names": "m_retransn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from retranslocated N to labile N portion of litter" + }, + { + "codes": 1739, + "names": "m_vegn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Total vegetation senescence N flux" + }, + { + "codes": 1740, + "names": "m_leafn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Leaf senescence N flux" + }, + { + "codes": 1741, + "names": "m_leafn_to_SNSCgenprog", + "units": "kgN m-2 day-1", + "descriptions": "Leaf gen. prog. scenescene N flux" + }, + { + "codes": 1742, + "names": "m_frootn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fine root senescene N flux" + }, + { + "codes": 1743, + "names": "m_leafn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Leaf storage pool senescence N flux" + }, + { + "codes": 1744, + "names": "m_frootn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fine root storage pool senescence N flux" + }, + { + "codes": 1745, + "names": "m_leafn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Leaf transfer pool senescence N flux" + }, + { + "codes": 1746, + "names": "m_frootn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fine root transfer pool senescence N flux" + }, + { + "codes": 1747, + "names": "m_fruitn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fruit senescence N flux" + }, + { + "codes": 1748, + "names": "m_fruitn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fruit storage pool senescence N flux" + }, + { + "codes": 1749, + "names": "m_fruitn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fruit transfer pool senescence N flux" + }, + { + "codes": 1750, + "names": "m_softstemn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Softstem senescence N flux" + }, + { + "codes": 1751, + "names": "m_softstemn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Softstem storage pool senescence N flux" + }, + { + "codes": 1752, + "names": "m_softstemn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Softstem transfer pool senescence N flux" + }, + { + "codes": 1753, + "names": "m_retransn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Retranslocated N senescene N flux" + }, + { + "codes": 1754, + "names": "HRV_leafn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested leaf storage pool senescence N flux" + }, + { + "codes": 1755, + "names": "HRV_leafn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested leaf transfer pool senescence N flux" + }, + { + "codes": 1756, + "names": "HRV_fruitn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fruit storage pool senescence N flux" + }, + { + "codes": 1757, + "names": "HRV_fruitn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fruit transfer pool senescence N flux" + }, + { + "codes": 1758, + "names": "HRV_frootn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fine root senescence N flux" + }, + { + "codes": 1759, + "names": "HRV_softstemn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested softstem senscence N flux" + }, + { + "codes": 1760, + "names": "HRV_frootn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fine root storage senescence N flux" + }, + { + "codes": 1761, + "names": "HRV_frootn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fine root transfer senescence N flux" + }, + { + "codes": 1762, + "names": "HRV_softstemn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested softstem storage senescence N flux" + }, + { + "codes": 1763, + "names": "HRV_softstemn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested softstem transfer senescence N flux" + }, + { + "codes": 1764, + "names": "HRV_retransn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested retranslocated N senescence N flux" + }, + { + "codes": 1765, + "names": "fruitn_to_flowHS", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit flowering heat stress" + }, + { + "codes": 1766, + "names": "STDBn_leaf_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Leaf standing dead biomass N flux to litter" + }, + { + "codes": 1767, + "names": "STDBn_froot_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Fine root standing dead biomass N flux to litter" + }, + { + "codes": 1768, + "names": "STDBn_fruit_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Fruit standing dead biomass N flux to litter" + }, + { + "codes": 1769, + "names": "STDBn_softstem_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Softstem standing dead biomass N flux to litter" + }, + { + "codes": 1770, + "names": "STDBn_nsc_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Standing dead biomass non-structured pool N flux to litter" + }, + { + "codes": 1771, + "names": "STDBn_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Standing dead biomass N flux to litter" + }, + { + "codes": 1772, + "names": "CTDBn_leaf_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down leaf dead biomass N flux to litter" + }, + { + "codes": 1773, + "names": "CTDBn_froot_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down fine root dead biomass N flux to litter" + }, + { + "codes": 1774, + "names": "CTDBn_fruit_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down fruit dead biomass N flux to litter" + }, + { + "codes": 1775, + "names": "CTDBn_softstem_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down softstem dead biomass N flux to litter" + }, + { + "codes": 1776, + "names": "CTDBn_nsc_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down dead biomass non-structured pool N flux to litter" + }, + { + "codes": 1777, + "names": "CTDBn_cstem_to_cwd", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down coarse stem dead biomass N flux to coarse woody debris" + }, + { + "codes": 1778, + "names": "CTDBn_croot_to_cwd", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down coarse root dead biomass N flux to coarse woody debris" + }, + { + "codes": 1779, + "names": "CTDBn_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down dead biomass N flux to litter" + }, + { + "codes": 1780, + "names": "m_leafn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Leaf fire N flux" + }, + { + "codes": 1781, + "names": "m_frootn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fine root fire N flux" + }, + { + "codes": 1782, + "names": "m_fruitn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fruit fire N flux" + }, + { + "codes": 1783, + "names": "m_softstemn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Softstem fire N flux" + }, + { + "codes": 1784, + "names": "m_STDBn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Wilted plant biomass fire N flux" + }, + { + "codes": 1785, + "names": "m_CTDBn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down plant biomass fire N flux" + }, + { + "codes": 1786, + "names": "m_leafn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Leaf storage pool fire N flux" + }, + { + "codes": 1787, + "names": "m_frootn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fine root storage pool fire N flux" + }, + { + "codes": 1788, + "names": "m_fruitn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fruit storage pool fire N flux" + }, + { + "codes": 1789, + "names": "m_fruitn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fruit transfer pool fire N flux" + }, + { + "codes": 1790, + "names": "m_softstemn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Softstem storage pool fire N flux" + }, + { + "codes": 1791, + "names": "m_softstemn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Softstem transfer pool fire N flux" + }, + { + "codes": 1792, + "names": "m_livestemn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live stem storage pool fire N flux" + }, + { + "codes": 1793, + "names": "m_deadstemn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead stem storage pool fire N flux" + }, + { + "codes": 1794, + "names": "m_livecrootn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live coarse root storage pool fire N flux" + }, + { + "codes": 1795, + "names": "m_deadcrootn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead coarse root storage pool fire N flux" + }, + { + "codes": 1796, + "names": "m_leafn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Leaf transfer pool fire N flux" + }, + { + "codes": 1797, + "names": "m_frootn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fine root transfer pool fire N flux" + }, + { + "codes": 1798, + "names": "m_livestemn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live stem transfer pool fire N flux" + }, + { + "codes": 1799, + "names": "m_deadstemn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead stem transfer pool fire N flux" + }, + { + "codes": 1800, + "names": "m_livecrootn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live coarse root transfer pool fire N flux" + }, + { + "codes": 1801, + "names": "m_deadcrootn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead coarse root transfer pool fire N flux" + }, + { + "codes": 1802, + "names": "m_livestemn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live stem fire N flux" + }, + { + "codes": 1803, + "names": "m_deadstemn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead stem fire N flux" + }, + { + "codes": 1804, + "names": "m_livecrootn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live coarse root fire N flux" + }, + { + "codes": 1805, + "names": "m_deadcrootn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead coarse root fire N flux" + }, + { + "codes": 1806, + "names": "m_retransn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Retranslocated N fire N flux" + }, + { + "codes": 1807, + "names": "m_litr1n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Labile N portion of litter fire N flux" + }, + { + "codes": 1808, + "names": "m_litr2n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Unshielded cellulose portion N of litter fire N flux" + }, + { + "codes": 1809, + "names": "m_litr3n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Shielded cellulose portion N of litter fire N flux" + }, + { + "codes": 1810, + "names": "m_litr4n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Lignin N portion of litter fire N flux" + }, + { + "codes": 1811, + "names": "m_cwdn_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Coarse woody debris fire N flux" + }, + { + "codes": 1812, + "names": "leafn_transfer_to_leafn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from leaf transfer pool to leaf" + }, + { + "codes": 1813, + "names": "frootn_transfer_to_frootn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from fine root transfer pool to fine root" + }, + { + "codes": 1814, + "names": "fruitn_transfer_to_fruitn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from fruit transfer pool to fruit" + }, + { + "codes": 1815, + "names": "softstemn_transfer_to_softstemn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from softstem transfer pool to softstem" + }, + { + "codes": 1816, + "names": "livestemn_transfer_to_livestemn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from live stem transfer pool to live stem" + }, + { + "codes": 1817, + "names": "deadstemn_transfer_to_deadstemn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from dead stem transfer to dead stem" + }, + { + "codes": 1818, + "names": "livecrootn_transfer_to_livecrootn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from live coarse root transfer pool to live coarse root" + }, + { + "codes": 1819, + "names": "deadcrootn_transfer_to_deadcrootn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from dead coarse root transfer pool to dead coarse root" + }, + { + "codes": 1820, + "names": "leafn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to labile N portion of litter" + }, + { + "codes": 1821, + "names": "leafn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to unshielded cellulose N portion of litter" + }, + { + "codes": 1822, + "names": "leafn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to shielded cellulose N portion of litter" + }, + { + "codes": 1823, + "names": "leafn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to lignin N portion of litter" + }, + { + "codes": 1824, + "names": "leafn_to_retransn", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to retranslocated N" + }, + { + "codes": 1825, + "names": "frootn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to labile N portion of litter" + }, + { + "codes": 1826, + "names": "frootn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 1827, + "names": "frootn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 1828, + "names": "frootn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to lignin N portion of litter" + }, + { + "codes": 1829, + "names": "fruitn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to labile N portion of litter" + }, + { + "codes": 1830, + "names": "fruitn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to unshielded cellulose portion of litter" + }, + { + "codes": 1831, + "names": "fruitn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to shielded cellulose portion of litter" + }, + { + "codes": 1832, + "names": "fruitn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to lignin N portion of litter" + }, + { + "codes": 1833, + "names": "softstemn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to labile N portion of litter" + }, + { + "codes": 1834, + "names": "softstemn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 1835, + "names": "softstemn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 1836, + "names": "softstemn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to lignin N portion of litter" + }, + { + "codes": 1837, + "names": "ndep_to_sminnTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from N deposition to soil mineral N" + }, + { + "codes": 1838, + "names": "nfix_to_sminnTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from N fixation to soil mineral N" + }, + { + "codes": 1839, + "names": "cwdn_to_litr2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1840, + "names": "cwdn_to_litr2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1841, + "names": "cwdn_to_litr2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1842, + "names": "cwdn_to_litr2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1843, + "names": "cwdn_to_litr2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1844, + "names": "cwdn_to_litr2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1845, + "names": "cwdn_to_litr2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1846, + "names": "cwdn_to_litr2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1847, + "names": "cwdn_to_litr2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1848, + "names": "cwdn_to_litr2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1849, + "names": "cwdn_to_litr3n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1850, + "names": "cwdn_to_litr3n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1851, + "names": "cwdn_to_litr3n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1852, + "names": "cwdn_to_litr3n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1853, + "names": "cwdn_to_litr3n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1854, + "names": "cwdn_to_litr3n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1855, + "names": "cwdn_to_litr3n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1856, + "names": "cwdn_to_litr3n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1857, + "names": "cwdn_to_litr3n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1858, + "names": "cwdn_to_litr3n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1859, + "names": "cwdn_to_litr4n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1860, + "names": "cwdn_to_litr4n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1861, + "names": "cwdn_to_litr4n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1862, + "names": "cwdn_to_litr4n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1863, + "names": "cwdn_to_litr4n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1864, + "names": "cwdn_to_litr4n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1865, + "names": "cwdn_to_litr4n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1866, + "names": "cwdn_to_litr4n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1867, + "names": "cwdn_to_litr4n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1868, + "names": "cwdn_to_litr4n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1869, + "names": "litr1n_to_soil1n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1870, + "names": "litr1n_to_soil1n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1871, + "names": "litr1n_to_soil1n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1872, + "names": "litr1n_to_soil1n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1873, + "names": "litr1n_to_soil1n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1874, + "names": "litr1n_to_soil1n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1875, + "names": "litr1n_to_soil1n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1876, + "names": "litr1n_to_soil1n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1877, + "names": "litr1n_to_soil1n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1878, + "names": "litr1n_to_soil1n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1879, + "names": "litr2n_to_soil2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1880, + "names": "litr2n_to_soil2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1881, + "names": "litr2n_to_soil2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1882, + "names": "litr2n_to_soil2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1883, + "names": "litr2n_to_soil2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1884, + "names": "litr2n_to_soil2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1885, + "names": "litr2n_to_soil2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1886, + "names": "litr2n_to_soil2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1887, + "names": "litr2n_to_soil2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1888, + "names": "litr2n_to_soil2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1889, + "names": "litr3n_to_litr2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1890, + "names": "litr3n_to_litr2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1891, + "names": "litr3n_to_litr2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1892, + "names": "litr3n_to_litr2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1893, + "names": "litr3n_to_litr2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1894, + "names": "litr3n_to_litr2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1895, + "names": "litr3n_to_litr2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1896, + "names": "litr3n_to_litr2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1897, + "names": "litr3n_to_litr2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1898, + "names": "litr3n_to_litr2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1899, + "names": "litr4n_to_soil3n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1900, + "names": "litr4n_to_soil3n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1901, + "names": "litr4n_to_soil3n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1902, + "names": "litr4n_to_soil3n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1903, + "names": "litr4n_to_soil3n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1904, + "names": "litr4n_to_soil3n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1905, + "names": "litr4n_to_soil3n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1906, + "names": "litr4n_to_soil3n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1907, + "names": "litr4n_to_soil3n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1908, + "names": "litr4n_to_soil3n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1909, + "names": "soil1n_to_soil2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1910, + "names": "soil1n_to_soil2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1911, + "names": "soil1n_to_soil2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1912, + "names": "soil1n_to_soil2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1913, + "names": "soil1n_to_soil2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1914, + "names": "soil1n_to_soil2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1915, + "names": "soil1n_to_soil2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1916, + "names": "soil1n_to_soil2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1917, + "names": "soil1n_to_soil2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1918, + "names": "soil1n_to_soil2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1919, + "names": "soil2n_to_soil3n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1920, + "names": "soil2n_to_soil3n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1921, + "names": "soil2n_to_soil3n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1922, + "names": "soil2n_to_soil3n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1923, + "names": "soil2n_to_soil3n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1924, + "names": "soil2n_to_soil3n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1925, + "names": "soil2n_to_soil3n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1926, + "names": "soil2n_to_soil3n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1927, + "names": "soil2n_to_soil3n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1928, + "names": "soil2n_to_soil3n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1929, + "names": "soil3n_to_soil4n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 1 (0-3 cm)" + }, + { + "codes": 1930, + "names": "soil3n_to_soil4n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 2 (3-10 cm)" + }, + { + "codes": 1931, + "names": "soil3n_to_soil4n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 3 (10-30 cm)" + }, + { + "codes": 1932, + "names": "soil3n_to_soil4n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 4 (30-60 cm)" + }, + { + "codes": 1933, + "names": "soil3n_to_soil4n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 5 (60-90 cm)" + }, + { + "codes": 1934, + "names": "soil3n_to_soil4n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 6 (90-120 cm)" + }, + { + "codes": 1935, + "names": "soil3n_to_soil4n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 7 (120-150 cm)" + }, + { + "codes": 1936, + "names": "soil3n_to_soil4n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 8 (150-200 cm)" + }, + { + "codes": 1937, + "names": "soil3n_to_soil4n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 9 (200-400 cm)" + }, + { + "codes": 1938, + "names": "soil3n_to_soil4n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1939, + "names": "soil4n_to_sminNH4[0]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 1 (0-3 cm)" + }, + { + "codes": 1940, + "names": "soil4n_to_sminNH4[1]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer (3-10 cm)" + }, + { + "codes": 1941, + "names": "soil4n_to_sminNH4[2]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 3 (10-30 cm)" + }, + { + "codes": 1942, + "names": "soil4n_to_sminNH4[3]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 4 (30-60 cm)" + }, + { + "codes": 1943, + "names": "soil4n_to_sminNH4[4]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 5 (60-90 cm)" + }, + { + "codes": 1944, + "names": "soil4n_to_sminNH4[5]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 6 (90-120 cm)" + }, + { + "codes": 1945, + "names": "soil4n_to_sminNH4[6]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 7 (120-150 cm)" + }, + { + "codes": 1946, + "names": "soil4n_to_sminNH4[7]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 8 (150-200 cm)" + }, + { + "codes": 1947, + "names": "soil4n_to_sminNH4[8]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 9 (200-400 cm)" + }, + { + "codes": 1948, + "names": "soil4n_to_sminNH4[9]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 1 (400-1000 cm)" + }, + { + "codes": 1949, + "names": "soil4n_to_sminNH4_total", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4" + }, + { + "codes": 1950, + "names": "sminn_to_soil_SUM[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 1 (0-3 cm)" + }, + { + "codes": 1951, + "names": "sminn_to_soil_SUM[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 2 (3-10 cm)" + }, + { + "codes": 1952, + "names": "sminn_to_soil_SUM[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 3 (10-30 cm)" + }, + { + "codes": 1953, + "names": "sminn_to_soil_SUM[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 4 (30-60 cm)" + }, + { + "codes": 1954, + "names": "sminn_to_soil_SUM[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 5 (60-90 cm)" + }, + { + "codes": 1955, + "names": "sminn_to_soil_SUM[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 6 (90-120 cm)" + }, + { + "codes": 1956, + "names": "sminn_to_soil_SUM[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 7 (120-150 cm)" + }, + { + "codes": 1957, + "names": "sminn_to_soil_SUM[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 8 (150-200 cm)" + }, + { + "codes": 1958, + "names": "sminn_to_soil_SUM[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 9 (200-400 cm)" + }, + { + "codes": 1959, + "names": "sminn_to_soil_SUM[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1960, + "names": "sminNH4_to_soil_SUM[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 1 (0-3 cm)" + }, + { + "codes": 1961, + "names": "sminNH4_to_soil_SUM[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 2 (3-10 cm)" + }, + { + "codes": 1962, + "names": "sminNH4_to_soil_SUM[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 3 (10-30 cm)" + }, + { + "codes": 1963, + "names": "sminNH4_to_soil_SUM[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 4 (30-60 cm)" + }, + { + "codes": 1964, + "names": "sminNH4_to_soil_SUM[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 5 (60-90 cm)" + }, + { + "codes": 1965, + "names": "sminNH4_to_soil_SUM[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 6 (90-120 cm)" + }, + { + "codes": 1966, + "names": "sminNH4_to_soil_SUM[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 7 (120-150 cm)" + }, + { + "codes": 1967, + "names": "sminNH4_to_soil_SUM[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 8 (150-200 cm)" + }, + { + "codes": 1968, + "names": "sminNH4_to_soil_SUM[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 9 (200-400 cm)" + }, + { + "codes": 1969, + "names": "sminNH4_to_soil_SUM[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1970, + "names": "sminNO3_to_soil_SUM[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 1 (0-3 cm)" + }, + { + "codes": 1971, + "names": "sminNO3_to_soil_SUM[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 2 (3-10 cm)" + }, + { + "codes": 1972, + "names": "sminNO3_to_soil_SUM[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 3 (10-30 cm)" + }, + { + "codes": 1973, + "names": "sminNO3_to_soil_SUM[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 4 (30-60 cm)" + }, + { + "codes": 1974, + "names": "sminNO3_to_soil_SUM[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 5 (60-90 cm)" + }, + { + "codes": 1975, + "names": "sminNO3_to_soil_SUM[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 6 (90-120 cm)" + }, + { + "codes": 1976, + "names": "sminNO3_to_soil_SUM[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 7 (120-150 cm)" + }, + { + "codes": 1977, + "names": "sminNO3_to_soil_SUM[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 8 (150-200 cm)" + }, + { + "codes": 1978, + "names": "sminNO3_to_soil_SUM[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 9 (200-400 cm)" + }, + { + "codes": 1979, + "names": "sminNO3_to_soil_SUM[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1980, + "names": "sminn_to_soil1n_l1[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1981, + "names": "sminn_to_soil1n_l1[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1982, + "names": "sminn_to_soil1n_l1[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1983, + "names": "sminn_to_soil1n_l1[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1984, + "names": "sminn_to_soil1n_l1[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1985, + "names": "sminn_to_soil1n_l1[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1986, + "names": "sminn_to_soil1n_l1[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1987, + "names": "sminn_to_soil1n_l1[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1988, + "names": "sminn_to_soil1n_l1[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1989, + "names": "sminn_to_soil1n_l1[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1990, + "names": "sminn_to_soil2n_l2[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1991, + "names": "sminn_to_soil2n_l2[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1992, + "names": "sminn_to_soil2n_l2[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1993, + "names": "sminn_to_soil2n_l2[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1994, + "names": "sminn_to_soil2n_l2[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1995, + "names": "sminn_to_soil2n_l2[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1996, + "names": "sminn_to_soil2n_l2[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1997, + "names": "sminn_to_soil2n_l2[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1998, + "names": "sminn_to_soil2n_l2[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1999, + "names": "sminn_to_soil2n_l2[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2000, + "names": "sminn_to_soil3n_l4[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2001, + "names": "sminn_to_soil3n_l4[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2002, + "names": "sminn_to_soil3n_l4[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2003, + "names": "sminn_to_soil3n_l4[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2004, + "names": "sminn_to_soil3n_l4[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2005, + "names": "sminn_to_soil3n_l4[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2006, + "names": "sminn_to_soil3n_l4[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2007, + "names": "sminn_to_soil3n_l4[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2008, + "names": "sminn_to_soil3n_l4[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2009, + "names": "sminn_to_soil3n_l4[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2010, + "names": "sminn_to_soil2n_s1[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2011, + "names": "sminn_to_soil2n_s1[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2012, + "names": "sminn_to_soil2n_s1[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2013, + "names": "sminn_to_soil2n_s1[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2014, + "names": "sminn_to_soil2n_s1[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2015, + "names": "sminn_to_soil2n_s1[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2016, + "names": "sminn_to_soil2n_s1[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2017, + "names": "sminn_to_soil2n_s1[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2018, + "names": "sminn_to_soil2n_s1[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2019, + "names": "sminn_to_soil2n_s1[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2020, + "names": "sminn_to_soil3n_s2[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2021, + "names": "sminn_to_soil3n_s2[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2022, + "names": "sminn_to_soil3n_s2[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2023, + "names": "sminn_to_soil3n_s2[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2024, + "names": "sminn_to_soil3n_s2[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2025, + "names": "sminn_to_soil3n_s2[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2026, + "names": "sminn_to_soil3n_s2[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2027, + "names": "sminn_to_soil3n_s2[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2028, + "names": "sminn_to_soil3n_s2[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2029, + "names": "sminn_to_soil3n_s2[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2030, + "names": "sminn_to_soil4n_s3[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2031, + "names": "sminn_to_soil4n_s3[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2032, + "names": "sminn_to_soil4n_s3[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2033, + "names": "sminn_to_soil4n_s3[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2034, + "names": "sminn_to_soil4n_s3[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2035, + "names": "sminn_to_soil4n_s3[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2036, + "names": "sminn_to_soil4n_s3[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2037, + "names": "sminn_to_soil4n_s3[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2038, + "names": "sminn_to_soil4n_s3[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2039, + "names": "sminn_to_soil4n_s3[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2040, + "names": "sminn_to_soil_SUM_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil" + }, + { + "codes": 2041, + "names": "sminNH4_to_soil_SUM_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux srom soil mineral NH4 to soil" + }, + { + "codes": 2042, + "names": "sminNO3_to_soil_SUM_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral NO3 to soil" + }, + { + "codes": 2043, + "names": "sminNO3_to_denitr[0]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2044, + "names": "sminNO3_to_denitr[1]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2045, + "names": "sminNO3_to_denitr[2]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2045, + "names": "cwdn_to_litr2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in total soil" + }, + { + "codes": 2046, + "names": "sminNO3_to_denitr[3]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2046, + "names": "cwdn_to_litr3n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in total soil" + }, + { + "codes": 2047, + "names": "sminNO3_to_denitr[4]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2047, + "names": "cwdn_to_litr4n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in total soil" + }, + { + "codes": 2048, + "names": "sminNO3_to_denitr[5]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2048, + "names": "litr1n_to_soil1n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in total soil" + }, + { + "codes": 2049, + "names": "sminNO3_to_denitr[6]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2049, + "names": "litr2n_to_soil2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in total soil" + }, + { + "codes": 2050, + "names": "sminNO3_to_denitr[7]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2050, + "names": "litr3n_to_litr2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in total soil" + }, + { + "codes": 2051, + "names": "sminNO3_to_denitr[8]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2051, + "names": "litr4n_to_soil3n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in total soil" + }, + { + "codes": 2052, + "names": "sminNO3_to_denitr[9]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2052, + "names": "soil1n_to_soil2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast decomposing SOM pool in total soil" + }, + { + "codes": 2053, + "names": "sminNH4_to_nitrif[0]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2053, + "names": "soil2n_to_soil3n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow decomposing SOM pool in total soil" + }, + { + "codes": 2054, + "names": "sminNH4_to_nitrif[1]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2054, + "names": "soil3n_to_soil4n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM Carbon content of SOM pool in total soil" + }, + { + "codes": 2055, + "names": "sminNH4_to_nitrif[2]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2055, + "names": "sminn_to_soil1n_l1_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2056, + "names": "sminNH4_to_nitrif[3]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2056, + "names": "sminn_to_soil2n_l2_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2057, + "names": "sminNH4_to_nitrif[4]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2057, + "names": "sminn_to_soil3n_l4_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2058, + "names": "sminNH4_to_nitrif[5]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2058, + "names": "sminn_to_soil2n_s1_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2059, + "names": "sminNH4_to_nitrif[6]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2059, + "names": "sminn_to_soil3n_s2_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2060, + "names": "sminNH4_to_nitrif[7]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2060, + "names": "sminn_to_soil4n_s3_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2061, + "names": "sminNH4_to_nitrif[8]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2062, + "names": "sminNH4_to_nitrif[9]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2063, + "names": "N2_flux_DENITR[0]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2064, + "names": "N2_flux_DENITR[1]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2065, + "names": "N2_flux_DENITR[2]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2066, + "names": "N2_flux_DENITR[3]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2067, + "names": "N2_flux_DENITR[4]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2068, + "names": "N2_flux_DENITR[5]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2069, + "names": "N2_flux_DENITR[6]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2070, + "names": "N2_flux_DENITR[7]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2071, + "names": "N2_flux_DENITR[8]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2072, + "names": "N2_flux_DENITR[9]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2073, + "names": "N2O_flux_NITRIF[0]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 1 (1-2 cm)" + }, + { + "codes": 2074, + "names": "N2O_flux_NITRIF[1]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 2 (3-10 cm)" + }, + { + "codes": 2075, + "names": "N2O_flux_NITRIF[2]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 3 (10-30 cm)" + }, + { + "codes": 2076, + "names": "N2O_flux_NITRIF[3]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 4 (30-60 cm)" + }, + { + "codes": 2077, + "names": "N2O_flux_NITRIF[4]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 5 (60-90 cm)" + }, + { + "codes": 2078, + "names": "N2O_flux_NITRIF[5]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 6 (90-120 cm)" + }, + { + "codes": 2079, + "names": "N2O_flux_NITRIF[6]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 7 (120-150 cm)" + }, + { + "codes": 2080, + "names": "N2O_flux_NITRIF[7]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 8 (150-200 cm)" + }, + { + "codes": 2081, + "names": "N2O_flux_NITRIF[8]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 9 (200-400 cm)" + }, + { + "codes": 2082, + "names": "N2O_flux_NITRIF[9]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2083, + "names": "N2O_flux_DENITR[0]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 1 (1-2 cm)" + }, + { + "codes": 2084, + "names": "N2O_flux_DENITR[1]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 2 (3-10 cm)" + }, + { + "codes": 2085, + "names": "N2O_flux_DENITR[2]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 3 (10-30 cm)" + }, + { + "codes": 2086, + "names": "N2O_flux_DENITR[3]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 4 (30-60 cm)" + }, + { + "codes": 2087, + "names": "N2O_flux_DENITR[4]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 5 (60-90 cm)" + }, + { + "codes": 2088, + "names": "N2O_flux_DENITR[5]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 6 (90-120 cm)" + }, + { + "codes": 2089, + "names": "N2O_flux_DENITR[6]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 7 (120-150 cm)" + }, + { + "codes": 2090, + "names": "N2O_flux_DENITR[7]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 8 (150-200 cm)" + }, + { + "codes": 2091, + "names": "N2O_flux_DENITR[8]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 9 (200-400 cm)" + }, + { + "codes": 2092, + "names": "N2O_flux_DENITR[9]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2093, + "names": "sminNO3_to_denitr_total", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3" + }, + { + "codes": 2094, + "names": "sminNH4_to_nitrif_total", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4" + }, + { + "codes": 2095, + "names": "N2_flux_DENITR_total", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2" + }, + { + "codes": 2096, + "names": "N2O_flux_NITRIF_total", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O" + }, + { + "codes": 2097, + "names": "N2O_flux_DENITR_total", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O" + }, + { + "codes": 2098, + "names": "sminNH4_to_npool[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 1 (1-2 cm)" + }, + { + "codes": 2099, + "names": "sminNH4_to_npool[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2100, + "names": "sminNH4_to_npool[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2101, + "names": "sminNH4_to_npool[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2102, + "names": "sminNH4_to_npool[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2103, + "names": "sminNH4_to_npool[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2104, + "names": "sminNH4_to_npool[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2105, + "names": "sminNH4_to_npool[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2106, + "names": "sminNH4_to_npool[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2107, + "names": "sminNH4_to_npool[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2108, + "names": "sminNO3_to_npool[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 1 (1-2 cm)" + }, + { + "codes": 2109, + "names": "sminNO3_to_npool[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2110, + "names": "sminNO3_to_npool[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2111, + "names": "sminNO3_to_npool[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2112, + "names": "sminNO3_to_npool[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2113, + "names": "sminNO3_to_npool[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2114, + "names": "sminNO3_to_npool[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2115, + "names": "sminNO3_to_npool[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2116, + "names": "sminNO3_to_npool[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2117, + "names": "sminNO3_to_npool[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2118, + "names": "sminNH4_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool" + }, + { + "codes": 2119, + "names": "sminNO3_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool" + }, + { + "codes": 2120, + "names": "sminn_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral N to temporary plant N pool" + }, + { + "codes": 2121, + "names": "sminNH4_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2122, + "names": "sminNH4_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2123, + "names": "sminNH4_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2124, + "names": "sminNH4_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2125, + "names": "sminNH4_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2126, + "names": "sminNH4_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2127, + "names": "sminNH4_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2128, + "names": "sminNH4_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2129, + "names": "sminNH4_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2130, + "names": "sminNH4_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2131, + "names": "sminNH4_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2132, + "names": "sminNH4_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2133, + "names": "sminNH4_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2134, + "names": "sminNH4_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2135, + "names": "sminNH4_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2136, + "names": "sminNH4_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2137, + "names": "sminNH4_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2138, + "names": "sminNH4_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2139, + "names": "sminNH4_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2140, + "names": "sminNH4_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2141, + "names": "sminNO3_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2142, + "names": "sminNO3_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2143, + "names": "sminNO3_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2144, + "names": "sminNO3_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2145, + "names": "sminNO3_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2146, + "names": "sminNO3_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2147, + "names": "sminNO3_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2148, + "names": "sminNO3_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2149, + "names": "sminNO3_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2150, + "names": "sminNO3_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2151, + "names": "sminNO3_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2152, + "names": "sminNO3_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2153, + "names": "sminNO3_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2154, + "names": "sminNO3_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2155, + "names": "sminNO3_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2156, + "names": "sminNO3_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2157, + "names": "sminNO3_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2158, + "names": "sminNO3_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2159, + "names": "sminNO3_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2160, + "names": "sminNO3_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2161, + "names": "sminN_leached_RZ", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral N from rootzone" + }, + { + "codes": 2162, + "names": "soil1_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2163, + "names": "soil1_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2164, + "names": "soil1_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2165, + "names": "soil1_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2166, + "names": "soil1_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2167, + "names": "soil1_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2168, + "names": "soil1_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2169, + "names": "soil1_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2170, + "names": "soil1_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2171, + "names": "soil1_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2172, + "names": "soil2_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2173, + "names": "soil2_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2174, + "names": "soil2_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2175, + "names": "soil2_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2176, + "names": "soil2_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2177, + "names": "soil2_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2178, + "names": "soil2_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2179, + "names": "soil2_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2180, + "names": "soil2_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2181, + "names": "soil2_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2182, + "names": "soil3_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2183, + "names": "soil3_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2184, + "names": "soil3_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2185, + "names": "soil3_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2186, + "names": "soil3_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2187, + "names": "soil3_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2188, + "names": "soil3_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2189, + "names": "soil3_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2190, + "names": "soil3_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2191, + "names": "soil3_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2192, + "names": "soil4_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 2193, + "names": "soil4_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 2194, + "names": "soil4_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 2195, + "names": "soil4_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 2196, + "names": "soil4_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 2197, + "names": "soil4_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 2198, + "names": "soil4_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 2199, + "names": "soil4_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 2200, + "names": "soil4_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 2201, + "names": "soil4_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2202, + "names": "soil1_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2203, + "names": "soil1_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2204, + "names": "soil1_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2205, + "names": "soil1_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2206, + "names": "soil1_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2207, + "names": "soil1_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2208, + "names": "soil1_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2209, + "names": "soil1_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2210, + "names": "soil1_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2211, + "names": "soil1_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2212, + "names": "soil2_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2213, + "names": "soil2_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2214, + "names": "soil2_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2215, + "names": "soil2_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2216, + "names": "soil2_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2217, + "names": "soil2_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2218, + "names": "soil2_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2219, + "names": "soil2_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2220, + "names": "soil2_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2221, + "names": "soil2_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2222, + "names": "soil3_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2223, + "names": "soil3_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2224, + "names": "soil3_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2225, + "names": "soil3_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2226, + "names": "soil3_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2227, + "names": "soil3_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2228, + "names": "soil3_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2229, + "names": "soil3_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2230, + "names": "soil3_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2231, + "names": "soil3_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2232, + "names": "soil4_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 2233, + "names": "soil4_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 2234, + "names": "soil4_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 2235, + "names": "soil4_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 2236, + "names": "soil4_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 2237, + "names": "soil4_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 2238, + "names": "soil4_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 2239, + "names": "soil4_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 2240, + "names": "soil4_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 2241, + "names": "soil4_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2242, + "names": "DON_leached_RZ", + "units": "kgN m-2 day-1", + "descriptions": "Leached DON from rootzone" + }, + { + "codes": 2243, + "names": "retransn_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from retransclocated N to temporary plant N pool" + }, + { + "codes": 2244, + "names": "npool_to_leafn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to leaf" + }, + { + "codes": 2245, + "names": "npool_to_leafn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Dail allocation N flux from temporary plant N pool to leaf storage pool" + }, + { + "codes": 2246, + "names": "npool_to_frootn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fine root" + }, + { + "codes": 2247, + "names": "npool_to_frootn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fine root storage pool" + }, + { + "codes": 2248, + "names": "npool_to_fruitn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fruit" + }, + { + "codes": 2249, + "names": "npool_to_fruitn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fruit storage pool" + }, + { + "codes": 2250, + "names": "npool_to_softstemn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to softstem" + }, + { + "codes": 2251, + "names": "npool_to_softstemn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to softstem storage pool" + }, + { + "codes": 2252, + "names": "npool_to_livestemn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live stem" + }, + { + "codes": 2253, + "names": "npool_to_livestemn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily alloaction N flux from temporary plant N pool to live stem storage pool" + }, + { + "codes": 2254, + "names": "npool_to_deadstemn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead stem" + }, + { + "codes": 2255, + "names": "npool_to_deadstemn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead stem storage pool" + }, + { + "codes": 2256, + "names": "npool_to_livecrootn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live coarse root" + }, + { + "codes": 2257, + "names": "npool_to_livecrootn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live coarse root storage pool" + }, + { + "codes": 2258, + "names": "npool_to_deadcrootn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead coarse root" + }, + { + "codes": 2259, + "names": "npool_to_deadcrootn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead coarse root storage pool" + }, + { + "codes": 2260, + "names": "leafn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf storage pool" + }, + { + "codes": 2261, + "names": "frootn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root storage pool" + }, + { + "codes": 2262, + "names": "fruitn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fruit storage pool" + }, + { + "codes": 2263, + "names": "softstemn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem storage pool" + }, + { + "codes": 2264, + "names": "livestemn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem storage pool" + }, + { + "codes": 2265, + "names": "livecrootn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root storage pool" + }, + { + "codes": 2266, + "names": "deadstemn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead stem storage pool" + }, + { + "codes": 2267, + "names": "deadcrootn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead coarse root storage pool" + }, + { + "codes": 2268, + "names": "leafn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf transfer pool" + }, + { + "codes": 2269, + "names": "frootn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root transfer pool" + }, + { + "codes": 2270, + "names": "fruitn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fruit transfer pool" + }, + { + "codes": 2271, + "names": "softstemn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem transfer pool" + }, + { + "codes": 2272, + "names": "livestemn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem transfer pool" + }, + { + "codes": 2273, + "names": "livecrootn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root transfer pool" + }, + { + "codes": 2274, + "names": "deadstemn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead stem transfer pool" + }, + { + "codes": 2275, + "names": "deadcrootn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead coarse root transfer pool" + }, + { + "codes": 2276, + "names": "leafn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf" + }, + { + "codes": 2277, + "names": "frootn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root" + }, + { + "codes": 2278, + "names": "fruitn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fruit" + }, + { + "codes": 2279, + "names": "softstemn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem" + }, + { + "codes": 2280, + "names": "livestemn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem" + }, + { + "codes": 2281, + "names": "livecrootn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root" + }, + { + "codes": 2282, + "names": "NSN_nw_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-structured non-woody nitrogen" + }, + { + "codes": 2283, + "names": "actN_nw_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-woody portion of actual N pool" + }, + { + "codes": 2284, + "names": "NSN_w_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-structured woody nitrogen" + }, + { + "codes": 2285, + "names": "actN_w_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from woody portion ofactual N pool" + }, + { + "codes": 2286, + "names": "leafn_storage_to_leafn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of leaf storage to transfer pool" + }, + { + "codes": 2287, + "names": "frootn_storage_to_frootn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of fine root storage to transfer pool" + }, + { + "codes": 2288, + "names": "livestemn_storage_to_livestemn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live stem storage to transfer pool" + }, + { + "codes": 2289, + "names": "deadstemn_storage_to_deadstemn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of dead stem storage to transfer pool" + }, + { + "codes": 2290, + "names": "livecrootn_storage_to_livecrootn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live coarse root storage to transfer pool" + }, + { + "codes": 2291, + "names": "deadcrootn_storage_to_deadcrootn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of dead coarse root storage to transfer pool" + }, + { + "codes": 2292, + "names": "fruitn_storage_to_fruitn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of fruit storage to transfer pool" + }, + { + "codes": 2293, + "names": "softstemn_storage_to_softstemn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of softstem storage to transfer pool" + }, + { + "codes": 2294, + "names": "livestemn_to_deadstemn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live stem to dead stem" + }, + { + "codes": 2295, + "names": "livestemn_to_retransn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N trunover of live stem to retranslocated N" + }, + { + "codes": 2296, + "names": "livecrootn_to_deadcrootn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live coarse root to dead coarse root" + }, + { + "codes": 2297, + "names": "livecrootn_to_retransn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live coarse root to retranslocated N" + }, + { + "codes": 2298, + "names": "leafn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Leaf transfer pool N flux from planting" + }, + { + "codes": 2299, + "names": "frootn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Fine root transfer pool N flux from planting" + }, + { + "codes": 2300, + "names": "fruitn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Fruit transfer pool N flux from planting" + }, + { + "codes": 2301, + "names": "softstemn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Softstem transfer pool N flux from planting" + }, + { + "codes": 2302, + "names": "leafn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from leaf" + }, + { + "codes": 2303, + "names": "leafn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from leaf storage pool" + }, + { + "codes": 2304, + "names": "leafn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from leaf transfer pool" + }, + { + "codes": 2305, + "names": "fruitn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from fruit" + }, + { + "codes": 2306, + "names": "fruitn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from fruit storage pool" + }, + { + "codes": 2307, + "names": "fruitn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from fruit transfer pool" + }, + { + "codes": 2308, + "names": "livestemn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from live stem" + }, + { + "codes": 2309, + "names": "livestemn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from live stem storage pool" + }, + { + "codes": 2310, + "names": "livestemn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from live stem transfer pool" + }, + { + "codes": 2311, + "names": "deadstemn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from dead stem" + }, + { + "codes": 2312, + "names": "deadstemn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from dead stem storage pool" + }, + { + "codes": 2313, + "names": "deadstemn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from dead stem transfer pool" + }, + { + "codes": 2314, + "names": "retransn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from retranslocated N" + }, + { + "codes": 2315, + "names": "THN_to_CTDBn_leaf", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down leaf biomass" + }, + { + "codes": 2316, + "names": "THN_to_CTDBn_fruit", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down fruit biomass" + }, + { + "codes": 2317, + "names": "THN_to_CTDBn_nsc", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down plant biomass non-structured pool" + }, + { + "codes": 2318, + "names": "THN_to_CTDBn_cstem", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down coarse stem biomass" + }, + { + "codes": 2319, + "names": "STDBn_leaf_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from wilted leaf biomass" + }, + { + "codes": 2320, + "names": "STDBn_fruit_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from wilted fruit biomass" + }, + { + "codes": 2321, + "names": "STDBn_nsc_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2322, + "names": "leafn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from leaf" + }, + { + "codes": 2323, + "names": "leafn_storage_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from leaf storage pool" + }, + { + "codes": 2324, + "names": "leafn_transfer_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from leaf transfer pool" + }, + { + "codes": 2325, + "names": "fruitn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from fruit" + }, + { + "codes": 2326, + "names": "fruitn_storage_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from fruit storage pool" + }, + { + "codes": 2327, + "names": "fruitn_transfer_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from fruit transfer pool" + }, + { + "codes": 2328, + "names": "softstemn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from softstem" + }, + { + "codes": 2329, + "names": "softstemn_storage_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from softstem storage pool" + }, + { + "codes": 2330, + "names": "softstemn_transfer_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from softstem transfer pool" + }, + { + "codes": 2331, + "names": "retransn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from retranslocated N" + }, + { + "codes": 2332, + "names": "MOW_to_CTDBn_leaf", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down leaf biomass" + }, + { + "codes": 2333, + "names": "MOW_to_CTDBn_fruit", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down fruit biomass" + }, + { + "codes": 2334, + "names": "MOW_to_CTDBn_softstem", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down softstem biomass" + }, + { + "codes": 2335, + "names": "MOW_to_CTDBn_nsc", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down biomass non-structured pool" + }, + { + "codes": 2336, + "names": "STDBn_leaf_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted leaf biomass" + }, + { + "codes": 2337, + "names": "STDBn_fruit_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted fruit biomass" + }, + { + "codes": 2338, + "names": "STDBn_softstem_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted softstem biomass" + }, + { + "codes": 2339, + "names": "STDBn_nsc_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2340, + "names": "leafn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from leaf" + }, + { + "codes": 2341, + "names": "leafn_storage_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from leaf storage pool" + }, + { + "codes": 2342, + "names": "leafn_transfer_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from leaf transfer pool" + }, + { + "codes": 2343, + "names": "fruitn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from fruit" + }, + { + "codes": 2344, + "names": "fruitn_storage_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from fruit storage pool" + }, + { + "codes": 2345, + "names": "fruitn_transfer_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from fruit transfer pool" + }, + { + "codes": 2346, + "names": "softstemn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from softstem" + }, + { + "codes": 2347, + "names": "softstemn_storage_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from softstem storage pool" + }, + { + "codes": 2348, + "names": "softstemn_transfer_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from softstem transfer pool" + }, + { + "codes": 2349, + "names": "retransn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from retranslocated N" + }, + { + "codes": 2350, + "names": "HRV_to_CTDBn_leaf", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down leaf biomass" + }, + { + "codes": 2351, + "names": "HRV_to_CTDBn_fruit", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down fruit biomass" + }, + { + "codes": 2352, + "names": "HRV_to_CTDBn_softstem", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down softstem biomass" + }, + { + "codes": 2353, + "names": "HRV_to_CTDBn_nsc", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down biomass non-structured pool" + }, + { + "codes": 2354, + "names": "STDBn_leaf_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted leaf biomass" + }, + { + "codes": 2355, + "names": "STDBn_fruit_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted fruit biomass" + }, + { + "codes": 2356, + "names": "STDBn_softstem_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted softstem biomass" + }, + { + "codes": 2357, + "names": "STDBn_nsc_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2358, + "names": "leafn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from leaf" + }, + { + "codes": 2359, + "names": "leafn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from leaf storage pool" + }, + { + "codes": 2360, + "names": "leafn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from leaf transfer pool" + }, + { + "codes": 2361, + "names": "frootn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fine root" + }, + { + "codes": 2362, + "names": "frootn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fine root storage pool" + }, + { + "codes": 2363, + "names": "frootn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fine root transfer pool" + }, + { + "codes": 2364, + "names": "fruitn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fruit" + }, + { + "codes": 2365, + "names": "fruitn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fruit storage pool" + }, + { + "codes": 2366, + "names": "fruitn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fruit transfer pool" + }, + { + "codes": 2367, + "names": "softstemn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from softstem" + }, + { + "codes": 2368, + "names": "softstemn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from softstem storage pool" + }, + { + "codes": 2369, + "names": "softstemn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from softstem transfer pool" + }, + { + "codes": 2370, + "names": "retransn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from retranslocated N" + }, + { + "codes": 2371, + "names": "STDBn_leaf_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted leaf biomass" + }, + { + "codes": 2372, + "names": "STDBn_froot_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted fine root biomass" + }, + { + "codes": 2373, + "names": "STDBn_fruit_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted fruit biomass" + }, + { + "codes": 2374, + "names": "STDBn_softstem_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted softstem biomass" + }, + { + "codes": 2375, + "names": "STDBn_nsc_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2376, + "names": "CTDBn_leaf_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from cut-down leaf biomass" + }, + { + "codes": 2377, + "names": "CTDBn_fruit_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from cut-down fruit biomass" + }, + { + "codes": 2378, + "names": "CTDBn_softstem_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from cut-down softstem biomass" + }, + { + "codes": 2379, + "names": "leafn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from leaf" + }, + { + "codes": 2380, + "names": "leafn_storage_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazig N flux from leaf storage pool" + }, + { + "codes": 2381, + "names": "leafn_transfer_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux fromleaf transfer pool" + }, + { + "codes": 2382, + "names": "fruitn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from fruit" + }, + { + "codes": 2383, + "names": "fruitn_storage_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from fruit storage pool" + }, + { + "codes": 2384, + "names": "fruitn_transfer_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from fruit transfer pool" + }, + { + "codes": 2385, + "names": "softstemn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from softstem" + }, + { + "codes": 2386, + "names": "softstemn_storage_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from softstem storage pool" + }, + { + "codes": 2387, + "names": "softstemn_transfer_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from softstem transfer pool" + }, + { + "codes": 2388, + "names": "STDBn_leaf_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from wilted leaf biomass" + }, + { + "codes": 2389, + "names": "STDBn_fruit_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from wilted fruit biomass" + }, + { + "codes": 2390, + "names": "STDBn_softstem_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing flux from wilted softstem biomass" + }, + { + "codes": 2391, + "names": "STDBn_nsc_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2392, + "names": "retransn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing flux from retranslocated N" + }, + { + "codes": 2393, + "names": "GRZ_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to labile N portion of litter" + }, + { + "codes": 2394, + "names": "GRZ_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to unshielded cellulose N portion of litter" + }, + { + "codes": 2395, + "names": "GRZ_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to shielded cellulose N portion of litter" + }, + { + "codes": 2396, + "names": "GRZ_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to lignin N portion of litter" + }, + { + "codes": 2397, + "names": "FRZ_to_sminNH4", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to soil mineral NH4" + }, + { + "codes": 2398, + "names": "FRZ_to_sminNO3", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to soil mineral NO3" + }, + { + "codes": 2399, + "names": "FRZ_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to labile N portion of litter" + }, + { + "codes": 2400, + "names": "FRZ_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to unshielded cellulose N portion of litter" + }, + { + "codes": 2401, + "names": "FRZ_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to shielded cellulose N portion of litter" + }, + { + "codes": 2402, + "names": "FRZ_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to lignin N portion of litter" + }, + { + "codes": 2403, + "names": "N2O_flux_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Estimated N2O flux from grazing" + }, + { + "codes": 2404, + "names": "N2O_flux_FRZ", + "units": "kgN m-2 day-1", + "descriptions": "Estimated N2O flux from fertilizing" + }, + { + "codes": 2500, + "names": "thermal_time", + "units": "degree(Celsius)", + "descriptions": "Difference between avg. temp. and base temperature" + }, + { + "codes": 2501, + "names": "leafday", + "units": "n", + "descriptions": "Counter for days when leaves are on" + }, + { + "codes": 2502, + "names": "n_actphen", + "units": "n", + "descriptions": "Number of the actual phenophase" + }, + { + "codes": 2503, + "names": "leafday_lastmort", + "units": "degree(Celsius)", + "descriptions": "Last genetical mortality day" + }, + { + "codes": 2504, + "names": "flowHS_mort", + "units": "prop", + "descriptions": "Mortality coefficient of flowering heat stress" + }, + { + "codes": 2505, + "names": "transfer_ratio", + "units": "prop", + "descriptions": "Transfer proportion on actual day" + }, + { + "codes": 2506, + "names": "day_leafc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of leaf litterfall" + }, + { + "codes": 2507, + "names": "day_fruitc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of fruit litterfall" + }, + { + "codes": 2508, + "names": "day_softstemc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of softstem litterfall" + }, + { + "codes": 2509, + "names": "day_frootc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of fineroot litterfall" + }, + { + "codes": 2510, + "names": "day_livestemc_turnover_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of livestem turnover" + }, + { + "codes": 2511, + "names": "day_livecrootc_turnover_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of live coarse root turnover" + }, + { + "codes": 2512, + "names": "annmax_leafc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily leaf C content" + }, + { + "codes": 2513, + "names": "annmax_fruitc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily fruit C content" + }, + { + "codes": 2514, + "names": "annmax_softstemc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily softstem C content" + }, + { + "codes": 2515, + "names": "annmax_frootc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily fine root C content" + }, + { + "codes": 2516, + "names": "annmax_livestemc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily livestem C content" + }, + { + "codes": 2517, + "names": "annmax_livecrootc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily live coarse root C content" + }, + { + "codes": 2518, + "names": "dsr", + "units": "n", + "descriptions": "Number of days since rain" + }, + { + "codes": 2519, + "names": "cumSWCstress", + "units": "n", + "descriptions": "Cumulative soil water stress" + }, + { + "codes": 2520, + "names": "proj_lai", + "units": "m^2 m-2", + "descriptions": "Live projected leaf area index" + }, + { + "codes": 2521, + "names": "all_lai", + "units": "m^2 m-2", + "descriptions": "Live all-sided leaf area index" + }, + { + "codes": 2522, + "names": "sla_avg", + "units": "m^2 m-2", + "descriptions": "Canopy average proj. SLA" + }, + { + "codes": 2523, + "names": "plaisun", + "units": "m^2 m-2", + "descriptions": "Sunlit projected leaf area index" + }, + { + "codes": 2524, + "names": "plaishade", + "units": "m^2 m-2", + "descriptions": "Shaded projected leaf area index" + }, + { + "codes": 2525, + "names": "sun_proj_sla", + "units": "m2 kgC-1", + "descriptions": "Sunlit projected SLA" + }, + { + "codes": 2526, + "names": "shade_proj_sla", + "units": "m2 kgC-1", + "descriptions": "Shaded projected SLA" + }, + { + "codes": 2527, + "names": "plant_height", + "units": "m", + "descriptions": "Height of plant (based on stemw and" + }, + { + "codes": 2528, + "names": "NDVI", + "units": "ratio", + "descriptions": "Normalized difference vegetation index" + }, + { + "codes": 2529, + "names": "rootlength_prop[0]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 1 (0-3 cm)" + }, + { + "codes": 2530, + "names": "rootlength_prop[1]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 2 (3-10 cm)" + }, + { + "codes": 2531, + "names": "rootlength_prop[2]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 3 (10-30 cm)" + }, + { + "codes": 2532, + "names": "rootlength_prop[3]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 4 (30-60 cm)" + }, + { + "codes": 2533, + "names": "rootlength_prop[4]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 5 (60-90 cm)" + }, + { + "codes": 2534, + "names": "rootlength_prop[5]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 6 (90-120 cm)" + }, + { + "codes": 2535, + "names": "rootlength_prop[6]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 7 (120-150 cm)" + }, + { + "codes": 2536, + "names": "rootlength_prop[7]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 8 (150-200 cm)" + }, + { + "codes": 2537, + "names": "rootlength_prop[8]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 9 (200-400 cm)" + }, + { + "codes": 2538, + "names": "rootlength_prop[9]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2539, + "names": "psi[0]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 1 (0-3 cm)" + }, + { + "codes": 2540, + "names": "psi[1]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 2 (3-10 cm)" + }, + { + "codes": 2541, + "names": "psi[2]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 3 (10-30 cm)" + }, + { + "codes": 2542, + "names": "psi[3]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 4 (30-60 cm)" + }, + { + "codes": 2543, + "names": "psi[4]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 5 (60-90 cm)" + }, + { + "codes": 2544, + "names": "psi[5]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 6 (90-120 cm)" + }, + { + "codes": 2545, + "names": "psi[6]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 7 (120-150 cm)" + }, + { + "codes": 2546, + "names": "psi[7]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 8 (150-200 cm)" + }, + { + "codes": 2547, + "names": "psi[8]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 9 (200-400 cm)" + }, + { + "codes": 2548, + "names": "psi[9]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2549, + "names": "pF[0]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 1 (0-3 cm)" + }, + { + "codes": 2550, + "names": "pF[1]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 2 (3-10 cm)" + }, + { + "codes": 2551, + "names": "pF[2]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 3 (10-30 cm)" + }, + { + "codes": 2552, + "names": "pF[3]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 4 (30-60 cm)" + }, + { + "codes": 2553, + "names": "pF[4]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 5 (60-90 cm)" + }, + { + "codes": 2554, + "names": "pF[5]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 6 (90-120 cm)" + }, + { + "codes": 2555, + "names": "pF[6]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 7 (120-150 cm)" + }, + { + "codes": 2556, + "names": "pF[7]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 8 (150-200 cm)" + }, + { + "codes": 2557, + "names": "pF[8]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 9 (200-400 cm)" + }, + { + "codes": 2558, + "names": "pF[9]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2559, + "names": "hydr_conductSTART[0]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2560, + "names": "hydr_conductSTART[1]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2561, + "names": "hydr_conductSTART[2]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2562, + "names": "hydr_conductSTART[3]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2563, + "names": "hydr_conductSTART[4]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2564, + "names": "hydr_conductSTART[5]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2565, + "names": "hydr_conductSTART[6]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2566, + "names": "hydr_conductSTART[7]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2567, + "names": "hydr_conductSTART[8]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2568, + "names": "hydr_conductSTART[9]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2569, + "names": "hydr_diffusSTART[0]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2570, + "names": "hydr_diffusSTART[1]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2571, + "names": "hydr_diffusSTART[2]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2572, + "names": "hydr_diffusSTART[3]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2573, + "names": "hydr_diffusSTART[4]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2574, + "names": "hydr_diffusSTART[5]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2575, + "names": "hydr_diffusSTART[6]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2576, + "names": "hydr_diffusSTART[7]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2577, + "names": "hydr_diffusSTART[8]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2578, + "names": "hydr_diffusSTART[9]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2579, + "names": "hydr_conductEND[0]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2580, + "names": "hydr_conductEND[1]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2581, + "names": "hydr_conductEND[2]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2582, + "names": "hydr_conductEND[3]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2583, + "names": "hydr_conductEND[4]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2584, + "names": "hydr_conductEND[5]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2585, + "names": "rootdepth5", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2586, + "names": "hydr_conductEND[7]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2587, + "names": "hydr_conductEND[8]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2588, + "names": "hydr_conductEND[9]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2589, + "names": "hydr_diffusEND[0]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2590, + "names": "hydr_diffusEND[1]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2591, + "names": "hydr_diffusEND[2]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2592, + "names": "hydr_diffusEND[3]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2593, + "names": "hydr_diffusEND[4]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2594, + "names": "hydr_diffusEND[5]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2595, + "names": "hydr_diffusEND[6]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2596, + "names": "hydr_diffusEND[7]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2597, + "names": "hydr_diffusEND[8]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2598, + "names": "hydr_diffusEND[9]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2599, + "names": "vwcSAT_RZ", + "units": "m3 m-3", + "descriptions": "Average value of VWC saturation (max.soil.depth)" + }, + { + "codes": 2600, + "names": "vwcFC_RZ", + "units": "m3 m-3", + "descriptions": "Average value of VWC field capacity (max.soil.depth)" + }, + { + "codes": 2601, + "names": "vwcWP_RZ", + "units": "m3 m-3", + "descriptions": "Average value of VWC wilting point (max.soil.depth)" + }, + { + "codes": 2602, + "names": "vwcHW_RZ", + "units": "m3 m-3", + "descriptions": "Average value of hygroscopic VWC (max.soil.depth)" + }, + { + "codes": 2603, + "names": "vwc[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 1 (0-3 cm)" + }, + { + "codes": 2604, + "names": "vwc[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 2 (3-10 cm)" + }, + { + "codes": 2605, + "names": "vwc[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 3 (10-30 cm)" + }, + { + "codes": 2606, + "names": "vwc[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 4 (30-60 cm)" + }, + { + "codes": 2607, + "names": "vwc[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 5 (60-90 cm)" + }, + { + "codes": 2608, + "names": "vwc[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 6 (90-120 cm)" + }, + { + "codes": 2609, + "names": "vwc[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 7 (120-150 cm)" + }, + { + "codes": 2610, + "names": "vwc[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 8 (150-200 cm)" + }, + { + "codes": 2611, + "names": "vwc[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 9 (200-400 cm)" + }, + { + "codes": 2612, + "names": "vwc[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2613, + "names": "vwc_crit1[0]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 1 (0-3 cm)" + }, + { + "codes": 2614, + "names": "vwc_crit1[1]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 2 (3-10 cm)" + }, + { + "codes": 2615, + "names": "vwc_crit1[2]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 3 (10-30 cm)" + }, + { + "codes": 2616, + "names": "vwc_crit1[3]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 4 (30-60 cm)" + }, + { + "codes": 2617, + "names": "vwc_crit1[4]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 5 (60-90 cm)" + }, + { + "codes": 2618, + "names": "vwc_crit1[5]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 6 (90-120 cm)" + }, + { + "codes": 2619, + "names": "vwc_crit1[6]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 7 (120-150 cm)" + }, + { + "codes": 2620, + "names": "vwc_crit1[7]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 8 (150-200 cm)" + }, + { + "codes": 2621, + "names": "vwc_crit1[8]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 9 (200-400 cm)" + }, + { + "codes": 2622, + "names": "vwc_crit1[9]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2623, + "names": "vwc_crit2[0]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 1 (0-3 cm)" + }, + { + "codes": 2624, + "names": "vwc_crit2[1]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 2 (3-10 cm)" + }, + { + "codes": 2625, + "names": "vwc_crit2[2]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 3 (10-30 cm)" + }, + { + "codes": 2626, + "names": "vwc_crit2[3]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 4 (30-60 cm)" + }, + { + "codes": 2627, + "names": "vwc_crit2[4]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 5 (60-90 cm)" + }, + { + "codes": 2628, + "names": "vwc_crit2[5]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 6 (90-120 cm)" + }, + { + "codes": 2629, + "names": "vwc_crit2[6]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 7 (120-150 cm)" + }, + { + "codes": 2630, + "names": "vwc_crit2[7]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 8 (150-200 cm)" + }, + { + "codes": 2631, + "names": "vwc_crit2[8]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 9 (200-400 cm)" + }, + { + "codes": 2632, + "names": "vwc_crit2[9]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2633, + "names": "vwc_avg", + "units": "m3 m-3", + "descriptions": "Average volumetric water content in active layers" + }, + { + "codes": 2634, + "names": "vwc_RZ", + "units": "m3 m-3", + "descriptions": "Average volumetric water content in rootzone (max.soil.depth)" + }, + { + "codes": 2635, + "names": "psi_RZ", + "units": "MPa", + "descriptions": "Average water potential of soil and leaves" + }, + { + "codes": 2636, + "names": "rootdepth", + "units": "m", + "descriptions": "Actual depth of the rooting zone" + }, + { + "codes": 2637, + "names": "dlmr_area_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit leaf MR" + }, + { + "codes": 2638, + "names": "dlmr_area_shade", + "units": "umol/m2/s", + "descriptions": "Shaded leaf MR" + }, + { + "codes": 2639, + "names": "gl_t_wv_sun", + "units": "m s-1", + "descriptions": "Sunlit leaf-scale conductance to transpired water" + }, + { + "codes": 2640, + "names": "gl_t_wv_shade", + "units": "m s-1", + "descriptions": "Shaded leaf-scale conductance to transpired water" + }, + { + "codes": 2641, + "names": "assim_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit assimilation per unit pleaf area index" + }, + { + "codes": 2642, + "names": "assim_shade", + "units": "umol/m2/s", + "descriptions": "Shaded assimilation per unit pleaf area index" + }, + { + "codes": 2643, + "names": "t_scalar[0]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2644, + "names": "t_scalar[1]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2645, + "names": "t_scalar[2]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2646, + "names": "t_scalar[3]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2647, + "names": "t_scalar[4]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2648, + "names": "t_scalar[5]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2649, + "names": "t_scalar[6]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2650, + "names": "t_scalar[7]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2651, + "names": "t_scalar[8]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2652, + "names": "t_scalar[9]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2653, + "names": "w_scalar[0]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2654, + "names": "w_scalar[1]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2655, + "names": "w_scalar[2]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2656, + "names": "w_scalar[3]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2657, + "names": "w_scalar[4]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2658, + "names": "w_scalar[5]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2659, + "names": "w_scalar[6]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2660, + "names": "w_scalar[7]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2661, + "names": "w_scalar[8]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2662, + "names": "w_scalar[9]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2663, + "names": "rate_scalar[0]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2664, + "names": "rate_scalar[1]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2665, + "names": "rate_scalar[2]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2666, + "names": "rate_scalar[3]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2667, + "names": "rate_scalar[4]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2668, + "names": "rate_scalar[5]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2669, + "names": "rate_scalar[6]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2670, + "names": "rate_scalar[7]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2671, + "names": "rate_scalar[8]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2672, + "names": "rate_scalar[9]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2673, + "names": "rate_scalar_avg", + "units": "dimless", + "descriptions": "Decomposition combined and averaged scalar" + }, + { + "codes": 2674, + "names": "annmax_rootDepth", + "units": "m", + "descriptions": "Year-to-date maximum rooting depth" + }, + { + "codes": 2675, + "names": "annmax_plantHeight", + "units": "m", + "descriptions": "Year-to-date maximum plant height" + }, + { + "codes": 2676, + "names": "grossMINER[0]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2677, + "names": "grossMINER[1]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2678, + "names": "grossMINER[2]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2679, + "names": "grossMINER[3]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2680, + "names": "grossMINER[4]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2681, + "names": "grossMINER[5]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2682, + "names": "grossMINER[6]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2683, + "names": "grossMINER[7]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2684, + "names": "potIMMOB[0]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2685, + "names": "potIMMOB[1]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2686, + "names": "potIMMOB[2]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2687, + "names": "potIMMOB[3]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2688, + "names": "potIMMOB[4]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2689, + "names": "potIMMOB[5]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2690, + "names": "potIMMOB[6]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2691, + "names": "potIMMOB[7]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2692, + "names": "netMINER[0]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2693, + "names": "netMINER[1]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2694, + "names": "netMINER[2]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2695, + "names": "netMINER[3]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2696, + "names": "netMINER[4]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2697, + "names": "netMINER[5]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2698, + "names": "netMINER[6]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2699, + "names": "netMINER[7]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2700, + "names": "grossMINER_tot", + "units": "kgN/m2/day", + "descriptions": "Total gross N mineralization" + }, + { + "codes": 2701, + "names": "potIMMOB_total", + "units": "kgN/m2/day", + "descriptions": "Total potential N immobilization" + }, + { + "codes": 2702, + "names": "netMINER_total", + "units": "kgN/m2/day", + "descriptions": "Total net N mineralization" + }, + { + "codes": 2703, + "names": "actIMMOB_total", + "units": "kgN/m2/day", + "descriptions": "Total actual N immobilization" + }, + { + "codes": 2704, + "names": "stomaCONDUCT_max", + "units": "m/s", + "descriptions": "Maximal stomatal conductance with temperature-pressure correction" + }, + { + "codes": 2705, + "names": "m_tmin", + "units": "dimless", + "descriptions": "Freezing night temperature multiplier" + }, + { + "codes": 2706, + "names": "m_SWCstress_layer[0]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 1 (0-3 cm)" + }, + { + "codes": 2707, + "names": "m_SWCstress_layer[1]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 2 (3-10 cm)" + }, + { + "codes": 2708, + "names": "m_SWCstress_layer[2]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 3 (10-30 cm)" + }, + { + "codes": 2709, + "names": "m_SWCstress_layer[3]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 4 (30-60 cm)" + }, + { + "codes": 2710, + "names": "m_SWCstress_layer[4]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 5 (60-90 cm)" + }, + { + "codes": 2711, + "names": "m_SWCstress_layer[5]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 6 (90-120 cm)" + }, + { + "codes": 2712, + "names": "m_SWCstress_layer[6]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 7 (120-150 cm)" + }, + { + "codes": 2713, + "names": "m_SWCstress_layer[7]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 8 (150-200 cm)" + }, + { + "codes": 2714, + "names": "m_SWCstress_layer[8]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 9 (200-400 cm)" + }, + { + "codes": 2715, + "names": "m_SWCstress_layer[9]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2716, + "names": "m_SWCstress", + "units": "dimless", + "descriptions": "Soil water properties multiplier" + }, + { + "codes": 2717, + "names": "m_ppfd_sun", + "units": "dimless", + "descriptions": "Sunlit PAR flux density multiplier" + }, + { + "codes": 2718, + "names": "m_ppfd_shade", + "units": "dimless", + "descriptions": "Sunshade PAR flux density multiplier" + }, + { + "codes": 2719, + "names": "m_vpd", + "units": "dimless", + "descriptions": "Vapor pressure deficit multiplier" + }, + { + "codes": 2720, + "names": "m_final_sun", + "units": "dimless", + "descriptions": "Sunlit product of all other multipliers" + }, + { + "codes": 2721, + "names": "m_final_shade", + "units": "dimless", + "descriptions": "Sunshade product of all other multipliers" + }, + { + "codes": 2722, + "names": "m_SWCstressLENGTH", + "units": "dimless", + "descriptions": "Soil water stress length multiplier" + }, + { + "codes": 2723, + "names": "m_extremT", + "units": "dimless", + "descriptions": "Extrem temperature multiplier" + }, + { + "codes": 2724, + "names": "SMSI", + "units": "prop", + "descriptions": "Soil moisture stress index" + }, + { + "codes": 2725, + "names": "gcorr", + "units": "dimless", + "descriptions": "Temperature and pressure correction factor for conductances" + }, + { + "codes": 2726, + "names": "gl_bl", + "units": "ms-1", + "descriptions": "Leaf boundary layer conductance" + }, + { + "codes": 2727, + "names": "gl_c", + "units": "ms-1", + "descriptions": "Leaf cuticular conductance" + }, + { + "codes": 2728, + "names": "gl_s_sun", + "units": "ms-1", + "descriptions": "Sunlit leaf-scale stomatal conductance" + }, + { + "codes": 2729, + "names": "gl_s_shade", + "units": "ms-1", + "descriptions": "Sunshade leaf-scale stomatal conductance" + }, + { + "codes": 2730, + "names": "gl_e_wv", + "units": "ms-1", + "descriptions": "Leaf conductance to evaporated water" + }, + { + "codes": 2731, + "names": "gl_sh", + "units": "ms-1", + "descriptions": "Leaf conductance to sensible heat" + }, + { + "codes": 2732, + "names": "gc_e_wv", + "units": "ms-1", + "descriptions": "Canopy conductance to evaporated water" + }, + { + "codes": 2733, + "names": "gc_sh", + "units": "ms-1", + "descriptions": "Canopy conductance to sensible heat" + }, + { + "codes": 2734, + "names": "annmax_lai", + "units": "m^{2 m-2", + "descriptions": "Year-to-date maximum projected leaf area index" + }, + { + "codes": 2735, + "names": "IMMOBratio[0]", + "units": "dimless", + "descriptions": "Immobilization ratio (act:pot) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2736, + "names": "IMMOBratio[1]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 2 (3-10 cm)" + }, + { + "codes": 2737, + "names": "IMMOBratio[2]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 3 (10-30 cm)" + }, + { + "codes": 2738, + "names": "IMMOBratio[3]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 4 (30-60 cm)" + }, + { + "codes": 2739, + "names": "IMMOBratio[4]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 5 (60-90 cm)" + }, + { + "codes": 2740, + "names": "IMMOBratio[5]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 6 (90-120 cm)" + }, + { + "codes": 2741, + "names": "IMMOBratio[6]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 7 (120-150 cm)" + }, + { + "codes": 2742, + "names": "IMMOBratio[7]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 8 (150-200 cm)" + }, + { + "codes": 2743, + "names": "IMMOBratio[8]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 9 (200-400 cm)" + }, + { + "codes": 2744, + "names": "IMMOBratio[9]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 9 (400-1000 cm)" + }, + { + "codes": 2745, + "names": "plant_calloc", + "units": "kgC m-2", + "descriptions": "Amount of allocated C" + }, + { + "codes": 2746, + "names": "plant_nalloc", + "units": "kgN m-2", + "descriptions": "Amount of allocated N" + }, + { + "codes": 2747, + "names": "excess_c", + "units": "kgC m-2", + "descriptions": "Difference between available and allocated carbon" + }, + { + "codes": 2748, + "names": "pnow", + "units": "prop", + "descriptions": "Proportion of growth displayed on current day" + }, + { + "codes": 2749, + "names": "NSC_limit_nw", + "units": "flag", + "descriptions": "For NSC-limitation in maint.resp.calculation for nw-biomass" + }, + { + "codes": 2750, + "names": "NSC_limit_w", + "units": "flag", + "descriptions": "For NSC-limitation in maint.resp.calculation for w-biomass" + }, + { + "codes": 2751, + "names": "plantNdemand", + "units": "kgN m-2", + "descriptions": "Plant N demand" + }, + { + "codes": 2752, + "names": "assim_Tcoeff", + "units": "dimless", + "descriptions": "Maximum temperature limitation factor of photosynthesis" + }, + { + "codes": 2753, + "names": "assim_SScoeff", + "units": "dimless", + "descriptions": "Soil moisture stress limitation factor of photosynthesis" + }, + { + "codes": 2754, + "names": "cumNstress", + "units": "dimless", + "descriptions": "Cumulative soil N stress" + }, + { + "codes": 2755, + "names": "SWCstressLENGTH", + "units": "dimless", + "descriptions": "Limitiation factor of SWC-stress length" + }, + { + "codes": 2756, + "names": "WFPS[1]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 1 (0-3 cm)" + }, + { + "codes": 2757, + "names": "WFPS[1]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 2 (3-10 cm)" + }, + { + "codes": 2758, + "names": "WFPS[2]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 3 (10-30 cm)" + }, + { + "codes": 2759, + "names": "WFPS[3]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 4 (30-60 cm)" + }, + { + "codes": 2760, + "names": "WFPS[4]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 5 (60-90 cm)" + }, + { + "codes": 2761, + "names": "WFPS[5]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 6 (90-120 cm)" + }, + { + "codes": 2762, + "names": "WFPS[6]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 7 (120-150 cm)" + }, + { + "codes": 2763, + "names": "WFPS[7]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 8 (150-200 cm)" + }, + { + "codes": 2764, + "names": "WFPS[8]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 9 (200-400 cm)" + }, + { + "codes": 2765, + "names": "WFPS[9]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 10 (400-1000 cm)" + }, + { + "codes": 2766, + "names": "wfps_scalar[1]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 2 (0-3 cm)" + }, + { + "codes": 2767, + "names": "wfps_scalar[1]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2768, + "names": "wfps_scalar[2]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2769, + "names": "wfps_scalar[3]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2770, + "names": "wfps_scalar[4]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2771, + "names": "wfps_scalar[5]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2772, + "names": "wfps_scalar[6]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2773, + "names": "wfps_scalar[7]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2774, + "names": "wfps_scalar[8]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2775, + "names": "wfps_scalar[9]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2776, + "names": "wfps_scalar[10]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2777, + "names": "pH_scalar[1]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2778, + "names": "pH_scalar[2]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2779, + "names": "pH_scalar[3]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2780, + "names": "pH_scalar[4]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2781, + "names": "pH_scalar[5]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2782, + "names": "pH_scalar[6]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2783, + "names": "pH_scalar[7]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2784, + "names": "pH_scalar[8]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2785, + "names": "pH_scalar[9]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2786, + "names": "phenphase_date[0]", + "units": "dimless", + "descriptions": "First day of the phenphase1" + }, + { + "codes": 2787, + "names": "phenphase_date[1]", + "units": "dimless", + "descriptions": "First day of the phenphase2" + }, + { + "codes": 2788, + "names": "phenphase_date[2]", + "units": "dimless", + "descriptions": "First day of the phenphase3" + }, + { + "codes": 2789, + "names": "phenphase_date[3]", + "units": "dimless", + "descriptions": "First day of the phenphase4" + }, + { + "codes": 2790, + "names": "phenphase_date[4]", + "units": "dimless", + "descriptions": "First day of the phenphase5" + }, + { + "codes": 2791, + "names": "phenphase_date[5]", + "units": "dimless", + "descriptions": "First day of the phenphase6" + }, + { + "codes": 2792, + "names": "phenphase_date[6]", + "units": "dimless", + "descriptions": "First day of the phenphase7" + }, + { + "codes": 2793, + "names": "wpm_act", + "units": "dimless", + "descriptions": "Whole plant mortality value on actual day" + }, + { + "codes": 2794, + "names": "flower_date", + "units": "day of year", + "descriptions": "Start of flowering phenophase" + }, + { + "codes": 2795, + "names": "mulch_coverage", + "units": "%", + "descriptions": "Percent of mulch coverage" + }, + { + "codes": 2796, + "names": "evapREDmulch", + "units": "prop", + "descriptions": "Evaporation reduction of mulch" + }, + { + "codes": 2800, + "names": "RCN", + "units": "dimless", + "descriptions": "Runoff curve number" + }, + { + "codes": 2801, + "names": "soil_b[0]", + "units": "dimless", + "descriptions": "Clapp-Hornberger parameter in soil layer 1 (0-3 cm)" + }, + { + "codes": 2802, + "names": "soil_b[1]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 2 (3-10 cm)" + }, + { + "codes": 2803, + "names": "soil_b[2]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 3 (10-30 cm)" + }, + { + "codes": 2804, + "names": "soil_b[3]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 4 (30-60 cm)" + }, + { + "codes": 2805, + "names": "soil_b[4]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 5 (60-90 cm)" + }, + { + "codes": 2806, + "names": "soil_b[5]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 6 (90-120 cm)" + }, + { + "codes": 2807, + "names": "soil_b[6]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 7 (120-150 cm)" + }, + { + "codes": 2808, + "names": "soil_b[7]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 8 (150-200 cm)" + }, + { + "codes": 2809, + "names": "soil_b[8]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 9 (200-400 cm)" + }, + { + "codes": 2810, + "names": "soil_b[9]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2811, + "names": "BD[0]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 1 (0-3 cm)" + }, + { + "codes": 2812, + "names": "BD[1]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 2 (3-10 cm)" + }, + { + "codes": 2813, + "names": "BD[2]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 3 (10-30 cm)" + }, + { + "codes": 2814, + "names": "BD[3]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 4 (30-60 cm)" + }, + { + "codes": 2815, + "names": "BD[4]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 5 (60-90 cm)" + }, + { + "codes": 2816, + "names": "BD[5]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 6 (90-120 cm)" + }, + { + "codes": 2817, + "names": "BD[6]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 7 (120-150 cm)" + }, + { + "codes": 2818, + "names": "BD[7]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 8 (150-200 cm)" + }, + { + "codes": 2819, + "names": "BD[8]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 9 (200-400 cm)" + }, + { + "codes": 2820, + "names": "BD[9]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2821, + "names": "vwc_sat[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2822, + "names": "vwc_sat[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2823, + "names": "vwc_sat[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2824, + "names": "vwc_sat[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2825, + "names": "vwc_sat[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2826, + "names": "vwc_sat[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2827, + "names": "vwc_sat[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2828, + "names": "vwc_sat[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2829, + "names": "vwc_sat[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2830, + "names": "vwc_sat[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2831, + "names": "vwc_fc[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2832, + "names": "vwc_fc[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2833, + "names": "vwc_fc[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2834, + "names": "vwc_fc[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2835, + "names": "vwc_fc[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2836, + "names": "vwc_fc[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2837, + "names": "vwc_fc[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2838, + "names": "vwc_fc[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2839, + "names": "vwc_fc[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2840, + "names": "vwc_fc[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2841, + "names": "vwc_wp[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 1 (0-3 cm)" + }, + { + "codes": 2842, + "names": "vwc_wp[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 2 (3-10 cm)" + }, + { + "codes": 2843, + "names": "vwc_wp[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 3 (10-30 cm)" + }, + { + "codes": 2844, + "names": "vwc_wp[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 4 (30-60 cm)" + }, + { + "codes": 2845, + "names": "vwc_wp[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 5 (60-90 cm)" + }, + { + "codes": 2846, + "names": "vwc_wp[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 6 (90-120 cm)" + }, + { + "codes": 2847, + "names": "vwc_wp[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 7 (120-150 cm)" + }, + { + "codes": 2848, + "names": "vwc_wp[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 8 (150-200 cm)" + }, + { + "codes": 2849, + "names": "vwc_wp[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 9 (200-400 cm)" + }, + { + "codes": 2850, + "names": "vwc_wp[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2851, + "names": "vwc_hw[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 1 (0-3 cm)" + }, + { + "codes": 2852, + "names": "vwc_hw[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 2 (3-10 cm)" + }, + { + "codes": 2853, + "names": "vwc_hw[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 3 (10-30 cm)" + }, + { + "codes": 2854, + "names": "vwc_hw[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 4 (30-60 cm)" + }, + { + "codes": 2855, + "names": "vwc_hw[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 5 (60-90 cm)" + }, + { + "codes": 2856, + "names": "vwc_hw[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 6 (90-120 cm)" + }, + { + "codes": 2857, + "names": "vwc_hw[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 7 (120-150 cm)" + }, + { + "codes": 2858, + "names": "vwc_hw[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 8 (150-200 cm)" + }, + { + "codes": 2859, + "names": "vwc_hw[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 9 (200-400 cm)" + }, + { + "codes": 2860, + "names": "vwc_hw[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2861, + "names": "psi_sat[0]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2862, + "names": "psi_sat[1]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2863, + "names": "psi_sat[2]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2864, + "names": "psi_sat[3]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2865, + "names": "psi_sat[4]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2866, + "names": "psi_sat[5]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2867, + "names": "psi_sat[6]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2868, + "names": "psi_sat[7]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2869, + "names": "psi_sat[8]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2870, + "names": "psi_sat[9]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2871, + "names": "psi_fc[0]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2872, + "names": "psi_fc[1]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2873, + "names": "psi_fc[2]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2874, + "names": "psi_fc[3]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2875, + "names": "psi_fc[4]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2876, + "names": "psi_fc[5]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2877, + "names": "psi_fc[6]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2878, + "names": "psi_fc[7]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2879, + "names": "psi_fc[8]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2880, + "names": "psi_fc[9]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2881, + "names": "psi_wp[0]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 1 (0-3 cm)" + }, + { + "codes": 2882, + "names": "psi_wp[1]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 2 (3-10 cm)" + }, + { + "codes": 2883, + "names": "psi_wp[2]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 3 (10-30 cm)" + }, + { + "codes": 2884, + "names": "psi_wp[3]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 4 (30-60 cm)" + }, + { + "codes": 2885, + "names": "psi_wp[4]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 5 (60-90 cm)" + }, + { + "codes": 2886, + "names": "psi_wp[5]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 6 (90-120 cm)" + }, + { + "codes": 2887, + "names": "psi_wp[6]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 7 (120-150 cm)" + }, + { + "codes": 2888, + "names": "psi_wp[7]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 8 (150-200 cm)" + }, + { + "codes": 2889, + "names": "psi_wp[8]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 9 (200-400 cm)" + }, + { + "codes": 2890, + "names": "psi_wp[9]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2891, + "names": "hydr_conduct_sat[0]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2892, + "names": "hydr_conduct_sat[1]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2893, + "names": "hydr_conduct_sat[2]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2894, + "names": "hydr_conduct_sat[3]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2895, + "names": "hydr_conduct_sat[4]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2896, + "names": "hydr_conduct_sat[5]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2897, + "names": "hydr_conduct_sat[6]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2898, + "names": "hydr_conduct_sat[7]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2899, + "names": "hydr_conduct_sat[8]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2900, + "names": "hydr_conduct_sat[9]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2901, + "names": "hydr_diffus_sat[0]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2902, + "names": "hydr_diffus_sat[1]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2903, + "names": "hydr_diffus_sat[2]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2904, + "names": "hydr_diffus_sat[3]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2905, + "names": "hydr_diffus_sat[4]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2906, + "names": "hydr_diffus_sat[5]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2907, + "names": "hydr_diffus_sat[6]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2908, + "names": "hydr_diffus_sat[7]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2909, + "names": "hydr_diffus_sat[8]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2910, + "names": "hydr_diffus_sat[9]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2911, + "names": "hydr_conduct_fc[0]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2912, + "names": "hydr_conduct_fc[1]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2913, + "names": "hydr_conduct_fc[2]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2914, + "names": "hydr_conduct_fc[3]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2915, + "names": "hydr_conduct_fc[4]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2916, + "names": "hydr_conduct_fc[5]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2917, + "names": "hydr_conduct_fc[6]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2918, + "names": "hydr_conduct_fc[7]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2919, + "names": "hydr_conduct_fc[8]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2920, + "names": "hydr_conduct_fc[9]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2921, + "names": "hydr_diffus_fc[0]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2922, + "names": "hydr_diffus_fc[1]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2923, + "names": "hydr_diffus_fc[2]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2924, + "names": "hydr_diffus_fc[3]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2925, + "names": "hydr_diffus_fc[4]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2926, + "names": "hydr_diffus_fc[5]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2927, + "names": "hydr_diffus_fc[6]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2928, + "names": "hydr_diffus_fc[7]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2929, + "names": "hydr_diffus_fc[8]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2930, + "names": "hydr_diffus_fc[9]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2950, + "names": "pa_sun", + "units": "Pa", + "descriptions": "Sunlit atmospheric pressure" + }, + { + "codes": 2951, + "names": "pa_shade", + "units": "Pa", + "descriptions": "Sunshade atmospheric pressure" + }, + { + "codes": 2952, + "names": "co2_sun", + "units": "ppm", + "descriptions": "Sunlit atmospheric CO2 conc." + }, + { + "codes": 2953, + "names": "co2_shade", + "units": "ppm", + "descriptions": "Sunshade atmospheric CO2 conc." + }, + { + "codes": 2954, + "names": "t_sun", + "units": "degree(Celsius)", + "descriptions": "Sunlit temperature" + }, + { + "codes": 2955, + "names": "t_shade", + "units": "degree(Celsius)", + "descriptions": "Sunshade temperature" + }, + { + "codes": 2956, + "names": "lnc_sun", + "units": "kgN/(leaf)m2", + "descriptions": "Leaf N per unit sunlit leaf area" + }, + { + "codes": 2957, + "names": "lnc_shade", + "units": "kgN/(leaf)m2", + "descriptions": "Leaf N per unit sunshade area" + }, + { + "codes": 2958, + "names": "flnr_sun", + "units": "kgN Rubisco/kgN (leaf)", + "descriptions": "Sunlit fraction of leaf N in Rubisco" + }, + { + "codes": 2959, + "names": "flnr_shade", + "units": "kgN Rubisco/kgN (leaf)", + "descriptions": "Sunshade fraction of leaf N in Rubisco" + }, + { + "codes": 2960, + "names": "flnp_sun", + "units": "kgN PEP/kgN (leaf)", + "descriptions": "Sunlit fraction of leaf N in PEP Carboxylase" + }, + { + "codes": 2961, + "names": "flnp_shade", + "units": "kgN PEP/kgN (leaf)", + "descriptions": "Sunshade fraction of leaf N in PEP Carboxylase" + }, + { + "codes": 2962, + "names": "ppfd_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit PAR flux per unit sunlit leaf area" + }, + { + "codes": 2963, + "names": "ppfd_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade PAR flux per unit sunlit leaf area" + }, + { + "codes": 2964, + "names": "g_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit conductance to CO2" + }, + { + "codes": 2965, + "names": "g_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade conductance to CO2" + }, + { + "codes": 2966, + "names": "dlmr_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit day leaf maintenance respiration" + }, + { + "codes": 2967, + "names": "dlmr_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade day leaf maintenance respiration" + }, + { + "codes": 2968, + "names": "Ci_sun", + "units": "Pa", + "descriptions": "Sunlit intercellular CO2 concentration" + }, + { + "codes": 2969, + "names": "Ci_shade", + "units": "Pa", + "descriptions": "Sunshade intercellular CO2 concentration" + }, + { + "codes": 2970, + "names": "O2_sun", + "units": "Pa", + "descriptions": "Sunlit atmospheric O2 concentration" + }, + { + "codes": 2971, + "names": "O2_shade", + "units": "Pa", + "descriptions": "Sunshade atmospheric O2 concentration" + }, + { + "codes": 2972, + "names": "Ca_sun", + "units": "Pa", + "descriptions": "Sunlit atmospheric CO2 concentration" + }, + { + "codes": 2973, + "names": "Ca_shade", + "units": "Pa", + "descriptions": "Sunshade atmospheric CO2 concentration" + }, + { + "codes": 2974, + "names": "gamma_sun", + "units": "Pa", + "descriptions": "Sunlit CO2 compensation point" + }, + { + "codes": 2975, + "names": "gamma_shade", + "units": "Pa", + "descriptions": "Sunshade CO2 compensation point" + }, + { + "codes": 2976, + "names": "Kc_sun", + "units": "Pa", + "descriptions": "Sunlit MM constant carboxylation" + }, + { + "codes": 2977, + "names": "Kc_shade", + "units": "Pa", + "descriptions": "Sunshade MM constant carboxylation" + }, + { + "codes": 2978, + "names": "Ko_sun", + "units": "Pa", + "descriptions": "Sunlit MM constant oxygenation" + }, + { + "codes": 2979, + "names": "Ko_shade", + "units": "Pa", + "descriptions": "Sunshade MM constant oxygenation" + }, + { + "codes": 2980, + "names": "Vmax_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit max. rate of carboxylation" + }, + { + "codes": 2981, + "names": "Vmax_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade max. rate of carboxylation" + }, + { + "codes": 2982, + "names": "Jmax_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit max. rate of electron transport" + }, + { + "codes": 2983, + "names": "Jmax_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade max. rate of electron transport" + }, + { + "codes": 2984, + "names": "J_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit rate of RuBP regeneration" + }, + { + "codes": 2985, + "names": "J_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade rate of RuBP regeneration" + }, + { + "codes": 2986, + "names": "Av_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit carboxylation limited assimilation" + }, + { + "codes": 2987, + "names": "Av_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade carboxylation limited assimilation" + }, + { + "codes": 2988, + "names": "Aj_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit RuBP regeneration limited assimilation" + }, + { + "codes": 2989, + "names": "Aj_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade RuBP regeneration limited assimilation" + }, + { + "codes": 2990, + "names": "A_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit final assimilation rate" + }, + { + "codes": 2991, + "names": "A_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade final assimilation rate" + }, + { + "codes": 3000, + "names": "annprcp", + "units": "mm year-1", + "descriptions": "Annual precipitation" + }, + { + "codes": 3001, + "names": "anntavg", + "units": "degree", + "descriptions": "Annual average air temperature" + }, + { + "codes": 3002, + "names": "cum_runoff", + "units": "kgH2O m-2 year-1", + "descriptions": "Cumulated SUM of runoff" + }, + { + "codes": 3003, + "names": "cum_WleachRZ", + "units": "kgH2O m-2 year-1", + "descriptions": "Cumulated SUM of water leaching from rootzone" + }, + { + "codes": 3004, + "names": "daily_n2o", + "units": "kgN m-2 day-1", + "descriptions": "Daily N2O flux" + }, + { + "codes": 3005, + "names": "daily_nep", + "units": "kgC m-2 day-1", + "descriptions": "Net ecosystem production" + }, + { + "codes": 3006, + "names": "daily_npp", + "units": "kgC m-2 day-1", + "descriptions": "Net primary production" + }, + { + "codes": 3007, + "names": "daily_nee", + "units": "kgC m-2 day-1", + "descriptions": "Net ecosystem exchange" + }, + { + "codes": 3008, + "names": "daily_nbp", + "units": "kgC m-2 day-1", + "descriptions": "Net biom production" + }, + { + "codes": 3009, + "names": "daily_gpp", + "units": "kgC m-2 day-1", + "descriptions": "Gross primary production" + }, + { + "codes": 3010, + "names": "daily_mr", + "units": "kgC m-2 day-1", + "descriptions": "Maintenance respiration" + }, + { + "codes": 3011, + "names": "daily_gr", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration" + }, + { + "codes": 3012, + "names": "daily_hr", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration" + }, + { + "codes": 3013, + "names": "daily_sr", + "units": "kgC m-2 day-1", + "descriptions": "Soil respiration" + }, + { + "codes": 3014, + "names": "daily_tr", + "units": "kgC m-2 day-1", + "descriptions": "Total respiration" + }, + { + "codes": 3015, + "names": "daily_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fire losses" + }, + { + "codes": 3016, + "names": "daily_litfallc", + "units": "kgC m-2 day-1", + "descriptions": "Total litterfall" + }, + { + "codes": 3017, + "names": "daily_litfallc_above", + "units": "kgC m-2 day-1", + "descriptions": "Total litterfall aboveground" + }, + { + "codes": 3018, + "names": "daily_litfallc_below", + "units": "kgC m-2 day-1", + "descriptions": "Total litterfall belowground" + }, + { + "codes": 3019, + "names": "daily_litdecomp", + "units": "kgC m-2 day-1", + "descriptions": "Total litter decomposition" + }, + { + "codes": 3020, + "names": "daily_litfire", + "units": "kgC m-2 day-1", + "descriptions": "Total litter fire mortality" + }, + { + "codes": 3021, + "names": "daily_litter", + "units": "kgC m-2", + "descriptions": "Total amount of litter" + }, + { + "codes": 3022, + "names": "cum_npp", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NPP" + }, + { + "codes": 3023, + "names": "cum_nep", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NEP" + }, + { + "codes": 3024, + "names": "cum_nee", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NEE" + }, + { + "codes": 3025, + "names": "cum_gpp", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of GPP" + }, + { + "codes": 3026, + "names": "cum_mr", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of MR" + }, + { + "codes": 3027, + "names": "cum_gr", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of GR" + }, + { + "codes": 3028, + "names": "cum_hr", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of HR" + }, + { + "codes": 3029, + "names": "cum_tr", + "units": "kgC m-2", + "descriptions": "Cumulative SUM of total ecosystem respiration" + }, + { + "codes": 3030, + "names": "cum_n2o", + "units": "kgN m-2", + "descriptions": "Cumulative annual SUM N2O flux" + }, + { + "codes": 3031, + "names": "cum_Closs_MGM", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of management C loss" + }, + { + "codes": 3032, + "names": "cum_Cplus_MGM", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of management C plus" + }, + { + "codes": 3033, + "names": "cum_Closs_THN_w", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of thinning woody C loss" + }, + { + "codes": 3034, + "names": "cum_Closs_THN_nw", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of thinning non-woody C loss" + }, + { + "codes": 3035, + "names": "cum_Closs_MOW", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of mowing C loss" + }, + { + "codes": 3036, + "names": "cum_Closs_HRV", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of harvesting C loss" + }, + { + "codes": 3037, + "names": "cum_yieldC_HRV", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of harvested yield" + }, + { + "codes": 3038, + "names": "cum_Closs_PLG", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of ploughing C loss" + }, + { + "codes": 3039, + "names": "cum_Closs_GRZ", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of grazing C loss" + }, + { + "codes": 3040, + "names": "cum_Cplus_GRZ", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of grazing C plus" + }, + { + "codes": 3041, + "names": "cum_Cplus_FRZ", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of fertilizing C plus" + }, + { + "codes": 3042, + "names": "cum_Cplus_PLT", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of planting C change" + }, + { + "codes": 3043, + "names": "cum_Nplus_GRZ", + "units": "kgN m-2", + "descriptions": "Cumulative annual SUM of grazing N plus" + }, + { + "codes": 3044, + "names": "cum_Nplus_FRZ", + "units": "kgN m-2", + "descriptions": "Cumulative annual SUM of fertilizing N plus" + }, + { + "codes": 3045, + "names": "cum_Closs_SNSC", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of senescence C loss" + }, + { + "codes": 3046, + "names": "cum_Cplus_STDB", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of standing dead biome C plus" + }, + { + "codes": 3047, + "names": "cum_Cplus_CTDB", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of cut-down dead biome C plus" + }, + { + "codes": 3048, + "names": "cum_evap", + "units": "kgH2O m-2", + "descriptions": "Cumulative SUM of evaporation" + }, + { + "codes": 3049, + "names": "cum_transp", + "units": "kgH2O m-2", + "descriptions": "Cumulative SUM of transpiration" + }, + { + "codes": 3050, + "names": "cum_ET", + "units": "kgH2O m-2", + "descriptions": "Cumulative SUM of evapotranspiration" + }, + { + "codes": 3051, + "names": "leaf_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of leaves" + }, + { + "codes": 3052, + "names": "leaflitr_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of leaf litter" + }, + { + "codes": 3053, + "names": "froot_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of fine roots" + }, + { + "codes": 3054, + "names": "fruit_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of fruits" + }, + { + "codes": 3055, + "names": "softstem_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of softstems" + }, + { + "codes": 3056, + "names": "livewood_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of live wood" + }, + { + "codes": 3057, + "names": "deadwood_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of dead wood" + }, + { + "codes": 3058, + "names": "vegC", + "units": "kgC m-2", + "descriptions": "Total vegetation C content" + }, + { + "codes": 3059, + "names": "litrN_total", + "units": "kgN m-2", + "descriptions": "Total litter N content" + }, + { + "codes": 3060, + "names": "litrC_total", + "units": "kgC m-2", + "descriptions": "Total litter C content" + }, + { + "codes": 3061, + "names": "soilC_total", + "units": "kgC m-2", + "descriptions": "Total soil C content" + }, + { + "codes": 3062, + "names": "soilN_total", + "units": "kgN m-2", + "descriptions": "Total soil N content" + }, + { + "codes": 3063, + "names": "sminN_total", + "units": "kgN m-2", + "descriptions": "Total soil mineralized N content" + }, + { + "codes": 3064, + "names": "totalC", + "units": "kgC m-2", + "descriptions": "Total C content" + }, + { + "codes": 3065, + "names": "stableSOC_top30", + "units": "%", + "descriptions": "C content of stable SOM in soil top 0-30 cm" + }, + { + "codes": 3066, + "names": "SOC_top30", + "units": "%", + "descriptions": "Soil organic matter C content in soil top 0-30 cm" + }, + { + "codes": 3067, + "names": "SOM_N_top30", + "units": "%", + "descriptions": "Soil organic matter N content in soil top 0-30 cm" + }, + { + "codes": 3068, + "names": "NH4_top30avail", + "units": "ppm", + "descriptions": "Available soil NH4-content in soil top 0-30 cm" + }, + { + "codes": 3069, + "names": "NO3_top30avail", + "units": "ppm", + "descriptions": "Available soil NO3-content in soil top 0-30 cm" + }, + { + "codes": 3070, + "names": "SOC_30to60", + "units": "%", + "descriptions": "Soil organic matter C content in 30-60 cm" + }, + { + "codes": 3071, + "names": "SOC_60to90", + "units": "%", + "descriptions": "Soil organic matter C content in 60-90 cm" + }, + { + "codes": 3072, + "names": "litrCwdC_total", + "units": "kgN m-2", + "descriptions": "Total Litter and cwdc carbon content" + }, + { + "codes": 3073, + "names": "litrCwdN_total", + "units": "kgC m-2", + "descriptions": "Total litter and cwdc nitrogen content" + }, + { + "codes": 3074, + "names": "sminNavail_top30", + "units": "ppm", + "descriptions": "Available mineralized N in soil top 0-30 cm" + }, + { + "codes": 3075, + "names": "leafc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead leaf C content" + }, + { + "codes": 3076, + "names": "frootc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead fine root C content" + }, + { + "codes": 3077, + "names": "fruitc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead fruit C content" + }, + { + "codes": 3078, + "names": "softstemc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead sofstem C content" + }, + { + "codes": 3079, + "names": "sminNH4_ppm[0]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 1 (0-3 cm)" + }, + { + "codes": 3080, + "names": "sminNH4_ppm[1]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 2 (3-10 cm)" + }, + { + "codes": 3081, + "names": "sminNH4_ppm[2]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 3 (10-30 cm)" + }, + { + "codes": 3082, + "names": "sminNH4_ppm[3]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 4 (30-60 cm)" + }, + { + "codes": 3083, + "names": "sminNH4_ppm[4]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 5 (60-90 cm)" + }, + { + "codes": 3084, + "names": "sminNH4_ppm[5]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 6 (90-120 cm)" + }, + { + "codes": 3085, + "names": "sminNH4_ppm[6]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 7 (120-150 cm)" + }, + { + "codes": 3086, + "names": "sminNH4_ppm[7]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 8 (150-200 cm)" + }, + { + "codes": 3087, + "names": "sminNH4_ppm[8]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 9 (200-400 cm)" + }, + { + "codes": 3088, + "names": "sminNH4_ppm[9]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 10 (400-1000 cm)" + }, + { + "codes": 3089, + "names": "sminNO3_ppm[0]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 1 (0-3 cm)" + }, + { + "codes": 3090, + "names": "sminNO3_ppm[1]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 2 (3-10 cm)" + }, + { + "codes": 3091, + "names": "sminNO3_ppm[2]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 3 (10-30 cm)" + }, + { + "codes": 3092, + "names": "sminNO3_ppm[3]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 4 (30-60 cm)" + }, + { + "codes": 3093, + "names": "sminNO3_ppm[4]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 5 (60-90 cm)" + }, + { + "codes": 3094, + "names": "sminNO3_ppm[5]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 6 (90-120 cm)" + }, + { + "codes": 3095, + "names": "sminNO3_ppm[6]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 7 (120-150 cm)" + }, + { + "codes": 3096, + "names": "sminNO3_ppm[7]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 8 (150-200 cm)" + }, + { + "codes": 3097, + "names": "sminNO3_ppm[8]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 9 (200-400 cm)" + }, + { + "codes": 3098, + "names": "sminNO3_ppm[9]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 10 (400-1000 cm)" + }, + { + "codes": 3099, + "names": "CH4_flux_TOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Estimated total CH4 flux of ecosystem" + }, + { + "codes": 3100, + "names": "daily_ngb", + "units": "kgC m-2 m-2", + "descriptions": "Net greenhouse gas balance" + }, + { + "codes": 3101, + "names": "cum_ngb", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NGB" + }, + { + "codes": 3102, + "names": "lateral_Cflux", + "units": "kgC m-2 day-1", + "descriptions": "Lateral carbon flux" + }, + { + "codes": 3103, + "names": "harvest_index", + "units": "dimless", + "descriptions": "Harvest index" + }, + { + "codes": 3104, + "names": "sminNavail_total", + "units": "kgN m-2", + "descriptions": "Total available soil mineralized N content" + }, + { + "codes": 3105, + "names": "cum_NleachRZ", + "units": "kgN m-2", + "descriptions": "Cumulated SUM of N leaching from rootzone" + }, + { + "codes": 3106, + "names": "cum_sr", + "units": "kgC m-2", + "descriptions": "Cumulated SUM of soil respiration" + }, + { + "codes": 3107, + "names": "CNlitr_total", + "units": "ppm", + "descriptions": "C:N ratio of litter pool" + }, + { + "codes": 3108, + "names": "CNsoil_total", + "units": "ppm", + "descriptions": "C:N ratio of soil pool" + }, + { + "codes": 3109, + "names": "litr1HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of labile litter in soil" + }, + { + "codes": 3110, + "names": "litr2HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of unshielded cellulose soil" + }, + { + "codes": 3111, + "names": "litr4HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil" + }, + { + "codes": 3112, + "names": "soil1HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil" + }, + { + "codes": 3113, + "names": "soil2HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil" + }, + { + "codes": 3114, + "names": "soil3HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil" + }, + { + "codes": 3115, + "names": "soil4HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil" + }, + { + "codes": 3116, + "names": "grainDM_HRV", + "units": "kgDM m-2", + "descriptions": "dry matter carbon content of grain at harvest - annual variable" + }, + { + "codes": 3157, + "names": "LDaboveC_nw", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound non-woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3158, + "names": "LDaboveC_w", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3159, + "names": "LDaboveCnsc_nw", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3160, + "names": "LDaboveCnsc_w", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3161, + "names": "LaboveC_nw", + "units": "kgC m-2", + "descriptions": "Living abovegound non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3162, + "names": "LaboveC_w", + "units": "kgC m-2", + "descriptions": "Living abovegound woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3163, + "names": "LaboveCnsc_nw", + "units": "kgC m-2", + "descriptions": "Living abovegound non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3164, + "names": "LaboveCnsc_w", + "units": "kgC m-2", + "descriptions": "Living abovegound woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3165, + "names": "DaboveC_nw", + "units": "kgC m-2", + "descriptions": "Dead abovegound non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3166, + "names": "DaboveC_w", + "units": "kgC m-2", + "descriptions": "Dead abovegound woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3167, + "names": "DaboveCnsc_nw", + "units": "kgC m-2", + "descriptions": "Dead abovegound non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3168, + "names": "DaboveCnsc_w", + "units": "kgC m-2", + "descriptions": "Dead abovegound woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3169, + "names": "sminN_maxRZ", + "units": "kgN m-2", + "descriptions": "Soil mineralized N content in maximal rooting zone" + }, + { + "codes": 3170, + "names": "soilC_maxRZ", + "units": "kgC m-2", + "descriptions": "Soil carbon content in maximal rooting zone" + }, + { + "codes": 3171, + "names": "soilN_maxRZ", + "units": "kgN m-2", + "descriptions": "Soil nitrogen content in maximal rooting zone" + }, + { + "codes": 3172, + "names": "litrC_maxRZ", + "units": "kgC m-2", + "descriptions": "Litter carbon content in maximal rooting zone" + }, + { + "codes": 3173, + "names": "litrN_maxRZ", + "units": "kgN m-2", + "descriptions": "Litter nitrogen content in maximal rooting zone" + }, + { + "codes": 3174, + "names": "sminNavail_maxRZ", + "units": "kgN m-2", + "descriptions": "Available soil mineralized N content in maximal rooting zone" + }, + { + "codes": 3175, + "names": "tally1", + "units": "kgC m-2", + "descriptions": "Tally of total soil C during successive met cycles (metcyle=1) for comparison" + }, + { + "codes": 3176, + "names": "tally2", + "units": "kgC m-2", + "descriptions": "Tally of total soil C during successive met cycles (metcyle=2) for comparison" + }, + { + "codes": 3177, + "names": "steady1", + "units": "flag", + "descriptions": "Marker for comparison of soilC change and spinup tolerance in metcyle=1" + }, + { + "codes": 3178, + "names": "steady2", + "units": "flag", + "descriptions": "Marker for comparison of soilC change and spinup tolerance in metcyle=2" + }, + { + "codes": 3179, + "names": "metcycle", + "units": "flag", + "descriptions": "Counter for metcyles (0,1 or 2)" + } +] diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.R new file mode 100644 index 0000000..0497c85 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.R @@ -0,0 +1,7 @@ +## ---- fig.show='hold'--------------------------------------------------------- +plot(1:10) +plot(10:1) + +## ---- echo=FALSE, results='asis'---------------------------------------------- +knitr::kable(head(mtcars, 10)) + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.Rmd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.Rmd new file mode 100644 index 0000000..aace6af --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.Rmd @@ -0,0 +1,58 @@ +--- +title: "Vignette Title" +author: "Vignette Author" +date: "`r Sys.Date()`" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{Vignette Title} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + +Vignettes are long form documentation commonly included in packages. Because they are part of the distribution of the package, they need to be as compact as possible. The `html_vignette` output type provides a custom style sheet (and tweaks some options) to ensure that the resulting html is as small as possible. The `html_vignette` format: + +- Never uses retina figures +- Has a smaller default figure size +- Uses a custom CSS stylesheet instead of the default Twitter Bootstrap style + +## Vignette Info + +Note the various macros within the `vignette` section of the metadata block above. These are required in order to instruct R how to build the vignette. Note that you should change the `title` field and the `\VignetteIndexEntry` to match the title of your vignette. + +## Styles + +The `html_vignette` template includes a basic CSS theme. To override this theme you can specify your own CSS in the document metadata as follows: + + output: + rmarkdown::html_vignette: + css: mystyles.css + +## Figures + +The figure sizes have been customised so that you can easily put two images side-by-side. + +```{r, fig.show='hold'} +plot(1:10) +plot(10:1) +``` + +You can enable figure captions by `fig_caption: yes` in YAML: + + output: + rmarkdown::html_vignette: + fig_caption: yes + +Then you can use the chunk option `fig.cap = "Your figure caption."` in **knitr**. + +## More Examples + +You can write math expressions, e.g. $Y = X\beta + \epsilon$, footnotes^[A footnote here.], and tables, e.g. using `knitr::kable()`. + +```{r, echo=FALSE, results='asis'} +knitr::kable(head(mtcars, 10)) +``` + +Also a quote using `>`: + +> "He who gives up [code] safety for [code] speed deserves neither." +([via](https://twitter.com/hadleywickham/status/504368538874703872)) diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.html b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.html new file mode 100644 index 0000000..b0ff013 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/doc/my-vignette.html @@ -0,0 +1,600 @@ + + + + + + + + + + + + + + + + +Vignette Title + + + + + + + + + + + + + + + + + + + + + + + + + + +

Vignette Title

+

Vignette Author

+

2023-02-06

+ + + +

Vignettes are long form documentation commonly included in packages. +Because they are part of the distribution of the package, they need to +be as compact as possible. The html_vignette output type +provides a custom style sheet (and tweaks some options) to ensure that +the resulting html is as small as possible. The +html_vignette format:

+ +
+

Vignette Info

+

Note the various macros within the vignette section of +the metadata block above. These are required in order to instruct R how +to build the vignette. Note that you should change the +title field and the \VignetteIndexEntry to +match the title of your vignette.

+
+
+

Styles

+

The html_vignette template includes a basic CSS theme. +To override this theme you can specify your own CSS in the document +metadata as follows:

+
output: 
+  rmarkdown::html_vignette:
+    css: mystyles.css
+
+
+

Figures

+

The figure sizes have been customised so that you can easily put two +images side-by-side.

+
plot(1:10)
+plot(10:1)
+

+

You can enable figure captions by fig_caption: yes in +YAML:

+
output:
+  rmarkdown::html_vignette:
+    fig_caption: yes
+

Then you can use the chunk option +fig.cap = "Your figure caption." in +knitr.

+
+
+

More Examples

+

You can write math expressions, e.g. \(Y = +X\beta + \epsilon\), footnotes1, and tables, e.g. using +knitr::kable().

+ ++++++++++++++ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
mpgcyldisphpdratwtqsecvsamgearcarb
Mazda RX421.06160.01103.902.62016.460144
Mazda RX4 Wag21.06160.01103.902.87517.020144
Datsun 71022.84108.0933.852.32018.611141
Hornet 4 Drive21.46258.01103.083.21519.441031
Hornet Sportabout18.78360.01753.153.44017.020032
Valiant18.16225.01052.763.46020.221031
Duster 36014.38360.02453.213.57015.840034
Merc 240D24.44146.7623.693.19020.001042
Merc 23022.84140.8953.923.15022.901042
Merc 28019.26167.61233.923.44018.301044
+

Also a quote using >:

+
+

“He who gives up [code] safety for [code] speed deserves neither.” +(via)

+
+
+
+
+
    +
  1. A footnote here.↩︎

  2. +
+
+ + + + + + + + + + + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/CO2.txt b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/CO2.txt new file mode 100644 index 0000000..b710046 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/CO2.txt @@ -0,0 +1,119 @@ + 1900 296.10 + 1901 296.10 + 1902 296.50 + 1903 296.80 + 1904 297.20 + 1905 297.60 + 1906 298.10 + 1907 298.50 + 1908 298.90 + 1909 299.30 + 1910 299.70 + 1911 300.10 + 1912 300.40 + 1913 300.80 + 1914 301.10 + 1915 301.40 + 1916 301.70 + 1917 302.10 + 1918 302.40 + 1919 302.70 + 1920 303.00 + 1921 303.40 + 1922 303.80 + 1923 304.10 + 1924 304.50 + 1925 305.00 + 1926 305.40 + 1927 305.80 + 1928 306.30 + 1929 306.80 + 1930 307.20 + 1931 307.70 + 1932 308.20 + 1933 308.60 + 1934 309.00 + 1935 309.40 + 1936 309.80 + 1937 310.00 + 1938 310.20 + 1939 310.30 + 1940 310.40 + 1941 310.40 + 1942 310.30 + 1943 310.20 + 1944 310.10 + 1945 310.10 + 1946 310.10 + 1947 310.20 + 1948 310.30 + 1949 310.50 + 1950 310.70 + 1951 311.10 + 1952 311.50 + 1953 311.90 + 1954 312.40 + 1955 313.00 + 1956 313.60 + 1957 314.20 + 1958 314.90 + 1959 315.79 + 1960 316.61 + 1961 317.33 + 1962 318.08 + 1963 318.70 + 1964 319.36 + 1965 320.02 + 1966 321.09 + 1967 321.99 + 1968 322.93 + 1969 324.21 + 1970 325.24 + 1971 326.06 + 1972 327.18 + 1973 328.84 + 1974 329.73 + 1975 330.73 + 1976 331.83 + 1977 333.25 + 1978 334.60 + 1979 336.85 + 1980 338.69 + 1981 339.93 + 1982 341.13 + 1983 342.78 + 1984 344.42 + 1985 345.90 + 1986 347.15 + 1987 348.93 + 1988 351.48 + 1989 352.91 + 1990 354.19 + 1991 355.59 + 1992 356.37 + 1993 357.04 + 1994 358.88 + 1995 360.88 + 1996 362.64 + 1997 363.76 + 1998 366.63 + 1999 368.31 + 2000 369.48 + 2001 372.59 + 2002 374.37 + 2003 378.04 + 2004 380.88 + 2005 383.88 + 2006 385.64 + 2007 385.76 + 2008 386.13 + 2009 387.37 + 2010 389.85 + 2011 391.62 + 2012 393.82 + 2013 396.48 + 2014 398.61 + 2015 400.00 + 2016 401.00 + 2017 402.00 + 2018 404.00 diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/HU-He2_2012_MEASURED.txt b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/HU-He2_2012_MEASURED.txt new file mode 100644 index 0000000..63696cb --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/HU-He2_2012_MEASURED.txt @@ -0,0 +1,367 @@ + yyyy mm dd NEE GPP TER LE flag + 2012 1 1 0.440 0.284 0.724 0.030 0 + 2012 1 2 0.540 0.486 1.026 0.222 0 + 2012 1 3 0.716 0.313 1.030 0.002 0 + 2012 1 4 0.627 0.468 1.095 0.055 0 + 2012 1 5 0.868 0.080 0.948 0.061 0 + 2012 1 6 0.077 0.751 0.828 0.372 0 + 2012 1 7 0.396 0.394 0.791 0.219 0 + 2012 1 8 0.110 0.767 0.877 0.125 0 + 2012 1 9 0.239 0.771 1.010 0.182 0 + 2012 1 10 0.207 0.732 0.938 0.271 0 + 2012 1 11 0.115 1.043 1.158 0.173 0 + 2012 1 12 0.509 0.443 0.952 0.351 0 + 2012 1 13 0.245 0.694 0.940 0.294 0 + 2012 1 14 0.509 0.521 1.030 0.192 0 + 2012 1 15 0.516 0.521 1.037 0.120 0 + 2012 1 16 0.142 0.630 0.772 0.195 0 + 2012 1 17 0.423 0.333 0.756 0.172 0 + 2012 1 18 0.277 0.586 0.863 0.256 0 + 2012 1 19 0.609 0.264 0.873 0.179 0 + 2012 1 20 0.853 0.191 1.043 0.028 0 + 2012 1 21 1.004 0.345 1.349 0.240 0 + 2012 1 22 0.658 0.828 1.486 0.313 0 + 2012 1 23 0.339 0.739 1.078 0.153 0 + 2012 1 24 0.281 0.752 1.032 0.045 0 + 2012 1 25 0.275 0.612 0.886 0.234 0 + 2012 1 26 0.098 0.614 0.712 0.189 0 + 2012 1 27 0.065 0.526 0.591 0.198 0 + 2012 1 28 0.270 0.307 0.577 0.101 0 + 2012 1 29 0.180 0.327 0.507 0.062 0 + 2012 1 30 0.916 0.371 1.287 0.086 0 + 2012 1 31 0.462 0.159 0.621 0.119 0 + 2012 2 1 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 2 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 3 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 4 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 5 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 6 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 7 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 8 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 9 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 10 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 11 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 12 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 13 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 14 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 15 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 16 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 17 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 18 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 19 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 20 0.263 0.396 0.660 0.255 0 + 2012 2 21 0.517 0.294 0.811 0.450 0 + 2012 2 22 0.497 0.381 0.878 0.340 0 + 2012 2 23 0.593 0.362 0.955 0.254 0 + 2012 2 24 0.361 0.510 0.872 0.491 0 + 2012 2 25 1.043 0.667 1.710 0.435 0 + 2012 2 26 0.471 0.545 1.016 0.287 0 + 2012 2 27 0.208 0.616 0.825 0.416 0 + 2012 2 28 0.421 0.399 0.820 0.092 0 + 2012 2 29 1.095 0.905 2.000 0.336 0 + 2012 3 1 0.458 1.085 1.542 0.146 0 + 2012 3 2 1.019 1.193 2.212 0.515 0 + 2012 3 3 0.848 1.016 1.865 0.681 0 + 2012 3 4 0.043 1.019 1.063 0.478 0 + 2012 3 5 0.326 0.870 1.196 0.502 0 + 2012 3 6 0.478 0.837 1.315 0.495 0 + 2012 3 7 0.206 0.470 0.675 0.332 0 + 2012 3 8 0.117 0.888 1.005 0.400 0 + 2012 3 9 -0.025 1.098 1.074 0.476 0 + 2012 3 10 0.449 1.011 1.460 0.587 0 + 2012 3 11 1.073 0.594 1.667 0.219 0 + 2012 3 12 1.044 0.590 1.634 0.047 0 + 2012 3 13 0.517 1.387 1.904 0.408 0 + 2012 3 14 0.166 1.769 1.935 0.505 0 + 2012 3 15 0.412 1.703 2.115 0.599 0 + 2012 3 16 0.244 1.535 1.779 0.483 0 + 2012 3 17 0.908 1.756 2.664 0.687 0 + 2012 3 18 0.885 1.659 2.544 0.539 0 + 2012 3 19 -0.386 2.395 2.009 0.502 0 + 2012 3 20 -0.606 2.823 2.217 0.859 0 + 2012 3 21 0.268 2.692 2.960 0.995 0 + 2012 3 22 -0.066 2.926 2.861 0.886 0 + 2012 3 23 0.009 3.536 3.545 0.854 0 + 2012 3 24 0.148 3.509 3.658 0.906 0 + 2012 3 25 -0.373 4.010 3.638 1.150 0 + 2012 3 26 -0.715 3.039 2.325 0.854 0 + 2012 3 27 -1.472 4.040 2.568 1.404 0 + 2012 3 28 -1.693 4.342 2.649 1.060 0 + 2012 3 29 0.028 3.126 3.155 0.736 0 + 2012 3 30 0.353 2.246 2.598 0.348 0 + 2012 3 31 -1.879 5.469 3.589 1.439 0 + 2012 4 1 -2.075 3.925 1.849 0.868 0 + 2012 4 2 -1.823 3.726 1.903 0.912 0 + 2012 4 3 -1.644 4.712 3.068 1.198 0 + 2012 4 4 -1.513 5.074 3.562 1.154 0 + 2012 4 5 -1.560 5.514 3.954 1.246 0 + 2012 4 6 1.817 1.514 3.331 0.048 0 + 2012 4 7 2.102 1.280 3.382 1.149 0 + 2012 4 8 -1.261 4.121 2.861 1.043 0 + 2012 4 9 -0.849 3.436 2.586 1.254 0 + 2012 4 10 -1.403 4.031 2.628 1.119 0 + 2012 4 11 -2.714 5.045 2.331 0.973 0 + 2012 4 12 -0.814 3.435 2.621 0.371 0 + 2012 4 13 -1.430 5.563 4.133 1.196 0 + 2012 4 14 0.886 3.198 4.085 0.124 0 + 2012 4 15 -1.468 5.235 3.767 0.354 0 + 2012 4 16 -0.391 3.663 3.272 0.408 0 + 2012 4 17 -2.404 5.576 3.172 0.967 0 + 2012 4 18 -2.231 5.599 3.368 0.857 0 + 2012 4 19 -4.172 7.629 3.457 1.407 0 + 2012 4 20 -3.302 7.423 4.121 1.344 0 + 2012 4 21 -2.392 6.356 3.965 0.839 0 + 2012 4 22 -1.016 4.731 3.715 0.532 0 + 2012 4 23 -3.809 7.395 3.586 0.974 0 + 2012 4 24 -2.960 6.773 3.813 0.612 0 + 2012 4 25 -4.338 8.789 4.451 2.042 0 + 2012 4 26 -5.087 10.121 5.034 2.478 0 + 2012 4 27 -4.817 8.607 3.790 2.461 0 + 2012 4 28 -4.396 8.659 4.263 2.372 0 + 2012 4 29 -6.780 10.393 3.613 2.607 0 + 2012 4 30 -6.309 9.668 3.358 2.703 0 + 2012 5 1 -3.619 8.815 5.196 2.805 0 + 2012 5 2 -4.568 10.142 5.574 2.899 0 + 2012 5 3 -3.377 7.731 4.355 1.086 0 + 2012 5 4 -0.910 5.555 4.645 0.711 0 + 2012 5 5 -5.536 11.269 5.733 2.516 0 + 2012 5 6 -6.022 11.611 5.589 2.154 0 + 2012 5 7 -1.552 6.454 4.903 0.780 0 + 2012 5 8 -4.539 11.023 6.485 2.654 0 + 2012 5 9 -6.838 12.291 5.453 2.248 0 + 2012 5 10 -6.109 13.095 6.986 2.653 0 + 2012 5 11 -6.404 13.728 7.324 2.453 0 + 2012 5 12 -3.041 11.038 7.998 1.494 0 + 2012 5 13 -2.685 8.466 5.781 1.701 0 + 2012 5 14 -1.911 7.159 5.247 0.614 0 + 2012 5 15 -4.420 10.143 5.723 1.881 0 + 2012 5 16 -2.677 7.455 4.778 0.899 0 + 2012 5 17 -4.086 8.456 4.370 1.535 0 + 2012 5 18 -2.892 8.133 5.241 1.827 0 + 2012 5 19 -3.103 9.789 6.686 2.036 0 + 2012 5 20 -3.446 10.774 7.328 1.722 0 + 2012 5 21 -1.290 8.958 7.668 0.755 0 + 2012 5 22 2.787 3.587 6.373 1.697 0 + 2012 5 23 -0.447 9.872 9.425 1.763 0 + 2012 5 24 0.187 10.434 10.622 2.221 0 + 2012 5 25 -1.949 10.115 8.166 2.603 0 + 2012 5 26 0.660 5.055 5.715 1.618 0 + 2012 5 27 2.652 3.893 6.545 1.588 0 + 2012 5 28 1.376 4.117 5.492 0.978 0 + 2012 5 29 1.416 4.619 6.035 1.400 0 + 2012 5 30 2.294 4.686 6.981 1.480 0 + 2012 5 31 4.244 2.414 6.659 1.549 0 + 2012 6 1 5.654 1.717 7.371 1.859 0 + 2012 6 2 -0.535 6.426 5.891 0.618 0 + 2012 6 3 -2.344 10.030 7.686 2.302 0 + 2012 6 4 1.526 5.390 6.916 1.171 0 + 2012 6 5 3.911 2.762 6.673 1.908 0 + 2012 6 6 -2.767 7.480 4.713 1.747 0 + 2012 6 7 -0.002 5.994 5.993 2.189 0 + 2012 6 8 -1.293 8.200 6.907 2.516 0 + 2012 6 9 2.902 3.437 6.339 0.607 0 + 2012 6 10 1.859 5.307 7.167 1.120 0 + 2012 6 11 2.909 4.120 7.030 0.814 0 + 2012 6 12 1.635 7.776 9.411 0.162 0 + 2012 6 13 3.300 9.112 12.413 1.079 0 + 2012 6 14 -0.500 13.424 12.924 2.230 0 + 2012 6 15 -0.555 13.719 13.164 2.650 0 + 2012 6 16 -2.240 15.315 13.075 2.788 0 + 2012 6 17 -3.710 15.421 11.711 3.815 0 + 2012 6 18 -1.316 13.615 12.299 3.467 0 + 2012 6 19 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 6 20 0.835 9.146 9.981 2.682 0 + 2012 6 21 -3.757 11.764 8.007 2.801 0 + 2012 6 22 -3.178 9.991 6.813 1.756 0 + 2012 6 23 -2.973 11.667 8.695 2.479 0 + 2012 6 24 -1.681 8.276 6.595 2.378 0 + 2012 6 25 1.698 4.862 6.559 0.469 0 + 2012 6 26 -0.333 8.257 7.924 2.947 0 + 2012 6 27 -1.240 9.078 7.839 2.568 0 + 2012 6 28 -2.438 8.591 6.153 2.323 0 + 2012 6 29 -0.041 6.786 6.745 2.320 0 + 2012 6 30 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 1 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 2 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 3 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 4 -1.694 7.565 5.871 2.055 0 + 2012 7 5 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 6 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 7 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 8 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 9 0.081 8.633 8.714 1.883 0 + 2012 7 10 5.480 4.571 10.050 2.978 0 + 2012 7 11 3.540 6.345 9.885 2.251 0 + 2012 7 12 3.573 6.518 10.092 2.055 0 + 2012 7 13 0.738 6.337 7.074 0.663 0 + 2012 7 14 2.392 5.352 7.744 1.730 0 + 2012 7 15 2.621 3.246 5.867 0.517 0 + 2012 7 16 0.002 5.766 5.768 2.395 0 + 2012 7 17 2.181 4.233 6.414 2.290 0 + 2012 7 18 0.333 5.522 5.855 2.121 0 + 2012 7 19 2.896 4.745 7.641 1.881 0 + 2012 7 20 -4.409 12.188 7.779 2.913 0 + 2012 7 21 2.161 4.473 6.635 0.085 0 + 2012 7 22 -1.966 9.473 7.507 1.158 0 + 2012 7 23 -3.943 12.987 9.044 2.395 0 + 2012 7 24 -1.126 11.111 9.984 1.840 0 + 2012 7 25 0.630 9.271 9.901 1.197 0 + 2012 7 26 0.641 10.025 10.666 2.289 0 + 2012 7 27 -3.677 14.036 10.359 3.401 0 + 2012 7 28 4.881 6.944 11.825 2.951 0 + 2012 7 29 -0.567 10.221 9.654 2.393 0 + 2012 7 30 -5.159 13.376 8.217 2.932 0 + 2012 7 31 -1.854 11.970 10.116 2.514 0 + 2012 8 1 -2.916 12.214 9.298 3.764 0 + 2012 8 2 0.390 8.301 8.691 2.852 0 + 2012 8 3 -3.120 12.612 9.492 2.479 0 + 2012 8 4 -0.243 9.906 9.662 3.369 0 + 2012 8 5 0.921 7.809 8.730 2.621 0 + 2012 8 6 1.958 7.150 9.108 2.832 0 + 2012 8 7 -3.802 12.456 8.654 2.834 0 + 2012 8 8 -3.271 10.859 7.588 1.917 0 + 2012 8 9 -2.539 10.918 8.379 1.708 0 + 2012 8 10 -4.573 13.220 8.647 2.166 0 + 2012 8 11 -1.417 7.881 6.464 0.969 0 + 2012 8 12 -5.064 11.249 6.185 2.064 0 + 2012 8 13 -3.401 10.948 7.547 1.999 0 + 2012 8 14 -4.735 11.421 6.685 2.658 0 + 2012 8 15 -1.630 9.253 7.623 2.609 0 + 2012 8 16 -0.523 9.221 8.698 2.449 0 + 2012 8 17 1.732 5.620 7.352 1.526 0 + 2012 8 18 1.792 5.627 7.419 1.600 0 + 2012 8 19 1.106 5.309 6.415 1.804 0 + 2012 8 20 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 8 21 -1.427 6.966 5.539 1.564 0 + 2012 8 22 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 8 23 1.842 3.369 5.211 1.107 0 + 2012 8 24 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 8 25 0.752 4.044 4.796 1.564 0 + 2012 8 26 3.442 2.638 6.080 0.522 0 + 2012 8 27 4.227 2.070 6.297 1.209 0 + 2012 8 28 2.774 2.543 5.317 0.935 0 + 2012 8 29 0.889 6.332 7.221 1.144 0 + 2012 8 30 1.106 5.600 6.705 0.831 0 + 2012 8 31 1.499 4.726 6.225 0.397 0 + 2012 9 1 5.480 0.607 6.087 0.086 0 + 2012 9 2 4.770 3.085 7.854 1.212 0 + 2012 9 3 1.925 4.683 6.608 1.032 0 + 2012 9 4 1.147 4.621 5.768 0.847 0 + 2012 9 5 0.741 4.361 5.102 1.092 0 + 2012 9 6 0.236 3.269 3.505 0.792 0 + 2012 9 7 0.763 2.721 3.484 0.940 0 + 2012 9 8 1.173 3.364 4.537 1.023 0 + 2012 9 9 0.653 4.112 4.765 1.027 0 + 2012 9 10 0.912 4.461 5.373 0.874 0 + 2012 9 11 1.132 4.765 5.898 0.767 0 + 2012 9 12 1.016 5.574 6.589 0.666 0 + 2012 9 13 4.085 0.392 4.477 0.011 0 + 2012 9 14 3.004 2.271 5.276 0.517 0 + 2012 9 15 2.511 3.204 5.715 0.893 0 + 2012 9 16 1.539 4.356 5.896 0.949 0 + 2012 9 17 1.364 4.156 5.520 1.255 0 + 2012 9 18 2.299 4.659 6.957 0.954 0 + 2012 9 19 0.491 5.345 5.836 0.542 0 + 2012 9 20 1.374 4.325 5.699 1.097 0 + 2012 9 21 0.522 3.115 3.637 0.972 0 + 2012 9 22 0.051 3.473 3.524 1.001 0 + 2012 9 23 -0.100 2.702 2.602 0.878 0 + 2012 9 24 0.966 2.419 3.385 0.719 0 + 2012 9 25 1.793 2.237 4.030 1.720 0 + 2012 9 26 1.756 2.586 4.342 1.772 0 + 2012 9 27 0.954 3.168 4.122 0.882 0 + 2012 9 28 0.857 3.393 4.250 1.065 0 + 2012 9 29 1.165 3.372 4.537 0.451 0 + 2012 9 30 -0.759 5.569 4.811 0.830 0 + 2012 10 1 0.207 4.616 4.823 0.919 0 + 2012 10 2 2.516 1.735 4.251 0.041 0 + 2012 10 3 -1.047 4.089 3.042 0.614 0 + 2012 10 4 -1.631 4.975 3.343 0.784 0 + 2012 10 5 -1.277 4.647 3.369 0.901 0 + 2012 10 6 -1.711 5.633 3.922 0.899 0 + 2012 10 7 -1.559 5.570 4.011 0.717 0 + 2012 10 8 -2.029 5.085 3.056 0.904 0 + 2012 10 9 -1.604 5.274 3.671 0.692 0 + 2012 10 10 0.803 1.903 2.705 0.122 0 + 2012 10 11 -2.131 4.498 2.367 0.456 0 + 2012 10 12 0.644 2.323 2.966 0.063 0 + 2012 10 13 0.037 2.745 2.783 0.162 0 + 2012 10 14 -1.170 4.054 2.884 0.115 0 + 2012 10 15 -2.453 5.964 3.511 0.608 0 + 2012 10 16 0.666 1.569 2.235 0.361 0 + 2012 10 17 -2.423 5.213 2.790 0.140 0 + 2012 10 18 -2.999 7.236 4.237 0.575 0 + 2012 10 19 -2.974 6.842 3.869 0.509 0 + 2012 10 20 -0.961 6.009 5.047 0.313 0 + 2012 10 21 -1.929 6.137 4.208 0.308 0 + 2012 10 22 -1.843 7.383 5.540 0.478 0 + 2012 10 23 0.129 4.387 4.516 0.030 0 + 2012 10 24 1.710 3.265 4.975 0.073 0 + 2012 10 25 1.606 3.260 4.866 0.060 0 + 2012 10 26 0.887 2.925 3.811 0.051 0 + 2012 10 27 -1.423 4.769 3.346 0.060 0 + 2012 10 28 0.073 2.014 2.088 0.099 0 + 2012 10 29 0.697 0.838 1.535 0.002 0 + 2012 10 30 -0.362 1.947 1.585 0.214 0 + 2012 10 31 -0.675 2.402 1.727 0.288 0 + 2012 11 1 0.985 0.571 1.556 0.159 0 + 2012 11 2 0.282 1.449 1.731 0.123 0 + 2012 11 3 -1.547 3.771 2.224 0.479 0 + 2012 11 4 -1.364 4.402 3.038 0.569 0 + 2012 11 5 1.604 0.670 2.273 0.159 0 + 2012 11 6 0.679 2.410 3.089 0.170 0 + 2012 11 7 -0.727 2.904 2.176 0.374 0 + 2012 11 8 -0.928 3.313 2.385 0.377 0 + 2012 11 9 -0.790 2.533 1.743 0.293 0 + 2012 11 10 -0.660 2.691 2.031 0.184 0 + 2012 11 11 -0.739 2.588 1.850 0.136 0 + 2012 11 12 2.039 0.224 2.263 0.002 0 + 2012 11 13 1.237 2.104 3.341 0.052 0 + 2012 11 14 0.073 2.379 2.452 0.243 0 + 2012 11 15 -1.381 3.138 1.757 0.207 0 + 2012 11 16 0.103 1.772 1.875 0.067 0 + 2012 11 17 -0.843 2.621 1.778 0.094 0 + 2012 11 18 0.383 1.353 1.736 0.017 0 + 2012 11 19 1.891 0.365 2.256 0.007 0 + 2012 11 20 0.456 1.504 1.960 0.027 0 + 2012 11 21 0.973 1.028 2.002 0.011 0 + 2012 11 22 1.407 0.499 1.905 0.014 0 + 2012 11 23 0.676 1.122 1.798 0.011 0 + 2012 11 24 -0.320 2.203 1.883 0.023 0 + 2012 11 25 0.519 1.067 1.586 0.024 0 + 2012 11 26 0.191 1.449 1.640 0.067 0 + 2012 11 27 -0.142 2.655 2.512 0.536 0 + 2012 11 28 -0.100 2.787 2.686 0.361 0 + 2012 11 29 -0.291 2.827 2.536 0.099 0 + 2012 11 30 1.480 0.791 2.271 0.216 0 + 2012 12 1 -0.573 1.355 0.782 0.104 0 + 2012 12 2 1.006 0.284 1.290 0.009 0 + 2012 12 3 0.518 1.285 1.803 0.211 0 + 2012 12 4 0.150 1.210 1.360 0.035 0 + 2012 12 5 0.435 1.623 2.058 0.033 0 + 2012 12 6 0.319 0.842 1.161 0.022 0 + 2012 12 7 0.430 0.904 1.334 0.080 0 + 2012 12 8 1.286 0.000 1.286 0.012 0 + 2012 12 9 0.610 0.205 0.815 0.104 0 + 2012 12 10 0.676 0.293 0.969 0.087 0 + 2012 12 11 0.656 0.223 0.878 0.034 0 + 2012 12 12 0.418 0.242 0.660 0.101 0 + 2012 12 13 0.494 0.000 0.494 0.042 0 + 2012 12 14 0.662 0.316 0.978 0.005 0 + 2012 12 15 0.458 0.707 1.164 0.006 0 + 2012 12 16 0.185 0.889 1.073 0.005 0 + 2012 12 17 0.743 0.345 1.088 0.044 0 + 2012 12 18 0.764 0.111 0.875 0.009 0 + 2012 12 19 0.554 0.677 1.231 0.044 0 + 2012 12 20 0.308 0.775 1.083 0.028 0 + 2012 12 21 0.439 0.496 0.934 0.044 0 + 2012 12 22 0.141 0.800 0.941 0.005 0 + 2012 12 23 0.146 0.846 0.992 0.044 0 + 2012 12 24 -0.763 1.761 0.999 0.066 0 + 2012 12 25 0.390 1.345 1.735 0.131 0 + 2012 12 26 1.101 0.369 1.470 0.015 0 + 2012 12 27 -0.462 1.742 1.280 0.048 0 + 2012 12 28 0.525 0.520 1.045 0.044 0 + 2012 12 29 -0.086 0.827 0.740 0.060 0 + 2012 12 30 -0.044 0.648 0.604 0.056 0 + 2012 12 31 -0.040 0.731 0.692 0.092 0 diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/Ndep.txt b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/Ndep.txt new file mode 100644 index 0000000..fe6c63d --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/Ndep.txt @@ -0,0 +1,119 @@ +1900 0.0003911 +1901 0.0003922 +1902 0.0003952 +1903 0.0003982 +1904 0.0004012 +1905 0.0004043 +1906 0.0004073 +1907 0.0004103 +1908 0.0004133 +1909 0.0004164 +1910 0.0004224 +1911 0.0004267 +1912 0.0004310 +1913 0.0004353 +1914 0.0004396 +1915 0.0004439 +1916 0.0004482 +1917 0.0004525 +1918 0.0004568 +1919 0.0004611 +1920 0.0004697 +1921 0.0004741 +1922 0.0004786 +1923 0.0004830 +1924 0.0004875 +1925 0.0004919 +1926 0.0004964 +1927 0.0005008 +1928 0.0005053 +1929 0.0005097 +1930 0.0005186 +1931 0.0005214 +1932 0.0005243 +1933 0.0005271 +1934 0.0005299 +1935 0.0005327 +1936 0.0005356 +1937 0.0005384 +1938 0.0005412 +1939 0.0005440 +1940 0.0005497 +1941 0.0005600 +1942 0.0005703 +1943 0.0005806 +1944 0.0005909 +1945 0.0006013 +1946 0.0006116 +1947 0.0006219 +1948 0.0006322 +1949 0.0006425 +1950 0.0006632 +1951 0.0006775 +1952 0.0006919 +1953 0.0007063 +1954 0.0007207 +1955 0.0007350 +1956 0.0007494 +1957 0.0007638 +1958 0.0007782 +1959 0.0007925 +1960 0.0008213 +1961 0.0008407 +1962 0.0008601 +1963 0.0008795 +1964 0.0008989 +1965 0.0009183 +1966 0.0009378 +1967 0.0009572 +1968 0.0009766 +1969 0.0009960 +1970 0.0010348 +1971 0.0010591 +1972 0.0010465 +1973 0.0010524 +1974 0.0010582 +1975 0.0010641 +1976 0.0010699 +1977 0.0010758 +1978 0.0010816 +1979 0.0010875 +1980 0.0010933 +1981 0.0010992 +1982 0.0011050 +1983 0.0011109 +1984 0.0011167 +1985 0.0011226 +1986 0.0011284 +1987 0.0011343 +1988 0.0011401 +1989 0.0011460 +1990 0.0011519 +1991 0.0011577 +1992 0.0011636 +1993 0.0011694 +1994 0.0011753 +1995 0.0011811 +1996 0.0011870 +1997 0.0011928 +1998 0.0011987 +1999 0.0012045 +2000 0.0012104 +2001 0.0012239 +2002 0.0012347 +2003 0.0012654 +2004 0.0012762 +2005 0.0012870 +2006 0.0012977 +2007 0.0013085 +2008 0.0013192 +2009 0.0013200 +2010 0.0013407 +2011 0.0013515 +2012 0.0013722 +2013 0.0013830 +2014 0.0013938 +2015 0.0014010 +2016 0.0014020 +2017 0.0014040 +2018 0.0014050 diff --git a/RBBGCMuso/inst/examples/hhs/c3grass_muso6.epc b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/c3grass_muso6.epc similarity index 98% rename from RBBGCMuso/inst/examples/hhs/c3grass_muso6.epc rename to RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/c3grass_muso6.epc index aff3b31..7ca48f3 100644 --- a/RBBGCMuso/inst/examples/hhs/c3grass_muso6.epc +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/c3grass_muso6.epc @@ -1,139 +1,139 @@ -ECOPHYS FILE - C3 grass muso6 ----------------------------------------------------------------------------------------- -FLAGS -0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY) -0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS) -1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN) ----------------------------------------------------------------------------------------- -PLANT FUNCTIONING PARAMETERS -0 (yday) yearday to start new growth (when phenology flag = 0) -364 (yday) yearday to end litterfall (when phenology flag = 0) -0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0) -0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0) -0 (Celsius) base temperature --9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) --9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation) --9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation) --9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) --9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation) --9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation) --9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation) --9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation) -1.0 (1/yr) annual leaf and fine root turnover fraction -0.00 (1/yr) annual live wood turnover fraction -0.03 (1/yr) annual fire mortality fraction -0.01 (1/vegper) whole-plant mortality fraction in vegetation period -36.6 (kgC/kgN) C:N of leaves -45.0 (kgC/kgN) C:N of leaf litter, after retranslocation -50.0 (kgC/kgN) C:N of fine roots -36.6 *(kgC/kgN) C:N of fruit -36.6 (kgC/kgN) C:N of soft stem -0.0 *(kgC/kgN) C:N of live wood -0.0 *(kgC/kgN) C:N of dead wood -0.4 (kgC/kgDM) dry matter carbon content of leaves -0.4 (kgC/kgDM) dry matter carbon content of leaf litter -0.4 (kgC/kgDM) dry matter carbon content of fine roots -0.4 *(kgC/kgDM) dry matter carbon content of fruit -0.4 (kgC/kgDM) dry matter carbon content of soft stem -0.4 *(kgC/kgDM) dry matter carbon content of live wood -0.4 *(kgC/kgDM) dry matter carbon content of dead wood -0.68 (DIM) leaf litter labile proportion -0.23 (DIM) leaf litter cellulose proportion -0.34 (DIM) fine root labile proportion -0.44 (DIM) fine root cellulose proportion -0.68 *(DIM) fruit litter labile proportion -0.23 *(DIM) fruit litter cellulose proportion -0.68 (DIM) soft stem litter labile proportion -0.23 (DIM) soft stem litter cellulose proportion -0.00 *(DIM) dead wood cellulose proportion -0.01 (1/LAI/d) canopy water interception coefficient -0.63 (DIM) canopy light extinction coefficient -2.0 (g/MJ) potential radiation use efficiency -0.781 (DIM) radiation parameter1 (Jiang et al.2015) --13.596 (DIM) radiation parameter2 (Jiang et al.2015) -2.0 (DIM) all-sided to projected leaf area ratio -2.0 (DIM) ratio of shaded SLA:sunlit SLA -0.14 (DIM) fraction of leaf N in Rubisco -0.03 (DIM) fraction of leaf N in PEP Carboxylase -0.004 (m/s) maximum stomatal conductance (projected area basis) -0.00006 (m/s) cuticular conductance (projected area basis) -0.04 (m/s) boundary layer conductance (projected area basis) -1.5 (m) maximum height of plant -0.8 (kgC) stem weight corresponding to maximum height -0.5 (dimless) plant height function shape parameter (slope) -4.0 (m) maximum depth of rooting zone -3.67 (DIM) root distribution parameter -0.4 (kgC) root weight corresponding to max root depth -0.5 (dimless) root depth function shape parameter (slope) -1000 (m/kg) root weight to root length conversion factor -0.3 (prop.) growth resp per unit of C grown -0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N -0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates -0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration -0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N -0 (day) time delay for temperature in photosynthesis acclimation ----------------------------------------------------------------------------------------- -CROP SPECIFIC PARAMETERS -0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific) -0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific) -0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination -0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect) -20 (hour) critical photoslow daylength -0.005 (DIM) slope of relative photoslow development rate -0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect) -0 (Celsius) critical vernalization temperature 1 -5 (Celsius) critical vernalization temperature 2 -8 (Celsius) critical vernalization temperature 3 -15 (Celsius) critical vernalization temperature 4 -0.04 (DIM) slope of relative vernalization development rate -50 (n) required vernalization days (in vernalization development rate) -0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect) -35 (Celsius) critical flowering heat stress temperature 1 -40 (Celsius) critical flowering heat stress temperature 2 -0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter ----------------------------------------------------------------------------------------- -STRESS AND SENESCENCE PARAMETERS -0.98 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP) -0.7 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC) -0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value) -1000 (Pa) vapor pressure deficit: start of conductance reduction -4000 (Pa) vapor pressure deficit: complete conductance reduction -0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material -0.001 (prop.) maximum senescence mortality coefficient of belowground plant material -0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material -35 (Celsius) lower limit extreme high temperature effect on senescence mortality -40 (Celsius) upper limit extreme high temperature effect on senescence mortality -0.01 (prop.) turnover rate of wilted standing biomass to litter -0.047 (prop.) turnover rate of non-woody cut-down biomass to litter -0.01 (prop.) turnover rate of woody cut-down biomass to litter -17 (nday) drought tolerance parameter (critical value of DSWS) -0.3 (prop) soil water deficit effect on photosynthesis downregulation ----------------------------------------------------------------------------------------- -GROWING SEASON PARAMETERS -5 (kg/m2) crit. amount of snow limiting photosyn. -20 (Celsius) limit1 (under:full constrained) of HEATSUM index -60 (Celsius) limit2 (above:unconstrained) of HEATSUM index -0 (Celsius) limit1 (under:full constrained) of TMIN index -5 (Celsius) limit2 (above:unconstrained) of TMIN index -4000 (Pa) limit1 (above:full constrained) of VPD index -1000 (Pa) limit2 (under:unconstrained) of VPD index -0 (s) limit1 (under:full constrained) of DAYLENGTH index -0 (s) limit2 (above:unconstrained) of DAYLENGTH index -10 (day) moving average (to avoid the effects of extreme events) -0.10 (dimless) GSI limit1 (greater that limit -> start of vegper) -0.01 (dimless) GSI limit2 (less that limit -> end of vegper) ----------------------------------------------------------------------------------------- -PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases) -phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase -5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD) -0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION -0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION -0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION -0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION -0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION -0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION -0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION -0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION -49 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis) -0.37 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion -10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue +ECOPHYS FILE - C3 grass muso6 +---------------------------------------------------------------------------------------- +FLAGS +0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY) +0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS) +1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN) +---------------------------------------------------------------------------------------- +PLANT FUNCTIONING PARAMETERS +0 (yday) yearday to start new growth (when phenology flag = 0) +364 (yday) yearday to end litterfall (when phenology flag = 0) +0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0) +0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0) +0 (Celsius) base temperature +-9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +1.0 (1/yr) annual leaf and fine root turnover fraction +0.00 (1/yr) annual live wood turnover fraction +0.03 (1/yr) annual fire mortality fraction +0.01 (1/vegper) whole-plant mortality fraction in vegetation period +36.6 (kgC/kgN) C:N of leaves +45.0 (kgC/kgN) C:N of leaf litter, after retranslocation +50.0 (kgC/kgN) C:N of fine roots +36.6 *(kgC/kgN) C:N of fruit +36.6 (kgC/kgN) C:N of soft stem +0.0 *(kgC/kgN) C:N of live wood +0.0 *(kgC/kgN) C:N of dead wood +0.4 (kgC/kgDM) dry matter carbon content of leaves +0.4 (kgC/kgDM) dry matter carbon content of leaf litter +0.4 (kgC/kgDM) dry matter carbon content of fine roots +0.4 *(kgC/kgDM) dry matter carbon content of fruit +0.4 (kgC/kgDM) dry matter carbon content of soft stem +0.4 *(kgC/kgDM) dry matter carbon content of live wood +0.4 *(kgC/kgDM) dry matter carbon content of dead wood +0.68 (DIM) leaf litter labile proportion +0.23 (DIM) leaf litter cellulose proportion +0.34 (DIM) fine root labile proportion +0.44 (DIM) fine root cellulose proportion +0.68 *(DIM) fruit litter labile proportion +0.23 *(DIM) fruit litter cellulose proportion +0.68 (DIM) soft stem litter labile proportion +0.23 (DIM) soft stem litter cellulose proportion +0.00 *(DIM) dead wood cellulose proportion +0.01 (1/LAI/d) canopy water interception coefficient +0.63 (DIM) canopy light extinction coefficient +2.0 (g/MJ) potential radiation use efficiency +0.781 (DIM) radiation parameter1 (Jiang et al.2015) +-13.596 (DIM) radiation parameter2 (Jiang et al.2015) +2.0 (DIM) all-sided to projected leaf area ratio +2.0 (DIM) ratio of shaded SLA:sunlit SLA +0.14 (DIM) fraction of leaf N in Rubisco +0.03 (DIM) fraction of leaf N in PEP Carboxylase +0.004 (m/s) maximum stomatal conductance (projected area basis) +0.00006 (m/s) cuticular conductance (projected area basis) +0.04 (m/s) boundary layer conductance (projected area basis) +1.5 (m) maximum height of plant +0.8 (kgC) stem weight corresponding to maximum height +0.5 (dimless) plant height function shape parameter (slope) +4.0 (m) maximum depth of rooting zone +3.67 (DIM) root distribution parameter +0.4 (kgC) root weight corresponding to max root depth +0.5 (dimless) root depth function shape parameter (slope) +1000 (m/kg) root weight to root length conversion factor +0.3 (prop.) growth resp per unit of C grown +0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N +0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates +0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration +0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N +0 (day) time delay for temperature in photosynthesis acclimation +---------------------------------------------------------------------------------------- +CROP SPECIFIC PARAMETERS +0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific) +0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific) +0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination +0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect) +20 (hour) critical photoslow daylength +0.005 (DIM) slope of relative photoslow development rate +0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect) +0 (Celsius) critical vernalization temperature 1 +5 (Celsius) critical vernalization temperature 2 +8 (Celsius) critical vernalization temperature 3 +15 (Celsius) critical vernalization temperature 4 +0.04 (DIM) slope of relative vernalization development rate +50 (n) required vernalization days (in vernalization development rate) +0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect) +35 (Celsius) critical flowering heat stress temperature 1 +40 (Celsius) critical flowering heat stress temperature 2 +0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter +---------------------------------------------------------------------------------------- +STRESS AND SENESCENCE PARAMETERS +0.98 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP) +0.7 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC) +0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value) +1000 (Pa) vapor pressure deficit: start of conductance reduction +4000 (Pa) vapor pressure deficit: complete conductance reduction +0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material +0.001 (prop.) maximum senescence mortality coefficient of belowground plant material +0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material +35 (Celsius) lower limit extreme high temperature effect on senescence mortality +40 (Celsius) upper limit extreme high temperature effect on senescence mortality +0.01 (prop.) turnover rate of wilted standing biomass to litter +0.047 (prop.) turnover rate of non-woody cut-down biomass to litter +0.01 (prop.) turnover rate of woody cut-down biomass to litter +17 (nday) drought tolerance parameter (critical value of DSWS) +0.3 (prop) soil water deficit effect on photosynthesis downregulation +---------------------------------------------------------------------------------------- +GROWING SEASON PARAMETERS +5 (kg/m2) crit. amount of snow limiting photosyn. +20 (Celsius) limit1 (under:full constrained) of HEATSUM index +60 (Celsius) limit2 (above:unconstrained) of HEATSUM index +0 (Celsius) limit1 (under:full constrained) of TMIN index +5 (Celsius) limit2 (above:unconstrained) of TMIN index +4000 (Pa) limit1 (above:full constrained) of VPD index +1000 (Pa) limit2 (under:unconstrained) of VPD index +0 (s) limit1 (under:full constrained) of DAYLENGTH index +0 (s) limit2 (above:unconstrained) of DAYLENGTH index +10 (day) moving average (to avoid the effects of extreme events) +0.10 (dimless) GSI limit1 (greater that limit -> start of vegper) +0.01 (dimless) GSI limit2 (less that limit -> end of vegper) +---------------------------------------------------------------------------------------- +PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases) +phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase +5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD) +0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION +0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION +0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION +0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION +0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION +49 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis) +0.37 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion +10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue diff --git a/RBBGCMuso/inst/examples/hhs/compile_log_linux.txt b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/compile_log_linux.txt similarity index 100% rename from RBBGCMuso/inst/examples/hhs/compile_log_linux.txt rename to RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/compile_log_linux.txt diff --git a/RBBGCMuso/inst/examples/hhs/hhs.mgm b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mgm similarity index 98% rename from RBBGCMuso/inst/examples/hhs/hhs.mgm rename to RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mgm index d0b9b35..c2ab5e8 100644 --- a/RBBGCMuso/inst/examples/hhs/hhs.mgm +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mgm @@ -1,33 +1,33 @@ -MANAGEMENT_INFORMATION MuSo6 -------------------------------------------------------------------------------------------------------------------- -PLANTING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none -------------------------------------------------------------------------------------------------------------------- -THINNING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none -------------------------------------------------------------------------------------------------------------------- -MOWING -1 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -hhs.mow -------------------------------------------------------------------------------------------------------------------- -GRAZING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none -------------------------------------------------------------------------------------------------------------------- -HARVESTING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none -------------------------------------------------------------------------------------------------------------------- -PLOUGHING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none -------------------------------------------------------------------------------------------------------------------- -FERTILIZING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none -------------------------------------------------------------------------------------------------------------------- -IRRIGATING -0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below -none +MANAGEMENT_INFORMATION MuSo6 +------------------------------------------------------------------------------------------------------------------- +PLANTING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +THINNING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +MOWING +1 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +hhs.mow +------------------------------------------------------------------------------------------------------------------- +GRAZING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +HARVESTING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +PLOUGHING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +FERTILIZING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +IRRIGATING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mow b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mow new file mode 100644 index 0000000..9144646 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mow @@ -0,0 +1,23 @@ +DATE afterLAI(m2/m2) transPART(%) +2006.08.09 1 90 +2007.06.18 1 90 +2008.05.30 1 90 +2008.08.18 1 90 +2009.06.08 1 90 +2009.08.07 1 90 +2010.06.12 1 90 +2010.09.26 1 90 +2011.06.01 1 90 +2011.08.21 1 90 +2012.05.24 1 90 +2012.08.17 1 90 +2013.06.16 1 90 +2013.09.29 1 90 +2014.06.09 1 90 +2015.06.13 1 90 +2015.09.30 1 90 +2016.06.22 1 90 +2016.08.14 1 90 +2017.06.18 1 90 +2018.06.03 1 90 +2018.07.30 1 90 diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mtc43 b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mtc43 new file mode 100644 index 0000000..1c71d0b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.mtc43 @@ -0,0 +1,42344 @@ +Hegyhatsal, 1901-2016, input for BBGCMuSo6 +MTCLIM v4.3 OUTPUT FILE +year yday Tmax Tmin Tday prcp VPD srad daylen + (degC) (degC) (degC) (cm) (Pa) (Wm-2) (s) +1901 1 -1.28 -7.28 -2.93 0 138.46 175.61 30438 +1901 2 -4.34 -10.34 -5.99 0 112.36 177.35 30492 +1901 3 -2.56 -8.56 -4.21 0 126.96 177.62 30551 +1901 4 -0.5 -6.5 -2.15 0 145.9 177.66 30614 +1901 5 -0.25 -6.25 -1.9 0 148.35 178.12 30681 +1901 6 1.43 -4.57 -0.22 0 165.8 177.97 30752 +1901 7 1.23 -4.77 -0.42 0 163.64 178.59 30828 +1901 8 -0.27 -6.27 -1.92 0 148.15 180.65 30907 +1901 9 -3.52 -9.52 -5.17 0.13 118.89 148.54 30991 +1901 10 -1.86 -7.86 -3.51 0 133.14 184.05 31079 +1901 11 0.57 -5.43 -1.08 0.1 156.66 148.72 31171 +1901 12 1.39 -4.61 -0.26 0.03 165.37 148.88 31266 +1901 13 2.51 -3.49 0.86 0 177.93 184.73 31366 +1901 14 0.65 -5.35 -1 0 157.49 186.92 31469 +1901 15 0.71 -5.29 -0.94 0.89 158.12 151.64 31575 +1901 16 -3.05 -9.05 -4.7 1.16 122.79 157.18 31686 +1901 17 -5.78 -11.78 -7.43 0.62 101.63 160.86 31800 +1901 18 -0.57 -6.57 -2.22 0.13 145.22 161.06 31917 +1901 19 -3.52 -9.52 -5.17 0.05 118.89 163.39 32038 +1901 20 0.82 -5.18 -0.83 0 159.27 201.48 32161 +1901 21 -0.39 -6.39 -2.04 0 146.97 203.9 32289 +1901 22 -0.86 -6.86 -2.51 0 142.42 205.7 32419 +1901 23 -2.91 -8.91 -4.56 0 123.97 208.17 32552 +1901 24 -7.01 -13.01 -8.66 0 93.18 211.49 32688 +1901 25 -7.25 -13.25 -8.9 0 91.61 213.29 32827 +1901 26 -5.69 -11.69 -7.34 0 102.27 214.57 32969 +1901 27 -6.63 -12.63 -8.28 0 95.72 216.74 33114 +1901 28 -11.28 -17.28 -12.93 0 68.4 220.04 33261 +1901 29 -13.02 -19.02 -14.67 0 60.09 222.64 33411 +1901 30 -13.82 -19.82 -15.47 0 56.57 224.89 33564 +1901 31 -6.81 -12.81 -8.46 0 94.51 225.36 33718 +1901 32 0.2 -5.8 -1.45 0 152.86 224.34 33875 +1901 33 -2.69 -8.69 -4.34 0.01 125.84 182.31 34035 +1901 34 0.94 -5.06 -0.71 0.62 160.54 182.3 34196 +1901 35 -3.32 -9.32 -4.97 0 120.54 232.38 34360 +1901 36 -5.62 -11.62 -7.27 0 102.78 235.64 34526 +1901 37 -3.7 -9.7 -5.35 0.37 117.43 189.79 34694 +1901 38 -5.97 -11.97 -7.62 0 100.28 241.63 34863 +1901 39 -5.69 -11.69 -7.34 0 102.27 243.97 35035 +1901 40 -3.3 -9.3 -4.95 0.02 120.7 195.13 35208 +1901 41 -4.39 -10.39 -6.04 0 111.97 248.4 35383 +1901 42 -5.89 -11.89 -7.54 0.01 100.85 199.48 35560 +1901 43 -5.03 -11.03 -6.68 0 107.1 253.62 35738 +1901 44 -2.09 -8.09 -3.74 0 131.09 254.68 35918 +1901 45 -4.86 -10.86 -6.51 0 108.37 258.41 36099 +1901 46 -4.6 -10.6 -6.25 0 110.35 260.83 36282 +1901 47 -3.64 -9.64 -5.29 0 117.92 263.05 36466 +1901 48 -0.3 -6.3 -1.95 0 147.86 263.93 36652 +1901 49 1.47 -4.53 -0.18 1.24 166.24 209.42 36838 +1901 50 3.44 -2.56 1.79 0.02 188.98 209.78 37026 +1901 51 6 0 4.35 0 222.51 265.85 37215 +1901 52 5.04 -0.96 3.39 0.02 209.38 211.54 37405 +1901 53 4.67 -1.33 3.02 0.04 204.5 213.3 37596 +1901 54 5.46 -0.54 3.81 0 215.04 272.65 37788 +1901 55 5.63 -0.37 3.98 0 217.37 274.7 37981 +1901 56 2.85 -3.15 1.2 0 181.9 279.3 38175 +1901 57 -0.37 -6.37 -2.02 0.26 147.17 223.1 38370 +1901 58 0.8 -5.2 -0.85 0 159.06 286.89 38565 +1901 59 -5.47 -11.47 -7.12 0.05 103.86 229.15 38761 +1901 60 7.62 1.62 5.97 1.5 246.26 223.09 38958 +1901 61 9.72 3.72 8.07 0.02 280.28 222.21 39156 +1901 62 5.31 -0.69 3.66 0 213 291.62 39355 +1901 63 5.46 -0.54 3.81 0.16 215.04 228.7 39553 +1901 64 7.53 1.53 5.88 0.08 244.89 195.7 39753 +1901 65 6.32 0.32 4.67 0 227.04 265.15 39953 +1901 66 7.67 1.67 6.02 0 247.03 266.38 40154 +1901 67 5.89 -0.11 4.24 0 220.97 271.26 40355 +1901 68 5.33 -0.67 3.68 0.96 213.27 206.05 40556 +1901 69 9.09 3.09 7.44 0 269.68 272.99 40758 +1901 70 9.36 3.36 7.71 0 274.18 275.46 40960 +1901 71 10.93 4.93 9.28 0 301.65 276.12 41163 +1901 72 10.65 4.65 9 0.05 296.59 209.5 41366 +1901 73 7.07 1.07 5.42 1 237.97 215.05 41569 +1901 74 8.9 2.9 7.25 0.31 266.55 215.38 41772 +1901 75 7.99 1.99 6.34 0 251.99 291.08 41976 +1901 76 2.87 -3.13 1.22 0 182.14 299.33 42179 +1901 77 5.22 -0.78 3.57 0.61 211.79 224.71 42383 +1901 78 5.76 -0.24 4.11 0.15 219.16 226.28 42587 +1901 79 7.18 1.18 5.53 0.01 239.61 227.07 42791 +1901 80 6.6 0.6 4.95 0.24 231.07 229.51 42996 +1901 81 6.8 0.8 5.15 0.21 233.98 231.28 43200 +1901 82 7.29 1.29 5.64 0.33 241.26 232.82 43404 +1901 83 8.5 2.5 6.85 0.04 260.06 233.48 43608 +1901 84 5.69 -0.31 4.04 1.54 218.19 238.08 43812 +1901 85 5.72 -0.28 4.07 0 218.61 319.94 44016 +1901 86 3.88 -2.12 2.23 0.43 194.41 243.32 44220 +1901 87 4.82 -1.18 3.17 0.38 206.47 244.48 44424 +1901 88 3.89 -2.11 2.24 0 194.54 329.38 44627 +1901 89 7.86 1.86 6.21 0.04 249.96 245.14 44831 +1901 90 6.24 0.24 4.59 0 225.9 331.37 45034 +1901 91 14.78 8.78 13.13 0.11 379.19 239.58 45237 +1901 92 14.59 8.59 12.94 0.02 375 241.53 45439 +1901 93 11.68 5.68 10.03 0.1 315.59 247.43 45642 +1901 94 12.65 6.65 11 0.01 334.42 247.69 45843 +1901 95 13.04 7.04 11.39 0.34 342.26 248.72 46045 +1901 96 10.45 4.45 8.8 0 293.01 338.44 46246 +1901 97 14.6 8.6 12.95 0 375.22 332.51 46446 +1901 98 13.7 7.7 12.05 0.22 355.89 252.27 46647 +1901 99 10.61 4.61 8.96 0 295.87 344.21 46846 +1901 100 12.31 6.31 10.66 0 327.71 343.06 47045 +1901 101 13.43 7.43 11.78 0 350.26 342.75 47243 +1901 102 15.52 9.52 13.87 0 395.89 340.02 47441 +1901 103 12.69 6.69 11.04 0.29 335.22 260.98 47638 +1901 104 12.21 6.21 10.56 0.04 325.76 263.05 47834 +1901 105 11.46 5.46 9.81 1.09 311.44 265.47 48030 +1901 106 12.1 6.1 10.45 0.34 323.63 265.79 48225 +1901 107 16.52 10.52 14.87 0 419.46 346.19 48419 +1901 108 15.18 9.18 13.53 0 388.14 351.18 48612 +1901 109 18.4 12.4 16.75 0.44 467.02 258.29 48804 +1901 110 19.42 13.42 17.77 0 494.69 342.74 48995 +1901 111 17.6 11.6 15.95 0 446.25 349.51 49185 +1901 112 17.67 11.67 16.02 0 448.04 350.8 49374 +1901 113 14.7 8.7 13.05 0.47 377.42 269.75 49561 +1901 114 11.01 5.01 9.36 0 303.11 368.87 49748 +1901 115 13.23 7.23 11.58 0 346.14 365.86 49933 +1901 116 10.86 4.86 9.21 0 300.38 371.82 50117 +1901 117 7.64 1.64 5.99 0 246.57 378.59 50300 +1901 118 13.04 7.04 11.39 0.51 342.26 277.59 50481 +1901 119 10.35 4.35 8.7 0 291.24 376.63 50661 +1901 120 5.66 -0.34 4.01 0.23 217.78 288.91 50840 +1901 121 9.06 3.06 7.41 0.55 269.18 285.92 51016 +1901 122 12.78 6.78 11.13 0.61 337.02 281.54 51191 +1901 123 12.28 6.28 10.63 0.53 327.13 283.1 51365 +1901 124 12.67 6.67 11.02 0 334.82 377.75 51536 +1901 125 13.41 7.41 11.76 0 349.85 377.14 51706 +1901 126 15.37 9.37 13.72 0.07 392.46 280.13 51874 +1901 127 14.6 8.6 12.95 0 375.22 376.29 52039 +1901 128 18.66 12.66 17.01 0 473.94 366.29 52203 +1901 129 16.2 10.2 14.55 0 411.79 374.11 52365 +1901 130 16.71 10.71 15.06 0 424.07 373.53 52524 +1901 131 15.25 9.25 13.6 0 389.73 378.14 52681 +1901 132 18.64 12.64 16.99 0 473.41 369.55 52836 +1901 133 16.91 10.91 15.26 0 428.97 375.29 52989 +1901 134 20.91 14.91 19.26 0.05 537.61 272.63 53138 +1901 135 22.61 16.61 20.96 0 590.41 357.95 53286 +1901 136 22.81 16.81 21.16 0.04 596.9 268.34 53430 +1901 137 21.6 15.6 19.95 0.07 558.54 272.27 53572 +1901 138 17.92 11.92 16.27 0 454.46 375.73 53711 +1901 139 17.35 11.35 15.7 0 439.92 378.07 53848 +1901 140 17.28 11.28 15.63 0.11 438.16 284.07 53981 +1901 141 17.55 11.55 15.9 0 444.98 378.41 54111 +1901 142 16.93 10.93 15.28 0 429.47 380.68 54238 +1901 143 18.4 12.4 16.75 0.67 467.02 282.68 54362 +1901 144 20.19 14.19 18.54 0.09 516.49 278.71 54483 +1901 145 23.85 17.85 22.2 0 631.63 358.29 54600 +1901 146 20.92 14.92 19.27 0.58 537.91 277.44 54714 +1901 147 22.38 16.38 20.73 1.43 583.02 273.75 54824 +1901 148 22.29 16.29 20.64 0.59 580.15 274.28 54931 +1901 149 19.18 13.18 17.53 0.78 488.06 282.71 55034 +1901 150 19.6 13.6 17.95 0.04 499.72 281.93 55134 +1901 151 17.82 11.82 16.17 0.02 451.88 286.4 55229 +1901 152 19.94 13.94 18.29 0.65 509.33 281.45 55321 +1901 153 16.41 10.41 14.76 0 416.81 386.25 55409 +1901 154 18.16 12.16 16.51 0 460.7 381.52 55492 +1901 155 21.58 15.58 19.93 0 557.92 370.23 55572 +1901 156 22 16 20.35 0 570.98 368.98 55648 +1901 157 25.86 19.86 24.21 0.02 703.64 264.64 55719 +1901 158 25.42 19.42 23.77 0.21 687.31 266.29 55786 +1901 159 27.27 21.27 25.62 0.01 758.19 259.79 55849 +1901 160 27.06 21.06 25.41 0.36 749.85 260.71 55908 +1901 161 24.97 18.97 23.32 0.5 670.94 268.17 55962 +1901 162 22.97 16.97 21.32 0.02 602.13 274.56 56011 +1901 163 26.21 20.21 24.56 0 716.86 352.09 56056 +1901 164 27.32 21.32 25.67 0.37 760.19 260 56097 +1901 165 26.4 20.4 24.75 0.17 724.13 263.48 56133 +1901 166 22.73 16.73 21.08 1.73 594.29 275.59 56165 +1901 167 21.16 15.16 19.51 0.03 545.11 280 56192 +1901 168 19.25 13.25 17.6 0.08 489.98 284.97 56214 +1901 169 20.35 14.35 18.7 0 521.12 376.29 56231 +1901 170 20.31 14.31 18.66 0.61 519.96 282.32 56244 +1901 171 21.77 15.77 20.12 0.86 563.79 278.43 56252 +1901 172 23.45 17.45 21.8 2.46 618.08 273.47 56256 +1901 173 20.31 14.31 18.66 0.62 519.96 282.35 56255 +1901 174 15.08 9.08 13.43 0.01 385.89 293.96 56249 +1901 175 13.24 7.24 11.59 0 346.35 396.35 56238 +1901 176 17.25 11.25 15.6 0 437.41 385.99 56223 +1901 177 23.25 17.25 21.6 0 611.39 365.19 56203 +1901 178 22.55 16.55 20.9 0 588.47 368.01 56179 +1901 179 21.05 15.05 19.4 0.01 541.8 280.15 56150 +1901 180 19.1 13.1 17.45 0.49 485.86 285.03 56116 +1901 181 20.86 14.86 19.21 0.87 536.12 280.51 56078 +1901 182 21.47 15.47 19.82 0.41 554.54 278.75 56035 +1901 183 22.53 16.53 20.88 0 587.83 367.48 55987 +1901 184 21.65 15.65 20 0 560.08 370.67 55935 +1901 185 25.43 19.43 23.78 0.02 687.68 266.24 55879 +1901 186 29.49 23.49 27.84 0.2 851.31 250.49 55818 +1901 187 28.05 22.05 26.4 0 789.88 341.69 55753 +1901 188 26.3 20.3 24.65 0.35 720.29 262.67 55684 +1901 189 27.46 21.46 25.81 0.07 765.81 258.25 55611 +1901 190 24.03 18.03 22.38 0.03 637.82 269.94 55533 +1901 191 21.22 15.22 19.57 0.01 546.93 277.99 55451 +1901 192 26.43 20.43 24.78 0.31 725.28 261.4 55366 +1901 193 24.25 18.25 22.6 0.35 645.44 268.63 55276 +1901 194 21.02 15.02 19.37 0.41 540.9 277.93 55182 +1901 195 19.92 13.92 18.27 0 508.76 374.1 55085 +1901 196 18.33 12.33 16.68 0.01 465.17 284.08 54984 +1901 197 20.98 14.98 19.33 0.09 539.7 277.19 54879 +1901 198 23.28 17.28 21.63 0.22 612.39 270.34 54770 +1901 199 24.75 18.75 23.1 0 663.06 353.94 54658 +1901 200 24.48 18.48 22.83 0 653.5 354.72 54542 +1901 201 24.67 18.67 23.02 0 660.22 353.45 54423 +1901 202 28.17 22.17 26.52 0.02 794.85 252.13 54301 +1901 203 27.7 21.7 26.05 0 775.52 338.14 54176 +1901 204 25.28 19.28 23.63 0 682.18 349.24 54047 +1901 205 22.19 16.19 20.54 0 576.97 361.45 53915 +1901 206 21.29 15.29 19.64 0 549.05 364.2 53780 +1901 207 23.56 17.56 21.91 0.54 621.78 266.17 53643 +1901 208 20.75 14.75 19.1 0 532.86 364.79 53502 +1901 209 19.15 13.15 17.5 0 487.23 369.43 53359 +1901 210 19.87 13.87 18.22 0.94 507.33 274.86 53213 +1901 211 20.42 14.42 18.77 0.02 523.16 272.91 53064 +1901 212 24.21 18.21 22.56 0.17 644.05 261.61 52913 +1901 213 21.53 15.53 19.88 0 556.38 358.46 52760 +1901 214 21.05 15.05 19.4 0.19 541.8 269.56 52604 +1901 215 20.77 14.77 19.12 0 533.45 359.71 52445 +1901 216 22.64 16.64 20.99 0.4 591.38 263.96 52285 +1901 217 24.74 18.74 23.09 0.81 662.71 256.96 52122 +1901 218 26.07 20.07 24.42 0 711.55 335.96 51958 +1901 219 27.76 21.76 26.11 0 777.97 326.88 51791 +1901 220 28.08 22.08 26.43 0 791.12 324.4 51622 +1901 221 25.37 19.37 23.72 0 685.47 336.24 51451 +1901 222 21.67 15.67 20.02 0.19 560.7 262.4 51279 +1901 223 20.64 14.64 18.99 0 529.61 352.29 51105 +1901 224 21.39 15.39 19.74 0.61 552.1 261.51 50929 +1901 225 22.56 16.56 20.91 0.17 588.79 257.5 50751 +1901 226 20.54 14.54 18.89 0 526.67 349.29 50572 +1901 227 19.67 13.67 18.02 0 501.68 350.82 50392 +1901 228 21.07 15.07 19.42 0.03 542.4 258.78 50210 +1901 229 23.25 17.25 21.6 1.07 611.39 251.98 50026 +1901 230 25.35 19.35 23.7 0.38 684.74 244.7 49842 +1901 231 22.81 16.81 21.16 0.05 596.9 251.22 49656 +1901 232 20.34 14.34 18.69 0.62 520.83 256.62 49469 +1901 233 23.11 17.11 21.46 0 606.75 331.14 49280 +1901 234 23.02 17.02 21.37 0.76 603.78 247.57 49091 +1901 235 18.99 12.99 17.34 0.29 482.86 256.5 48900 +1901 236 19.76 13.76 18.11 0 504.22 338.25 48709 +1901 237 19.7 13.7 18.05 0 502.53 336.8 48516 +1901 238 19.21 13.21 17.56 0 488.88 336.6 48323 +1901 239 20.61 14.61 18.96 0.16 528.72 248.1 48128 +1901 240 20.7 14.7 19.05 0 531.38 328.78 47933 +1901 241 20.61 14.61 18.96 0 528.72 327.36 47737 +1901 242 22.55 16.55 20.9 0 588.47 319.19 47541 +1901 243 22.65 16.65 21 0.06 591.7 237.77 47343 +1901 244 14.51 8.51 12.86 0.02 373.25 253.56 47145 +1901 245 13.49 7.49 11.84 0 351.51 338.35 46947 +1901 246 15.61 9.61 13.96 0 397.97 331.72 46747 +1901 247 18.16 12.16 16.51 1.51 460.7 242.62 46547 +1901 248 17.46 11.46 15.81 0.28 442.7 242.53 46347 +1901 249 15.68 9.68 14.03 2.56 399.59 244.21 46146 +1901 250 15.34 9.34 13.69 1.98 391.77 243.31 45945 +1901 251 15.81 9.81 14.16 0.64 402.61 240.9 45743 +1901 252 15.99 9.99 14.34 0.78 406.83 238.96 45541 +1901 253 16.4 10.4 14.75 0.43 416.57 236.64 45339 +1901 254 17.49 11.49 15.84 1.11 443.46 233.06 45136 +1901 255 21.55 15.55 19.9 0.39 557 222.88 44933 +1901 256 20.83 14.83 19.18 0.01 535.23 222.87 44730 +1901 257 21.48 15.48 19.83 0 554.85 293.09 44527 +1901 258 25.43 19.43 23.78 0 687.68 277.31 44323 +1901 259 30.62 24.62 28.97 0 902.3 252.38 44119 +1901 260 21.4 15.4 19.75 0.09 552.4 214.8 43915 +1901 261 21.25 15.25 19.6 1.05 547.84 213.36 43711 +1901 262 18.13 12.13 16.48 0.02 459.92 217.96 43507 +1901 263 17.87 11.87 16.22 0 453.17 288.8 43303 +1901 264 18.57 12.57 16.92 0.55 471.54 213.41 43099 +1901 265 15.6 9.6 13.95 0.02 397.74 216.74 42894 +1901 266 16.96 10.96 15.31 0 430.2 283.57 42690 +1901 267 16.74 10.74 15.09 0 424.8 281.4 42486 +1901 268 15.63 9.63 13.98 0 398.43 281.2 42282 +1901 269 14.33 8.33 12.68 0 369.33 281.23 42078 +1901 270 15.09 9.09 13.44 0 386.11 277.13 41875 +1901 271 13.33 7.33 11.68 0 348.2 277.76 41671 +1901 272 17.87 11.87 16.22 0.03 453.17 199.47 41468 +1901 273 18.1 12.1 16.45 0.09 459.14 197.21 41265 +1901 274 11.69 5.69 10.04 0.05 315.78 204.33 41062 +1901 275 13.28 7.28 11.63 0 347.17 267.07 40860 +1901 276 13.63 7.63 11.98 0 354.42 263.77 40658 +1901 277 15.91 9.91 14.26 0 404.95 256.94 40456 +1901 278 15.49 9.49 13.84 0.11 395.2 191.18 40255 +1901 279 16.77 10.77 15.12 0 425.54 249.63 40054 +1901 280 16.58 10.58 14.93 0 420.91 247.4 39854 +1901 281 17.4 11.4 15.75 0 441.18 243.08 39654 +1901 282 20.43 14.43 18.78 0 523.45 233.62 39455 +1901 283 16.87 10.87 15.22 0 427.99 238.7 39256 +1901 284 16.53 10.53 14.88 0.59 419.7 177.29 39058 +1901 285 17.7 11.7 16.05 0.82 448.8 173.63 38861 +1901 286 18.84 12.84 17.19 0 478.79 226.44 38664 +1901 287 16.61 10.61 14.96 0 421.64 228.06 38468 +1901 288 17.1 11.1 15.45 0 433.67 224.42 38273 +1901 289 16.38 10.38 14.73 0.09 416.09 167.39 38079 +1901 290 8.69 2.69 7.04 0.09 263.12 173.6 37885 +1901 291 9.54 3.54 7.89 1.03 277.21 170.82 37693 +1901 292 13.66 7.66 12.01 0 355.05 219.56 37501 +1901 293 10.06 4.06 8.41 0.42 286.15 166.26 37311 +1901 294 11.14 5.14 9.49 0.61 305.5 163.08 37121 +1901 295 12.42 6.42 10.77 0 329.87 212.93 36933 +1901 296 14.6 8.6 12.95 0 375.22 207.22 36745 +1901 297 15.08 9.08 13.43 0 385.89 203.8 36560 +1901 298 14.86 8.86 13.21 0 380.96 201.58 36375 +1901 299 13.77 7.77 12.12 0 357.36 200.45 36191 +1901 300 12.41 6.41 10.76 0 329.68 199.66 36009 +1901 301 12.69 6.69 11.04 0 335.22 196.8 35829 +1901 302 9.58 3.58 7.93 0 277.89 197.88 35650 +1901 303 10.75 4.75 9.1 0.13 298.39 145.51 35472 +1901 304 12.73 6.73 11.08 0 336.02 189.18 35296 +1901 305 8.48 2.48 6.83 0 259.74 191.2 35122 +1901 306 10.81 4.81 9.16 0 299.47 186.52 34950 +1901 307 8.67 2.67 7.02 0 262.8 186.24 34779 +1901 308 7.94 1.94 6.29 0.28 251.21 138.23 34610 +1901 309 6.12 0.12 4.47 0.15 224.2 137.66 34444 +1901 310 2.48 -3.52 0.83 1.21 177.58 137.75 34279 +1901 311 5.5 -0.5 3.85 0 215.58 179.36 34116 +1901 312 4.42 -1.58 2.77 0 201.26 177.48 33956 +1901 313 3.37 -2.63 1.72 0 188.13 176.05 33797 +1901 314 3.7 -2.3 2.05 0 192.17 173.84 33641 +1901 315 7.4 1.4 5.75 0 242.92 168.55 33488 +1901 316 11.5 5.5 9.85 0.15 312.19 121.89 33337 +1901 317 10.6 4.6 8.95 0 295.69 161.28 33188 +1901 318 5.79 -0.21 4.14 0 219.58 163.07 33042 +1901 319 13.77 7.77 12.12 0 357.36 153.87 32899 +1901 320 14.31 8.31 12.66 0.16 368.89 113.56 32758 +1901 321 12.28 6.28 10.63 0 327.13 151.67 32620 +1901 322 12.58 6.58 10.93 0 333.03 149.56 32486 +1901 323 8.91 2.91 7.26 0 266.71 151.5 32354 +1901 324 5.25 -0.75 3.6 1.34 212.19 114.17 32225 +1901 325 1.49 -4.51 -0.16 0 166.46 152.72 32100 +1901 326 1.57 -4.43 -0.08 0 167.33 151.2 31977 +1901 327 -4.03 -10.03 -5.68 0 114.79 151.73 31858 +1901 328 -1.09 -7.09 -2.74 1.1 140.24 156.35 31743 +1901 329 0.78 -5.22 -0.87 0 158.85 191.19 31631 +1901 330 1.19 -4.81 -0.46 0 163.21 189.53 31522 +1901 331 0.26 -5.74 -1.39 0 153.47 188.75 31417 +1901 332 7.33 1.33 5.68 0 241.86 182.19 31316 +1901 333 3.83 -2.17 2.18 0.07 193.79 148.24 31218 +1901 334 1.63 -4.37 -0.02 0.21 167.99 148.21 31125 +1901 335 1.53 -4.47 -0.12 0 166.89 181.78 31035 +1901 336 3.14 -2.86 1.49 0 185.35 179.59 30949 +1901 337 3.93 -2.07 2.28 0.07 195.04 143.59 30867 +1901 338 5.65 -0.35 4 0.04 217.64 99.02 30790 +1901 339 4.13 -1.87 2.48 0 197.56 132.14 30716 +1901 340 6.29 0.29 4.64 0 226.61 130.1 30647 +1901 341 5.55 -0.45 3.9 0 216.27 129.65 30582 +1901 342 8.8 2.8 7.15 0.02 264.91 95.01 30521 +1901 343 8.87 2.87 7.22 0 266.06 125.81 30465 +1901 344 12.15 6.15 10.5 0.08 324.6 91.46 30413 +1901 345 8.8 2.8 7.15 0.86 264.91 93.24 30366 +1901 346 7.66 1.66 6.01 0 246.88 124.6 30323 +1901 347 7.1 1.1 5.45 0.01 238.41 93.29 30284 +1901 348 6.97 0.97 5.32 0.11 236.48 93.1 30251 +1901 349 6.84 0.84 5.19 0 234.57 123.84 30221 +1901 350 5.01 -0.99 3.36 0.52 208.98 93.47 30197 +1901 351 4.72 -1.28 3.07 0 205.16 124.58 30177 +1901 352 5.64 -0.36 3.99 0 217.5 123.95 30162 +1901 353 5.34 -0.66 3.69 0 213.41 124.06 30151 +1901 354 5.59 -0.41 3.94 0 216.82 123.88 30145 +1901 355 5.66 -0.34 4.01 0 217.78 123.84 30144 +1901 356 6.77 0.77 5.12 0.06 233.54 92.38 30147 +1901 357 2.12 -3.88 0.47 0.14 173.47 94.37 30156 +1901 358 2.51 -3.49 0.86 0.14 177.93 94.3 30169 +1901 359 5.08 -0.92 3.43 0.69 209.91 93.35 30186 +1901 360 4.82 -1.18 3.17 2.14 206.47 93.74 30208 +1901 361 3.25 -2.75 1.6 0.01 186.68 94.63 30235 +1901 362 3.49 -2.51 1.84 0 189.59 126.49 30267 +1901 363 4.68 -1.32 3.03 0 204.63 126.42 30303 +1901 364 5.8 -0.2 4.15 0 219.72 126.15 30343 +1901 365 2.12 -3.88 0.47 0 173.47 128.74 30388 +1902 1 0.23 -5.77 -1.42 0.97 153.17 97.87 30438 +1902 2 -0.88 -6.88 -2.53 0.28 142.23 142.94 30492 +1902 3 0.28 -5.72 -1.37 0.33 153.68 143.17 30551 +1902 4 1.61 -4.39 -0.04 1.01 167.77 143.1 30614 +1902 5 3.63 -2.37 1.98 0.19 191.31 142.24 30681 +1902 6 6.06 0.06 4.41 0 223.35 131.53 30752 +1902 7 6.04 0.04 4.39 0.37 223.07 99.25 30828 +1902 8 5.02 -0.98 3.37 0.31 209.11 100.84 30907 +1902 9 7.12 1.12 5.47 0.06 238.71 100.75 30991 +1902 10 2.64 -3.36 0.99 0.03 179.44 103.77 31079 +1902 11 2.12 -3.88 0.47 0 173.47 139.62 31171 +1902 12 4.33 -1.67 2.68 0 200.11 139.41 31266 +1902 13 3.46 -2.54 1.81 0 189.23 141.54 31366 +1902 14 5.14 -0.86 3.49 0 210.72 142 31469 +1902 15 6.59 0.59 4.94 0 230.92 142.47 31575 +1902 16 12.54 6.54 10.89 0 332.24 138.63 31686 +1902 17 8.6 2.6 6.95 0 261.67 143.88 31800 +1902 18 11.86 5.86 10.21 0.01 319.01 107.1 31917 +1902 19 12.19 6.19 10.54 0 325.37 144.35 32038 +1902 20 6.89 0.89 5.24 0 235.3 150.56 32161 +1902 21 6.68 0.68 5.03 0 232.23 152.71 32289 +1902 22 4.83 -1.17 3.18 0 206.6 155.74 32419 +1902 23 4.51 -1.49 2.86 0 202.42 157.72 32552 +1902 24 2.93 -3.07 1.28 0 182.85 160.77 32688 +1902 25 0.67 -5.33 -0.98 0 157.7 163.92 32827 +1902 26 4.88 -1.12 3.23 0.05 207.26 122.51 32969 +1902 27 5.6 -0.4 3.95 0 216.95 164.85 33114 +1902 28 7.91 1.91 6.26 0 250.74 165.23 33261 +1902 29 8.51 2.51 6.86 0 260.22 167.06 33411 +1902 30 7.79 1.79 6.14 0 248.88 169.9 33564 +1902 31 1.88 -4.12 0.23 0.08 170.77 132.37 33718 +1902 32 -3.16 -9.16 -4.81 2.66 121.87 182.37 33875 +1902 33 -3.37 -9.37 -5.02 1.59 120.12 188.7 34035 +1902 34 -4.19 -10.19 -5.84 2.1 113.53 196.29 34196 +1902 35 -0.81 -6.81 -2.46 0.01 142.9 196.54 34360 +1902 36 5.26 -0.74 3.61 0.51 212.33 194.68 34526 +1902 37 6.14 0.14 4.49 0.86 224.48 194.99 34694 +1902 38 3.89 -2.11 2.24 1.65 194.54 197.62 34863 +1902 39 0.75 -5.25 -0.9 0.18 158.54 200.77 35035 +1902 40 2.96 -3.04 1.31 0.9 183.21 201.09 35208 +1902 41 6.17 0.17 4.52 0 224.9 249.76 35383 +1902 42 6.18 0.18 4.53 0 225.05 251.34 35560 +1902 43 7.21 1.21 5.56 0.02 240.06 201.45 35738 +1902 44 3.66 -2.34 2.01 0 191.68 256.91 35918 +1902 45 0.91 -5.09 -0.74 0.13 160.22 207.98 36099 +1902 46 4.62 -1.38 2.97 0.18 203.85 207.26 36282 +1902 47 9.12 3.12 7.47 0.85 270.17 204.93 36466 +1902 48 0.93 -5.07 -0.72 0.23 160.43 211.92 36652 +1902 49 -1.84 -7.84 -3.49 0.05 133.32 215.15 36838 +1902 50 2.02 -3.98 0.37 0 172.34 271.32 37026 +1902 51 3.62 -2.38 1.97 0.17 191.19 215.65 37215 +1902 52 4.64 -1.36 2.99 0 204.11 273.76 37405 +1902 53 8.12 2.12 6.47 0.01 254.02 215.02 37596 +1902 54 8.27 2.27 6.62 0 256.39 273.73 37788 +1902 55 5.49 -0.51 3.84 0 215.45 278.72 37981 +1902 56 6.89 0.89 5.24 0 235.3 279.11 38175 +1902 57 6.54 0.54 4.89 0.12 230.2 220.98 38370 +1902 58 7.34 1.34 5.69 0 242.01 282.57 38565 +1902 59 9.73 3.73 8.08 0.25 280.45 220.3 38761 +1902 60 14.67 8.67 13.02 0 376.76 275.1 38958 +1902 61 13.39 7.39 11.74 0 349.43 278.51 39156 +1902 62 12.51 6.51 10.86 0 331.65 248.48 39355 +1902 63 11.02 5.02 9.37 0 303.3 253.62 39553 +1902 64 10.92 4.92 9.27 0.06 301.47 192.47 39753 +1902 65 7.75 1.75 6.1 0.15 248.26 197.67 39953 +1902 66 6.95 0.95 5.3 0 236.19 267.21 40154 +1902 67 8.67 2.67 7.02 0 262.8 268.06 40355 +1902 68 6.84 0.84 5.19 0 234.57 273.11 40556 +1902 69 5.99 -0.01 4.34 0 222.37 276.67 40758 +1902 70 5.43 -0.57 3.78 0 214.63 280.13 40960 +1902 71 5.86 -0.14 4.21 0 220.55 282.6 41163 +1902 72 5.59 -0.41 3.94 0.01 216.82 214.3 41366 +1902 73 6.2 0.2 4.55 0 225.33 287.74 41569 +1902 74 5.99 -0.01 4.34 0 222.37 290.74 41772 +1902 75 7.36 1.36 5.71 0.11 242.31 218.9 41976 +1902 76 5.21 -0.79 3.56 0.12 211.65 222.75 42179 +1902 77 5.93 -0.07 4.28 0.11 221.53 224.12 42383 +1902 78 9.76 3.76 8.11 0.07 280.97 222.41 42587 +1902 79 8.12 2.12 6.47 0.38 254.02 226.16 42791 +1902 80 5.87 -0.13 4.22 0 220.69 306.88 42996 +1902 81 5.77 -0.23 4.12 0.14 219.3 232.2 43200 +1902 82 5.18 -0.82 3.53 0.1 211.25 234.71 43404 +1902 83 5.77 -0.23 4.12 1.03 219.3 236.09 43608 +1902 84 4.08 -1.92 2.43 1.16 196.93 239.42 43812 +1902 85 4.38 -1.62 2.73 0 200.75 321.45 44016 +1902 86 8.73 2.73 7.08 0 263.77 318.44 44220 +1902 87 8.8 2.8 7.15 0 264.91 320.87 44424 +1902 88 6.24 0.24 4.59 0 225.9 326.68 44627 +1902 89 3.49 -2.51 1.84 0 189.59 332.12 44831 +1902 90 1.93 -4.07 0.28 0 171.33 336.08 45034 +1902 91 4.87 -1.13 3.22 0 207.13 335.31 45237 +1902 92 8.31 2.31 6.66 0 257.03 333.13 45439 +1902 93 12.29 6.29 10.64 0 327.32 328.8 45642 +1902 94 11.47 5.47 9.82 0 311.63 332.43 45843 +1902 95 13.75 7.75 12.1 0 356.94 330.2 46045 +1902 96 10.52 4.52 8.87 0.15 294.26 253.74 46246 +1902 97 8.81 2.81 7.16 0.77 265.08 257.35 46446 +1902 98 10.1 4.1 8.45 0.16 286.85 257.29 46647 +1902 99 6.75 0.75 5.1 0.09 233.25 262.59 46846 +1902 100 6.8 0.8 5.15 0.79 233.98 264.03 47045 +1902 101 12.52 6.52 10.87 0.13 331.84 258.43 47243 +1902 102 14.25 8.25 12.6 0.58 367.6 257.17 47441 +1902 103 14.62 8.62 12.97 0.13 375.66 257.92 47638 +1902 104 13.98 7.98 12.33 0.81 361.81 260.33 47834 +1902 105 15.07 9.07 13.42 0.71 385.66 259.83 48030 +1902 106 11.94 5.94 10.29 0.05 320.54 266.02 48225 +1902 107 13.88 7.88 12.23 0 359.69 352.4 48419 +1902 108 16.37 10.37 14.72 0.04 415.85 261.21 48612 +1902 109 15.26 9.26 13.61 0 389.95 352.58 48804 +1902 110 15.57 9.57 13.92 0.22 397.04 264.92 48995 +1902 111 17.38 11.38 15.73 0 440.68 350.11 49185 +1902 112 16.53 10.53 14.88 0 419.7 353.85 49374 +1902 113 12.77 6.77 11.12 0 336.82 363.9 49561 +1902 114 13 7 11.35 0 341.45 364.92 49748 +1902 115 15.67 9.67 14.02 0 399.35 360.23 49933 +1902 116 12.39 6.39 10.74 0 329.28 368.84 50117 +1902 117 12.66 6.66 11.01 0 334.62 369.6 50300 +1902 118 11.78 5.78 10.13 0.41 317.49 279.53 50481 +1902 119 12.69 6.69 11.04 0 335.22 372.06 50661 +1902 120 13.61 7.61 11.96 0.3 354.01 278.44 50840 +1902 121 11.83 5.83 10.18 1.19 318.44 282.1 51016 +1902 122 12.12 6.12 10.47 1.78 324.02 282.57 51191 +1902 123 13.92 7.92 12.27 0 360.53 373.91 51365 +1902 124 16.4 10.4 14.75 0.99 416.57 276.67 51536 +1902 125 11.98 5.98 10.33 0.26 321.31 285.13 51706 +1902 126 10.43 4.43 8.78 0 292.66 384.2 51874 +1902 127 11.83 5.83 10.18 0.29 318.44 286.79 52039 +1902 128 13.18 7.18 11.53 0.01 345.12 285.41 52203 +1902 129 16.11 10.11 14.46 0.13 409.66 280.76 52365 +1902 130 16.4 10.4 14.75 0.14 416.57 280.77 52524 +1902 131 15.37 9.37 13.72 1.07 392.46 283.38 52681 +1902 132 18.68 12.68 17.03 0.12 474.48 277.07 52836 +1902 133 16.18 10.18 14.53 0.03 411.32 282.95 52989 +1902 134 15.1 9.1 13.45 0.49 386.34 285.57 53138 +1902 135 14.2 8.2 12.55 0 366.52 383.65 53286 +1902 136 11.81 5.81 10.16 0 318.06 389.57 53430 +1902 137 13.45 7.45 11.8 0.05 350.68 290.06 53572 +1902 138 17.03 11.03 15.38 0.28 431.94 283.72 53711 +1902 139 15.42 9.42 13.77 0.55 393.6 287.48 53848 +1902 140 8.31 2.31 6.66 0.67 257.03 298.94 53981 +1902 141 11.52 5.52 9.87 1.56 312.57 294.86 54111 +1902 142 12.5 6.5 10.85 0.01 331.45 293.71 54238 +1902 143 12.58 6.58 10.93 0.75 333.03 293.99 54362 +1902 144 9.07 3.07 7.42 0 269.35 399.31 54483 +1902 145 10.27 4.27 8.62 0.11 289.83 298.22 54600 +1902 146 7 1 5.35 0.24 236.93 302.69 54714 +1902 147 13.38 7.38 11.73 0 349.23 392.04 54824 +1902 148 13.54 7.54 11.89 0 352.55 392.06 54931 +1902 149 18.77 12.77 17.12 0 476.9 378.24 55034 +1902 150 18.92 12.92 17.27 0.16 480.96 283.58 55134 +1902 151 16.3 10.3 14.65 0.6 414.18 289.65 55229 +1902 152 19.51 13.51 17.86 1.47 497.2 282.52 55321 +1902 153 17.66 11.66 16.01 0.38 447.78 287.02 55409 +1902 154 16.98 10.98 15.33 0.13 430.7 288.74 55492 +1902 155 14.35 8.35 12.7 0 369.76 392.09 55572 +1902 156 18.84 12.84 17.19 0.06 478.79 284.94 55648 +1902 157 19.66 13.66 18.01 0 501.4 377.44 55719 +1902 158 20.27 14.27 18.62 0.29 518.8 281.66 55786 +1902 159 21.51 15.51 19.86 0.78 555.77 278.53 55849 +1902 160 20.46 14.46 18.81 0.05 524.33 281.49 55908 +1902 161 21.15 15.15 19.5 2.09 544.81 279.7 55962 +1902 162 21.21 15.21 19.56 1.3 546.63 279.59 56011 +1902 163 17.85 11.85 16.2 0 452.65 384.08 56056 +1902 164 17.64 11.64 15.99 0 447.27 384.75 56097 +1902 165 24.53 18.53 22.88 0 655.26 359.9 56133 +1902 166 19.4 13.4 17.75 0.03 494.14 284.59 56165 +1902 167 19.63 13.63 17.98 0 500.56 378.64 56192 +1902 168 22.37 16.37 20.72 0.04 582.7 276.66 56214 +1902 169 17.31 11.31 15.66 0 438.92 385.93 56231 +1902 170 11.84 5.84 10.19 0.49 318.63 299.62 56244 +1902 171 15.43 9.43 13.78 0.64 393.83 293.37 56252 +1902 172 15.43 9.43 13.78 0.16 393.83 293.36 56256 +1902 173 20.87 14.87 19.22 0 536.42 374.5 56255 +1902 174 21.66 15.66 20.01 0.22 560.39 278.66 56249 +1902 175 18.18 12.18 16.53 0.2 461.23 287.45 56238 +1902 176 17.61 11.61 15.96 0.74 446.5 288.7 56223 +1902 177 22.85 16.85 21.2 0 598.2 366.79 56203 +1902 178 21.56 15.56 19.91 0 557.3 371.77 56179 +1902 179 24.67 18.67 23.02 0 660.22 359.11 56150 +1902 180 20.5 14.5 18.85 0 525.5 375.35 56116 +1902 181 18.16 12.16 16.51 2.16 460.7 287.18 56078 +1902 182 21.09 15.09 19.44 0.12 543 279.79 56035 +1902 183 18.38 12.38 16.73 0.68 466.49 286.43 55987 +1902 184 17.12 11.12 15.47 0.7 434.17 289.12 55935 +1902 185 17.7 11.7 16.05 1.72 448.8 287.79 55879 +1902 186 14.98 8.98 13.33 0 383.64 390.9 55818 +1902 187 19.12 13.12 17.47 0 486.41 378.89 55753 +1902 188 22.02 16.02 20.37 0 571.61 368.5 55684 +1902 189 19.18 13.18 17.53 0.32 488.06 283.69 55611 +1902 190 18.76 12.76 17.11 0.15 476.63 284.41 55533 +1902 191 21.35 15.35 19.7 0.22 550.88 277.63 55451 +1902 192 22.66 16.66 21.01 0.3 592.02 273.7 55366 +1902 193 23.95 17.95 22.3 0.07 635.06 269.58 55276 +1902 194 23.61 17.61 21.96 1.18 623.47 270.48 55182 +1902 195 25.99 19.99 24.34 1.86 708.52 262.43 55085 +1902 196 26.06 20.06 24.41 0.26 711.17 261.89 54984 +1902 197 22.47 16.47 20.82 0.05 585.9 273.05 54879 +1902 198 23.08 17.08 21.43 1.01 605.76 270.94 54770 +1902 199 22.29 16.29 20.64 0.24 580.15 272.99 54658 +1902 200 20.38 14.38 18.73 0.12 522 277.87 54542 +1902 201 21.85 15.85 20.2 0 566.28 364.79 54423 +1902 202 24.78 18.78 23.13 0.16 664.13 264.32 54301 +1902 203 26.37 20.37 24.72 0 722.97 344.69 54176 +1902 204 22.1 16.1 20.45 0.58 574.13 271.72 54047 +1902 205 19.36 13.36 17.71 0 493.03 371.31 53915 +1902 206 20.26 14.26 18.61 0 518.51 367.78 53780 +1902 207 23.89 17.89 22.24 0 633 353.54 53643 +1902 208 22.11 16.11 20.46 0 574.44 359.89 53502 +1902 209 21.32 15.32 19.67 0.3 549.96 271.6 53359 +1902 210 21.55 15.55 19.9 0 557 360.69 53213 +1902 211 23.9 17.9 22.25 0 633.35 350.86 53064 +1902 212 20.32 14.32 18.67 0.36 520.25 272.57 52913 +1902 213 18.49 12.49 16.84 0.28 469.41 276.37 52760 +1902 214 17.4 11.4 15.75 0 441.18 370.92 52604 +1902 215 14.56 8.56 12.91 0 374.34 377.62 52445 +1902 216 16.94 10.94 15.29 0 429.71 370.48 52285 +1902 217 20.01 14.01 18.36 0 511.32 360.36 52122 +1902 218 21.09 15.09 19.44 0 543 355.9 51958 +1902 219 22.92 16.92 21.27 0 600.49 348.18 51791 +1902 220 22.13 16.13 20.48 0 575.07 350.22 51622 +1902 221 20.53 14.53 18.88 0.08 526.38 266.13 51451 +1902 222 18.87 12.87 17.22 0 479.6 359.08 51279 +1902 223 22.12 16.12 20.47 0.03 574.76 260.34 51105 +1902 224 20.97 14.97 19.32 0 539.4 350.12 50929 +1902 225 25.06 19.06 23.41 0 674.19 333.38 50751 +1902 226 21.4 15.4 19.75 0 552.4 346.38 50572 +1902 227 25.88 19.88 24.23 0 704.39 327.5 50392 +1902 228 25.54 19.54 23.89 0 691.73 327.83 50210 +1902 229 25.32 19.32 23.67 0 683.64 327.6 50026 +1902 230 25.41 19.41 23.76 0 686.94 326.01 49842 +1902 231 24.31 18.31 22.66 0 647.54 329.16 49656 +1902 232 21.43 15.43 19.78 0 553.32 338.55 49469 +1902 233 24.28 18.28 22.63 0.02 646.49 244.96 49280 +1902 234 21.36 15.36 19.71 0.07 551.18 251.99 49091 +1902 235 27.53 21.53 25.88 1.05 768.63 232.28 48900 +1902 236 25.61 19.61 23.96 0.97 694.32 237.75 48709 +1902 237 21.76 15.76 20.11 0.05 563.48 247.6 48516 +1902 238 21.76 15.76 20.11 0.06 563.48 246.37 48323 +1902 239 21.37 15.37 19.72 0.12 551.49 246.25 48128 +1902 240 19.49 13.49 17.84 0.15 496.64 249.38 47933 +1902 241 21.35 15.35 19.7 0.08 550.88 243.73 47737 +1902 242 18.15 12.15 16.5 0 460.44 332.87 47541 +1902 243 20.8 14.8 19.15 0.03 534.34 242.41 47343 +1902 244 19.92 13.92 18.27 0 508.76 324.12 47145 +1902 245 21.6 15.6 19.95 1.19 558.54 237.77 46947 +1902 246 17.51 11.51 15.86 0 443.96 327.06 46747 +1902 247 18.11 12.11 16.46 0 459.4 323.62 46547 +1902 248 23.23 17.23 21.58 0 610.73 305.87 46347 +1902 249 21.79 15.79 20.14 0.47 564.42 231.58 46146 +1902 250 18.61 12.61 16.96 0.12 472.61 237.25 45945 +1902 251 19.54 13.54 17.89 0 498.04 311.66 45743 +1902 252 17.97 11.97 16.32 0.14 455.76 235.33 45541 +1902 253 19.28 13.28 17.63 0 490.81 308.16 45339 +1902 254 17.41 11.41 15.76 0.24 441.43 233.21 45136 +1902 255 17.07 11.07 15.42 0.21 432.93 232.14 44933 +1902 256 14.63 8.63 12.98 0 375.88 312.71 44730 +1902 257 17.65 11.65 16 0 447.52 303.68 44527 +1902 258 16.28 10.28 14.63 0 413.7 304.58 44323 +1902 259 14.45 8.45 12.8 0 371.94 306.06 44119 +1902 260 12.54 6.54 10.89 0 332.24 307.27 43915 +1902 261 17.42 11.42 15.77 0 441.69 294.68 43711 +1902 262 15.82 9.82 14.17 0.28 402.84 221.95 43507 +1902 263 16.71 10.71 15.06 0.11 424.07 218.63 43303 +1902 264 15.81 9.81 14.16 0 402.61 290.92 43099 +1902 265 16.93 10.93 15.28 0 429.47 286.1 42894 +1902 266 12.18 6.18 10.53 0 325.18 292.92 42690 +1902 267 15.38 9.38 13.73 0 392.69 284.28 42486 +1902 268 18.68 12.68 17.03 0 474.48 274.36 42282 +1902 269 18.76 12.76 17.11 0 476.63 271.7 42078 +1902 270 22.13 16.13 20.48 0 575.07 260.1 41875 +1902 271 23.04 17.04 21.39 0.78 604.44 191.16 41671 +1902 272 24.91 18.91 23.26 0.02 668.79 184.72 41468 +1902 273 23.35 17.35 21.7 0.15 614.73 186.72 41265 +1902 274 14.64 8.64 12.99 0 376.1 267.44 41062 +1902 275 18.69 12.69 17.04 0 474.75 256.27 40860 +1902 276 19.81 13.81 18.16 0.04 505.63 188.22 40658 +1902 277 17.6 11.6 15.95 0.16 446.25 190.11 40456 +1902 278 16.81 10.81 15.16 0.88 426.52 189.23 40255 +1902 279 16.96 10.96 15.31 0 430.2 249.24 40054 +1902 280 17.61 11.61 15.96 0.36 446.5 183.97 39854 +1902 281 13.71 7.71 12.06 0 356.1 249.92 39654 +1902 282 9.45 3.45 7.8 0.11 275.69 190.01 39455 +1902 283 9.83 3.83 8.18 0.02 282.17 187.5 39256 +1902 284 10.42 4.42 8.77 0.86 292.48 184.63 39058 +1902 285 13.95 7.95 12.3 0 361.17 238.34 38861 +1902 286 9.29 3.29 7.64 0.07 273.01 181.6 38664 +1902 287 9.56 3.56 7.91 0.14 277.55 179.13 38468 +1902 288 12.15 6.15 10.5 0.37 324.6 174.46 38273 +1902 289 11.88 5.88 10.23 0.26 319.39 172.77 38079 +1902 290 8.17 2.17 6.52 0.98 254.81 174.04 37885 +1902 291 12.58 6.58 10.93 0.72 333.03 167.86 37693 +1902 292 11.92 5.92 10.27 0.11 320.16 166.53 37501 +1902 293 9.92 3.92 8.27 0.07 283.72 166.38 37311 +1902 294 10.95 4.95 9.3 0.04 302.02 163.26 37121 +1902 295 12.95 6.95 11.3 0.3 340.44 159.15 36933 +1902 296 8.77 2.77 7.12 1.23 264.42 161.07 36745 +1902 297 8.29 2.29 6.64 0.08 256.71 159.39 36560 +1902 298 10.42 4.42 8.77 0 292.48 207.55 36375 +1902 299 12.54 6.54 10.89 2.35 332.24 151.6 36191 +1902 300 10.98 4.98 9.33 0.81 302.56 151.08 36009 +1902 301 11.45 5.45 9.8 0.31 311.26 148.77 35829 +1902 302 10.57 4.57 8.92 0 295.15 196.79 35650 +1902 303 14.85 8.85 13.2 0.8 380.74 141.53 35472 +1902 304 18.81 12.81 17.16 0 477.98 179.83 35296 +1902 305 7.55 1.55 5.9 0 245.19 192.07 35122 +1902 306 8.86 2.86 7.21 0 265.89 188.56 34950 +1902 307 10.02 4.02 8.37 0.46 285.45 138.66 34779 +1902 308 5.87 -0.13 4.22 0 220.69 186.08 34610 +1902 309 6.48 0.48 4.83 0 229.33 183.25 34444 +1902 310 6.11 0.11 4.46 0 224.06 181.09 34279 +1902 311 9.13 3.13 7.48 0 270.34 176.25 34116 +1902 312 7.31 1.31 5.66 0 241.56 175.25 33956 +1902 313 6.53 0.53 4.88 0 230.05 173.76 33797 +1902 314 3.5 -2.5 1.85 0 189.71 173.98 33641 +1902 315 4.32 -1.68 2.67 0 199.98 170.87 33488 +1902 316 5.08 -0.92 3.43 0 209.91 168.14 33337 +1902 317 3.81 -2.19 2.16 0.47 193.54 125.09 33188 +1902 318 2.92 -3.08 1.27 0 182.73 164.98 33042 +1902 319 -2.9 -8.9 -4.55 0 124.05 166.14 32899 +1902 320 -3.28 -9.28 -4.93 0 120.87 164.37 32758 +1902 321 1.42 -4.58 -0.23 0 165.69 160.07 32620 +1902 322 7.81 1.81 6.16 0 249.19 154.02 32486 +1902 323 8.54 2.54 6.89 0 260.7 151.82 32354 +1902 324 8.83 2.83 7.18 0 265.4 149.53 32225 +1902 325 8.57 2.57 6.92 0.01 261.19 111.03 32100 +1902 326 2.83 -3.17 1.18 0.19 181.67 112.89 31977 +1902 327 0.85 -5.15 -0.8 0 159.59 149.69 31858 +1902 328 -2.12 -8.12 -3.77 0 130.82 149.01 31743 +1902 329 -3.18 -9.18 -4.83 0 121.7 147.89 31631 +1902 330 -1.3 -7.3 -2.95 0 138.27 145.68 31522 +1902 331 1.11 -4.89 -0.54 0 162.35 143.26 31417 +1902 332 1.41 -4.59 -0.24 0 165.58 141.46 31316 +1902 333 1.23 -4.77 -0.42 0.27 163.64 105.33 31218 +1902 334 2.42 -3.58 0.77 0.2 176.89 104.05 31125 +1902 335 0.87 -5.13 -0.78 0.04 159.8 103.74 31035 +1902 336 -2.16 -8.16 -3.81 0 130.46 138.5 30949 +1902 337 -1.03 -7.03 -2.68 0 140.81 136.38 30867 +1902 338 1.03 -4.97 -0.62 0 161.49 134.53 30790 +1902 339 -1.57 -7.57 -3.22 0.06 135.78 144.28 30716 +1902 340 0.22 -5.78 -1.43 0 153.07 176.58 30647 +1902 341 -0.41 -6.41 -2.06 0 146.78 176.01 30582 +1902 342 1.29 -4.71 -0.36 0 164.28 131.17 30521 +1902 343 -1.77 -7.77 -3.42 0.09 133.96 142.33 30465 +1902 344 -5.11 -11.11 -6.76 0.16 106.5 142.89 30413 +1902 345 -1.25 -7.25 -2.9 0 138.74 174.1 30366 +1902 346 0.25 -5.75 -1.4 0 153.37 172.97 30323 +1902 347 3.67 -2.33 2.02 0 191.8 170.3 30284 +1902 348 2.01 -3.99 0.36 0 172.22 170.57 30251 +1902 349 -1.44 -7.44 -3.09 0.27 136.97 140.55 30221 +1902 350 -1.69 -7.69 -3.34 0 134.68 172.34 30197 +1902 351 1.43 -4.57 -0.22 0 165.8 170.68 30177 +1902 352 -2.23 -8.23 -3.88 0 129.85 172.08 30162 +1902 353 2.56 -3.44 0.91 0 178.51 169.67 30151 +1902 354 2.67 -3.33 1.02 0 179.79 125.48 30145 +1902 355 3.41 -2.59 1.76 0 188.62 125.1 30144 +1902 356 1.57 -4.43 -0.08 0 167.33 126.03 30147 +1902 357 0.02 -5.98 -1.63 0 151.05 126.77 30156 +1902 358 -1.64 -7.64 -3.29 0 135.14 127.51 30169 +1902 359 -0.32 -6.32 -1.97 0.22 147.66 139.77 30186 +1902 360 -2.29 -8.29 -3.94 0.23 129.32 141.3 30208 +1902 361 -5.15 -11.15 -6.8 0 106.21 174.58 30235 +1902 362 -2.86 -8.86 -4.51 0 124.39 174.26 30267 +1902 363 -0.41 -6.41 -2.06 0 146.78 173.88 30303 +1902 364 -1.46 -7.46 -3.11 0 136.79 174.63 30343 +1902 365 1.32 -4.68 -0.33 0 164.61 173.8 30388 +1903 1 -1.34 -7.34 -2.99 0 137.9 175.75 30438 +1903 2 -1.37 -7.37 -3.02 0.1 137.62 143.76 30492 +1903 3 -5.93 -11.93 -7.58 0.12 100.56 145.9 30551 +1903 4 -6.95 -12.95 -8.6 0 93.58 180.61 30614 +1903 5 -4.09 -10.09 -5.74 0 114.32 180.34 30681 +1903 6 -2.92 -8.92 -4.57 0 123.88 180.74 30752 +1903 7 -1.61 -7.61 -3.26 0 135.41 180.95 30828 +1903 8 2.26 -3.74 0.61 0.23 175.06 146.32 30907 +1903 9 -0.69 -6.69 -2.34 1.02 144.05 151.32 30991 +1903 10 1.94 -4.06 0.29 0.58 171.44 151.02 31079 +1903 11 4.81 -1.19 3.16 0 206.34 184.33 31171 +1903 12 7.79 1.79 6.14 0 248.88 182.17 31266 +1903 13 6.28 0.28 4.63 0 226.47 183.9 31366 +1903 14 1.38 -4.62 -0.27 0 165.26 187.92 31469 +1903 15 3.14 -2.86 1.49 0 185.35 187.89 31575 +1903 16 4.51 -1.49 2.86 0 202.42 187.64 31686 +1903 17 0.03 -5.97 -1.62 0 151.15 191.58 31800 +1903 18 1.41 -4.59 -0.24 0.14 165.58 154.88 31917 +1903 19 5.29 -0.71 3.64 0.07 212.73 153.8 32038 +1903 20 4.44 -1.56 2.79 0.18 201.52 114.19 32161 +1903 21 3.29 -2.71 1.64 0.46 187.16 116.22 32289 +1903 22 0.84 -5.16 -0.81 0 159.48 158.06 32419 +1903 23 -2.68 -8.68 -4.33 0 125.93 161.45 32552 +1903 24 -0.8 -6.8 -2.45 0.69 143 164.46 32688 +1903 25 -0.56 -6.56 -2.21 0.18 145.31 166.15 32827 +1903 26 0.81 -5.19 -0.84 0.82 159.17 166.81 32969 +1903 27 -0.4 -6.4 -2.05 0 146.88 210.73 33114 +1903 28 -0.9 -6.9 -2.55 0.01 142.04 170.31 33261 +1903 29 -1.69 -7.69 -3.34 0 134.68 215.62 33411 +1903 30 1.53 -4.47 -0.12 0 166.89 215.87 33564 +1903 31 1.99 -4.01 0.34 0 172 217.56 33718 +1903 32 5.38 -0.62 3.73 0 213.95 216.59 33875 +1903 33 3.59 -2.41 1.94 0 190.82 219.87 34035 +1903 34 4.83 -1.17 3.18 0 206.6 220.45 34196 +1903 35 4.55 -1.45 2.9 0 202.94 183.86 34360 +1903 36 3.27 -2.73 1.62 0.37 186.92 140.46 34526 +1903 37 7.21 1.21 5.56 0.95 240.06 139.99 34694 +1903 38 3.38 -2.62 1.73 0 188.25 192.38 34863 +1903 39 1.29 -4.71 -0.36 0 164.28 196.36 35035 +1903 40 8.93 2.93 7.28 0 267.04 192.91 35208 +1903 41 7.81 1.81 6.16 0 249.19 196.6 35383 +1903 42 8.87 2.87 7.22 0 266.06 198.08 35560 +1903 43 5.83 -0.17 4.18 0 220.13 203.6 35738 +1903 44 9.52 3.52 7.87 0 276.88 202.59 35918 +1903 45 9.33 3.33 7.68 0 273.67 205.38 36099 +1903 46 12.09 6.09 10.44 0 323.43 204.74 36282 +1903 47 14.35 8.35 12.7 0 369.76 204.33 36466 +1903 48 12.88 6.88 11.23 0.11 339.03 156.87 36652 +1903 49 15.3 9.3 13.65 0 390.86 208.23 36838 +1903 50 11.18 5.18 9.53 0 306.24 216.73 37026 +1903 51 11.58 5.58 9.93 0.02 313.7 164.34 37215 +1903 52 7.75 1.75 6.1 0.02 248.26 169.81 37405 +1903 53 5.46 -0.54 3.81 0 215.04 231.59 37596 +1903 54 3.02 -2.98 1.37 0.11 183.92 177.32 37788 +1903 55 2.77 -3.23 1.12 0 180.96 239.63 37981 +1903 56 2.84 -3.16 1.19 0 181.79 242.29 38175 +1903 57 4.54 -1.46 2.89 0 202.81 243.77 38370 +1903 58 5.43 -0.57 3.78 0 214.63 245.89 38565 +1903 59 1.43 -4.57 -0.22 0 165.8 251.97 38761 +1903 60 8.26 2.26 6.61 0 256.23 248.5 38958 +1903 61 13.74 7.74 12.09 0.76 356.73 182.86 39156 +1903 62 13.92 7.92 12.27 0.18 360.53 184.67 39355 +1903 63 11.62 5.62 9.97 0 314.45 252.76 39553 +1903 64 12.27 6.27 10.62 0 326.93 254.64 39753 +1903 65 13.31 7.31 11.66 0 347.78 255.81 39953 +1903 66 13.54 7.54 11.89 0 352.55 258.09 40154 +1903 67 11.14 5.14 9.49 0 305.5 264.71 40355 +1903 68 11.53 5.53 9.88 0 312.76 266.96 40556 +1903 69 13.06 7.06 11.41 0 342.67 267.1 40758 +1903 70 11.08 5.08 9.43 0.02 304.4 204.77 40960 +1903 71 9.36 3.36 7.71 0 274.18 278.35 41163 +1903 72 9.8 3.8 8.15 0.28 281.65 210.41 41366 +1903 73 9.37 3.37 7.72 0.13 274.35 212.85 41569 +1903 74 7.42 1.42 5.77 0.08 243.22 216.8 41772 +1903 75 9.88 3.88 8.23 0.28 283.03 216.39 41976 +1903 76 11.25 5.25 9.6 1.28 307.53 216.8 42179 +1903 77 10.37 4.37 8.72 0.14 291.59 219.75 42383 +1903 78 12.21 6.21 10.56 0 325.76 292.7 42587 +1903 79 16.27 10.27 14.62 0.18 413.46 215.66 42791 +1903 80 15.16 9.16 13.51 0.06 387.69 219.26 42996 +1903 81 14.85 8.85 13.2 0 380.74 295.49 43200 +1903 82 10.97 4.97 9.32 0 302.38 305.13 43404 +1903 83 7.73 1.73 6.08 0 247.95 312.35 43608 +1903 84 7.01 1.01 5.36 0 237.08 315.84 43812 +1903 85 6.57 0.57 4.92 0 230.63 318.91 44016 +1903 86 3.4 -2.6 1.75 0 188.49 324.92 44220 +1903 87 4.16 -1.84 2.51 0 197.94 326.7 44424 +1903 88 8.34 2.34 6.69 0 257.5 323.89 44627 +1903 89 3.74 -2.26 2.09 0 192.67 331.86 44831 +1903 90 6.89 0.89 5.24 0 235.3 330.54 45034 +1903 91 3.88 -2.12 2.23 0.37 194.41 252.31 45237 +1903 92 6.51 0.51 4.86 0 229.76 335.58 45439 +1903 93 7.02 1.02 5.37 0 237.22 337.15 45642 +1903 94 5.8 -0.2 4.15 0 219.72 340.91 45843 +1903 95 7.07 1.07 5.42 0.5 237.97 256.08 46045 +1903 96 6.59 0.59 4.94 0.13 230.92 258.16 46246 +1903 97 11.25 5.25 9.6 0.18 307.53 254.33 46446 +1903 98 11.55 5.55 9.9 0.04 313.13 255.4 46647 +1903 99 12.25 6.25 10.6 0 326.54 341.24 46846 +1903 100 11.63 5.63 9.98 1.99 314.64 258.26 47045 +1903 101 14.11 8.11 12.46 3.9 364.59 255.99 47243 +1903 102 11.92 5.92 10.27 0.39 320.16 260.72 47441 +1903 103 10.9 4.9 9.25 0.14 301.11 263.51 47638 +1903 104 12.31 6.31 10.66 0.17 327.71 262.91 47834 +1903 105 12.81 6.81 11.16 0.23 337.62 263.5 48030 +1903 106 10.56 4.56 8.91 0.01 294.97 267.93 48225 +1903 107 10.52 4.52 8.87 0.16 294.26 269.25 48419 +1903 108 11.06 5.06 9.41 0.01 304.03 269.84 48612 +1903 109 9.22 3.22 7.57 0 271.84 364.61 48804 +1903 110 9.26 3.26 7.61 0 272.5 365.97 48995 +1903 111 8.81 2.81 7.16 0.19 265.08 276.21 49185 +1903 112 5.52 -0.48 3.87 1.71 215.86 280.97 49374 +1903 113 6.51 0.51 4.86 0.18 229.76 281 49561 +1903 114 8.36 2.36 6.71 0.03 257.82 280.07 49748 +1903 115 9.54 3.54 7.89 1.22 277.21 279.71 49933 +1903 116 12.31 6.31 10.66 0.19 327.71 276.75 50117 +1903 117 15.78 9.78 14.13 0.12 401.91 271.84 50300 +1903 118 14.3 8.3 12.65 0.58 368.68 275.49 50481 +1903 119 9.74 3.74 8.09 0 280.62 377.72 50661 +1903 120 9.77 3.77 8.12 0 281.14 378.86 50840 +1903 121 17 11 15.35 0 431.19 364.01 51016 +1903 122 19.41 13.41 17.76 0 494.41 358.13 51191 +1903 123 18.14 12.14 16.49 0 460.18 362.98 51365 +1903 124 18.23 12.23 16.58 0 462.54 363.78 51536 +1903 125 15.63 9.63 13.98 0.02 398.43 278.9 51706 +1903 126 13.11 7.11 11.46 0.19 343.69 284.1 51874 +1903 127 16.05 10.05 14.4 0.31 408.24 279.5 52039 +1903 128 14.98 8.98 13.33 0.86 383.64 282.27 52203 +1903 129 15.13 9.13 13.48 0 387.01 376.84 52365 +1903 130 20.04 14.04 18.39 0.02 512.18 272.64 52524 +1903 131 21.86 15.86 20.21 0 566.6 357.95 52681 +1903 132 21.5 15.5 19.85 0.1 555.46 270.04 52836 +1903 133 24.52 18.52 22.87 0 654.91 348.87 52989 +1903 134 18.74 12.74 17.09 0.05 476.09 277.98 53138 +1903 135 18.22 12.22 16.57 0.19 462.28 279.68 53286 +1903 136 13.28 7.28 11.63 0.01 347.17 289.81 53430 +1903 137 10.71 4.71 9.06 0.51 297.67 294.35 53572 +1903 138 14.85 8.85 13.2 0 380.74 384.04 53711 +1903 139 13.72 7.72 12.07 0.13 356.31 290.58 53848 +1903 140 11.63 5.63 9.98 0 314.64 392.47 53981 +1903 141 15.68 9.68 14.03 0 399.59 383.56 54111 +1903 142 18.44 12.44 16.79 0 468.08 376.26 54238 +1903 143 18.14 12.14 16.49 0.09 460.18 283.27 54362 +1903 144 17.32 11.32 15.67 0 439.17 380.59 54483 +1903 145 16.44 10.44 14.79 0.07 417.53 287.64 54600 +1903 146 19.5 13.5 17.85 0.87 496.92 281.06 54714 +1903 147 20.38 14.38 18.73 0.21 522 279.2 54824 +1903 148 16.72 10.72 15.07 0.47 424.32 288 54931 +1903 149 20.51 14.51 18.86 0 525.79 372.5 55034 +1903 150 18.72 12.72 17.07 0.04 475.56 284.05 55134 +1903 151 20.85 14.85 19.2 0 535.82 372.03 55229 +1903 152 22 16 20.35 0 570.98 367.93 55321 +1903 153 21.13 15.13 19.48 0 544.21 371.37 55409 +1903 154 21.72 15.72 20.07 0 562.24 369.52 55492 +1903 155 21.5 15.5 19.85 1.72 555.46 277.89 55572 +1903 156 18.5 12.5 16.85 0.58 469.67 285.74 55648 +1903 157 17.79 11.79 16.14 0 451.11 383.31 55719 +1903 158 17.65 11.65 16 0.18 447.52 287.93 55786 +1903 159 16.71 10.71 15.06 0 424.07 386.85 55849 +1903 160 16.29 10.29 14.64 0 413.94 388.2 55908 +1903 161 14.94 8.94 13.29 0 382.75 391.81 55962 +1903 162 18.11 12.11 16.46 0.1 459.4 287.31 56011 +1903 163 18.38 12.38 16.73 0.09 466.49 286.85 56056 +1903 164 20.97 14.97 19.32 0 539.4 373.9 56097 +1903 165 27.37 21.37 25.72 0 762.19 346.5 56133 +1903 166 25.49 19.49 23.84 0 689.89 355.67 56165 +1903 167 23.86 17.86 22.21 0.02 631.98 272.09 56192 +1903 168 20.33 14.33 18.68 0 520.54 376.35 56214 +1903 169 20.61 14.61 18.96 1.37 528.72 281.54 56231 +1903 170 20.84 14.84 19.19 0.56 535.53 280.93 56244 +1903 171 18.78 12.78 17.13 0 477.17 381.54 56252 +1903 172 19.43 13.43 17.78 0 494.97 379.44 56256 +1903 173 23.91 17.91 22.26 0 633.69 362.7 56255 +1903 174 21.05 15.05 19.4 0.13 541.8 280.33 56249 +1903 175 18 12 16.35 0.08 456.53 287.86 56238 +1903 176 13.45 7.45 11.8 0 350.68 395.83 56223 +1903 177 19.77 13.77 18.12 0.03 504.5 283.53 56203 +1903 178 18.17 12.17 16.52 0.02 460.97 287.38 56179 +1903 179 17.79 11.79 16.14 0.53 451.11 288.16 56150 +1903 180 17.95 11.95 16.3 0.07 455.24 287.71 56116 +1903 181 19.27 13.27 17.62 0.55 490.54 284.56 56078 +1903 182 23.88 17.88 22.23 0.36 632.66 271.64 56035 +1903 183 24.74 18.74 23.09 0.14 662.71 268.73 55987 +1903 184 27.11 21.11 25.46 0.29 751.83 260.26 55935 +1903 185 27.2 21.2 25.55 0 755.4 346.48 55879 +1903 186 22.62 16.62 20.97 0 590.73 366.64 55818 +1903 187 26.1 20.1 24.45 0 712.68 351.44 55753 +1903 188 24.66 18.66 23.01 0.02 659.86 268.31 55684 +1903 189 22.41 16.41 20.76 1.33 583.98 275.12 55611 +1903 190 17.5 11.5 15.85 0.74 443.71 287.27 55533 +1903 191 19.74 13.74 18.09 2.98 503.65 281.83 55451 +1903 192 18.71 12.71 17.06 0.44 475.29 284.1 55366 +1903 193 20.56 14.56 18.91 0.11 527.26 279.31 55276 +1903 194 22.96 16.96 21.31 0.01 601.8 272.45 55182 +1903 195 23.79 17.79 22.14 0.71 629.58 269.72 55085 +1903 196 24.18 18.18 22.53 0.93 643.01 268.19 54984 +1903 197 18.67 12.67 17.02 0.21 474.21 282.95 54879 +1903 198 15.96 9.96 14.31 0.14 406.12 288.47 54770 +1903 199 21.44 15.44 19.79 0.57 553.62 275.37 54658 +1903 200 19.21 13.21 17.56 0.19 488.88 280.78 54542 +1903 201 17.29 11.29 15.64 0.08 438.42 284.78 54423 +1903 202 18.51 12.51 16.86 0.97 469.94 281.64 54301 +1903 203 20.05 14.05 18.4 0.05 512.47 277.56 54176 +1903 204 19.55 13.55 17.9 0.76 498.32 278.41 54047 +1903 205 18.35 12.35 16.7 0.18 465.7 280.84 53915 +1903 206 19.63 13.63 17.98 0.09 500.56 277.4 53780 +1903 207 21.61 15.61 19.96 0.1 558.84 271.79 53643 +1903 208 22.02 16.02 20.37 1.28 571.61 270.17 53502 +1903 209 21.06 15.06 19.41 1.14 542.1 272.3 53359 +1903 210 25.47 19.47 23.82 0 689.15 344.87 53213 +1903 211 27.8 21.8 26.15 0 779.6 332.99 53064 +1903 212 28.29 22.29 26.64 0.18 799.85 247.29 52913 +1903 213 27.77 21.77 26.12 0.06 778.38 248.76 52760 +1903 214 27.64 21.64 25.99 0.44 773.09 248.73 52604 +1903 215 25.5 19.5 23.85 0.18 690.25 255.85 52445 +1903 216 26.49 20.49 24.84 1.41 727.59 251.72 52285 +1903 217 23.02 17.02 21.37 0.61 603.78 262.21 52122 +1903 218 23.36 17.36 21.71 0.06 615.06 260.62 51958 +1903 219 25.34 19.34 23.69 0 684.38 338.23 51791 +1903 220 21.88 15.88 20.23 0 567.22 351.13 51622 +1903 221 23.12 17.12 21.47 0.03 607.08 259.13 51451 +1903 222 22.93 16.93 21.28 0.93 600.82 258.91 51279 +1903 223 19.17 13.17 17.52 0.04 487.78 267.76 51105 +1903 224 17.88 11.88 16.23 0.07 453.43 269.83 50929 +1903 225 15.78 9.78 14.13 0 401.91 364.24 50751 +1903 226 16.82 10.82 15.17 0.39 426.76 270.28 50572 +1903 227 18.03 12.03 16.38 0.35 457.31 266.8 50392 +1903 228 19.31 13.31 17.66 0.08 491.64 263.04 50210 +1903 229 17.4 11.4 15.75 0 441.18 355.01 50026 +1903 230 22.07 16.07 20.42 0 573.18 339.09 49842 +1903 231 20.63 14.63 18.98 0.05 529.31 256.92 49656 +1903 232 19.08 13.08 17.43 0.54 485.32 259.55 49469 +1903 233 22.74 16.74 21.09 0 594.62 332.51 49280 +1903 234 22.86 16.86 21.21 0 598.53 330.69 49091 +1903 235 24.23 18.23 22.58 0 644.75 324.02 48900 +1903 236 21.38 15.38 19.73 0.97 551.79 249.78 48709 +1903 237 20.63 14.63 18.98 1 529.31 250.42 48516 +1903 238 21.8 15.8 20.15 0 564.73 328.36 48323 +1903 239 21.81 15.81 20.16 0 565.04 326.85 48128 +1903 240 20.29 14.29 18.64 0 519.38 330.07 47933 +1903 241 22.32 16.32 20.67 0 581.1 321.69 47737 +1903 242 25.03 19.03 23.38 0 673.11 309.85 47541 +1903 243 20.93 14.93 19.28 0.12 538.21 242.1 47343 +1903 244 19.53 13.53 17.88 0.17 497.76 243.96 47145 +1903 245 22.72 16.72 21.07 0 593.97 313.23 46947 +1903 246 23.55 17.55 21.9 0 621.44 308.36 46747 +1903 247 21.21 15.21 19.56 0.37 546.63 235.92 46547 +1903 248 19.62 13.62 17.97 0.45 500.28 238.11 46347 +1903 249 18.93 12.93 17.28 0 481.23 317.4 46146 +1903 250 19.64 13.64 17.99 0.08 500.84 235.09 45945 +1903 251 14.99 8.99 13.34 0.02 383.87 242.28 45743 +1903 252 17.37 11.37 15.72 0 440.43 315.3 45541 +1903 253 18.84 12.84 17.19 0 478.79 309.37 45339 +1903 254 17.89 11.89 16.24 0 453.69 309.74 45136 +1903 255 15.3 9.3 13.65 0 390.86 313.58 44933 +1903 256 14.93 8.93 13.28 0.07 382.52 234.06 44730 +1903 257 14.13 8.13 12.48 0 365.02 311.54 44527 +1903 258 19.46 13.46 17.81 0 495.8 296.66 44323 +1903 259 19.44 13.44 17.79 0 495.25 294.32 44119 +1903 260 18.86 12.86 17.21 0 479.33 293.52 43915 +1903 261 22.2 16.2 20.55 0.83 577.29 211.19 43711 +1903 262 20.29 14.29 18.64 0.05 519.38 213.7 43507 +1903 263 18.24 12.24 16.59 0.33 462.8 215.93 43303 +1903 264 19.98 13.98 18.33 0.43 510.47 210.66 43099 +1903 265 20.51 14.51 18.86 0.65 525.79 207.84 42894 +1903 266 22.53 16.53 20.88 0.04 587.83 201.62 42690 +1903 267 19.97 13.97 18.32 0.7 510.18 205.18 42486 +1903 268 19.41 13.41 17.76 0 494.41 272.53 42282 +1903 269 19.48 13.48 17.83 0.28 496.36 202.43 42078 +1903 270 17.56 11.56 15.91 0.61 445.23 203.95 41875 +1903 271 10.92 4.92 9.27 0 301.47 281.68 41671 +1903 272 13.03 7.03 11.38 0 342.06 275.52 41468 +1903 273 12.19 6.19 10.54 0 325.37 274.36 41265 +1903 274 11.37 5.37 9.72 0.87 309.76 204.7 41062 +1903 275 12.47 6.47 10.82 0 330.86 268.41 40860 +1903 276 11.95 5.95 10.3 0.27 320.74 199.88 40658 +1903 277 12.32 6.32 10.67 0 327.91 263.24 40456 +1903 278 10.56 4.56 8.91 0 294.97 262.96 40255 +1903 279 13.28 7.28 11.63 0 347.17 256 40054 +1903 280 12.14 6.14 10.49 0 324.4 255.13 39854 +1903 281 13.42 7.42 11.77 0 350.05 250.39 39654 +1903 282 17.26 11.26 15.61 0 437.66 240.68 39455 +1903 283 21.46 15.46 19.81 0 554.23 228.36 39256 +1903 284 25.15 19.15 23.5 0 677.45 215.08 39058 +1903 285 19.62 13.62 17.97 0 500.28 227.38 38861 +1903 286 17.36 11.36 15.71 0 440.17 229.49 38664 +1903 287 15.56 9.56 13.91 0.35 396.81 172.48 38468 +1903 288 12.63 6.63 10.98 0 334.03 231.92 38273 +1903 289 16.37 10.37 14.72 0.28 415.85 167.4 38079 +1903 290 11.21 5.21 9.56 0.4 306.79 171.29 37885 +1903 291 8.68 2.68 7.03 0 262.96 228.74 37693 +1903 292 7.33 1.33 5.68 0.01 241.86 170.59 37501 +1903 293 8 2 6.35 0 252.14 223.99 37311 +1903 294 10.48 4.48 8.83 0.17 293.55 163.7 37121 +1903 295 12.83 6.83 11.18 0.82 338.02 159.28 36933 +1903 296 14.9 8.9 13.25 0 381.86 206.76 36745 +1903 297 17.52 11.52 15.87 0.03 444.22 149.77 36560 +1903 298 18.05 12.05 16.4 0.53 457.83 147.15 36375 +1903 299 14.13 8.13 12.48 0.18 365.02 149.95 36191 +1903 300 14.8 8.8 13.15 0.78 379.63 147.24 36009 +1903 301 16.44 10.44 14.79 0.92 417.53 143.48 35829 +1903 302 11.46 5.46 9.81 1.14 311.44 146.81 35650 +1903 303 11.72 5.72 10.07 0.39 316.34 144.65 35472 +1903 304 12.52 6.52 10.87 0.02 331.84 142.08 35296 +1903 305 6.81 0.81 5.16 0.15 234.13 144.55 35122 +1903 306 4.96 -1.04 3.31 0 208.32 191.97 34950 +1903 307 5.03 -0.97 3.38 0 209.25 189.37 34779 +1903 308 10.22 4.22 8.57 0 288.95 182.07 34610 +1903 309 10.43 4.43 8.78 0 292.66 179.54 34444 +1903 310 12.3 6.3 10.65 0 327.52 175.04 34279 +1903 311 13.32 7.32 11.67 0 347.99 171.67 34116 +1903 312 12.37 6.37 10.72 0.02 328.89 127.66 33956 +1903 313 8.8 2.8 7.15 0 264.91 171.81 33797 +1903 314 7.59 1.59 5.94 0 245.81 170.93 33641 +1903 315 7.57 1.57 5.92 2.06 245.5 126.31 33488 +1903 316 8.53 2.53 6.88 0 260.54 165.4 33337 +1903 317 10.9 4.9 9.25 0 301.11 160.98 33188 +1903 318 16.26 10.26 14.61 0.06 413.22 114.22 33042 +1903 319 10.41 4.41 8.76 0.86 292.3 118.11 32899 +1903 320 11.11 5.11 9.46 0.07 304.95 116.21 32758 +1903 321 10.75 4.75 9.1 0.07 298.39 114.92 32620 +1903 322 8.87 2.87 7.22 0.84 266.06 114.86 32486 +1903 323 9.51 3.51 7.86 0 276.71 150.98 32354 +1903 324 11.81 5.81 10.16 0.58 318.06 110.08 32225 +1903 325 11.48 5.48 9.83 0.03 311.82 109.06 32100 +1903 326 10.64 4.64 8.99 0.41 296.41 108.6 31977 +1903 327 10.63 4.63 8.98 0.32 296.23 107.24 31858 +1903 328 8.16 2.16 6.51 0.08 254.65 107.35 31743 +1903 329 2.07 -3.93 0.42 0.31 172.9 109.18 31631 +1903 330 -0.11 -6.11 -1.76 0.46 149.74 152.15 31522 +1903 331 1.37 -4.63 -0.28 0.02 165.15 150.6 31417 +1903 332 3.63 -2.37 1.98 0 191.31 183.2 31316 +1903 333 3.81 -2.19 2.16 0.62 193.54 146.87 31218 +1903 334 7.91 1.91 6.26 0 250.74 135.3 31125 +1903 335 6.73 0.73 5.08 0 232.96 134.98 31035 +1903 336 6.55 0.55 4.9 0 230.34 134.03 30949 +1903 337 2.54 -3.46 0.89 0.04 178.28 101.06 30867 +1903 338 4.55 -1.45 2.9 0 202.94 132.69 30790 +1903 339 6.29 0.29 4.64 0 226.61 130.83 30716 +1903 340 9.47 3.47 7.82 0.03 276.03 95.86 30647 +1903 341 9.12 3.12 7.47 0.91 270.17 95.39 30582 +1903 342 9.77 3.77 8.12 0 281.14 125.92 30521 +1903 343 9.74 3.74 8.09 0 280.62 125.14 30465 +1903 344 6.58 0.58 4.93 0 230.78 126.29 30413 +1903 345 5.03 -0.97 3.38 0.25 209.25 95.12 30366 +1903 346 -1.91 -7.91 -3.56 0.06 132.69 140.87 30323 +1903 347 2.22 -3.78 0.57 0.45 174.6 95.39 30284 +1903 348 -0.27 -6.27 -1.92 0 148.15 127.94 30251 +1903 349 -0.14 -6.14 -1.79 0.68 149.44 141.47 30221 +1903 350 -1.83 -7.83 -3.48 0 133.41 173.7 30197 +1903 351 2.27 -3.73 0.62 0.15 175.17 140 30177 +1903 352 5.64 -0.36 3.99 2.18 217.5 137.83 30162 +1903 353 4.44 -1.56 2.79 1.98 201.52 137.73 30151 +1903 354 3.31 -2.69 1.66 0.23 187.4 137.72 30145 +1903 355 1.07 -4.93 -0.58 0.06 161.92 94.67 30144 +1903 356 0.16 -5.84 -1.49 1.11 152.46 94.99 30147 +1903 357 -0.09 -6.09 -1.74 1.37 149.94 143.24 30156 +1903 358 4.47 -1.53 2.82 0.31 201.91 141.04 30169 +1903 359 2.01 -3.99 0.36 0.99 172.22 141.79 30186 +1903 360 -2.56 -8.56 -4.21 0.01 126.96 143.46 30208 +1903 361 0.18 -5.82 -1.47 0.68 152.66 142.86 30235 +1903 362 3.92 -2.08 2.27 0.04 194.91 141.27 30267 +1903 363 0.17 -5.83 -1.48 0 152.56 175.15 30303 +1903 364 5.23 -0.77 3.58 0.01 211.92 140.61 30343 +1903 365 3.33 -2.67 1.68 0 187.64 173.36 30388 +1904 1 -1.4 -7.4 -3.05 0 137.34 176.32 30438 +1904 2 3.57 -2.43 1.92 0 190.57 174.23 30492 +1904 3 1.82 -4.18 0.17 0.29 170.1 142.88 30551 +1904 4 3.21 -2.79 1.56 0 186.2 175.44 30614 +1904 5 5.2 -0.8 3.55 0 211.52 131.19 30681 +1904 6 1.54 -4.46 -0.11 0 167 134.05 30752 +1904 7 -1.17 -7.17 -2.82 0 139.49 136.05 30828 +1904 8 1.2 -4.8 -0.45 0 163.31 136.51 30907 +1904 9 9.34 3.34 7.69 0 273.84 132.66 30991 +1904 10 8.26 2.26 6.61 0 256.23 134.79 31079 +1904 11 3.15 -2.85 1.5 0.59 185.47 104.31 31171 +1904 12 2.33 -3.67 0.68 0.27 175.86 105.39 31266 +1904 13 -0.29 -6.29 -1.94 0.04 147.96 149.77 31366 +1904 14 -0.25 -6.25 -1.9 0.07 148.35 150.95 31469 +1904 15 3.85 -2.15 2.2 0 194.04 144.23 31575 +1904 16 2.16 -3.84 0.51 0.05 173.92 109.85 31686 +1904 17 -0.57 -6.57 -2.22 0.44 145.22 154.95 31800 +1904 18 -5.28 -11.28 -6.93 0 105.25 195.88 31917 +1904 19 -2.69 -8.69 -4.34 0 125.84 196.76 32038 +1904 20 -1.59 -7.59 -3.24 0.03 135.6 159 32161 +1904 21 0.69 -5.31 -0.96 0 157.91 198.57 32289 +1904 22 1.2 -4.8 -0.45 0 163.31 199.75 32419 +1904 23 1.9 -4.1 0.25 0 170.99 200.75 32552 +1904 24 -1.44 -7.44 -3.09 0 136.97 204.32 32688 +1904 25 -3.69 -9.69 -5.34 0 117.51 206.98 32827 +1904 26 -0.24 -6.24 -1.89 0 148.45 207.26 32969 +1904 27 -1.98 -7.98 -3.63 0 132.07 209.93 33114 +1904 28 -2.98 -8.98 -4.63 0 123.38 212.42 33261 +1904 29 -3.9 -9.9 -5.55 0 115.82 215.02 33411 +1904 30 -2.22 -8.22 -3.87 0 129.93 216.41 33564 +1904 31 -1.17 -7.17 -2.82 0.65 139.49 175.47 33718 +1904 32 6.22 0.22 4.57 1.1 225.61 172.68 33875 +1904 33 6.77 0.77 5.12 1.15 233.54 173.31 34035 +1904 34 5.26 -0.74 3.61 0.1 212.33 175.04 34196 +1904 35 4.23 -1.77 2.58 0 198.83 222.56 34360 +1904 36 6.19 0.19 4.54 0 225.19 185.11 34526 +1904 37 7.53 1.53 5.88 0 244.89 186.37 34694 +1904 38 8.67 2.67 7.02 0.05 262.8 141.01 34863 +1904 39 9.01 3.01 7.36 0 268.36 190.25 35035 +1904 40 6.38 0.38 4.73 0.05 227.89 146.46 35208 +1904 41 7.96 1.96 6.31 0.23 251.52 147.34 35383 +1904 42 6.72 0.72 5.07 0 232.81 200.13 35560 +1904 43 5.17 -0.83 3.52 0 211.12 204.15 35738 +1904 44 4.33 -1.67 2.68 0 200.11 207.39 35918 +1904 45 6.91 0.91 5.26 0.51 235.6 155.86 36099 +1904 46 7.07 1.07 5.42 0 237.97 210.33 36282 +1904 47 3.96 -2.04 2.31 0 195.41 215.83 36466 +1904 48 6.08 0.08 4.43 0.06 223.63 162.64 36652 +1904 49 4.22 -1.78 2.57 0.83 198.7 165.91 36838 +1904 50 7.58 1.58 5.93 0.15 245.65 165.62 37026 +1904 51 9.75 3.75 8.1 1.16 280.79 166.05 37215 +1904 52 4.27 -1.73 2.62 1.23 199.34 172.25 37405 +1904 53 -0.59 -6.59 -2.24 0.08 145.02 212.41 37596 +1904 54 2.47 -3.53 0.82 0 177.47 236.84 37788 +1904 55 3.49 -2.51 1.84 0 189.59 239.06 37981 +1904 56 4.83 -1.17 3.18 0 206.6 240.62 38175 +1904 57 4.55 -1.45 2.9 0.46 202.94 182.82 38370 +1904 58 5.7 -0.3 4.05 0.9 218.33 184.23 38565 +1904 59 7.46 1.46 5.81 0.99 243.83 184.9 38761 +1904 60 7.79 1.79 6.14 0 248.88 249.04 38958 +1904 61 8.85 2.85 7.2 0 265.73 250.72 39156 +1904 62 11.59 5.59 9.94 0.22 313.89 187.38 39355 +1904 63 15.14 9.14 13.49 0 387.24 247.03 39553 +1904 64 16.57 10.57 14.92 0 420.67 247.12 39753 +1904 65 14.51 8.51 12.86 0.19 373.25 190.32 39953 +1904 66 18.53 12.53 16.88 0.35 470.47 186.25 40154 +1904 67 16.85 10.85 15.2 0 427.5 254.72 40355 +1904 68 17.65 11.65 16 0 447.52 255.78 40556 +1904 69 11.51 5.51 9.86 0 312.38 269.57 40758 +1904 70 8.94 2.94 7.29 0.66 267.2 207.01 40960 +1904 71 5.99 -0.01 4.34 0.75 222.37 211.84 41163 +1904 72 10.08 4.08 8.43 0 286.5 280.16 41366 +1904 73 9.07 3.07 7.42 0.07 269.35 213.15 41569 +1904 74 7.31 1.31 5.66 0 241.56 289.2 41772 +1904 75 5.16 -0.84 3.51 0 210.98 294.39 41976 +1904 76 4.4 -1.6 2.75 0 201 297.85 42179 +1904 77 3.25 -2.75 1.6 0.06 186.68 226.21 42383 +1904 78 2.49 -3.51 0.84 0 177.7 305.03 42587 +1904 79 3.47 -2.53 1.82 1.12 189.35 230.15 42791 +1904 80 0.81 -5.19 -0.84 0.29 159.17 233.89 42996 +1904 81 -0.35 -6.35 -2 1.89 147.37 271.31 43200 +1904 82 2.17 -3.83 0.52 1.24 174.03 271.39 43404 +1904 83 3.11 -2.89 1.46 0.16 184.99 272.17 43608 +1904 84 2.78 -3.22 1.13 0 181.08 354.07 43812 +1904 85 -0.06 -6.06 -1.71 0 150.24 358.98 44016 +1904 86 3.93 -2.07 2.28 0.01 195.04 276.14 44220 +1904 87 5.16 -0.84 3.51 0.26 210.98 276.43 44424 +1904 88 6.62 0.62 4.97 0.12 231.36 276.15 44627 +1904 89 8.95 2.95 7.3 0.23 267.37 274.52 44831 +1904 90 13.09 7.09 11.44 0.21 343.28 240.48 45034 +1904 91 17.15 11.15 15.5 1.47 434.92 235.5 45237 +1904 92 11.21 5.21 9.56 0 306.79 328.53 45439 +1904 93 10.86 4.86 9.21 0 300.38 331.34 45642 +1904 94 10.57 4.57 8.92 0 295.15 333.98 45843 +1904 95 8.5 2.5 6.85 0.03 260.06 254.55 46045 +1904 96 12.52 6.52 10.87 0 331.84 334.73 46246 +1904 97 15.58 9.58 13.93 0 397.27 330.31 46446 +1904 98 16.19 10.19 14.54 0 411.56 330.79 46647 +1904 99 15.05 9.05 13.4 0.95 385.21 251.56 46846 +1904 100 14.51 8.51 12.86 0 373.25 338.54 47045 +1904 101 15.17 9.17 13.52 0.18 387.92 254.22 47243 +1904 102 12.89 6.89 11.24 0.2 339.23 259.31 47441 +1904 103 13.89 7.89 12.24 0 359.9 345.49 47638 +1904 104 14.82 8.82 13.17 0 380.08 345.25 47834 +1904 105 17.24 11.24 15.59 0.62 437.16 255.81 48030 +1904 106 17.79 11.79 16.14 0 451.11 341.21 48225 +1904 107 19.34 13.34 17.69 0 492.47 338.4 48419 +1904 108 14.64 8.64 12.99 0 376.1 352.43 48612 +1904 109 17.61 11.61 15.96 0.35 446.5 259.95 48804 +1904 110 14.26 8.26 12.61 0.17 367.81 267.22 48995 +1904 111 14.66 8.66 13.01 0 376.54 356.92 49185 +1904 112 11.47 5.47 9.82 0.52 311.63 273.86 49374 +1904 113 10.23 4.23 8.58 0.15 289.12 276.59 49561 +1904 114 11.27 5.27 9.62 0 307.9 368.38 49748 +1904 115 10.55 4.55 8.9 0 294.79 371.16 49933 +1904 116 11.98 5.98 10.33 0 321.31 369.67 50117 +1904 117 13.23 7.23 11.58 0.16 346.14 276.29 50300 +1904 118 9.11 3.11 7.46 0.86 270.01 283.19 50481 +1904 119 9.57 3.57 7.92 0.15 277.72 283.51 50661 +1904 120 7.54 1.54 5.89 0 245.04 382.51 50840 +1904 121 9 3 7.35 0.23 268.19 286 51016 +1904 122 7.61 1.61 5.96 0.2 246.11 288.59 51191 +1904 123 4.6 -1.4 2.95 0 203.59 390.07 51365 +1904 124 11.06 5.06 9.41 0 304.03 380.99 51536 +1904 125 13.05 7.05 11.4 0.14 342.47 283.44 51706 +1904 126 17.49 11.49 15.84 0 443.46 367.86 51874 +1904 127 16.63 10.63 14.98 0.57 422.13 278.34 52039 +1904 128 17.9 11.9 16.25 0 453.94 368.55 52203 +1904 129 15.63 9.63 13.98 0.08 398.43 281.69 52365 +1904 130 14.03 8.03 12.38 0 362.88 380.28 52524 +1904 131 13.99 7.99 12.34 0.27 362.02 285.88 52681 +1904 132 11.4 5.4 9.75 0 310.32 387.59 52836 +1904 133 14.08 8.08 12.43 0 363.94 382.51 52989 +1904 134 21.04 15.04 19.39 0 541.5 363.05 53138 +1904 135 17.71 11.71 16.06 1.43 449.06 280.81 53286 +1904 136 22.71 16.71 21.06 1.27 593.64 268.63 53430 +1904 137 19.26 13.26 17.61 1.62 490.26 278.26 53572 +1904 138 20.27 14.27 18.62 0 518.8 368.28 53711 +1904 139 16.41 10.41 14.76 2.34 416.81 285.52 53848 +1904 140 16.32 10.32 14.67 0.46 414.65 286.07 53981 +1904 141 16.54 10.54 14.89 0.27 419.95 285.95 54111 +1904 142 23.37 17.37 21.72 0 615.39 358.83 54238 +1904 143 22.85 16.85 21.2 0 598.2 361.42 54362 +1904 144 21.77 15.77 20.12 0 563.79 366.01 54483 +1904 145 20.26 14.26 18.61 0 518.51 371.84 54600 +1904 146 24.03 18.03 22.38 0 637.82 357.89 54714 +1904 147 21.35 15.35 19.7 0 550.88 368.84 54824 +1904 148 23.3 17.3 21.65 0.25 613.06 271.3 54931 +1904 149 19.18 13.18 17.53 0.1 488.06 282.71 55034 +1904 150 17.83 11.83 16.18 0 452.14 381.45 55134 +1904 151 21.65 15.65 20 0 560.08 369.13 55229 +1904 152 26.24 20.24 24.59 2.06 718 262.41 55321 +1904 153 25.65 19.65 24 0.09 695.8 264.66 55409 +1904 154 23.89 17.89 22.24 0.1 633 270.7 55492 +1904 155 19.18 13.18 17.53 0.57 488.06 283.89 55572 +1904 156 15.86 9.86 14.21 1.27 403.78 291.43 55648 +1904 157 16.21 10.21 14.56 0.54 412.03 290.86 55719 +1904 158 13.38 7.38 11.73 0 349.23 395.06 55786 +1904 159 14.06 8.06 12.41 0 363.52 393.71 55849 +1904 160 18.52 12.52 16.87 0 470.21 381.7 55908 +1904 161 17.24 11.24 15.59 0.03 437.16 289.2 55962 +1904 162 21.02 15.02 19.37 0 540.9 373.47 56011 +1904 163 17.12 11.12 15.47 0 434.17 386.22 56056 +1904 164 18.41 12.41 16.76 0 467.28 382.43 56097 +1904 165 21.16 15.16 19.51 0.07 545.11 279.98 56133 +1904 166 21.99 15.99 20.34 1.31 570.66 277.74 56165 +1904 167 24.16 18.16 22.51 0.04 642.31 271.14 56192 +1904 168 24.24 18.24 22.59 0.65 645.09 270.94 56214 +1904 169 27.95 21.95 26.3 0.23 785.75 257.7 56231 +1904 170 25.61 19.61 23.96 0.11 694.32 266.36 56244 +1904 171 26.91 20.91 25.26 0.08 743.94 261.73 56252 +1904 172 25.89 19.89 24.24 0.24 704.76 265.42 56256 +1904 173 24.87 18.87 23.22 0.52 667.35 268.91 56255 +1904 174 21.5 15.5 19.85 0 555.46 372.13 56249 +1904 175 24.08 18.08 22.43 0 639.54 361.87 56238 +1904 176 20.73 14.73 19.08 0 532.26 374.85 56223 +1904 177 23.37 17.37 21.72 0.09 615.39 273.52 56203 +1904 178 20.33 14.33 18.68 0.09 520.54 282.12 56179 +1904 179 20.47 14.47 18.82 0 524.62 375.58 56150 +1904 180 16.69 10.69 15.04 0.01 423.59 290.45 56116 +1904 181 16.49 10.49 14.84 0 418.74 387.75 56078 +1904 182 20.11 14.11 18.46 0 514.19 376.48 56035 +1904 183 25.05 19.05 23.4 0 673.83 356.93 55987 +1904 184 24.18 18.18 22.53 0 643.01 360.59 55935 +1904 185 28.59 22.59 26.94 0 812.46 339.22 55879 +1904 186 26.24 20.24 24.59 0 718 350.95 55818 +1904 187 25.02 19.02 23.37 0.01 672.74 267.31 55753 +1904 188 22.29 16.29 20.64 0 580.15 367.47 55684 +1904 189 21.36 15.36 19.71 0 551.18 370.77 55611 +1904 190 21.73 15.73 20.08 0 562.55 369.04 55533 +1904 191 24.62 18.62 22.97 0 658.44 357.12 55451 +1904 192 28.46 22.46 26.81 0 806.98 338.21 55366 +1904 193 29.69 23.69 28.04 0.12 860.16 248.36 55276 +1904 194 27.79 21.79 26.14 0.02 779.19 255.97 55182 +1904 195 24.86 18.86 23.21 0 666.99 355.04 55085 +1904 196 22.46 16.46 20.81 0 585.58 364.56 54984 +1904 197 23.12 17.12 21.47 0.65 607.08 271.13 54879 +1904 198 23.37 17.37 21.72 0.11 615.39 270.07 54770 +1904 199 25.71 19.71 24.06 0.29 698.04 262.22 54658 +1904 200 22.47 16.47 20.82 0.13 585.9 272.18 54542 +1904 201 20.66 14.66 19.01 0.32 530.2 276.8 54423 +1904 202 24.63 18.63 22.98 0.62 658.8 264.8 54301 +1904 203 25.89 19.89 24.24 0.31 704.76 260.21 54176 +1904 204 23.1 17.1 21.45 0.32 606.42 268.83 54047 +1904 205 26.02 20.02 24.37 0 709.66 345.36 53915 +1904 206 28.19 22.19 26.54 0 795.68 334.12 53780 +1904 207 26.63 20.63 24.98 0.03 733 255.99 53643 +1904 208 26.19 20.19 24.54 0 716.1 342.78 53502 +1904 209 25.97 19.97 24.32 0.09 707.77 257.39 53359 +1904 210 24.9 18.9 23.25 0 668.43 347.39 53213 +1904 211 22.61 16.61 20.96 0 590.41 355.98 53064 +1904 212 23.06 17.06 21.41 0.08 605.1 265.1 52913 +1904 213 24.7 18.7 23.05 0.19 661.28 259.5 52760 +1904 214 30.68 24.68 29.03 0.01 905.08 236.32 52604 +1904 215 30.49 24.49 28.84 0.45 896.31 236.71 52445 +1904 216 20.16 14.16 18.51 0.58 515.63 270.56 52285 +1904 217 21.37 15.37 19.72 0.02 551.49 266.8 52122 +1904 218 20.5 14.5 18.85 0 525.5 357.91 51958 +1904 219 24.11 18.11 22.46 0.42 640.58 257.59 51791 +1904 220 23.51 17.51 21.86 1.46 620.09 258.72 51622 +1904 221 19.43 13.43 17.78 0.7 494.97 268.8 51451 +1904 222 19.84 13.84 18.19 0.14 506.48 267.04 51279 +1904 223 18.39 12.39 16.74 0 466.76 359.36 51105 +1904 224 19.21 13.21 17.56 0 488.88 355.83 50929 +1904 225 22.81 16.81 21.16 0.07 596.9 256.8 50751 +1904 226 18.33 12.33 16.68 0.59 465.17 267.12 50572 +1904 227 21.75 15.75 20.1 0.48 563.17 257.92 50392 +1904 228 21.46 15.46 19.81 0.37 554.23 257.78 50210 +1904 229 18.65 12.65 17 0.26 473.68 263.59 50026 +1904 230 20.91 14.91 19.26 1.04 537.61 257.32 49842 +1904 231 22.98 16.98 21.33 0 602.46 334.33 49656 +1904 232 22.96 16.96 21.31 0 601.8 333.08 49469 +1904 233 23.62 17.62 21.97 0 623.81 329.2 49280 +1904 234 26.27 20.27 24.62 0 719.15 316.88 49091 +1904 235 28.75 22.75 27.1 0 819.26 303.75 48900 +1904 236 27.87 21.87 26.22 0.19 782.47 230.08 48709 +1904 237 25.99 19.99 24.34 0.15 708.52 235.35 48516 +1904 238 28.05 22.05 26.4 0.3 789.88 227.12 48323 +1904 239 22.76 16.76 21.11 3.25 595.27 242.64 48128 +1904 240 21.28 15.28 19.63 1.03 548.75 245.17 47933 +1904 241 23.31 17.31 21.66 0.14 613.39 238.61 47737 +1904 242 22.24 16.24 20.59 0 578.56 320.27 47541 +1904 243 23.79 17.79 22.14 0 629.58 312.89 47343 +1904 244 18 12 16.35 0.04 456.53 247.19 47145 +1904 245 17.38 11.38 15.73 0.22 440.68 247.03 46947 +1904 246 23.09 17.09 21.44 1.47 606.09 232.52 46747 +1904 247 19.83 13.83 18.18 0.25 506.2 239.09 46547 +1904 248 22 16 20.35 1.73 570.98 232.57 46347 +1904 249 19.78 13.78 18.13 1.33 504.78 236.24 46146 +1904 250 15.24 9.24 13.59 0.01 389.5 243.47 45945 +1904 251 14.63 8.63 12.98 0.06 375.88 242.86 45743 +1904 252 16.98 10.98 15.33 0 430.7 316.26 45541 +1904 253 17.86 11.86 16.21 0.02 452.91 233.96 45339 +1904 254 19.94 13.94 18.29 0.36 509.33 228.15 45136 +1904 255 19.58 13.58 17.93 0 499.16 302.99 44933 +1904 256 16.78 10.78 15.13 1.5 425.78 230.96 44730 +1904 257 15.43 9.43 13.78 0.33 393.83 231.62 44527 +1904 258 16.38 10.38 14.73 0.93 416.09 228.27 44323 +1904 259 17.01 11.01 15.36 0.1 431.44 225.35 44119 +1904 260 14.47 8.47 12.82 0.55 372.37 227.7 43915 +1904 261 15.29 9.29 13.64 0.3 390.64 224.59 43711 +1904 262 17.77 11.77 16.12 0.47 450.6 218.61 43507 +1904 263 17.42 11.42 15.77 0.47 441.69 217.41 43303 +1904 264 11.97 5.97 10.32 0.86 321.12 223.66 43099 +1904 265 12.94 6.94 11.29 0 340.24 294.12 42894 +1904 266 13.74 7.74 12.09 0.7 356.73 217.61 42690 +1904 267 13.5 7.5 11.85 0.05 351.71 215.92 42486 +1904 268 13.07 7.07 11.42 0 342.87 286.07 42282 +1904 269 11.7 5.7 10.05 0.15 315.97 214.36 42078 +1904 270 14.5 8.5 12.85 0 373.03 278.27 41875 +1904 271 22.12 16.12 20.47 0.08 574.76 193.22 41671 +1904 272 23.87 17.87 22.22 0 632.32 249.71 41468 +1904 273 22.01 16.01 20.36 0 571.29 252.94 41265 +1904 274 20.77 14.77 19.12 0 533.45 253.78 41062 +1904 275 19.91 13.91 18.26 0 508.47 253.33 40860 +1904 276 18.23 12.23 16.58 0.72 462.54 191.02 40658 +1904 277 18.51 12.51 16.86 1.58 469.94 188.6 40456 +1904 278 12.78 6.78 11.13 0.55 337.02 194.72 40255 +1904 279 11.44 5.44 9.79 0 311.07 258.85 40054 +1904 280 12.01 6.01 10.36 0.01 321.89 191.5 39854 +1904 281 15.61 9.61 13.96 0 397.97 246.58 39654 +1904 282 13.06 7.06 11.41 1.19 342.67 186.17 39455 +1904 283 13.26 7.26 11.61 0.06 346.76 183.82 39256 +1904 284 13.85 7.85 12.2 0.14 359.05 180.85 39058 +1904 285 14.31 8.31 12.66 0.11 368.89 178.31 38861 +1904 286 14.6 8.6 12.95 0 375.22 234.52 38664 +1904 287 15.56 9.56 13.91 0.94 396.81 172.48 38468 +1904 288 7.59 1.59 5.94 0.46 245.81 178.7 38273 +1904 289 10.21 4.21 8.56 1.36 288.77 174.42 38079 +1904 290 8.3 2.3 6.65 0 256.87 231.91 37885 +1904 291 7.09 1.09 5.44 0 238.26 230.44 37693 +1904 292 9.49 3.49 7.84 0.48 276.37 168.83 37501 +1904 293 16.14 10.14 14.49 0.45 410.37 159.65 37311 +1904 294 14.18 8.18 12.53 0.47 366.09 159.91 37121 +1904 295 11.64 5.64 9.99 0 314.83 213.97 36933 +1904 296 13.56 7.56 11.91 0 352.96 208.77 36745 +1904 297 13.14 7.14 11.49 0 344.3 206.67 36560 +1904 298 13.41 7.41 11.76 0.07 349.85 152.78 36375 +1904 299 12.7 6.7 11.05 0.37 335.42 151.44 36191 +1904 300 10.01 4.01 8.36 0.33 285.28 151.92 36009 +1904 301 12.11 6.11 10.46 0.24 323.82 148.16 35829 +1904 302 12.92 6.92 11.27 0.01 339.83 145.44 35650 +1904 303 13.09 7.09 11.44 0.45 343.28 143.36 35472 +1904 304 13.97 7.97 12.32 0.24 361.6 140.65 35296 +1904 305 4.64 -1.36 2.99 0 204.11 194.51 35122 +1904 306 2.32 -3.68 0.67 0 175.74 193.84 34950 +1904 307 1.87 -4.13 0.22 0 170.65 191.56 34779 +1904 308 3.02 -2.98 1.37 0 183.92 188.16 34610 +1904 309 8.07 2.07 6.42 0 253.24 181.87 34444 +1904 310 11.89 5.89 10.24 0.04 319.59 131.64 34279 +1904 311 7.93 1.93 6.28 0 251.05 177.36 34116 +1904 312 4.97 -1.03 3.32 0 208.45 177.09 33956 +1904 313 2.3 -3.7 0.65 0 175.51 176.72 33797 +1904 314 3.72 -2.28 2.07 0 192.42 173.83 33641 +1904 315 3.7 -2.3 2.05 0 192.17 171.28 33488 +1904 316 3.77 -2.23 2.12 0 193.04 169.03 33337 +1904 317 -0.77 -6.77 -2.42 0.29 143.28 167.61 33188 +1904 318 3.3 -2.7 1.65 0.43 187.28 163.95 33042 +1904 319 3.74 -2.26 2.09 0 192.67 162.75 32899 +1904 320 5.39 -0.61 3.74 0 214.09 159.77 32758 +1904 321 8.55 2.55 6.9 0 260.86 155.22 32620 +1904 322 9.62 3.62 7.97 0.04 278.57 114.36 32486 +1904 323 8.56 2.56 6.91 0 261.02 151.8 32354 +1904 324 12.49 6.49 10.84 0 331.25 146.07 32225 +1904 325 11.17 5.17 9.52 0 306.05 145.72 32100 +1904 326 11.98 5.98 10.33 0.61 321.31 107.62 31977 +1904 327 10.27 4.27 8.62 1.93 289.83 107.48 31858 +1904 328 8.15 2.15 6.5 0 254.5 143.14 31743 +1904 329 7.35 1.35 5.7 0.17 242.16 106.7 31631 +1904 330 8.56 2.56 6.91 0.01 261.02 104.93 31522 +1904 331 9.79 3.79 8.14 0.01 281.48 103.19 31417 +1904 332 5.18 -0.82 3.53 0 211.25 139.35 31316 +1904 333 3.27 -2.73 1.62 0 186.92 139.39 31218 +1904 334 -0.7 -6.7 -2.35 0 143.96 140.2 31125 +1904 335 -3.23 -9.23 -4.88 0.01 121.28 147.55 31035 +1904 336 -1.72 -7.72 -3.37 0.23 134.41 147.14 30949 +1904 337 1.02 -4.98 -0.63 0 161.39 178.86 30867 +1904 338 0.85 -5.15 -0.8 0 159.59 177.99 30790 +1904 339 1.29 -4.71 -0.36 0 164.28 176.92 30716 +1904 340 2.75 -3.25 1.1 0.17 180.73 99.11 30647 +1904 341 1.44 -4.56 -0.21 0 165.91 131.87 30582 +1904 342 -1.7 -7.7 -3.35 0 134.59 132.43 30521 +1904 343 0.39 -5.61 -1.26 0.16 154.8 98.06 30465 +1904 344 -0.02 -6.02 -1.67 0.09 150.64 141.02 30413 +1904 345 0.83 -5.17 -0.82 0 159.38 172.62 30366 +1904 346 1.18 -4.82 -0.47 0 163.1 171.82 30323 +1904 347 -0.65 -6.65 -2.3 0 144.44 172.05 30284 +1904 348 5.1 -0.9 3.45 0 210.18 125.29 30251 +1904 349 6.65 0.65 5 1.2 231.79 92.97 30221 +1904 350 7.26 1.26 5.61 0.19 240.81 92.42 30197 +1904 351 3.63 -2.37 1.98 0 191.31 125.18 30177 +1904 352 9.03 3.03 7.38 0 268.69 121.67 30162 +1904 353 11.22 5.22 9.57 0 306.98 119.85 30151 +1904 354 11.91 5.91 10.26 0 319.97 119.22 30145 +1904 355 10.85 4.85 9.2 0 300.2 120.13 30144 +1904 356 9.38 3.38 7.73 0.18 274.51 91 30147 +1904 357 10.12 4.12 8.47 0.42 287.2 90.61 30156 +1904 358 10.53 4.53 8.88 0.21 294.44 90.42 30169 +1904 359 8.09 2.09 6.44 0.39 253.55 91.9 30186 +1904 360 7.89 1.89 6.24 0.1 250.43 92.28 30208 +1904 361 6.9 0.9 5.25 0 235.45 124.04 30235 +1904 362 6.39 0.39 4.74 0.45 228.04 93.6 30267 +1904 363 3.18 -2.82 1.53 0.15 185.83 95.43 30303 +1904 364 7.5 1.5 5.85 0.03 244.43 93.78 30343 +1904 365 4.16 -1.84 2.51 0 197.94 127.67 30388 +1905 1 0.77 -5.23 -0.88 0 158.75 130.26 30438 +1905 2 -4.68 -10.68 -6.33 0 109.74 133.03 30492 +1905 3 -1.38 -7.38 -3.03 0 137.53 132.84 30551 +1905 4 1.89 -4.11 0.24 0 170.88 132.34 30614 +1905 5 -0.05 -6.05 -1.7 0 150.34 133.88 30681 +1905 6 -0.93 -6.93 -2.58 0 141.76 135.14 30752 +1905 7 -1.47 -7.47 -3.12 0 136.7 136.16 30828 +1905 8 -2.19 -8.19 -3.84 0 130.2 137.94 30907 +1905 9 -3.14 -9.14 -4.79 0 122.03 139.56 30991 +1905 10 -4.15 -10.15 -5.8 0 113.84 141.22 31079 +1905 11 -4.55 -10.55 -6.2 0 110.73 142.36 31171 +1905 12 -2.81 -8.81 -4.46 0 124.82 142.79 31266 +1905 13 1.43 -4.57 -0.22 0 165.8 142.61 31366 +1905 14 -1.89 -7.89 -3.54 0 132.87 145.58 31469 +1905 15 1.74 -4.26 0.09 0 169.21 145.39 31575 +1905 16 -0.04 -6.04 -1.69 0 150.44 147.55 31686 +1905 17 0.09 -5.91 -1.56 0.46 151.75 111.89 31800 +1905 18 1.36 -4.64 -0.29 0.45 165.04 112.86 31917 +1905 19 -0.28 -6.28 -1.93 0.22 148.06 156.77 32038 +1905 20 -1.16 -7.16 -2.81 0 139.58 196.92 32161 +1905 21 -2.44 -8.44 -4.09 0 128.01 199.32 32289 +1905 22 -0.22 -6.22 -1.87 0.23 148.65 160.99 32419 +1905 23 -1.33 -7.33 -2.98 0 137.99 202.76 32552 +1905 24 -0.13 -6.13 -1.78 0 149.54 204.12 32688 +1905 25 -1.14 -7.14 -2.79 0 139.77 206.32 32827 +1905 26 -2.5 -8.5 -4.15 0 127.48 208.69 32969 +1905 27 -2.01 -8.01 -3.66 0 131.8 210.35 33114 +1905 28 -1.69 -7.69 -3.34 0.09 134.68 169.7 33261 +1905 29 -2.16 -8.16 -3.81 0.01 130.46 171.51 33411 +1905 30 -1.89 -7.89 -3.54 0 132.87 216.95 33564 +1905 31 -5.58 -11.58 -7.23 0.44 103.06 176.92 33718 +1905 32 1.15 -4.85 -0.5 0 162.78 220.68 33875 +1905 33 -1.22 -7.22 -2.87 0.13 139.02 179.01 34035 +1905 34 -0.18 -6.18 -1.83 0 149.05 226.25 34196 +1905 35 1.06 -4.94 -0.59 0 161.81 227.42 34360 +1905 36 1.83 -4.17 0.18 0 170.21 229.08 34526 +1905 37 6.34 0.34 4.69 0 227.32 227.33 34694 +1905 38 4.53 -1.47 2.88 0.62 202.68 182.89 34863 +1905 39 6.41 0.41 4.76 0 228.32 230.95 35035 +1905 40 3.93 -2.07 2.28 0.06 195.04 185.57 35208 +1905 41 0.21 -5.79 -1.44 0.92 152.96 189.16 35383 +1905 42 -0.49 -6.49 -2.14 0 145.99 242.52 35560 +1905 43 -0.24 -6.24 -1.89 0.18 148.45 193.45 35738 +1905 44 -1.15 -7.15 -2.8 0.29 139.68 196.37 35918 +1905 45 1.37 -4.63 -0.28 0 165.15 249.93 36099 +1905 46 4.06 -1.94 2.41 0.66 196.67 196.85 36282 +1905 47 4.13 -1.87 2.48 0 197.56 252.21 36466 +1905 48 3.52 -2.48 1.87 0 189.96 218.98 36652 +1905 49 3.56 -2.44 1.91 0 190.45 221.74 36838 +1905 50 4.9 -1.1 3.25 0 207.52 223.33 37026 +1905 51 0.96 -5.04 -0.69 0.22 160.75 171.96 37215 +1905 52 3.4 -2.6 1.75 0.01 188.49 172.78 37405 +1905 53 4.06 -1.94 2.41 0 196.67 232.81 37596 +1905 54 5.08 -0.92 3.43 0.04 209.91 176.02 37788 +1905 55 5.47 -0.53 3.82 0 215.17 237.34 37981 +1905 56 9.49 3.49 7.84 0 276.37 235.75 38175 +1905 57 8.22 2.22 6.57 0 255.6 240.08 38370 +1905 58 4.3 -1.7 2.65 0 199.72 246.93 38565 +1905 59 7.31 1.31 5.66 0 241.56 246.69 38761 +1905 60 12.47 6.47 10.82 0 330.86 242.94 38958 +1905 61 12.51 6.51 10.86 0 331.65 245.75 39156 +1905 62 11.64 5.64 9.99 0 314.83 249.77 39355 +1905 63 10.16 4.16 8.51 0 287.9 254.8 39553 +1905 64 4.5 -1.5 2.85 0.22 202.29 198.05 39753 +1905 65 3.22 -2.78 1.57 0.43 186.32 201.11 39953 +1905 66 4.07 -1.93 2.42 0 196.8 270.14 40154 +1905 67 6.23 0.23 4.58 0 225.75 270.9 40355 +1905 68 8.94 2.94 7.29 0 267.2 270.57 40556 +1905 69 8.11 2.11 6.46 0 253.87 274.23 40758 +1905 70 7.21 1.21 5.56 0.03 240.06 208.62 40960 +1905 71 9.59 3.59 7.94 0 278.06 278.04 41163 +1905 72 8.21 2.21 6.56 0 255.44 282.67 41366 +1905 73 7.27 1.27 5.62 0 240.96 286.5 41569 +1905 74 9.85 3.85 8.2 0 282.51 285.86 41772 +1905 75 14.12 8.12 12.47 0.21 364.8 211.17 41976 +1905 76 17.46 11.46 15.81 0.35 442.7 207.91 42179 +1905 77 18.87 12.87 17.22 0 479.6 276.32 42383 +1905 78 11.86 5.86 10.21 0.29 319.01 219.97 42587 +1905 79 10.58 4.58 8.93 1.36 295.33 223.52 42791 +1905 80 8.29 2.29 6.64 0.12 256.71 227.9 42996 +1905 81 6.74 0.74 5.09 0 233.1 308.44 43200 +1905 82 6.19 0.19 4.54 0 225.19 311.78 43404 +1905 83 5.37 -0.63 3.72 0 213.82 315.25 43608 +1905 84 6.27 0.27 4.62 0 226.32 316.75 43812 +1905 85 7.05 1.05 5.4 0.37 237.67 238.72 44016 +1905 86 5.75 -0.25 4.1 0.12 219.02 241.75 44220 +1905 87 5.58 -0.42 3.93 0.35 216.68 243.82 44424 +1905 88 5.32 -0.68 3.67 0.7 213.14 245.84 44627 +1905 89 9.49 3.49 7.84 0.01 276.37 243.36 44831 +1905 90 10.1 4.1 8.45 0 286.85 325.89 45034 +1905 91 14.14 8.14 12.49 0 365.23 320.78 45237 +1905 92 7.86 1.86 6.21 0 249.96 333.77 45439 +1905 93 8.23 2.23 6.58 0.02 255.76 251.6 45642 +1905 94 10.76 4.76 9.11 1.34 298.57 250.25 45843 +1905 95 15.01 9.01 13.36 1.16 384.31 245.64 46045 +1905 96 13.72 7.72 12.07 0.39 356.31 249.26 46246 +1905 97 10.49 4.49 8.84 0 293.72 340.43 46446 +1905 98 8.48 2.48 6.83 0 259.74 345.62 46647 +1905 99 12.52 6.52 10.87 0 331.84 340.72 46846 +1905 100 16.69 10.69 15.04 0 423.59 333.43 47045 +1905 101 15.11 9.11 13.46 0.19 386.56 254.32 47243 +1905 102 15.89 9.89 14.24 0.01 404.48 254.36 47441 +1905 103 13.53 7.53 11.88 0.16 352.34 259.69 47638 +1905 104 11.22 5.22 9.57 0.03 306.98 264.45 47834 +1905 105 12.77 6.77 11.12 1.01 336.82 263.56 48030 +1905 106 9.17 3.17 7.52 0.01 271 269.7 48225 +1905 107 10.73 4.73 9.08 0.47 298.03 268.97 48419 +1905 108 15.15 9.15 13.5 0 387.46 351.25 48612 +1905 109 14.23 8.23 12.58 0 367.17 354.96 48804 +1905 110 11.11 5.11 9.46 0 304.95 362.73 48995 +1905 111 8.97 2.97 7.32 0.47 267.7 276.02 49185 +1905 112 6.51 0.51 4.86 1.46 229.76 279.97 49374 +1905 113 4.78 -1.22 3.13 0.14 205.94 282.72 49561 +1905 114 5.8 -0.2 4.15 0 219.72 377.17 49748 +1905 115 9.11 3.11 7.46 0 270.01 373.67 49933 +1905 116 10.53 4.53 8.88 0 294.44 372.43 50117 +1905 117 11.91 5.91 10.26 0 319.97 371.13 50300 +1905 118 8.83 2.83 7.18 0 265.4 378.05 50481 +1905 119 13.06 7.06 11.41 0 342.67 371.27 50661 +1905 120 10.6 4.6 8.95 0.01 295.69 283.02 50840 +1905 121 10.22 4.22 8.57 0 288.95 379.2 51016 +1905 122 12.62 6.62 10.97 0 333.83 375.72 51191 +1905 123 14.13 8.13 12.48 0 365.02 373.43 51365 +1905 124 13.98 7.98 12.33 0 361.81 374.86 51536 +1905 125 17.06 11.06 15.41 0 432.68 368.08 51706 +1905 126 14.84 8.84 13.19 0.1 380.52 281.11 51874 +1905 127 18.74 12.74 17.09 0 476.09 365.06 52039 +1905 128 17.52 11.52 15.87 0.35 444.22 277.23 52203 +1905 129 16.3 10.3 14.65 0.03 414.18 280.38 52365 +1905 130 16.88 10.88 15.23 0 428.23 373.06 52524 +1905 131 16.19 10.19 14.54 0.11 411.56 281.79 52681 +1905 132 16.05 10.05 14.4 1.27 408.24 282.68 52836 +1905 133 12.76 6.76 11.11 0 336.62 385.48 52989 +1905 134 15.01 9.01 13.36 0.43 384.31 285.74 53138 +1905 135 19.32 13.32 17.67 0.01 491.92 277.13 53286 +1905 136 20.2 14.2 18.55 0.79 516.78 275.43 53430 +1905 137 18.65 12.65 17 1.2 473.68 279.69 53572 +1905 138 19.01 13.01 17.36 1.48 483.41 279.3 53711 +1905 139 18.67 12.67 17.02 1.62 474.21 280.61 53848 +1905 140 13.35 7.35 11.7 0.45 348.61 291.58 53981 +1905 141 17.46 11.46 15.81 0.49 442.7 284.01 54111 +1905 142 19.69 13.69 18.04 0.01 502.24 279.22 54238 +1905 143 14.71 8.71 13.06 0.48 377.64 290.29 54362 +1905 144 14.24 8.24 12.59 0 367.38 388.68 54483 +1905 145 17.71 11.71 16.06 0 449.06 379.92 54600 +1905 146 18.9 12.9 17.25 0 480.41 376.67 54714 +1905 147 19.45 13.45 17.8 0.05 495.53 281.53 54824 +1905 148 20.14 14.14 18.49 0 515.05 373.46 54931 +1905 149 21.58 15.58 19.93 0.12 557.92 276.51 55034 +1905 150 20.22 14.22 18.57 0.82 517.36 280.37 55134 +1905 151 21.46 15.46 19.81 0.82 554.23 277.37 55229 +1905 152 26.17 20.17 24.52 0 715.34 350.21 55321 +1905 153 25.61 19.61 23.96 0 694.32 353.06 55409 +1905 154 26.4 20.4 24.75 0 724.13 349.64 55492 +1905 155 26.15 20.15 24.5 0 714.58 351.01 55572 +1905 156 24.6 18.6 22.95 0.6 657.73 268.79 55648 +1905 157 25.54 19.54 23.89 1.34 691.73 265.75 55719 +1905 158 23.1 17.1 21.45 0.07 606.42 273.76 55786 +1905 159 20.92 14.92 19.27 0.15 537.91 280.14 55849 +1905 160 22.5 16.5 20.85 0 586.86 367.81 55908 +1905 161 22.24 16.24 20.59 0 578.56 368.88 55962 +1905 162 15.64 9.64 13.99 0 398.66 390.07 56011 +1905 163 15.66 9.66 14.01 0.05 399.12 292.68 56056 +1905 164 15.37 9.37 13.72 0.04 392.46 293.28 56097 +1905 165 16.19 10.19 14.54 0 411.56 388.96 56133 +1905 166 15.91 9.91 14.26 0 404.95 389.8 56165 +1905 167 20.19 14.19 18.54 0 516.49 376.75 56192 +1905 168 20.72 14.72 19.07 0 531.97 374.99 56214 +1905 169 20.37 14.37 18.72 0 521.7 376.22 56231 +1905 170 19.95 13.95 18.3 0.06 509.61 283.24 56244 +1905 171 22.11 16.11 20.46 0.41 574.44 277.47 56252 +1905 172 22.16 16.16 20.51 0 576.02 369.75 56256 +1905 173 22.09 16.09 20.44 1.27 573.81 277.5 56255 +1905 174 17.1 11.1 15.45 0.11 433.67 289.87 56249 +1905 175 20.02 14.02 18.37 0.62 511.61 283.01 56238 +1905 176 21.43 15.43 19.78 0.08 553.32 279.24 56223 +1905 177 23.44 17.44 21.79 0 617.74 364.41 56203 +1905 178 25.09 19.09 23.44 0.03 675.27 268.01 56179 +1905 179 23.1 17.1 21.45 0.17 606.42 274.29 56150 +1905 180 19.1 13.1 17.45 0 485.86 380.04 56116 +1905 181 21.18 15.18 19.53 0 545.72 372.87 56078 +1905 182 22.34 16.34 20.69 0.12 581.74 276.29 56035 +1905 183 22.59 16.59 20.94 0 589.76 367.24 55987 +1905 184 26.55 20.55 24.9 0.51 729.9 262.33 55935 +1905 185 27.47 21.47 25.82 0.33 766.21 258.84 55879 +1905 186 24.2 18.2 22.55 0.11 643.7 270.13 55818 +1905 187 23.87 17.87 22.22 0.3 632.32 271.04 55753 +1905 188 23.29 17.29 21.64 0.14 612.72 272.64 55684 +1905 189 27.17 21.17 25.52 0 754.21 345.79 55611 +1905 190 30.66 24.66 29.01 0 904.15 326.21 55533 +1905 191 30.93 24.93 29.28 0 916.73 324.33 55451 +1905 192 25.28 19.28 23.63 0.7 682.18 265.43 55366 +1905 193 25.84 19.84 24.19 0 702.89 351.07 55276 +1905 194 26.93 20.93 25.28 0 744.72 345.63 55182 +1905 195 30.96 24.96 29.31 0 918.14 323.2 55085 +1905 196 30.47 24.47 28.82 0.09 895.39 244.34 54984 +1905 197 29.52 23.52 27.87 0.04 852.64 248.15 54879 +1905 198 29.82 23.82 28.17 0.09 865.95 246.58 54770 +1905 199 28.87 22.87 27.22 0.02 824.39 250.33 54658 +1905 200 24.15 18.15 22.5 0.01 641.97 267.1 54542 +1905 201 22.39 16.39 20.74 0.41 583.34 272.06 54423 +1905 202 23.39 17.39 21.74 0.26 616.06 268.7 54301 +1905 203 22.07 16.07 20.42 0.12 573.18 272.18 54176 +1905 204 23.21 17.21 21.56 0 610.06 358 54047 +1905 205 22.88 16.88 21.23 0.72 599.18 269.1 53915 +1905 206 20.6 14.6 18.95 0.38 528.43 274.96 53780 +1905 207 20.95 14.95 19.3 0.68 538.81 273.56 53643 +1905 208 18.18 12.18 16.53 2.07 461.23 279.8 53502 +1905 209 18.47 12.47 16.82 0.03 468.88 278.65 53359 +1905 210 19.25 13.25 17.6 0 489.98 368.49 53213 +1905 211 19.88 13.88 18.23 0 507.62 365.67 53064 +1905 212 20.45 14.45 18.8 0.66 524.04 272.24 52913 +1905 213 16.87 10.87 15.22 0.02 427.99 279.87 52760 +1905 214 14.13 8.13 12.48 0 365.02 379.34 52604 +1905 215 14.55 8.55 12.9 0.55 374.12 283.23 52445 +1905 216 18.05 12.05 16.4 0 457.83 367.33 52285 +1905 217 17.73 11.73 16.08 0 449.57 367.35 52122 +1905 218 20.43 14.43 18.78 0 523.45 358.15 51958 +1905 219 19.6 13.6 17.95 0.15 499.72 269.86 51791 +1905 220 15.99 9.99 14.34 0.96 406.83 276.92 51622 +1905 221 22.82 16.82 21.17 0.01 597.22 260 51451 +1905 222 19.43 13.43 17.78 0.39 494.97 268.02 51279 +1905 223 19.48 13.48 17.83 0.53 496.36 267.04 51105 +1905 224 20.42 14.42 18.77 0.22 523.16 263.98 50929 +1905 225 21.06 15.06 19.41 0.02 542.1 261.51 50751 +1905 226 24.07 18.07 22.42 0.02 639.2 252.29 50572 +1905 227 27.04 21.04 25.39 0 749.06 322.19 50392 +1905 228 25.27 19.27 23.62 0.01 681.82 246.75 50210 +1905 229 23.38 17.38 21.73 0.2 615.73 251.61 50026 +1905 230 24.53 18.53 22.88 1.11 655.26 247.27 49842 +1905 231 23.2 17.2 21.55 0.32 609.73 250.12 49656 +1905 232 25.57 19.57 23.92 0 692.84 322.63 49469 +1905 233 28.43 22.43 26.78 0 805.71 308.02 49280 +1905 234 27.23 21.23 25.58 2.04 756.6 234.38 49091 +1905 235 29.68 23.68 28.03 0 859.71 298.93 48900 +1905 236 33.48 27.48 31.83 0.01 1042.97 206.58 48709 +1905 237 29.39 23.39 27.74 0.05 846.92 223.25 48516 +1905 238 28.17 22.17 26.52 0.06 794.85 226.69 48323 +1905 239 28.81 22.81 27.16 0 821.82 297.73 48128 +1905 240 28.51 22.51 26.86 1.41 809.08 223.2 47933 +1905 241 28.55 22.55 26.9 0.16 810.77 221.87 47737 +1905 242 25.84 19.84 24.19 0 702.89 306.51 47541 +1905 243 25.33 19.33 23.68 0 684.01 306.87 47343 +1905 244 21.73 15.73 20.08 0 562.55 318.4 47145 +1905 245 23.58 17.58 21.93 0 622.45 310.14 46947 +1905 246 20.84 14.84 19.19 0 535.53 317.55 46747 +1905 247 20.04 14.04 18.39 1.51 512.18 238.63 46547 +1905 248 22.05 16.05 20.4 0.53 572.55 232.45 46347 +1905 249 22.93 16.93 21.28 0.03 600.82 228.7 46146 +1905 250 21.65 15.65 20 0 560.08 307.34 45945 +1905 251 23.47 17.47 21.82 0 618.75 299.14 45743 +1905 252 19.37 13.37 17.72 0.08 493.3 232.5 45541 +1905 253 19.14 13.14 17.49 0 486.96 308.55 45339 +1905 254 17.97 11.97 16.32 0.01 455.76 232.15 45136 +1905 255 24.53 18.53 22.88 0.01 655.26 215.29 44933 +1905 256 21.41 15.41 19.76 0.01 552.71 221.55 44730 +1905 257 21.19 15.19 19.54 0 546.02 293.98 44527 +1905 258 20.02 14.02 18.37 0.6 511.61 221.33 44323 +1905 259 18.16 12.16 16.51 1.46 460.7 223.25 44119 +1905 260 19.42 13.42 17.77 0 494.69 292.04 43915 +1905 261 21.19 15.19 19.54 0.8 546.02 213.49 43711 +1905 262 20.72 14.72 19.07 1.33 531.97 212.79 43507 +1905 263 15.16 9.16 13.51 0.29 387.69 221.14 43303 +1905 264 17.31 11.31 15.66 0 438.92 287.58 43099 +1905 265 21.53 15.53 19.88 0 556.38 274.21 42894 +1905 266 17.88 11.88 16.23 0.1 453.43 211.08 42690 +1905 267 19.77 13.77 18.12 0 504.5 274.1 42486 +1905 268 17.48 11.48 15.83 0 443.2 277.2 42282 +1905 269 14.67 8.67 13.02 0.05 376.76 210.44 42078 +1905 270 15.13 9.13 13.48 0 387.01 277.05 41875 +1905 271 19.87 13.87 18.22 0 507.33 263.79 41671 +1905 272 20.47 14.47 18.82 0 524.62 259.59 41468 +1905 273 21.56 15.56 19.91 0.16 557.3 190.65 41265 +1905 274 8.46 2.46 6.81 0.81 259.42 207.73 41062 +1905 275 7.42 1.42 5.77 0.02 243.22 206.55 40860 +1905 276 9.49 3.49 7.84 0 276.37 270.05 40658 +1905 277 8.81 2.81 7.16 0 265.08 268.21 40456 +1905 278 10.66 4.66 9.01 0.16 296.77 197.12 40255 +1905 279 9.07 3.07 7.42 0.4 269.35 196.57 40054 +1905 280 9.05 3.05 7.4 0.42 269.02 194.56 39854 +1905 281 8.23 2.23 6.58 1.63 255.76 193.23 39654 +1905 282 14.25 8.25 12.6 0.76 367.6 184.71 39455 +1905 283 17.35 11.35 15.7 0.92 439.92 178.3 39256 +1905 284 16.54 10.54 14.89 0.21 419.95 177.28 39058 +1905 285 13.06 7.06 11.41 0 342.67 239.75 38861 +1905 286 12.86 6.86 11.21 0.75 338.63 177.97 38664 +1905 287 10.61 4.61 8.96 0.26 295.87 178.13 38468 +1905 288 10.14 4.14 8.49 0.23 287.55 176.48 38273 +1905 289 11.35 5.35 9.7 0 309.39 231.08 38079 +1905 290 10.98 4.98 9.33 0.04 302.56 171.52 37885 +1905 291 10.99 4.99 9.34 1.02 302.75 169.48 37693 +1905 292 7.83 1.83 6.18 0.28 249.5 170.2 37501 +1905 293 5.97 -0.03 4.32 2.07 222.09 169.49 37311 +1905 294 5.66 -0.34 4.01 1.59 217.78 167.5 37121 +1905 295 6.22 0.22 4.57 0 225.61 219.93 36933 +1905 296 5.05 -0.95 3.4 0.09 209.51 163.74 36745 +1905 297 2.61 -3.39 0.96 0.05 179.09 163.08 36560 +1905 298 4.22 -1.78 2.57 0.15 198.7 160.16 36375 +1905 299 7.86 1.86 6.21 0.11 249.96 155.63 36191 +1905 300 6.91 0.91 5.26 0.31 235.6 154.28 36009 +1905 301 4.51 -1.49 2.86 0 202.42 205.19 35829 +1905 302 7.49 1.49 5.84 0 244.28 199.98 35650 +1905 303 6.24 0.24 4.59 0.41 225.9 148.87 35472 +1905 304 3.92 -2.08 2.27 2.05 194.91 148.37 35296 +1905 305 5.38 -0.62 3.73 0.77 213.95 145.45 35122 +1905 306 7.64 1.64 5.99 0.59 246.57 142.29 34950 +1905 307 8.25 2.25 6.6 1.02 256.08 139.98 34779 +1905 308 7.49 1.49 5.84 1.31 244.28 138.54 34610 +1905 309 12.01 6.01 10.36 0.54 321.89 133.34 34444 +1905 310 13.47 7.47 11.82 0.27 351.09 130.21 34279 +1905 311 11.69 5.69 10.04 0.12 315.78 130.2 34116 +1905 312 9.82 3.82 8.17 0.08 282 129.71 33956 +1905 313 9.54 3.54 7.89 0 277.21 171.11 33797 +1905 314 8.2 2.2 6.55 0.09 255.28 127.8 33641 +1905 315 6.06 0.06 4.41 1.61 223.35 127.21 33488 +1905 316 5.47 -0.53 3.82 1.06 215.17 125.89 33337 +1905 317 8.32 2.32 6.67 0.02 257.19 122.55 33188 +1905 318 8.98 2.98 7.33 0.16 267.86 120.37 33042 +1905 319 9.01 3.01 7.36 0.1 268.36 119.08 32899 +1905 320 8.92 2.92 7.27 1.1 266.88 117.75 32758 +1905 321 5.97 -0.03 4.32 0 222.09 157.24 32620 +1905 322 8.8 2.8 7.15 0.07 264.91 114.9 32486 +1905 323 9.79 3.79 8.14 0.65 281.48 113.05 32354 +1905 324 7.36 1.36 5.71 0.48 242.31 113.04 32225 +1905 325 7.98 1.98 6.33 0.04 251.83 111.39 32100 +1905 326 7.44 1.44 5.79 0.51 243.52 110.62 31977 +1905 327 9.81 3.81 8.16 1.4 281.82 107.79 31858 +1905 328 9.06 3.06 7.41 1.05 269.18 106.81 31743 +1905 329 8.57 2.57 6.92 0.87 261.19 105.99 31631 +1905 330 6.88 0.88 5.23 0.22 235.16 105.87 31522 +1905 331 6.77 0.77 5.12 0.02 233.54 104.95 31417 +1905 332 7.01 1.01 5.36 0.14 237.08 103.6 31316 +1905 333 8.39 2.39 6.74 0.72 258.3 102.02 31218 +1905 334 6.99 0.99 5.34 0 236.78 135.97 31125 +1905 335 1.4 -4.6 -0.25 0 165.48 138.06 31035 +1905 336 2.51 -3.49 0.86 0 177.93 136.43 30949 +1905 337 6.83 0.83 5.18 0 234.42 132.19 30867 +1905 338 6.14 0.14 4.49 0 224.48 131.71 30790 +1905 339 5.63 -0.37 3.98 0 217.37 131.25 30716 +1905 340 1.16 -4.84 -0.49 0 162.88 132.93 30647 +1905 341 3.19 -2.81 1.54 0 185.95 131 30582 +1905 342 2.36 -3.64 0.71 0.03 176.2 98 30521 +1905 343 2.65 -3.35 1 0 179.56 129.69 30465 +1905 344 2.33 -3.67 0.68 0 175.86 128.71 30413 +1905 345 5.17 -0.83 3.52 0.05 211.12 95.06 30366 +1905 346 3.73 -2.27 2.08 0 192.55 127.01 30323 +1905 347 3.33 -2.67 1.68 0 187.64 126.62 30284 +1905 348 1.07 -4.93 -0.58 0 161.92 127.37 30251 +1905 349 3.65 -2.35 2 0 191.56 125.72 30221 +1905 350 1.55 -4.45 -0.1 0 167.11 126.43 30197 +1905 351 4.8 -1.2 3.15 0 206.2 124.54 30177 +1905 352 6.65 0.65 5 0 231.79 123.32 30162 +1905 353 7.51 1.51 5.86 0 244.59 122.69 30151 +1905 354 5.13 -0.87 3.48 0 210.58 124.15 30145 +1905 355 4.52 -1.48 2.87 0 202.55 124.5 30144 +1905 356 3.91 -2.09 2.26 0 194.79 124.86 30147 +1905 357 0.68 -5.32 -0.97 0 157.8 126.49 30156 +1905 358 2.49 -3.51 0.84 0.09 177.7 94.3 30169 +1905 359 4.89 -1.11 3.24 0 207.39 124.58 30186 +1905 360 5.46 -0.54 3.81 0 215.04 124.61 30208 +1905 361 5.27 -0.73 3.62 0 212.46 125.05 30235 +1905 362 4.71 -1.29 3.06 0 205.02 125.82 30267 +1905 363 7.89 1.89 6.24 0 250.43 124.38 30303 +1905 364 11.32 5.32 9.67 0 308.83 122.07 30343 +1905 365 7.05 1.05 5.4 0.04 237.67 94.43 30388 +1906 1 4.29 -1.71 2.64 0 199.59 128.49 30438 +1906 2 3.02 -2.98 1.37 0 183.92 129.91 30492 +1906 3 2.15 -3.85 0.5 0 173.81 131.3 30551 +1906 4 2.22 -3.78 0.57 0 174.6 132.18 30614 +1906 5 4.43 -1.57 2.78 1.16 201.39 98.73 30681 +1906 6 5.62 -0.38 3.97 0.43 217.23 98.86 30752 +1906 7 5.43 -0.57 3.78 0.04 214.63 99.54 30828 +1906 8 3.38 -2.62 1.73 0 188.25 135.4 30907 +1906 9 2.62 -3.38 0.97 0 179.21 137.06 30991 +1906 10 3.56 -2.44 1.91 0.01 190.45 103.39 31079 +1906 11 1.2 -4.8 -0.45 0 163.31 140.08 31171 +1906 12 -0.82 -6.82 -2.47 0 142.8 142.01 31266 +1906 13 5.68 -0.32 4.03 0 218.05 140.18 31366 +1906 14 0.11 -5.89 -1.54 0.06 151.95 108.54 31469 +1906 15 -2.08 -8.08 -3.73 0.13 131.17 152.54 31575 +1906 16 -1.31 -7.31 -2.96 0.01 138.18 153.16 31686 +1906 17 -0.59 -6.59 -2.24 0 145.02 191.43 31800 +1906 18 -0.82 -6.82 -2.47 0.05 142.8 155.56 31917 +1906 19 -0.61 -6.61 -2.26 0.18 144.83 157.34 32038 +1906 20 -0.29 -6.29 -1.94 0.52 147.96 159.82 32161 +1906 21 0.82 -5.18 -0.83 0.09 159.27 160.66 32289 +1906 22 -1.19 -7.19 -2.84 0 139.3 202.28 32419 +1906 23 -4.12 -10.12 -5.77 0 114.08 205.08 32552 +1906 24 0.41 -5.59 -1.24 0.46 155.01 164.46 32688 +1906 25 -1.29 -7.29 -2.94 0.84 138.37 168.77 32827 +1906 26 1.93 -4.07 0.28 0.33 171.33 168.57 32969 +1906 27 6.38 0.38 4.73 0 227.89 207.98 33114 +1906 28 5.6 -0.4 3.95 0 216.95 209.89 33261 +1906 29 4.56 -1.44 2.91 0 203.07 212.26 33411 +1906 30 4.96 -1.04 3.31 0.07 208.32 170.4 33564 +1906 31 3.7 -2.3 2.05 0 192.17 216.04 33718 +1906 32 1.95 -4.05 0.3 0 171.55 218.84 33875 +1906 33 2.97 -3.03 1.32 0 183.33 220.31 34035 +1906 34 7.36 1.36 5.71 0 242.31 218.16 34196 +1906 35 5.12 -0.88 3.47 0 210.45 183.44 34360 +1906 36 5.9 -0.1 4.25 0 221.11 185.34 34526 +1906 37 3.13 -2.87 1.48 0 185.23 189.8 34694 +1906 38 5.35 -0.65 3.7 0 213.54 190.93 34863 +1906 39 6.39 0.39 4.74 1.7 228.04 144.51 35035 +1906 40 5.53 -0.47 3.88 1.94 215.99 147 35208 +1906 41 2.38 -3.62 0.73 0.09 176.43 150.7 35383 +1906 42 2.7 -3.3 1.05 0 180.14 203.29 35560 +1906 43 0.77 -5.23 -0.88 0.03 158.75 155.45 35738 +1906 44 -0.46 -6.46 -2.11 0 146.29 210.59 35918 +1906 45 1.84 -4.16 0.19 0 170.32 211.82 36099 +1906 46 1.32 -4.68 -0.33 0.07 164.61 161.15 36282 +1906 47 5.2 -0.8 3.55 0.45 211.52 161.11 36466 +1906 48 2.27 -3.73 0.62 0.24 175.17 164.93 36652 +1906 49 3.57 -2.43 1.92 0 190.57 221.73 36838 +1906 50 5.82 -0.18 4.17 0.11 219.99 166.89 37026 +1906 51 8.45 2.45 6.8 0 259.26 222.86 37215 +1906 52 9.81 3.81 8.16 0 281.82 224.11 37405 +1906 53 10.33 4.33 8.68 0.21 290.89 169.8 37596 +1906 54 1.88 -4.12 0.23 0.01 170.77 177.96 37788 +1906 55 0.28 -5.72 -1.37 0.27 153.68 181.06 37981 +1906 56 1.83 -4.17 0.18 0 170.21 243.06 38175 +1906 57 0.46 -5.54 -1.19 0.05 155.52 185.21 38370 +1906 58 1.86 -4.14 0.21 0 170.54 248.91 38565 +1906 59 0.84 -5.16 -0.81 0.03 159.48 189.3 38761 +1906 60 5.89 -0.11 4.24 0 220.97 251.05 38958 +1906 61 10.17 4.17 8.52 0.08 288.07 186.79 39156 +1906 62 11.14 5.14 9.49 0.13 305.5 187.86 39355 +1906 63 12.42 6.42 10.77 1.29 329.87 188.67 39553 +1906 64 11.21 5.21 9.56 0.19 306.79 192.16 39753 +1906 65 10.4 4.4 8.75 0.01 292.12 195.15 39953 +1906 66 4.89 -1.11 3.24 1.19 207.39 202.02 40154 +1906 67 7.49 1.49 5.84 0.1 244.28 202.12 40355 +1906 68 5.63 -0.37 3.98 0 217.37 274.42 40556 +1906 69 11.66 5.66 10.01 0 315.21 269.34 40758 +1906 70 10.12 4.12 8.47 0 287.2 274.41 40960 +1906 71 9.82 3.82 8.17 0 282 277.72 41163 +1906 72 13 7 11.35 0 341.45 275.6 41366 +1906 73 7.47 1.47 5.82 0.36 243.98 214.69 41569 +1906 74 7.46 1.46 5.81 0 243.83 289.02 41772 +1906 75 6.29 0.29 4.64 0 226.61 293.14 41976 +1906 76 6.8 0.8 5.15 0.03 233.98 221.4 42179 +1906 77 4.28 -1.72 2.63 0 199.47 300.6 42383 +1906 78 4.22 -1.78 2.57 0.31 198.7 227.52 42587 +1906 79 -2.58 -8.58 -4.23 0.09 126.79 264.86 42791 +1906 80 -1.2 -7.2 -2.85 0 139.21 344.3 42996 +1906 81 2.05 -3.95 0.4 0.29 172.67 265.62 43200 +1906 82 6.55 0.55 4.9 0.01 230.34 233.51 43404 +1906 83 9.4 3.4 7.75 0 274.85 310.02 43608 +1906 84 7.85 1.85 6.2 0.63 249.81 236.05 43812 +1906 85 9.81 3.81 8.16 0 281.82 314.43 44016 +1906 86 12.94 6.94 11.29 0.03 340.24 233.65 44220 +1906 87 12.6 6.6 10.95 0 333.43 314.66 44424 +1906 88 10.84 4.84 9.19 0 300.02 320.06 44627 +1906 89 7.78 1.78 6.13 0.57 248.73 245.22 44831 +1906 90 5.65 -0.35 4 0.62 217.64 249.07 45034 +1906 91 10.47 4.47 8.82 0.24 293.37 245.66 45237 +1906 92 12.51 6.51 10.86 0 331.65 326.19 45439 +1906 93 14.71 8.71 13.06 0 377.64 323.95 45642 +1906 94 17.65 11.65 16 0 447.52 319.13 45843 +1906 95 17.26 11.26 15.61 0.01 437.66 241.65 46045 +1906 96 12.43 6.43 10.78 0.2 330.07 251.17 46246 +1906 97 12.63 6.63 10.98 0.24 334.03 252.41 46446 +1906 98 12.81 6.81 11.16 0.37 337.62 253.61 46647 +1906 99 17.9 11.9 16.25 0 453.94 328.42 46846 +1906 100 15.75 9.75 14.1 0.04 401.21 251.79 47045 +1906 101 15.56 9.56 13.91 0 396.81 338.06 47243 +1906 102 17.3 11.3 15.65 0.02 438.67 251.71 47441 +1906 103 16.59 10.59 14.94 0.03 421.16 254.42 47638 +1906 104 17.67 11.67 16.02 0.12 448.04 253.64 47834 +1906 105 14.52 8.52 12.87 0.04 373.46 260.77 48030 +1906 106 12.15 6.15 10.5 0.18 324.6 265.72 48225 +1906 107 11.18 5.18 9.53 0.79 306.24 268.36 48419 +1906 108 13.12 7.12 11.47 0.06 343.89 266.81 48612 +1906 109 14.3 8.3 12.65 0 368.68 354.8 48804 +1906 110 13.12 7.12 11.47 0.11 343.89 269.07 48995 +1906 111 12.5 6.5 10.85 0 331.45 361.59 49185 +1906 112 13.08 7.08 11.43 0 343.08 361.91 49374 +1906 113 11.3 5.3 9.65 0 308.46 366.82 49561 +1906 114 10.99 4.99 9.34 0 302.75 368.9 49748 +1906 115 11.36 5.36 9.71 0 309.57 369.65 49933 +1906 116 10.07 4.07 8.42 0.02 286.32 279.94 50117 +1906 117 8.56 2.56 6.91 0 261.02 377.15 50300 +1906 118 11.41 5.41 9.76 0.3 310.51 280.07 50481 +1906 119 12.67 6.67 11.02 0 334.82 372.1 50661 +1906 120 16.41 10.41 14.76 0 416.81 364.48 50840 +1906 121 23.8 17.8 22.15 0 629.93 341.37 51016 +1906 122 22.04 16.04 20.39 0.17 572.24 261.92 51191 +1906 123 21.62 15.62 19.97 0.5 559.15 263.79 51365 +1906 124 15.57 9.57 13.92 0 397.04 371.03 51536 +1906 125 17.05 11.05 15.4 0.63 432.43 276.08 51706 +1906 126 16.56 10.56 14.91 0.99 420.43 277.82 51874 +1906 127 16.52 10.52 14.87 0.01 419.46 278.56 52039 +1906 128 17.22 11.22 15.57 1.45 436.66 277.87 52203 +1906 129 17.15 11.15 15.5 0.04 434.92 278.65 52365 +1906 130 17.16 11.16 15.51 0 435.17 372.29 52524 +1906 131 18.47 12.47 16.82 0 468.88 369.26 52681 +1906 132 16.84 10.84 15.19 0 427.25 374.78 52836 +1906 133 13.73 7.73 12.08 0.3 356.52 287.49 52989 +1906 134 17.92 11.92 16.27 0.24 454.46 279.83 53138 +1906 135 21.63 15.63 19.98 0 559.46 361.62 53286 +1906 136 17.67 11.67 16.02 0.39 448.04 281.37 53430 +1906 137 17.85 11.85 16.2 0.64 452.65 281.5 53572 +1906 138 18.75 12.75 17.1 0.06 476.36 279.91 53711 +1906 139 17.66 11.66 16.01 0 447.78 377.18 53848 +1906 140 21.67 15.67 20.02 0 560.7 364.49 53981 +1906 141 16.02 10.02 14.37 0 407.53 382.66 54111 +1906 142 15.12 9.12 13.47 0.02 386.79 289.12 54238 +1906 143 14.2 8.2 12.55 0 366.52 388.29 54362 +1906 144 15.89 9.89 14.24 0.26 404.48 288.4 54483 +1906 145 15.88 9.88 14.23 0.22 404.24 288.77 54600 +1906 146 18.15 12.15 16.5 0.94 460.44 284.24 54714 +1906 147 20.29 14.29 18.64 0 519.38 372.58 54824 +1906 148 19.87 13.87 18.22 0.24 507.33 280.78 54931 +1906 149 18.07 12.07 16.42 0.82 458.35 285.3 55034 +1906 150 17.61 11.61 15.96 0.09 446.5 286.57 55134 +1906 151 19.59 13.59 17.94 0 499.44 376.33 55229 +1906 152 20.35 14.35 18.7 0 521.12 373.88 55321 +1906 153 22.52 16.52 20.87 0.01 587.51 274.63 55409 +1906 154 25.26 19.26 23.61 0.6 681.45 266.22 55492 +1906 155 24.29 18.29 22.64 0.76 646.84 269.57 55572 +1906 156 20.93 14.93 19.28 0.47 538.21 279.68 55648 +1906 157 20.55 14.55 18.9 0.04 526.96 280.81 55719 +1906 158 20.72 14.72 19.07 0.04 531.97 280.49 55786 +1906 159 20.39 14.39 18.74 0.01 522.29 281.53 55849 +1906 160 16.47 10.47 14.82 0.27 418.26 290.78 55908 +1906 161 18.01 12.01 16.36 0.74 456.79 287.49 55962 +1906 162 16.56 10.56 14.91 0.14 420.43 290.69 56011 +1906 163 15.55 9.55 13.9 0.36 396.58 292.89 56056 +1906 164 21.88 15.88 20.23 0 567.22 370.56 56097 +1906 165 24.31 18.31 22.66 0.55 647.54 270.64 56133 +1906 166 26.42 20.42 24.77 0.26 724.89 263.46 56165 +1906 167 24.51 18.51 22.86 0.15 654.55 270.01 56192 +1906 168 20.94 14.94 19.29 0.24 538.51 280.65 56214 +1906 169 18.92 12.92 17.27 0.23 480.96 285.78 56231 +1906 170 15.97 9.97 14.32 1.39 406.36 292.26 56244 +1906 171 17.38 11.38 15.73 0.74 440.68 289.34 56252 +1906 172 20.56 14.56 18.91 0 527.26 375.61 56256 +1906 173 22.7 16.7 21.05 0 593.32 367.64 56255 +1906 174 24.84 18.84 23.19 0 666.28 358.59 56249 +1906 175 21.35 15.35 19.7 0.03 550.88 279.49 56238 +1906 176 15.46 9.46 13.81 2.21 394.52 293.18 56223 +1906 177 14.78 8.78 13.13 0.41 379.19 294.4 56203 +1906 178 15.68 9.68 14.03 0.05 399.59 292.68 56179 +1906 179 15.26 9.26 13.61 0.01 389.95 293.42 56150 +1906 180 18.54 12.54 16.89 0 470.74 381.81 56116 +1906 181 23.23 17.23 21.58 0 610.73 365.01 56078 +1906 182 24.47 18.47 22.82 0.08 653.15 269.74 56035 +1906 183 22.37 16.37 20.72 0.06 582.7 276.07 55987 +1906 184 22.8 16.8 21.15 0 596.57 366.26 55935 +1906 185 24.55 18.55 22.9 0 655.97 358.91 55879 +1906 186 18.87 12.87 17.22 0.14 479.6 284.91 55818 +1906 187 18.6 12.6 16.95 1.01 472.34 285.4 55753 +1906 188 18.78 12.78 17.13 2.95 477.17 284.78 55684 +1906 189 17.85 11.85 16.2 0.84 452.65 286.78 55611 +1906 190 20.5 14.5 18.85 0.18 525.5 280.1 55533 +1906 191 19.02 13.02 17.37 0 483.68 378.12 55451 +1906 192 18.01 12.01 16.36 0.27 456.79 285.7 55366 +1906 193 16.72 10.72 15.07 0.27 424.32 288.3 55276 +1906 194 19.57 13.57 17.92 0.47 498.88 281.65 55182 +1906 195 22.48 16.48 20.83 0 586.22 364.88 55085 +1906 196 23.29 17.29 21.64 0 612.72 361.28 54984 +1906 197 23.61 17.61 21.96 0.04 623.47 269.64 54879 +1906 198 21.59 15.59 19.94 0 558.23 366.96 54770 +1906 199 24.27 18.27 22.62 0 646.14 356.01 54658 +1906 200 23.35 17.35 21.7 0.37 614.73 269.58 54542 +1906 201 28.19 22.19 26.54 0 795.68 336.6 54423 +1906 202 27.86 21.86 26.21 0.11 782.06 253.34 54301 +1906 203 26.34 20.34 24.69 1.56 721.82 258.62 54176 +1906 204 24.09 18.09 22.44 0.44 639.89 265.8 54047 +1906 205 25.49 19.49 23.84 0 689.89 347.79 53915 +1906 206 23.01 17.01 21.36 0 603.45 357.73 53780 +1906 207 24.06 18.06 22.41 0 638.85 352.83 53643 +1906 208 21.71 15.71 20.06 0 561.93 361.37 53502 +1906 209 22.22 16.22 20.57 0 577.92 358.84 53359 +1906 210 23.02 17.02 21.37 0 603.78 355.16 53213 +1906 211 21.73 15.73 20.08 0.55 562.55 269.45 53064 +1906 212 21.15 15.15 19.5 1.25 544.81 270.42 52913 +1906 213 21.64 15.64 19.99 0 559.77 358.06 52760 +1906 214 23.76 17.76 22.11 0.75 628.56 261.9 52604 +1906 215 18.75 12.75 17.1 0.36 476.36 274.69 52445 +1906 216 24.09 18.09 22.44 0.15 639.89 259.65 52285 +1906 217 19.96 13.96 18.31 0.13 509.9 270.39 52122 +1906 218 17.02 11.02 15.37 0 431.69 368.51 51958 +1906 219 14.41 8.41 12.76 0.21 371.06 280.57 51791 +1906 220 19.04 13.04 17.39 0 484.22 360.62 51622 +1906 221 18.48 12.48 16.83 0 469.14 361.31 51451 +1906 222 23.96 17.96 22.31 0 635.41 341.17 51279 +1906 223 25.73 19.73 24.08 0 698.78 332.56 51105 +1906 224 29.19 23.19 27.54 0 838.19 314.7 50929 +1906 225 24.52 18.52 22.87 0.58 654.91 251.74 50751 +1906 226 26.93 20.93 25.28 0.37 744.72 242.93 50572 +1906 227 22.74 16.74 21.09 0 594.62 340.3 50392 +1906 228 25.4 19.4 23.75 1.41 686.58 246.33 50210 +1906 229 20.76 14.76 19.11 0.18 533.15 258.64 50026 +1906 230 25.08 19.08 23.43 0 674.91 327.41 49842 +1906 231 28.92 22.92 27.27 0 826.53 308.08 49656 +1906 232 27.44 21.44 25.79 0 765.01 314.17 49469 +1906 233 27.67 21.67 26.02 0.09 774.3 233.81 49280 +1906 234 24.24 18.24 22.59 0.23 645.09 244.06 49091 +1906 235 18.82 12.82 17.17 1.53 478.25 256.87 48900 +1906 236 22.21 16.21 20.56 0 577.6 330.19 48709 +1906 237 17.32 11.32 15.67 0.54 439.17 257.68 48516 +1906 238 18.04 12.04 16.39 0.16 457.57 254.96 48323 +1906 239 20.18 14.18 18.53 0 516.2 332.16 48128 +1906 240 18.91 12.91 17.26 0 480.69 334.21 47933 +1906 241 17.65 11.65 16 0.15 447.52 251.98 47737 +1906 242 18.7 12.7 17.05 0 475.02 331.35 47541 +1906 243 19.85 13.85 18.2 0.43 506.77 244.61 47343 +1906 244 18.42 12.42 16.77 0 467.55 328.44 47145 +1906 245 21.33 15.33 19.68 0 550.27 317.91 46947 +1906 246 20.53 14.53 18.88 0.21 526.38 238.88 46747 +1906 247 18.69 12.69 17.04 0.38 474.75 241.53 46547 +1906 248 19.99 13.99 18.34 2.06 510.75 237.3 46347 +1906 249 16.21 10.21 14.56 0.55 412.03 243.28 46146 +1906 250 16.84 10.84 15.19 0 427.25 320.9 45945 +1906 251 17.21 11.21 15.56 0.03 436.41 238.4 45743 +1906 252 13.61 7.61 11.96 1.41 354.01 242.79 45541 +1906 253 18.91 12.91 17.26 0 480.69 309.18 45339 +1906 254 20.63 14.63 18.98 0.01 529.31 226.63 45136 +1906 255 16.96 10.96 15.31 0.36 430.2 232.34 44933 +1906 256 15.61 9.61 13.96 0 397.97 310.61 44730 +1906 257 15.59 9.59 13.94 0 397.51 308.48 44527 +1906 258 18.69 12.69 17.04 0.04 474.75 224.04 44323 +1906 259 20.07 14.07 18.42 0 513.04 292.59 44119 +1906 260 20.91 14.91 19.26 0 537.61 287.85 43915 +1906 261 19.55 13.55 17.9 0.04 498.32 216.96 43711 +1906 262 15.78 9.78 14.13 0.17 401.91 222.02 43507 +1906 263 13.87 7.87 12.22 0.61 359.47 223.06 43303 +1906 264 15.46 9.46 13.81 0 394.52 291.65 43099 +1906 265 17.03 11.03 15.38 0 431.94 285.87 42894 +1906 266 16.33 10.33 14.68 0.22 414.89 213.72 42690 +1906 267 18.27 12.27 16.62 0.8 463.59 208.4 42486 +1906 268 16.43 10.43 14.78 0.52 417.29 209.64 42282 +1906 269 15.22 9.22 13.57 0 389.05 279.51 42078 +1906 270 15.69 9.69 14.04 1.91 399.82 206.95 41875 +1906 271 16.16 10.16 14.51 0.35 410.84 204.27 41671 +1906 272 15.76 9.76 14.11 0.33 401.44 202.85 41468 +1906 273 14.71 8.71 13.06 0.1 377.64 202.48 41265 +1906 274 12.49 6.49 10.84 0 331.25 271.17 41062 +1906 275 13.35 7.35 11.7 0.13 348.61 200.21 40860 +1906 276 12.88 6.88 11.23 0 339.03 265.02 40658 +1906 277 14.92 8.92 13.27 0 382.3 258.82 40456 +1906 278 12.32 6.32 10.67 0 327.91 260.36 40255 +1906 279 10.75 4.75 9.1 0 298.39 259.84 40054 +1906 280 11.88 5.88 10.23 0 319.39 255.53 39854 +1906 281 14.6 8.6 12.95 0 375.22 248.4 39654 +1906 282 11.76 5.76 10.11 0.88 317.1 187.65 39455 +1906 283 10.04 4.04 8.39 0.12 285.8 187.3 39256 +1906 284 13.28 7.28 11.63 0 347.17 242.04 39058 +1906 285 11.58 5.58 9.93 0.05 313.7 181.45 38861 +1906 286 10.99 4.99 9.34 0.15 302.75 179.97 38664 +1906 287 12.49 6.49 10.84 0 331.25 234.91 38468 +1906 288 15.37 9.37 13.72 0 392.46 227.56 38273 +1906 289 15.72 9.72 14.07 0 400.51 224.36 38079 +1906 290 15.7 9.7 14.05 0.03 400.05 166.19 37885 +1906 291 15.21 9.21 13.56 0 388.82 219.76 37693 +1906 292 15.63 9.63 13.98 0 398.43 216.41 37501 +1906 293 10.99 4.99 9.34 0.07 302.75 165.4 37311 +1906 294 12.34 6.34 10.69 0 328.3 215.87 37121 +1906 295 10.84 4.84 9.19 0.51 300.02 161.24 36933 +1906 296 10.71 4.71 9.06 0 297.67 212.55 36745 +1906 297 14.39 8.39 12.74 0.07 370.63 153.64 36560 +1906 298 9.5 3.5 7.85 0 276.54 208.59 36375 +1906 299 13.1 7.1 11.45 0.34 343.48 151.04 36191 +1906 300 15.02 9.02 13.37 0 384.54 195.99 36009 +1906 301 16.29 10.29 14.64 0.05 413.94 143.66 35829 +1906 302 14.55 8.55 12.9 0.46 374.12 143.75 35650 +1906 303 17.54 11.54 15.89 0.07 444.72 138.33 35472 +1906 304 14.42 8.42 12.77 0 371.28 186.91 35296 +1906 305 6.95 0.95 5.3 0.96 236.19 144.46 35122 +1906 306 8.63 2.63 6.98 0.37 262.15 141.59 34950 +1906 307 7.5 1.5 5.85 0 244.43 187.32 34779 +1906 308 6.42 0.42 4.77 0.32 228.47 139.22 34610 +1906 309 3.93 -2.07 2.28 0 195.04 185.19 34444 +1906 310 5.94 -0.06 4.29 0 221.67 181.22 34279 +1906 311 13.24 7.24 11.59 0.1 346.35 128.83 34116 +1906 312 13.53 7.53 11.88 0.11 352.34 126.61 33956 +1906 313 15.91 9.91 14.26 0.43 404.95 122.69 33797 +1906 314 11.62 5.62 9.97 0.77 314.45 125.29 33641 +1906 315 12.9 6.9 11.25 0.1 339.43 122.33 33488 +1906 316 13.68 7.68 12.03 0.07 355.47 120.04 33337 +1906 317 12.78 6.78 11.13 0.51 337.02 119.22 33188 +1906 318 15.8 9.8 14.15 0.14 402.38 114.7 33042 +1906 319 15.45 9.45 13.8 0 394.29 151.77 32899 +1906 320 15.08 9.08 13.43 0 385.89 150.45 32758 +1906 321 10.52 4.52 8.87 0 294.26 153.45 32620 +1906 322 9.11 3.11 7.46 0 270.01 152.93 32486 +1906 323 9.73 3.73 8.08 0 280.45 150.79 32354 +1906 324 12.7 6.7 11.05 0 335.42 145.85 32225 +1906 325 7.63 1.63 5.98 0.09 246.42 111.59 32100 +1906 326 8.56 2.56 6.91 0 261.02 146.61 31977 +1906 327 10.7 4.7 9.05 0.37 297.48 107.19 31858 +1906 328 12.18 6.18 10.53 0.05 325.18 104.67 31743 +1906 329 13.05 7.05 11.4 0 342.47 137.2 31631 +1906 330 9.27 3.27 7.62 0.09 272.67 104.5 31522 +1906 331 5.59 -0.41 3.94 0.37 216.82 105.55 31417 +1906 332 5.51 -0.49 3.86 0 215.72 139.14 31316 +1906 333 4.61 -1.39 2.96 0.28 203.72 103.96 31218 +1906 334 6.19 0.19 4.54 0.79 225.19 102.38 31125 +1906 335 -4.5 -10.5 -6.15 0 111.12 140.41 31035 +1906 336 -0.75 -6.75 -2.4 0.01 143.48 146.14 30949 +1906 337 -0.76 -6.76 -2.41 0 143.38 179.06 30867 +1906 338 1.86 -4.14 0.21 0 170.54 134.13 30790 +1906 339 3.2 -2.8 1.55 0.22 186.07 99.49 30716 +1906 340 0.9 -5.1 -0.75 0 160.12 133.05 30647 +1906 341 0.13 -5.87 -1.52 1.21 152.15 99.35 30582 +1906 342 1.6 -4.4 -0.05 0.3 167.66 98.27 30521 +1906 343 0.84 -5.16 -0.81 0 159.48 130.55 30465 +1906 344 2 -4 0.35 0.02 172.11 96.65 30413 +1906 345 0.08 -5.92 -1.57 0 151.65 129.31 30366 +1906 346 -0.17 -6.17 -1.82 0 149.15 128.85 30323 +1906 347 0.85 -5.15 -0.8 0 159.59 127.82 30284 +1906 348 3.09 -2.91 1.44 0 184.76 126.4 30251 +1906 349 1.01 -4.99 -0.64 0 161.28 127.01 30221 +1906 350 1.64 -4.36 -0.01 0 168.1 126.39 30197 +1906 351 1.29 -4.71 -0.36 0.37 164.28 94.74 30177 +1906 352 0.25 -5.75 -1.4 0.49 153.37 95.01 30162 +1906 353 2.64 -3.36 0.99 0.03 179.44 94.15 30151 +1906 354 1.49 -4.51 -0.16 0.49 166.46 94.53 30145 +1906 355 -0.06 -6.06 -1.71 1.63 150.24 144.01 30144 +1906 356 1.62 -4.38 -0.03 0 167.88 174.76 30147 +1906 357 5.77 -0.23 4.12 0 219.3 171.83 30156 +1906 358 6 0 4.35 0.04 222.51 140 30169 +1906 359 2.46 -3.54 0.81 0.46 177.35 141.2 30186 +1906 360 0.89 -5.11 -0.76 0 160.01 173.61 30208 +1906 361 2.68 -3.32 1.03 0 179.91 172.71 30235 +1906 362 3.65 -2.35 2 0 191.56 172.11 30267 +1906 363 1.94 -4.06 0.29 1.23 171.44 141.29 30303 +1906 364 -5.64 -11.64 -7.29 0.56 102.63 145.42 30343 +1906 365 -3.12 -9.12 -4.77 0.14 122.2 145.64 30388 +1907 1 -1.7 -7.7 -3.35 0.07 134.59 146.08 30438 +1907 2 3.26 -2.74 1.61 0.19 186.8 144.45 30492 +1907 3 -0.03 -6.03 -1.68 0.49 150.54 147.78 30551 +1907 4 1.66 -4.34 0.01 0.7 168.32 147.58 30614 +1907 5 2.08 -3.92 0.43 0.47 173.01 147.53 30681 +1907 6 0.05 -5.95 -1.6 0.74 151.35 148.79 30752 +1907 7 0.3 -5.7 -1.35 0.53 153.88 149.16 30828 +1907 8 2 -4 0.35 0.57 172.11 149.29 30907 +1907 9 2.15 -3.85 0.5 0 173.81 184.1 30991 +1907 10 3.13 -2.87 1.48 0.88 185.23 149.83 31079 +1907 11 -1.07 -7.07 -2.72 0.04 140.43 152.06 31171 +1907 12 -2.07 -8.07 -3.72 0.33 131.26 154 31266 +1907 13 -2.34 -8.34 -3.99 0 128.88 191.22 31366 +1907 14 0.78 -5.22 -0.87 0 158.85 191.13 31469 +1907 15 3.99 -2.01 2.34 0 195.79 190.19 31575 +1907 16 1.88 -4.12 0.23 0.25 170.77 155.61 31686 +1907 17 2.4 -3.6 0.75 0 176.66 193.2 31800 +1907 18 1.53 -4.47 -0.12 0 166.89 195.21 31917 +1907 19 0.8 -5.2 -0.85 0 159.06 197.25 32038 +1907 20 1.86 -4.14 0.21 0.15 170.54 159.46 32161 +1907 21 2.54 -3.46 0.89 0.47 178.28 160.2 32289 +1907 22 4.86 -1.14 3.21 0.42 206.99 159.67 32419 +1907 23 -1.62 -7.62 -3.27 0 135.32 203.71 32552 +1907 24 -4.31 -10.31 -5.96 0 112.59 206.69 32688 +1907 25 -6.19 -12.19 -7.84 0 98.74 209.07 32827 +1907 26 -3.36 -9.36 -5.01 0 120.21 209.85 32969 +1907 27 -2.09 -8.09 -3.74 0 131.09 211.19 33114 +1907 28 0.36 -5.64 -1.29 0 154.5 212.03 33261 +1907 29 4.78 -1.22 3.13 0 205.94 210.99 33411 +1907 30 5.91 -0.09 4.26 0 221.25 211.5 33564 +1907 31 2.52 -3.48 0.87 0 178.05 215.71 33718 +1907 32 8.96 2.96 7.31 0 267.53 173.28 33875 +1907 33 9.53 3.53 7.88 0 277.05 175.32 34035 +1907 34 10 4 8.35 0.18 285.11 132.76 34196 +1907 35 7.05 1.05 5.4 0.01 237.67 136.42 34360 +1907 36 2.51 -3.49 0.86 0 177.93 187.78 34526 +1907 37 3 -3 1.35 0 183.68 189.89 34694 +1907 38 1.31 -4.69 -0.34 0.26 164.5 145.29 34863 +1907 39 1.12 -4.88 -0.53 0.33 162.45 147.35 35035 +1907 40 0.26 -5.74 -1.39 0.3 153.47 149.71 35208 +1907 41 3.61 -2.39 1.96 0 191.06 200.09 35383 +1907 42 -0.6 -6.6 -2.25 0 144.92 205.33 35560 +1907 43 -0.73 -6.73 -2.38 0 143.67 208.14 35738 +1907 44 0.19 -5.81 -1.46 0.35 152.76 157.66 35918 +1907 45 -1.16 -7.16 -2.81 0 139.58 213.63 36099 +1907 46 0.62 -5.38 -1.03 0 157.18 215.32 36282 +1907 47 0.39 -5.61 -1.26 0 154.8 218.31 36466 +1907 48 -0.49 -6.49 -2.14 0.37 145.99 203.24 36652 +1907 49 -1.73 -7.73 -3.38 0 134.32 261.99 36838 +1907 50 -5.13 -11.13 -6.78 0 106.36 266.18 37026 +1907 51 1.16 -4.84 -0.49 0 162.88 265.45 37215 +1907 52 -0.39 -6.39 -2.04 0 146.97 269.13 37405 +1907 53 -2.19 -8.19 -3.84 0.1 130.2 213.98 37596 +1907 54 1.9 -4.1 0.25 0 170.99 273.06 37788 +1907 55 1.79 -4.21 0.14 0 169.76 275.79 37981 +1907 56 -4.19 -10.19 -5.84 0 113.53 281.94 38175 +1907 57 -0.76 -6.76 -2.41 0 143.38 282.81 38370 +1907 58 2.01 -3.99 0.36 0 172.22 283.48 38565 +1907 59 2.42 -3.58 0.77 0 176.89 285.47 38761 +1907 60 3.4 -2.6 1.75 0.4 188.49 190 38958 +1907 61 4.82 -1.18 3.17 0 206.47 255.02 39156 +1907 62 -1.05 -7.05 -2.7 0 140.62 262.41 39355 +1907 63 6.73 0.73 5.08 0.02 232.96 194.19 39553 +1907 64 7.89 1.89 6.24 0.01 250.43 195.39 39753 +1907 65 7.97 1.97 6.32 0 251.67 263.3 39953 +1907 66 5.02 -0.98 3.37 0 209.11 269.23 40154 +1907 67 5.43 -0.57 3.78 0 214.63 271.74 40355 +1907 68 6.75 0.75 5.1 0 233.25 273.21 40556 +1907 69 8.93 2.93 7.28 0 267.04 273.2 40758 +1907 70 8.04 2.04 6.39 0 252.77 277.16 40960 +1907 71 8.31 2.31 6.66 0 257.03 279.73 41163 +1907 72 1.24 -4.76 -0.41 0 163.74 289.78 41366 +1907 73 5.34 -0.66 3.69 0 213.41 288.68 41569 +1907 74 6.34 0.34 4.69 0 227.32 290.34 41772 +1907 75 6.11 0.11 4.46 0 224.06 293.34 41976 +1907 76 0.48 -5.52 -1.17 0 155.73 301.37 42179 +1907 77 -1.33 -7.33 -2.98 0 137.99 305.37 42383 +1907 78 -0.65 -6.65 -2.3 0 144.44 307.61 42587 +1907 79 0.85 -5.15 -0.8 0 159.59 309.23 42791 +1907 80 1.43 -4.57 -0.22 0.03 165.8 233.49 42996 +1907 81 2.28 -3.72 0.63 0 175.29 313.2 43200 +1907 82 9.7 3.7 8.05 0.05 279.94 230.32 43404 +1907 83 8.12 2.12 6.47 0.05 254.02 233.87 43608 +1907 84 10.19 4.19 8.54 0 288.42 311.36 43812 +1907 85 9.8 3.8 8.15 0 281.65 314.45 44016 +1907 86 9.19 3.19 7.54 0.06 271.34 238.33 44220 +1907 87 8.66 2.66 7.01 0.19 262.64 240.81 44424 +1907 88 6.49 0.49 4.84 0.54 229.48 244.77 44627 +1907 89 9.96 3.96 8.31 0.14 284.41 242.81 44831 +1907 90 9.18 3.18 7.53 0.47 271.17 245.49 45034 +1907 91 11.02 5.02 9.37 1.81 303.3 244.97 45237 +1907 92 9.63 3.63 7.98 1.25 278.74 248.35 45439 +1907 93 11.22 5.22 9.57 0 306.98 330.72 45642 +1907 94 7.07 1.07 5.42 0.31 237.97 254.45 45843 +1907 95 6.29 0.29 4.64 0.73 226.61 256.85 46045 +1907 96 4.1 -1.9 2.45 0.39 197.18 260.44 46246 +1907 97 3.84 -2.16 2.19 0.19 193.91 262.24 46446 +1907 98 2.53 -3.47 0.88 0 178.16 353.06 46647 +1907 99 6.1 0.1 4.45 0 223.91 350.99 46846 +1907 100 5.88 -0.12 4.23 0 220.83 353.25 47045 +1907 101 11.95 5.95 10.3 0 320.74 345.67 47243 +1907 102 10.43 4.43 8.78 0.5 292.66 262.74 47441 +1907 103 15.35 9.35 13.7 2.68 392 256.67 47638 +1907 104 17.58 11.58 15.93 0.89 445.74 253.83 47834 +1907 105 18.53 12.53 16.88 0.54 470.47 253.17 48030 +1907 106 14.9 8.9 13.25 0.08 381.86 261.34 48225 +1907 107 12.34 6.34 10.69 0 328.3 355.59 48419 +1907 108 10.25 4.25 8.6 0.81 289.48 270.92 48612 +1907 109 9.32 3.32 7.67 0.47 273.51 273.33 48804 +1907 110 11.04 5.04 9.39 0.57 303.66 272.15 48995 +1907 111 13.65 7.65 12 0.16 354.84 269.38 49185 +1907 112 11.33 5.33 9.68 0.78 309.02 274.06 49374 +1907 113 11.97 5.97 10.32 0.32 321.12 274.14 49561 +1907 114 11.67 5.67 10.02 0 315.4 367.61 49748 +1907 115 11.55 5.55 9.9 0 313.13 369.28 49933 +1907 116 10.73 4.73 9.08 0 298.03 372.07 50117 +1907 117 10.73 4.73 9.08 0.01 298.03 280.04 50300 +1907 118 4.37 -1.63 2.72 0.57 200.62 288.33 50481 +1907 119 9.96 3.96 8.31 0.21 284.41 283 50661 +1907 120 11.35 5.35 9.7 0 309.39 375.94 50840 +1907 121 24.2 18.2 22.55 0 643.7 339.75 51016 +1907 122 21.21 15.21 19.56 0 546.63 352.18 51191 +1907 123 22.41 16.41 20.76 0 583.98 348.84 51365 +1907 124 19.28 13.28 17.63 0 490.81 360.59 51536 +1907 125 15.78 9.78 14.13 0 401.91 371.48 51706 +1907 126 15.71 9.71 14.06 0 400.28 372.65 51874 +1907 127 16.87 10.87 15.22 0.34 427.99 277.85 52039 +1907 128 18.07 12.07 16.42 0 458.35 368.05 52203 +1907 129 18.03 12.03 16.38 0.41 457.31 276.75 52365 +1907 130 14.95 8.95 13.3 0.07 382.97 283.56 52524 +1907 131 14.3 8.3 12.65 0.03 368.68 285.34 52681 +1907 132 14.48 8.48 12.83 0 372.59 380.85 52836 +1907 133 20.02 14.02 18.37 0 511.61 365.85 52989 +1907 134 21.51 15.51 19.86 0 555.77 361.38 53138 +1907 135 20.14 14.14 18.49 0 515.05 366.82 53286 +1907 136 23.08 17.08 21.43 0 605.76 356.72 53430 +1907 137 20.29 14.29 18.64 0.19 519.38 275.72 53572 +1907 138 21.03 15.03 19.38 0.62 541.2 274.24 53711 +1907 139 22.42 16.42 20.77 0 584.3 361.21 53848 +1907 140 20.01 14.01 18.36 0.01 511.32 277.73 53981 +1907 141 19.62 13.62 17.97 1.71 500.28 279.02 54111 +1907 142 17.41 11.41 15.76 0 441.43 379.32 54238 +1907 143 15.32 9.32 13.67 0 391.32 385.53 54362 +1907 144 14.1 8.1 12.45 0 364.37 389.02 54483 +1907 145 18.12 12.12 16.47 0.76 459.66 284.03 54600 +1907 146 16.26 10.26 14.61 0.09 413.22 288.29 54714 +1907 147 17.67 11.67 16.02 0.02 448.04 285.67 54824 +1907 148 25.48 19.48 23.83 0.01 689.52 264.26 54931 +1907 149 24.26 18.26 22.61 0 645.79 358.04 55034 +1907 150 24.34 18.34 22.69 0.42 648.58 268.51 55134 +1907 151 22.36 16.36 20.71 0.91 582.38 274.84 55229 +1907 152 26.27 20.27 24.62 0 719.15 349.74 55321 +1907 153 21.57 15.57 19.92 0 557.61 369.77 55409 +1907 154 21.86 15.86 20.21 0 566.6 369 55492 +1907 155 20.89 14.89 19.24 0.15 537.02 279.55 55572 +1907 156 20.11 14.11 18.46 0.39 514.19 281.82 55648 +1907 157 20.95 14.95 19.3 0.08 538.81 279.75 55719 +1907 158 22 16 20.35 0.05 570.98 276.98 55786 +1907 159 23.39 17.39 21.74 0 616.06 364.07 55849 +1907 160 18.72 12.72 17.07 0.52 475.56 285.8 55908 +1907 161 21.96 15.96 20.31 0 569.72 369.95 55962 +1907 162 23.88 17.88 22.23 0 632.66 362.34 56011 +1907 163 20.43 14.43 18.78 0 523.45 375.76 56056 +1907 164 16.87 10.87 15.22 0 427.99 386.98 56097 +1907 165 15.04 9.04 13.39 0.19 384.99 293.99 56133 +1907 166 17.5 11.5 15.85 0 443.71 385.34 56165 +1907 167 19.17 13.17 17.52 0.11 487.78 285.11 56192 +1907 168 22.62 16.62 20.97 0 590.73 367.91 56214 +1907 169 24.49 18.49 22.84 0 653.85 360.18 56231 +1907 170 23.42 17.42 21.77 0.15 617.07 273.53 56244 +1907 171 18.57 12.57 16.92 0.01 471.54 286.65 56252 +1907 172 20.54 14.54 18.89 0 526.67 375.68 56256 +1907 173 23.19 17.19 21.54 0.32 609.4 274.26 56255 +1907 174 22.19 16.19 20.54 0.85 576.97 277.15 56249 +1907 175 21.91 15.91 20.26 0 568.16 370.58 56238 +1907 176 21.28 15.28 19.63 0 548.75 372.87 56223 +1907 177 21.44 15.44 19.79 0.52 553.62 279.14 56203 +1907 178 20.06 14.06 18.41 0 512.76 377.09 56179 +1907 179 23.47 17.47 21.82 0 618.75 364.21 56150 +1907 180 24.8 18.8 23.15 0 664.85 358.42 56116 +1907 181 28.11 22.11 26.46 0 792.36 342.31 56078 +1907 182 25.42 19.42 23.77 0 687.31 355.42 56035 +1907 183 25.05 19.05 23.4 0.38 673.83 267.7 55987 +1907 184 22.47 16.47 20.82 0.66 585.9 275.67 55935 +1907 185 22.94 16.94 21.29 0.08 601.15 274.22 55879 +1907 186 21 15 19.35 0 540.3 372.7 55818 +1907 187 23.2 17.2 21.55 0.16 609.73 273.11 55753 +1907 188 21.02 15.02 19.37 2.21 540.9 279.14 55684 +1907 189 19.97 13.97 18.32 1.63 510.18 281.73 55611 +1907 190 17.33 11.33 15.68 0 439.42 383.52 55533 +1907 191 18 12 16.35 0.06 456.53 285.96 55451 +1907 192 20.81 14.81 19.16 1.45 534.64 278.86 55366 +1907 193 19.23 13.23 17.58 0.67 489.43 282.65 55276 +1907 194 23.36 17.36 21.71 0.07 615.06 271.24 55182 +1907 195 19.06 13.06 17.41 0.01 484.77 282.68 55085 +1907 196 18.39 12.39 16.74 0.02 466.76 283.94 54984 +1907 197 24.02 18.02 22.37 0.09 637.47 268.36 54879 +1907 198 27.54 21.54 25.89 0 769.04 341.1 54770 +1907 199 24.32 18.32 22.67 0 647.88 355.8 54658 +1907 200 26.9 20.9 25.25 0.02 743.54 257.69 54542 +1907 201 25.72 19.72 24.07 0 698.41 348.75 54423 +1907 202 24.66 18.66 23.01 0 659.86 352.94 54301 +1907 203 21.62 15.62 19.97 0.42 559.15 273.43 54176 +1907 204 23.52 17.52 21.87 0.62 620.43 267.56 54047 +1907 205 17.69 11.69 16.04 0.16 448.55 282.32 53915 +1907 206 20.02 14.02 18.37 0.46 511.61 276.44 53780 +1907 207 16.22 10.22 14.57 0.56 412.27 284.46 53643 +1907 208 14.15 8.15 12.5 0.07 365.44 287.85 53502 +1907 209 12.41 6.41 10.76 0 329.68 387.02 53359 +1907 210 17.42 11.42 15.77 0 441.69 374 53213 +1907 211 20.59 14.59 18.94 0.05 528.14 272.47 53064 +1907 212 22.52 16.52 20.87 0.61 587.51 266.66 52913 +1907 213 26.53 20.53 24.88 0.17 729.13 253.32 52760 +1907 214 28.96 22.96 27.31 0 828.25 324.79 52604 +1907 215 25.99 19.99 24.34 0 708.52 338.92 52445 +1907 216 23.52 17.52 21.87 0.09 620.43 261.39 52285 +1907 217 26.24 20.24 24.59 0 718 335.95 52122 +1907 218 27.33 21.33 25.68 0 760.59 330 51958 +1907 219 26.4 20.4 24.75 0.12 724.13 250.08 51791 +1907 220 28.8 22.8 27.15 0 821.39 320.68 51622 +1907 221 30.29 24.29 28.64 0.05 887.15 233.69 51451 +1907 222 26.13 20.13 24.48 0 713.82 331.85 51279 +1907 223 24.51 18.51 22.86 0 654.55 337.81 51105 +1907 224 23.14 17.14 21.49 0 607.74 342.26 50929 +1907 225 23.7 17.7 22.05 0.08 626.52 254.22 50751 +1907 226 20.89 14.89 19.24 0.05 537.02 261.09 50572 +1907 227 20.83 14.83 19.18 0.04 535.23 260.29 50392 +1907 228 19.11 13.11 17.46 0.06 486.14 263.5 50210 +1907 229 19.09 13.09 17.44 0.47 485.59 262.61 50026 +1907 230 22.03 16.03 20.38 0.01 571.92 254.42 49842 +1907 231 17.23 11.23 15.58 0.09 436.91 264.52 49656 +1907 232 16.61 10.61 14.96 1.21 421.64 264.72 49469 +1907 233 22.52 16.52 20.87 1.24 587.51 249.99 49280 +1907 234 22.78 16.78 21.13 0.56 595.92 248.24 49091 +1907 235 23.5 17.5 21.85 0.01 619.76 245.14 48900 +1907 236 23.9 17.9 22.25 0 633.35 323.94 48709 +1907 237 22.46 16.46 20.81 0.05 585.58 245.77 48516 +1907 238 22.15 16.15 20.5 0.4 575.7 245.36 48323 +1907 239 18.23 12.23 16.58 0.08 462.54 253.42 48128 +1907 240 18.26 12.26 16.61 0.62 463.33 252.04 47933 +1907 241 17.67 11.67 16.02 0.27 448.04 251.94 47737 +1907 242 15.28 9.28 13.63 0.59 390.41 255.08 47541 +1907 243 12.85 6.85 11.2 0.38 338.42 257.56 47343 +1907 244 7.06 1.06 5.41 0.1 237.82 263.39 47145 +1907 245 9.04 3.04 7.39 0 268.85 346.34 46947 +1907 246 10.42 4.42 8.77 0 292.48 342.05 46747 +1907 247 17.26 11.26 15.61 0 437.66 325.84 46547 +1907 248 20.55 14.55 18.9 0 526.96 314.72 46347 +1907 249 22.62 16.62 20.97 0 590.73 306.01 46146 +1907 250 23.01 17.01 21.36 0 603.45 302.78 45945 +1907 251 20.42 14.42 18.77 0 523.16 309.09 45743 +1907 252 19.09 13.09 17.44 0 485.59 310.78 45541 +1907 253 15.37 9.37 13.72 0 392.46 317.87 45339 +1907 254 20.58 14.58 18.93 0 527.84 302.33 45136 +1907 255 25.48 19.48 23.83 0 689.52 283.46 44933 +1907 256 25.96 19.96 24.31 0.57 707.39 209.59 44730 +1907 257 20.64 14.64 18.99 0.87 529.61 221.71 44527 +1907 258 20.33 14.33 18.68 0.21 520.54 220.67 44323 +1907 259 18.52 12.52 16.87 0.08 470.21 222.56 44119 +1907 260 16.37 10.37 14.72 2.3 415.85 224.67 43915 +1907 261 19.57 13.57 17.92 0.15 498.88 216.92 43711 +1907 262 18.03 12.03 16.38 0 457.31 290.85 43507 +1907 263 16.75 10.75 15.1 0 425.05 291.42 43303 +1907 264 17.73 11.73 16.08 0.1 449.57 214.95 43099 +1907 265 15.21 9.21 13.56 0 388.82 289.79 42894 +1907 266 12.93 6.93 11.28 0 340.04 291.62 42690 +1907 267 17.22 11.22 15.57 0 436.66 280.32 42486 +1907 268 22.81 16.81 21.16 0 596.9 262.96 42282 +1907 269 22.36 16.36 20.71 0 582.38 261.94 42078 +1907 270 23.05 17.05 21.4 0 604.77 257.33 41875 +1907 271 21.97 15.97 20.32 0.01 570.04 193.55 41671 +1907 272 25.35 19.35 23.7 0.07 684.74 183.59 41468 +1907 273 25.91 19.91 24.26 0.02 705.51 180.38 41265 +1907 274 25.73 19.73 24.08 0.19 698.78 179.01 41062 +1907 275 20.72 14.72 19.07 0.05 531.97 188.44 40860 +1907 276 18.94 12.94 17.29 0.54 481.5 189.79 40658 +1907 277 18.46 12.46 16.81 0 468.61 251.57 40456 +1907 278 16.41 10.41 14.76 0.22 416.81 189.84 40255 +1907 279 12.91 6.91 11.26 0 339.63 256.6 40054 +1907 280 15.27 9.27 13.62 0 390.18 249.9 39854 +1907 281 11.51 5.51 9.86 0.32 312.38 190 39654 +1907 282 13.39 7.39 11.74 0 349.43 247.7 39455 +1907 283 12.66 6.66 11.01 0 334.62 246.02 39256 +1907 284 15.53 9.53 13.88 0.02 396.12 178.68 39058 +1907 285 16.58 10.58 14.93 0.78 420.91 175.28 38861 +1907 286 11.68 5.68 10.03 0.04 315.59 179.26 38664 +1907 287 15.13 9.13 13.48 0.05 387.01 173.04 38468 +1907 288 17.65 11.65 16 0 447.52 223.35 38273 +1907 289 20.08 14.08 18.43 0 513.33 215.69 38079 +1907 290 22.67 16.67 21.02 0 592.35 206.73 37885 +1907 291 20.85 14.85 19.2 0 535.82 208.63 37693 +1907 292 19.09 13.09 17.44 0.02 485.59 157.44 37501 +1907 293 18.01 12.01 16.36 0 456.79 209.45 37311 +1907 294 19.95 13.95 18.3 0.11 509.61 152.05 37121 +1907 295 16.67 10.67 15.02 1.28 423.1 154.76 36933 +1907 296 17.45 11.45 15.8 0.04 442.44 151.84 36745 +1907 297 15.7 9.7 14.05 0 400.05 202.81 36560 +1907 298 17.5 11.5 15.85 0 443.71 197.21 36375 +1907 299 16.41 10.41 14.76 1.14 416.81 147.29 36191 +1907 300 18.74 12.74 17.09 0 476.09 189.68 36009 +1907 301 18.46 12.46 16.81 0 468.61 187.79 35829 +1907 302 22.04 16.04 20.39 0 572.24 178.04 35650 +1907 303 19.58 13.58 17.93 0 499.16 180.73 35472 +1907 304 19.13 13.13 17.48 0 486.69 179.24 35296 +1907 305 4.98 -1.02 3.33 0.02 208.58 145.68 35122 +1907 306 4.12 -1.88 2.47 0.35 197.43 144.45 34950 +1907 307 2.99 -3.01 1.34 0.25 183.56 143.13 34779 +1907 308 2.41 -3.59 0.76 0.31 176.78 141.42 34610 +1907 309 -0.45 -6.45 -2.1 0 146.39 187.85 34444 +1907 310 3.08 -2.92 1.43 0 184.64 183.28 34279 +1907 311 1.97 -4.03 0.32 0 171.77 181.76 34116 +1907 312 6.57 0.57 4.92 0.34 230.63 131.9 33956 +1907 313 10.3 4.3 8.65 0.05 290.36 127.77 33797 +1907 314 4.19 -1.81 2.54 0.13 198.32 130.14 33641 +1907 315 2.12 -3.88 0.47 0.15 173.47 129.2 33488 +1907 316 0.77 -5.23 -0.88 0 158.75 170.8 33337 +1907 317 5.57 -0.43 3.92 0 216.54 165.58 33188 +1907 318 10.59 4.59 8.94 0 295.51 158.98 33042 +1907 319 14.71 8.71 13.06 0 377.64 152.72 32899 +1907 320 14 8 12.35 0.12 362.24 113.84 32758 +1907 321 14.27 8.27 12.62 0 368.03 149.41 32620 +1907 322 11.38 5.38 9.73 0 309.95 150.81 32486 +1907 323 12.36 6.36 10.71 0 328.69 148.22 32354 +1907 324 10.03 4.03 8.38 0 285.63 148.49 32225 +1907 325 11.35 5.35 9.7 0 309.39 145.55 32100 +1907 326 6.09 0.09 4.44 0.05 223.77 111.35 31977 +1907 327 10.01 4.01 8.36 0 285.28 143.55 31858 +1907 328 7.93 1.93 6.28 0 251.05 143.31 31743 +1907 329 5.64 -0.36 3.99 1.08 217.5 107.6 31631 +1907 330 -0.41 -6.41 -2.06 0.27 146.78 151.67 31522 +1907 331 4.37 -1.63 2.72 0 200.62 183.77 31417 +1907 332 6.54 0.54 4.89 0 230.2 138.46 31316 +1907 333 6.84 0.84 5.19 0.22 234.57 102.87 31218 +1907 334 8.41 2.41 6.76 0 258.62 134.93 31125 +1907 335 6.67 0.67 5.02 0 232.08 135.02 31035 +1907 336 7.34 1.34 5.69 0.36 242.01 100.12 30949 +1907 337 3.56 -2.44 1.91 0.15 190.45 100.65 30867 +1907 338 4.98 -1.02 3.33 0.01 208.58 99.33 30790 +1907 339 2.03 -3.97 0.38 0.5 172.45 99.94 30716 +1907 340 0.57 -5.43 -1.08 0.11 156.66 99.9 30647 +1907 341 -0.46 -6.46 -2.11 0.29 146.29 143.61 30582 +1907 342 0.69 -5.31 -0.96 0 157.91 175.52 30521 +1907 343 1.56 -4.44 -0.09 0.09 167.22 141.61 30465 +1907 344 -1.01 -7.01 -2.66 0.38 141 142.86 30413 +1907 345 0.73 -5.27 -0.92 0.18 158.33 141.96 30366 +1907 346 3.91 -2.09 2.26 0.02 194.79 139.92 30323 +1907 347 5.07 -0.93 3.42 0 209.78 169.78 30284 +1907 348 4.73 -1.27 3.08 0 205.29 125.51 30251 +1907 349 5.97 -0.03 4.32 0 222.09 124.39 30221 +1907 350 8.78 2.78 7.13 0 264.59 122.16 30197 +1907 351 10.56 4.56 8.91 0.44 294.97 90.42 30177 +1907 352 7.55 1.55 5.9 0.25 245.19 92.04 30162 +1907 353 2.97 -3.03 1.32 0.04 183.33 94.02 30151 +1907 354 2.63 -3.37 0.98 0.2 179.33 94.12 30145 +1907 355 4.03 -1.97 2.38 0.1 196.29 93.58 30144 +1907 356 4.73 -1.27 3.08 0 205.29 124.41 30147 +1907 357 5.87 -0.13 4.22 1.84 220.69 92.85 30156 +1907 358 2.41 -3.59 0.76 0 176.78 125.78 30169 +1907 359 6.44 0.44 4.79 0 228.76 123.64 30186 +1907 360 9.28 3.28 7.63 0 272.84 122.02 30208 +1907 361 11.84 5.84 10.19 0 318.63 120.23 30235 +1907 362 10.42 4.42 8.77 0.38 292.48 91.41 30267 +1907 363 6.91 0.91 5.26 0.07 235.6 93.79 30303 +1907 364 4.43 -1.57 2.78 0.24 201.39 95.22 30343 +1907 365 4.4 -1.6 2.75 0.18 201 95.66 30388 +1908 1 -1.17 -7.17 -2.82 0 139.49 131.07 30438 +1908 2 -1.21 -7.21 -2.86 0 139.11 131.82 30492 +1908 3 -0.81 -6.81 -2.46 0 142.9 132.62 30551 +1908 4 -2.05 -8.05 -3.7 0 131.44 134.02 30614 +1908 5 0.3 -5.7 -1.35 0 153.88 133.73 30681 +1908 6 -1.28 -7.28 -2.93 0 138.46 135.28 30752 +1908 7 0.77 -5.23 -0.88 0 158.75 135.21 30828 +1908 8 3.15 -2.85 1.5 0 185.47 135.53 30907 +1908 9 2.66 -3.34 1.01 0.08 179.67 102.78 30991 +1908 10 0.26 -5.74 -1.39 0 153.47 139.52 31079 +1908 11 -0.83 -6.83 -2.48 0 142.71 140.99 31171 +1908 12 0.99 -5.01 -0.66 0 161.07 141.2 31266 +1908 13 2.53 -3.47 0.88 0 178.16 142.05 31366 +1908 14 0.23 -5.77 -1.42 0 153.17 144.67 31469 +1908 15 -0.05 -6.05 -1.7 0 150.34 146.26 31575 +1908 16 2.29 -3.71 0.64 0 175.4 146.4 31686 +1908 17 1.8 -4.2 0.15 0 169.87 148.35 31800 +1908 18 2.82 -3.18 1.17 0 181.55 149.7 31917 +1908 19 2.02 -3.98 0.37 0 172.34 152.07 32038 +1908 20 -0.54 -6.54 -2.19 0 145.51 154.94 32161 +1908 21 -2.15 -8.15 -3.8 0 130.55 157.66 32289 +1908 22 -4.35 -10.35 -6 0.12 112.28 161.28 32419 +1908 23 -1.93 -7.93 -3.58 0 132.51 202.05 32552 +1908 24 -1.76 -7.76 -3.41 0 134.05 203.9 32688 +1908 25 -1.5 -7.5 -3.15 0 136.42 205.52 32827 +1908 26 0.74 -5.26 -0.91 0 158.43 206.12 32969 +1908 27 2.59 -3.41 0.94 0.1 178.86 125.12 33114 +1908 28 -1.01 -7.01 -2.66 0 141 170.97 33261 +1908 29 -0.98 -6.98 -2.63 0.01 141.28 169.55 33411 +1908 30 -2.79 -8.79 -4.44 0.11 124.99 172 33564 +1908 31 -3.55 -9.55 -5.2 0 118.65 218.65 33718 +1908 32 2.78 -3.22 1.13 0 181.08 217.05 33875 +1908 33 2.94 -3.06 1.29 0 182.97 180.6 34035 +1908 34 2.82 -3.18 1.17 0.02 181.55 137.17 34196 +1908 35 4.35 -1.65 2.7 0 200.36 184.01 34360 +1908 36 1.31 -4.69 -0.34 0 164.5 188.52 34526 +1908 37 2.36 -3.64 0.71 0.04 176.2 142.73 34694 +1908 38 0.04 -5.96 -1.61 0 151.25 194.45 34863 +1908 39 3.85 -2.15 2.2 0 194.04 194.66 35035 +1908 40 4.49 -1.51 2.84 0.72 202.16 147.61 35208 +1908 41 2.73 -3.27 1.08 0 180.49 200.7 35383 +1908 42 1.78 -4.22 0.13 0.01 169.65 152.93 35560 +1908 43 -1.34 -7.34 -2.99 0 137.9 208.47 35738 +1908 44 1.3 -4.7 -0.35 0 164.39 209.53 35918 +1908 45 1.88 -4.12 0.23 0 170.77 211.79 36099 +1908 46 2.21 -3.79 0.56 0.64 174.49 160.71 36282 +1908 47 6.33 0.33 4.68 0 227.18 213.82 36466 +1908 48 6.98 0.98 5.33 0 236.63 216.01 36652 +1908 49 7.39 1.39 5.74 0 242.76 218.37 36838 +1908 50 5.95 -0.05 4.3 0 221.81 222.4 37026 +1908 51 11.52 5.52 9.87 0 312.57 219.2 37215 +1908 52 7.35 1.35 5.7 0.98 242.16 170.12 37405 +1908 53 6.47 0.47 4.82 0.44 229.19 172.98 37596 +1908 54 6.08 0.08 4.43 0.02 223.63 175.33 37788 +1908 55 4.14 -1.86 2.49 0 197.68 238.52 37981 +1908 56 3.32 -2.68 1.67 0 187.52 241.91 38175 +1908 57 6.14 0.14 4.49 0 224.48 242.27 38370 +1908 58 7.06 1.06 5.41 0 237.82 244.26 38565 +1908 59 7.38 1.38 5.73 0 242.61 246.62 38761 +1908 60 7.64 1.64 5.99 0.27 246.57 186.9 38958 +1908 61 4.99 -1.01 3.34 0.69 208.72 191.14 39156 +1908 62 4.05 -1.95 2.4 0.18 196.55 193.9 39355 +1908 63 5.08 -0.92 3.43 0 209.91 260.6 39553 +1908 64 3.42 -2.58 1.77 0.49 188.74 198.79 39753 +1908 65 3.49 -2.51 1.84 0 189.59 267.91 39953 +1908 66 2.91 -3.09 1.26 0 182.61 271.18 40154 +1908 67 6.32 0.32 4.67 0 227.04 270.8 40355 +1908 68 1.74 -4.26 0.09 0 169.21 278 40556 +1908 69 6.52 0.52 4.87 0 229.91 276.09 40758 +1908 70 9.14 3.14 7.49 0 270.51 275.75 40960 +1908 71 7.43 1.43 5.78 0 243.37 280.81 41163 +1908 72 8.47 2.47 6.82 0 259.58 282.34 41366 +1908 73 7.12 1.12 5.47 0 238.71 286.68 41569 +1908 74 5.06 -0.94 3.41 0 209.65 291.74 41772 +1908 75 7.04 1.04 5.39 0.23 237.52 219.19 41976 +1908 76 9.65 3.65 8 0.05 279.08 218.6 42179 +1908 77 7.36 1.36 5.71 0.74 242.31 222.84 42383 +1908 78 5.72 -0.28 4.07 1.08 218.61 226.31 42587 +1908 79 4.69 -1.31 3.04 1.77 204.76 229.22 42791 +1908 80 8.29 2.29 6.64 0.04 256.71 227.9 42996 +1908 81 10.35 4.35 8.7 0.38 291.24 227.6 43200 +1908 82 10.54 4.54 8.89 0.06 294.62 229.36 43404 +1908 83 12.37 6.37 10.72 0 328.89 305.23 43608 +1908 84 7.8 1.8 6.15 0 249.03 314.81 43812 +1908 85 5.24 -0.76 3.59 0.3 212.06 240.37 44016 +1908 86 4.84 -1.16 3.19 0 206.73 323.38 44220 +1908 87 6.83 0.83 5.18 0.52 234.42 242.67 44424 +1908 88 9.09 3.09 7.44 0 269.68 322.8 44627 +1908 89 9.48 3.48 7.83 0 276.2 324.5 44831 +1908 90 7.24 1.24 5.59 0 240.5 330.08 45034 +1908 91 11.54 5.54 9.89 0 312.94 325.73 45237 +1908 92 13.8 7.8 12.15 0.49 357.99 242.76 45439 +1908 93 12.03 6.03 10.38 0 322.28 329.28 45642 +1908 94 7.35 1.35 5.7 1.65 242.16 254.16 45843 +1908 95 10.12 4.12 8.47 0.57 287.2 252.66 46045 +1908 96 6.61 0.61 4.96 0 231.21 344.19 46246 +1908 97 13.04 7.04 11.39 0 342.26 335.75 46446 +1908 98 10.42 4.42 8.77 0 292.48 342.52 46647 +1908 99 7.14 1.14 5.49 0 239.01 349.59 46846 +1908 100 10.68 4.68 9.03 0 297.12 346.04 47045 +1908 101 11.19 5.19 9.54 0.54 306.42 260.31 47243 +1908 102 12.27 6.27 10.62 0.43 326.93 260.22 47441 +1908 103 12.14 6.14 10.49 1.87 324.4 261.79 47638 +1908 104 12.33 6.33 10.68 0.31 328.11 262.88 47834 +1908 105 8.48 2.48 6.83 0.16 259.74 269.27 48030 +1908 106 10.38 4.38 8.73 0.19 291.77 268.17 48225 +1908 107 9.98 3.98 8.33 0.01 284.76 269.96 48419 +1908 108 13.43 7.43 11.78 0 350.26 355.1 48612 +1908 109 14.26 8.26 12.61 0 367.81 354.89 48804 +1908 110 11.4 5.4 9.75 0 310.32 362.19 48995 +1908 111 12.36 6.36 10.71 0 328.69 361.87 49185 +1908 112 13.26 7.26 11.61 0.03 346.76 271.15 49374 +1908 113 14.2 8.2 12.55 0.46 366.52 270.61 49561 +1908 114 13.06 7.06 11.41 0.88 342.67 273.59 49748 +1908 115 8.61 2.61 6.96 1.62 261.83 280.86 49933 +1908 116 9.36 3.36 7.71 0.25 274.18 280.87 50117 +1908 117 12.48 6.48 10.83 0.09 331.05 277.48 50300 +1908 118 15.38 9.38 13.73 0 392.69 364.75 50481 +1908 119 11.92 5.92 10.27 0 320.16 373.63 50661 +1908 120 13.6 7.6 11.95 0 353.8 371.27 50840 +1908 121 22.67 16.67 21.02 0 592.35 345.76 51016 +1908 122 19.96 13.96 18.31 0.09 509.9 267.28 51191 +1908 123 20.48 14.48 18.83 0.87 524.91 266.75 51365 +1908 124 18.3 12.3 16.65 0.01 464.38 272.68 51536 +1908 125 20.78 14.78 19.13 0 533.75 356.64 51706 +1908 126 24.68 18.68 23.03 0 660.57 342.69 51874 +1908 127 19.59 13.59 17.94 0 499.44 362.41 52039 +1908 128 15.02 9.02 13.37 0 384.54 376.26 52203 +1908 129 17.29 11.29 15.64 0 438.42 371.13 52365 +1908 130 15.66 9.66 14.01 0.08 399.12 282.23 52524 +1908 131 17.23 11.23 15.58 0.06 436.91 279.66 52681 +1908 132 14.82 8.82 13.17 0 380.08 380.03 52836 +1908 133 18.81 12.81 17.16 0 477.98 369.72 52989 +1908 134 19.98 13.98 18.33 0 510.47 366.67 53138 +1908 135 18.16 12.16 16.51 0 460.7 373.09 53286 +1908 136 18.27 12.27 16.62 0 463.59 373.39 53430 +1908 137 20.31 14.31 18.66 0 519.96 367.56 53572 +1908 138 23.44 17.44 21.79 0 617.74 356.53 53711 +1908 139 22.36 16.36 20.71 0 582.38 361.44 53848 +1908 140 25.03 19.03 23.38 0.01 673.11 263.19 53981 +1908 141 21.43 15.43 19.78 0 553.32 365.79 54111 +1908 142 18.29 12.29 16.64 0 464.12 376.71 54238 +1908 143 19.36 13.36 17.71 0 493.03 373.89 54362 +1908 144 16.99 10.99 15.34 0 430.95 381.53 54483 +1908 145 18.69 12.69 17.04 0 474.75 376.96 54600 +1908 146 20.01 14.01 18.36 0 511.32 373.05 54714 +1908 147 22.78 16.78 21.13 0 595.92 363.44 54824 +1908 148 23.83 17.83 22.18 0 630.95 359.55 54931 +1908 149 27.11 21.11 25.46 0 751.83 344.86 55034 +1908 150 21.81 15.81 20.16 0.75 565.04 276.11 55134 +1908 151 18.87 12.87 17.22 0.72 479.6 283.99 55229 +1908 152 21.23 15.23 19.58 0.1 547.23 278.08 55321 +1908 153 18.09 12.09 16.44 0.13 458.88 286.06 55409 +1908 154 23.23 17.23 21.58 0 610.73 363.66 55492 +1908 155 23.89 17.89 22.24 0 633 361.12 55572 +1908 156 23.26 17.26 21.61 0 611.72 364.04 55648 +1908 157 21.49 15.49 19.84 1.2 555.15 278.28 55719 +1908 158 24.17 18.17 22.52 0.23 642.66 270.43 55786 +1908 159 25.24 19.24 23.59 0.91 680.72 267.08 55849 +1908 160 27.03 21.03 25.38 0 748.66 347.76 55908 +1908 161 23.81 17.81 22.16 0 630.27 362.58 55962 +1908 162 23.07 17.07 21.42 0 605.43 365.67 56011 +1908 163 22.5 16.5 20.85 0 586.86 368.14 56056 +1908 164 23.46 17.46 21.81 0.17 618.41 273.25 56097 +1908 165 21.35 15.35 19.7 0 550.88 372.62 56133 +1908 166 18.39 12.39 16.74 0 466.76 382.66 56165 +1908 167 20.87 14.87 19.22 0.15 536.42 280.78 56192 +1908 168 21.65 15.65 20 0 560.08 371.62 56214 +1908 169 22.66 16.66 21.01 0.17 592.02 275.82 56231 +1908 170 25.28 19.28 23.63 0 682.18 356.67 56244 +1908 171 22.74 16.74 21.09 0 594.62 367.51 56252 +1908 172 24.24 18.24 22.59 0 645.09 361.31 56256 +1908 173 24.01 18.01 22.36 0 637.13 362.28 56255 +1908 174 22.61 16.61 20.96 0 590.41 367.91 56249 +1908 175 25.46 19.46 23.81 0 688.78 355.77 56238 +1908 176 24.07 18.07 22.42 0 639.2 361.88 56223 +1908 177 25.52 19.52 23.87 0.01 690.99 266.52 56203 +1908 178 22.41 16.41 20.76 0 583.98 368.55 56179 +1908 179 22.9 16.9 21.25 0 599.84 366.52 56150 +1908 180 20.54 14.54 18.89 0 526.67 375.21 56116 +1908 181 20.71 14.71 19.06 0 531.67 374.55 56078 +1908 182 19.78 13.78 18.13 0 504.78 377.59 56035 +1908 183 22.26 16.26 20.61 0.04 579.19 276.39 55987 +1908 184 18.26 12.26 16.61 1.49 463.33 286.59 55935 +1908 185 17.9 11.9 16.25 0.91 453.94 287.34 55879 +1908 186 17.26 11.26 15.61 0.05 437.66 288.56 55818 +1908 187 19.76 13.76 18.11 0.04 504.22 282.6 55753 +1908 188 19.71 13.71 18.06 0.35 502.81 282.52 55684 +1908 189 18.49 12.49 16.84 0 469.41 380.43 55611 +1908 190 17.17 11.17 15.52 0.07 435.41 287.99 55533 +1908 191 19.12 13.12 17.47 0 486.41 377.8 55451 +1908 192 25.66 19.66 24.01 0 696.18 352.17 55366 +1908 193 28.13 22.13 26.48 0 793.19 339.72 55276 +1908 194 27.1 21.1 25.45 0.48 751.43 258.59 55182 +1908 195 27.28 21.28 25.63 0.2 758.59 257.73 55085 +1908 196 24.71 18.71 23.06 0 661.64 355.31 54984 +1908 197 21.71 15.71 20.06 0 561.93 366.94 54879 +1908 198 20.16 14.16 18.51 0 515.63 372 54770 +1908 199 22.03 16.03 20.38 0.03 571.92 273.73 54658 +1908 200 20.19 14.19 18.54 0.19 516.49 278.36 54542 +1908 201 23.33 17.33 21.68 0.06 614.06 269.29 54423 +1908 202 26.77 20.77 25.12 0 738.45 343.25 54301 +1908 203 23.98 17.98 22.33 0 636.09 355.35 54176 +1908 204 25.52 19.52 23.87 0.21 690.99 261.12 54047 +1908 205 23.8 17.8 22.15 0.01 629.93 266.32 53915 +1908 206 25.66 19.66 24.01 0 696.18 346.48 53780 +1908 207 23.68 17.68 22.03 0.91 625.84 265.8 53643 +1908 208 25.38 19.38 23.73 0 685.84 346.49 53502 +1908 209 24.49 18.49 22.84 0.63 653.85 262.31 53359 +1908 210 23.76 17.76 22.11 0 628.56 352.19 53213 +1908 211 25.87 19.87 24.22 0 704.01 342.31 53064 +1908 212 25.73 19.73 24.08 0 698.78 342.19 52913 +1908 213 26.5 20.5 24.85 0.03 727.97 253.42 52760 +1908 214 25.48 19.48 23.83 0.22 689.52 256.4 52604 +1908 215 24.26 18.26 22.61 0.2 645.79 259.86 52445 +1908 216 23.81 17.81 22.16 0.77 630.27 260.51 52285 +1908 217 21.01 15.01 19.36 1.51 540.6 267.74 52122 +1908 218 21.65 15.65 20 0.21 560.08 265.44 51958 +1908 219 18.8 12.8 17.15 0.29 477.71 271.73 51791 +1908 220 18.82 12.82 17.17 1.83 478.25 270.97 51622 +1908 221 20.79 14.79 19.14 0 534.04 353.96 51451 +1908 222 21.43 15.43 19.78 0.22 553.32 263.04 51279 +1908 223 19.72 13.72 18.07 0.08 503.09 266.47 51105 +1908 224 15.71 9.71 14.06 0.1 400.28 274.19 50929 +1908 225 19.49 13.49 17.84 0.04 496.64 265.36 50751 +1908 226 18.37 12.37 16.72 0.14 466.23 267.03 50572 +1908 227 20.28 14.28 18.63 0 519.09 348.87 50392 +1908 228 20.07 14.07 18.42 1.05 513.04 261.25 50210 +1908 229 17.74 11.74 16.09 0.85 449.83 265.55 50026 +1908 230 15.41 9.41 13.76 1.61 393.37 269.13 49842 +1908 231 16.64 10.64 14.99 0.64 422.37 265.69 49656 +1908 232 22.3 16.3 20.65 0 580.46 335.5 49469 +1908 233 19.6 13.6 17.95 0 499.72 343.07 49280 +1908 234 23.31 17.31 21.66 0.84 613.39 246.76 49091 +1908 235 18.86 12.86 17.21 0.07 479.33 256.78 48900 +1908 236 22.71 16.71 21.06 0.01 593.64 246.3 48709 +1908 237 22.84 16.84 21.19 0.04 597.88 244.74 48516 +1908 238 20.79 14.79 19.14 0.01 534.04 248.79 48323 +1908 239 21.79 15.79 20.14 0.89 564.42 245.19 48128 +1908 240 21.17 15.17 19.52 0 545.42 327.26 47933 +1908 241 18.93 12.93 17.28 0 481.23 332.43 47737 +1908 242 20.05 14.05 18.4 0 512.47 327.38 47541 +1908 243 18.83 12.83 17.18 0.92 478.52 246.84 47343 +1908 244 13.91 7.91 12.26 1.2 360.32 254.52 47145 +1908 245 10.23 4.23 8.58 0.12 289.12 258.31 46947 +1908 246 13.18 7.18 11.53 0 345.12 336.96 46747 +1908 247 12.77 6.77 11.12 0 336.82 335.86 46547 +1908 248 12.5 6.5 10.85 0 331.45 334.38 46347 +1908 249 13.32 7.32 11.67 0 347.99 330.67 46146 +1908 250 13.86 7.86 12.21 0 359.26 327.58 45945 +1908 251 16.18 10.18 14.53 0 411.32 320.35 45743 +1908 252 14.17 8.17 12.52 0.05 365.87 241.94 45541 +1908 253 12.52 6.52 10.87 0.59 331.84 242.74 45339 +1908 254 14.02 8.02 12.37 0 362.66 318.56 45136 +1908 255 24.34 18.34 22.69 0 648.58 287.75 44933 +1908 256 19.91 13.91 18.26 0 508.47 299.84 44730 +1908 257 21.38 15.38 19.73 0 551.79 293.4 44527 +1908 258 23.8 17.8 22.15 0 629.93 283.25 44323 +1908 259 22.68 16.68 21.03 0 592.67 284.69 44119 +1908 260 23.11 17.11 21.46 0.74 606.75 210.75 43915 +1908 261 16.89 10.89 15.24 0.11 428.48 221.94 43711 +1908 262 17.51 11.51 15.86 0 443.96 292.11 43507 +1908 263 17.67 11.67 16.02 0 448.04 289.28 43303 +1908 264 15.05 9.05 13.4 0.35 385.21 219.37 43099 +1908 265 16.02 10.02 14.37 0 407.53 288.1 42894 +1908 266 19.19 13.19 17.54 0.18 488.33 208.67 42690 +1908 267 17.62 11.62 15.97 0 446.76 279.41 42486 +1908 268 14.37 8.37 12.72 0 370.19 283.69 42282 +1908 269 17.26 11.26 15.61 0.06 437.66 206.41 42078 +1908 270 21.3 15.3 19.65 0.82 549.35 196.86 41875 +1908 271 20.97 14.97 19.32 0 539.4 260.88 41671 +1908 272 20.62 14.62 18.97 0 529.02 259.19 41468 +1908 273 20.31 14.31 18.66 0 519.96 257.56 41265 +1908 274 14.9 8.9 13.25 0.02 381.86 200.21 41062 +1908 275 14.18 8.18 12.53 0 366.09 265.51 40860 +1908 276 15.09 9.09 13.44 0 386.11 261.15 40658 +1908 277 15.65 9.65 14 0 398.89 257.44 40456 +1908 278 13.38 7.38 11.73 0 349.23 258.65 40255 +1908 279 13.94 7.94 12.29 0 360.96 254.89 40054 +1908 280 12.28 6.28 10.63 0 327.13 254.92 39854 +1908 281 13.86 7.86 12.21 0 359.26 249.67 39654 +1908 282 14.82 8.82 13.17 0 380.08 245.29 39455 +1908 283 14.17 8.17 12.52 0 365.87 243.6 39256 +1908 284 10.2 4.2 8.55 0 288.6 246.47 39058 +1908 285 6.09 0.09 4.44 0 223.77 248.48 38861 +1908 286 3.24 -2.76 1.59 0 186.56 248.23 38664 +1908 287 5.34 -0.66 3.69 0 213.41 243.37 38468 +1908 288 7.98 1.98 6.33 0 251.83 237.84 38273 +1908 289 12.67 6.67 11.02 0 334.82 229.23 38079 +1908 290 11.39 5.39 9.74 0 310.13 228.15 37885 +1908 291 12.4 6.4 10.75 0.27 329.48 168.05 37693 +1908 292 12.15 6.15 10.5 0.02 324.6 166.3 37501 +1908 293 13.72 7.72 12.07 0.03 356.31 162.57 37311 +1908 294 16.04 10.04 14.39 0 408 210.21 37121 +1908 295 13.09 7.09 11.44 0.72 343.28 159 36933 +1908 296 11.73 5.73 10.08 0.13 316.53 158.45 36745 +1908 297 11.73 5.73 10.08 0.42 316.53 156.41 36560 +1908 298 13.35 7.35 11.7 0.1 348.61 152.85 36375 +1908 299 13.54 7.54 11.89 0 352.55 200.77 36191 +1908 300 15.75 9.75 14.1 0 401.21 194.86 36009 +1908 301 17.28 11.28 15.63 0 438.16 189.89 35829 +1908 302 12.65 6.65 11 0 334.42 194.27 35650 +1908 303 10.95 4.95 9.3 0 302.02 193.78 35472 +1908 304 14.57 8.57 12.92 0 374.56 186.7 35296 +1908 305 1.96 -4.04 0.31 0 171.66 196.38 35122 +1908 306 4.05 -1.95 2.4 0.08 196.55 144.49 34950 +1908 307 4.78 -1.22 3.13 0.26 205.94 142.17 34779 +1908 308 3.2 -2.8 1.55 0 186.07 188.04 34610 +1908 309 3.5 -2.5 1.85 0 189.71 185.48 34444 +1908 310 -1.12 -7.12 -2.77 0 139.96 185.68 34279 +1908 311 -1.63 -7.63 -3.28 0.09 135.23 176.71 34116 +1908 312 1.02 -4.98 -0.63 0.1 161.39 173.73 33956 +1908 313 1.16 -4.84 -0.49 0.23 162.88 133.04 33797 +1908 314 -0.15 -6.15 -1.8 1.24 149.35 174.84 33641 +1908 315 3.02 -2.98 1.37 0 183.92 214.33 33488 +1908 316 3.17 -2.83 1.52 0 185.71 211.83 33337 +1908 317 3.68 -2.32 2.03 0 191.93 209.03 33188 +1908 318 2.61 -3.39 0.96 0 179.09 207.19 33042 +1908 319 8.31 2.31 6.66 0 257.03 200.58 32899 +1908 320 6.34 0.34 4.69 0 227.32 199.67 32758 +1908 321 6.89 0.89 5.24 0 235.3 156.56 32620 +1908 322 5.45 -0.55 3.8 0 214.9 155.78 32486 +1908 323 3.52 -2.48 1.87 0 189.96 155.39 32354 +1908 324 5.01 -0.99 3.36 0 208.98 152.39 32225 +1908 325 -0.41 -6.41 -2.06 0.38 146.78 157.49 32100 +1908 326 6.07 0.07 4.42 0 223.49 190.14 31977 +1908 327 5.03 -0.97 3.38 0 209.25 147.33 31858 +1908 328 3.99 -2.01 2.34 0 195.79 146 31743 +1908 329 5.71 -0.29 4.06 0.03 218.47 107.56 31631 +1908 330 2.92 -3.08 1.27 0.14 182.73 107.74 31522 +1908 331 0.83 -5.17 -0.82 0.65 159.38 107.55 31417 +1908 332 -0.84 -6.84 -2.49 0 142.61 142.48 31316 +1908 333 -0.7 -6.7 -2.35 0 143.96 141.32 31218 +1908 334 -1.7 -7.7 -3.35 0.42 134.59 149.16 31125 +1908 335 0.41 -5.59 -1.24 0 155.01 182.3 31035 +1908 336 1.89 -4.11 0.24 0.14 170.88 146.21 30949 +1908 337 2.55 -3.45 0.9 0 178.39 178.17 30867 +1908 338 -0.69 -6.69 -2.34 0 144.05 178.83 30790 +1908 339 -3.19 -9.19 -4.84 0 121.62 179.07 30716 +1908 340 -8.06 -14.06 -9.71 0.57 86.46 147.6 30647 +1908 341 -5.56 -11.56 -7.21 0.36 103.21 147.62 30582 +1908 342 -5.15 -11.15 -6.8 0.09 106.21 147.33 30521 +1908 343 -5.68 -11.68 -7.33 0.44 102.34 148.29 30465 +1908 344 -5.41 -11.41 -7.06 0.14 104.3 147.9 30413 +1908 345 -0.98 -6.98 -2.63 0 141.28 178.95 30366 +1908 346 -0.09 -6.09 -1.74 0 149.94 178.1 30323 +1908 347 0.27 -5.73 -1.38 0 153.58 177.38 30284 +1908 348 1.36 -4.64 -0.29 0 165.04 176.42 30251 +1908 349 5.05 -0.95 3.4 0 209.51 173.5 30221 +1908 350 4.69 -1.31 3.04 0 204.76 172.78 30197 +1908 351 4.39 -1.61 2.74 0 200.88 172.18 30177 +1908 352 2.65 -3.35 1 0 179.56 172.67 30162 +1908 353 5.98 -0.02 4.33 0 222.23 169.98 30151 +1908 354 7.55 1.55 5.9 0 245.19 167.93 30145 +1908 355 7.05 1.05 5.4 0.15 237.67 136.58 30144 +1908 356 3.79 -2.21 2.14 0 193.29 168.77 30147 +1908 357 3.93 -2.07 2.28 0.35 195.04 93.68 30156 +1908 358 4.43 -1.57 2.78 0.19 201.39 93.54 30169 +1908 359 -1.05 -7.05 -2.7 0 140.62 127.41 30186 +1908 360 -0.59 -6.59 -2.24 0.12 145.02 139.77 30208 +1908 361 -1.11 -7.11 -2.76 0.14 140.05 140.58 30235 +1908 362 0.73 -5.27 -0.92 0 158.33 172.16 30267 +1908 363 0.12 -5.88 -1.53 0.2 152.05 140.77 30303 +1908 364 0.04 -5.96 -1.61 0.04 151.25 141.04 30343 +1908 365 -1.54 -7.54 -3.19 0 136.05 174.45 30388 +1909 1 -1.4 -7.4 -3.05 0 137.34 175.23 30438 +1909 2 -2.29 -8.29 -3.94 0 129.32 176.22 30492 +1909 3 0.08 -5.92 -1.57 0 151.65 176.14 30551 +1909 4 0.31 -5.69 -1.34 0 153.98 176.83 30614 +1909 5 2.87 -3.13 1.22 0 182.14 175.79 30681 +1909 6 1.64 -4.36 -0.01 0 168.1 176.98 30752 +1909 7 2.04 -3.96 0.39 0 172.56 134.61 30828 +1909 8 0.45 -5.55 -1.2 0 155.42 136.86 30907 +1909 9 0.7 -5.3 -0.95 0.56 158.01 103.51 30991 +1909 10 4.98 -1.02 3.33 0.09 208.58 102.77 31079 +1909 11 6.3 0.3 4.65 0.02 226.75 102.87 31171 +1909 12 2.55 -3.45 0.9 0.17 178.39 105.31 31266 +1909 13 -1.5 -7.5 -3.15 0 136.42 143.93 31366 +1909 14 1.59 -4.41 -0.06 0 167.55 144.02 31469 +1909 15 2.26 -3.74 0.61 0 175.06 145.12 31575 +1909 16 2.95 -3.05 1.3 0 183.09 146.04 31686 +1909 17 5.27 -0.73 3.62 0 212.46 146.31 31800 +1909 18 2.67 -3.33 1.02 0 179.79 149.78 31917 +1909 19 -3.2 -9.2 -4.85 0 121.53 154.44 32038 +1909 20 -1.82 -7.82 -3.47 0.38 133.5 158.8 32161 +1909 21 -2.73 -8.73 -4.38 0 125.5 199.91 32289 +1909 22 -1.04 -7.04 -2.69 0 140.71 200.8 32419 +1909 23 -0.04 -6.04 -1.69 0 150.44 201.96 32552 +1909 24 -0.56 -6.56 -2.21 0 145.31 204.12 32688 +1909 25 -6.53 -12.53 -8.18 0 96.4 208.16 32827 +1909 26 -1.09 -7.09 -2.74 0 140.24 207.87 32969 +1909 27 -1.72 -7.72 -3.37 0 134.41 210.02 33114 +1909 28 -4.22 -10.22 -5.87 0.17 113.29 170.51 33261 +1909 29 -5.45 -11.45 -7.1 0.02 104.01 172.53 33411 +1909 30 -6.73 -12.73 -8.38 0 95.05 218.86 33564 +1909 31 -2.91 -8.91 -4.56 0.07 123.97 175.14 33718 +1909 32 0.24 -5.76 -1.41 0 153.27 220.29 33875 +1909 33 -0.66 -6.66 -2.31 0 144.34 223.22 34035 +1909 34 -2.14 -8.14 -3.79 0.05 130.64 179.72 34196 +1909 35 -0.07 -6.07 -1.72 0 150.14 227.07 34360 +1909 36 -4.59 -10.59 -6.24 0 110.43 231.52 34526 +1909 37 -4.39 -10.39 -6.04 0 111.97 233.71 34694 +1909 38 -4.03 -10.03 -5.68 0 114.79 236.15 34863 +1909 39 -5.27 -11.27 -6.92 0.69 105.32 191.11 35035 +1909 40 -1.02 -7.02 -2.67 0.31 140.9 192.31 35208 +1909 41 -0.83 -6.83 -2.48 0.39 142.71 195.07 35383 +1909 42 -1.97 -7.97 -3.62 0 132.16 248.75 35560 +1909 43 -2.61 -8.61 -4.26 0 126.53 251.6 35738 +1909 44 -0.37 -6.37 -2.02 0.18 147.17 200.67 35918 +1909 45 3.86 -2.14 2.21 0.03 194.16 199.9 36099 +1909 46 1.2 -4.8 -0.45 0 163.31 256.72 36282 +1909 47 0.52 -5.48 -1.13 0 156.14 259.74 36466 +1909 48 2.75 -3.25 1.1 0 180.73 260.55 36652 +1909 49 0.01 -5.99 -1.64 0 150.94 264.98 36838 +1909 50 2.75 -3.25 1.1 0 180.73 265.31 37026 +1909 51 1.74 -4.26 0.09 0 169.21 268.64 37215 +1909 52 1.09 -4.91 -0.56 0.27 162.13 213.61 37405 +1909 53 -1.59 -7.59 -3.24 0.02 135.6 216.96 37596 +1909 54 1.41 -4.59 -0.24 0.22 165.58 217.27 37788 +1909 55 2.59 -3.41 0.94 0 178.86 278.36 37981 +1909 56 4.59 -1.41 2.94 0 203.46 278.74 38175 +1909 57 8.76 2.76 7.11 0 264.26 276.26 38370 +1909 58 11.94 5.94 10.29 0 320.54 273.61 38565 +1909 59 8.37 2.37 6.72 0.01 257.98 218.44 38761 +1909 60 13.25 7.25 11.6 0.42 346.55 181.31 38958 +1909 61 12.29 6.29 10.64 0.28 327.32 184.56 39156 +1909 62 10.74 4.74 9.09 0.14 298.21 188.28 39355 +1909 63 6.23 0.23 4.58 0 225.75 259.44 39553 +1909 64 8.96 2.96 7.31 0 267.53 259.22 39753 +1909 65 5.73 -0.27 4.08 0 218.75 265.77 39953 +1909 66 7.58 1.58 5.93 0 245.65 266.49 40154 +1909 67 6.02 0.02 4.37 0 222.79 271.12 40355 +1909 68 3.31 -2.69 1.66 0.01 187.4 207.5 40556 +1909 69 3.66 -2.34 2.01 0 191.68 279 40758 +1909 70 5.7 -0.3 4.05 0 218.33 279.84 40960 +1909 71 8.44 2.44 6.79 0 259.1 279.56 41163 +1909 72 7.95 1.95 6.3 0 251.36 283 41366 +1909 73 8.63 2.63 6.98 0 262.15 284.79 41569 +1909 74 4.62 -1.38 2.97 0.02 203.85 219.15 41772 +1909 75 4.32 -1.68 2.67 0.11 199.98 221.44 41976 +1909 76 3.85 -2.15 2.2 0.33 194.04 223.8 42179 +1909 77 1.89 -4.11 0.24 0 170.88 302.85 42383 +1909 78 3.59 -2.41 1.94 1.17 190.82 227.99 42587 +1909 79 3.92 -2.08 2.27 1.15 194.91 229.82 42791 +1909 80 0.78 -5.22 -0.87 0.72 158.85 233.9 42996 +1909 81 2.35 -3.65 0.7 0.34 176.09 234.85 43200 +1909 82 5.24 -0.76 3.59 0.05 212.06 234.66 43404 +1909 83 6.21 0.21 4.56 0 225.47 314.27 43608 +1909 84 6.37 0.37 4.72 0 227.75 316.63 43812 +1909 85 7.95 1.95 6.3 0 251.36 317.11 44016 +1909 86 9.98 3.98 8.33 0 284.76 316.57 44220 +1909 87 10.44 4.44 8.79 0 292.83 318.37 44424 +1909 88 7.57 1.57 5.92 0.2 245.5 243.72 44627 +1909 89 10.17 4.17 8.52 0 288.07 323.42 44831 +1909 90 10.25 4.25 8.6 0 289.48 325.65 45034 +1909 91 11.36 5.36 9.71 0.14 309.57 244.53 45237 +1909 92 9.33 3.33 7.68 0 273.67 331.6 45439 +1909 93 9.42 3.42 7.77 0 275.19 333.69 45642 +1909 94 12.97 6.97 11.32 0 340.85 329.64 45843 +1909 95 13.56 7.56 11.91 0.32 352.96 247.94 46045 +1909 96 13.23 7.23 11.58 0.14 346.14 250 46246 +1909 97 14.75 8.75 13.1 0 378.52 332.18 46446 +1909 98 18.84 12.84 17.19 0 478.79 323.9 46647 +1909 99 20.14 14.14 18.49 0 515.05 322.04 46846 +1909 100 15.47 9.47 13.82 0 394.74 336.37 47045 +1909 101 14.79 8.79 13.14 0.37 379.41 254.87 47243 +1909 102 15.96 9.96 14.31 0.03 406.12 254.23 47441 +1909 103 18.55 12.55 16.9 0.16 471 250.5 47638 +1909 104 13.12 7.12 11.47 0 343.89 348.92 47834 +1909 105 14.02 8.02 12.37 0.09 362.66 261.6 48030 +1909 106 14.44 8.44 12.79 0.34 371.72 262.13 48225 +1909 107 13.5 7.5 11.85 0.34 351.71 264.91 48419 +1909 108 9.31 3.31 7.66 0.47 273.34 272.12 48612 +1909 109 11.79 5.79 10.14 0 317.68 360.03 48804 +1909 110 9.98 3.98 8.33 0.05 284.76 273.57 48995 +1909 111 12.86 6.86 11.21 0 338.63 360.85 49185 +1909 112 13.37 7.37 11.72 0 349.02 361.3 49374 +1909 113 10.01 4.01 8.36 0 285.28 369.17 49561 +1909 114 11.23 5.23 9.58 0 307.16 368.45 49748 +1909 115 7.14 1.14 5.49 0 239.01 376.75 49933 +1909 116 12.52 6.52 10.87 0 331.84 368.57 50117 +1909 117 13.85 7.85 12.2 0 359.05 367.03 50300 +1909 118 14.95 8.95 13.3 0 382.97 365.79 50481 +1909 119 13.68 7.68 12.03 0 355.47 369.92 50661 +1909 120 15.11 9.11 13.46 0 386.56 367.76 50840 +1909 121 18.24 12.24 16.59 0 462.8 360.51 51016 +1909 122 20.91 14.91 19.26 0 537.61 353.22 51191 +1909 123 21.27 15.27 19.62 0 548.44 352.96 51365 +1909 124 20.45 14.45 18.8 0.21 524.04 267.6 51536 +1909 125 17.76 11.76 16.11 0.24 450.34 274.59 51706 +1909 126 17.44 11.44 15.79 0 442.19 368.01 51874 +1909 127 17.34 11.34 15.69 0 439.67 369.17 52039 +1909 128 16.07 10.07 14.42 0.48 408.71 280.2 52203 +1909 129 15.76 9.76 14.11 0.17 401.44 281.44 52365 +1909 130 13.96 7.96 12.31 0.39 361.38 285.34 52524 +1909 131 12.5 6.5 10.85 0 331.45 384.49 52681 +1909 132 11.94 5.94 10.29 0 320.54 386.5 52836 +1909 133 13.45 7.45 11.8 0.33 350.68 287.97 52989 +1909 134 13.87 7.87 12.22 0.56 359.47 287.79 53138 +1909 135 13.73 7.73 12.08 0.98 356.52 288.56 53286 +1909 136 16.64 10.64 14.99 1.49 422.37 283.55 53430 +1909 137 13.15 7.15 11.5 0.17 344.5 290.56 53572 +1909 138 16.39 10.39 14.74 0.16 416.33 285.04 53711 +1909 139 14.13 8.13 12.48 0 365.02 386.48 53848 +1909 140 21.84 15.84 20.19 0 565.97 363.86 53981 +1909 141 20.8 14.8 19.15 0.01 534.34 276.02 54111 +1909 142 20.41 14.41 18.76 0.32 522.87 277.4 54238 +1909 143 17.09 11.09 15.44 0 433.42 380.77 54362 +1909 144 15.24 9.24 13.59 0 389.5 386.21 54483 +1909 145 15.09 9.09 13.44 0.02 386.11 290.3 54600 +1909 146 14.08 8.08 12.43 1.11 363.94 292.44 54714 +1909 147 15.07 9.07 13.42 0.32 385.66 290.99 54824 +1909 148 13.6 7.6 11.95 0.1 353.8 293.94 54931 +1909 149 15.51 9.51 13.86 0 395.66 387.56 55034 +1909 150 16.36 10.36 14.71 0 415.61 385.64 55134 +1909 151 15.95 9.95 14.3 0 405.89 387.14 55229 +1909 152 21.04 15.04 19.39 0 541.5 371.45 55321 +1909 153 23.99 17.99 22.34 0 636.44 360.21 55409 +1909 154 24.22 18.22 22.57 0 644.4 359.54 55492 +1909 155 26.62 20.62 24.97 0 732.62 348.75 55572 +1909 156 22.13 16.13 20.48 0 575.07 368.48 55648 +1909 157 24.39 18.39 22.74 0 650.34 359.46 55719 +1909 158 20.88 14.88 19.23 0 536.72 373.42 55786 +1909 159 21.97 15.97 20.32 0 570.04 369.66 55849 +1909 160 20.08 14.08 18.43 0 513.33 376.62 55908 +1909 161 21.39 15.39 19.74 0 552.1 372.07 55962 +1909 162 20.11 14.11 18.46 1.35 514.19 282.49 56011 +1909 163 20.23 14.23 18.58 0.03 517.65 282.34 56056 +1909 164 20.81 14.81 19.16 0 534.64 374.47 56097 +1909 165 23.46 17.46 21.81 0 618.41 364.43 56133 +1909 166 23.74 17.74 22.09 0 627.88 363.35 56165 +1909 167 21.12 15.12 19.47 0 543.91 373.48 56192 +1909 168 19.33 13.33 17.68 0.06 492.19 284.78 56214 +1909 169 15.83 9.83 14.18 0 403.08 390.05 56231 +1909 170 18.24 12.24 16.59 0 462.8 383.16 56244 +1909 171 17.83 11.83 16.18 0.23 452.14 288.35 56252 +1909 172 16.61 10.61 14.96 0 421.64 387.97 56256 +1909 173 16.95 10.95 15.3 0.08 429.96 290.25 56255 +1909 174 16.31 10.31 14.66 0 414.42 388.7 56249 +1909 175 16.3 10.3 14.65 0.2 414.18 291.52 56238 +1909 176 22.46 16.46 20.81 0.07 585.58 276.32 56223 +1909 177 18.62 12.62 16.97 1.07 472.87 286.32 56203 +1909 178 17.06 11.06 15.41 1.06 432.68 289.84 56179 +1909 179 18.08 12.08 16.43 0.05 458.62 287.51 56150 +1909 180 17.06 11.06 15.41 0.73 432.68 289.67 56116 +1909 181 15.88 9.88 14.23 0 404.24 389.41 56078 +1909 182 16.66 10.66 15.01 0.08 422.85 290.35 56035 +1909 183 18.19 12.19 16.54 0.23 461.49 286.87 55987 +1909 184 19.59 13.59 17.94 0 499.44 377.89 55935 +1909 185 22.27 16.27 20.62 0.04 579.51 276.19 55879 +1909 186 21.35 15.35 19.7 0 550.88 371.44 55818 +1909 187 23.62 17.62 21.97 0.01 623.81 271.82 55753 +1909 188 27.35 21.35 25.7 0.22 761.39 258.79 55684 +1909 189 23.3 17.3 21.65 0.01 613.06 272.48 55611 +1909 190 22.74 16.74 21.09 0.04 594.62 273.88 55533 +1909 191 17.93 11.93 16.28 0 454.72 381.49 55451 +1909 192 17.36 11.36 15.71 0.55 440.17 287.14 55366 +1909 193 20.88 14.88 19.23 0.41 536.72 278.47 55276 +1909 194 16.59 10.59 14.94 0.31 421.16 288.39 55182 +1909 195 15.05 9.05 13.4 0.03 385.21 291.23 55085 +1909 196 22.36 16.36 20.71 0 582.38 364.94 54984 +1909 197 23.4 17.4 21.75 0 616.4 360.38 54879 +1909 198 24.64 18.64 22.99 0 659.15 354.76 54770 +1909 199 24.82 18.82 23.17 0.14 665.56 265.22 54658 +1909 200 26.68 20.68 25.03 0.25 734.95 258.5 54542 +1909 201 24.78 18.78 23.13 0 664.13 352.97 54423 +1909 202 27 21 25.35 0 747.48 342.12 54301 +1909 203 24.74 18.74 23.09 1.2 662.71 264.08 54176 +1909 204 26.77 20.77 25.12 1.67 738.45 256.72 54047 +1909 205 23.75 17.75 22.1 0.47 628.22 266.48 53915 +1909 206 21.08 15.08 19.43 0.02 542.7 273.71 53780 +1909 207 20.43 14.43 18.78 0 523.45 366.54 53643 +1909 208 16.91 10.91 15.26 0 428.97 376.73 53502 +1909 209 16.22 10.22 14.57 0.04 412.27 283.46 53359 +1909 210 17.18 11.18 15.53 0.03 435.66 281.01 53213 +1909 211 15.31 9.31 13.66 0.11 391.09 284.14 53064 +1909 212 18.13 12.13 16.48 0 459.92 370.34 52913 +1909 213 20.65 14.65 19 0.33 529.9 271.16 52760 +1909 214 25.19 19.19 23.54 0 678.9 343.16 52604 +1909 215 22.5 16.5 20.85 1.9 586.86 265.11 52445 +1909 216 21.41 15.41 19.76 1.91 552.71 267.35 52285 +1909 217 24.01 18.01 22.36 0.17 637.13 259.25 52122 +1909 218 27.81 21.81 26.16 0 780.01 327.62 51958 +1909 219 22.75 16.75 21.1 0 594.94 348.83 51791 +1909 220 24.7 18.7 23.05 0.01 661.28 255.07 51622 +1909 221 25.87 19.87 24.22 0.47 704.01 250.52 51451 +1909 222 22.82 16.82 21.17 0.19 597.22 259.23 51279 +1909 223 21.26 15.26 19.61 0.04 548.14 262.63 51105 +1909 224 25.28 19.28 23.63 0.22 682.18 250.15 50929 +1909 225 24.77 18.77 23.12 0.32 663.78 250.95 50751 +1909 226 21.2 15.2 19.55 0.4 546.32 260.3 50572 +1909 227 22.14 16.14 20.49 0 575.39 342.5 50392 +1909 228 22.28 16.28 20.63 1.08 579.83 255.6 50210 +1909 229 21.47 15.47 19.82 0.02 554.54 256.84 50026 +1909 230 26.26 20.26 24.61 0 718.77 322.28 49842 +1909 231 25.22 19.22 23.57 0.69 679.99 244.06 49656 +1909 232 23.92 17.92 22.27 0.82 634.03 247.06 49469 +1909 233 22.17 16.17 20.52 0.09 576.34 250.93 49280 +1909 234 20.71 14.71 19.06 0.8 531.67 253.61 49091 +1909 235 23.41 17.41 21.76 1 616.73 245.39 48900 +1909 236 17.14 11.14 15.49 0 434.67 345.72 48709 +1909 237 17.25 11.25 15.6 0 437.41 343.76 48516 +1909 238 18.41 12.41 16.76 0 467.28 338.91 48323 +1909 239 18.46 12.46 16.81 0.46 468.61 252.94 48128 +1909 240 22.3 16.3 20.65 0.35 580.46 242.58 47933 +1909 241 21.93 15.93 20.28 0.06 568.78 242.27 47737 +1909 242 23.46 17.46 21.81 0.03 618.41 236.93 47541 +1909 243 23.55 17.55 21.9 1.38 621.44 235.34 47343 +1909 244 16.64 10.64 14.99 0.54 422.37 249.83 47145 +1909 245 14.98 8.98 13.33 0 383.64 335.15 46947 +1909 246 15.59 9.59 13.94 0 397.51 331.76 46747 +1909 247 18.1 12.1 16.45 0 459.14 323.65 46547 +1909 248 17.19 11.19 15.54 1.21 435.91 243.05 46347 +1909 249 17.35 11.35 15.7 0 439.92 321.59 46146 +1909 250 16.38 10.38 14.73 0.03 416.09 241.5 45945 +1909 251 18.37 12.37 16.72 0 466.23 314.88 45743 +1909 252 17.96 11.96 16.31 0 455.5 313.8 45541 +1909 253 18.63 12.63 16.98 0 473.14 309.93 45339 +1909 254 22.87 16.87 21.22 0 598.86 295.06 45136 +1909 255 24.24 18.24 22.59 0.13 645.09 216.08 44933 +1909 256 25.81 19.81 24.16 0 701.77 280.04 44730 +1909 257 26.08 20.08 24.43 0.02 711.92 207.73 44527 +1909 258 23.07 17.07 21.42 0.03 605.43 214.3 44323 +1909 259 23.8 17.8 22.15 1.54 629.93 210.7 44119 +1909 260 23.79 17.79 22.14 0.47 629.58 209.03 43915 +1909 261 21.54 15.54 19.89 0 556.69 283.61 43711 +1909 262 20.27 14.27 18.62 0.77 518.8 213.74 43507 +1909 263 19.07 13.07 17.42 1.29 485.04 214.35 43303 +1909 264 18.32 12.32 16.67 0.59 464.91 213.87 43099 +1909 265 14.13 8.13 12.48 0 365.02 291.92 42894 +1909 266 16.02 10.02 14.37 0 407.53 285.62 42690 +1909 267 16.09 10.09 14.44 0 409.18 282.8 42486 +1909 268 18 12 16.35 0 456.53 275.99 42282 +1909 269 15.79 9.79 14.14 0 402.14 278.36 42078 +1909 270 14.68 8.68 13.03 1.66 376.98 208.44 41875 +1909 271 14.02 8.02 12.37 0 362.66 276.53 41671 +1909 272 17.33 11.33 15.68 0 439.42 267.16 41468 +1909 273 21.61 15.61 19.96 0.04 558.84 190.55 41265 +1909 274 18.2 12.2 16.55 0 461.75 260.1 41062 +1909 275 18.35 12.35 16.7 0 465.7 257.05 40860 +1909 276 22.02 16.02 20.37 0 571.61 245.16 40658 +1909 277 20.75 14.75 19.1 0 532.86 246.03 40456 +1909 278 14.95 8.95 13.3 0 382.97 255.91 40255 +1909 279 15.55 9.55 13.9 0 396.58 252 40054 +1909 280 14.94 8.94 13.29 0.14 382.75 187.87 39854 +1909 281 14.4 8.4 12.75 0.03 370.85 186.56 39654 +1909 282 9.73 3.73 8.08 0.37 280.45 189.74 39455 +1909 283 7.12 1.12 5.47 0 238.71 253.21 39256 +1909 284 9.85 3.85 8.2 0 282.51 246.92 39058 +1909 285 8.44 2.44 6.79 0 259.1 245.95 38861 +1909 286 12.78 6.78 11.13 0 337.02 237.42 38664 +1909 287 14.53 8.53 12.88 0 373.68 231.73 38468 +1909 288 16.81 10.81 15.16 0 426.52 224.96 38273 +1909 289 21.38 15.38 19.73 0 551.79 212.65 38079 +1909 290 20.46 14.46 18.81 0 524.33 212.09 37885 +1909 291 19.9 13.9 18.25 0.12 508.19 158.08 37693 +1909 292 15.39 9.39 13.74 0.35 392.91 162.61 37501 +1909 293 13.69 7.69 12.04 1.43 355.68 162.61 37311 +1909 294 11.17 5.17 9.52 0.13 306.05 163.06 37121 +1909 295 11.25 5.25 9.6 0.35 307.53 160.85 36933 +1909 296 12.72 6.72 11.07 0 335.82 209.95 36745 +1909 297 13.44 7.44 11.79 0.02 350.47 154.68 36560 +1909 298 16.14 10.14 14.49 0 410.37 199.54 36375 +1909 299 14.64 8.64 12.99 0 376.1 199.18 36191 +1909 300 13.95 7.95 12.3 0 361.17 197.57 36009 +1909 301 15.8 9.8 14.15 0 402.38 192.33 35829 +1909 302 13.17 7.17 11.52 0 344.91 193.58 35650 +1909 303 17.57 11.57 15.92 0 445.49 184.39 35472 +1909 304 17.62 11.62 15.97 0 446.76 181.94 35296 +1909 305 9.83 3.83 8.18 0 282.17 189.83 35122 +1909 306 9.09 3.09 7.44 0 269.68 188.34 34950 +1909 307 6.89 0.89 5.24 0 235.3 187.86 34779 +1909 308 8.69 2.69 7.04 0 263.12 183.61 34610 +1909 309 9.11 3.11 7.46 0 270.01 180.89 34444 +1909 310 4.59 -1.41 2.94 0.01 203.46 136.68 34279 +1909 311 4.19 -1.81 2.54 0 198.32 180.32 34116 +1909 312 6.65 0.65 5 0 231.79 175.8 33956 +1909 313 7.57 1.57 5.92 0.3 245.5 129.68 33797 +1909 314 7.83 1.83 6.18 0.04 249.5 128.04 33641 +1909 315 8.57 2.57 6.92 1.2 261.19 125.66 33488 +1909 316 9.89 3.89 8.24 0 283.2 164.15 33337 +1909 317 6.78 0.78 5.13 0 233.69 164.67 33188 +1909 318 6.15 0.15 4.5 0 224.62 162.8 33042 +1909 319 4.67 -1.33 3.02 0.01 204.5 121.61 32899 +1909 320 5.53 -0.47 3.88 0 215.99 159.67 32758 +1909 321 4.33 -1.67 2.68 0.13 200.11 118.77 32620 +1909 322 1.1 -4.9 -0.55 0 162.24 158.39 32486 +1909 323 2.66 -3.34 1.01 0 179.67 155.9 32354 +1909 324 4.04 -1.96 2.39 0 196.42 153.01 32225 +1909 325 6.04 0.04 4.39 0 223.07 149.96 32100 +1909 326 4.26 -1.74 2.61 0 199.21 149.67 31977 +1909 327 4.19 -1.81 2.54 0 198.32 147.86 31858 +1909 328 4.55 -1.45 2.9 0.17 202.94 109.25 31743 +1909 329 3.88 -2.12 2.23 0 194.41 144.56 31631 +1909 330 2.17 -3.83 0.52 0 174.03 144.06 31522 +1909 331 5.94 -0.06 4.29 0 221.67 140.5 31417 +1909 332 6.32 0.32 4.67 0 227.04 138.61 31316 +1909 333 7.73 1.73 6.08 0 247.95 136.53 31218 +1909 334 8.6 2.6 6.95 0 261.67 134.78 31125 +1909 335 5.13 -0.87 3.48 0.74 210.58 102.01 31035 +1909 336 1.74 -4.26 0.09 0.76 169.21 102.61 30949 +1909 337 4.25 -1.75 2.6 0.2 199.08 100.36 30867 +1909 338 5.87 -0.13 4.22 0 220.69 131.88 30790 +1909 339 7.94 1.94 6.29 0 251.21 129.7 30716 +1909 340 3.61 -2.39 1.96 0 191.06 131.7 30647 +1909 341 4.4 -1.6 2.75 0 201 130.33 30582 +1909 342 4.06 -1.94 2.41 0 196.67 129.76 30521 +1909 343 5.59 -0.41 3.94 0.06 216.82 96.03 30465 +1909 344 9.54 3.54 7.89 0 277.21 124.17 30413 +1909 345 7.33 1.33 5.68 0.45 241.86 94.03 30366 +1909 346 4.67 -1.33 3.02 0.05 204.5 94.86 30323 +1909 347 1.93 -4.07 0.28 0 171.33 127.32 30284 +1909 348 2.72 -3.28 1.07 0 180.38 126.58 30251 +1909 349 1.53 -4.47 -0.12 0 166.89 126.77 30221 +1909 350 0.19 -5.81 -1.46 0 152.76 127.03 30197 +1909 351 0.78 -5.22 -0.87 0.01 158.85 94.91 30177 +1909 352 3.9 -2.1 2.25 0.26 194.66 93.71 30162 +1909 353 4.93 -1.07 3.28 0.32 207.92 93.23 30151 +1909 354 7.96 1.96 6.31 0 251.52 122.35 30145 +1909 355 10.29 4.29 8.64 0.19 290.18 90.44 30144 +1909 356 16.62 10.62 14.97 0.52 421.88 85.78 30147 +1909 357 12.67 6.67 11.02 0.24 334.82 88.95 30156 +1909 358 13.58 7.58 11.93 0.77 353.38 88.36 30169 +1909 359 6.52 0.52 4.87 0.38 229.91 92.69 30186 +1909 360 5.56 -0.44 3.91 1.19 216.41 93.41 30208 +1909 361 4.67 -1.33 3.02 2.44 204.5 94.05 30235 +1909 362 4.87 -1.13 3.22 0 207.13 125.72 30267 +1909 363 4.78 -1.22 3.13 0.18 205.94 94.77 30303 +1909 364 3.1 -2.9 1.45 0.23 184.88 95.76 30343 +1909 365 4.25 -1.75 2.6 0 199.08 127.62 30388 +1910 1 3.36 -2.64 1.71 0 188.01 129 30438 +1910 2 5.92 -0.08 4.27 0.15 221.39 96.19 30492 +1910 3 5.76 -0.24 4.11 0 219.16 129.29 30551 +1910 4 5.39 -0.61 3.74 0 214.09 130.43 30614 +1910 5 5.32 -0.68 3.67 0 213.14 131.11 30681 +1910 6 3.58 -2.42 1.93 0 190.7 133.01 30752 +1910 7 7.6 1.6 5.95 0.41 245.96 98.45 30828 +1910 8 3.96 -2.04 2.31 0.14 195.41 101.31 30907 +1910 9 6.01 0.01 4.36 0.47 222.65 101.31 30991 +1910 10 7.44 1.44 5.79 0.25 243.52 101.54 31079 +1910 11 3.28 -2.72 1.63 0.58 187.04 104.25 31171 +1910 12 3.64 -2.36 1.99 0 191.43 139.81 31266 +1910 13 3.81 -2.19 2.16 0 193.54 141.34 31366 +1910 14 3.31 -2.69 1.66 0 187.4 143.1 31469 +1910 15 4.99 -1.01 3.34 0 208.72 143.54 31575 +1910 16 3.24 -2.76 1.59 0.08 186.56 109.41 31686 +1910 17 0.24 -5.76 -1.41 0 153.27 149.12 31800 +1910 18 -0.03 -6.03 -1.68 0 150.54 151.16 31917 +1910 19 0.35 -5.65 -1.3 0 154.39 152.92 32038 +1910 20 -0.3 -6.3 -1.95 0 147.86 154.83 32161 +1910 21 0.34 -5.66 -1.31 0 154.29 156.55 32289 +1910 22 4.1 -1.9 2.45 0.14 197.18 117.16 32419 +1910 23 6.27 0.27 4.62 0.64 226.32 117.38 32552 +1910 24 5.06 -0.94 3.41 0.01 209.65 119.56 32688 +1910 25 6.9 0.9 5.25 0.55 235.45 119.96 32827 +1910 26 2.61 -3.39 0.96 0.81 179.09 123.59 32969 +1910 27 2.52 -3.48 0.87 0.82 178.05 125.15 33114 +1910 28 2.24 -3.76 0.59 0.31 174.83 126.94 33261 +1910 29 -0.2 -6.2 -1.85 1.03 148.85 172.2 33411 +1910 30 -1.08 -7.08 -2.73 0.72 140.33 176.09 33564 +1910 31 -1.63 -7.63 -3.28 0.53 135.23 179.39 33718 +1910 32 4.18 -1.82 2.53 0.8 198.19 177.79 33875 +1910 33 3.75 -2.25 2.1 0.42 192.79 179.33 34035 +1910 34 1.16 -4.84 -0.49 0.4 162.88 181.86 34196 +1910 35 5.67 -0.33 4.02 0 217.92 226.07 34360 +1910 36 5.01 -0.99 3.36 0 208.98 228.3 34526 +1910 37 6.21 0.21 4.56 0.17 225.47 181.96 34694 +1910 38 3.78 -2.22 2.13 0 193.17 232.8 34863 +1910 39 5.77 -0.23 4.12 0.13 219.3 184.73 35035 +1910 40 5.48 -0.52 3.83 0 215.31 235.05 35208 +1910 41 4.83 -1.17 3.18 0 206.6 237.44 35383 +1910 42 9.45 3.45 7.8 0 275.69 197.47 35560 +1910 43 8.21 2.21 6.56 0 255.44 201.42 35738 +1910 44 7.61 1.61 5.96 0 246.11 204.54 35918 +1910 45 9.98 3.98 8.33 0 284.76 204.66 36099 +1910 46 5.21 -0.79 3.56 0 211.65 211.99 36282 +1910 47 5.17 -0.83 3.52 1.04 211.12 161.13 36466 +1910 48 4.1 -1.9 2.45 0.1 197.18 163.9 36652 +1910 49 4.62 -1.38 2.97 0 203.85 220.89 36838 +1910 50 5.9 -0.1 4.25 0.28 221.11 166.83 37026 +1910 51 7.37 1.37 5.72 0.32 242.46 167.99 37215 +1910 52 9.45 3.45 7.8 1.71 275.69 168.4 37405 +1910 53 8.77 2.77 7.12 0.79 264.42 171.18 37596 +1910 54 5.75 -0.25 4.1 0 219.02 234.08 37788 +1910 55 7.69 1.69 6.04 0.02 247.34 176.34 37981 +1910 56 10.39 4.39 8.74 0 291.95 234.63 38175 +1910 57 6.93 0.93 5.28 0.15 235.89 181.11 38370 +1910 58 7.97 1.97 6.32 0.26 251.67 182.46 38565 +1910 59 9.66 3.66 8.01 0 279.26 243.96 38761 +1910 60 12.32 6.32 10.67 0.17 327.91 182.37 38958 +1910 61 10.94 4.94 9.29 0.12 301.83 186.01 39156 +1910 62 7.81 1.81 6.16 0.02 249.19 191.04 39355 +1910 63 4.24 -1.76 2.59 0 198.96 261.39 39553 +1910 64 4.03 -1.97 2.38 0.05 196.29 198.38 39753 +1910 65 5.46 -0.54 3.81 0 215.04 266.04 39953 +1910 66 5.87 -0.13 4.22 0 220.69 268.37 40154 +1910 67 5.67 -0.33 4.02 0 217.92 271.49 40355 +1910 68 6.28 0.28 4.63 0 226.47 273.73 40556 +1910 69 8.35 2.35 6.7 0 257.66 273.93 40758 +1910 70 6.47 0.47 4.82 0 229.19 279 40960 +1910 71 4.8 -1.2 3.15 0 206.2 283.71 41163 +1910 72 6.09 0.09 4.44 0 223.77 285.18 41366 +1910 73 4.26 -1.74 2.61 0 199.21 289.79 41569 +1910 74 3.16 -2.84 1.51 0.1 185.59 220.22 41772 +1910 75 8.22 2.22 6.57 0 255.6 290.79 41976 +1910 76 12.8 6.8 11.15 0 337.42 286.51 42179 +1910 77 11.36 5.36 9.71 0 309.57 291.47 42383 +1910 78 11.04 5.04 9.39 0 303.66 294.61 42587 +1910 79 12.97 6.97 11.32 0 340.85 294.06 42791 +1910 80 10.15 4.15 8.5 0 287.72 301.21 42996 +1910 81 12.43 6.43 10.78 0 330.07 300.05 43200 +1910 82 13.75 7.75 12.1 0 356.94 300.25 43404 +1910 83 10.53 4.53 8.88 0 294.44 308.3 43608 +1910 84 6.78 0.78 5.13 0 233.69 316.13 43812 +1910 85 6.85 0.85 5.2 0 234.71 318.55 44016 +1910 86 7.42 1.42 5.77 0 243.22 320.24 44220 +1910 87 11.01 5.01 9.36 0 303.11 317.44 44424 +1910 88 10.93 4.93 9.28 0 301.65 319.91 44627 +1910 89 12.74 6.74 11.09 0 336.22 318.97 44831 +1910 90 13.61 7.61 11.96 0 354.01 319.63 45034 +1910 91 15.63 9.63 13.98 0 398.43 317.57 45237 +1910 92 16.66 10.66 15.01 0 422.85 317.36 45439 +1910 93 11.63 5.63 9.98 0 314.64 330 45642 +1910 94 9.11 3.11 7.46 0.23 270.01 252.25 45843 +1910 95 9.09 3.09 7.44 0.02 269.68 253.89 46045 +1910 96 7.13 1.13 5.48 0 238.86 343.49 46246 +1910 97 2.43 -3.57 0.78 0.08 177.01 263.36 46446 +1910 98 5.7 -0.3 4.05 0 218.33 349.45 46647 +1910 99 8.16 2.16 6.51 0 254.65 348.13 46846 +1910 100 8.07 2.07 6.42 0.29 253.24 262.68 47045 +1910 101 10.49 4.49 8.84 0.07 293.72 261.23 47243 +1910 102 12.08 6.08 10.43 0 323.24 347.33 47441 +1910 103 10.97 4.97 9.32 0 302.38 351.22 47638 +1910 104 10.72 4.72 9.07 0 297.85 353.5 47834 +1910 105 13 7 11.35 0 341.45 350.95 48030 +1910 106 10.28 4.28 8.63 0 290 357.74 48225 +1910 107 13.63 7.63 11.98 0 354.42 352.94 48419 +1910 108 15.54 9.54 13.89 0 396.35 350.32 48612 +1910 109 16.62 10.62 14.97 0 421.88 349.22 48804 +1910 110 16.41 10.41 14.76 0 416.81 351.14 48995 +1910 111 13.49 7.49 11.84 0.15 351.51 269.64 49185 +1910 112 11.79 5.79 10.14 0.11 317.68 273.39 49374 +1910 113 11.55 5.55 9.9 0 313.13 366.34 49561 +1910 114 12.14 6.14 10.49 0.01 324.4 275.01 49748 +1910 115 16.58 10.58 14.93 0.31 420.91 268.43 49933 +1910 116 15.82 9.82 14.17 0.11 402.84 270.79 50117 +1910 117 13.63 7.63 11.98 0.83 354.42 275.64 50300 +1910 118 13.6 7.6 11.95 0.85 353.8 276.68 50481 +1910 119 13.74 7.74 12.09 0.92 356.73 277.34 50661 +1910 120 13.05 7.05 11.4 0.8 342.47 279.35 50840 +1910 121 18.33 12.33 16.68 1.07 465.17 270.18 51016 +1910 122 20.17 14.17 18.52 0.28 515.92 266.77 51191 +1910 123 21.41 15.41 19.76 0.05 552.71 264.35 51365 +1910 124 20.24 14.24 18.59 0.02 517.94 268.13 51536 +1910 125 20.38 14.38 18.73 0.44 522 268.49 51706 +1910 126 17.38 11.38 15.73 1.73 440.68 276.13 51874 +1910 127 16.25 10.25 14.6 0.19 412.98 279.1 52039 +1910 128 14.8 8.8 13.15 0.08 379.63 282.6 52203 +1910 129 15.41 9.41 13.76 0 393.37 376.15 52365 +1910 130 14.54 8.54 12.89 0 373.9 379.08 52524 +1910 131 13.85 7.85 12.2 0 359.05 381.5 52681 +1910 132 14.15 8.15 12.5 0.01 365.44 286.23 52836 +1910 133 14.79 8.79 13.14 0 379.41 380.81 52989 +1910 134 12.49 6.49 10.84 0 331.25 386.79 53138 +1910 135 13.83 7.83 12.18 0.09 358.63 288.39 53286 +1910 136 11.56 5.56 9.91 1.24 313.32 292.56 53430 +1910 137 10.92 4.92 9.27 0.31 301.47 294.05 53572 +1910 138 14.71 8.71 13.06 0.7 377.64 288.29 53711 +1910 139 14.73 8.73 13.08 0 378.08 385.03 53848 +1910 140 19.41 13.41 17.76 0.03 494.41 279.21 53981 +1910 141 17.06 11.06 15.41 0 432.68 379.82 54111 +1910 142 15.44 9.44 13.79 0 394.06 384.68 54238 +1910 143 17.81 11.81 16.16 0 451.62 378.68 54362 +1910 144 18.68 12.68 17.03 0.9 474.48 282.39 54483 +1910 145 22.87 16.87 21.22 0.03 598.86 271.69 54600 +1910 146 19.3 13.3 17.65 0.15 491.36 281.54 54714 +1910 147 18.48 12.48 16.83 0.01 469.14 283.84 54824 +1910 148 20.04 14.04 18.39 0.28 512.18 280.35 54931 +1910 149 21.86 15.86 20.21 1.85 566.6 275.73 55034 +1910 150 18.59 12.59 16.94 1.65 472.07 284.35 55134 +1910 151 22.87 16.87 21.22 0.1 598.86 273.34 55229 +1910 152 27.26 21.26 25.61 0 757.79 344.88 55321 +1910 153 26.23 20.23 24.58 0.21 717.62 262.62 55409 +1910 154 24.61 18.61 22.96 0.27 658.09 268.39 55492 +1910 155 24.71 18.71 23.06 0.05 661.64 268.2 55572 +1910 156 18.42 12.42 16.77 0.79 467.55 285.93 55648 +1910 157 18.44 12.44 16.79 0 468.08 381.34 55719 +1910 158 16.15 10.15 14.5 0.09 410.61 291.11 55786 +1910 159 13.27 7.27 11.62 0.73 346.96 296.67 55849 +1910 160 11.55 5.55 9.9 0 313.13 399.47 55908 +1910 161 14.4 8.4 12.75 0.02 370.85 294.86 55962 +1910 162 12.31 6.31 10.66 0 327.71 398.01 56011 +1910 163 12.05 6.05 10.4 0.14 322.66 299.09 56056 +1910 164 13.55 7.55 11.9 0.14 352.75 296.63 56097 +1910 165 15.43 9.43 13.78 0.01 393.83 293.24 56133 +1910 166 18.02 12.02 16.37 0.41 457.05 287.84 56165 +1910 167 17.42 11.42 15.77 0.18 441.69 289.14 56192 +1910 168 19.51 13.51 17.86 0.09 497.2 284.34 56214 +1910 169 22.6 16.6 20.95 0.37 590.08 276 56231 +1910 170 25.72 19.72 24.07 0.26 698.41 265.98 56244 +1910 171 27.4 21.4 25.75 0.29 763.4 259.88 56252 +1910 172 25.32 19.32 23.67 1.27 683.64 267.4 56256 +1910 173 25.37 19.37 23.72 4.11 685.47 267.22 56255 +1910 174 21.67 15.67 20.02 0.8 560.7 278.63 56249 +1910 175 25.93 19.93 24.28 0 706.27 353.58 56238 +1910 176 27.29 21.29 25.64 0.06 758.99 260.17 56223 +1910 177 30.6 24.6 28.95 0.3 901.38 246.35 56203 +1910 178 26.87 20.87 25.22 0.92 742.37 261.7 56179 +1910 179 25.83 19.83 24.18 0.93 702.51 265.38 56150 +1910 180 21.82 15.82 20.17 1.2 565.35 277.93 56116 +1910 181 23.56 17.56 21.91 0.66 621.78 272.74 56078 +1910 182 24.79 18.79 23.14 0.01 664.49 268.69 56035 +1910 183 21.23 15.23 19.58 0 547.23 372.37 55987 +1910 184 20.97 14.97 19.32 0.06 539.4 279.86 55935 +1910 185 24.71 18.71 23.06 0.04 661.64 268.66 55879 +1910 186 20.57 14.57 18.92 0 527.55 374.22 55818 +1910 187 23.81 17.81 22.16 1.13 630.27 271.23 55753 +1910 188 20.43 14.43 18.78 0.88 523.45 280.69 55684 +1910 189 21.45 15.45 19.8 0.7 553.93 277.83 55611 +1910 190 23.07 17.07 21.42 0 605.43 363.87 55533 +1910 191 25.54 19.54 23.89 0 691.73 353.01 55451 +1910 192 26.07 20.07 24.42 0.08 711.55 262.69 55366 +1910 193 23.12 17.12 21.47 0 607.08 362.85 55276 +1910 194 20.38 14.38 18.73 0 522 372.81 55182 +1910 195 19.46 13.46 17.81 0 495.8 375.62 55085 +1910 196 16.73 10.73 15.08 0.54 424.56 287.58 54984 +1910 197 17.13 11.13 15.48 0.02 434.42 286.39 54879 +1910 198 15.04 9.04 13.39 0 384.99 387.01 54770 +1910 199 17.01 11.01 15.36 0 431.44 381.39 54658 +1910 200 19.43 13.43 17.78 0.04 494.97 280.25 54542 +1910 201 21.25 15.25 19.6 0.3 547.84 275.23 54423 +1910 202 19.21 13.21 17.56 0 488.88 373.33 54301 +1910 203 21.55 15.55 19.9 0.87 557 273.62 54176 +1910 204 22.78 16.78 21.13 0.53 595.92 269.77 54047 +1910 205 20.7 14.7 19.05 0.43 531.38 275.13 53915 +1910 206 17.87 11.87 16.22 0.04 453.17 281.49 53780 +1910 207 21.36 15.36 19.71 0 551.18 363.29 53643 +1910 208 22.93 16.93 21.28 0 600.82 356.76 53502 +1910 209 25.4 19.4 23.75 0 686.58 345.78 53359 +1910 210 23.44 17.44 21.79 0.43 617.74 265.12 53213 +1910 211 21.4 15.4 19.75 0.67 552.4 270.35 53064 +1910 212 19.16 13.16 17.51 0.85 487.51 275.39 52913 +1910 213 17.11 11.11 15.46 2.1 433.92 279.37 52760 +1910 214 16.51 10.51 14.86 0.14 419.22 280.03 52604 +1910 215 14.5 8.5 12.85 0 373.03 377.77 52445 +1910 216 14.67 8.67 13.02 0.31 376.76 282.24 52285 +1910 217 19.98 13.98 18.33 0.71 510.47 270.34 52122 +1910 218 20.98 14.98 19.33 0 539.7 356.28 51958 +1910 219 20.28 14.28 18.63 0 519.09 357.61 51791 +1910 220 22.93 16.93 21.28 0 600.82 347.22 51622 +1910 221 22.69 16.69 21.04 0.21 593 260.37 51451 +1910 222 25.04 19.04 23.39 0.15 673.47 252.5 51279 +1910 223 20.45 14.45 18.8 0 524.04 352.92 51105 +1910 224 21.44 15.44 19.79 0 553.62 348.5 50929 +1910 225 22.49 16.49 20.84 0 586.54 343.6 50751 +1910 226 23.35 17.35 21.7 0.72 614.73 254.42 50572 +1910 227 23.6 17.6 21.95 0 623.13 337.01 50392 +1910 228 26.25 20.25 24.6 0 718.38 324.69 50210 +1910 229 25.93 19.93 24.28 0.01 706.27 243.71 50026 +1910 230 26.94 20.94 25.29 0.1 745.11 239.37 49842 +1910 231 24.87 18.87 23.22 0.29 667.35 245.16 49656 +1910 232 23.72 17.72 22.07 0.13 627.2 247.64 49469 +1910 233 22.49 16.49 20.84 0.5 586.54 250.07 49280 +1910 234 25.4 19.4 23.75 0.75 686.58 240.49 49091 +1910 235 23.38 17.38 21.73 0.07 615.73 245.48 48900 +1910 236 21.17 15.17 19.52 0 545.42 333.75 48709 +1910 237 18.24 12.24 16.59 0.16 462.8 255.8 48516 +1910 238 23.37 17.37 21.72 0.23 615.39 242.06 48323 +1910 239 19.59 13.59 17.94 0 499.44 333.96 48128 +1910 240 18.46 12.46 16.81 0.01 468.61 251.62 47933 +1910 241 20.08 14.08 18.43 0 513.33 329.02 47737 +1910 242 21.91 15.91 20.26 0.25 568.16 241.05 47541 +1910 243 20.42 14.42 18.77 1.43 523.16 243.3 47343 +1910 244 17.49 11.49 15.84 0.81 443.46 248.2 47145 +1910 245 13.19 7.19 11.54 0 345.32 338.96 46947 +1910 246 18.53 12.53 16.88 0 470.47 324.34 46747 +1910 247 18.5 12.5 16.85 0.05 469.67 241.93 46547 +1910 248 19.26 13.26 17.61 0 490.26 318.52 46347 +1910 249 18.55 12.55 16.9 0 471 318.44 46146 +1910 250 20.22 14.22 18.57 0.02 517.36 233.82 45945 +1910 251 19 13 17.35 0.12 483.13 234.88 45743 +1910 252 15.79 9.79 14.14 0.18 402.14 239.3 45541 +1910 253 16.12 10.12 14.47 0.9 409.89 237.13 45339 +1910 254 13.35 7.35 11.7 0.75 348.61 239.92 45136 +1910 255 14.46 8.46 12.81 1.47 372.15 236.52 44933 +1910 256 17.01 11.01 15.36 0.07 431.44 230.55 44730 +1910 257 19.09 13.09 17.44 0.87 485.59 224.98 44527 +1910 258 18.81 12.81 17.16 0 477.98 298.4 44323 +1910 259 16.28 10.28 14.63 0.06 413.7 226.61 44119 +1910 260 15.47 9.47 13.82 1.9 394.74 226.15 43915 +1910 261 17.31 11.31 15.66 0 438.92 294.94 43711 +1910 262 18.16 12.16 16.51 0.37 460.7 217.9 43507 +1910 263 18.01 12.01 16.36 0.33 456.79 216.35 43303 +1910 264 22.4 16.4 20.75 0.28 583.66 205.39 43099 +1910 265 21.62 15.62 19.97 0.2 559.15 205.46 42894 +1910 266 15.87 9.87 14.22 0.68 404.01 214.45 42690 +1910 267 12.9 6.9 11.25 0 339.43 288.96 42486 +1910 268 16.2 10.2 14.55 0 411.79 280.01 42282 +1910 269 19.57 13.57 17.92 0.14 498.88 202.25 42078 +1910 270 12.17 6.17 10.52 0.55 324.99 211.78 41875 +1910 271 13.48 7.48 11.83 0.58 351.3 208.12 41671 +1910 272 15.65 9.65 14 0.61 398.89 203.01 41468 +1910 273 11.07 5.07 9.42 0 304.21 276.1 41265 +1910 274 9.4 3.4 7.75 0 274.85 275.75 41062 +1910 275 10.82 4.82 9.17 0 299.65 270.94 40860 +1910 276 8.82 2.82 7.17 0 265.24 270.92 40658 +1910 277 7.93 1.93 6.28 0.01 251.05 201.97 40456 +1910 278 8.1 2.1 6.45 0 253.71 266.16 40255 +1910 279 15.63 9.63 13.98 0 398.43 251.85 40054 +1910 280 19.93 13.93 18.28 0 509.04 240.07 39854 +1910 281 17.53 11.53 15.88 0 444.47 242.81 39654 +1910 282 18.28 12.28 16.63 0.32 463.85 178.91 39455 +1910 283 17.72 11.72 16.07 0.16 449.31 177.74 39256 +1910 284 17.62 11.62 15.97 0 446.76 234.24 39058 +1910 285 17.4 11.4 15.75 0 441.18 232.11 38861 +1910 286 15.65 9.65 14 0 398.89 232.71 38664 +1910 287 14.01 8.01 12.36 0 362.45 232.58 38468 +1910 288 12.32 6.32 10.67 0 327.91 232.37 38273 +1910 289 15.73 9.73 14.08 0 400.75 224.34 38079 +1910 290 16.96 10.96 15.31 0.08 430.2 164.49 37885 +1910 291 15.15 9.15 13.5 0 387.46 219.86 37693 +1910 292 13.59 7.59 11.94 0.02 353.59 164.75 37501 +1910 293 10.83 4.83 9.18 0 299.83 220.73 37311 +1910 294 12.85 6.85 11.2 0 338.42 215.16 37121 +1910 295 14.53 8.53 12.88 0 373.68 209.87 36933 +1910 296 13.41 7.41 11.76 0.08 349.85 156.74 36745 +1910 297 13.89 7.89 12.24 0.07 359.9 154.2 36560 +1910 298 15.15 9.15 13.5 0.31 387.46 150.85 36375 +1910 299 14.17 8.17 12.52 0.78 365.87 149.91 36191 +1910 300 14.21 8.21 12.56 0 366.73 197.2 36009 +1910 301 14.53 8.53 12.88 0 373.68 194.26 35829 +1910 302 11.75 5.75 10.1 0 316.91 195.4 35650 +1910 303 7.64 1.64 5.99 0 246.57 197.24 35472 +1910 304 6.24 0.24 4.59 0 225.9 196 35296 +1910 305 -0.9 -6.9 -2.55 1.13 142.04 189.2 35122 +1910 306 -0.93 -6.93 -2.58 0.51 141.76 189.07 34950 +1910 307 3.57 -2.43 1.92 1.37 190.57 184.9 34779 +1910 308 2.63 -3.37 0.98 0.3 179.33 183.28 34610 +1910 309 -2.85 -8.85 -4.5 0.01 124.48 183.95 34444 +1910 310 -2.7 -8.7 -4.35 0.78 125.76 184.4 34279 +1910 311 -2.75 -8.75 -4.4 0.46 125.33 184.24 34116 +1910 312 3.76 -2.24 2.11 0.16 192.92 179.32 33956 +1910 313 6.42 0.42 4.77 0 228.47 219.16 33797 +1910 314 9 3 7.35 0.02 268.19 171.7 33641 +1910 315 3.83 -2.17 2.18 0.22 193.79 172.58 33488 +1910 316 3.52 -2.48 1.87 0.51 189.96 170.85 33337 +1910 317 1.65 -4.35 0 0.01 168.21 170.02 33188 +1910 318 6.15 0.15 4.5 0.37 224.62 165.5 33042 +1910 319 7.6 1.6 5.95 0.01 245.96 162.64 32899 +1910 320 4.76 -1.24 3.11 0.1 205.68 162.4 32758 +1910 321 6.98 0.98 5.33 0 236.63 198.06 32620 +1910 322 9.96 3.96 8.31 0 284.41 152.17 32486 +1910 323 13.56 7.56 11.91 0 352.96 146.91 32354 +1910 324 14.7 8.7 13.05 0 377.42 143.58 32225 +1910 325 16.41 10.41 14.76 0.06 416.81 104.82 32100 +1910 326 13.23 7.23 11.58 1.62 346.14 106.64 31977 +1910 327 10.46 4.46 8.81 1.29 293.19 107.36 31858 +1910 328 11.76 5.76 10.11 1.7 317.1 104.98 31743 +1910 329 14.29 8.29 12.64 0.83 368.46 101.89 31631 +1910 330 12.51 6.51 10.86 0 331.65 136.35 31522 +1910 331 13.18 7.18 11.53 0.03 345.12 100.79 31417 +1910 332 9.37 3.37 7.72 0 274.35 136.32 31316 +1910 333 9.51 3.51 7.86 0 276.71 135.14 31218 +1910 334 10.59 4.59 8.94 0.22 295.51 99.85 31125 +1910 335 12.97 6.97 11.32 0 340.85 129.75 31035 +1910 336 10.18 4.18 8.53 0.27 288.25 98.47 30949 +1910 337 8.1 2.1 6.45 0 253.71 131.29 30867 +1910 338 9.25 3.25 7.6 0.76 272.34 97.11 30790 +1910 339 6.83 0.83 5.18 0.61 234.42 97.85 30716 +1910 340 2.01 -3.99 0.36 0 172.22 132.52 30647 +1910 341 2.69 -3.31 1.04 0 180.03 131.26 30582 +1910 342 3.83 -2.17 2.18 0.01 193.79 97.42 30521 +1910 343 4.75 -1.25 3.1 0 205.55 128.55 30465 +1910 344 8.41 2.41 6.76 0 258.62 125.03 30413 +1910 345 7.3 1.3 5.65 0 241.41 125.39 30366 +1910 346 4.79 -1.21 3.14 0.01 206.07 94.81 30323 +1910 347 7.24 1.24 5.59 0 240.5 124.3 30284 +1910 348 5.46 -0.54 3.81 0 215.04 125.08 30251 +1910 349 9.56 3.56 7.91 0 277.55 121.9 30221 +1910 350 9.38 3.38 7.73 0 274.51 121.71 30197 +1910 351 6.83 0.83 5.18 0 234.42 123.3 30177 +1910 352 3.86 -2.14 2.21 0 194.16 124.96 30162 +1910 353 2.4 -3.6 0.75 0.08 176.66 94.23 30151 +1910 354 5.46 -0.54 3.81 0 215.04 123.96 30145 +1910 355 7.94 1.94 6.29 0 251.21 122.36 30144 +1910 356 10.48 4.48 8.83 0 293.55 120.46 30147 +1910 357 6.31 0.31 4.66 0 226.89 123.52 30156 +1910 358 8.01 2.01 6.36 0 252.3 122.48 30169 +1910 359 10.34 4.34 8.69 0.38 291.06 90.62 30186 +1910 360 8.44 2.44 6.79 0.47 259.1 91.99 30208 +1910 361 7.44 1.44 5.79 0 243.52 123.68 30235 +1910 362 7.54 1.54 5.89 0 245.04 124.04 30267 +1910 363 5.86 -0.14 4.21 0 220.55 125.72 30303 +1910 364 3.61 -2.39 1.96 0.12 191.06 95.55 30343 +1910 365 3.7 -2.3 2.05 0.35 192.17 95.94 30388 +1911 1 -0.74 -6.74 -2.39 0 143.57 130.9 30438 +1911 2 2.5 -3.5 0.85 0 177.82 130.18 30492 +1911 3 -2.89 -8.89 -4.54 0 124.14 133.4 30551 +1911 4 -5.98 -11.98 -7.63 0.08 100.21 144.84 30614 +1911 5 -3.27 -9.27 -4.92 0 120.95 178.39 30681 +1911 6 -4.05 -10.05 -5.7 0.04 114.63 145.51 30752 +1911 7 0.43 -5.57 -1.22 0 155.21 178.5 30828 +1911 8 4.76 -1.24 3.11 0.01 205.68 100.96 30907 +1911 9 5.08 -0.92 3.43 0 209.91 135.67 30991 +1911 10 6.1 0.1 4.45 1.08 223.91 102.24 31079 +1911 11 7.56 1.56 5.91 2.19 245.35 102.21 31171 +1911 12 2.82 -3.18 1.17 0.22 181.55 105.2 31266 +1911 13 -0.71 -6.71 -2.36 0.01 143.86 149.81 31366 +1911 14 -4.17 -10.17 -5.82 0 113.69 188.39 31469 +1911 15 -3.76 -9.76 -5.41 0 116.95 189.58 31575 +1911 16 -4.98 -10.98 -6.63 0 107.47 191.16 31686 +1911 17 -2.1 -8.1 -3.75 0 131 191.67 31800 +1911 18 4.61 -1.39 2.96 0 203.72 148.63 31917 +1911 19 3.83 -2.17 2.18 0 193.79 151.04 32038 +1911 20 6.89 0.89 5.24 0 235.3 150.56 32161 +1911 21 4.23 -1.77 2.58 0 198.83 154.39 32289 +1911 22 1.11 -4.89 -0.54 0 162.35 157.93 32419 +1911 23 -1.75 -7.75 -3.4 0 134.14 161.07 32552 +1911 24 1.18 -4.82 -0.47 0 163.1 161.75 32688 +1911 25 6.76 0.76 5.11 0 233.39 160.06 32827 +1911 26 6.14 0.14 4.49 0 224.48 162.44 32969 +1911 27 3.06 -2.94 1.41 0.05 184.4 124.91 33114 +1911 28 1.52 -4.48 -0.13 0 166.78 169.67 33261 +1911 29 3.35 -2.65 1.7 0 187.89 170.96 33411 +1911 30 0.18 -5.82 -1.47 0 152.66 175.04 33564 +1911 31 1.33 -4.67 -0.32 0 164.72 176.81 33718 +1911 32 0.81 -5.19 -0.84 0.14 159.17 134.42 33875 +1911 33 -0.03 -6.03 -1.68 0 150.54 182.34 34035 +1911 34 -0.46 -6.46 -2.11 0 146.29 184.79 34196 +1911 35 5.51 -0.49 3.86 0 215.72 183.14 34360 +1911 36 6.79 0.79 5.14 0 233.83 184.61 34526 +1911 37 6.88 0.88 5.23 0 235.16 186.94 34694 +1911 38 7.87 1.87 6.22 0 250.12 188.77 34863 +1911 39 6.22 0.22 4.57 0.16 225.61 144.61 35035 +1911 40 0.69 -5.31 -0.96 0 157.91 199.36 35208 +1911 41 5.91 -0.09 4.26 0.29 221.25 148.72 35383 +1911 42 5.13 -0.87 3.48 0.16 210.58 151.11 35560 +1911 43 3.99 -2.01 2.34 0 195.79 205.08 35738 +1911 44 3.96 -2.04 2.31 0 195.41 207.67 35918 +1911 45 3.34 -2.66 1.69 0 187.77 210.77 36099 +1911 46 0.06 -5.94 -1.59 0.26 151.45 161.74 36282 +1911 47 -0.72 -6.72 -2.37 0.1 143.77 200.69 36466 +1911 48 -1.23 -7.23 -2.88 0 138.93 258.38 36652 +1911 49 -1.21 -7.21 -2.86 0 139.11 261 36838 +1911 50 3.73 -2.27 2.08 0 192.55 224.29 37026 +1911 51 0.48 -5.52 -1.17 0 155.73 229.6 37215 +1911 52 -2.42 -8.42 -4.07 0 128.18 234.17 37405 +1911 53 1.43 -4.57 -0.22 0 165.8 234.82 37596 +1911 54 2.89 -3.11 1.24 0 182.38 236.52 37788 +1911 55 3.33 -2.67 1.68 0 187.64 239.19 37981 +1911 56 1.03 -4.97 -0.62 0 161.49 243.63 38175 +1911 57 3.91 -2.09 2.26 0 194.79 244.32 38370 +1911 58 8.37 2.37 6.72 0 257.98 242.82 38565 +1911 59 10.39 4.39 8.74 0 291.95 243.02 38761 +1911 60 15.8 9.8 14.15 0 402.38 237.41 38958 +1911 61 12.89 6.89 11.24 0 339.23 245.16 39156 +1911 62 14.41 8.41 12.76 0 371.06 245.4 39355 +1911 63 12.2 6.2 10.55 0.02 325.57 188.92 39553 +1911 64 11.84 5.84 10.19 0.14 318.63 191.46 39753 +1911 65 9.99 3.99 8.34 0.12 284.93 195.56 39953 +1911 66 9.85 3.85 8.2 0.22 282.51 197.74 40154 +1911 67 5.34 -0.66 3.69 0.31 213.41 203.87 40355 +1911 68 3.43 -2.57 1.78 0.7 188.86 207.42 40556 +1911 69 3.43 -2.57 1.78 0 188.86 279.21 40758 +1911 70 3.76 -2.24 2.11 0.2 192.92 211.34 40960 +1911 71 5 -1 3.35 0.14 208.85 212.63 41163 +1911 72 7.87 1.87 6.22 0 250.12 283.1 41366 +1911 73 9.69 3.69 8.04 0 279.77 283.35 41569 +1911 74 11.25 5.25 9.6 0 307.53 283.77 41772 +1911 75 7.32 1.32 5.67 0 241.71 291.92 41976 +1911 76 6.84 0.84 5.19 0.01 234.57 221.36 42179 +1911 77 8.03 2.03 6.38 0 252.61 296.27 42383 +1911 78 6.81 0.81 5.16 0 234.13 300.47 42587 +1911 79 6.88 0.88 5.23 0.27 235.16 227.35 42791 +1911 80 5.06 -0.94 3.41 0 209.65 307.79 42996 +1911 81 4.27 -1.73 2.62 0 199.34 311.24 43200 +1911 82 7.51 1.51 5.86 0.02 244.59 232.6 43404 +1911 83 9.67 3.67 8.02 0 279.43 309.62 43608 +1911 84 11.53 5.53 9.88 0 312.76 309.19 43812 +1911 85 8.03 2.03 6.38 0.01 252.61 237.75 44016 +1911 86 8.85 2.85 7.2 0 265.73 318.26 44220 +1911 87 6.89 0.89 5.24 0.1 235.3 242.61 44424 +1911 88 6.86 0.86 5.21 0 234.86 325.89 44627 +1911 89 5.15 -0.85 3.5 0.19 210.85 247.72 44831 +1911 90 3.07 -2.93 1.42 0.41 184.52 251.22 45034 +1911 91 7.99 1.99 6.34 0 251.99 331.32 45237 +1911 92 9.31 3.31 7.66 0 273.34 331.63 45439 +1911 93 9.38 3.38 7.73 0.05 274.51 250.31 45642 +1911 94 15.8 9.8 14.15 0.27 402.38 242.73 45843 +1911 95 15.35 9.35 13.7 0 392 326.76 46045 +1911 96 15.27 9.27 13.62 0.38 390.18 246.76 46246 +1911 97 9.06 3.06 7.41 0.07 269.18 257.07 46446 +1911 98 9.8 3.8 8.15 0.21 281.65 257.66 46647 +1911 99 12.45 6.45 10.8 0 330.46 340.85 46846 +1911 100 10.62 4.62 8.97 0 296.05 346.15 47045 +1911 101 11.56 5.56 9.91 0.33 313.32 259.8 47243 +1911 102 10.97 4.97 9.32 0 302.38 349.38 47441 +1911 103 11.45 5.45 9.8 0 311.26 350.35 47638 +1911 104 10.41 4.41 8.76 0 292.3 354.05 47834 +1911 105 13.03 7.03 11.38 0 342.06 350.89 48030 +1911 106 10.46 4.46 8.81 0 293.19 357.42 48225 +1911 107 10.16 4.16 8.51 0.02 287.9 269.72 48419 +1911 108 14.72 8.72 13.07 0.79 377.86 264.19 48612 +1911 109 12.22 6.22 10.57 0.21 325.96 269.39 48804 +1911 110 13.23 7.23 11.58 0 346.14 358.53 48995 +1911 111 14.6 8.6 12.95 0 375.22 357.05 49185 +1911 112 16.81 10.81 15.16 0.15 426.52 264.84 49374 +1911 113 14.88 8.88 13.23 0.09 381.41 269.43 49561 +1911 114 13.53 7.53 11.88 0 352.34 363.78 49748 +1911 115 14.02 8.02 12.37 0 362.66 364.12 49933 +1911 116 13.4 7.4 11.75 0 349.64 366.71 50117 +1911 117 16.31 10.31 14.66 0 414.42 361.1 50300 +1911 118 15.64 9.64 13.99 0 398.66 364.11 50481 +1911 119 13.6 7.6 11.95 0 353.8 370.09 50661 +1911 120 10.15 4.15 8.5 0.16 287.72 283.64 50840 +1911 121 16.36 10.36 14.71 0.34 415.61 274.29 51016 +1911 122 18.56 12.56 16.91 0 471.27 360.73 51191 +1911 123 19.01 13.01 17.36 0.28 483.41 270.28 51365 +1911 124 20.21 14.21 18.56 0.75 517.07 268.2 51536 +1911 125 19.91 13.91 18.26 0.72 508.47 269.66 51706 +1911 126 18.11 12.11 16.46 2.93 459.4 274.56 51874 +1911 127 19.53 13.53 17.88 0 497.76 362.6 52039 +1911 128 19.1 13.1 17.45 0.23 485.86 273.7 52203 +1911 129 14.64 8.64 12.99 0.23 376.1 283.53 52365 +1911 130 11.67 5.67 10.02 0.76 315.4 289.05 52524 +1911 131 15.68 9.68 14.03 0 399.59 377.05 52681 +1911 132 18.44 12.44 16.79 0 468.08 370.16 52836 +1911 133 15.93 9.93 14.28 0.85 405.42 283.45 52989 +1911 134 16.25 10.25 14.6 0.44 412.98 283.34 53138 +1911 135 17.9 11.9 16.25 0.28 453.94 280.39 53286 +1911 136 16.95 10.95 15.3 0.63 429.96 282.91 53430 +1911 137 18.35 12.35 16.7 0.47 465.7 280.38 53572 +1911 138 13.73 7.73 12.08 0.61 356.52 290.04 53711 +1911 139 11.01 5.01 9.36 0.23 303.11 294.91 53848 +1911 140 11.2 5.2 9.55 0.47 306.61 295 53981 +1911 141 11.98 5.98 10.33 0 321.31 392.2 54111 +1911 142 13.45 7.45 11.8 0.19 350.68 292.13 54238 +1911 143 12.93 6.93 11.28 0 340.04 391.21 54362 +1911 144 12.96 6.96 11.31 0.42 340.64 293.73 54483 +1911 145 15.29 9.29 13.64 0 390.64 386.56 54600 +1911 146 22.04 16.04 20.39 0.02 572.24 274.37 54714 +1911 147 22.52 16.52 20.87 0 587.51 364.45 54824 +1911 148 25.04 19.04 23.39 0 673.47 354.33 54931 +1911 149 20.06 14.06 18.41 0.01 512.76 280.53 55034 +1911 150 19.51 13.51 17.86 1.48 497.2 282.15 55134 +1911 151 16.57 10.57 14.92 0.84 420.67 289.09 55229 +1911 152 18.29 12.29 16.64 0 464.12 380.56 55321 +1911 153 18.73 12.73 17.08 0.1 475.82 284.58 55409 +1911 154 16.18 10.18 14.53 0.86 411.32 290.4 55492 +1911 155 16.75 10.75 15.1 0.41 425.05 289.37 55572 +1911 156 14.67 8.67 13.02 0.47 376.76 293.72 55648 +1911 157 14.42 8.42 12.77 0.03 371.28 294.31 55719 +1911 158 15.3 9.3 13.65 0 390.86 390.39 55786 +1911 159 13.4 7.4 11.75 0 349.64 395.26 55849 +1911 160 15.05 9.05 13.4 0.04 385.21 293.6 55908 +1911 161 20.46 14.46 18.81 0 524.33 375.38 55962 +1911 162 23.03 17.03 21.38 0 604.11 365.83 56011 +1911 163 25.85 19.85 24.2 0.98 703.26 265.34 56056 +1911 164 21.18 15.18 19.53 0.12 545.72 279.86 56097 +1911 165 20.18 14.18 18.53 0.13 516.2 282.57 56133 +1911 166 19.28 13.28 17.63 0 490.81 379.84 56165 +1911 167 18.74 12.74 17.09 0.11 476.09 286.14 56192 +1911 168 20.17 14.17 18.52 0.02 515.92 282.67 56214 +1911 169 18.77 12.77 17.12 0.07 476.9 286.13 56231 +1911 170 19.61 13.61 17.96 0.62 500 284.1 56244 +1911 171 16.69 10.69 15.04 0.09 423.59 290.82 56252 +1911 172 21.42 15.42 19.77 0 553.01 372.53 56256 +1911 173 21.42 15.42 19.77 0 553.01 372.51 56255 +1911 174 23.7 17.7 22.05 0 626.52 363.5 56249 +1911 175 26.1 20.1 24.45 0 712.68 352.78 56238 +1911 176 27.1 21.1 25.45 0.42 751.43 260.89 56223 +1911 177 23.81 17.81 22.16 0.02 630.27 272.16 56203 +1911 178 22.18 16.18 20.53 0 576.65 369.44 56179 +1911 179 23.53 17.53 21.88 0 620.77 363.97 56150 +1911 180 22.35 16.35 20.7 0 582.06 368.56 56116 +1911 181 17.75 11.75 16.1 0.78 450.08 288.11 56078 +1911 182 22.85 16.85 21.2 0 598.2 366.39 56035 +1911 183 24.93 18.93 23.28 0.03 669.5 268.1 55987 +1911 184 25.46 19.46 23.81 0.08 688.78 266.19 55935 +1911 185 26.22 20.22 24.57 1.61 717.24 263.47 55879 +1911 186 27.23 21.23 25.58 0.05 756.6 259.57 55818 +1911 187 26.45 20.45 24.8 0 726.05 349.76 55753 +1911 188 26.72 20.72 25.07 0 736.5 348.19 55684 +1911 189 26.67 20.67 25.02 0 734.56 348.27 55611 +1911 190 27.71 21.71 26.06 0 775.93 342.69 55533 +1911 191 27.65 21.65 26 0 773.49 342.75 55451 +1911 192 23.12 17.12 21.47 0 607.08 363.11 55366 +1911 193 17.27 11.27 15.62 0 437.91 382.84 55276 +1911 194 16.54 10.54 14.89 0 419.95 384.66 55182 +1911 195 19.66 13.66 18.01 0 501.4 374.96 55085 +1911 196 19.19 13.19 17.54 0 488.33 376.08 54984 +1911 197 16.7 10.7 15.05 0.09 423.83 287.29 54879 +1911 198 19.36 13.36 17.71 0.15 493.03 280.99 54770 +1911 199 19.33 13.33 17.68 0 492.19 374.39 54658 +1911 200 17.46 11.46 15.81 0 442.7 379.7 54542 +1911 201 18.9 12.9 17.25 0.02 480.41 281.16 54423 +1911 202 22.98 16.98 21.33 0 602.46 359.9 54301 +1911 203 23.51 17.51 21.86 0 620.09 357.28 54176 +1911 204 25.42 19.42 23.77 0.28 687.31 261.46 54047 +1911 205 24.14 18.14 22.49 0 641.62 353.68 53915 +1911 206 24.48 18.48 22.83 0 653.5 351.7 53780 +1911 207 25.25 19.25 23.6 0 681.09 347.7 53643 +1911 208 31.93 25.93 30.28 0 964.61 311.35 53502 +1911 209 30.3 24.3 28.65 0 887.61 320.67 53359 +1911 210 29.29 23.29 27.64 0 842.55 325.83 53213 +1911 211 31.22 25.22 29.57 0 930.41 313.93 53064 +1911 212 32.06 26.06 30.41 0 970.99 308 52913 +1911 213 33.59 27.59 31.94 1.15 1048.73 222.94 52760 +1911 214 31.36 25.36 29.71 0 937.07 311.02 52604 +1911 215 29.94 23.94 28.29 0.03 871.32 239.08 52445 +1911 216 24.86 18.86 23.21 1.14 666.99 257.22 52285 +1911 217 23.7 17.7 22.05 0.4 626.52 260.2 52122 +1911 218 22.85 16.85 21.2 0.33 598.2 262.1 51958 +1911 219 24.18 18.18 22.53 0 643.01 343.17 51791 +1911 220 19.12 13.12 17.47 0.02 486.41 270.28 51622 +1911 221 17.95 11.95 16.3 0 455.24 362.86 51451 +1911 222 19.63 13.63 17.98 0 500.56 356.72 51279 +1911 223 19.83 13.83 18.18 0.02 506.2 266.21 51105 +1911 224 21.31 15.31 19.66 0.17 549.66 261.72 50929 +1911 225 20.01 14.01 18.36 0 511.32 352.16 50751 +1911 226 24.68 18.68 23.03 0.09 660.57 250.41 50572 +1911 227 24.48 18.48 22.83 0.4 653.5 250.11 50392 +1911 228 24.84 18.84 23.19 0 666.28 330.82 50210 +1911 229 25.9 19.9 24.25 0 705.14 325.08 50026 +1911 230 23.32 17.32 21.67 0.04 613.72 250.85 49842 +1911 231 22.76 16.76 21.11 0 595.27 335.14 49656 +1911 232 25.71 19.71 24.06 0.07 698.04 241.52 49469 +1911 233 27.45 21.45 25.8 0.49 765.41 234.6 49280 +1911 234 24.91 18.91 23.26 0 668.79 322.7 49091 +1911 235 26.13 20.13 24.48 0 713.82 316.09 48900 +1911 236 24.46 18.46 22.81 0 652.79 321.74 48709 +1911 237 21.66 15.66 20.01 0 560.39 330.48 48516 +1911 238 23.74 17.74 22.09 0.73 627.88 241.01 48323 +1911 239 21.7 15.7 20.05 0.05 561.62 245.42 48128 +1911 240 20.15 14.15 18.5 0.06 515.34 247.88 47933 +1911 241 20.13 14.13 18.48 0 514.76 328.86 47737 +1911 242 22.94 16.94 21.29 0 601.15 317.8 47541 +1911 243 24.98 18.98 23.33 0 671.3 308.28 47343 +1911 244 20.39 14.39 18.74 0 522.29 322.69 47145 +1911 245 20.68 14.68 19.03 0.04 530.79 239.98 46947 +1911 246 19.6 13.6 17.95 0 499.72 321.3 46747 +1911 247 14.06 8.06 12.41 0 363.52 333.25 46547 +1911 248 14.69 8.69 13.04 1.41 377.2 247.44 46347 +1911 249 11.72 5.72 10.07 0.1 316.34 250.28 46146 +1911 250 16.17 10.17 14.52 0.15 411.08 241.88 45945 +1911 251 15.87 9.87 14.22 0 404.01 321.07 45743 +1911 252 19.49 13.49 17.84 0 496.64 309.66 45541 +1911 253 23.48 17.48 21.83 0 619.08 295 45339 +1911 254 25.92 19.92 24.27 0 705.89 283.84 45136 +1911 255 21.53 15.53 19.88 0.04 556.38 222.93 44933 +1911 256 21.83 15.83 20.18 0.74 565.66 220.57 44730 +1911 257 18.1 12.1 16.45 0.93 459.14 226.92 44527 +1911 258 18.13 12.13 16.48 0.06 459.92 225.11 44323 +1911 259 21.39 15.39 19.74 0 552.1 288.74 44119 +1911 260 20.42 14.42 18.77 0.25 523.16 216.95 43915 +1911 261 20.22 14.22 18.57 0 517.36 287.44 43711 +1911 262 20.63 14.63 18.98 0 529.31 283.98 43507 +1911 263 22.51 16.51 20.86 0.04 587.18 206.98 43303 +1911 264 22.11 16.11 20.46 0.03 574.44 206.06 43099 +1911 265 23.87 17.87 22.22 0.82 632.32 200.15 42894 +1911 266 19.22 13.22 17.57 0 489.16 278.14 42690 +1911 267 21.26 15.26 19.61 0 548.14 270.02 42486 +1911 268 17.65 11.65 16 0.06 447.52 207.6 42282 +1911 269 16.72 10.72 15.07 0.43 424.32 207.3 42078 +1911 270 16.68 10.68 15.03 0 423.34 273.87 41875 +1911 271 20.66 14.66 19.01 0 530.2 261.72 41671 +1911 272 18.85 12.85 17.2 0 479.06 263.67 41468 +1911 273 16.16 10.16 14.51 0 410.84 267.14 41265 +1911 274 8.31 2.31 6.66 0 257.03 277.16 41062 +1911 275 11.54 5.54 9.89 0.47 312.94 202.4 40860 +1911 276 8.45 2.45 6.8 0.83 259.26 203.54 40658 +1911 277 9.82 3.82 8.17 0 282 266.89 40456 +1911 278 8.75 2.75 7.1 0.06 264.1 199.02 40255 +1911 279 10.4 4.4 8.75 0 292.12 260.33 40054 +1911 280 11.5 5.5 9.85 0.02 312.19 192.07 39854 +1911 281 12.5 6.5 10.85 1.34 331.45 188.89 39654 +1911 282 12.11 6.11 10.46 0.03 323.82 187.27 39455 +1911 283 13.09 7.09 11.44 0 343.28 245.36 39256 +1911 284 13.37 7.37 11.72 0.7 349.02 181.42 39058 +1911 285 13.69 7.69 12.04 0.07 355.68 179.07 38861 +1911 286 16.14 10.14 14.49 0 410.37 231.82 38664 +1911 287 13.95 7.95 12.3 0.14 361.17 174.5 38468 +1911 288 13.94 7.94 12.29 0.03 360.96 172.44 38273 +1911 289 10.86 4.86 9.21 0.29 300.38 173.8 38079 +1911 290 10.74 4.74 9.09 0.35 298.21 171.75 37885 +1911 291 10.7 4.7 9.05 0 297.48 226.34 37693 +1911 292 13.34 7.34 11.69 0 348.4 220.04 37501 +1911 293 15.4 9.4 13.75 0.07 393.14 160.59 37311 +1911 294 13.35 7.35 11.7 0.4 348.61 160.83 37121 +1911 295 14.5 8.5 12.85 0.09 373.03 157.44 36933 +1911 296 15.43 9.43 13.78 0.03 393.83 154.44 36745 +1911 297 10.05 4.05 8.4 0.26 285.98 157.94 36560 +1911 298 9.08 3.08 7.43 0 269.51 209.05 36375 +1911 299 13.06 7.06 11.41 0 342.67 201.44 36191 +1911 300 16.5 10.5 14.85 0 418.98 193.65 36009 +1911 301 21.79 15.79 20.14 1.03 564.42 135.78 35829 +1911 302 21.65 15.65 20 0.27 560.08 134.18 35650 +1911 303 21.64 15.64 19.99 0 559.77 176.52 35472 +1911 304 21.06 15.06 19.41 0.54 542.1 131.59 35296 +1911 305 15.87 9.87 14.22 0.2 404.01 136.58 35122 +1911 306 14.92 8.92 13.27 0.02 382.3 135.99 34950 +1911 307 14.69 8.69 13.04 0 377.2 179.2 34779 +1911 308 9.63 3.63 7.98 0 278.74 182.68 34610 +1911 309 9.13 3.13 7.48 0.71 270.34 135.65 34444 +1911 310 7.6 1.6 5.95 0.01 245.96 134.88 34279 +1911 311 5.23 -0.77 3.58 0 211.92 179.56 34116 +1911 312 8.24 2.24 6.59 0.03 255.92 130.83 33956 +1911 313 10.37 4.37 8.72 0.12 291.59 127.72 33797 +1911 314 7.18 1.18 5.53 0 239.61 171.27 33641 +1911 315 7.15 1.15 5.5 0.5 239.16 126.57 33488 +1911 316 3.53 -2.47 1.88 0.61 190.08 126.89 33337 +1911 317 8.81 2.81 7.16 0.01 265.08 122.23 33188 +1911 318 11.37 5.37 9.72 0 309.76 158.19 33042 +1911 319 12.59 6.59 10.94 0 333.23 155.22 32899 +1911 320 10.97 4.97 9.32 0.13 302.38 116.32 32758 +1911 321 10.37 4.37 8.72 0 291.59 153.59 32620 +1911 322 10.82 4.82 9.17 0 299.65 151.36 32486 +1911 323 10.58 4.58 8.93 0 295.33 150 32354 +1911 324 10.21 4.21 8.56 0 288.77 148.32 32225 +1911 325 13.35 7.35 11.7 0 348.61 143.47 32100 +1911 326 12.78 6.78 11.13 0 337.02 142.67 31977 +1911 327 12.21 6.21 10.56 0 325.76 141.46 31858 +1911 328 11.27 5.27 9.62 0 307.9 140.44 31743 +1911 329 9.67 3.67 8.02 0 279.43 140.42 31631 +1911 330 9.82 3.82 8.17 0 282 138.86 31522 +1911 331 7.09 1.09 5.44 0 238.26 139.7 31417 +1911 332 9.12 3.12 7.47 0 270.17 136.53 31316 +1911 333 8.7 2.7 7.05 0 263.29 135.79 31218 +1911 334 11.04 5.04 9.39 0 303.66 132.74 31125 +1911 335 8.02 2.02 6.37 0 252.46 134.06 31035 +1911 336 4.95 -1.05 3.3 0 208.18 135.06 30949 +1911 337 8.13 2.13 6.48 0 254.18 131.27 30867 +1911 338 9.56 3.56 7.91 0 277.55 129.23 30790 +1911 339 8.25 2.25 6.6 0 256.08 129.47 30716 +1911 340 6.89 0.89 5.24 0.02 235.3 97.28 30647 +1911 341 3.96 -2.04 2.31 0.18 195.41 97.94 30582 +1911 342 2.7 -3.3 1.05 1.29 180.14 97.87 30521 +1911 343 -0.09 -6.09 -1.74 1.34 149.94 145.76 30465 +1911 344 -1.58 -7.58 -3.23 0.5 135.69 147.02 30413 +1911 345 0.8 -5.2 -0.85 0.98 159.06 145.93 30366 +1911 346 0.12 -5.88 -1.53 0.33 152.05 145.78 30323 +1911 347 -1.25 -7.25 -2.9 0 138.74 177.98 30284 +1911 348 0.02 -5.98 -1.63 0 151.05 177.17 30251 +1911 349 2.01 -3.99 0.36 0 172.22 175.68 30221 +1911 350 -1.9 -7.9 -3.55 0 132.78 177.02 30197 +1911 351 4.28 -1.72 2.63 0 199.47 173.46 30177 +1911 352 7.37 1.37 5.72 0 242.46 170.52 30162 +1911 353 7.69 1.69 6.04 0 247.34 169.22 30151 +1911 354 5.69 -0.31 4.04 0 218.19 169.73 30145 +1911 355 8.1 2.1 6.45 0 253.71 167.07 30144 +1911 356 11.42 5.42 9.77 0 310.69 119.67 30147 +1911 357 8.62 2.62 6.97 0.02 261.99 91.47 30156 +1911 358 11.28 5.28 9.63 0 308.09 119.93 30169 +1911 359 10.12 4.12 8.47 0 287.2 121.01 30186 +1911 360 13.04 7.04 11.39 0 342.26 118.8 30208 +1911 361 13.06 7.06 11.41 0 342.67 119.1 30235 +1911 362 8.89 2.89 7.24 0.01 266.38 92.31 30267 +1911 363 7.4 1.4 5.75 0 242.92 124.72 30303 +1911 364 7.58 1.58 5.93 0 245.65 124.98 30343 +1911 365 2.3 -3.7 0.65 0.51 175.51 96.49 30388 +1912 1 -4.56 -10.56 -6.21 1.36 110.66 146.84 30438 +1912 2 -2.86 -8.86 -4.51 0 124.39 180 30492 +1912 3 -1.57 -7.57 -3.22 0 135.78 180.4 30551 +1912 4 -2.1 -8.1 -3.75 0 131 181.42 30614 +1912 5 -6.72 -12.72 -8.37 0.25 95.12 150.19 30681 +1912 6 -6.69 -12.69 -8.34 0 95.32 185.02 30752 +1912 7 -9.97 -15.97 -11.62 0 75.31 186.5 30828 +1912 8 -7.3 -13.3 -8.95 0 91.28 187.26 30907 +1912 9 -6.43 -12.43 -8.08 0.39 97.09 154.24 30991 +1912 10 -4.44 -10.44 -6.09 0 111.58 189.97 31079 +1912 11 -3.35 -9.35 -5 0 120.29 190.47 31171 +1912 12 -1.49 -7.49 -3.14 0 136.51 190.64 31266 +1912 13 3.17 -2.83 1.52 0.66 185.71 154.07 31366 +1912 14 6.67 0.67 5.02 0 232.08 187.77 31469 +1912 15 3.64 -2.36 1.99 0 191.43 190.52 31575 +1912 16 5.32 -0.68 3.67 0.01 213.14 153.78 31686 +1912 17 3.18 -2.82 1.53 0.38 185.83 155.46 31800 +1912 18 3.97 -2.03 2.32 0 195.54 193.12 31917 +1912 19 6.95 0.95 5.3 0 236.19 192 32038 +1912 20 5.37 -0.63 3.72 0.06 213.82 155.95 32161 +1912 21 7.45 1.45 5.8 0.07 243.67 155.21 32289 +1912 22 7.24 1.24 5.59 0 240.5 154.02 32419 +1912 23 4.93 -1.07 3.28 0.05 207.92 118.08 32552 +1912 24 4.53 -1.47 2.88 0.12 202.68 119.83 32688 +1912 25 3.33 -2.67 1.68 0.09 187.64 121.82 32827 +1912 26 2.57 -3.43 0.92 0 178.63 164.81 32969 +1912 27 -0.38 -6.38 -2.03 0 147.07 168.43 33114 +1912 28 1.11 -4.89 -0.54 0 162.35 169.89 33261 +1912 29 -0.38 -6.38 -2.03 0 147.07 173.06 33411 +1912 30 -2.17 -8.17 -3.82 0 130.38 176.17 33564 +1912 31 2.19 -3.81 0.54 0 174.26 176.31 33718 +1912 32 5.91 -0.09 4.26 0 221.25 175.88 33875 +1912 33 7.16 1.16 5.51 0.21 239.31 133.11 34035 +1912 34 8.93 2.93 7.28 0.42 267.04 133.55 34196 +1912 35 8.41 2.41 6.76 0 258.62 180.67 34360 +1912 36 5.89 -0.11 4.24 0 220.97 185.35 34526 +1912 37 6.44 0.44 4.79 0 228.76 187.31 34694 +1912 38 8.44 2.44 6.79 1.38 259.1 141.18 34863 +1912 39 4 -2 2.35 1.01 195.92 145.92 35035 +1912 40 3.79 -2.21 2.14 0.09 193.29 148 35208 +1912 41 5.1 -0.9 3.45 0.69 210.18 149.22 35383 +1912 42 5.97 -0.03 4.32 0.35 222.09 150.59 35560 +1912 43 3.89 -2.11 2.24 0.27 194.54 153.86 35738 +1912 44 1.22 -4.78 -0.43 0.07 163.53 157.18 35918 +1912 45 1.46 -4.54 -0.19 0 166.13 212.07 36099 +1912 46 2.4 -3.6 0.75 0 176.66 214.15 36282 +1912 47 7.66 1.66 6.01 0 246.88 212.56 36466 +1912 48 10.68 4.68 9.03 0.06 297.12 159.01 36652 +1912 49 12.15 6.15 10.5 0 324.6 212.86 36838 +1912 50 13.02 7.02 11.37 0.69 341.86 160.69 37026 +1912 51 13.51 7.51 11.86 0 351.92 216.43 37215 +1912 52 14.01 8.01 12.36 0 362.45 218.42 37405 +1912 53 13.58 7.58 11.93 0 353.38 221.95 37596 +1912 54 10.48 4.48 8.83 0 293.55 228.92 37788 +1912 55 6.28 0.28 4.63 0 226.47 236.57 37981 +1912 56 1.92 -4.08 0.27 0 171.21 242.99 38175 +1912 57 0.23 -5.77 -1.42 0 153.17 247.1 38370 +1912 58 -0.79 -6.79 -2.44 0.09 143.09 222.5 38565 +1912 59 2.28 -3.72 0.63 0 175.29 251.33 38761 +1912 60 5.86 -0.14 4.21 1.32 220.55 188.31 38958 +1912 61 5.58 -0.42 3.93 0.09 216.68 190.72 39156 +1912 62 4.68 -1.32 3.03 0.57 204.63 193.47 39355 +1912 63 8.66 2.66 7.01 0.02 262.64 192.53 39553 +1912 64 12.23 6.23 10.58 0 326.15 254.7 39753 +1912 65 15.2 9.2 13.55 0 388.59 252.52 39953 +1912 66 13.64 7.64 11.99 0.63 354.63 193.44 40154 +1912 67 12.11 6.11 10.46 0.62 323.82 197.43 40355 +1912 68 11.41 5.41 9.76 0.75 310.51 200.35 40556 +1912 69 11.89 5.89 10.24 0.1 319.59 201.74 40758 +1912 70 7.37 1.37 5.72 0.87 242.46 208.48 40960 +1912 71 2.15 -3.85 0.5 0.18 173.81 214.62 41163 +1912 72 2.9 -3.1 1.25 0.21 182.5 216.28 41366 +1912 73 8.54 2.54 6.89 0.4 260.7 213.68 41569 +1912 74 9.89 3.89 8.24 0 283.2 285.8 41772 +1912 75 7.15 1.15 5.5 0 239.16 292.13 41976 +1912 76 6.9 0.9 5.25 0 235.45 295.08 42179 +1912 77 11.34 5.34 9.69 0 309.2 291.5 42383 +1912 78 9.58 3.58 7.93 0 277.89 296.81 42587 +1912 79 15.82 9.82 14.17 0 402.84 288.51 42791 +1912 80 15.47 9.47 13.82 0 394.74 291.71 42996 +1912 81 16.52 10.52 14.87 0.09 419.46 218.95 43200 +1912 82 20.71 14.71 19.06 0 531.67 283.84 43404 +1912 83 20.76 14.76 19.11 0 533.15 286.03 43608 +1912 84 20.95 14.95 19.3 0.37 538.81 215.9 43812 +1912 85 15.83 9.83 14.18 0.4 403.08 227.49 44016 +1912 86 10.07 4.07 8.42 0.32 286.32 237.32 44220 +1912 87 8.73 2.73 7.08 0.1 263.77 240.73 44424 +1912 88 9.37 3.37 7.72 0.25 274.35 241.79 44627 +1912 89 7.34 1.34 5.69 0.14 242.01 245.67 44831 +1912 90 3.5 -2.5 1.85 0.04 189.71 250.89 45034 +1912 91 9.03 3.03 7.38 0.35 268.69 247.36 45237 +1912 92 12.24 6.24 10.59 0 326.35 326.69 45439 +1912 93 16.75 10.75 15.1 0 425.05 319.29 45642 +1912 94 15.24 9.24 13.59 0 389.5 324.91 45843 +1912 95 12.9 6.9 11.25 0 339.43 331.9 46045 +1912 96 10.14 4.14 8.49 0.28 287.55 254.22 46246 +1912 97 10.89 4.89 9.24 1 300.92 254.81 46446 +1912 98 12.04 6.04 10.39 0 322.47 339.63 46647 +1912 99 9.45 3.45 7.8 0 275.69 346.14 46846 +1912 100 9.87 3.87 8.22 0 282.86 347.42 47045 +1912 101 11.86 5.86 10.21 0.21 319.01 259.38 47243 +1912 102 14.52 8.52 12.87 0 373.46 342.3 47441 +1912 103 10.45 4.45 8.8 0 293.01 352.14 47638 +1912 104 9.03 3.03 7.38 0 268.69 356.35 47834 +1912 105 6.39 0.39 4.74 0 228.04 362.05 48030 +1912 106 4.17 -1.83 2.52 0.09 198.07 274.91 48225 +1912 107 2.1 -3.9 0.45 0 173.24 370.56 48419 +1912 108 2.73 -3.27 1.08 0 180.49 371.69 48612 +1912 109 4.94 -1.06 3.29 0 208.05 370.77 48804 +1912 110 9.55 3.55 7.9 0 277.38 365.49 48995 +1912 111 13.49 7.49 11.84 0 351.51 359.52 49185 +1912 112 9.74 3.74 8.09 0 280.62 368.27 49374 +1912 113 10.78 4.78 9.13 0 298.93 367.79 49561 +1912 114 9.63 3.63 7.98 0.03 278.74 278.5 49748 +1912 115 13.11 7.11 11.46 0.11 343.69 274.59 49933 +1912 116 12.34 6.34 10.69 0.09 328.3 276.71 50117 +1912 117 14.72 8.72 13.07 0 377.86 365.03 50300 +1912 118 15.73 9.73 14.08 0 400.75 363.88 50481 +1912 119 15.13 9.13 13.48 1.19 387.01 274.91 50661 +1912 120 13.97 7.97 12.32 0.21 361.6 277.83 50840 +1912 121 18.37 12.37 16.72 0.07 466.23 270.1 51016 +1912 122 21.14 15.14 19.49 0 544.51 352.43 51191 +1912 123 23.34 17.34 21.69 0.48 614.39 258.97 51365 +1912 124 16.55 10.55 14.9 0.88 420.19 276.37 51536 +1912 125 16.5 10.5 14.85 0.26 418.98 277.2 51706 +1912 126 17.43 11.43 15.78 0 441.94 368.03 51874 +1912 127 17.12 11.12 15.47 0.33 434.17 277.34 52039 +1912 128 14.67 8.67 13.02 0 376.76 377.12 52203 +1912 129 18.46 12.46 16.81 0 468.61 367.73 52365 +1912 130 17.56 11.56 15.91 0.16 445.23 278.36 52524 +1912 131 16.57 10.57 14.92 0.17 420.67 281.03 52681 +1912 132 20.83 14.83 19.18 1.13 535.23 271.81 52836 +1912 133 19.3 13.3 17.65 0 491.36 368.19 52989 +1912 134 22.7 16.7 21.05 0 593.32 356.93 53138 +1912 135 21.17 15.17 19.52 0 545.42 363.27 53286 +1912 136 22.42 16.42 20.77 0.01 584.3 269.46 53430 +1912 137 20.49 14.49 18.84 0.46 525.2 275.21 53572 +1912 138 18.06 12.06 16.41 0 458.09 375.31 53711 +1912 139 15.18 9.18 13.53 0 388.14 383.91 53848 +1912 140 11.78 5.78 10.13 0.8 317.49 294.12 53981 +1912 141 11.72 5.72 10.07 0.44 316.34 294.55 54111 +1912 142 10.96 4.96 9.31 0.03 302.2 296.08 54238 +1912 143 13.8 7.8 12.15 0.01 357.99 291.93 54362 +1912 144 17.57 11.57 15.92 0.93 445.49 284.9 54483 +1912 145 18.06 12.06 16.41 0.03 458.09 284.16 54600 +1912 146 16.45 10.45 14.8 0 417.77 383.87 54714 +1912 147 13.89 7.89 12.24 0 359.9 390.86 54824 +1912 148 13.94 7.94 12.29 0 360.96 391.13 54931 +1912 149 15.26 9.26 13.61 0.01 389.95 291.15 55034 +1912 150 16.36 10.36 14.71 0.06 415.61 289.23 55134 +1912 151 17.13 11.13 15.48 0.96 434.42 287.91 55229 +1912 152 20.92 14.92 19.27 0 537.91 371.88 55321 +1912 153 26.36 20.36 24.71 0.19 722.59 262.15 55409 +1912 154 28.79 22.79 27.14 0.3 820.96 253.02 55492 +1912 155 25 19 23.35 1.39 672.02 267.23 55572 +1912 156 22.93 16.93 21.28 0.31 600.82 274.02 55648 +1912 157 23.6 17.6 21.95 0 623.13 362.81 55719 +1912 158 22.97 16.97 21.32 0.43 602.13 274.15 55786 +1912 159 25.2 19.2 23.55 0.1 679.27 267.21 55849 +1912 160 24.87 18.87 23.22 0.01 667.35 268.46 55908 +1912 161 22.61 16.61 20.96 0.07 590.41 275.58 55962 +1912 162 24.01 18.01 22.36 0 637.13 361.79 56011 +1912 163 21.74 15.74 20.09 0 562.86 371.04 56056 +1912 164 21.91 15.91 20.26 0.05 568.16 277.84 56097 +1912 165 21.24 15.24 19.59 0.13 547.53 279.77 56133 +1912 166 18.78 12.78 17.13 0 477.17 381.44 56165 +1912 167 17.08 11.08 15.43 0.24 433.18 289.88 56192 +1912 168 18.21 12.21 16.56 0 462.01 383.24 56214 +1912 169 20.49 14.49 18.84 0 525.2 375.8 56231 +1912 170 22.48 16.48 20.83 0.04 586.22 276.35 56244 +1912 171 19.66 13.66 18.01 2.01 501.4 284.02 56252 +1912 172 18.24 12.24 16.59 1.13 462.8 287.41 56256 +1912 173 17.37 11.37 15.72 0.81 440.43 289.34 56255 +1912 174 16.12 10.12 14.47 1.1 409.89 291.91 56249 +1912 175 13.82 7.82 12.17 0.21 358.42 296.25 56238 +1912 176 15.2 9.2 13.55 0.24 388.59 293.68 56223 +1912 177 16.89 10.89 15.24 0.16 428.48 290.18 56203 +1912 178 16.81 10.81 15.16 0 426.52 387.16 56179 +1912 179 21.7 15.7 20.05 0 561.62 371.15 56150 +1912 180 19.25 13.25 17.6 0.04 489.98 284.67 56116 +1912 181 21.13 15.13 19.48 0 544.21 373.05 56078 +1912 182 22.08 16.08 20.43 0 573.49 369.39 56035 +1912 183 22.3 16.3 20.65 0 580.46 368.37 55987 +1912 184 23.66 17.66 22.01 0 625.16 362.78 55935 +1912 185 27.36 21.36 25.71 0 761.79 345.68 55879 +1912 186 25.46 19.46 23.81 0 688.78 354.59 55818 +1912 187 23.24 17.24 21.59 0.12 611.06 272.99 55753 +1912 188 21.28 15.28 19.63 0 548.75 371.24 55684 +1912 189 19.89 13.89 18.24 0.01 507.9 281.94 55611 +1912 190 19.97 13.97 18.32 0 510.18 375.27 55533 +1912 191 18.97 12.97 17.32 0 482.32 378.28 55451 +1912 192 24.24 18.24 22.59 0.01 645.09 268.85 55366 +1912 193 24.02 18.02 22.37 0 637.47 359.14 55276 +1912 194 20.89 14.89 19.24 0.06 537.02 278.28 55182 +1912 195 19.93 13.93 18.28 0 509.04 374.07 55085 +1912 196 20.95 14.95 19.3 0.31 538.81 277.61 54984 +1912 197 22.48 16.48 20.83 0 586.22 364.03 54879 +1912 198 22.58 16.58 20.93 0 589.44 363.22 54770 +1912 199 24.71 18.71 23.06 0 661.64 354.11 54658 +1912 200 24.09 18.09 22.44 0.11 639.89 267.29 54542 +1912 201 25.73 19.73 24.08 0.58 698.78 261.53 54423 +1912 202 21.27 15.27 19.62 0 548.44 366.35 54301 +1912 203 22.14 16.14 20.49 0 575.39 362.65 54176 +1912 204 21.29 15.29 19.64 0 549.05 365.27 54047 +1912 205 23.16 17.16 21.51 0 608.4 357.69 53915 +1912 206 22.57 16.57 20.92 0.6 589.12 269.58 53780 +1912 207 21.27 15.27 19.62 1.98 548.44 272.71 53643 +1912 208 21.71 15.71 20.06 0 561.93 361.37 53502 +1912 209 22.27 16.27 20.62 0.15 579.51 268.99 53359 +1912 210 23.94 17.94 22.29 0.05 634.72 263.59 53213 +1912 211 21.97 15.97 20.32 0 570.04 358.39 53064 +1912 212 22.11 16.11 20.46 0.27 574.44 267.82 52913 +1912 213 11.91 5.91 10.26 0 319.97 384.98 52760 +1912 214 12.69 6.69 11.04 0.29 335.22 286.92 52604 +1912 215 16.31 10.31 14.66 0 414.42 373.21 52445 +1912 216 16.89 10.89 15.24 0.43 428.48 277.96 52285 +1912 217 22.35 16.35 20.7 0.2 582.06 264.12 52122 +1912 218 18.74 12.74 17.09 0 476.09 363.54 51958 +1912 219 18.21 12.21 16.56 0.06 462.01 273.05 51791 +1912 220 18.3 12.3 16.65 0.11 464.38 272.14 51622 +1912 221 19.6 13.6 17.95 0.5 499.72 268.4 51451 +1912 222 19.13 13.13 17.48 0.85 486.69 268.71 51279 +1912 223 14.64 8.64 12.99 1.37 376.1 276.96 51105 +1912 224 17.56 11.56 15.91 0.05 445.23 270.51 50929 +1912 225 16.42 10.42 14.77 0.29 417.05 271.95 50751 +1912 226 14.36 8.36 12.71 0 369.98 366.48 50572 +1912 227 14.52 8.52 12.87 0 373.46 364.8 50392 +1912 228 19.65 13.65 18 0 501.12 349.67 50210 +1912 229 19.85 13.85 18.2 0 506.77 347.8 50026 +1912 230 22.43 16.43 20.78 0 584.62 337.79 49842 +1912 231 21.68 15.68 20.03 0 561.01 339.02 49656 +1912 232 22.14 16.14 20.49 0 575.39 336.07 49469 +1912 233 20.4 14.4 18.75 0.02 522.58 255.42 49280 +1912 234 20.62 14.62 18.97 0.2 529.02 253.83 49091 +1912 235 23.47 17.47 21.82 1.87 618.75 245.22 48900 +1912 236 19.99 13.99 18.34 0 510.75 337.54 48709 +1912 237 24.65 18.65 23 0.54 659.51 239.55 48516 +1912 238 25.48 19.48 23.83 0 689.52 314.39 48323 +1912 239 26.05 20.05 24.4 0.28 710.79 232.91 48128 +1912 240 26.8 20.8 25.15 0.65 739.62 229.2 47933 +1912 241 28.05 22.05 26.4 0 789.88 298.23 47737 +1912 242 28.59 22.59 26.94 0 812.46 294.04 47541 +1912 243 28.42 22.42 26.77 1.8 805.29 219.86 47343 +1912 244 19.18 13.18 17.53 1.45 488.06 244.72 47145 +1912 245 15.29 9.29 13.64 0.59 390.64 250.84 46947 +1912 246 10.82 4.82 9.17 0.43 299.65 256.03 46747 +1912 247 13.08 7.08 11.43 0.37 343.08 251.44 46547 +1912 248 15.07 9.07 13.42 0 385.66 329.09 46347 +1912 249 17.57 11.57 15.92 0.26 445.49 240.77 46146 +1912 250 19.82 13.82 18.17 0.63 505.92 234.7 45945 +1912 251 21.24 15.24 19.59 0.07 547.53 229.93 45743 +1912 252 14.12 8.12 12.47 0.66 364.8 242.01 45541 +1912 253 13.01 7.01 11.36 0.23 341.66 242.05 45339 +1912 254 9.99 3.99 8.34 0 284.93 325.81 45136 +1912 255 10.02 4.02 8.37 0.61 285.45 242.57 44933 +1912 256 8.84 2.84 7.19 0.11 265.57 242.15 44730 +1912 257 14.75 8.75 13.1 1.32 378.52 232.7 44527 +1912 258 15.45 9.45 13.8 0.01 394.29 229.81 44323 +1912 259 17.37 11.37 15.72 0 440.43 299.61 44119 +1912 260 19.68 13.68 18.03 0 501.96 291.33 43915 +1912 261 19.94 13.94 18.29 0.08 509.33 216.17 43711 +1912 262 17.21 11.21 15.56 0.12 436.41 219.61 43507 +1912 263 17.87 11.87 16.22 0.33 453.17 216.6 43303 +1912 264 17.31 11.31 15.66 0.12 438.92 215.69 43099 +1912 265 11.62 5.62 9.97 0.13 314.45 222.28 42894 +1912 266 6.04 0.04 4.39 1.39 223.07 226.15 42690 +1912 267 4.07 -1.93 2.42 0 196.8 300.87 42486 +1912 268 8.84 2.84 7.19 0.03 265.57 219.46 42282 +1912 269 7.03 1.03 5.38 1.17 237.37 219.25 42078 +1912 270 8.13 2.13 6.48 0.02 254.18 216.18 41875 +1912 271 11.83 5.83 10.18 0 318.44 280.27 41671 +1912 272 10.73 4.73 9.08 0 298.03 279.18 41468 +1912 273 13.7 7.7 12.05 0 355.89 271.81 41265 +1912 274 11.87 5.87 10.22 0 319.2 272.16 41062 +1912 275 11.12 5.12 9.47 0 305.13 270.5 40860 +1912 276 8.12 2.12 6.47 0.01 254.02 203.84 40658 +1912 277 9.65 3.65 8 0.25 279.08 200.34 40456 +1912 278 7.02 1.02 5.37 0 237.22 267.41 40255 +1912 279 5.43 -0.57 3.78 0 214.63 266.21 40054 +1912 280 6.02 0.02 4.37 0 222.79 262.87 39854 +1912 281 6.75 0.75 5.1 0 233.25 259.31 39654 +1912 282 8.45 2.45 6.8 0.33 259.26 190.93 39455 +1912 283 7.11 1.11 5.46 0.28 238.56 189.91 39256 +1912 284 10.25 4.25 8.6 1.56 289.48 184.8 39058 +1912 285 13.78 7.78 12.13 0.48 357.57 178.96 38861 +1912 286 14.14 8.14 12.49 0 365.23 235.28 38664 +1912 287 18.84 12.84 17.19 0 478.79 223.6 38468 +1912 288 15.32 9.32 13.67 0 391.32 227.65 38273 +1912 289 13.82 7.82 12.17 0 358.42 227.5 38079 +1912 290 10.42 4.42 8.77 0.14 292.48 172.06 37885 +1912 291 13.88 7.88 12.23 0.12 359.69 166.42 37693 +1912 292 9.26 3.26 7.61 0.12 272.5 169.03 37501 +1912 293 10.47 4.47 8.82 0.08 293.37 165.88 37311 +1912 294 10.34 4.34 8.69 0.78 291.06 163.83 37121 +1912 295 10.13 4.13 8.48 0.58 287.37 161.88 36933 +1912 296 14.47 8.47 12.82 1.71 372.37 155.56 36745 +1912 297 15.94 9.94 14.29 1.82 405.65 151.81 36560 +1912 298 15.78 9.78 14.13 0.58 401.91 150.1 36375 +1912 299 14.32 8.32 12.67 0 369.11 199.65 36191 +1912 300 12.77 6.77 11.12 0 336.82 199.19 36009 +1912 301 12.26 6.26 10.61 0 326.74 197.36 35829 +1912 302 11.68 5.68 10.03 0 315.59 195.48 35650 +1912 303 10.55 4.55 8.9 0 294.79 194.24 35472 +1912 304 9.95 3.95 8.3 0.21 284.24 144.33 35296 +1912 305 2.52 -3.48 0.87 0 178.05 196.01 35122 +1912 306 3.65 -2.35 2 0 191.56 192.94 34950 +1912 307 2.3 -3.7 0.65 0.01 175.51 143.46 34779 +1912 308 0.72 -5.28 -0.93 0 158.22 189.58 34610 +1912 309 0.5 -5.5 -1.15 0.45 155.94 140.5 34444 +1912 310 1.46 -4.54 -0.19 0 166.13 184.29 34279 +1912 311 -0.31 -6.31 -1.96 0.25 147.76 176.67 34116 +1912 312 -0.86 -6.86 -2.51 0 142.42 220.2 33956 +1912 313 3.11 -2.89 1.46 0 184.99 215.61 33797 +1912 314 -0.36 -6.36 -2.01 0 147.27 215.77 33641 +1912 315 2.83 -3.17 1.18 0 181.67 211.25 33488 +1912 316 2.04 -3.96 0.39 0 172.56 170.09 33337 +1912 317 6.72 0.72 5.07 0 232.81 164.71 33188 +1912 318 4.88 -1.12 3.23 0.03 207.26 122.79 33042 +1912 319 3.13 -2.87 1.48 0.04 185.23 122.34 32899 +1912 320 2.49 -3.51 0.84 0 177.7 161.61 32758 +1912 321 6.8 0.8 5.15 0 233.98 156.63 32620 +1912 322 8.06 2.06 6.41 0 253.08 153.82 32486 +1912 323 4.79 -1.21 3.14 0.19 206.07 115.95 32354 +1912 324 6.58 0.58 4.93 0.19 230.78 113.48 32225 +1912 325 6.67 0.67 5.02 0 232.08 149.51 32100 +1912 326 5.99 -0.01 4.34 0 222.37 148.54 31977 +1912 327 6.48 0.48 4.83 0 229.33 146.35 31858 +1912 328 10.23 4.23 8.58 0.18 289.12 106.05 31743 +1912 329 10.53 4.53 8.88 1.21 294.44 104.75 31631 +1912 330 9.37 3.37 7.72 0.17 274.35 104.43 31522 +1912 331 13.14 7.14 11.49 0.78 344.3 100.82 31417 +1912 332 11.41 5.41 9.76 0.86 310.51 100.9 31316 +1912 333 5.76 -0.24 4.11 0.03 219.16 103.42 31218 +1912 334 3.9 -2.1 2.25 0.36 194.66 103.45 31125 +1912 335 4.46 -1.54 2.81 0.52 201.78 102.32 31035 +1912 336 6.03 0.03 4.38 0 222.93 134.38 30949 +1912 337 6.9 0.9 5.25 0 235.45 132.14 30867 +1912 338 8.06 2.06 6.41 0 253.08 130.39 30790 +1912 339 6.43 0.43 4.78 0.21 228.61 98.05 30716 +1912 340 4.66 -1.34 3.01 0.59 204.37 98.33 30647 +1912 341 7.09 1.09 5.44 0 238.26 128.66 30582 +1912 342 8.22 2.22 6.57 0 255.6 127.11 30521 +1912 343 4.24 -1.76 2.59 0 198.96 128.84 30465 +1912 344 6.45 0.45 4.8 0 228.9 126.38 30413 +1912 345 7.54 1.54 5.89 0.02 245.04 93.92 30366 +1912 346 6.23 0.23 4.58 0 225.75 125.55 30323 +1912 347 8.73 2.73 7.08 0 263.77 123.24 30284 +1912 348 5.17 -0.83 3.52 0.1 211.12 93.94 30251 +1912 349 3.29 -2.71 1.64 0 187.16 125.91 30221 +1912 350 3.8 -2.2 2.15 0 193.42 125.31 30197 +1912 351 8.09 2.09 6.44 0 253.55 122.44 30177 +1912 352 5.19 -0.81 3.54 0 211.39 124.22 30162 +1912 353 3.78 -2.22 2.13 0.01 193.17 93.71 30151 +1912 354 1.5 -4.5 -0.15 0.08 166.57 94.53 30145 +1912 355 -0.88 -6.88 -2.53 0.09 142.23 139.36 30144 +1912 356 1.03 -4.97 -0.62 0 161.49 170.21 30147 +1912 357 0.8 -5.2 -0.85 0 159.06 170.25 30156 +1912 358 0.5 -5.5 -1.15 0 155.94 126.65 30169 +1912 359 5.52 -0.48 3.87 0.01 215.86 93.16 30186 +1912 360 6.55 0.55 4.9 0.29 230.34 92.95 30208 +1912 361 2.91 -3.09 1.26 0.04 182.61 94.76 30235 +1912 362 2.81 -3.19 1.16 0 181.43 126.84 30267 +1912 363 2.87 -3.13 1.22 0 182.14 127.4 30303 +1912 364 1.81 -4.19 0.16 0 169.99 128.31 30343 +1912 365 0.2 -5.8 -1.45 0 152.86 129.61 30388 +1913 1 -2.5 -8.5 -4.15 0 127.48 131.56 30438 +1913 2 -1.6 -7.6 -3.25 0 135.5 131.97 30492 +1913 3 -0.37 -6.37 -2.02 0 147.17 132.44 30551 +1913 4 3.95 -2.05 2.3 0 195.29 131.27 30614 +1913 5 7.83 1.83 6.18 0 249.5 129.45 30681 +1913 6 5.45 -0.55 3.8 0 214.9 131.92 30752 +1913 7 4.02 -1.98 2.37 0 196.17 133.56 30828 +1913 8 3.83 -2.17 2.18 0.79 193.79 101.36 30907 +1913 9 2.74 -3.26 1.09 0 180.61 137 30991 +1913 10 1.55 -4.45 -0.1 0 167.11 138.91 31079 +1913 11 0.52 -5.48 -1.13 0 156.14 140.4 31171 +1913 12 -0.26 -6.26 -1.91 0 148.25 141.77 31266 +1913 13 -2.09 -8.09 -3.74 0 131.09 144.16 31366 +1913 14 -1.74 -7.74 -3.39 0.66 134.23 153.1 31469 +1913 15 -1.71 -7.71 -3.36 0 134.5 190.78 31575 +1913 16 -1.27 -7.27 -2.92 0 138.55 191.75 31686 +1913 17 -1.13 -7.13 -2.78 0 139.86 193.23 31800 +1913 18 1.67 -4.33 0.02 0 168.43 193.45 31917 +1913 19 2.28 -3.72 0.63 0 175.29 194.62 32038 +1913 20 2.08 -3.92 0.43 0 173.01 195.89 32161 +1913 21 2.95 -3.05 1.3 0 183.09 196.88 32289 +1913 22 -0.16 -6.16 -1.81 0.59 149.25 162.22 32419 +1913 23 1.31 -4.69 -0.34 0.46 164.5 162.67 32552 +1913 24 -0.56 -6.56 -2.21 0.77 145.31 167.01 32688 +1913 25 -2.01 -8.01 -3.66 0 131.8 210.04 32827 +1913 26 -4.32 -10.32 -5.97 0.16 112.51 171.17 32969 +1913 27 -0.83 -6.83 -2.48 0 142.71 213.58 33114 +1913 28 1.42 -4.58 -0.23 0 165.69 214.28 33261 +1913 29 1.19 -4.81 -0.46 0 163.21 216.46 33411 +1913 30 2.18 -3.82 0.53 0 174.15 217.68 33564 +1913 31 -1.63 -7.63 -3.28 0 135.23 221.88 33718 +1913 32 2.59 -3.41 0.94 0 178.86 221.23 33875 +1913 33 4.1 -1.9 2.45 0 197.18 222.18 34035 +1913 34 3.36 -2.64 1.71 0 188.01 224.3 34196 +1913 35 2.85 -3.15 1.2 0 181.9 226.26 34360 +1913 36 3.75 -2.25 2.1 0 192.79 227.54 34526 +1913 37 3.76 -2.24 2.11 0.35 192.92 181.98 34694 +1913 38 1.67 -4.33 0.02 0 168.43 233.07 34863 +1913 39 -2 -8 -3.65 0.15 131.89 188.4 35035 +1913 40 -1.91 -7.91 -3.56 0 132.69 240.35 35208 +1913 41 -0.02 -6.02 -1.67 0 150.64 241.81 35383 +1913 42 -1.75 -7.75 -3.4 0.16 134.14 194.08 35560 +1913 43 -0.43 -6.43 -2.08 0 146.58 247.4 35738 +1913 44 3.91 -2.09 2.26 0 194.79 246.51 35918 +1913 45 5.58 -0.42 3.93 0 216.68 246.97 36099 +1913 46 4.18 -1.82 2.53 0 198.19 250.15 36282 +1913 47 6.92 0.92 5.27 0 235.74 249.64 36466 +1913 48 8.33 2.33 6.68 0 257.34 214.66 36652 +1913 49 2.27 -3.73 0.62 0 175.17 222.7 36838 +1913 50 4.18 -1.82 2.53 0 198.19 223.93 37026 +1913 51 4.54 -1.46 2.89 0 202.81 226.6 37215 +1913 52 1.41 -4.59 -0.24 0 165.58 231.84 37405 +1913 53 1.44 -4.56 -0.21 0 165.91 234.81 37596 +1913 54 1.31 -4.69 -0.34 0 164.5 237.68 37788 +1913 55 -0.82 -6.82 -2.47 0 142.8 242.11 37981 +1913 56 4.85 -1.15 3.2 0 206.86 240.6 38175 +1913 57 6.44 0.44 4.79 0 228.76 241.98 38370 +1913 58 7.81 1.81 6.16 0 249.19 243.45 38565 +1913 59 2.52 -3.48 0.87 0.01 178.05 188.36 38761 +1913 60 8.37 2.37 6.72 0 257.98 248.38 38958 +1913 61 11.13 5.13 9.48 0 305.31 247.75 39156 +1913 62 12.66 6.66 11.01 0 334.62 248.25 39355 +1913 63 13.84 7.84 12.19 0 358.84 249.29 39553 +1913 64 11.43 5.43 9.78 0 310.88 255.89 39753 +1913 65 12.04 6.04 10.39 0.15 322.47 193.36 39953 +1913 66 8.64 2.64 6.99 0 262.32 265.21 40154 +1913 67 7.56 1.56 5.91 0 245.35 269.41 40355 +1913 68 8.75 2.75 7.1 0 264.1 270.82 40556 +1913 69 10.72 4.72 9.07 0.4 297.85 203.06 40758 +1913 70 3.92 -2.08 2.27 0 194.91 281.63 40960 +1913 71 5.57 -0.43 3.92 0 216.54 282.91 41163 +1913 72 3.28 -2.72 1.63 0 187.04 288.03 41366 +1913 73 6 0 4.35 0 222.51 287.96 41569 +1913 74 8.04 2.04 6.39 0 252.77 288.29 41772 +1913 75 7.14 1.14 5.49 0 239.01 292.14 41976 +1913 76 9.95 3.95 8.3 0 284.24 291.04 42179 +1913 77 11.7 5.7 10.05 0 315.97 290.92 42383 +1913 78 10.44 4.44 8.79 0 292.83 295.54 42587 +1913 79 7.51 1.51 5.86 0 244.59 302.34 42791 +1913 80 10.39 4.39 8.74 0 291.95 300.84 42996 +1913 81 15.36 9.36 13.71 0 392.23 294.44 43200 +1913 82 13.52 7.52 11.87 0 352.13 300.68 43404 +1913 83 12.58 6.58 10.93 0 333.03 304.86 43608 +1913 84 12.33 6.33 10.68 0.38 328.11 230.85 43812 +1913 85 14.36 8.36 12.71 0.07 369.98 229.81 44016 +1913 86 13.01 7.01 11.36 0.56 341.66 233.55 44220 +1913 87 10.65 4.65 9 0.06 296.59 238.52 44424 +1913 88 12.58 6.58 10.93 0 333.03 317.02 44627 +1913 89 13.53 7.53 11.88 0.04 352.34 238.09 44831 +1913 90 12.14 6.14 10.49 0 324.4 322.42 45034 +1913 91 15.59 9.59 13.94 0 397.51 317.66 45237 +1913 92 14.91 8.91 13.26 0 382.08 321.35 45439 +1913 93 15.67 9.67 14.02 0 399.35 321.83 45642 +1913 94 17.91 11.91 16.26 0 454.2 318.46 45843 +1913 95 14.17 8.17 12.52 0.19 365.87 246.99 46045 +1913 96 15.19 9.19 13.54 1.87 388.37 246.89 46246 +1913 97 7.87 1.87 6.22 0.61 250.12 258.4 46446 +1913 98 8 2 6.35 0 252.14 346.33 46647 +1913 99 7.27 1.27 5.62 0 240.96 349.41 46846 +1913 100 9.41 3.41 7.76 0 275.02 348.17 47045 +1913 101 15.27 9.27 13.62 0 390.18 338.73 47243 +1913 102 12.93 6.93 11.28 0 340.04 345.66 47441 +1913 103 11.17 5.17 9.52 0 306.05 350.86 47638 +1913 104 11.86 5.86 10.21 0 319.01 351.41 47834 +1913 105 17.43 11.43 15.78 0 441.94 340.58 48030 +1913 106 11.81 5.81 10.16 0 318.06 354.95 48225 +1913 107 16.84 10.84 15.19 0 427.25 345.37 48419 +1913 108 15.18 9.18 13.53 0 388.14 351.18 48612 +1913 109 17.99 11.99 16.34 0.37 456.27 259.16 48804 +1913 110 15.58 9.58 13.93 0 397.27 353.2 48995 +1913 111 15.53 9.53 13.88 0 396.12 354.86 49185 +1913 112 13.17 7.17 11.52 0 344.91 361.72 49374 +1913 113 11 5 9.35 0.07 302.93 275.54 49561 +1913 114 11.53 5.53 9.88 0 312.76 367.88 49748 +1913 115 10.62 4.62 8.97 0 296.05 371.03 49933 +1913 116 7.39 1.39 5.74 0.11 242.76 283.22 50117 +1913 117 7.19 1.19 5.54 0.13 239.76 284.45 50300 +1913 118 9.78 3.78 8.13 0 281.31 376.43 50481 +1913 119 8.04 2.04 6.39 0 252.77 380.54 50661 +1913 120 11.1 5.1 9.45 0 304.76 376.42 50840 +1913 121 16.09 10.09 14.44 0.09 409.18 274.82 51016 +1913 122 14.63 8.63 12.98 0 375.88 371.23 51191 +1913 123 14.16 8.16 12.51 0 365.66 373.36 51365 +1913 124 14.98 8.98 13.33 0 383.64 372.5 51536 +1913 125 18.1 12.1 16.45 0 459.14 365.13 51706 +1913 126 14.36 8.36 12.71 0.3 369.98 281.97 51874 +1913 127 14.91 8.91 13.26 0 382.08 375.54 52039 +1913 128 14.9 8.9 13.25 0.08 381.86 282.42 52203 +1913 129 18.7 12.7 17.05 0.68 475.02 275.25 52365 +1913 130 20.19 14.19 18.54 0.4 516.49 272.26 52524 +1913 131 21.6 15.6 19.95 0 558.54 358.89 52681 +1913 132 20.39 14.39 18.74 0 522.29 363.92 52836 +1913 133 18.09 12.09 16.44 0 458.88 371.9 52989 +1913 134 21.19 15.19 19.54 0 546.02 362.52 53138 +1913 135 19.79 13.79 18.14 0 505.07 367.98 53286 +1913 136 19.46 13.46 17.81 0.21 495.8 277.26 53430 +1913 137 21.45 15.45 19.8 0.85 553.93 272.68 53572 +1913 138 20.04 14.04 18.39 1.3 512.18 276.79 53711 +1913 139 19.62 13.62 17.97 0 500.28 371.12 53848 +1913 140 16 10 14.35 0 407.06 382.28 53981 +1913 141 14.84 8.84 13.19 0 380.52 385.69 54111 +1913 142 11.63 5.63 9.98 0 314.64 393.43 54238 +1913 143 13.1 7.1 11.45 0.35 343.48 293.13 54362 +1913 144 13.3 7.3 11.65 0.93 347.58 293.15 54483 +1913 145 11.98 5.98 10.33 0.4 321.31 295.67 54600 +1913 146 11.06 5.06 9.41 0.02 304.03 297.36 54714 +1913 147 13.21 7.21 11.56 0 345.73 392.43 54824 +1913 148 18.13 12.13 16.48 0 459.92 379.9 54931 +1913 149 18.02 12.02 16.37 0 457.05 380.55 55034 +1913 150 17.84 11.84 16.19 0 452.4 381.42 55134 +1913 151 16.28 10.28 14.63 0.34 413.7 289.69 55229 +1913 152 22.07 16.07 20.42 0.03 573.18 275.75 55321 +1913 153 17.71 11.71 16.06 0.6 449.06 286.91 55409 +1913 154 18.89 12.89 17.24 0.1 480.14 284.44 55492 +1913 155 22.56 16.56 20.91 0 588.79 366.51 55572 +1913 156 23.47 17.47 21.82 0 618.75 363.18 55648 +1913 157 22.96 16.96 21.31 0 601.8 365.41 55719 +1913 158 25.04 19.04 23.39 0.27 673.47 267.58 55786 +1913 159 24.97 18.97 23.32 0.07 670.94 267.99 55849 +1913 160 20.9 14.9 19.25 1.06 537.31 280.33 55908 +1913 161 19.9 13.9 18.25 0.62 508.19 282.97 55962 +1913 162 18.04 12.04 16.39 0.09 457.57 287.47 56011 +1913 163 21.07 15.07 19.42 0 542.4 373.5 56056 +1913 164 20.75 14.75 19.1 0 532.86 374.68 56097 +1913 165 23.69 17.69 22.04 0 626.18 363.48 56133 +1913 166 19.15 13.15 17.5 0 487.23 380.26 56165 +1913 167 22.12 16.12 20.47 0 574.76 369.77 56192 +1913 168 21.2 15.2 19.55 0.34 546.32 279.95 56214 +1913 169 25.06 19.06 23.41 2.09 674.19 268.24 56231 +1913 170 26.05 20.05 24.4 0.15 710.79 264.82 56244 +1913 171 20.64 14.64 18.99 0.02 529.61 281.5 56252 +1913 172 18.56 12.56 16.91 0.27 471.27 286.67 56256 +1913 173 17.28 11.28 15.63 0.07 438.16 289.54 56255 +1913 174 19.79 13.79 18.14 0 505.07 378.14 56249 +1913 175 17.98 11.98 16.33 0 456.02 383.87 56238 +1913 176 20.55 14.55 18.9 0.04 526.96 281.61 56223 +1913 177 22.13 16.13 20.48 1.24 575.07 277.2 56203 +1913 178 18.65 12.65 17 0.17 473.68 286.27 56179 +1913 179 14.83 8.83 13.18 0 380.3 392.32 56150 +1913 180 17.75 11.75 16.1 0 450.08 384.21 56116 +1913 181 18.04 12.04 16.39 0.07 457.57 287.45 56078 +1913 182 17.78 11.78 16.13 0 450.85 383.91 56035 +1913 183 19.8 13.8 18.15 0 505.35 377.35 55987 +1913 184 19.24 13.24 17.59 0.01 489.71 284.28 55935 +1913 185 18.3 12.3 16.65 0.71 464.38 286.43 55879 +1913 186 16.11 10.11 14.46 2.54 409.66 290.96 55818 +1913 187 17.14 11.14 15.49 1.04 434.67 288.68 55753 +1913 188 18.64 12.64 16.99 0.52 473.41 285.11 55684 +1913 189 17.69 11.69 16.04 2.34 448.55 287.13 55611 +1913 190 17.55 11.55 15.9 0.66 444.98 287.16 55533 +1913 191 16.47 10.47 14.82 0.28 418.26 289.26 55451 +1913 192 17.22 11.22 15.57 0.01 436.66 287.44 55366 +1913 193 18.98 12.98 17.33 0.06 482.59 283.25 55276 +1913 194 17.19 11.19 15.54 1.08 435.91 287.13 55182 +1913 195 21.87 15.87 20.22 1.29 566.91 275.4 55085 +1913 196 20.49 14.49 18.84 0.36 525.2 278.82 54984 +1913 197 18.55 12.55 16.9 0.02 471 283.23 54879 +1913 198 17.44 11.44 15.79 0.01 442.19 285.4 54770 +1913 199 23.84 17.84 22.19 0.16 631.29 268.36 54658 +1913 200 21.47 15.47 19.82 0 554.54 366.65 54542 +1913 201 21.88 15.88 20.23 0.36 567.22 273.51 54423 +1913 202 21.27 15.27 19.62 0.09 548.44 274.76 54301 +1913 203 22.16 16.16 20.51 0.33 576.02 271.93 54176 +1913 204 21.57 15.57 19.92 0.93 557.61 273.19 54047 +1913 205 20.43 14.43 18.78 1.2 523.45 275.82 53915 +1913 206 24.24 18.24 22.59 0 645.09 352.72 53780 +1913 207 22.88 16.88 21.23 0 599.18 357.6 53643 +1913 208 19.57 13.57 17.92 0 498.88 368.74 53502 +1913 209 18.21 12.21 16.56 0 462.01 372.32 53359 +1913 210 17.57 11.57 15.92 0 445.49 373.57 53213 +1913 211 19.1 13.1 17.45 0 485.86 368.18 53064 +1913 212 19.11 13.11 17.46 0.63 486.14 275.51 52913 +1913 213 19.76 13.76 18.11 0.73 504.22 273.38 52760 +1913 214 18.15 12.15 16.5 0.08 460.44 276.56 52604 +1913 215 18.12 12.12 16.47 0 459.66 368.15 52445 +1913 216 18.99 12.99 17.34 0.04 482.86 273.37 52285 +1913 217 19.86 13.86 18.21 0 507.05 360.85 52122 +1913 218 16.85 10.85 15.2 0.05 427.5 276.73 51958 +1913 219 19.39 13.39 17.74 0 493.86 360.48 51791 +1913 220 19.58 13.58 17.93 0.35 499.16 269.2 51622 +1913 221 20.51 14.51 18.86 0.14 525.79 266.18 51451 +1913 222 19.16 13.16 17.51 0 487.51 358.19 51279 +1913 223 18.44 12.44 16.79 0.34 468.08 269.41 51105 +1913 224 20.74 14.74 19.09 0.18 532.56 263.18 50929 +1913 225 20.49 14.49 18.84 0 525.2 350.6 50751 +1913 226 20.35 14.35 18.7 0.41 521.12 262.44 50572 +1913 227 20.68 14.68 19.03 0 530.79 347.56 50392 +1913 228 19.17 13.17 17.52 0.08 487.78 263.36 50210 +1913 229 20.51 14.51 18.86 0 525.79 345.68 50026 +1913 230 19.35 13.35 17.7 2.05 492.75 261.06 49842 +1913 231 24.79 18.79 23.14 0.5 664.49 245.4 49656 +1913 232 26.47 20.47 24.82 0 726.82 318.66 49469 +1913 233 26.29 20.29 24.64 1.32 719.91 238.6 49280 +1913 234 24.43 18.43 22.78 2.06 651.74 243.49 49091 +1913 235 23.93 17.93 22.28 0.12 634.38 243.9 48900 +1913 236 19.05 13.05 17.4 0.12 484.5 255.29 48709 +1913 237 17.51 11.51 15.86 1.28 443.96 257.3 48516 +1913 238 15.03 9.03 13.38 0 384.76 347.56 48323 +1913 239 20.06 14.06 18.41 0.38 512.76 249.4 48128 +1913 240 23.71 17.71 22.06 0.71 626.86 238.74 47933 +1913 241 22.97 16.97 21.32 0.27 602.13 239.54 47737 +1913 242 22.29 16.29 20.64 0.89 580.15 240.07 47541 +1913 243 19.92 13.92 18.27 0.44 508.76 244.45 47343 +1913 244 16.23 10.23 14.58 0 412.51 334.11 47145 +1913 245 10.85 4.85 9.2 0 300.2 343.35 46947 +1913 246 14.67 8.67 13.02 1.01 376.76 250.38 46747 +1913 247 14.74 8.74 13.09 0.44 378.3 248.84 46547 +1913 248 14.27 8.27 12.62 0 368.03 330.82 46347 +1913 249 13.33 7.33 11.68 0 348.2 330.65 46146 +1913 250 13.12 7.12 11.47 0 343.89 329.06 45945 +1913 251 18.91 12.91 17.26 0 480.69 313.42 45743 +1913 252 23.68 17.68 22.03 0 625.84 296.32 45541 +1913 253 23.15 17.15 21.5 0.03 608.07 222.12 45339 +1913 254 20.29 14.29 18.64 0.13 519.38 227.39 45136 +1913 255 20.89 14.89 19.24 0.03 537.02 224.4 44933 +1913 256 23.47 17.47 21.82 0 618.75 288.68 44730 +1913 257 24.71 18.71 23.06 0 661.64 282.21 44527 +1913 258 23.06 17.06 21.41 0.45 605.1 214.33 44323 +1913 259 23.67 17.67 22.02 0.03 625.5 211.03 44119 +1913 260 18.84 12.84 17.19 1.21 478.79 220.18 43915 +1913 261 19.36 13.36 17.71 0.17 493.03 217.34 43711 +1913 262 22.59 16.59 20.94 0 589.76 278.08 43507 +1913 263 19.43 13.43 17.78 0.78 494.97 213.65 43303 +1913 264 18.56 12.56 16.91 1.6 471.27 213.43 43099 +1913 265 22.05 16.05 20.4 0.5 572.55 204.49 42894 +1913 266 19.63 13.63 17.98 0.05 500.56 207.81 42690 +1913 267 12.72 6.72 11.07 0 335.82 289.27 42486 +1913 268 11.13 5.13 9.48 0.04 305.31 216.96 42282 +1913 269 13.67 7.67 12.02 0 355.26 282.45 42078 +1913 270 19.19 13.19 17.54 0.3 488.33 201.04 41875 +1913 271 18.1 12.1 16.45 1.31 459.14 201.08 41671 +1913 272 18.29 12.29 16.64 0.23 464.12 198.74 41468 +1913 273 18.69 12.69 17.04 0.14 474.75 196.18 41265 +1913 274 13.73 7.73 12.08 0 356.52 269.07 41062 +1913 275 14.9 8.9 13.25 0 381.86 264.19 40860 +1913 276 14.3 8.3 12.65 0 368.68 262.59 40658 +1913 277 12.11 6.11 10.46 0 323.82 263.57 40456 +1913 278 13.56 7.56 11.91 0.01 352.96 193.76 40255 +1913 279 10.25 4.25 8.6 0.01 289.48 195.4 40054 +1913 280 9.87 3.87 8.22 0 282.86 258.35 39854 +1913 281 6.06 0.06 4.41 0 223.35 260.03 39654 +1913 282 5.02 -0.98 3.37 0 209.11 258.24 39455 +1913 283 8.24 2.24 6.59 0 255.92 251.95 39256 +1913 284 9.02 3.02 7.37 0 268.52 247.95 39058 +1913 285 9.08 3.08 7.43 0.07 269.51 183.9 38861 +1913 286 8.79 2.79 7.14 0.04 264.75 182.05 38664 +1913 287 10.38 4.38 8.73 0 291.77 237.81 38468 +1913 288 11.89 5.89 10.24 0 319.59 232.98 38273 +1913 289 15.72 9.72 14.07 0 400.51 224.36 38079 +1913 290 17.73 11.73 16.08 0 449.57 217.85 37885 +1913 291 19.1 13.1 17.45 0 485.86 212.48 37693 +1913 292 16.66 10.66 15.01 0.27 422.85 160.96 37501 +1913 293 17.03 11.03 15.38 0.84 431.94 158.46 37311 +1913 294 15.42 9.42 13.77 0 393.6 211.25 37121 +1913 295 17.61 11.61 15.96 0 446.5 204.66 36933 +1913 296 17.82 11.82 16.17 0 451.88 201.77 36745 +1913 297 18.14 12.14 16.49 0 460.18 198.55 36560 +1913 298 22.24 16.24 20.59 0.81 578.56 140.59 36375 +1913 299 17.59 11.59 15.94 0.59 446 145.76 36191 +1913 300 15.11 9.11 13.46 0 386.56 195.86 36009 +1913 301 17.93 11.93 16.28 0 454.72 188.75 35829 +1913 302 16 10 14.35 0.1 407.06 142.1 35650 +1913 303 15.35 9.35 13.7 0 392 187.96 35472 +1913 304 14.09 8.09 12.44 0 364.16 187.37 35296 +1913 305 14.18 8.18 12.53 0 366.09 184.55 35122 +1913 306 17.5 11.5 15.85 0 443.71 177.34 34950 +1913 307 15.58 9.58 13.93 1.95 397.27 133.44 34779 +1913 308 13.74 7.74 12.09 0 356.73 177.93 34610 +1913 309 13.31 7.31 11.66 0 347.78 176.21 34444 +1913 310 10.81 4.81 9.16 0 299.47 176.71 34279 +1913 311 14.2 8.2 12.55 0 366.52 170.55 34116 +1913 312 12.06 6.06 10.41 0.38 322.85 127.92 33956 +1913 313 8.5 2.5 6.85 0.25 260.06 129.07 33797 +1913 314 6.49 0.49 4.84 0.1 229.48 128.87 33641 +1913 315 6.42 0.42 4.77 0 228.47 169.34 33488 +1913 316 8.25 2.25 6.6 0 256.08 165.65 33337 +1913 317 14.22 8.22 12.57 0 366.95 157.25 33188 +1913 318 13.68 7.68 12.03 0 355.47 155.62 33042 +1913 319 11.19 5.19 9.54 0.16 306.42 117.53 32899 +1913 320 7.32 1.32 5.67 0 241.71 158.33 32758 +1913 321 9.87 3.87 8.22 0 282.86 154.06 32620 +1913 322 10.83 4.83 9.18 0.19 299.83 113.52 32486 +1913 323 7.32 1.32 5.67 1.61 241.71 114.6 32354 +1913 324 6.15 0.15 4.5 0.19 224.62 113.71 32225 +1913 325 8.18 2.18 6.53 0 254.97 148.36 32100 +1913 326 8.49 2.49 6.84 0.01 259.9 110 31977 +1913 327 9.68 3.68 8.03 0 279.6 143.83 31858 +1913 328 8.87 2.87 7.22 0.37 266.06 106.92 31743 +1913 329 8.04 2.04 6.39 0.49 252.77 106.31 31631 +1913 330 7.06 1.06 5.41 0.01 237.82 105.78 31522 +1913 331 6.5 0.5 4.85 0.22 229.62 105.09 31417 +1913 332 8.85 2.85 7.2 0.39 265.73 102.56 31316 +1913 333 3.19 -2.81 1.54 0 185.95 139.43 31218 +1913 334 6.3 0.3 4.65 0 226.75 136.44 31125 +1913 335 2.62 -3.38 0.97 0 179.21 137.45 31035 +1913 336 4.92 -1.08 3.27 0 207.79 135.08 30949 +1913 337 3.46 -2.54 1.81 0 189.23 134.25 30867 +1913 338 0.39 -5.61 -1.26 0 154.8 134.82 30790 +1913 339 0.83 -5.17 -0.82 0.97 159.38 100.37 30716 +1913 340 0.77 -5.23 -0.88 0.01 158.75 99.83 30647 +1913 341 0.71 -5.29 -0.94 0.33 158.12 99.15 30582 +1913 342 3.54 -2.46 1.89 0.67 190.2 97.54 30521 +1913 343 4.73 -1.27 3.08 0.2 205.29 96.42 30465 +1913 344 5.4 -0.6 3.75 0 214.22 127.03 30413 +1913 345 7.2 1.2 5.55 0.21 239.91 94.09 30366 +1913 346 3.21 -2.79 1.56 0 186.2 127.28 30323 +1913 347 4.27 -1.73 2.62 0 199.34 126.12 30284 +1913 348 1.84 -4.16 0.19 0 170.32 127.01 30251 +1913 349 4.86 -1.14 3.21 0 206.99 125.05 30221 +1913 350 9.18 3.18 7.53 0.03 271.17 91.39 30197 +1913 351 8.01 2.01 6.36 0 252.3 122.5 30177 +1913 352 7.14 1.14 5.49 0 239.01 123 30162 +1913 353 4.33 -1.67 2.68 0 200.11 124.64 30151 +1913 354 1.16 -4.84 -0.49 0 162.88 126.19 30145 +1913 355 3.12 -2.88 1.47 0 185.11 125.25 30144 +1913 356 2.39 -3.61 0.74 0 176.55 125.64 30147 +1913 357 5.54 -0.46 3.89 0 216.13 123.99 30156 +1913 358 5.1 -0.9 3.45 0.03 210.18 93.26 30169 +1913 359 6.05 0.05 4.4 0.2 223.21 92.92 30186 +1913 360 6.36 0.36 4.71 1.2 227.61 93.04 30208 +1913 361 6.75 0.75 5.1 0.19 233.25 93.1 30235 +1913 362 4.7 -1.3 3.05 0.66 204.89 94.37 30267 +1913 363 3.03 -2.97 1.38 0.62 184.04 95.49 30303 +1913 364 8.62 2.62 6.97 0 261.99 124.24 30343 +1913 365 8.92 2.92 7.27 0.31 266.88 93.43 30388 +1914 1 0.73 -5.27 -0.92 0 158.33 130.28 30438 +1914 2 -4.41 -10.41 -6.06 0 111.81 132.95 30492 +1914 3 -7 -13 -8.65 0 93.25 134.64 30551 +1914 4 -3.25 -9.25 -4.9 0.05 121.12 144.11 30614 +1914 5 -0.22 -6.22 -1.87 0 148.65 177.13 30681 +1914 6 1.43 -4.57 -0.22 0 165.8 134.11 30752 +1914 7 -3.24 -9.24 -4.89 0 121.2 136.82 30828 +1914 8 -2.24 -8.24 -3.89 0 129.76 137.96 30907 +1914 9 -1.36 -7.36 -3.01 0 137.72 138.89 30991 +1914 10 -0.31 -6.31 -1.96 0 147.76 139.77 31079 +1914 11 -1.16 -7.16 -2.81 0 139.58 141.13 31171 +1914 12 0.75 -5.25 -0.9 0.59 158.54 105.98 31266 +1914 13 -0.5 -6.5 -2.15 0.45 145.9 151.09 31366 +1914 14 -5.42 -11.42 -7.07 0.05 104.22 153.59 31469 +1914 15 -4.75 -10.75 -6.4 0.12 109.21 154.75 31575 +1914 16 -4.8 -10.8 -6.45 0 108.83 192.94 31686 +1914 17 -6.88 -12.88 -8.53 0 94.04 195.14 31800 +1914 18 -6.19 -12.19 -7.84 0 98.74 196.71 31917 +1914 19 -4.26 -10.26 -5.91 0 112.98 197.88 32038 +1914 20 -1.18 -7.18 -2.83 0 139.39 198.12 32161 +1914 21 2.27 -3.73 0.62 0 175.17 197.99 32289 +1914 22 -1.39 -7.39 -3.04 0 137.44 201.39 32419 +1914 23 -5.12 -11.12 -6.77 0.7 106.43 165.93 32552 +1914 24 -6.39 -12.39 -8.04 0 97.36 208.85 32688 +1914 25 -3.37 -9.37 -5.02 0 120.12 209.53 32827 +1914 26 -5.85 -11.85 -7.5 0 101.13 212.19 32969 +1914 27 0.74 -5.26 -0.91 0 158.43 211.19 33114 +1914 28 0.41 -5.59 -1.24 0 155.01 213.34 33261 +1914 29 -1.24 -7.24 -2.89 0.17 138.83 173.49 33411 +1914 30 -1.09 -7.09 -2.74 0 140.24 218.86 33564 +1914 31 0.5 -5.5 -1.15 0 155.94 220.19 33718 +1914 32 5.64 -0.36 3.99 0 217.5 218.14 33875 +1914 33 2.81 -3.19 1.16 0.27 181.43 177.04 34035 +1914 34 1.65 -4.35 0 0.03 168.21 178.85 34196 +1914 35 3.59 -2.41 1.94 0.01 190.82 178.92 34360 +1914 36 3.27 -2.73 1.62 0 186.92 227.21 34526 +1914 37 5.51 -0.49 3.86 0 215.72 227.17 34694 +1914 38 6.41 0.41 4.76 0 228.32 228.23 34863 +1914 39 7.81 1.81 6.16 0.07 249.19 143.56 35035 +1914 40 5.46 -0.54 3.81 0.53 215.04 147.04 35208 +1914 41 3.38 -2.62 1.73 0 188.25 200.25 35383 +1914 42 1.39 -4.61 -0.26 0 165.37 204.15 35560 +1914 43 -1.5 -7.5 -3.15 0 136.42 208.55 35738 +1914 44 -1.57 -7.57 -3.22 0 135.78 211.19 35918 +1914 45 -3.32 -9.32 -4.97 0 120.54 214.72 36099 +1914 46 -4.89 -10.89 -6.54 0 108.15 218.16 36282 +1914 47 -7 -13 -8.65 0 93.25 221.88 36466 +1914 48 -7.73 -13.73 -9.38 0 88.52 225.01 36652 +1914 49 -3.38 -9.38 -5.03 0 120.04 226.04 36838 +1914 50 -1.85 -7.85 -3.5 0 133.23 227.97 37026 +1914 51 0.64 -5.36 -1.01 0 157.39 229.5 37215 +1914 52 -0.06 -6.06 -1.71 0 150.24 232.81 37405 +1914 53 3.67 -2.33 2.02 0 191.8 233.13 37596 +1914 54 7.46 1.46 5.81 0 243.83 232.39 37788 +1914 55 3.9 -2.1 2.25 0 194.66 238.72 37981 +1914 56 2.47 -3.53 0.82 0 177.47 242.58 38175 +1914 57 0.8 -5.2 -0.85 0 159.06 246.71 38370 +1914 58 -0.38 -6.38 -2.03 0 147.07 250.47 38565 +1914 59 0.18 -5.82 -1.47 0 152.66 252.85 38761 +1914 60 10.72 4.72 9.07 0 297.85 245.43 38958 +1914 61 10.49 4.49 8.84 0.01 293.72 186.47 39156 +1914 62 11.18 5.18 9.53 0.29 306.24 187.82 39355 +1914 63 9.34 3.34 7.69 0.01 273.84 191.9 39553 +1914 64 8.56 2.56 6.91 0 261.02 259.72 39753 +1914 65 10.54 4.54 8.89 0.67 294.62 195 39953 +1914 66 12.06 6.06 10.41 0.88 322.85 195.36 40154 +1914 67 10.32 4.32 8.67 0.03 290.71 199.41 40355 +1914 68 13.46 7.46 11.81 0 350.88 263.86 40556 +1914 69 11.12 5.12 9.47 0.47 305.13 202.62 40758 +1914 70 10.06 4.06 8.41 0.68 286.15 205.87 40960 +1914 71 6.18 0.18 4.53 0.07 225.05 211.69 41163 +1914 72 6.93 0.93 5.28 0 235.89 284.23 41366 +1914 73 10.19 4.19 8.54 0 288.42 282.64 41569 +1914 74 8.19 2.19 6.54 0 255.13 288.1 41772 +1914 75 9.49 3.49 7.84 0 276.37 289.08 41976 +1914 76 9.95 3.95 8.3 0 284.24 291.04 42179 +1914 77 11.7 5.7 10.05 0 315.97 290.92 42383 +1914 78 7.21 1.21 5.56 0 240.06 299.98 42587 +1914 79 5.59 -0.41 3.94 0 216.82 304.64 42791 +1914 80 6.34 0.34 4.69 0.23 227.32 229.75 42996 +1914 81 8.71 2.71 7.06 0 263.45 305.87 43200 +1914 82 10.16 4.16 8.51 0.04 287.9 229.8 43404 +1914 83 10.93 4.93 9.28 0 301.65 307.66 43608 +1914 84 7.08 1.08 5.43 0.87 238.11 236.81 43812 +1914 85 8.6 2.6 6.95 0.24 261.67 237.16 44016 +1914 86 9.25 3.25 7.6 0 272.34 317.68 44220 +1914 87 6.56 0.56 4.91 0.11 230.49 242.93 44424 +1914 88 6.08 0.08 4.43 0 223.63 326.87 44627 +1914 89 3.41 -2.59 1.76 0.36 188.62 249.15 44831 +1914 90 8.15 2.15 6.5 0 254.5 328.83 45034 +1914 91 16.96 10.96 15.31 0 430.2 314.46 45237 +1914 92 19 13 17.35 0 483.13 311.35 45439 +1914 93 16.2 10.2 14.55 0 411.79 320.61 45642 +1914 94 15.98 9.98 14.33 0 406.59 323.22 45843 +1914 95 19.42 13.42 17.77 0.02 494.69 237.29 46045 +1914 96 16.03 10.03 14.38 0.19 407.77 245.44 46246 +1914 97 15.76 9.76 14.11 0 401.44 329.89 46446 +1914 98 14.64 8.64 12.99 0.45 376.1 250.76 46647 +1914 99 13.41 7.41 11.76 0 349.85 338.94 46846 +1914 100 10.19 4.19 8.54 0.09 288.42 260.16 47045 +1914 101 12.11 6.11 10.46 0 323.82 345.37 47243 +1914 102 16.26 10.26 14.61 0.07 413.22 253.68 47441 +1914 103 16.44 10.44 14.79 0.11 417.53 254.7 47638 +1914 104 17.16 11.16 15.51 0.55 435.17 254.66 47834 +1914 105 11.8 5.8 10.15 0 317.87 353.32 48030 +1914 106 8.45 2.45 6.8 0.16 259.26 270.56 48225 +1914 107 9.62 3.62 7.97 0.05 278.57 270.41 48419 +1914 108 10.35 4.35 8.7 0 291.24 361.06 48612 +1914 109 15.81 9.81 14.16 0 402.61 351.25 48804 +1914 110 16.72 10.72 15.07 0 424.32 350.34 48995 +1914 111 11.7 5.7 10.05 0 315.97 363.17 49185 +1914 112 12.28 6.28 10.63 0.02 327.13 272.67 49374 +1914 113 12.85 6.85 11.2 0 338.42 363.74 49561 +1914 114 15.66 9.66 14.01 0 399.12 358.84 49748 +1914 115 17.57 11.57 15.92 0 445.49 355.24 49933 +1914 116 17.8 11.8 16.15 0 451.37 355.79 50117 +1914 117 14.32 8.32 12.67 0 369.11 365.96 50300 +1914 118 10.81 4.81 9.16 0 299.47 374.57 50481 +1914 119 11.28 5.28 9.63 0 308.09 374.89 50661 +1914 120 12.22 6.22 10.57 0 325.96 374.21 50840 +1914 121 14.25 8.25 12.6 2.54 367.6 278.19 51016 +1914 122 15.57 9.57 13.92 1.65 397.04 276.7 51191 +1914 123 13.71 7.71 12.06 0 356.1 374.39 51365 +1914 124 17.11 11.11 15.46 0.14 433.92 275.23 51536 +1914 125 16.31 10.31 14.66 0.51 414.42 277.58 51706 +1914 126 18.52 12.52 16.87 1.02 470.21 273.64 51874 +1914 127 19.8 13.8 18.15 0.42 505.35 271.3 52039 +1914 128 23.41 17.41 21.76 0.44 616.73 262.27 52203 +1914 129 19.86 13.86 18.21 1.94 507.05 272.5 52365 +1914 130 17.89 11.89 16.24 0.73 453.69 277.65 52524 +1914 131 17.64 11.64 15.99 0.56 447.27 278.78 52681 +1914 132 16.57 10.57 14.92 0.33 420.67 281.64 52836 +1914 133 16.3 10.3 14.65 0 414.18 376.95 52989 +1914 134 16.22 10.22 14.57 0.03 412.27 283.4 53138 +1914 135 14.41 8.41 12.76 0.54 371.06 287.36 53286 +1914 136 15.19 9.19 13.54 0 388.37 381.88 53430 +1914 137 18.76 12.76 17.11 0 476.63 372.59 53572 +1914 138 16.66 10.66 15.01 0 422.85 379.32 53711 +1914 139 17.4 11.4 15.75 0.01 441.18 283.45 53848 +1914 140 13.79 7.79 12.14 0.06 357.78 290.83 53981 +1914 141 9.43 3.43 7.78 0 275.36 397.12 54111 +1914 142 10.04 4.04 8.39 0 285.8 396.53 54238 +1914 143 16.09 10.09 14.44 0 409.18 383.52 54362 +1914 144 16.76 10.76 15.11 0 425.29 382.17 54483 +1914 145 17.14 11.14 15.49 0 434.67 381.57 54600 +1914 146 18.48 12.48 16.83 0 469.14 377.98 54714 +1914 147 14.56 8.56 12.91 0 374.34 389.25 54824 +1914 148 21.11 15.11 19.46 0 543.61 370.08 54931 +1914 149 19.18 13.18 17.53 0 488.06 376.94 55034 +1914 150 20.17 14.17 18.52 0.45 515.92 280.5 55134 +1914 151 17.14 11.14 15.49 0.01 434.67 287.89 55229 +1914 152 22.95 16.95 21.3 0 601.48 364.24 55321 +1914 153 21.84 15.84 20.19 0 565.97 368.77 55409 +1914 154 22.96 16.96 21.31 0.96 601.8 273.56 55492 +1914 155 23.92 17.92 22.27 1.47 634.03 270.75 55572 +1914 156 19.53 13.53 17.88 0.45 497.76 283.27 55648 +1914 157 20.88 14.88 19.23 0 536.72 373.25 55719 +1914 158 22.97 16.97 21.32 0.06 602.13 274.15 55786 +1914 159 19.17 13.17 17.52 0 487.78 379.45 55849 +1914 160 21.24 15.24 19.59 0.1 547.53 279.41 55908 +1914 161 20.36 14.36 18.71 1.33 521.41 281.8 55962 +1914 162 19.79 13.79 18.14 1.45 505.07 283.3 56011 +1914 163 19.12 13.12 17.47 0.24 486.41 285.1 56056 +1914 164 20.24 14.24 18.59 0 517.94 376.46 56097 +1914 165 18.91 12.91 17.26 0 480.69 380.95 56133 +1914 166 19.44 13.44 17.79 0.41 495.25 284.49 56165 +1914 167 20.18 14.18 18.53 2.19 516.2 282.59 56192 +1914 168 21.33 15.33 19.68 0 550.27 372.8 56214 +1914 169 20.76 14.76 19.11 0 533.15 374.86 56231 +1914 170 15.1 9.1 13.45 0 386.34 391.95 56244 +1914 171 18.26 12.26 16.61 0 463.33 383.16 56252 +1914 172 20.87 14.87 19.22 0 536.42 374.52 56256 +1914 173 22.82 16.82 21.17 0.01 597.22 275.37 56255 +1914 174 17.71 11.71 16.06 0.04 449.06 288.53 56249 +1914 175 13.8 7.8 12.15 0 357.99 395.05 56238 +1914 176 16.35 10.35 14.7 0 415.37 388.52 56223 +1914 177 18.02 12.02 16.37 0 457.05 383.61 56203 +1914 178 18.15 12.15 16.5 0 460.44 383.24 56179 +1914 179 19.98 13.98 18.33 0 510.47 377.26 56150 +1914 180 17.37 11.37 15.72 0.01 440.43 289 56116 +1914 181 18.38 12.38 16.73 0 466.49 382.23 56078 +1914 182 17.94 11.94 16.29 0.69 454.98 287.57 56035 +1914 183 20.01 14.01 18.36 1.19 511.32 282.48 55987 +1914 184 24.13 18.13 22.48 0.01 641.27 270.6 55935 +1914 185 26.77 20.77 25.12 0.34 738.45 261.47 55879 +1914 186 24.81 18.81 23.16 1 665.2 268.14 55818 +1914 187 25.72 19.72 24.07 1.2 698.41 264.92 55753 +1914 188 24.27 18.27 22.62 0.81 646.14 269.57 55684 +1914 189 22.13 16.13 20.48 1.08 575.07 275.93 55611 +1914 190 23.49 17.49 21.84 1.52 619.42 271.62 55533 +1914 191 20.58 14.58 18.93 0.18 527.84 279.69 55451 +1914 192 22.55 16.55 20.9 0 588.47 365.36 55366 +1914 193 23.53 17.53 21.88 0 620.77 361.18 55276 +1914 194 22.83 16.83 21.18 1.82 597.55 272.84 55182 +1914 195 23.95 17.95 22.3 0.16 635.06 269.22 55085 +1914 196 20.96 14.96 19.31 1.27 539.11 277.58 54984 +1914 197 17.28 11.28 15.63 0.64 438.16 286.06 54879 +1914 198 15.87 9.87 14.22 0.72 404.01 288.65 54770 +1914 199 16.2 10.2 14.55 0.22 411.79 287.72 54658 +1914 200 12.82 6.82 11.17 0 337.82 391.44 54542 +1914 201 18.39 12.39 16.74 0 466.76 376.46 54423 +1914 202 16.29 10.29 14.64 1.46 413.94 286.44 54301 +1914 203 20.33 14.33 18.68 0.36 520.54 276.85 54176 +1914 204 20.12 14.12 18.47 1.1 514.48 277 54047 +1914 205 17.26 11.26 15.61 0.45 437.66 283.24 53915 +1914 206 21.43 15.43 19.78 0.08 553.32 272.77 53780 +1914 207 21.96 15.96 20.31 0 569.72 361.1 53643 +1914 208 24.77 18.77 23.12 0.77 663.78 261.88 53502 +1914 209 24.45 18.45 22.8 0.42 652.44 262.44 53359 +1914 210 20.07 14.07 18.42 0.03 513.04 274.37 53213 +1914 211 25.04 19.04 23.39 0.15 673.47 259.52 53064 +1914 212 20.89 14.89 19.24 0 537.02 361.47 52913 +1914 213 21.58 15.58 19.93 0.01 557.92 268.71 52760 +1914 214 20.58 14.58 18.93 0.79 527.84 270.78 52604 +1914 215 21.04 15.04 19.39 0 541.5 358.78 52445 +1914 216 20.91 14.91 19.26 0 537.61 358.22 52285 +1914 217 25.58 19.58 23.93 0 693.21 338.95 52122 +1914 218 22.06 16.06 20.41 0.21 572.86 264.33 51958 +1914 219 22 16 20.35 0 570.98 351.62 51791 +1914 220 19.6 13.6 17.95 1.83 499.72 269.15 51622 +1914 221 20.49 14.49 18.84 0.18 525.2 266.23 51451 +1914 222 22.94 16.94 21.29 0 601.15 345.18 51279 +1914 223 22.15 16.15 20.5 0.04 575.7 260.26 51105 +1914 224 19.33 13.33 17.68 0 492.19 355.46 50929 +1914 225 20.16 14.16 18.51 0 515.63 351.68 50751 +1914 226 22.92 16.92 21.27 0 600.49 340.87 50572 +1914 227 19.75 13.75 18.1 0 503.94 350.57 50392 +1914 228 21.65 15.65 20 0.04 560.08 257.28 50210 +1914 229 20.65 14.65 19 0 529.9 345.22 50026 +1914 230 21.42 15.42 19.77 0 553.01 341.36 49842 +1914 231 24.65 18.65 23 0 659.51 327.78 49656 +1914 232 26.75 20.75 25.1 0 737.67 317.39 49469 +1914 233 23.81 17.81 22.16 0 630.27 328.47 49280 +1914 234 26.61 20.61 24.96 0 732.23 315.36 49091 +1914 235 25.76 19.76 24.11 0.21 699.9 238.28 48900 +1914 236 26.39 20.39 24.74 0.12 723.74 235.21 48709 +1914 237 23.03 17.03 21.38 0 604.11 325.63 48516 +1914 238 22.31 16.31 20.66 0 580.78 326.59 48323 +1914 239 17.83 11.83 16.18 0 452.14 339 48128 +1914 240 18.71 12.71 17.06 0.62 475.29 251.09 47933 +1914 241 23.27 17.27 21.62 0.83 612.06 238.72 47737 +1914 242 24.1 18.1 22.45 0 640.23 313.5 47541 +1914 243 22.7 16.7 21.05 0 593.32 316.85 47343 +1914 244 15.89 9.89 14.24 0.04 404.48 251.19 47145 +1914 245 20.38 14.38 18.73 0 522 320.91 46947 +1914 246 19.48 13.48 17.83 0.44 496.36 241.24 46747 +1914 247 15.34 9.34 13.69 0.17 391.77 247.84 46547 +1914 248 19.05 13.05 17.4 0 484.5 319.11 46347 +1914 249 15.21 9.21 13.56 0.03 388.82 245.01 46146 +1914 250 14.68 8.68 13.03 0 376.98 325.86 45945 +1914 251 16 10 14.35 0.04 407.06 240.57 45743 +1914 252 16.09 10.09 14.44 0 409.18 318.38 45541 +1914 253 20.88 14.88 19.23 0 536.72 303.51 45339 +1914 254 17.79 11.79 16.14 0 451.11 309.99 45136 +1914 255 17.32 11.32 15.67 0.08 439.17 231.68 44933 +1914 256 19.12 13.12 17.47 0.22 486.41 226.52 44730 +1914 257 17.87 11.87 16.22 0.66 453.17 227.35 44527 +1914 258 20.7 14.7 19.05 1.98 531.38 219.87 44323 +1914 259 20.63 14.63 18.98 0.66 529.31 218.24 44119 +1914 260 18.14 12.14 16.49 0.3 460.18 221.52 43915 +1914 261 18.75 12.75 17.1 0.69 476.36 218.54 43711 +1914 262 19.89 13.89 18.24 0.01 507.9 214.53 43507 +1914 263 23.28 17.28 21.63 0 612.39 273.5 43303 +1914 264 26.54 20.54 24.89 0 729.52 259.41 43099 +1914 265 21.89 15.89 20.24 0.05 567.53 204.85 42894 +1914 266 17.73 11.73 16.08 0.52 449.57 211.35 42690 +1914 267 15.99 9.99 14.34 0.68 406.83 212.26 42486 +1914 268 15.48 9.48 13.83 0.94 394.97 211.13 42282 +1914 269 17.23 11.23 15.58 0 436.91 275.27 42078 +1914 270 13.63 7.63 11.98 0.05 354.42 209.9 41875 +1914 271 13.05 7.05 11.4 0.52 342.47 208.68 41671 +1914 272 8.95 2.95 7.3 0.23 267.37 211.26 41468 +1914 273 10.61 4.61 8.96 0.04 295.87 207.58 41265 +1914 274 3.55 -2.45 1.9 0.05 190.33 211.74 41062 +1914 275 9.23 3.23 7.58 0.98 272 204.86 40860 +1914 276 10.49 4.49 8.84 0 293.72 268.67 40658 +1914 277 11.39 5.39 9.74 0 310.13 264.67 40456 +1914 278 8.92 2.92 7.27 0 266.88 265.15 40255 +1914 279 10.22 4.22 8.57 0 288.95 260.58 40054 +1914 280 12.79 6.79 11.14 0 337.22 254.13 39854 +1914 281 12.43 6.43 10.78 0 330.07 251.96 39654 +1914 282 12.17 6.17 10.52 0 324.99 249.6 39455 +1914 283 5.94 -0.06 4.29 0 221.67 254.44 39256 +1914 284 8.5 2.5 6.85 0 260.06 248.57 39058 +1914 285 7.83 1.83 6.18 0 249.5 246.64 38861 +1914 286 11.02 5.02 9.37 0 303.3 239.92 38664 +1914 287 10.91 4.91 9.26 0.07 301.29 177.84 38468 +1914 288 12.69 6.69 11.04 0 335.22 231.83 38273 +1914 289 13.27 7.27 11.62 0.04 346.96 171.26 38079 +1914 290 16.07 10.07 14.42 0 408.71 220.94 37885 +1914 291 17.88 11.88 16.23 0 453.43 214.94 37693 +1914 292 13.66 7.66 12.01 0 355.05 219.56 37501 +1914 293 15.08 9.08 13.43 0 385.89 214.64 37311 +1914 294 16.08 10.08 14.43 0 408.95 210.14 37121 +1914 295 18.15 12.15 16.5 0 460.44 203.65 36933 +1914 296 16.8 10.8 15.15 0 426.27 203.61 36745 +1914 297 12.87 6.87 11.22 0 338.83 207.04 36560 +1914 298 13.26 7.26 11.61 0 346.76 203.92 36375 +1914 299 16.53 10.53 14.88 0.19 419.7 147.14 36191 +1914 300 16.66 10.66 15.01 0.07 422.85 145.04 36009 +1914 301 13.13 7.13 11.48 0 344.1 196.22 35829 +1914 302 17.3 11.3 15.65 0.72 438.67 140.5 35650 +1914 303 16.96 10.96 15.31 0.55 430.2 139.06 35472 +1914 304 12.49 6.49 10.84 0.07 331.25 142.11 35296 +1914 305 3.26 -2.74 1.61 0 186.8 195.51 35122 +1914 306 2.98 -3.02 1.33 0 183.44 193.4 34950 +1914 307 7.67 1.67 6.02 0 247.03 187.17 34779 +1914 308 3.41 -2.59 1.76 0 188.62 187.9 34610 +1914 309 5.09 -0.91 3.44 0 210.05 184.34 34444 +1914 310 3.01 -2.99 1.36 0.6 183.8 137.5 34279 +1914 311 5.38 -0.62 3.73 0 213.95 179.45 34116 +1914 312 5.89 -0.11 4.24 0 220.97 176.4 33956 +1914 313 6.2 0.2 4.55 0 225.33 174.02 33797 +1914 314 9.67 3.67 8.02 0 279.43 169.05 33641 +1914 315 9.41 3.41 7.76 0 275.02 166.78 33488 +1914 316 11.04 5.04 9.39 0 303.66 163 33337 +1914 317 6.47 0.47 4.82 0.61 229.19 123.68 33188 +1914 318 6.68 0.68 5.03 0 232.23 162.4 33042 +1914 319 4.46 -1.54 2.81 0 201.78 162.28 32899 +1914 320 8.06 2.06 6.41 0 253.08 157.73 32758 +1914 321 10.11 4.11 8.46 0 287.02 153.84 32620 +1914 322 12.12 6.12 10.47 0 324.02 150.05 32486 +1914 323 12.45 6.45 10.8 0.31 330.46 111.1 32354 +1914 324 8.95 2.95 7.3 0 267.37 149.43 32225 +1914 325 8.89 2.89 7.24 0.06 266.38 110.83 32100 +1914 326 7.85 1.85 6.2 0.06 249.81 110.38 31977 +1914 327 1.01 -4.99 -0.64 0 161.28 149.62 31858 +1914 328 5.36 -0.64 3.71 0 213.68 145.14 31743 +1914 329 5.63 -0.37 3.98 0 217.37 143.47 31631 +1914 330 7.31 1.31 5.66 0 241.56 140.86 31522 +1914 331 8.09 2.09 6.44 0 253.55 138.96 31417 +1914 332 4.12 -1.88 2.47 0.04 197.43 105 31316 +1914 333 3.41 -2.59 1.76 0.02 188.62 104.48 31218 +1914 334 2.44 -3.56 0.79 0 177.12 138.73 31125 +1914 335 2.27 -3.73 0.62 0 175.17 137.63 31035 +1914 336 3.98 -2.02 2.33 0 195.67 135.63 30949 +1914 337 4.52 -1.48 2.87 0 202.55 133.65 30867 +1914 338 9.92 3.92 8.27 0.1 283.72 96.7 30790 +1914 339 13.05 7.05 11.4 0 342.47 125.34 30716 +1914 340 10.89 4.89 9.24 0 300.92 126.64 30647 +1914 341 8 2 6.35 0 252.14 128.02 30582 +1914 342 8.81 2.81 7.16 0 265.08 126.67 30521 +1914 343 3.84 -2.16 2.19 0 193.91 129.06 30465 +1914 344 7.91 1.91 6.26 0 250.74 125.39 30413 +1914 345 8.12 2.12 6.47 0 254.02 124.82 30366 +1914 346 9.32 3.32 7.67 0.03 273.51 92.54 30323 +1914 347 10.34 4.34 8.69 0.17 291.06 91.49 30284 +1914 348 9.63 3.63 7.98 0.31 278.74 91.66 30251 +1914 349 8.31 2.31 6.66 0.85 257.03 92.12 30221 +1914 350 6.06 0.06 4.41 1.88 223.35 93 30197 +1914 351 2.04 -3.96 0.39 0.88 172.56 94.48 30177 +1914 352 0.47 -5.53 -1.18 1.52 155.63 94.94 30162 +1914 353 1.77 -4.23 0.12 0.22 169.54 94.46 30151 +1914 354 3.02 -2.98 1.37 0 183.92 125.3 30145 +1914 355 8.36 2.36 6.71 0.3 257.82 91.55 30144 +1914 356 8.07 2.07 6.42 0.04 253.24 91.72 30147 +1914 357 5.56 -0.44 3.91 0.16 216.41 92.99 30156 +1914 358 3.13 -2.87 1.48 0 185.23 125.42 30169 +1914 359 1.36 -4.64 -0.29 0 165.04 126.39 30186 +1914 360 0.41 -5.59 -1.24 0 155.01 127.18 30208 +1914 361 -2.97 -8.97 -4.62 0.01 123.46 140.3 30235 +1914 362 -0.39 -6.39 -2.04 0.24 146.97 140.62 30267 +1914 363 2.51 -3.49 0.86 0 177.93 171.59 30303 +1914 364 6.04 0.04 4.39 0.07 223.07 94.5 30343 +1914 365 8.49 2.49 6.84 0 259.9 124.9 30388 +1915 1 8.05 2.05 6.4 1.13 252.93 94.57 30438 +1915 2 5.5 -0.5 3.85 0.92 215.58 96.38 30492 +1915 3 3.82 -2.18 2.17 2.63 193.66 97.82 30551 +1915 4 -2.08 -8.08 -3.73 0.73 131.17 145.93 30614 +1915 5 2.38 -3.62 0.73 0.22 176.43 144.56 30681 +1915 6 8.19 2.19 6.54 0.09 255.13 141.36 30752 +1915 7 8.38 2.38 6.73 1.28 258.14 98.02 30828 +1915 8 11.59 5.59 9.94 0.28 313.89 97.12 30907 +1915 9 6.09 0.09 4.44 0 223.77 135.03 30991 +1915 10 2.92 -3.08 1.27 0.02 182.73 103.66 31079 +1915 11 4.47 -1.53 2.82 0.49 201.91 103.74 31171 +1915 12 5.15 -0.85 3.5 0 210.85 138.91 31266 +1915 13 6.69 0.69 5.04 0.1 232.37 104.63 31366 +1915 14 6.89 0.89 5.24 0 235.3 140.82 31469 +1915 15 6.14 0.14 4.49 0 224.48 142.78 31575 +1915 16 7.86 1.86 6.21 0 249.96 142.8 31686 +1915 17 7.66 1.66 6.01 0.02 246.88 108.47 31800 +1915 18 6.21 0.21 4.56 0 225.47 147.56 31917 +1915 19 4.64 -1.36 2.99 0 204.11 150.54 32038 +1915 20 3.7 -2.3 2.05 0 192.17 152.71 32161 +1915 21 5.98 -0.02 4.33 0.17 222.23 114.91 32289 +1915 22 5.68 -0.32 4.03 0 218.05 155.17 32419 +1915 23 2.51 -3.49 0.86 0.12 177.93 119.21 32552 +1915 24 1.99 -4.01 0.34 0.14 172 120.99 32688 +1915 25 0.55 -5.45 -1.1 0 156.45 163.98 32827 +1915 26 -0.82 -6.82 -2.47 0 142.8 166.6 32969 +1915 27 -1.63 -7.63 -3.28 0 135.23 169.02 33114 +1915 28 1.73 -4.27 0.08 0.03 169.1 127.16 33261 +1915 29 1.05 -4.95 -0.6 1.29 161.71 129.24 33411 +1915 30 -2.13 -8.13 -3.78 0 130.73 176.16 33564 +1915 31 -5.46 -11.46 -7.11 0 103.93 179.89 33718 +1915 32 -2.5 -8.5 -4.15 0 127.48 180.87 33875 +1915 33 0.63 -5.37 -1.02 0 157.28 181.98 34035 +1915 34 -0.99 -6.99 -2.64 0 141.19 185.06 34196 +1915 35 2.33 -3.67 0.68 0 175.86 185.36 34360 +1915 36 3.31 -2.69 1.66 0 187.4 187.25 34526 +1915 37 4.81 -1.19 3.16 0 206.34 188.61 34694 +1915 38 5.62 -0.38 3.97 0.45 217.23 143.03 34863 +1915 39 4.14 -1.86 2.49 0 197.68 194.45 35035 +1915 40 1.99 -4.01 0.34 0 172 198.56 35208 +1915 41 7.44 1.44 5.79 0 243.52 196.94 35383 +1915 42 7.42 1.42 5.77 0 243.22 199.5 35560 +1915 43 6.18 0.18 4.53 0 225.05 203.3 35738 +1915 44 6.58 0.58 4.93 0.86 230.78 154.13 35918 +1915 45 2.77 -3.23 1.12 0 180.96 211.18 36099 +1915 46 3.2 -2.8 1.55 0.94 186.07 160.18 36282 +1915 47 3.99 -2.01 2.34 0.08 195.79 161.85 36466 +1915 48 5.83 -0.17 4.18 0 220.13 217.07 36652 +1915 49 4.76 -1.24 3.11 0.11 205.68 165.58 36838 +1915 50 1.93 -4.07 0.28 0 171.33 225.63 37026 +1915 51 4.2 -1.8 2.55 0 198.45 226.89 37215 +1915 52 4.85 -1.15 3.2 0.52 206.86 171.88 37405 +1915 53 5.46 -0.54 3.81 0 215.04 231.59 37596 +1915 54 4.1 -1.9 2.45 0 197.18 235.54 37788 +1915 55 5.38 -0.62 3.73 0 213.95 237.42 37981 +1915 56 6.46 0.46 4.81 0.05 229.04 179.31 38175 +1915 57 7.89 1.89 6.24 0 250.43 240.45 38370 +1915 58 7.78 1.78 6.13 0.29 248.73 182.61 38565 +1915 59 4.13 -1.87 2.48 0 197.56 249.8 38761 +1915 60 4.82 -1.18 3.17 0 206.47 252.07 38958 +1915 61 8.47 2.47 6.82 0 259.58 251.17 39156 +1915 62 7.85 1.85 6.2 0 249.81 254.67 39355 +1915 63 8.14 2.14 6.49 0 254.34 257.33 39553 +1915 64 8.24 2.24 6.59 0 255.92 260.1 39753 +1915 65 8.68 2.68 7.03 0 262.96 262.44 39953 +1915 66 5.5 -0.5 3.85 0.02 215.58 201.56 40154 +1915 67 4.75 -1.25 3.1 0 205.55 272.42 40355 +1915 68 4.53 -1.47 2.88 0 202.68 275.53 40556 +1915 69 2.01 -3.99 0.36 0 172.22 280.44 40758 +1915 70 5.12 -0.88 3.47 0.37 210.45 210.34 40960 +1915 71 6.1 0.1 4.45 0.01 223.91 211.75 41163 +1915 72 4.95 -1.05 3.3 1.77 208.18 214.8 41366 +1915 73 5.99 -0.01 4.34 0 222.37 287.98 41569 +1915 74 7.54 1.54 5.89 0.03 245.04 216.69 41772 +1915 75 7.57 1.57 5.92 0 245.5 291.61 41976 +1915 76 10.64 4.64 8.99 0 296.41 290.02 42179 +1915 77 11.87 5.87 10.22 0 319.2 290.64 42383 +1915 78 9.02 3.02 7.37 0 268.52 297.61 42587 +1915 79 11.49 5.49 9.84 0 312.01 296.59 42791 +1915 80 7.86 1.86 6.21 0 249.96 304.43 42996 +1915 81 9.8 3.8 8.15 0 281.65 304.3 43200 +1915 82 9.7 3.7 8.05 0 279.94 307.09 43404 +1915 83 8.33 2.33 6.68 0 257.34 311.54 43608 +1915 84 9.72 3.72 8.07 0 280.28 312.08 43812 +1915 85 4.4 -1.6 2.75 0.08 201 241.07 44016 +1915 86 5.84 -0.16 4.19 0 220.27 322.23 44220 +1915 87 4.17 -1.83 2.52 0 198.07 326.69 44424 +1915 88 0.26 -5.74 -1.39 0 153.47 332.81 44627 +1915 89 -5.64 -11.64 -7.29 0.06 102.63 283.99 44831 +1915 90 -2.06 -8.06 -3.71 0.22 131.35 284.45 45034 +1915 91 7.15 1.15 5.5 0 239.16 332.48 45237 +1915 92 8.39 2.39 6.74 0.03 258.3 249.76 45439 +1915 93 14.26 8.26 12.61 0.42 367.81 243.68 45642 +1915 94 13.94 7.94 12.29 0 360.96 327.7 45843 +1915 95 13.22 7.22 11.57 0.38 345.94 248.45 46045 +1915 96 12.71 6.71 11.06 0 335.62 334.36 46246 +1915 97 12.67 6.67 11.02 0 334.82 336.48 46446 +1915 98 15.86 9.86 14.21 0 403.78 331.58 46647 +1915 99 11.89 5.89 10.24 0 319.59 341.92 46846 +1915 100 9.32 3.32 7.67 0 273.51 348.31 47045 +1915 101 7.06 1.06 5.41 0.01 237.82 265.23 47243 +1915 102 6.78 0.78 5.13 0.08 233.69 266.97 47441 +1915 103 6.58 0.58 4.93 0 230.78 358.11 47638 +1915 104 11.15 5.15 9.5 0 305.68 352.73 47834 +1915 105 12.05 6.05 10.4 0 322.66 352.84 48030 +1915 106 13.85 7.85 12.2 0 359.05 350.8 48225 +1915 107 10.4 4.4 8.75 0 292.12 359.21 48419 +1915 108 14.08 8.08 12.43 0 363.94 353.69 48612 +1915 109 16.86 10.86 15.21 0 427.74 348.6 48804 +1915 110 11.25 5.25 9.6 0 307.53 362.47 48995 +1915 111 12.19 6.19 10.54 0.07 325.37 271.66 49185 +1915 112 7.67 1.67 6.02 0.56 247.03 278.7 49374 +1915 113 7.02 1.02 5.37 0 237.22 373.94 49561 +1915 114 7.63 1.63 5.98 0.08 246.42 280.92 49748 +1915 115 12.77 6.77 11.12 1.69 336.82 275.12 49933 +1915 116 16.04 10.04 14.39 1.53 408 270.38 50117 +1915 117 17.67 11.67 16.02 0 448.04 357.44 50300 +1915 118 21.98 15.98 20.33 0 570.35 344.98 50481 +1915 119 20.41 14.41 18.76 0 522.87 351.53 50661 +1915 120 17.43 11.43 15.78 0.22 441.94 271.29 50840 +1915 121 23.54 17.54 21.89 0.88 621.1 256.8 51016 +1915 122 18.06 12.06 16.41 0.12 458.09 271.66 51191 +1915 123 22.97 16.97 21.32 0.41 602.13 260.04 51365 +1915 124 24.04 18.04 22.39 0.04 638.16 257.63 51536 +1915 125 21.32 15.32 19.67 0 549.96 354.77 51706 +1915 126 21.74 15.74 20.09 0.84 562.86 265.67 51874 +1915 127 18.26 12.26 16.61 0.35 463.33 274.88 52039 +1915 128 19.12 13.12 17.47 0 486.41 364.87 52203 +1915 129 19.61 13.61 17.96 0.2 500 273.11 52365 +1915 130 18.29 12.29 16.64 0 464.12 369.02 52524 +1915 131 17.2 11.2 15.55 0 436.16 372.96 52681 +1915 132 16.35 10.35 14.7 0 415.37 376.11 52836 +1915 133 18.68 12.68 17.03 0 474.48 370.12 52989 +1915 134 20.14 14.14 18.49 0.31 515.05 274.6 53138 +1915 135 21.27 15.27 19.62 0.33 548.44 272.19 53286 +1915 136 20.93 14.93 19.28 0.16 538.21 273.55 53430 +1915 137 20.57 14.57 18.92 0 527.55 366.67 53572 +1915 138 22.25 16.25 20.6 0 578.87 361.19 53711 +1915 139 17.93 11.93 16.28 0.02 454.72 282.29 53848 +1915 140 16.42 10.42 14.77 0.64 417.05 285.86 53981 +1915 141 16.68 10.68 15.03 0 423.34 380.88 54111 +1915 142 16.76 10.76 15.11 0 425.29 381.16 54238 +1915 143 12.97 6.97 11.32 0.05 340.85 293.34 54362 +1915 144 14.36 8.36 12.71 0 369.98 388.39 54483 +1915 145 13.89 7.89 12.24 0.03 359.9 292.49 54600 +1915 146 15.38 9.38 13.73 0.14 392.69 290.03 54714 +1915 147 11.14 5.14 9.49 1.03 305.5 297.61 54824 +1915 148 13.48 7.48 11.83 0.07 351.3 294.15 54931 +1915 149 11.89 5.89 10.24 0.07 319.59 297 55034 +1915 150 15.7 9.7 14.05 0 400.05 387.4 55134 +1915 151 17.63 11.63 15.98 0 447.01 382.43 55229 +1915 152 21.92 15.92 20.27 0.2 568.47 276.17 55321 +1915 153 25.4 19.4 23.75 0.06 686.58 265.52 55409 +1915 154 26.32 20.32 24.67 0.71 721.06 262.52 55492 +1915 155 28.82 22.82 27.17 0.34 822.25 253.03 55572 +1915 156 27.32 21.32 25.67 0.68 760.19 259.19 55648 +1915 157 22.27 16.27 20.62 0.16 579.51 276.08 55719 +1915 158 14.69 8.69 13.04 0.01 377.2 293.95 55786 +1915 159 15.86 9.86 14.21 0.42 403.78 291.88 55849 +1915 160 18.34 12.34 16.69 0 465.43 382.25 55908 +1915 161 19.8 13.8 18.15 0.23 505.35 283.23 55962 +1915 162 23.36 17.36 21.71 0.01 615.06 273.37 56011 +1915 163 25.22 19.22 23.57 0.38 679.99 267.52 56056 +1915 164 22.04 16.04 20.39 0.23 572.24 277.47 56097 +1915 165 22.04 16.04 20.39 0.18 572.24 277.54 56133 +1915 166 21.86 15.86 20.21 0.41 566.6 278.11 56165 +1915 167 21.71 15.71 20.06 0.19 561.93 278.49 56192 +1915 168 18.74 12.74 17.09 0 476.09 381.6 56214 +1915 169 15.58 9.58 13.93 0 397.27 390.71 56231 +1915 170 19.57 13.57 17.92 1.19 498.88 284.2 56244 +1915 171 19.99 13.99 18.34 0 510.75 377.58 56252 +1915 172 21.67 15.67 20.02 0 560.7 371.6 56256 +1915 173 23.81 17.81 22.16 0.62 630.27 272.34 56255 +1915 174 24.83 18.83 23.18 0 665.92 358.64 56249 +1915 175 23.72 17.72 22.07 2.83 627.2 272.54 56238 +1915 176 19.3 13.3 17.65 0 491.36 379.7 56223 +1915 177 21.39 15.39 19.74 0.31 552.1 279.28 56203 +1915 178 20.91 14.91 19.26 0.05 537.61 280.6 56179 +1915 179 19.48 13.48 17.83 0 496.36 378.92 56150 +1915 180 21.9 15.9 20.25 0.15 567.85 277.71 56116 +1915 181 26.24 20.24 24.59 0.05 718 263.79 56078 +1915 182 24.42 18.42 22.77 1.37 651.39 269.91 56035 +1915 183 21.72 15.72 20.07 0.4 562.24 277.92 55987 +1915 184 23.86 17.86 22.21 0 631.98 361.94 55935 +1915 185 24.46 18.46 22.81 0.16 652.79 269.48 55879 +1915 186 28.12 22.12 26.47 0 792.78 341.5 55818 +1915 187 24.66 18.66 23.01 0 659.86 358 55753 +1915 188 23.55 17.55 21.9 0.57 621.44 271.84 55684 +1915 189 24.03 18.03 22.38 1.06 637.82 270.21 55611 +1915 190 24.57 18.57 22.92 0.16 656.67 268.2 55533 +1915 191 23.08 17.08 21.43 0.35 605.76 272.68 55451 +1915 192 19.73 13.73 18.08 0.58 503.37 281.63 55366 +1915 193 21.65 15.65 20 0 560.08 368.51 55276 +1915 194 23.51 17.51 21.86 0.34 620.09 270.78 55182 +1915 195 20.45 14.45 18.8 0.36 524.04 279.22 55085 +1915 196 19.36 13.36 17.71 0.22 493.03 281.65 54984 +1915 197 19.67 13.67 18.02 0 501.68 374.06 54879 +1915 198 22.46 16.46 20.81 0.11 585.58 272.77 54770 +1915 199 21.67 15.67 20.02 0.01 560.7 274.74 54658 +1915 200 26.63 20.63 24.98 0.52 733 258.68 54542 +1915 201 27.36 21.36 25.71 0.19 761.79 255.65 54423 +1915 202 24.67 18.67 23.02 0.35 660.22 264.67 54301 +1915 203 24.68 18.68 23.03 1.65 660.57 264.28 54176 +1915 204 21.81 15.81 20.16 0.56 565.04 272.53 54047 +1915 205 19.56 13.56 17.91 1.65 498.6 278 53915 +1915 206 17.3 11.3 15.65 0.63 438.67 282.73 53780 +1915 207 16.42 10.42 14.77 0.08 417.05 284.06 53643 +1915 208 17.06 11.06 15.41 0.01 432.68 282.23 53502 +1915 209 15.75 9.75 14.1 0 401.21 379.18 53359 +1915 210 15.65 9.65 14 0 398.89 378.79 53213 +1915 211 19.56 13.56 17.91 0 498.6 366.72 53064 +1915 212 26.18 20.18 24.53 0 715.72 340.12 52913 +1915 213 21.69 15.69 20.04 0.46 561.31 268.41 52760 +1915 214 23.01 17.01 21.36 0.3 603.45 264.14 52604 +1915 215 20.67 14.67 19.02 0.13 530.49 270.04 52445 +1915 216 21.55 15.55 19.9 0.5 557 266.98 52285 +1915 217 15.45 9.45 13.8 0.08 394.29 280.11 52122 +1915 218 19.68 13.68 18.03 2.76 501.96 270.45 51958 +1915 219 21.16 15.16 19.51 3.32 545.11 265.96 51791 +1915 220 19.39 13.39 17.74 0.65 493.86 269.65 51622 +1915 221 15.5 9.5 13.85 0 395.43 369.45 51451 +1915 222 17.42 11.42 15.77 0 441.69 363.3 51279 +1915 223 17.16 11.16 15.51 0.03 435.17 272.15 51105 +1915 224 19.72 13.72 18.07 0.6 503.09 265.67 50929 +1915 225 17.33 11.33 15.68 0.29 439.42 270.12 50751 +1915 226 20.95 14.95 19.3 0.04 538.81 260.94 50572 +1915 227 22.78 16.78 21.13 0.36 595.92 255.11 50392 +1915 228 23.95 17.95 22.3 0.57 635.06 250.84 50210 +1915 229 25.09 19.09 23.44 0.75 675.27 246.44 50026 +1915 230 19.93 13.93 18.28 0.14 509.04 259.71 49842 +1915 231 22.54 16.54 20.89 0 588.15 335.95 49656 +1915 232 20.67 14.67 19.02 0.38 530.49 255.82 49469 +1915 233 21.29 15.29 19.64 0.45 549.05 253.22 49280 +1915 234 22.64 16.64 20.99 0.2 591.38 248.62 49091 +1915 235 22.29 16.29 20.64 0.13 580.15 248.47 48900 +1915 236 23.96 17.96 22.31 0.31 635.41 242.78 48709 +1915 237 20.81 14.81 19.16 0.43 534.64 249.98 48516 +1915 238 19.48 13.48 17.83 1.31 496.36 251.85 48323 +1915 239 18.64 12.64 16.99 1.1 473.41 252.56 48128 +1915 240 18.95 12.95 17.3 0.55 481.77 250.57 47933 +1915 241 24.08 18.08 22.43 0.11 639.54 236.44 47737 +1915 242 24.75 18.75 23.1 1 663.06 233.23 47541 +1915 243 19.59 13.59 17.94 0.17 499.44 245.19 47343 +1915 244 17.23 11.23 15.58 0 436.91 331.61 47145 +1915 245 17.33 11.33 15.68 0.03 439.42 247.12 46947 +1915 246 16.51 10.51 14.86 0.02 419.22 247.18 46747 +1915 247 17.88 11.88 16.23 0.16 453.43 243.17 46547 +1915 248 12.14 6.14 10.49 0.1 324.4 251.3 46347 +1915 249 13.66 7.66 12.01 0 355.05 329.98 46146 +1915 250 19.26 13.26 17.61 0.06 490.26 235.91 45945 +1915 251 19.44 13.44 17.79 0.17 495.25 233.96 45743 +1915 252 20.54 14.54 18.89 0.67 526.67 229.96 45541 +1915 253 17.57 11.57 15.92 0.01 445.49 234.51 45339 +1915 254 16.04 10.04 14.39 1.55 408 235.66 45136 +1915 255 16.49 10.49 14.84 0.4 418.74 233.17 44933 +1915 256 16.99 10.99 15.34 0 430.95 307.44 44730 +1915 257 19.81 13.81 18.16 0.27 505.63 223.5 44527 +1915 258 18.61 12.61 16.96 0.29 472.61 224.19 44323 +1915 259 19.51 13.51 17.86 0 497.2 294.13 44119 +1915 260 18.72 12.72 17.07 0 475.56 293.88 43915 +1915 261 17.95 11.95 16.3 1.21 455.24 220.05 43711 +1915 262 14.61 8.61 12.96 0.06 375.44 223.84 43507 +1915 263 15.94 9.94 14.29 0 405.65 293.21 43303 +1915 264 14.53 8.53 12.88 0 373.68 293.54 43099 +1915 265 14.74 8.74 13.09 0 378.3 290.73 42894 +1915 266 14.69 8.69 13.04 0.4 377.2 216.25 42690 +1915 267 15.2 9.2 13.55 0.48 388.59 213.48 42486 +1915 268 13.42 7.42 11.77 0 350.05 285.44 42282 +1915 269 13.64 7.64 11.99 0 354.63 282.51 42078 +1915 270 16.37 10.37 14.72 0 415.85 274.53 41875 +1915 271 14.33 8.33 12.68 0 369.33 275.96 41671 +1915 272 14.46 8.46 12.81 0 372.15 272.98 41468 +1915 273 18.94 12.94 17.29 0.29 481.5 195.74 41265 +1915 274 14.03 8.03 12.38 2.16 362.88 201.41 41062 +1915 275 10.35 4.35 8.7 0.96 291.24 203.71 40860 +1915 276 12.55 6.55 10.9 0.19 332.44 199.17 40658 +1915 277 11.57 5.57 9.92 0.74 313.51 198.3 40456 +1915 278 11.65 5.65 10 1.58 315.02 196.04 40255 +1915 279 9.36 3.36 7.71 0.82 274.18 196.29 40054 +1915 280 8.33 2.33 6.68 0.37 257.34 195.22 39854 +1915 281 8.28 2.28 6.63 0.53 256.55 193.18 39654 +1915 282 8.66 2.66 7.01 0.42 262.64 190.75 39455 +1915 283 7.81 1.81 6.16 0.21 249.19 189.33 39256 +1915 284 10.62 4.62 8.97 0.5 296.05 184.43 39058 +1915 285 11.31 5.31 9.66 0.68 308.64 181.73 38861 +1915 286 11.99 5.99 10.34 0.07 321.51 178.93 38664 +1915 287 10.1 4.1 8.45 0.02 286.85 178.62 38468 +1915 288 11.37 5.37 9.72 0 309.76 233.7 38273 +1915 289 16.42 10.42 14.77 0 417.05 223.11 38079 +1915 290 16.52 10.52 14.87 1.29 419.46 165.1 37885 +1915 291 20.69 14.69 19.04 1.51 531.08 156.75 37693 +1915 292 19.03 13.03 17.38 0.05 483.95 157.53 37501 +1915 293 16.49 10.49 14.84 0.13 418.74 159.19 37311 +1915 294 13.94 7.94 12.29 0 360.96 213.57 37121 +1915 295 15.28 9.28 13.63 0 390.41 208.69 36933 +1915 296 15.5 9.5 13.85 0.06 395.43 154.35 36745 +1915 297 14.93 8.93 13.28 0.08 382.52 153.02 36560 +1915 298 11.15 5.15 9.5 0 305.68 206.67 36375 +1915 299 7.29 1.29 5.64 0 241.26 208.06 36191 +1915 300 1.74 -4.26 0.09 0.19 169.21 157.32 36009 +1915 301 4.32 -1.68 2.67 1.62 199.98 154 35829 +1915 302 2.32 -3.68 0.67 1.27 175.74 153.08 35650 +1915 303 3.14 -2.86 1.49 0 185.35 200.9 35472 +1915 304 8.32 2.32 6.67 0 257.19 194.11 35296 +1915 305 2.29 -3.71 0.64 0 175.4 196.16 35122 +1915 306 0.85 -5.15 -0.8 0 159.59 194.74 34950 +1915 307 -2.06 -8.06 -3.71 0.64 131.35 185 34779 +1915 308 3.02 -2.98 1.37 0 183.92 227.73 34610 +1915 309 6.32 0.32 4.67 0 227.04 222.39 34444 +1915 310 9.42 3.42 7.77 0 275.19 178.14 34279 +1915 311 7.7 1.7 6.05 0 247.49 177.56 34116 +1915 312 7.56 1.56 5.91 0 245.35 175.04 33956 +1915 313 11 5 9.35 0 302.93 169.64 33797 +1915 314 9.58 3.58 7.93 0 277.89 169.14 33641 +1915 315 4.14 -1.86 2.49 0 197.68 170.99 33488 +1915 316 5.11 -0.89 3.46 0.36 210.31 126.09 33337 +1915 317 6.1 0.1 4.45 0.28 223.91 123.89 33188 +1915 318 3.18 -2.82 1.53 0.46 185.83 123.61 33042 +1915 319 0.23 -5.77 -1.42 0.08 153.17 123.55 32899 +1915 320 2.52 -3.48 0.87 0.14 178.05 121.2 32758 +1915 321 4.25 -1.75 2.6 0.01 199.08 118.81 32620 +1915 322 6.08 0.08 4.43 0.08 223.63 116.5 32486 +1915 323 4.5 -1.5 2.85 1.6 202.29 116.09 32354 +1915 324 4.76 -1.24 3.11 1.22 205.68 114.42 32225 +1915 325 4.14 -1.86 2.49 0 197.68 151.22 32100 +1915 326 6.39 0.39 4.74 0 228.04 148.26 31977 +1915 327 3.04 -2.96 1.39 0.05 184.16 111.4 31858 +1915 328 4.56 -1.44 2.91 0 203.07 145.65 31743 +1915 329 6.33 0.33 4.68 0 227.18 142.99 31631 +1915 330 10.85 4.85 9.2 0 300.2 137.95 31522 +1915 331 10.38 4.38 8.73 0.11 291.77 102.81 31417 +1915 332 7.94 1.94 6.29 0.36 251.21 103.09 31316 +1915 333 10.93 4.93 9.28 0.02 301.65 100.43 31218 +1915 334 7.2 1.2 5.55 0 239.91 135.82 31125 +1915 335 7.7 1.7 6.05 0 247.49 134.29 31035 +1915 336 10.58 4.58 8.93 0.01 295.33 98.21 30949 +1915 337 5.59 -0.41 3.94 0 216.82 133 30867 +1915 338 10.3 4.3 8.65 0 290.36 128.62 30790 +1915 339 10.61 4.61 8.96 0.04 295.87 95.69 30716 +1915 340 12.13 6.13 10.48 0.03 324.21 94.14 30647 +1915 341 10.67 4.67 9.02 0 296.95 125.93 30582 +1915 342 8.52 2.52 6.87 0.19 260.38 95.17 30521 +1915 343 9.3 3.3 7.65 0.28 273.17 94.11 30465 +1915 344 8.91 2.91 7.26 0 266.71 124.66 30413 +1915 345 6.36 0.36 4.71 1.14 227.61 94.51 30366 +1915 346 8.2 2.2 6.55 0.52 255.28 93.16 30323 +1915 347 9.58 3.58 7.93 0.29 277.89 91.95 30284 +1915 348 6.53 0.53 4.88 0.9 230.05 93.31 30251 +1915 349 4.32 -1.68 2.67 0.52 199.98 94.02 30221 +1915 350 3.09 -2.91 1.44 0.06 184.76 94.26 30197 +1915 351 2.52 -3.48 0.87 0.06 178.05 94.31 30177 +1915 352 2.78 -3.22 1.13 0 181.08 125.52 30162 +1915 353 5.71 -0.29 4.06 0 218.47 123.84 30151 +1915 354 -0.65 -6.65 -2.3 0 144.44 126.95 30145 +1915 355 2.36 -3.64 0.71 0 176.2 125.63 30144 +1915 356 7.25 1.25 5.6 0 240.65 122.86 30147 +1915 357 7.2 1.2 5.55 0 239.91 122.95 30156 +1915 358 9.64 3.64 7.99 0.08 278.91 90.96 30169 +1915 359 9.41 3.41 7.76 0 275.02 121.57 30186 +1915 360 11.72 5.72 10.07 0 316.34 120.02 30208 +1915 361 10.02 4.02 8.37 0 285.45 121.77 30235 +1915 362 14.21 8.21 12.56 0.1 366.73 88.78 30267 +1915 363 13.69 7.69 12.04 0 355.68 119.47 30303 +1915 364 13.37 7.37 11.72 0 349.02 120.17 30343 +1915 365 15.55 9.55 13.9 0 396.58 118.4 30388 +1916 1 10.93 4.93 9.28 0.62 301.65 92.88 30438 +1916 2 9.62 3.62 7.97 0.57 278.57 94.23 30492 +1916 3 9.46 3.46 7.81 0.15 275.86 95.02 30551 +1916 4 3.9 -2.1 2.25 0 194.66 131.3 30614 +1916 5 8.29 2.29 6.64 0 256.71 129.11 30681 +1916 6 8.33 2.33 6.68 0 257.34 129.96 30752 +1916 7 8.27 2.27 6.62 0 256.39 130.78 30828 +1916 8 7.8 1.8 6.15 0 249.03 132.6 30907 +1916 9 7.88 1.88 6.23 0 250.27 133.78 30991 +1916 10 10.4 4.4 8.75 0 292.12 133.05 31079 +1916 11 8.83 2.83 7.18 0.03 265.4 101.48 31171 +1916 12 10.23 4.23 8.58 0 289.12 135.14 31266 +1916 13 12.12 6.12 10.47 0 324.02 134.98 31366 +1916 14 8.36 2.36 6.71 0 257.82 139.73 31469 +1916 15 10.16 4.16 8.51 0 287.9 139.65 31575 +1916 16 10.73 4.73 9.08 0 298.03 140.39 31686 +1916 17 10 4 8.35 0.01 285.11 107.02 31800 +1916 18 9.44 3.44 7.79 0.06 275.52 108.79 31917 +1916 19 9.48 3.48 7.83 0.08 276.2 110.19 32038 +1916 20 3.12 -2.88 1.47 0.1 185.11 114.79 32161 +1916 21 3.17 -2.83 1.52 0.03 185.71 116.27 32289 +1916 22 0.36 -5.64 -1.29 0.73 154.5 118.73 32419 +1916 23 -2.34 -8.34 -3.99 0 128.88 161.31 32552 +1916 24 0.66 -5.34 -0.99 0.28 157.6 121.52 32688 +1916 25 -3.59 -9.59 -5.24 0 118.32 165.82 32827 +1916 26 4.81 -1.19 3.16 0 206.34 163.39 32969 +1916 27 5.39 -0.61 3.74 0 214.09 165 33114 +1916 28 0.69 -5.31 -0.96 0 157.91 170.12 33261 +1916 29 -1.8 -7.8 -3.45 0 133.69 173.74 33411 +1916 30 0.19 -5.81 -1.46 0.04 152.76 131.28 33564 +1916 31 -0.91 -6.91 -2.56 0.26 141.95 173.38 33718 +1916 32 0.6 -5.4 -1.05 0 156.97 218.98 33875 +1916 33 4.87 -1.13 3.22 0 207.13 218.15 34035 +1916 34 2.58 -3.42 0.93 0 178.74 183.05 34196 +1916 35 3.47 -2.53 1.82 0 189.35 184.62 34360 +1916 36 4.37 -1.63 2.72 0.09 200.62 139.88 34526 +1916 37 4.57 -1.43 2.92 0 203.2 188.79 34694 +1916 38 5.99 -0.01 4.34 0 222.37 190.41 34863 +1916 39 3.8 -2.2 2.15 0 193.42 194.7 35035 +1916 40 1.76 -4.24 0.11 0 169.43 198.71 35208 +1916 41 2.44 -3.56 0.79 0.69 177.12 150.67 35383 +1916 42 0.93 -5.07 -0.72 0 160.43 204.44 35560 +1916 43 4.79 -1.21 3.14 0.24 206.07 153.34 35738 +1916 44 2.68 -3.32 1.03 0 179.91 208.61 35918 +1916 45 4.46 -1.54 2.81 0.54 201.78 157.43 36099 +1916 46 5.14 -0.86 3.49 0.1 210.72 159.04 36282 +1916 47 5.63 -0.37 3.98 0.8 217.37 160.84 36466 +1916 48 5.98 -0.02 4.33 0.8 222.23 162.7 36652 +1916 49 10.26 4.26 8.61 1.2 289.65 161.43 36838 +1916 50 7.94 1.94 6.29 0 251.21 220.46 37026 +1916 51 9.47 3.47 7.82 0.02 276.03 166.29 37215 +1916 52 6.49 0.49 4.84 0.04 229.48 170.75 37405 +1916 53 5.02 -0.98 3.37 0 209.11 231.99 37596 +1916 54 3.58 -2.42 1.93 0.02 190.7 176.98 37788 +1916 55 0.39 -5.61 -1.26 0.24 154.8 181 37981 +1916 56 -0.03 -6.03 -1.68 0.14 150.54 218.19 38175 +1916 57 0.91 -5.09 -0.74 0 160.22 281.29 38370 +1916 58 5.42 -0.58 3.77 0 214.49 245.9 38565 +1916 59 8.96 2.96 7.31 0 267.53 244.82 38761 +1916 60 11.84 5.84 10.19 0 318.63 243.87 38958 +1916 61 11.51 5.51 9.86 0 312.38 247.22 39156 +1916 62 9.07 3.07 7.42 0 269.35 253.22 39355 +1916 63 11.34 5.34 9.69 0 309.2 253.16 39553 +1916 64 12.56 6.56 10.91 0 332.64 254.19 39753 +1916 65 12.53 6.53 10.88 0.1 332.04 192.8 39953 +1916 66 10.37 4.37 8.72 0.83 291.59 197.21 40154 +1916 67 9.44 3.44 7.79 0.83 275.52 200.3 40355 +1916 68 13.33 7.33 11.68 0.05 348.2 198.06 40556 +1916 69 13.66 7.66 12.01 0 355.05 266.08 40758 +1916 70 17.01 11.01 15.36 0 431.44 262.38 40960 +1916 71 17.66 11.66 16.01 0 447.78 263.75 41163 +1916 72 16.13 10.13 14.48 0.05 410.13 202.3 41366 +1916 73 17.4 11.4 15.75 1.59 441.18 202.18 41569 +1916 74 14.25 8.25 12.6 1.5 367.6 209 41772 +1916 75 16.88 10.88 15.23 0.76 428.23 206.98 41976 +1916 76 17.02 11.02 15.37 0.29 431.69 208.65 42179 +1916 77 16 10 14.35 0 407.06 282.91 42383 +1916 78 14.57 8.57 12.92 0.16 374.56 216.3 42587 +1916 79 13.83 7.83 12.18 0 358.63 292.49 42791 +1916 80 10.52 4.52 8.87 0.24 294.26 225.48 42996 +1916 81 8.29 2.29 6.64 0.65 256.71 229.83 43200 +1916 82 3.55 -2.45 1.9 0.7 190.33 236.01 43404 +1916 83 3.38 -2.62 1.73 0.05 188.25 238.03 43608 +1916 84 5.74 -0.26 4.09 0.98 218.88 238.04 43812 +1916 85 3.75 -2.25 2.1 0.2 192.79 241.59 44016 +1916 86 0.25 -5.75 -1.4 0 153.37 327.82 44220 +1916 87 5 -1 3.35 0 208.85 325.77 44424 +1916 88 6.44 0.44 4.79 0 228.76 326.43 44627 +1916 89 6.52 0.52 4.87 0.08 229.91 246.47 44831 +1916 90 7.93 1.93 6.28 0.57 251.05 246.85 45034 +1916 91 11.35 5.35 9.7 1.01 309.39 244.54 45237 +1916 92 8.73 2.73 7.08 0.16 263.77 249.38 45439 +1916 93 10.23 4.23 8.58 0.71 289.12 249.29 45642 +1916 94 11.8 5.8 10.15 0 317.87 331.84 45843 +1916 95 8.72 2.72 7.07 0.14 263.61 254.31 46045 +1916 96 10.38 4.38 8.73 0.14 291.77 253.92 46246 +1916 97 12.31 6.31 10.66 0 327.71 337.17 46446 +1916 98 10.77 4.77 9.12 0 298.75 341.92 46647 +1916 99 15.98 9.98 14.33 0 406.59 333.26 46846 +1916 100 15.72 9.72 14.07 0.11 400.51 251.84 47045 +1916 101 9.13 3.13 7.48 0.65 270.34 262.92 47243 +1916 102 8.92 2.92 7.27 0 266.88 352.82 47441 +1916 103 12.13 6.13 10.48 0 324.21 349.07 47638 +1916 104 13.63 7.63 11.98 0.2 354.42 260.89 47834 +1916 105 16.76 10.76 15.11 0 425.29 342.33 48030 +1916 106 18.53 12.53 16.88 0.47 470.47 254.36 48225 +1916 107 15.38 9.38 13.73 0 392.69 348.99 48419 +1916 108 14.81 8.81 13.16 0.17 379.85 264.03 48612 +1916 109 14.19 8.19 12.54 0.06 366.3 266.28 48804 +1916 110 15.31 9.31 13.66 0 391.09 353.86 48995 +1916 111 16.1 10.1 14.45 0.67 409.42 265.09 49185 +1916 112 12.74 6.74 11.09 2.65 336.22 271.97 49374 +1916 113 13.97 7.97 12.32 0 361.6 361.32 49561 +1916 114 12.65 6.65 11 0.03 334.42 274.23 49748 +1916 115 14.25 8.25 12.6 0 367.6 363.6 49933 +1916 116 15.32 9.32 13.67 0 391.32 362.29 50117 +1916 117 16.28 10.28 14.63 0 413.7 361.18 50300 +1916 118 13.7 7.7 12.05 2.31 355.89 276.51 50481 +1916 119 10.19 4.19 8.54 1.15 288.42 282.69 50661 +1916 120 12.12 6.12 10.47 1.01 324.02 280.81 50840 +1916 121 14.79 8.79 13.14 0 379.41 369.66 51016 +1916 122 17.8 11.8 16.15 0.36 451.37 272.22 51191 +1916 123 15.3 9.3 13.65 0 390.86 370.63 51365 +1916 124 16.98 10.98 15.33 0 430.7 367.33 51536 +1916 125 18.31 12.31 16.66 0 464.64 364.51 51706 +1916 126 20.07 14.07 18.42 0 513.04 359.98 51874 +1916 127 20.23 14.23 18.58 0 517.65 360.32 52039 +1916 128 19.07 13.07 17.42 0.25 485.04 273.77 52203 +1916 129 19.15 13.15 17.5 0.17 487.23 274.2 52365 +1916 130 22.92 16.92 21.27 0 600.49 353.18 52524 +1916 131 18.5 12.5 16.85 0 469.67 369.17 52681 +1916 132 18.04 12.04 16.39 0.41 457.57 278.52 52836 +1916 133 17.49 11.49 15.84 0.05 443.46 280.24 52989 +1916 134 17 11 15.35 0 431.19 375.74 53138 +1916 135 11.86 5.86 10.21 0.24 319.01 291.61 53286 +1916 136 12.98 6.98 11.33 0.05 341.05 290.31 53430 +1916 137 13.15 7.15 11.5 0 344.5 387.42 53572 +1916 138 17.29 11.29 15.64 0.07 438.42 283.17 53711 +1916 139 18.77 12.77 17.12 2.13 476.9 280.38 53848 +1916 140 20.18 14.18 18.53 0.03 516.2 277.3 53981 +1916 141 18.25 12.25 16.6 1.72 463.06 282.25 54111 +1916 142 17.39 11.39 15.74 0.05 440.93 284.53 54238 +1916 143 17.68 11.68 16.03 0 448.29 379.07 54362 +1916 144 17 11 15.35 0.14 431.19 286.12 54483 +1916 145 17.87 11.87 16.22 0.14 453.17 284.59 54600 +1916 146 20.05 14.05 18.4 0.41 512.47 279.69 54714 +1916 147 20.74 14.74 19.09 0 532.56 371.02 54824 +1916 148 25.76 19.76 24.11 0.7 699.9 263.3 54931 +1916 149 21.92 15.92 20.27 0.6 568.47 275.56 55034 +1916 150 21.55 15.55 19.9 0 557 369.12 55134 +1916 151 16.97 10.97 15.32 0 430.45 384.33 55229 +1916 152 20.52 14.52 18.87 0 526.08 373.29 55321 +1916 153 23.31 17.31 21.66 1.7 613.39 272.27 55409 +1916 154 22.14 16.14 20.49 0 575.39 367.94 55492 +1916 155 24.06 18.06 22.41 0 638.85 360.4 55572 +1916 156 19.92 13.92 18.27 0.08 508.76 282.3 55648 +1916 157 16.51 10.51 14.86 0 419.22 386.99 55719 +1916 158 18.19 12.19 16.54 0 461.49 382.29 55786 +1916 159 18.59 12.59 16.94 0.09 472.07 285.97 55849 +1916 160 15.29 9.29 13.64 0 390.64 390.85 55908 +1916 161 17.81 11.81 16.16 0.24 451.62 287.94 55962 +1916 162 17.78 11.78 16.13 0.06 450.85 288.06 56011 +1916 163 19.81 13.81 18.16 1 505.63 283.41 56056 +1916 164 22.95 16.95 21.3 0 601.48 366.41 56097 +1916 165 24.93 18.93 23.28 1.28 669.5 268.6 56133 +1916 166 18.08 12.08 16.43 0.75 458.62 287.71 56165 +1916 167 19.8 13.8 18.15 0.02 505.35 283.56 56192 +1916 168 18.39 12.39 16.74 0.97 466.76 287.02 56214 +1916 169 15.14 9.14 13.49 0.15 387.24 293.88 56231 +1916 170 18.66 12.66 17.01 0.34 473.94 286.4 56244 +1916 171 19.9 13.9 18.25 0.2 508.19 283.41 56252 +1916 172 18.39 12.39 16.74 0.54 466.76 287.06 56256 +1916 173 18.62 12.62 16.97 0.01 472.87 286.51 56255 +1916 174 17.17 11.17 15.52 0.6 435.41 289.71 56249 +1916 175 15.86 9.86 14.21 0 403.78 389.89 56238 +1916 176 21.01 15.01 19.36 0 540.6 373.85 56223 +1916 177 26.42 20.42 24.77 0.01 724.89 263.33 56203 +1916 178 24.88 18.88 23.23 0 667.71 358.28 56179 +1916 179 24.18 18.18 22.53 0 643.01 361.23 56150 +1916 180 23.94 17.94 22.29 0.22 634.72 271.6 56116 +1916 181 22.53 16.53 20.88 0 587.83 367.79 56078 +1916 182 27.27 21.27 25.62 0.25 758.19 259.89 56035 +1916 183 23.14 17.14 21.49 0 607.74 365.06 55987 +1916 184 22.13 16.13 20.48 0 575.07 368.87 55935 +1916 185 20.83 14.83 19.18 0 535.23 373.56 55879 +1916 186 27.03 21.03 25.38 0 748.66 347.09 55818 +1916 187 22.19 16.19 20.54 0.26 576.97 276.09 55753 +1916 188 22.93 16.93 21.28 0 600.82 364.97 55684 +1916 189 23.93 17.93 22.28 0 634.38 360.7 55611 +1916 190 23.94 17.94 22.29 0.03 634.72 270.22 55533 +1916 191 22.09 16.09 20.44 1.24 573.81 275.57 55451 +1916 192 19.82 13.82 18.17 0.83 505.92 281.41 55366 +1916 193 20.36 14.36 18.71 0.01 521.41 279.83 55276 +1916 194 20.29 14.29 18.64 0.1 519.38 279.84 55182 +1916 195 20.55 14.55 18.9 0.12 526.96 278.96 55085 +1916 196 20.67 14.67 19.02 0 530.49 371.13 54984 +1916 197 22.21 16.21 20.56 0.37 577.6 273.8 54879 +1916 198 22.79 16.79 21.14 0 596.25 362.4 54770 +1916 199 22 16 20.35 0 570.98 365.09 54658 +1916 200 22.42 16.42 20.77 0.04 584.3 272.32 54542 +1916 201 22.89 16.89 21.24 1.16 599.51 270.61 54423 +1916 202 18.98 12.98 17.33 0.05 482.59 280.55 54301 +1916 203 19.18 13.18 17.53 0 488.06 372.92 54176 +1916 204 20.53 14.53 18.88 0 526.38 367.94 54047 +1916 205 21.79 15.79 20.14 0 564.42 362.94 53915 +1916 206 23.32 17.32 21.67 0 613.72 356.5 53780 +1916 207 27.58 21.58 25.93 0 770.65 336.64 53643 +1916 208 30.92 24.92 29.27 0.04 916.26 238.19 53502 +1916 209 27.26 21.26 25.61 0.05 757.79 252.76 53359 +1916 210 20.42 14.42 18.77 0.38 523.16 273.49 53213 +1916 211 19.31 13.31 17.66 0.95 491.64 275.64 53064 +1916 212 20.33 14.33 18.68 0.56 520.54 272.54 52913 +1916 213 18.8 12.8 17.15 0.01 477.71 275.66 52760 +1916 214 18.97 12.97 17.32 0.1 482.32 274.7 52604 +1916 215 20.45 14.45 18.8 0.28 524.04 270.6 52445 +1916 216 22.77 16.77 21.12 0 595.59 351.45 52285 +1916 217 23.03 17.03 21.38 0.19 604.11 262.18 52122 +1916 218 23.89 17.89 22.24 0 633 345.37 51958 +1916 219 25.85 19.85 24.2 0.08 703.26 251.97 51791 +1916 220 22.85 16.85 21.2 0 598.2 347.53 51622 +1916 221 23.15 17.15 21.5 0.57 608.07 259.05 51451 +1916 222 20.43 14.43 18.78 0.02 523.45 265.6 51279 +1916 223 18.14 12.14 16.49 0 460.18 360.1 51105 +1916 224 16.09 10.09 14.44 0 409.18 364.62 50929 +1916 225 18.99 12.99 17.34 0.07 482.86 266.51 50751 +1916 226 20.91 14.91 19.26 0 537.61 348.06 50572 +1916 227 21.05 15.05 19.4 0 541.8 346.31 50392 +1916 228 23.23 17.23 21.58 0 610.73 337.26 50210 +1916 229 24.96 18.96 23.31 0 670.58 329.13 50026 +1916 230 21.98 15.98 20.33 0 570.35 339.41 49842 +1916 231 21.71 15.71 20.06 0 561.93 338.91 49656 +1916 232 21.53 15.53 19.88 0 556.38 338.2 49469 +1916 233 21.31 15.31 19.66 0 549.66 337.55 49280 +1916 234 22.96 16.96 21.31 0 601.8 330.32 49091 +1916 235 25.66 19.66 24.01 0 696.18 318.13 48900 +1916 236 23.33 17.33 21.68 0.13 614.06 244.58 48709 +1916 237 23.06 17.06 21.41 0 605.1 325.52 48516 +1916 238 23.81 17.81 22.16 0 630.27 321.08 48323 +1916 239 24.41 18.41 22.76 0.18 651.04 237.98 48128 +1916 240 25.19 19.19 23.54 0.02 678.9 234.37 47933 +1916 241 22.4 16.4 20.75 1.24 583.66 241.06 47737 +1916 242 22.12 16.12 20.47 0.48 574.76 240.51 47541 +1916 243 17.65 11.65 16 1.02 447.52 249.26 47343 +1916 244 12.16 6.16 10.51 0.92 324.79 257.16 47145 +1916 245 12.4 6.4 10.75 0.02 329.48 255.38 46947 +1916 246 12.35 6.35 10.7 0.32 328.5 253.94 46747 +1916 247 11.79 5.79 10.14 0.48 317.68 253.29 46547 +1916 248 12.06 6.06 10.41 0 322.85 335.21 46347 +1916 249 12.9 6.9 11.25 1.89 339.43 248.62 46146 +1916 250 14.26 8.26 12.61 0.03 367.81 245.06 45945 +1916 251 13.46 7.46 11.81 0 350.88 326.23 45743 +1916 252 13.09 7.09 11.44 0 343.28 324.74 45541 +1916 253 13.05 7.05 11.4 0.73 342.47 241.99 45339 +1916 254 11.88 5.88 10.23 0.48 319.39 241.97 45136 +1916 255 17.2 11.2 15.55 0.09 436.16 231.9 44933 +1916 256 21.23 15.23 19.58 0.45 547.23 221.97 44730 +1916 257 20.49 14.49 18.84 0 525.2 296.06 44527 +1916 258 24.48 18.48 22.83 0.08 653.5 210.62 44323 +1916 259 24.01 18.01 22.36 0 637.13 280.2 44119 +1916 260 25.34 19.34 23.69 0.18 684.38 204.86 43915 +1916 261 23.99 17.99 22.34 0.17 636.44 206.77 43711 +1916 262 24.55 18.55 22.9 0.04 655.97 203.62 43507 +1916 263 19.87 13.87 18.22 0.02 507.33 212.76 43303 +1916 264 18.58 12.58 16.93 1.77 471.8 213.39 43099 +1916 265 18.53 12.53 16.88 0 470.47 282.31 42894 +1916 266 21.52 15.52 19.87 0.08 556.07 203.89 42690 +1916 267 18.17 12.17 16.52 0.09 460.97 208.58 42486 +1916 268 16.4 10.4 14.75 0.18 416.57 209.69 42282 +1916 269 17.51 11.51 15.86 1.08 443.96 205.98 42078 +1916 270 16.16 10.16 14.51 0.93 410.84 206.23 41875 +1916 271 14.81 8.81 13.16 2.19 379.85 206.29 41671 +1916 272 16.16 10.16 14.51 0 410.84 269.65 41468 +1916 273 17.58 11.58 15.93 0 445.74 264.12 41265 +1916 274 14.06 8.06 12.41 0 363.52 268.49 41062 +1916 275 13.87 7.87 12.22 0 359.47 266.05 40860 +1916 276 13.01 7.01 11.36 0 341.66 264.81 40658 +1916 277 9.64 3.64 7.99 0.24 278.91 200.35 40456 +1916 278 6.8 0.8 5.15 1.41 233.98 200.74 40255 +1916 279 7.97 1.97 6.32 0.02 251.67 197.58 40054 +1916 280 11.54 5.54 9.89 0 312.94 256.03 39854 +1916 281 10.1 4.1 8.45 0.78 286.85 191.47 39654 +1916 282 11.5 5.5 9.85 0.25 312.19 187.94 39455 +1916 283 13 7 11.35 0 341.45 245.5 39256 +1916 284 13.33 7.33 11.68 0.02 348.2 181.47 39058 +1916 285 13.43 7.43 11.78 0 350.26 239.17 38861 +1916 286 16.9 10.9 15.25 0 428.73 230.39 38664 +1916 287 12.12 6.12 10.47 0.2 324.02 176.58 38468 +1916 288 15.12 9.12 13.47 0 386.79 227.99 38273 +1916 289 11.46 5.46 9.81 0 311.44 230.93 38079 +1916 290 12.76 6.76 11.11 0 336.62 226.25 37885 +1916 291 15.26 9.26 13.61 0 389.95 219.68 37693 +1916 292 13.77 7.77 12.12 0 357.36 219.39 37501 +1916 293 14.27 8.27 12.62 0 368.03 215.93 37311 +1916 294 14.92 8.92 13.27 0.02 382.3 159.04 37121 +1916 295 13.34 7.34 11.69 0 348.4 211.65 36933 +1916 296 10.48 4.48 8.83 0 293.55 212.82 36745 +1916 297 12.84 6.84 11.19 0 338.22 207.08 36560 +1916 298 12.67 6.67 11.02 0 334.82 204.73 36375 +1916 299 11.43 5.43 9.78 0 310.88 203.55 36191 +1916 300 13.74 7.74 12.09 0 356.73 197.87 36009 +1916 301 19.49 13.49 17.84 0 496.64 185.84 35829 +1916 302 12.72 6.72 11.07 0.35 335.82 145.63 35650 +1916 303 15.49 9.49 13.84 0 395.2 187.75 35472 +1916 304 17.11 11.11 15.46 0 433.92 182.79 35296 +1916 305 11.58 5.58 9.93 0.15 313.7 140.9 35122 +1916 306 13.15 7.15 11.5 0.19 344.5 137.79 34950 +1916 307 8.08 2.08 6.43 0.83 253.4 140.1 34779 +1916 308 2.79 -3.21 1.14 0.09 181.2 141.24 34610 +1916 309 6.17 0.17 4.52 0 224.9 183.5 34444 +1916 310 8.25 2.25 6.6 0.29 256.08 134.44 34279 +1916 311 8.11 2.11 6.46 0 253.87 177.2 34116 +1916 312 12.78 6.78 11.13 0 337.02 169.73 33956 +1916 313 11.06 5.06 9.41 0.11 304.03 127.18 33797 +1916 314 10.08 4.08 8.43 0.85 286.5 126.49 33641 +1916 315 8.31 2.31 6.66 0.02 257.03 125.83 33488 +1916 316 9.31 3.31 7.66 0 273.34 164.7 33337 +1916 317 7.41 1.41 5.76 0.25 243.07 123.12 33188 +1916 318 8.69 2.69 7.04 0 263.12 160.75 33042 +1916 319 6.92 0.92 5.27 0 235.74 160.51 32899 +1916 320 9.87 3.87 8.22 0.18 282.86 117.11 32758 +1916 321 9.33 3.33 7.68 0.07 273.67 115.91 32620 +1916 322 10 4 8.35 0.69 285.11 114.1 32486 +1916 323 9.54 3.54 7.89 0.01 277.21 113.22 32354 +1916 324 9.81 3.81 8.16 0.01 281.82 111.51 32225 +1916 325 6.48 0.48 4.83 0 229.33 149.65 32100 +1916 326 7.74 1.74 6.09 0.1 248.11 110.44 31977 +1916 327 8.27 2.27 6.62 0 256.39 145.01 31858 +1916 328 7.3 1.3 5.65 0 241.41 143.79 31743 +1916 329 9.78 3.78 8.13 0 281.31 140.32 31631 +1916 330 9.27 3.27 7.62 0 272.67 139.33 31522 +1916 331 10.08 4.08 8.43 0 286.5 137.34 31417 +1916 332 12.17 6.17 10.52 0 324.99 133.8 31316 +1916 333 12.47 6.47 10.82 0 330.86 132.46 31218 +1916 334 11.49 5.49 9.84 0.04 312.01 99.25 31125 +1916 335 6.6 0.6 4.95 1.24 231.07 101.3 31035 +1916 336 10.82 4.82 9.17 0.44 299.65 98.05 30949 +1916 337 11.73 5.73 10.08 0.65 316.53 96.21 30867 +1916 338 11.13 5.13 9.48 0.24 305.31 95.93 30790 +1916 339 9.12 3.12 7.47 0 270.17 128.81 30716 +1916 340 10.63 4.63 8.98 0.27 296.23 95.15 30647 +1916 341 6.61 0.61 4.96 0.47 231.21 96.73 30582 +1916 342 10.73 4.73 9.08 0 298.03 125.13 30521 +1916 343 9.22 3.22 7.57 0.06 271.84 94.16 30465 +1916 344 7.61 1.61 5.96 0 246.11 125.6 30413 +1916 345 8.6 2.6 6.95 0.96 261.67 93.35 30366 +1916 346 7.64 1.64 5.99 0.58 246.57 93.46 30323 +1916 347 6.38 0.38 4.73 0 227.89 124.86 30284 +1916 348 6.62 0.62 4.97 0 231.36 124.36 30251 +1916 349 6.39 0.39 4.74 0 228.04 124.13 30221 +1916 350 5.41 -0.59 3.76 0 214.36 124.4 30197 +1916 351 10.52 4.52 8.87 0.07 294.26 90.44 30177 +1916 352 10.38 4.38 8.73 0.03 291.77 90.46 30162 +1916 353 7.41 1.41 5.76 0.5 243.07 92.07 30151 +1916 354 8.84 2.84 7.19 0 265.57 121.71 30145 +1916 355 8.76 2.76 7.11 0 264.26 121.77 30144 +1916 356 9.18 3.18 7.53 0.08 271.17 91.11 30147 +1916 357 8.59 2.59 6.94 0 261.51 121.98 30156 +1916 358 3.1 -2.9 1.45 0.26 184.88 94.08 30169 +1916 359 -0.14 -6.14 -1.79 0 149.44 127.04 30186 +1916 360 -0.69 -6.69 -2.34 0 144.05 127.63 30208 +1916 361 1.34 -4.66 -0.31 0 164.82 127.1 30235 +1916 362 -0.98 -6.98 -2.63 0.8 141.28 142.55 30267 +1916 363 1.04 -4.96 -0.61 0 161.6 174.23 30303 +1916 364 2.58 -3.42 0.93 0 178.74 173.49 30343 +1916 365 8.84 2.84 7.19 0 265.57 168.95 30388 +1917 1 2.35 -3.65 0.7 0.04 176.09 141.07 30438 +1917 2 -1.13 -7.13 -2.78 0.02 139.86 142.76 30492 +1917 3 3.95 -2.05 2.3 0 195.29 173.66 30551 +1917 4 8.07 2.07 6.42 0.01 253.24 96.48 30614 +1917 5 10.96 4.96 9.31 0 302.2 126.96 30681 +1917 6 8.38 2.38 6.73 0.2 258.14 97.44 30752 +1917 7 5.32 -0.68 3.67 0 213.14 132.79 30828 +1917 8 7.05 1.05 5.4 0.07 237.67 99.85 30907 +1917 9 2.62 -3.38 0.97 1.34 179.21 102.8 30991 +1917 10 1.39 -4.61 -0.26 0.08 165.37 104.24 31079 +1917 11 0.35 -5.65 -1.3 0.03 154.39 105.36 31171 +1917 12 2.57 -3.43 0.92 0.12 178.63 105.3 31266 +1917 13 -0.07 -6.07 -1.72 0 150.14 143.32 31366 +1917 14 0.92 -5.08 -0.73 0 160.33 144.35 31469 +1917 15 -1.71 -7.71 -3.36 0 134.5 146.97 31575 +1917 16 -2.68 -8.68 -4.33 0 125.93 148.66 31686 +1917 17 -2.39 -8.39 -4.04 0 128.44 150.25 31800 +1917 18 0.89 -5.11 -0.76 0 160.01 150.71 31917 +1917 19 2.08 -3.92 0.43 0 173.01 152.04 32038 +1917 20 1.28 -4.72 -0.37 0 164.17 154.06 32161 +1917 21 -2.59 -8.59 -4.24 0 126.7 157.84 32289 +1917 22 -1.05 -7.05 -2.7 0 140.62 158.97 32419 +1917 23 -3.57 -9.57 -5.22 0 118.49 161.8 32552 +1917 24 -0.02 -6.02 -1.67 1 150.64 165.09 32688 +1917 25 -3.82 -9.82 -5.47 3.11 116.47 176.66 32827 +1917 26 -0.06 -6.06 -1.71 0 150.24 218.24 32969 +1917 27 0.54 -5.46 -1.11 0.04 156.35 177.69 33114 +1917 28 2.46 -3.54 0.81 0.26 177.35 178.03 33261 +1917 29 5.75 -0.25 4.1 0.04 219.02 177.24 33411 +1917 30 4.3 -1.7 2.65 0.1 199.72 178.95 33564 +1917 31 6.62 0.62 4.97 0 231.36 221.72 33718 +1917 32 1.78 -4.22 0.13 0 169.65 226.74 33875 +1917 33 0.08 -5.92 -1.57 0 151.65 230.1 34035 +1917 34 -3.89 -9.89 -5.54 0.25 115.9 188.08 34196 +1917 35 -4.47 -10.47 -6.12 0 111.35 236.86 34360 +1917 36 -6.84 -12.84 -8.49 0 94.31 240.05 34526 +1917 37 -7.88 -13.88 -9.53 0 87.58 242.64 34694 +1917 38 -4.8 -10.8 -6.45 0.2 108.83 195.48 34863 +1917 39 -8.15 -14.15 -9.8 0 85.9 248.27 35035 +1917 40 -4.59 -10.59 -6.24 0 110.43 249.43 35208 +1917 41 -2.26 -8.26 -3.91 0 129.58 250.82 35383 +1917 42 1.49 -4.51 -0.16 0 166.46 250.91 35560 +1917 43 0.08 -5.92 -1.57 0 151.65 254.26 35738 +1917 44 -0.81 -6.81 -2.46 0 142.9 257.13 35918 +1917 45 2.09 -3.91 0.44 0 173.13 257.53 36099 +1917 46 3.94 -2.06 2.29 0 195.16 258.22 36282 +1917 47 2.6 -3.4 0.95 0 178.98 261.54 36466 +1917 48 3.12 -2.88 1.47 0 185.11 263.41 36652 +1917 49 2.99 -3.01 1.34 0 183.56 265.75 36838 +1917 50 0.38 -5.62 -1.27 0 154.7 269.98 37026 +1917 51 -3.86 -9.86 -5.51 0 116.14 275.11 37215 +1917 52 -2.24 -8.24 -3.89 0 129.76 276.95 37405 +1917 53 -3.8 -9.8 -5.45 0 116.63 280.54 37596 +1917 54 -0.89 -6.89 -2.54 0 142.14 281.55 37788 +1917 55 -0.57 -6.57 -2.22 0 145.22 284.18 37981 +1917 56 -0.07 -6.07 -1.72 0 150.14 286.38 38175 +1917 57 -1.97 -7.97 -3.62 0 132.16 290.26 38370 +1917 58 -2.49 -8.49 -4.14 0.54 127.57 231.73 38565 +1917 59 -4.35 -10.35 -6 0.11 112.28 234.6 38761 +1917 60 2.17 -3.83 0.52 0.35 174.03 233.29 38958 +1917 61 4.22 -1.78 2.57 0.27 198.7 233.57 39156 +1917 62 6.86 0.86 5.21 0 234.86 296.75 39355 +1917 63 8.96 2.96 7.31 0 267.53 296.2 39553 +1917 64 10.1 4.1 8.45 0.06 286.85 231.94 39753 +1917 65 9.14 3.14 7.49 0 270.51 299.38 39953 +1917 66 10.37 4.37 8.72 0.46 291.59 233.49 40154 +1917 67 6.41 0.41 4.76 0.25 228.32 238.5 40355 +1917 68 6.98 0.98 5.33 0 236.63 307.55 40556 +1917 69 7.17 1.17 5.52 0.02 239.46 240.23 40758 +1917 70 7.16 1.16 5.51 0 239.31 311.06 40960 +1917 71 3.74 -2.26 2.09 0 192.67 317.06 41163 +1917 72 4.46 -1.54 2.81 0.03 201.78 215.17 41366 +1917 73 9.22 3.22 7.57 0.06 271.84 213 41569 +1917 74 7.37 1.37 5.72 0.22 242.46 216.85 41772 +1917 75 3.5 -2.5 1.85 1.57 189.71 222.05 41976 +1917 76 4.25 -1.75 2.6 0.43 199.08 223.5 42179 +1917 77 -1.4 -7.4 -3.05 0.07 137.34 260.37 42383 +1917 78 -1.77 -7.77 -3.42 0.79 133.96 264.24 42587 +1917 79 2.74 -3.26 1.09 0.67 180.61 263.19 42791 +1917 80 2.92 -3.08 1.27 0 182.73 342.07 42996 +1917 81 2.18 -3.82 0.53 0.11 174.15 266.7 43200 +1917 82 1.94 -4.06 0.29 1.95 171.44 268.56 43404 +1917 83 5.33 -0.67 3.68 0.05 213.27 267.24 43608 +1917 84 6.19 0.19 4.54 0.22 225.19 237.64 43812 +1917 85 6.08 0.08 4.43 0 223.63 319.51 44016 +1917 86 6.57 0.57 4.92 0.02 230.63 241 44220 +1917 87 6.87 0.87 5.22 0.27 235.01 242.63 44424 +1917 88 9.05 3.05 7.4 0 269.02 322.86 44627 +1917 89 7.85 1.85 6.2 0 249.81 326.87 44831 +1917 90 8.25 2.25 6.6 0.03 256.08 246.51 45034 +1917 91 11.19 5.19 9.54 0.13 306.42 244.75 45237 +1917 92 9.08 3.08 7.43 0 269.51 331.99 45439 +1917 93 10.58 4.58 8.93 0.29 295.33 248.86 45642 +1917 94 9.06 3.06 7.41 0.63 269.18 252.3 45843 +1917 95 7.93 1.93 6.28 0.38 251.05 255.18 46045 +1917 96 13.82 7.82 12.17 0 358.42 332.14 46246 +1917 97 14.35 8.35 12.7 0 369.76 333.05 46446 +1917 98 13.78 7.78 12.13 2.06 357.57 252.14 46647 +1917 99 10.22 4.22 8.57 0.45 288.95 258.66 46846 +1917 100 8.82 2.82 7.17 0 265.24 349.1 47045 +1917 101 7.97 1.97 6.32 0.28 251.67 264.25 47243 +1917 102 10.4 4.4 8.75 0.02 292.12 262.78 47441 +1917 103 11.58 5.58 9.93 0.54 313.7 262.58 47638 +1917 104 12.91 6.91 11.26 0 339.63 349.35 47834 +1917 105 13.77 7.77 12.12 0 357.36 349.34 48030 +1917 106 9.94 3.94 8.29 0 284.07 358.32 48225 +1917 107 14.1 8.1 12.45 0 364.37 351.92 48419 +1917 108 11.7 5.7 10.05 0.04 315.97 268.94 48612 +1917 109 9.64 3.64 7.99 0 278.91 363.91 48804 +1917 110 10.59 4.59 8.94 0 295.51 363.68 48995 +1917 111 8.17 2.17 6.52 0.03 254.81 276.97 49185 +1917 112 7.69 1.69 6.04 0.05 247.34 278.68 49374 +1917 113 6.22 0.22 4.57 0.23 225.61 281.3 49561 +1917 114 5.56 -0.44 3.91 0 216.41 377.49 49748 +1917 115 5.12 -0.88 3.47 0.02 210.45 284.65 49933 +1917 116 8.21 2.21 6.56 0.04 255.44 282.28 50117 +1917 117 6.94 0.94 5.29 0.02 236.04 284.73 50300 +1917 118 10.64 4.64 8.99 0 296.41 374.89 50481 +1917 119 9.31 3.31 7.66 0 273.34 378.46 50661 +1917 120 11.41 5.41 9.76 0 310.51 375.82 50840 +1917 121 22.88 16.88 21.23 0 599.18 344.96 51016 +1917 122 21.43 15.43 19.78 0 553.32 351.41 51191 +1917 123 20.56 14.56 18.91 0 527.26 355.39 51365 +1917 124 20.66 14.66 19.01 0.01 530.2 267.08 51536 +1917 125 20.64 14.64 18.99 0 529.61 357.12 51706 +1917 126 20.96 14.96 19.31 0 539.11 356.98 51874 +1917 127 21.1 15.1 19.45 0 543.31 357.36 52039 +1917 128 23.79 17.79 22.14 0 629.58 348.17 52203 +1917 129 23.93 17.93 22.28 0 634.38 348.4 52365 +1917 130 20.92 14.92 19.27 0 537.91 360.53 52524 +1917 131 18.04 12.04 16.39 0 457.57 370.54 52681 +1917 132 18 12 16.35 0 456.53 371.47 52836 +1917 133 19.32 13.32 17.67 0 491.92 368.12 52989 +1917 134 17.79 11.79 16.14 0 451.11 373.49 53138 +1917 135 21.05 15.05 19.4 0 541.8 363.69 53286 +1917 136 22.09 16.09 20.44 0 573.81 360.53 53430 +1917 137 18.42 12.42 16.77 0 467.55 373.63 53572 +1917 138 18.12 12.12 16.47 0.33 459.66 281.35 53711 +1917 139 19.01 13.01 17.36 0.01 483.41 279.81 53848 +1917 140 14.52 8.52 12.87 0.5 373.46 289.52 53981 +1917 141 15.01 9.01 13.36 0 384.31 385.27 54111 +1917 142 13.15 7.15 11.5 0.07 344.5 292.64 54238 +1917 143 15.16 9.16 13.51 0 387.69 385.94 54362 +1917 144 15.36 9.36 13.71 0 392.23 385.91 54483 +1917 145 14.94 8.94 13.29 0.27 382.75 290.58 54600 +1917 146 12.14 6.14 10.49 0.02 324.4 295.71 54714 +1917 147 16.33 10.33 14.68 0 414.89 384.68 54824 +1917 148 16.15 10.15 14.5 0 410.61 385.55 54931 +1917 149 21.42 15.42 19.77 0 553.01 369.27 55034 +1917 150 18.25 12.25 16.6 0.15 463.06 285.14 55134 +1917 151 18.48 12.48 16.83 0 469.14 379.87 55229 +1917 152 24.05 18.05 22.4 0 638.51 359.72 55321 +1917 153 25.52 19.52 23.87 0 690.99 353.48 55409 +1917 154 24.89 18.89 23.24 0.16 668.07 267.47 55492 +1917 155 27.11 21.11 25.46 0.62 751.83 259.75 55572 +1917 156 21.11 15.11 19.46 0 543.61 372.26 55648 +1917 157 18.37 12.37 16.72 0.31 466.23 286.17 55719 +1917 158 19.3 13.3 17.65 0 491.36 378.79 55786 +1917 159 21.51 15.51 19.86 0 555.77 371.38 55849 +1917 160 19.24 13.24 17.59 0 489.71 379.41 55908 +1917 161 20.46 14.46 18.81 0 524.33 375.38 55962 +1917 162 20.92 14.92 19.27 0 537.91 373.82 56011 +1917 163 22.61 16.61 20.96 0 590.41 367.71 56056 +1917 164 21.87 15.87 20.22 0.15 566.91 277.95 56097 +1917 165 20.06 14.06 18.41 0.19 512.76 282.88 56133 +1917 166 15.77 9.77 14.12 0.03 401.68 292.63 56165 +1917 167 20 14 18.35 0 511.04 377.4 56192 +1917 168 21.41 15.41 19.76 0 552.71 372.5 56214 +1917 169 22.37 16.37 20.72 0 582.7 368.89 56231 +1917 170 19.66 13.66 18.01 0 501.4 378.63 56244 +1917 171 20.54 14.54 18.89 0 526.67 375.69 56252 +1917 172 23.56 17.56 21.91 0 621.78 364.18 56256 +1917 173 23.64 17.64 21.99 0 624.48 363.83 56255 +1917 174 27.98 21.98 26.33 0 786.99 343.4 56249 +1917 175 31.21 25.21 29.56 0 929.93 324.85 56238 +1917 176 34.13 28.13 32.48 0.11 1077.39 228.88 56223 +1917 177 30.99 24.99 29.34 0 919.55 326.08 56203 +1917 178 28.92 22.92 27.27 0.14 826.53 253.65 56179 +1917 179 24.46 18.46 22.81 0 652.79 360.03 56150 +1917 180 24.74 18.74 23.09 0 662.71 358.68 56116 +1917 181 24.63 18.63 22.98 0 658.8 359.1 56078 +1917 182 22.55 16.55 20.9 0.16 588.47 275.68 56035 +1917 183 23.57 17.57 21.92 0.44 622.12 272.48 55987 +1917 184 20.34 14.34 18.69 0.03 520.83 281.52 55935 +1917 185 19.98 13.98 18.33 0 510.47 376.5 55879 +1917 186 21.51 15.51 19.86 0 555.77 370.85 55818 +1917 187 19.96 13.96 18.31 0.06 509.9 282.1 55753 +1917 188 22.93 16.93 21.28 0.35 600.82 273.73 55684 +1917 189 20.6 14.6 18.95 0.28 528.43 280.11 55611 +1917 190 20.94 14.94 19.29 0.59 538.51 278.94 55533 +1917 191 21.78 15.78 20.13 0.24 564.11 276.45 55451 +1917 192 18.9 12.9 17.25 0.18 480.41 283.65 55366 +1917 193 20.81 14.81 19.16 0 534.64 371.54 55276 +1917 194 22.48 16.48 20.83 1.04 586.22 273.86 55182 +1917 195 22.6 16.6 20.95 0.23 590.08 273.31 55085 +1917 196 18.82 12.82 17.17 0.12 478.25 282.94 54984 +1917 197 20.64 14.64 18.99 0.49 529.61 278.08 54879 +1917 198 23.66 17.66 22.01 0.33 625.16 269.18 54770 +1917 199 24.55 18.55 22.9 0.15 655.97 266.11 54658 +1917 200 21.63 15.63 19.98 0 559.46 366.06 54542 +1917 201 23.82 17.82 22.17 0 630.61 357.05 54423 +1917 202 28.48 22.48 26.83 0 807.82 334.54 54301 +1917 203 30.05 24.05 28.4 0.56 876.27 244.02 54176 +1917 204 26.01 20.01 24.36 0.08 709.28 259.43 54047 +1917 205 29.5 23.5 27.85 0.3 851.75 245.66 53915 +1917 206 28.32 22.32 26.67 0.11 801.1 250.08 53780 +1917 207 30.4 24.4 28.75 0 892.18 321.28 53643 +1917 208 30.52 24.52 28.87 0 897.69 319.97 53502 +1917 209 29.77 23.77 28.12 0.18 863.72 242.79 53359 +1917 210 26.11 20.11 24.46 0.41 713.06 256.46 53213 +1917 211 25.46 19.46 23.81 0 688.78 344.16 53064 +1917 212 24.62 18.62 22.97 0.01 658.44 260.31 52913 +1917 213 23.95 17.95 22.3 0 635.06 349.15 52760 +1917 214 23.67 17.67 22.02 0 625.5 349.56 52604 +1917 215 22.61 16.61 20.96 0 590.41 353.06 52445 +1917 216 24.96 18.96 23.31 0 670.58 342.53 52285 +1917 217 23.64 17.64 21.99 0.12 624.48 260.38 52122 +1917 218 22.97 16.97 21.32 0.35 602.13 261.76 51958 +1917 219 23.44 17.44 21.79 1.75 617.74 259.61 51791 +1917 220 21.47 15.47 19.82 1 554.54 264.45 51622 +1917 221 20.23 14.23 18.58 0.44 517.65 266.87 51451 +1917 222 19.37 13.37 17.72 0.46 493.3 268.16 51279 +1917 223 19.35 13.35 17.7 0 492.75 356.46 51105 +1917 224 20.81 14.81 19.16 0.03 534.64 263 50929 +1917 225 20.29 14.29 18.64 0 519.38 351.25 50751 +1917 226 23.5 17.5 21.85 0 619.76 338.64 50572 +1917 227 26.38 20.38 24.73 0 723.36 325.25 50392 +1917 228 26.73 20.73 25.08 0 736.89 322.5 50210 +1917 229 27.37 21.37 25.72 0.04 762.19 238.74 50026 +1917 230 25.37 19.37 23.72 0.22 685.47 244.63 49842 +1917 231 25.18 19.18 23.53 0.15 678.54 244.18 49656 +1917 232 25.23 19.23 23.58 0.22 680.36 243.06 49469 +1917 233 21.79 15.79 20.14 0.09 564.42 251.93 49280 +1917 234 22.18 16.18 20.53 0 576.65 333.15 49091 +1917 235 26.88 20.88 25.23 0.01 742.76 234.55 48900 +1917 236 30.87 24.87 29.22 0.01 913.93 218.37 48709 +1917 237 26.86 20.86 25.21 0.06 741.97 232.46 48516 +1917 238 22.75 16.75 21.1 0 594.94 325.02 48323 +1917 239 24.41 18.41 22.76 0.01 651.04 237.98 48128 +1917 240 22.04 16.04 20.39 0 572.24 324.34 47933 +1917 241 22.84 16.84 21.19 0.01 597.88 239.89 47737 +1917 242 23.39 17.39 21.74 0 616.06 316.17 47541 +1917 243 22.43 16.43 20.78 0 584.62 317.8 47343 +1917 244 16.35 10.35 14.7 0 415.37 333.82 47145 +1917 245 19.81 13.81 18.16 0 505.63 322.63 46947 +1917 246 22.49 16.49 20.84 0 586.54 312.12 46747 +1917 247 21.56 15.56 19.91 0 557.3 313.43 46547 +1917 248 22.22 16.22 20.57 0 577.92 309.36 46347 +1917 249 22.58 16.58 20.93 0 589.44 306.14 46146 +1917 250 26.55 20.55 24.9 0 729.9 289.19 45945 +1917 251 24.48 18.48 22.83 0 653.5 295.45 45743 +1917 252 22.85 16.85 21.2 0 598.2 299.22 45541 +1917 253 23.92 17.92 22.27 0.6 634.03 220.08 45339 +1917 254 21.72 15.72 20.07 0.29 562.24 224.12 45136 +1917 255 19.38 13.38 17.73 0 493.58 303.55 44933 +1917 256 19.77 13.77 18.12 0 504.5 300.23 44730 +1917 257 23.98 17.98 22.33 0 636.09 284.84 44527 +1917 258 21.9 15.9 20.25 0 567.85 289.52 44323 +1917 259 26.01 20.01 24.36 0.13 709.28 204.6 44119 +1917 260 24.37 18.37 22.72 0 649.63 276.68 43915 +1917 261 20.24 14.24 18.59 0 517.94 287.39 43711 +1917 262 19.59 13.59 17.94 0 499.44 286.85 43507 +1917 263 13.42 7.42 11.77 1.16 350.05 223.69 43303 +1917 264 15.11 9.11 13.46 0.11 386.56 219.28 43099 +1917 265 16.43 10.43 14.78 0.22 417.29 215.41 42894 +1917 266 19.75 13.75 18.1 0.31 503.94 207.57 42690 +1917 267 20.99 14.99 19.34 0.03 540 203.09 42486 +1917 268 20.3 14.3 18.65 0.38 519.67 202.65 42282 +1917 269 16.61 10.61 14.96 0.23 421.64 207.48 42078 +1917 270 21.61 15.61 19.96 0 558.84 261.61 41875 +1917 271 22.84 16.84 21.19 0 597.88 255.49 41671 +1917 272 18.53 12.53 16.88 0 470.47 264.43 41468 +1917 273 19.52 13.52 17.87 0 497.48 259.57 41265 +1917 274 11.33 5.33 9.68 0.75 309.02 204.74 41062 +1917 275 9.82 3.82 8.17 0.67 282 204.26 40860 +1917 276 15.54 9.54 13.89 0.21 396.35 195.22 40658 +1917 277 12.29 6.29 10.64 1.99 327.32 197.47 40456 +1917 278 9.4 3.4 7.75 1.08 274.85 198.4 40255 +1917 279 10.28 4.28 8.63 0.69 290 195.37 40054 +1917 280 11.25 5.25 9.6 0 307.53 256.45 39854 +1917 281 8.33 2.33 6.68 0.48 257.34 193.14 39654 +1917 282 5.03 -0.97 3.38 0.57 209.25 193.68 39455 +1917 283 8.83 2.83 7.18 0 265.4 251.25 39256 +1917 284 11.82 5.82 10.17 0.18 318.25 183.18 39058 +1917 285 11.66 5.66 10.01 0.12 315.21 181.36 38861 +1917 286 16.72 10.72 15.07 0 424.32 230.73 38664 +1917 287 19.56 13.56 17.91 0 498.6 222.04 38468 +1917 288 18.45 12.45 16.8 0.93 468.34 166.3 38273 +1917 289 17.26 11.26 15.61 0.07 437.66 166.16 38079 +1917 290 14.51 8.51 12.86 0.13 373.25 167.68 37885 +1917 291 13.93 7.93 12.28 0.11 360.75 166.36 37693 +1917 292 12.88 6.88 11.23 0.42 339.03 165.53 37501 +1917 293 11.06 5.06 9.41 0 304.03 220.44 37311 +1917 294 11.73 5.73 10.08 0 316.53 216.68 37121 +1917 295 9.64 3.64 7.99 0.37 278.91 162.31 36933 +1917 296 11.16 5.16 9.51 0.08 305.87 158.99 36745 +1917 297 14.71 8.71 13.06 0 377.64 204.37 36560 +1917 298 13.15 7.15 11.5 0 344.5 204.07 36375 +1917 299 14.88 8.88 13.23 0 381.41 198.82 36191 +1917 300 15.71 9.71 14.06 0.1 400.28 146.19 36009 +1917 301 15.82 9.82 14.17 0.04 402.84 144.22 35829 +1917 302 19.42 13.42 17.77 0.5 494.69 137.62 35650 +1917 303 23.54 17.54 21.89 0.02 621.1 129.13 35472 +1917 304 21.07 15.07 19.42 0 542.4 175.43 35296 +1917 305 16.18 10.18 14.53 1.4 411.32 136.22 35122 +1917 306 13.64 7.64 11.99 1.21 354.63 137.31 34950 +1917 307 7.65 1.65 6 0.05 246.72 140.39 34779 +1917 308 7.4 1.4 5.75 0 242.92 184.79 34610 +1917 309 4.74 -1.26 3.09 0 205.42 184.61 34444 +1917 310 6.98 0.98 5.33 0.17 236.63 135.28 34279 +1917 311 6.32 0.32 4.67 0 227.04 178.72 34116 +1917 312 2.89 -3.11 1.24 0 182.38 178.51 33956 +1917 313 6.01 0.01 4.36 0 222.65 174.17 33797 +1917 314 7.45 1.45 5.8 0 243.67 171.05 33641 +1917 315 11.01 5.01 9.36 0.19 303.11 123.89 33488 +1917 316 8.74 2.74 7.09 0.44 263.94 123.91 33337 +1917 317 11.72 5.72 10.07 0.09 316.34 120.1 33188 +1917 318 8.7 2.7 7.05 0 263.29 160.74 33042 +1917 319 11.35 5.35 9.7 0.02 309.39 117.41 32899 +1917 320 13.59 7.59 11.94 0 353.59 152.27 32758 +1917 321 12.56 6.56 10.91 0 332.64 151.36 32620 +1917 322 12.54 6.54 10.89 0 332.24 149.61 32486 +1917 323 8.49 2.49 6.84 0.01 259.9 113.89 32354 +1917 324 10.31 4.31 8.66 0.42 290.53 111.17 32225 +1917 325 11 5 9.35 0.46 302.93 109.41 32100 +1917 326 8.09 2.09 6.44 0.08 253.55 110.24 31977 +1917 327 4.31 -1.69 2.66 0 199.85 147.79 31858 +1917 328 6.46 0.46 4.81 0.92 229.04 108.3 31743 +1917 329 4.47 -1.53 2.82 0.17 201.91 108.16 31631 +1917 330 9.49 3.49 7.84 1.01 276.37 104.36 31522 +1917 331 6 0 4.35 0.04 222.51 105.34 31417 +1917 332 6.6 0.6 4.95 0 231.07 138.41 31316 +1917 333 1.44 -4.56 -0.21 0 165.91 140.34 31218 +1917 334 3.5 -2.5 1.85 0 189.71 138.15 31125 +1917 335 -2.65 -8.65 -4.3 0 126.19 139.77 31035 +1917 336 -4.94 -10.94 -6.59 0 107.77 139.45 30949 +1917 337 -3.56 -9.56 -5.21 0 118.57 137.32 30867 +1917 338 -6.05 -12.05 -7.7 0 99.72 137.13 30790 +1917 339 -4.93 -10.93 -6.58 0.09 107.85 145.25 30716 +1917 340 -4.53 -10.53 -6.18 0.03 110.89 144.78 30647 +1917 341 5.58 -0.42 3.93 0.12 216.68 97.23 30582 +1917 342 4.85 -1.15 3.2 0 206.86 129.31 30521 +1917 343 4.68 -1.32 3.03 0 204.63 128.59 30465 +1917 344 6.36 0.36 4.71 0 227.61 126.44 30413 +1917 345 1.46 -4.54 -0.19 0 166.13 128.69 30366 +1917 346 -0.1 -6.1 -1.75 0 149.84 128.83 30323 +1917 347 1.79 -4.21 0.14 0 169.76 127.39 30284 +1917 348 3.81 -2.19 2.16 0.71 193.54 94.51 30251 +1917 349 2.57 -3.43 0.92 0.18 178.63 94.71 30221 +1917 350 -2.04 -8.04 -3.69 2.18 131.53 146.57 30197 +1917 351 -1.78 -7.78 -3.43 0 133.87 178.26 30177 +1917 352 -1.48 -7.48 -3.13 0 136.61 178.08 30162 +1917 353 1.46 -4.54 -0.19 0 166.13 176.61 30151 +1917 354 -0.43 -6.43 -2.08 0.48 146.58 147.21 30145 +1917 355 2.33 -3.67 0.68 0 175.86 177.4 30144 +1917 356 4.56 -1.44 2.91 0 203.07 175.64 30147 +1917 357 2.19 -3.81 0.54 0 174.26 176.63 30156 +1917 358 3.04 -2.96 1.39 0 184.16 175.87 30169 +1917 359 5.29 -0.71 3.64 0.4 212.73 142.93 30186 +1917 360 1.23 -4.77 -0.42 0.02 163.64 144.58 30208 +1917 361 3.56 -2.44 1.91 0.01 190.45 143.46 30235 +1917 362 -0.76 -6.76 -2.41 0 143.38 177.34 30267 +1917 363 -0.02 -6.02 -1.67 0.07 150.64 145.61 30303 +1917 364 2.36 -3.64 0.71 0 176.2 176.73 30343 +1917 365 -0.73 -6.73 -2.38 0 143.67 178.61 30388 +1918 1 3.79 -2.21 2.14 0 193.29 176.8 30438 +1918 2 3.94 -2.06 2.29 0 195.16 176.84 30492 +1918 3 1.14 -4.86 -0.51 0.11 162.67 146.01 30551 +1918 4 3.19 -2.81 1.54 0 185.95 178.34 30614 +1918 5 4.19 -1.81 2.54 0.1 198.32 144.85 30681 +1918 6 2.5 -3.5 0.85 0 177.82 179.16 30752 +1918 7 3.37 -2.63 1.72 0.14 188.13 145.46 30828 +1918 8 7.31 1.31 5.66 0 241.56 176.91 30907 +1918 9 8.8 2.8 7.15 0 264.91 175.78 30991 +1918 10 8.41 2.41 6.76 1.15 258.62 101 31079 +1918 11 2 -4 0.35 0.16 172.11 104.76 31171 +1918 12 -1.09 -7.09 -2.74 0 140.24 142.12 31266 +1918 13 -0.49 -6.49 -2.14 0 145.99 143.5 31366 +1918 14 4.43 -1.57 2.78 0 201.39 142.44 31469 +1918 15 4.21 -1.79 2.56 0 198.57 144.02 31575 +1918 16 4.51 -1.49 2.86 0 202.42 145.12 31686 +1918 17 5.32 -0.68 3.67 0 213.14 146.28 31800 +1918 18 4.75 -1.25 3.1 0 205.55 148.54 31917 +1918 19 5.68 -0.32 4.03 0 218.05 149.85 32038 +1918 20 5.42 -0.58 3.77 0 214.49 151.61 32161 +1918 21 1.33 -4.67 -0.32 0 164.72 156.05 32289 +1918 22 4.53 -1.47 2.88 0 202.68 155.94 32419 +1918 23 7.38 1.38 5.73 0 242.61 155.66 32552 +1918 24 5.73 -0.27 4.08 0.29 218.75 119.21 32688 +1918 25 4.43 -1.57 2.78 0 201.39 161.72 32827 +1918 26 3.65 -2.35 2 0 191.56 164.15 32969 +1918 27 -1.06 -7.06 -2.71 0 140.52 168.76 33114 +1918 28 0.06 -5.94 -1.59 0 151.45 170.44 33261 +1918 29 -3.65 -9.65 -5.3 0 117.84 174.52 33411 +1918 30 -1.89 -7.89 -3.54 0.42 132.87 172.57 33564 +1918 31 0.99 -5.01 -0.66 0 161.07 217.23 33718 +1918 32 6.15 0.15 4.5 0 224.62 215 33875 +1918 33 7.55 1.55 5.9 0 245.19 177.15 34035 +1918 34 3.95 -2.05 2.3 0 195.29 182.14 34196 +1918 35 0.9 -5.1 -0.75 0 160.12 186.22 34360 +1918 36 3.1 -2.9 1.45 0 184.88 187.39 34526 +1918 37 -0.8 -6.8 -2.45 0 143 192.14 34694 +1918 38 1.48 -4.52 -0.17 0 166.35 193.62 34863 +1918 39 3.24 -2.76 1.59 0 186.56 195.1 35035 +1918 40 3.08 -2.92 1.43 0 184.64 197.83 35208 +1918 41 5.26 -0.74 3.61 0 212.33 198.83 35383 +1918 42 -0.19 -6.19 -1.84 0 148.95 205.1 35560 +1918 43 -1.01 -7.01 -2.66 0 141 208.29 35738 +1918 44 2.21 -3.79 0.56 0 174.49 208.93 35918 +1918 45 1.72 -4.28 0.07 0 168.99 211.9 36099 +1918 46 4 -2 2.35 0 195.92 212.97 36282 +1918 47 7.02 1.02 5.37 0 237.22 213.18 36466 +1918 48 6.59 0.59 4.94 0 230.92 216.38 36652 +1918 49 8.53 2.53 6.88 0 260.54 217.2 36838 +1918 50 5.24 -0.76 3.59 0 212.06 223.03 37026 +1918 51 7.45 1.45 5.8 0 243.67 223.91 37215 +1918 52 4.71 -1.29 3.06 0 205.02 229.29 37405 +1918 53 5.52 -0.48 3.87 0 215.86 231.54 37596 +1918 54 4.57 -1.43 2.92 0 203.2 235.14 37788 +1918 55 4.3 -1.7 2.65 0.08 199.72 178.79 37981 +1918 56 1.84 -4.16 0.19 0 170.32 243.05 38175 +1918 57 3.43 -2.57 1.78 0.02 188.86 183.54 38370 +1918 58 6.29 0.29 4.64 0.58 226.61 183.79 38565 +1918 59 1.61 -4.39 -0.04 0 167.77 251.84 38761 +1918 60 9.43 3.43 7.78 0 275.36 247.1 38958 +1918 61 10.14 4.14 8.49 0.54 287.55 186.82 39156 +1918 62 9.91 3.91 8.26 0 283.55 252.15 39355 +1918 63 6.5 0.5 4.85 0 229.62 259.16 39553 +1918 64 6.01 0.01 4.36 0 222.65 262.58 39753 +1918 65 14 8 12.35 0 362.24 254.65 39953 +1918 66 13.17 7.17 11.52 0 344.91 258.71 40154 +1918 67 12.9 6.9 11.25 0.44 339.43 196.49 40355 +1918 68 8.6 2.6 6.95 0.54 261.67 203.26 40556 +1918 69 9.21 3.21 7.56 0 271.67 272.83 40758 +1918 70 9.54 3.54 7.89 0 277.21 275.21 40960 +1918 71 4.76 -1.24 3.11 0 205.68 283.75 41163 +1918 72 7.82 1.82 6.17 0 249.34 283.16 41366 +1918 73 9 3 7.35 0 268.19 284.3 41569 +1918 74 6.84 0.84 5.19 0.1 234.57 217.32 41772 +1918 75 2.94 -3.06 1.29 0 182.97 296.59 41976 +1918 76 2.72 -3.28 1.07 0 180.38 299.47 42179 +1918 77 8.82 2.82 7.17 0 265.24 295.22 42383 +1918 78 7.79 1.79 6.14 0 248.88 299.25 42587 +1918 79 9.58 3.58 7.93 0 277.89 299.53 42791 +1918 80 6.05 0.05 4.4 0 223.21 306.67 42996 +1918 81 8.33 2.33 6.68 0 257.34 306.39 43200 +1918 82 7.88 1.88 6.23 0 250.27 309.65 43404 +1918 83 7.74 1.74 6.09 0 248.11 312.34 43608 +1918 84 8.04 2.04 6.39 0 252.77 314.48 43812 +1918 85 8.8 2.8 7.15 0 264.91 315.93 44016 +1918 86 11.08 5.08 9.43 0 304.4 314.8 44220 +1918 87 8.87 2.87 7.22 0 266.06 320.77 44424 +1918 88 7.53 1.53 5.88 0 244.89 325.01 44627 +1918 89 7.29 1.29 5.64 0 241.26 327.63 44831 +1918 90 8.37 2.37 6.72 0 257.98 328.51 45034 +1918 91 15.41 9.41 13.76 0 393.37 318.06 45237 +1918 92 15.23 9.23 13.58 0 389.27 320.65 45439 +1918 93 12.77 6.77 11.12 0.01 336.82 245.92 45642 +1918 94 13.93 7.93 12.28 0 360.75 327.72 45843 +1918 95 13.6 7.6 11.95 0 353.8 330.5 46045 +1918 96 13.91 7.91 12.26 1.23 360.32 248.97 46246 +1918 97 16.48 10.48 14.83 0.03 418.5 246.13 46446 +1918 98 16.32 10.32 14.67 0 414.65 330.48 46647 +1918 99 18.2 12.2 16.55 0 461.75 327.61 46846 +1918 100 18.35 12.35 16.7 0.37 465.7 246.81 47045 +1918 101 14.94 8.94 13.29 0.01 382.75 254.61 47243 +1918 102 10.61 4.61 8.96 0.08 295.87 262.51 47441 +1918 103 11.1 5.1 9.45 0 304.76 350.99 47638 +1918 104 12.51 6.51 10.86 0.03 331.65 262.61 47834 +1918 105 13.76 7.76 12.11 0 357.15 349.36 48030 +1918 106 15.44 9.44 13.79 0.04 394.06 260.4 48225 +1918 107 14.42 8.42 12.77 0.11 371.28 263.4 48419 +1918 108 13.56 7.56 11.91 0.24 352.96 266.12 48612 +1918 109 14.1 8.1 12.45 1.24 364.37 266.43 48804 +1918 110 12.12 6.12 10.47 0.39 324.02 270.6 48995 +1918 111 14.73 8.73 13.08 0.01 378.08 267.57 49185 +1918 112 13.64 7.64 11.99 0.88 354.63 270.54 49374 +1918 113 13.57 7.57 11.92 0.53 353.17 271.65 49561 +1918 114 11.56 5.56 9.91 0 313.32 367.82 49748 +1918 115 12.8 6.8 11.15 0 337.42 366.77 49933 +1918 116 16.3 10.3 14.65 0 414.18 359.84 50117 +1918 117 18.82 12.82 17.17 0 478.25 354.1 50300 +1918 118 18.67 12.67 17.02 0 474.21 355.83 50481 +1918 119 17.77 11.77 16.12 0 450.6 359.61 50661 +1918 120 15.07 9.07 13.42 0 385.66 367.86 50840 +1918 121 19.27 13.27 17.62 0.54 490.54 268.05 51016 +1918 122 21.4 15.4 19.75 0.22 552.4 263.64 51191 +1918 123 23.23 17.23 21.58 0 610.73 345.72 51365 +1918 124 20.91 14.91 19.26 0.32 537.61 266.44 51536 +1918 125 21.49 15.49 19.84 0.06 555.15 265.63 51706 +1918 126 14.43 8.43 12.78 0.01 371.5 281.85 51874 +1918 127 15.94 9.94 14.29 0.23 405.65 279.71 52039 +1918 128 17.89 11.89 16.24 0.03 453.69 276.43 52203 +1918 129 18.58 12.58 16.93 0.04 471.8 275.52 52365 +1918 130 21.01 15.01 19.36 0.05 540.6 270.16 52524 +1918 131 21.5 15.5 19.85 0.02 555.46 269.44 52681 +1918 132 16.8 10.8 15.15 0.59 426.27 281.17 52836 +1918 133 13.04 7.04 11.39 0 342.26 384.87 52989 +1918 134 17.12 11.12 15.47 0.33 434.17 281.56 53138 +1918 135 21.31 15.31 19.66 0 549.66 362.77 53286 +1918 136 18.84 12.84 17.19 0 478.79 371.64 53430 +1918 137 21.67 15.67 20.02 0.68 560.7 272.08 53572 +1918 138 21.86 15.86 20.21 0.06 566.6 271.99 53711 +1918 139 23.06 17.06 21.41 0 605.1 358.72 53848 +1918 140 21.11 15.11 19.46 0.05 543.61 274.89 53981 +1918 141 18.56 12.56 16.91 0 471.27 375.39 54111 +1918 142 21.23 15.23 19.58 0 547.23 366.99 54238 +1918 143 18.98 12.98 17.33 0.15 482.59 281.33 54362 +1918 144 17.31 11.31 15.66 0.42 438.92 285.46 54483 +1918 145 18.34 12.34 16.69 1.89 465.43 283.53 54600 +1918 146 13.17 7.17 11.52 0.99 344.91 294.02 54714 +1918 147 11.24 5.24 9.59 0 307.35 396.62 54824 +1918 148 17.31 11.31 15.66 0.09 438.92 286.74 54931 +1918 149 15.44 9.44 13.79 1.46 394.06 290.81 55034 +1918 150 11.1 5.1 9.45 1.37 304.76 298.47 55134 +1918 151 11.95 5.95 10.3 0 320.74 396.62 55229 +1918 152 13.05 7.05 11.4 0.11 342.47 295.77 55321 +1918 153 15.72 9.72 14.07 0 400.51 388.11 55409 +1918 154 17.01 11.01 15.36 1.08 431.44 288.67 55492 +1918 155 19.46 13.46 17.81 0 495.8 377.61 55572 +1918 156 20.19 14.19 18.54 0.39 516.49 281.61 55648 +1918 157 20.23 14.23 18.58 0 517.65 375.52 55719 +1918 158 20.06 14.06 18.41 0 512.76 376.27 55786 +1918 159 17.51 11.51 15.86 0.99 443.96 288.42 55849 +1918 160 19.75 13.75 18.1 0.93 503.94 283.3 55908 +1918 161 16.51 10.51 14.86 0.11 419.22 290.75 55962 +1918 162 17.42 11.42 15.77 0 441.69 385.14 56011 +1918 163 20.93 14.93 19.28 0 538.21 374 56056 +1918 164 22.42 16.42 20.77 0.32 584.3 276.37 56097 +1918 165 19.95 13.95 18.3 0.81 509.61 283.16 56133 +1918 166 19.59 13.59 17.94 0 499.44 378.83 56165 +1918 167 20.52 14.52 18.87 0 526.08 375.61 56192 +1918 168 18.11 12.11 16.46 2.06 459.4 287.66 56214 +1918 169 17.84 11.84 16.19 0 452.4 384.37 56231 +1918 170 15.56 9.56 13.91 0 396.81 390.76 56244 +1918 171 16.34 10.34 14.69 0.73 415.13 291.55 56252 +1918 172 15.79 9.79 14.14 0.2 402.14 292.65 56256 +1918 173 13.83 7.83 12.18 0.01 358.63 296.32 56255 +1918 174 11.49 5.49 9.84 0.15 312.01 300.12 56249 +1918 175 17.22 11.22 15.57 0.04 436.66 289.58 56238 +1918 176 13.92 7.92 12.27 0.01 360.53 296.05 56223 +1918 177 15.11 9.11 13.46 0.02 386.56 293.77 56203 +1918 178 19.99 13.99 18.34 0.43 510.75 283 56179 +1918 179 22.74 16.74 21.09 0 594.62 367.16 56150 +1918 180 26.83 20.83 25.18 0 740.8 348.92 56116 +1918 181 24.4 18.4 22.75 0.12 650.69 270.08 56078 +1918 182 23.68 17.68 22.03 0.1 625.84 272.26 56035 +1918 183 20.66 14.66 19.01 0.31 530.2 280.8 55987 +1918 184 19.44 13.44 17.79 0.02 495.25 283.79 55935 +1918 185 17.37 11.37 15.72 0 440.43 384.68 55879 +1918 186 20.87 14.87 19.22 0 536.42 373.16 55818 +1918 187 24.59 18.59 22.94 0 657.38 358.31 55753 +1918 188 23.57 17.57 21.92 0.02 622.12 271.78 55684 +1918 189 27.64 21.64 25.99 0.47 773.09 257.56 55611 +1918 190 25.98 19.98 24.33 0.75 708.15 263.41 55533 +1918 191 28.01 22.01 26.36 0.82 788.23 255.66 55451 +1918 192 29.44 23.44 27.79 0.06 849.12 249.61 55366 +1918 193 27.05 21.05 25.4 1.19 749.45 258.94 55276 +1918 194 23.86 17.86 22.21 0 631.98 359.6 55182 +1918 195 24.15 18.15 22.5 0.47 641.97 268.58 55085 +1918 196 23.57 17.57 21.92 1.44 622.12 270.1 54984 +1918 197 23.61 17.61 21.96 1.1 623.47 269.64 54879 +1918 198 19.94 13.94 18.29 0 509.33 372.74 54770 +1918 199 21.91 15.91 20.26 0 568.16 365.43 54658 +1918 200 22.09 16.09 20.44 0.18 573.81 273.27 54542 +1918 201 21.24 15.24 19.59 0 547.53 367.02 54423 +1918 202 20 14 18.35 0.6 511.04 278.06 54301 +1918 203 20.51 14.51 18.86 0.59 525.79 276.39 54176 +1918 204 18.38 12.38 16.73 0.1 466.49 281.17 54047 +1918 205 21.67 15.67 20.02 0 560.7 363.38 53915 +1918 206 22.36 16.36 20.71 0 582.38 360.25 53780 +1918 207 21.91 15.91 20.26 0.56 568.16 270.97 53643 +1918 208 18.04 12.04 16.39 0.69 457.57 280.12 53502 +1918 209 18.89 12.89 17.24 0.3 480.14 277.69 53359 +1918 210 22.34 16.34 20.69 0.01 581.74 268.33 53213 +1918 211 21.43 15.43 19.78 0.03 553.32 270.27 53064 +1918 212 19.45 13.45 17.8 0.58 495.53 274.7 52913 +1918 213 21.42 15.42 19.77 0.16 553.01 269.14 52760 +1918 214 23.01 17.01 21.36 0 603.45 352.18 52604 +1918 215 25.23 19.23 23.58 0 680.36 342.33 52445 +1918 216 21.58 15.58 19.93 0 557.92 355.86 52285 +1918 217 22.15 16.15 20.5 0.14 575.7 264.68 52122 +1918 218 20.86 14.86 19.21 0.25 536.12 267.52 51958 +1918 219 21.23 15.23 19.58 0 547.23 354.37 51791 +1918 220 18.51 12.51 16.86 0 469.94 362.23 51622 +1918 221 14.39 8.39 12.74 0 370.63 372.13 51451 +1918 222 22.16 16.16 20.51 0.63 576.02 261.07 51279 +1918 223 16.3 10.3 14.65 0.36 414.18 273.87 51105 +1918 224 15.41 9.41 13.76 0.07 393.37 274.75 50929 +1918 225 19.48 13.48 17.83 1.19 496.36 265.38 50751 +1918 226 21.02 15.02 19.37 0.92 540.9 260.76 50572 +1918 227 22.32 16.32 20.67 2.89 581.1 256.38 50392 +1918 228 23.03 17.03 21.38 1.65 604.11 253.51 50210 +1918 229 24.17 18.17 22.52 0.39 642.66 249.28 50026 +1918 230 23.17 17.17 21.52 1.01 608.73 251.28 49842 +1918 231 21.4 15.4 19.75 1.61 552.4 254.99 49656 +1918 232 21.93 15.93 20.28 0.89 568.78 252.61 49469 +1918 233 22.5 16.5 20.85 0.2 586.86 250.04 49280 +1918 234 20.49 14.49 18.84 0.37 525.2 254.14 49091 +1918 235 20.91 14.91 19.26 0.3 537.61 252.01 48900 +1918 236 23.02 17.02 21.37 0.6 603.78 245.45 48709 +1918 237 22.94 16.94 21.29 1.44 601.15 244.47 48516 +1918 238 24.05 18.05 22.4 0 638.51 320.16 48323 +1918 239 26.26 20.26 24.61 0.09 718.77 232.23 48128 +1918 240 26.01 20.01 24.36 0.09 709.28 231.79 47933 +1918 241 19.1 13.1 17.45 0.1 485.86 248.95 47737 +1918 242 19.18 13.18 17.53 0.19 488.06 247.48 47541 +1918 243 22.57 16.57 20.92 0.11 589.12 237.98 47343 +1918 244 21.78 15.78 20.13 0 564.11 318.23 47145 +1918 245 23.49 17.49 21.84 0 619.42 310.47 46947 +1918 246 21.65 15.65 20 0 560.08 314.95 46747 +1918 247 21.68 15.68 20.03 0 561.01 313.04 46547 +1918 248 21.3 15.3 19.65 0.45 549.35 234.28 46347 +1918 249 25.94 19.94 24.29 0 706.64 293.55 46146 +1918 250 23.87 17.87 22.22 0 632.32 299.72 45945 +1918 251 20.92 14.92 19.27 0 537.91 307.57 45743 +1918 252 21.04 15.04 19.39 0 541.5 305.09 45541 +1918 253 20.61 14.61 18.96 0 528.72 304.33 45339 +1918 254 17.52 11.52 15.87 0 444.22 310.67 45136 +1918 255 19.5 13.5 17.85 0.71 496.92 227.41 44933 +1918 256 15.68 9.68 14.03 0 399.59 310.46 44730 +1918 257 14.86 8.86 13.21 0.73 380.96 232.53 44527 +1918 258 16.6 10.6 14.95 0.52 421.4 227.89 44323 +1918 259 15.2 9.2 13.55 0.01 388.59 228.38 44119 +1918 260 18.18 12.18 16.53 0.91 461.23 221.44 43915 +1918 261 16.02 10.02 14.37 0 407.53 297.88 43711 +1918 262 18.25 12.25 16.6 0 463.06 290.31 43507 +1918 263 16.98 10.98 15.33 0 430.7 290.9 43303 +1918 264 21.47 15.47 19.82 0 554.54 276.66 43099 +1918 265 19.61 13.61 17.96 0 500 279.55 42894 +1918 266 21.49 15.49 19.84 0.49 555.15 203.95 42690 +1918 267 19.87 13.87 18.22 0.52 507.33 205.38 42486 +1918 268 18.28 12.28 16.63 0.44 463.85 206.49 42282 +1918 269 19.14 13.14 17.49 0 486.96 270.76 42078 +1918 270 18.63 12.63 16.98 0.06 473.14 202.07 41875 +1918 271 16.78 10.78 15.13 1.34 425.78 203.29 41671 +1918 272 16.76 10.76 15.11 0.8 425.29 201.3 41468 +1918 273 17.85 11.85 16.2 0.08 452.65 197.64 41265 +1918 274 10.56 4.56 8.91 0.91 294.97 205.6 41062 +1918 275 12.46 6.46 10.81 0.78 330.66 201.32 40860 +1918 276 12.64 6.64 10.99 1.07 334.22 199.06 40658 +1918 277 10.53 4.53 8.88 0.76 294.44 199.43 40456 +1918 278 12.4 6.4 10.75 0.24 329.48 195.17 40255 +1918 279 11.88 5.88 10.23 0 319.39 258.2 40054 +1918 280 16.43 10.43 14.78 0 417.29 247.7 39854 +1918 281 15.04 9.04 13.39 0.01 384.99 185.72 39654 +1918 282 10.6 4.6 8.95 0 295.69 251.84 39455 +1918 283 10.38 4.38 8.73 0 291.77 249.28 39256 +1918 284 14.46 8.46 12.81 0 372.15 240.11 39058 +1918 285 17.41 11.41 15.76 0 441.43 232.09 38861 +1918 286 17.52 11.52 15.87 0.33 444.22 171.88 38664 +1918 287 14.34 8.34 12.69 0.39 369.54 174.03 38468 +1918 288 16.65 10.65 15 0.12 422.61 168.95 38273 +1918 289 14.06 8.06 12.41 0.11 363.52 170.34 38079 +1918 290 8.66 2.66 7.01 0.88 262.64 173.63 37885 +1918 291 6.47 0.47 4.82 0.02 229.19 173.29 37693 +1918 292 8.46 2.46 6.81 0 259.42 226.26 37501 +1918 293 10.58 4.58 8.93 0 295.33 221.04 37311 +1918 294 10.18 4.18 8.53 0 288.25 218.63 37121 +1918 295 12.04 6.04 10.39 0.06 322.47 160.08 36933 +1918 296 12.61 6.61 10.96 0.06 333.63 157.58 36745 +1918 297 14.45 8.45 12.8 0.02 371.94 153.57 36560 +1918 298 14.63 8.63 12.98 0.5 375.88 151.45 36375 +1918 299 17.94 11.94 16.29 0 454.98 193.72 36191 +1918 300 15.24 9.24 13.59 0.43 389.5 146.74 36009 +1918 301 13.7 7.7 12.05 0.15 355.89 146.58 35829 +1918 302 15.66 9.66 14.01 0.38 399.12 142.5 35650 +1918 303 11.95 5.95 10.3 0.84 320.74 144.44 35472 +1918 304 14.44 8.44 12.79 0.56 371.72 140.16 35296 +1918 305 4.64 -1.36 2.99 0 204.11 194.51 35122 +1918 306 5.4 -0.6 3.75 0 214.22 191.63 34950 +1918 307 9.87 3.87 8.22 0 282.86 185.03 34779 +1918 308 10.85 4.85 9.2 0 300.2 181.39 34610 +1918 309 7.36 1.36 5.71 0 242.31 182.5 34444 +1918 310 9.17 3.17 7.52 0 271 178.39 34279 +1918 311 6.2 0.2 4.55 0 225.33 178.82 34116 +1918 312 4.69 -1.31 3.04 0.03 204.76 132.97 33956 +1918 313 2.8 -3.2 1.15 0 181.32 176.41 33797 +1918 314 4.83 -1.17 3.18 0 206.6 173.07 33641 +1918 315 7.02 1.02 5.37 0 237.22 168.86 33488 +1918 316 7.71 1.71 6.06 0 247.65 166.11 33337 +1918 317 6.86 0.86 5.21 0 234.86 164.6 33188 +1918 318 4.71 -1.29 3.06 0 205.02 163.83 33042 +1918 319 10.46 4.46 8.81 0 293.19 157.43 32899 +1918 320 10.37 4.37 8.72 0 291.59 155.67 32758 +1918 321 8.28 2.28 6.63 0.01 256.55 116.59 32620 +1918 322 5.06 -0.94 3.41 0.5 209.65 117.03 32486 +1918 323 1.4 -4.6 -0.25 0 165.48 156.59 32354 +1918 324 0.99 -5.01 -0.66 0 161.07 154.72 32225 +1918 325 5.6 -0.4 3.95 0.01 216.95 112.7 32100 +1918 326 2.73 -3.27 1.08 0 180.49 150.58 31977 +1918 327 7.32 1.32 5.67 0 241.71 145.74 31858 +1918 328 9.42 3.42 7.77 0.07 275.19 106.58 31743 +1918 329 7.26 1.26 5.61 0.17 240.81 106.75 31631 +1918 330 8.43 2.43 6.78 0.11 258.94 105 31522 +1918 331 4.95 -1.05 3.3 0.45 208.18 105.85 31417 +1918 332 5.98 -0.02 4.33 0 222.23 138.83 31316 +1918 333 3.65 -2.35 2 0 191.56 139.18 31218 +1918 334 5.06 -0.94 3.41 0 209.65 137.24 31125 +1918 335 1.04 -4.96 -0.61 0.04 161.6 103.68 31035 +1918 336 1.05 -4.95 -0.6 0.06 161.71 102.86 30949 +1918 337 2.97 -3.03 1.32 0.31 183.33 100.89 30867 +1918 338 1.37 -4.63 -0.28 0.01 165.15 100.78 30790 +1918 339 3.2 -2.8 1.55 0 186.07 132.65 30716 +1918 340 4.56 -1.44 2.91 0 203.07 131.16 30647 +1918 341 5.03 -0.97 3.38 0 209.25 129.97 30582 +1918 342 8.03 2.03 6.38 0 252.61 127.24 30521 +1918 343 9.14 3.14 7.49 1.75 270.51 94.2 30465 +1918 344 9.35 3.35 7.7 0 274.01 124.32 30413 +1918 345 9.83 3.83 8.18 0.48 282.17 92.65 30366 +1918 346 4.97 -1.03 3.32 0 208.45 126.31 30323 +1918 347 3.53 -2.47 1.88 0 190.08 126.52 30284 +1918 348 5.72 -0.28 4.07 0 218.61 124.92 30251 +1918 349 6.37 0.37 4.72 0 227.75 124.14 30221 +1918 350 9.33 3.33 7.68 0 273.67 121.75 30197 +1918 351 9.27 3.27 7.62 0.29 272.67 91.18 30177 +1918 352 9.03 3.03 7.38 1.18 268.69 91.25 30162 +1918 353 7.52 1.52 5.87 0.41 244.74 92.01 30151 +1918 354 4.73 -1.27 3.08 0 205.29 124.38 30145 +1918 355 5.34 -0.66 3.69 0 213.41 124.03 30144 +1918 356 3.08 -2.92 1.43 0 184.64 125.3 30147 +1918 357 1.36 -4.64 -0.29 0.39 165.04 94.64 30156 +1918 358 2.87 -3.13 1.22 0 182.14 125.55 30169 +1918 359 4.83 -1.17 3.18 0.92 206.6 93.46 30186 +1918 360 5.18 -0.82 3.53 0 211.25 124.78 30208 +1918 361 4.91 -1.09 3.26 0 207.65 125.27 30235 +1918 362 2.9 -3.1 1.25 0 182.5 126.79 30267 +1918 363 4.48 -1.52 2.83 0 202.04 126.53 30303 +1918 364 5.72 -0.28 4.07 0 218.61 126.2 30343 +1918 365 6.51 0.51 4.86 0 229.76 126.26 30388 +1919 1 7.35 1.35 5.7 0 242.16 126.59 30438 +1919 2 5.42 -0.58 3.77 0 214.49 128.56 30492 +1919 3 5.11 -0.89 3.46 0 210.31 129.69 30551 +1919 4 6.5 0.5 4.85 0 229.62 129.72 30614 +1919 5 4.27 -1.73 2.62 0.05 199.34 98.8 30681 +1919 6 3.69 -2.31 2.04 0.02 192.05 99.71 30752 +1919 7 7.17 1.17 5.52 0.62 239.46 98.68 30828 +1919 8 4.35 -1.65 2.7 0.36 200.36 101.14 30907 +1919 9 2.8 -3.2 1.15 1.12 181.32 102.73 30991 +1919 10 2.34 -3.66 0.69 0.41 175.97 103.89 31079 +1919 11 4.91 -1.09 3.26 0.34 207.65 103.54 31171 +1919 12 11.02 5.02 9.37 0.49 303.3 100.83 31266 +1919 13 4.67 -1.33 3.02 0.01 204.5 105.62 31366 +1919 14 4.55 -1.45 2.9 0.13 202.94 106.78 31469 +1919 15 -0.42 -6.42 -2.07 0 146.68 146.42 31575 +1919 16 -0.29 -6.29 -1.94 0 147.96 147.66 31686 +1919 17 8.11 2.11 6.46 0 253.87 144.27 31800 +1919 18 7.67 1.67 6.02 0 247.03 146.49 31917 +1919 19 7.28 1.28 5.63 0 241.11 148.7 32038 +1919 20 6.8 0.8 5.15 0 233.98 150.63 32161 +1919 21 3.96 -2.04 2.31 0 195.41 154.55 32289 +1919 22 1.02 -4.98 -0.63 0.06 161.39 118.48 32419 +1919 23 2.13 -3.87 0.48 1.09 173.58 119.37 32552 +1919 24 0.27 -5.73 -1.38 0 153.58 162.22 32688 +1919 25 3.18 -2.82 1.53 0 185.83 162.51 32827 +1919 26 5.96 -0.04 4.31 0.07 221.95 121.93 32969 +1919 27 5.7 -0.3 4.05 0 218.33 164.78 33114 +1919 28 4.4 -1.6 2.75 0 201 167.89 33261 +1919 29 4.57 -1.43 2.92 0.19 203.2 127.61 33411 +1919 30 1.51 -4.49 -0.14 0.78 166.68 130.74 33564 +1919 31 0.82 -5.18 -0.83 0 159.27 177.1 33718 +1919 32 1.14 -4.86 -0.51 0.36 162.67 134.29 33875 +1919 33 -0.09 -6.09 -1.74 0 149.94 182.37 34035 +1919 34 3.32 -2.68 1.67 0 187.52 182.57 34196 +1919 35 6 0 4.35 0 222.51 182.76 34360 +1919 36 3.73 -2.27 2.08 0 192.55 186.96 34526 +1919 37 7.61 1.61 5.96 0 246.11 186.29 34694 +1919 38 4.19 -1.81 2.54 0 198.32 191.81 34863 +1919 39 4.48 -1.52 2.83 0 202.04 194.2 35035 +1919 40 2.12 -3.88 0.47 0.43 173.47 148.86 35208 +1919 41 0.74 -5.26 -0.91 0 158.43 201.97 35383 +1919 42 -1.24 -7.24 -2.89 0 138.83 205.67 35560 +1919 43 -1.55 -7.55 -3.2 0.18 135.96 193.85 35738 +1919 44 -3.1 -9.1 -4.75 0 122.37 249.18 35918 +1919 45 -0.77 -6.77 -2.42 0 143.28 250.46 36099 +1919 46 -0.14 -6.14 -1.79 0.04 149.44 198.8 36282 +1919 47 1.41 -4.59 -0.24 0.18 165.58 199.87 36466 +1919 48 4.13 -1.87 2.48 0 197.56 218.51 36652 +1919 49 6.87 0.87 5.22 0 235.01 218.88 36838 +1919 50 7.42 1.42 5.77 0 243.22 220.99 37026 +1919 51 5.41 -0.59 3.76 0 214.36 225.85 37215 +1919 52 7.41 1.41 5.76 0.01 243.07 170.07 37405 +1919 53 5.1 -0.9 3.45 0.24 210.18 173.94 37596 +1919 54 5.69 -0.31 4.04 0 218.19 234.14 37788 +1919 55 7.7 1.7 6.05 0 247.49 235.12 37981 +1919 56 6.52 0.52 4.87 0.2 229.91 179.26 38175 +1919 57 7.5 1.5 5.85 0.82 244.43 180.66 38370 +1919 58 3.92 -2.08 2.27 0.03 194.91 185.44 38565 +1919 59 4.52 -1.48 2.87 0 202.55 249.45 38761 +1919 60 11.72 5.72 10.07 0.16 316.34 183.03 38958 +1919 61 5.1 -0.9 3.45 0.53 210.18 191.07 39156 +1919 62 3.6 -2.4 1.95 0 190.94 258.93 39355 +1919 63 9.88 3.88 8.23 0 283.03 255.17 39553 +1919 64 11.53 5.53 9.88 0.16 312.76 191.81 39753 +1919 65 9.49 3.49 7.84 0 276.37 261.41 39953 +1919 66 7.12 1.12 5.47 0 238.71 267.01 40154 +1919 67 10.15 4.15 8.5 0 287.72 266.11 40355 +1919 68 7.88 1.88 6.23 0 250.27 271.89 40556 +1919 69 8.12 2.12 6.47 0 254.02 274.22 40758 +1919 70 3.69 -2.31 2.04 0 192.05 281.85 40960 +1919 71 4.75 -1.25 3.1 0 205.55 283.76 41163 +1919 72 7.77 1.77 6.12 0 248.57 283.22 41366 +1919 73 7.98 1.98 6.33 0 251.83 285.62 41569 +1919 74 5.74 -0.26 4.09 0.05 218.88 218.26 41772 +1919 75 9.21 3.21 7.56 0.34 271.67 217.1 41976 +1919 76 8.49 2.49 6.84 0 259.9 293.07 42179 +1919 77 8.02 2.02 6.37 0 252.46 296.29 42383 +1919 78 7.25 1.25 5.6 0.4 240.65 224.95 42587 +1919 79 10.87 4.87 9.22 0 300.56 297.58 42791 +1919 80 7.81 1.81 6.16 0.01 249.19 228.37 42996 +1919 81 9.73 3.73 8.08 0.74 280.45 228.3 43200 +1919 82 10.44 4.44 8.79 0 292.83 305.97 43404 +1919 83 11.61 5.61 9.96 0.02 314.26 229.9 43608 +1919 84 11.18 5.18 9.53 0.12 306.24 232.33 43812 +1919 85 11.91 5.91 10.26 0 319.97 311.01 44016 +1919 86 9.01 3.01 7.36 0 268.36 318.03 44220 +1919 87 7.64 1.64 5.99 0.28 246.57 241.87 44424 +1919 88 6.09 0.09 4.44 0 223.77 326.86 44627 +1919 89 11.68 5.68 10.03 0 315.59 320.89 44831 +1919 90 9.49 3.49 7.84 0.93 276.37 245.14 45034 +1919 91 8.33 2.33 6.68 0 257.34 330.84 45237 +1919 92 9.95 3.95 8.3 0.12 284.24 247.97 45439 +1919 93 10.85 4.85 9.2 0.46 300.2 248.52 45642 +1919 94 12.66 6.66 11.01 0 334.62 330.24 45843 +1919 95 11.65 5.65 10 0 315.02 334.24 46045 +1919 96 11.35 5.35 9.7 0.11 309.39 252.66 46246 +1919 97 10.16 4.16 8.51 0.03 287.9 255.74 46446 +1919 98 11.82 5.82 10.17 0 318.25 340.04 46647 +1919 99 9.78 3.78 8.13 1.12 281.31 259.2 46846 +1919 100 10.9 4.9 9.25 0 301.11 345.66 47045 +1919 101 13.49 7.49 11.84 0.17 351.51 256.97 47243 +1919 102 12.07 6.07 10.42 0.56 323.05 260.51 47441 +1919 103 14.96 8.96 13.31 0.03 383.2 257.35 47638 +1919 104 14.64 8.64 12.99 0.27 376.1 259.24 47834 +1919 105 13.16 7.16 11.51 0.05 344.71 262.97 48030 +1919 106 5.24 -0.76 3.59 0 212.06 365.24 48225 +1919 107 8.45 2.45 6.8 0.43 259.26 271.83 48419 +1919 108 8.66 2.66 7.01 0.57 262.64 272.91 48612 +1919 109 6.03 0.03 4.38 0 222.93 369.36 48804 +1919 110 7.22 1.22 5.57 0 240.2 369.14 48995 +1919 111 11.77 5.77 10.12 0 317.3 363.04 49185 +1919 112 13.25 7.25 11.6 0.02 346.55 271.17 49374 +1919 113 12.86 6.86 11.21 0.01 338.63 272.79 49561 +1919 114 13.69 7.69 12.04 0.27 355.68 272.57 49748 +1919 115 14.1 8.1 12.45 0.91 364.37 272.96 49933 +1919 116 9.61 3.61 7.96 0.04 278.4 280.55 50117 +1919 117 10.57 4.57 8.92 0 295.15 373.68 50300 +1919 118 12.26 6.26 10.61 0.16 326.74 278.81 50481 +1919 119 9.92 3.92 8.27 0.93 283.72 283.05 50661 +1919 120 10.89 4.89 9.24 0.38 300.92 282.61 50840 +1919 121 13.12 7.12 11.47 0.22 343.89 280.09 51016 +1919 122 14.5 8.5 12.85 0 373.03 371.54 51191 +1919 123 12.19 6.19 10.54 0.28 325.37 283.24 51365 +1919 124 8.49 2.49 6.84 0.16 259.9 289.17 51536 +1919 125 8.95 2.95 7.3 0.65 267.37 289.35 51706 +1919 126 11.65 5.65 10 0.39 315.02 286.39 51874 +1919 127 12.42 6.42 10.77 0.07 329.87 285.88 52039 +1919 128 12.3 6.3 10.65 0 327.52 382.43 52203 +1919 129 12.09 6.09 10.44 0.33 323.43 287.8 52365 +1919 130 9.84 3.84 8.19 0.33 282.34 291.67 52524 +1919 131 8.71 2.71 7.06 0.63 263.45 293.75 52681 +1919 132 8.56 2.56 6.91 0.13 261.02 294.58 52836 +1919 133 12.98 6.98 11.33 1.23 341.05 288.75 52989 +1919 134 13.48 7.48 11.83 0.84 351.3 288.46 53138 +1919 135 17.97 11.97 16.32 0 455.76 373.65 53286 +1919 136 17.72 11.72 16.07 0 449.31 375.02 53430 +1919 137 14.89 8.89 13.24 0.18 381.63 287.5 53572 +1919 138 15.83 9.83 14.18 0 403.08 381.55 53711 +1919 139 19.79 13.79 18.14 0.89 505.07 277.92 53848 +1919 140 18.62 12.62 16.97 0.6 472.87 281.08 53981 +1919 141 21.36 15.36 19.71 0.24 551.18 274.53 54111 +1919 142 18.32 12.32 16.67 0.16 464.91 282.47 54238 +1919 143 15.92 9.92 14.27 0 405.18 383.97 54362 +1919 144 14.86 8.86 13.21 0 380.96 387.17 54483 +1919 145 10.56 4.56 8.91 0 294.97 397.07 54600 +1919 146 16.77 10.77 15.12 0 425.54 382.99 54714 +1919 147 14.81 8.81 13.16 0 379.85 388.63 54824 +1919 148 16.16 10.16 14.51 0 410.84 385.53 54931 +1919 149 18.52 12.52 16.87 0.2 470.21 284.27 55034 +1919 150 20.01 14.01 18.36 0 511.32 374.54 55134 +1919 151 19.91 13.91 18.26 0.02 508.47 281.45 55229 +1919 152 23.11 17.11 21.46 0.01 606.75 272.7 55321 +1919 153 23.67 17.67 22.02 0.41 625.5 271.16 55409 +1919 154 23.99 17.99 22.34 0.27 636.44 270.39 55492 +1919 155 19.95 13.95 18.3 0 509.61 375.98 55572 +1919 156 20.4 14.4 18.75 0.13 522.58 281.07 55648 +1919 157 23.72 17.72 22.07 0 627.2 362.31 55719 +1919 158 24.36 18.36 22.71 0 649.28 359.76 55786 +1919 159 24.41 18.41 22.76 0.07 651.04 269.84 55849 +1919 160 18.18 12.18 16.53 0.05 461.23 287.06 55908 +1919 161 19.07 13.07 17.42 0.31 485.04 285.02 55962 +1919 162 19.96 13.96 18.31 0.14 509.9 282.87 56011 +1919 163 18.37 12.37 16.72 0.42 466.23 286.88 56056 +1919 164 15.34 9.34 13.69 0 391.77 391.12 56097 +1919 165 14.95 8.95 13.3 0.02 382.97 294.16 56133 +1919 166 15.22 9.22 13.57 0 389.05 391.6 56165 +1919 167 18.28 12.28 16.63 1.11 463.85 287.21 56192 +1919 168 14.98 8.98 13.33 0.23 383.64 294.18 56214 +1919 169 13.54 7.54 11.89 0.31 352.55 296.81 56231 +1919 170 13.64 7.64 11.99 0 354.63 395.51 56244 +1919 171 13.4 7.4 11.75 0 349.64 396.13 56252 +1919 172 17.61 11.61 15.96 0 446.5 385.11 56256 +1919 173 20.34 14.34 18.69 0.1 520.83 282.27 56255 +1919 174 20.38 14.38 18.73 2.83 522 282.1 56249 +1919 175 18.3 12.3 16.65 0 464.38 382.9 56238 +1919 176 19.01 13.01 17.36 0 483.41 380.63 56223 +1919 177 20.86 14.86 19.21 0.51 536.12 280.71 56203 +1919 178 23.66 17.66 22.01 0.65 625.16 272.65 56179 +1919 179 22.3 16.3 20.65 0.4 580.46 276.66 56150 +1919 180 24.28 18.28 22.63 0.04 646.49 270.52 56116 +1919 181 24.96 18.96 23.31 0.05 670.58 268.23 56078 +1919 182 27.9 21.9 26.25 0.19 783.7 257.46 56035 +1919 183 23.13 17.13 21.48 0.02 607.41 273.82 55987 +1919 184 20.73 14.73 19.08 0 532.26 374 55935 +1919 185 17.99 11.99 16.34 0.67 456.27 287.14 55879 +1919 186 17.89 11.89 16.24 0 453.69 382.89 55818 +1919 187 18.06 12.06 16.41 0.87 458.09 286.65 55753 +1919 188 17.74 11.74 16.09 0.42 449.83 287.16 55684 +1919 189 15.54 9.54 13.89 0.15 396.35 291.61 55611 +1919 190 11.65 5.65 10 0 315.02 397.47 55533 +1919 191 20.1 14.1 18.45 0 513.9 374.57 55451 +1919 192 18.36 12.36 16.71 0.83 465.96 284.91 55366 +1919 193 14.79 8.79 13.14 0.68 379.41 292.11 55276 +1919 194 10.17 4.17 8.52 0.89 288.07 299.44 55182 +1919 195 10.91 4.91 9.26 0.09 301.29 298.16 55085 +1919 196 18.75 12.75 17.1 0.26 476.36 283.11 54984 +1919 197 21.71 15.71 20.06 0.33 561.93 275.2 54879 +1919 198 20.45 14.45 18.8 0 524.04 371.01 54770 +1919 199 22.15 16.15 20.5 0.19 575.7 273.39 54658 +1919 200 20.35 14.35 18.7 1.16 521.12 277.95 54542 +1919 201 19.54 13.54 17.89 0.34 498.04 279.62 54423 +1919 202 19.93 13.93 18.28 0.09 509.04 278.24 54301 +1919 203 24.19 18.19 22.54 0.06 643.35 265.85 54176 +1919 204 27.91 21.91 26.26 0.31 784.11 252.44 54047 +1919 205 26.44 20.44 24.79 0 725.66 343.39 53915 +1919 206 25.13 19.13 23.48 1.66 676.72 261.65 53780 +1919 207 27.09 21.09 25.44 0.13 751.04 254.31 53643 +1919 208 24.69 18.69 23.04 0.1 660.93 262.14 53502 +1919 209 24 18 22.35 0.19 636.78 263.86 53359 +1919 210 22.31 16.31 20.66 0.04 580.78 268.42 53213 +1919 211 19.35 13.35 17.7 0 492.75 367.39 53064 +1919 212 21.51 15.51 19.86 0 555.77 359.28 52913 +1919 213 23.18 17.18 21.53 0.45 609.06 264.18 52760 +1919 214 23.14 17.14 21.49 0.74 607.74 263.76 52604 +1919 215 16.36 10.36 14.71 0.06 415.61 279.81 52445 +1919 216 14.69 8.69 13.04 0 377.2 376.27 52285 +1919 217 15.66 9.66 14.01 0 399.12 372.95 52122 +1919 218 17.27 11.27 15.62 0 437.91 367.82 51958 +1919 219 16.09 10.09 14.44 0 409.18 369.94 51791 +1919 220 17.64 11.64 15.99 0 447.27 364.76 51622 +1919 221 19.19 13.19 17.54 0.07 488.33 269.36 51451 +1919 222 22.11 16.11 20.46 0.4 574.44 261.21 51279 +1919 223 20.75 14.75 19.1 0.35 532.86 263.94 51105 +1919 224 19.97 13.97 18.32 0 510.18 353.43 50929 +1919 225 22.12 16.12 20.47 0.06 574.76 258.71 50751 +1919 226 25.92 19.92 24.27 0.25 705.89 246.4 50572 +1919 227 25.38 19.38 23.73 0 685.84 329.69 50392 +1919 228 26.42 20.42 24.77 1.07 724.89 242.94 50210 +1919 229 25.43 19.43 23.78 0.49 687.68 245.35 50026 +1919 230 24.87 18.87 23.22 0 667.35 328.29 49842 +1919 231 25.28 19.28 23.63 0 682.18 325.15 49656 +1919 232 22.01 16.01 20.36 0 571.29 336.53 49469 +1919 233 28.43 22.43 26.78 0 805.71 308.02 49280 +1919 234 24.09 18.09 22.44 0 639.89 326 49091 +1919 235 25.4 19.4 23.75 0.81 686.58 239.43 48900 +1919 236 29 23 27.35 0 829.97 301.18 48709 +1919 237 26.55 20.55 24.9 0 729.9 311.35 48516 +1919 238 26.37 20.37 24.72 0 722.97 310.57 48323 +1919 239 27.37 21.37 25.72 0.13 762.19 228.49 48128 +1919 240 25.16 19.16 23.51 0.94 677.81 234.46 47933 +1919 241 21.68 15.68 20.03 0 561.01 323.88 47737 +1919 242 18.16 12.16 16.51 0 460.7 332.85 47541 +1919 243 16.63 10.63 14.98 0.19 422.13 251.23 47343 +1919 244 14.4 8.4 12.75 0.91 370.85 253.74 47145 +1919 245 18.23 12.23 16.58 1.26 462.54 245.34 46947 +1919 246 18.43 12.43 16.78 0.51 467.81 243.46 46747 +1919 247 20.92 14.92 19.27 0 537.91 315.48 46547 +1919 248 24.58 18.58 22.93 0.02 657.03 225.67 46347 +1919 249 24.96 18.96 23.31 0.16 670.58 223.1 46146 +1919 250 21.48 15.48 19.83 0.01 554.85 230.91 45945 +1919 251 22.14 16.14 20.49 0.17 575.39 227.77 45743 +1919 252 21.82 15.82 20.17 0 565.35 302.63 45541 +1919 253 19.32 13.32 17.67 0 491.92 308.05 45339 +1919 254 17.22 11.22 15.57 0 436.66 311.41 45136 +1919 255 14.45 8.45 12.8 0 371.94 315.39 44933 +1919 256 18.44 12.44 16.79 0.19 468.08 227.87 44730 +1919 257 15.34 9.34 13.69 0 391.77 309.02 44527 +1919 258 19.09 13.09 17.44 0 485.59 297.66 44323 +1919 259 20.53 14.53 18.88 0 526.38 291.28 44119 +1919 260 23.76 17.76 22.11 0 628.56 278.81 43915 +1919 261 25.67 19.67 24.02 1.21 696.55 202.21 43711 +1919 262 21.4 15.4 19.75 0.04 552.4 211.3 43507 +1919 263 22.16 16.16 20.51 0 576.02 277.06 43303 +1919 264 23.79 17.79 22.14 0 629.58 269.36 43099 +1919 265 22.03 16.03 20.38 0 571.92 272.72 42894 +1919 266 26.72 20.72 25.07 0 736.5 254.27 42690 +1919 267 24.98 18.98 23.33 0.05 671.3 193.66 42486 +1919 268 24.23 18.23 22.58 0.61 644.75 193.79 42282 +1919 269 18.35 12.35 16.7 1.91 465.7 204.52 42078 +1919 270 18.19 12.19 16.54 0.08 461.49 202.86 41875 +1919 271 18.08 12.08 16.43 0 458.62 268.16 41671 +1919 272 16.32 10.32 14.67 0.02 414.65 201.99 41468 +1919 273 15.54 9.54 13.89 0 396.35 268.38 41265 +1919 274 11.91 5.91 10.26 0.26 319.97 204.07 41062 +1919 275 9.15 3.15 7.5 0.26 270.67 204.94 40860 +1919 276 16.1 10.1 14.45 0.93 409.42 194.4 40658 +1919 277 16.42 10.42 14.77 0.28 417.05 191.95 40456 +1919 278 16.09 10.09 14.44 1.3 409.18 190.31 40255 +1919 279 14.46 8.46 12.81 0.06 372.15 190.49 40054 +1919 280 16.25 10.25 14.6 0 412.98 248.05 39854 +1919 281 15.9 9.9 14.25 0 404.71 246.04 39654 +1919 282 17.84 11.84 16.19 0 452.4 239.48 39455 +1919 283 17.71 11.71 16.06 0 449.06 237 39256 +1919 284 9.27 3.27 7.62 0.08 272.67 185.73 39058 +1919 285 9.96 3.96 8.31 0.97 284.41 183.08 38861 +1919 286 11.84 5.84 10.19 0 318.63 238.79 38664 +1919 287 5.11 -0.89 3.46 0 210.31 243.58 38468 +1919 288 4.22 -1.78 2.57 0 198.7 241.51 38273 +1919 289 3.91 -2.09 2.26 0 194.79 239.06 38079 +1919 290 8.85 2.85 7.2 0 265.73 231.29 37885 +1919 291 8 2 6.35 0 252.14 229.49 37693 +1919 292 9.01 3.01 7.36 0.55 268.36 169.24 37501 +1919 293 10.15 4.15 8.5 0.73 287.72 166.17 37311 +1919 294 16.11 10.11 14.46 0.01 409.66 157.57 37121 +1919 295 18.35 12.35 16.7 0.01 465.7 152.45 36933 +1919 296 13.1 7.1 11.45 0.19 343.48 157.07 36745 +1919 297 9.95 3.95 8.3 0 284.24 210.71 36560 +1919 298 9.43 3.43 7.78 0 275.36 208.67 36375 +1919 299 12.83 6.83 11.18 0 338.02 201.75 36191 +1919 300 14.38 8.38 12.73 0 370.41 196.95 36009 +1919 301 12.63 6.63 10.98 0 334.03 196.88 35829 +1919 302 11.29 5.29 9.64 0 308.27 195.95 35650 +1919 303 7.63 1.63 5.98 0.03 246.42 147.93 35472 +1919 304 8.19 2.19 6.54 0.4 255.13 145.67 35296 +1919 305 2 -4 0.35 0.95 172.11 147.26 35122 +1919 306 5.26 -0.74 3.61 0 212.33 191.74 34950 +1919 307 5.49 -0.51 3.84 0.41 215.45 141.76 34779 +1919 308 4.34 -1.66 2.69 0.05 200.23 140.44 34610 +1919 309 6.75 0.75 5.1 0.26 233.25 137.27 34444 +1919 310 9.35 3.35 7.7 0.16 274.01 133.66 34279 +1919 311 7.23 1.23 5.58 0 240.35 177.97 34116 +1919 312 3.85 -2.15 2.2 0 194.04 177.88 33956 +1919 313 6.61 0.61 4.96 0.52 231.21 130.27 33797 +1919 314 8.41 2.41 6.76 1.63 258.62 127.66 33641 +1919 315 5.65 -0.35 4 0.22 217.64 127.44 33488 +1919 316 6.87 0.87 5.22 0 235.01 166.79 33337 +1919 317 5.79 -0.21 4.14 0.35 219.58 124.06 33188 +1919 318 3.33 -2.67 1.68 1.3 187.64 123.54 33042 +1919 319 3.94 -2.06 2.29 0.08 195.16 121.97 32899 +1919 320 4.87 -1.13 3.22 0 207.13 160.12 32758 +1919 321 6.63 0.63 4.98 0 231.5 156.76 32620 +1919 322 4.02 -1.98 2.37 0 196.17 156.72 32486 +1919 323 3.89 -2.11 2.24 0 194.54 155.17 32354 +1919 324 2.15 -3.85 0.5 0 173.81 154.11 32225 +1919 325 3.16 -2.84 1.51 0 185.59 151.8 32100 +1919 326 4.55 -1.45 2.9 0.32 202.94 112.12 31977 +1919 327 7.99 1.99 6.34 0.01 251.99 108.92 31858 +1919 328 14.9 8.9 13.25 0 381.86 136.58 31743 +1919 329 13 7 11.35 0.06 341.45 102.94 31631 +1919 330 3.87 -2.13 2.22 0.11 194.29 107.34 31522 +1919 331 8.23 2.23 6.58 1.38 255.76 104.14 31417 +1919 332 9.75 3.75 8.1 0.04 280.79 102 31316 +1919 333 8.07 2.07 6.42 0 253.24 136.27 31218 +1919 334 8.43 2.43 6.78 0.04 258.94 101.18 31125 +1919 335 11.35 5.35 9.7 0 309.39 131.31 31035 +1919 336 10.43 4.43 8.78 0 292.66 131.08 30949 +1919 337 7.3 1.3 5.65 0.02 241.41 98.9 30867 +1919 338 3.99 -2.01 2.34 0.07 195.79 99.76 30790 +1919 339 7.43 1.43 5.78 0 243.37 130.06 30716 +1919 340 6.3 0.3 4.65 0.26 226.75 97.57 30647 +1919 341 3.19 -2.81 1.54 0.17 185.95 98.25 30582 +1919 342 -0.33 -6.33 -1.98 0.52 147.56 143.8 30521 +1919 343 -3.11 -9.11 -4.76 0 122.28 177.07 30465 +1919 344 1.09 -4.91 -0.56 0.04 162.13 141.87 30413 +1919 345 5.29 -0.71 3.64 0 212.73 170.94 30366 +1919 346 5.12 -0.88 3.47 0.04 210.45 138.32 30323 +1919 347 3.82 -2.18 2.17 0.49 193.66 94.77 30284 +1919 348 3.95 -2.05 2.3 0.25 195.29 94.46 30251 +1919 349 2.75 -3.25 1.1 0.22 180.73 94.64 30221 +1919 350 1.37 -4.63 -0.28 0.06 165.15 94.88 30197 +1919 351 5.21 -0.79 3.56 0.09 211.65 93.22 30177 +1919 352 5.48 -0.52 3.83 0 215.31 124.04 30162 +1919 353 4.51 -1.49 2.86 0 202.42 124.54 30151 +1919 354 0.65 -5.35 -1 0 157.49 126.41 30145 +1919 355 4.69 -1.31 3.04 0 204.76 124.4 30144 +1919 356 2.57 -3.43 0.92 0 178.63 125.55 30147 +1919 357 1.9 -4.1 0.25 0 170.99 125.93 30156 +1919 358 0.52 -5.48 -1.13 0 156.14 126.64 30169 +1919 359 1.05 -4.95 -0.6 0 161.71 126.53 30186 +1919 360 6.55 0.55 4.9 0 230.34 123.94 30208 +1919 361 5.21 -0.79 3.56 0 211.65 125.09 30235 +1919 362 5.47 -0.53 3.82 0.03 215.17 94.03 30267 +1919 363 6.55 0.55 4.9 0 230.34 125.28 30303 +1919 364 6.73 0.73 5.08 0 232.96 125.56 30343 +1919 365 3.48 -2.52 1.83 0 189.47 128.04 30388 +1920 1 3.58 -2.42 1.93 0 190.7 128.88 30438 +1920 2 3.51 -2.49 1.86 0 189.84 129.65 30492 +1920 3 1.87 -4.13 0.22 0 170.65 131.43 30551 +1920 4 0.1 -5.9 -1.55 0 151.85 133.16 30614 +1920 5 5.07 -0.93 3.42 0 209.78 131.26 30681 +1920 6 4.44 -1.56 2.79 0 201.52 132.52 30752 +1920 7 2.73 -3.27 1.08 0.85 180.49 100.69 30828 +1920 8 3.72 -2.28 2.07 0 192.42 135.21 30907 +1920 9 2.88 -3.12 1.23 0 182.26 136.93 30991 +1920 10 3.99 -2.01 2.34 0 195.79 137.62 31079 +1920 11 9.02 3.02 7.37 0 268.52 135.16 31171 +1920 12 5.61 -0.39 3.96 0.06 217.09 103.96 31266 +1920 13 2.88 -3.12 1.23 0.87 182.26 106.39 31366 +1920 14 2.18 -3.82 0.53 0 174.15 143.71 31469 +1920 15 4.3 -1.7 2.65 0 199.72 143.96 31575 +1920 16 5.92 -0.08 4.27 0.44 221.39 108.15 31686 +1920 17 2.18 -3.82 0.53 0 174.15 148.15 31800 +1920 18 3.24 -2.76 1.59 0 186.56 149.46 31917 +1920 19 5.59 -0.41 3.94 0 216.82 149.91 32038 +1920 20 8.63 2.63 6.98 0 262.15 149.2 32161 +1920 21 9.93 3.93 8.28 0 283.89 150.04 32289 +1920 22 8.35 2.35 6.7 0.04 257.66 114.85 32419 +1920 23 7.79 1.79 6.14 0.26 248.88 116.5 32552 +1920 24 9.33 3.33 7.68 0 273.67 156.06 32688 +1920 25 13.16 7.16 11.51 0 344.71 154.01 32827 +1920 26 11.12 5.12 9.47 0.34 305.13 118.56 32969 +1920 27 8.79 2.79 7.14 0.68 264.75 121.71 33114 +1920 28 3.71 -2.29 2.06 0 192.3 168.35 33261 +1920 29 4.89 -1.11 3.24 0 207.39 169.93 33411 +1920 30 4.64 -1.36 2.99 0.05 204.11 129.26 33564 +1920 31 5.12 -0.88 3.47 0.51 210.45 130.78 33718 +1920 32 3.21 -2.79 1.56 0 186.2 177.8 33875 +1920 33 2.82 -3.18 1.17 0 181.55 180.68 34035 +1920 34 1.86 -4.14 0.21 0.01 170.54 137.62 34196 +1920 35 2.5 -3.5 0.85 0 177.82 185.26 34360 +1920 36 0.29 -5.71 -1.36 0 153.78 189.1 34526 +1920 37 2.65 -3.35 1 0 179.56 190.12 34694 +1920 38 2.68 -3.32 1.03 0 179.91 192.85 34863 +1920 39 6.32 0.32 4.67 0 227.04 192.73 35035 +1920 40 8.21 2.21 6.56 0 255.44 193.62 35208 +1920 41 9.19 3.19 7.54 0 271.34 195.23 35383 +1920 42 7.58 1.58 5.93 0 245.65 199.35 35560 +1920 43 7.19 1.19 5.54 0 239.76 202.39 35738 +1920 44 8.43 2.43 6.78 0 258.94 203.73 35918 +1920 45 8.02 2.02 6.37 0 252.46 206.74 36099 +1920 46 10.28 4.28 8.63 0.13 290 155.22 36282 +1920 47 7.72 1.72 6.07 0.1 247.8 159.37 36466 +1920 48 3.43 -2.57 1.78 0 188.86 219.05 36652 +1920 49 5.53 -0.47 3.88 0 215.99 220.11 36838 +1920 50 4.96 -1.04 3.31 0 208.32 223.27 37026 +1920 51 3.34 -2.66 1.69 0 187.77 227.57 37215 +1920 52 4.52 -1.48 2.87 0 202.55 229.46 37405 +1920 53 6.97 0.97 5.32 0 236.48 230.15 37596 +1920 54 9.45 3.45 7.8 0 275.69 230.18 37788 +1920 55 9.82 3.82 8.17 0 282 232.69 37981 +1920 56 13.46 7.46 11.81 0 350.88 230.32 38175 +1920 57 10.74 4.74 9.09 0.01 298.21 177.76 38370 +1920 58 7.19 1.19 5.54 0 239.76 244.12 38565 +1920 59 9.65 3.65 8 0 279.08 243.97 38761 +1920 60 12.22 6.22 10.57 0 325.96 243.31 38958 +1920 61 16.47 10.47 14.82 0 418.26 238.97 39156 +1920 62 13.69 7.69 12.04 0 355.68 246.61 39355 +1920 63 16.15 10.15 14.5 0 410.61 245.15 39553 +1920 64 19.73 13.73 18.08 0 503.37 240.25 39753 +1920 65 20.04 14.04 18.39 0 512.18 242.21 39953 +1920 66 18.73 12.73 17.08 0 475.82 247.88 40154 +1920 67 18.46 12.46 16.81 0 468.61 251.24 40355 +1920 68 16.74 10.74 15.09 0 424.8 257.71 40556 +1920 69 10.46 4.46 8.81 0.42 293.19 203.34 40758 +1920 70 11.14 5.14 9.49 0.22 305.5 204.7 40960 +1920 71 10.33 4.33 8.68 0.02 290.89 207.75 41163 +1920 72 9.47 3.47 7.82 0.23 276.03 210.76 41366 +1920 73 7.43 1.43 5.78 0.18 243.37 214.73 41569 +1920 74 4.95 -1.05 3.3 0.01 208.18 218.89 41772 +1920 75 5.46 -0.54 3.81 0 215.04 294.07 41976 +1920 76 8.33 2.33 6.68 0 257.34 293.28 42179 +1920 77 7.02 1.02 5.37 0 237.22 297.54 42383 +1920 78 7.65 1.65 6 0.16 246.72 224.57 42587 +1920 79 7.52 1.52 5.87 0 244.74 302.33 42791 +1920 80 8.94 2.94 7.29 0 267.2 302.97 42996 +1920 81 9.73 3.73 8.08 0.09 280.45 228.3 43200 +1920 82 7.24 1.24 5.59 0.07 240.5 232.86 43404 +1920 83 7.16 1.16 5.51 0.01 239.31 234.82 43608 +1920 84 6.73 0.73 5.08 0 232.96 316.19 43812 +1920 85 2.93 -3.07 1.28 0 182.85 322.94 44016 +1920 86 1.99 -4.01 0.34 0 172 326.29 44220 +1920 87 5.24 -0.76 3.59 0 212.06 325.49 44424 +1920 88 8.23 2.23 6.58 0 255.76 324.05 44627 +1920 89 8.08 2.08 6.43 0 253.4 326.55 44831 +1920 90 12.92 6.92 11.27 0 339.83 320.97 45034 +1920 91 15.87 9.87 14.22 0 404.01 317.03 45237 +1920 92 16.34 10.34 14.69 0 415.13 318.12 45439 +1920 93 19.39 13.39 17.74 0 493.86 312.37 45642 +1920 94 19.22 13.22 17.57 0 489.16 314.91 45843 +1920 95 15.94 9.94 14.29 0.09 405.65 244.05 46045 +1920 96 12.38 6.38 10.73 0 329.09 334.99 46246 +1920 97 10.67 4.67 9.02 0 296.95 340.13 46446 +1920 98 12.35 6.35 10.7 1.27 328.5 254.28 46647 +1920 99 13.68 7.68 12.03 0.04 355.47 253.79 46846 +1920 100 16.62 10.62 14.97 0.02 421.88 250.2 47045 +1920 101 19.08 13.08 17.43 0.39 485.32 246.66 47243 +1920 102 18.56 12.56 16.91 0.03 471.27 249.15 47441 +1920 103 18.17 12.17 16.52 0.73 460.97 251.3 47638 +1920 104 11.1 5.1 9.45 0.02 304.76 264.62 47834 +1920 105 9.32 3.32 7.67 0 273.51 357.69 48030 +1920 106 12.17 6.17 10.52 0.01 324.99 265.69 48225 +1920 107 15.59 9.59 13.94 0 397.51 348.49 48419 +1920 108 17.73 11.73 16.08 0 449.57 344.7 48612 +1920 109 14.4 8.4 12.75 0 370.85 354.57 48804 +1920 110 15.16 9.16 13.51 0 387.69 354.21 48995 +1920 111 14.39 8.39 12.74 0 370.63 357.53 49185 +1920 112 14.11 8.11 12.46 0 364.59 359.68 49374 +1920 113 17.45 11.45 15.8 0 442.44 352.71 49561 +1920 114 16.45 10.45 14.8 0 417.77 356.84 49748 +1920 115 18.47 12.47 16.82 0.19 468.88 264.51 49933 +1920 116 19.42 13.42 17.77 0.01 494.69 263.25 50117 +1920 117 17.97 11.97 16.32 1.72 455.76 267.44 50300 +1920 118 15.12 9.12 13.47 0.19 386.79 274.04 50481 +1920 119 14.36 8.36 12.71 0.29 369.98 276.28 50661 +1920 120 13.37 7.37 11.72 0 349.02 371.78 50840 +1920 121 19.67 13.67 18.02 0.01 501.68 267.11 51016 +1920 122 17.67 11.67 16.02 0 448.04 363.33 51191 +1920 123 14.98 8.98 13.33 0.27 383.64 278.56 51365 +1920 124 17 11 15.35 0.16 431.19 275.46 51536 +1920 125 15.58 9.58 13.93 0.03 397.27 278.99 51706 +1920 126 19.3 13.3 17.65 0 491.36 362.46 51874 +1920 127 20.78 14.78 19.13 0 533.75 358.46 52039 +1920 128 22.86 16.86 21.21 0 598.53 351.85 52203 +1920 129 22.02 16.02 20.37 0.1 571.61 266.87 52365 +1920 130 23.99 17.99 22.34 0.36 636.44 261.67 52524 +1920 131 23.32 17.32 21.67 0.04 613.72 264.27 52681 +1920 132 24.95 18.95 23.3 0.48 670.22 259.77 52836 +1920 133 22.56 16.56 20.91 0 588.79 356.79 52989 +1920 134 22.84 16.84 21.19 0.28 597.88 267.29 53138 +1920 135 19.37 13.37 17.72 1.22 493.3 277.01 53286 +1920 136 18.13 12.13 16.48 1.35 459.92 280.36 53430 +1920 137 16.74 10.74 15.09 0.12 424.8 283.87 53572 +1920 138 16.71 10.71 15.06 0 424.07 379.18 53711 +1920 139 20.63 14.63 18.98 0.09 529.31 275.8 53848 +1920 140 17.79 11.79 16.14 0.19 451.11 282.96 53981 +1920 141 19.95 13.95 18.3 0.27 509.61 278.2 54111 +1920 142 19.34 13.34 17.69 0 492.47 373.43 54238 +1920 143 19.74 13.74 18.09 0.58 503.65 279.49 54362 +1920 144 17.87 11.87 16.22 0.36 453.17 284.23 54483 +1920 145 19.31 13.31 17.66 0.2 491.64 281.24 54600 +1920 146 17.12 11.12 15.47 0 434.17 382.01 54714 +1920 147 19.7 13.7 18.05 0.8 502.53 280.92 54824 +1920 148 18.48 12.48 16.83 0.53 469.14 284.13 54931 +1920 149 20.54 14.54 18.89 0.49 526.67 279.3 55034 +1920 150 17.39 11.39 15.74 0.03 440.93 287.05 55134 +1920 151 22.61 16.61 20.96 0.31 590.41 274.11 55229 +1920 152 24.13 18.13 22.48 0 641.27 359.39 55321 +1920 153 24.18 18.18 22.53 0.38 643.01 269.55 55409 +1920 154 21.03 15.03 19.38 3.98 541.2 279.03 55492 +1920 155 19.2 13.2 17.55 0.27 488.61 283.84 55572 +1920 156 20.85 14.85 19.2 0.03 535.82 279.89 55648 +1920 157 20.44 14.44 18.79 0 523.74 374.79 55719 +1920 158 19.44 13.44 17.79 0 495.25 378.34 55786 +1920 159 21.69 15.69 20.04 0 561.31 370.71 55849 +1920 160 24.58 18.58 22.93 0.01 657.03 269.41 55908 +1920 161 20.87 14.87 19.22 0.25 536.42 280.46 55962 +1920 162 21.19 15.19 19.54 0 546.02 372.85 56011 +1920 163 20.51 14.51 18.86 0.32 525.79 281.61 56056 +1920 164 19.59 13.59 17.94 1.09 499.44 283.99 56097 +1920 165 18.76 12.76 17.11 0.33 476.63 286.07 56133 +1920 166 20.35 14.35 18.7 0 521.12 376.25 56165 +1920 167 18.69 12.69 17.04 0.23 474.75 286.26 56192 +1920 168 18.17 12.17 16.52 0.35 460.97 287.52 56214 +1920 169 18.03 12.03 16.38 0.43 457.31 287.85 56231 +1920 170 20.38 14.38 18.73 0.05 522 282.14 56244 +1920 171 16.96 10.96 15.31 1.32 430.2 290.25 56252 +1920 172 18.61 12.61 16.96 0.33 472.61 286.55 56256 +1920 173 19.2 13.2 17.55 0.25 488.61 285.13 56255 +1920 174 18.48 12.48 16.83 0.04 469.14 286.78 56249 +1920 175 15.38 9.38 13.73 0 392.69 391.15 56238 +1920 176 18.69 12.69 17.04 0 474.75 381.65 56223 +1920 177 16.74 10.74 15.09 0 424.8 387.34 56203 +1920 178 17.56 11.56 15.91 0.6 445.23 288.75 56179 +1920 179 18.55 12.55 16.9 0 471 381.9 56150 +1920 180 19 13 17.35 0 483.13 380.36 56116 +1920 181 18.64 12.64 16.99 0.1 473.41 286.07 56078 +1920 182 22.17 16.17 20.52 0 576.34 369.04 56035 +1920 183 24.77 18.77 23.12 0 663.78 358.17 55987 +1920 184 24.77 18.77 23.12 0.68 663.78 268.52 55935 +1920 185 22.01 16.01 20.36 0 571.29 369.24 55879 +1920 186 24.01 18.01 22.36 0.01 637.13 270.73 55818 +1920 187 22.38 16.38 20.73 0.1 583.02 275.54 55753 +1920 188 22.44 16.44 20.79 0.02 584.94 275.17 55684 +1920 189 27.17 21.17 25.52 0 754.21 345.79 55611 +1920 190 23.32 17.32 21.67 1.39 613.72 272.14 55533 +1920 191 23 17 21.35 0.81 603.12 272.92 55451 +1920 192 25.09 19.09 23.44 1.47 675.27 266.07 55366 +1920 193 24.8 18.8 23.15 0.67 664.85 266.84 55276 +1920 194 26.62 20.62 24.97 0.35 732.62 260.36 55182 +1920 195 26.44 20.44 24.79 0.1 725.66 260.82 55085 +1920 196 23.09 17.09 21.44 0 606.09 362.08 54984 +1920 197 22.58 16.58 20.93 0.37 589.44 272.73 54879 +1920 198 26.33 20.33 24.68 0.25 721.44 260.3 54770 +1920 199 27.97 21.97 26.32 0 786.58 338.56 54658 +1920 200 27.43 21.43 25.78 0 764.6 340.96 54542 +1920 201 28.74 22.74 27.09 0.49 818.83 250.25 54423 +1920 202 24.15 18.15 22.5 1.29 641.97 266.34 54301 +1920 203 21.05 15.05 19.4 0.89 541.8 274.97 54176 +1920 204 25.4 19.4 23.75 0 686.58 348.7 54047 +1920 205 25.48 19.48 23.83 0.13 689.52 260.88 53915 +1920 206 26.18 20.18 24.53 0.57 715.72 258.06 53780 +1920 207 19.47 13.47 17.82 0.35 496.08 277.29 53643 +1920 208 19.17 13.17 17.52 0.25 487.78 277.52 53502 +1920 209 20.82 14.82 19.17 1.1 534.93 272.93 53359 +1920 210 18.1 12.1 16.45 0 459.14 372.02 53213 +1920 211 14.23 8.23 12.58 0 367.17 381.49 53064 +1920 212 20 14 18.35 0 511.04 364.49 52913 +1920 213 20.77 14.77 19.12 0.26 533.45 270.85 52760 +1920 214 20.19 14.19 18.54 0 516.49 362.35 52604 +1920 215 17.81 11.81 16.16 0.01 451.62 276.79 52445 +1920 216 21.64 15.64 19.99 0 559.77 355.65 52285 +1920 217 22.24 16.24 20.59 0.53 578.56 264.43 52122 +1920 218 21.26 15.26 19.61 0.08 548.14 266.48 51958 +1920 219 20.94 14.94 19.29 0.05 538.51 266.53 51791 +1920 220 20.64 14.64 18.99 0.03 529.61 266.6 51622 +1920 221 19.71 13.71 18.06 0.12 502.81 268.14 51451 +1920 222 16.07 10.07 14.42 0.4 408.71 275.19 51279 +1920 223 17.38 11.38 15.73 0 440.68 362.25 51105 +1920 224 16.94 10.94 15.29 1.41 429.71 271.79 50929 +1920 225 17.56 11.56 15.91 0 445.23 359.52 50751 +1920 226 19.24 13.24 17.59 0 489.71 353.44 50572 +1920 227 20.42 14.42 18.77 0.67 523.16 261.31 50392 +1920 228 21.34 15.34 19.69 0.44 550.57 258.09 50210 +1920 229 23.92 17.92 22.27 0 634.03 333.37 50026 +1920 230 24.61 18.61 22.96 0 658.09 329.36 49842 +1920 231 23.1 17.1 21.45 0.63 606.42 250.41 49656 +1920 232 18.33 12.33 16.68 0 465.17 348.27 49469 +1920 233 21.06 15.06 19.41 0 542.1 338.39 49280 +1920 234 24.02 18.02 22.37 0 637.47 326.28 49091 +1920 235 24.06 18.06 22.41 0 638.85 324.69 48900 +1920 236 25.45 19.45 23.8 0.21 688.41 238.26 48709 +1920 237 22.16 16.16 20.51 0 576.02 328.75 48516 +1920 238 21.95 15.95 20.3 0 569.41 327.85 48323 +1920 239 21.66 15.66 20.01 0 560.39 327.36 48128 +1920 240 19.28 13.28 17.63 0.21 490.81 249.85 47933 +1920 241 23.67 17.67 22.02 0.79 625.5 237.6 47737 +1920 242 18.12 12.12 16.47 0.83 459.66 249.72 47541 +1920 243 15.91 9.91 14.26 1.19 404.95 252.55 47343 +1920 244 13.76 7.76 12.11 0 357.15 339.68 47145 +1920 245 14.58 8.58 12.93 0 374.78 336.04 46947 +1920 246 14.56 8.56 12.91 0 374.34 334.08 46747 +1920 247 15.84 9.84 14.19 0.83 403.31 246.98 46547 +1920 248 15.73 9.73 14.08 0.48 400.75 245.69 46347 +1920 249 17.19 11.19 15.54 0 435.91 321.99 46146 +1920 250 17.82 11.82 16.17 0.25 451.88 238.82 45945 +1920 251 22.49 16.49 20.84 0 586.54 302.52 45743 +1920 252 20.4 14.4 18.75 0.02 522.58 230.27 45541 +1920 253 23.86 17.86 22.21 0 631.98 293.65 45339 +1920 254 21.23 15.23 19.58 0 547.23 300.36 45136 +1920 255 24.04 18.04 22.39 0 638.16 288.83 44933 +1920 256 25.92 19.92 24.27 0 705.89 279.61 44730 +1920 257 28.81 22.81 27.16 0 821.82 265.31 44527 +1920 258 26.83 20.83 25.18 0 740.8 271.77 44323 +1920 259 28.02 22.02 26.37 0 788.64 264.51 44119 +1920 260 24.68 18.68 23.03 0 660.57 275.57 43915 +1920 261 19.71 13.71 18.06 0.21 502.81 216.64 43711 +1920 262 22.22 16.22 20.57 0 577.92 279.24 43507 +1920 263 24.22 18.22 22.57 0.01 644.4 202.75 43303 +1920 264 19.98 13.98 18.33 0 510.47 280.88 43099 +1920 265 16.42 10.42 14.77 0 417.05 287.23 42894 +1920 266 15.5 9.5 13.85 1.11 395.43 215.03 42690 +1920 267 13.09 7.09 11.44 0.43 343.28 216.47 42486 +1920 268 13.29 7.29 11.64 0 347.37 285.68 42282 +1920 269 12.46 6.46 10.81 0.33 330.66 213.42 42078 +1920 270 12.74 6.74 11.09 0.03 336.22 211.07 41875 +1920 271 12.23 6.23 10.58 0.12 326.15 209.71 41671 +1920 272 13.98 7.98 12.33 0 361.81 273.86 41468 +1920 273 20.15 14.15 18.5 0 515.34 257.98 41265 +1920 274 10.53 4.53 8.88 0 294.44 274.17 41062 +1920 275 11.67 5.67 10.02 0 315.4 269.67 40860 +1920 276 9.72 3.72 8.07 0 280.28 269.74 40658 +1920 277 8.25 2.25 6.6 0 256.08 268.91 40456 +1920 278 7.62 1.62 5.97 0 246.26 266.72 40255 +1920 279 3.57 -2.43 1.92 0 190.57 267.97 40054 +1920 280 4.8 -1.2 3.15 0 206.2 264.09 39854 +1920 281 6.31 0.31 4.66 0.33 226.89 194.83 39654 +1920 282 5.88 -0.12 4.23 0 220.83 257.4 39455 +1920 283 7.02 1.02 5.37 0 237.22 253.32 39256 +1920 284 9.52 3.52 7.87 0.07 276.88 185.5 39058 +1920 285 10.05 4.05 8.4 0 285.98 243.99 38861 +1920 286 10.98 4.98 9.33 0 302.56 239.98 38664 +1920 287 14.03 8.03 12.38 0 362.88 232.54 38468 +1920 288 13.65 7.65 12 0.07 354.84 172.79 38273 +1920 289 11.94 5.94 10.29 0 320.54 230.27 38079 +1920 290 13.86 7.86 12.21 0.05 359.26 168.45 37885 +1920 291 10.53 4.53 8.88 0 294.44 226.55 37693 +1920 292 18.9 12.9 17.25 0 480.41 210.31 37501 +1920 293 15.49 9.49 13.84 0 395.2 213.97 37311 +1920 294 17.5 11.5 15.85 0 443.71 207.61 37121 +1920 295 13.45 7.45 11.8 0.58 350.68 158.62 36933 +1920 296 10.17 4.17 8.52 0.49 288.07 159.89 36745 +1920 297 10.49 4.49 8.84 0.34 293.72 157.56 36560 +1920 298 8.45 2.45 6.8 0 259.26 209.72 36375 +1920 299 10 4 8.35 0 285.11 205.24 36191 +1920 300 14.12 8.12 12.47 0 364.8 197.33 36009 +1920 301 15.84 9.84 14.19 0 403.31 192.26 35829 +1920 302 15.26 9.26 13.61 0.75 389.95 142.96 35650 +1920 303 12.84 6.84 11.19 0.19 338.22 143.6 35472 +1920 304 6.77 0.77 5.12 0.01 233.54 146.65 35296 +1920 305 -1 -7 -2.65 0.03 141.09 186.23 35122 +1920 306 -1.16 -7.16 -2.81 0 139.58 233.69 34950 +1920 307 -3 -9 -4.65 0 123.21 232.17 34779 +1920 308 2.73 -3.27 1.08 0 180.49 188.36 34610 +1920 309 0.82 -5.18 -0.83 0 159.27 187.15 34444 +1920 310 3.36 -2.64 1.71 0 188.01 183.1 34279 +1920 311 5.14 -0.86 3.49 0 210.72 179.63 34116 +1920 312 5.79 -0.21 4.14 0 219.58 176.48 33956 +1920 313 9.94 3.94 8.29 0 284.07 170.72 33797 +1920 314 9.3 3.3 7.65 0.12 273.17 127.05 33641 +1920 315 7.07 1.07 5.42 0 237.97 168.82 33488 +1920 316 2.22 -3.78 0.57 0 174.6 169.99 33337 +1920 317 4.82 -1.18 3.17 0.01 206.47 124.58 33188 +1920 318 1.94 -4.06 0.29 0 171.44 165.55 33042 +1920 319 0.65 -5.35 -1 0.08 157.49 123.39 32899 +1920 320 1.2 -4.8 -0.45 0 163.31 162.33 32758 +1920 321 -0.08 -6.08 -1.73 0 150.04 160.83 32620 +1920 322 1.32 -4.68 -0.33 0 164.61 158.28 32486 +1920 323 2.01 -3.99 0.36 0 172.22 156.26 32354 +1920 324 3.5 -2.5 1.85 0 189.71 153.34 32225 +1920 325 2.13 -3.87 0.48 0 173.58 152.38 32100 +1920 326 2.45 -3.55 0.8 0.06 177.24 113.05 31977 +1920 327 5.81 -0.19 4.16 0 219.85 146.82 31858 +1920 328 1.48 -4.52 -0.17 0 166.35 147.39 31743 +1920 329 -0.23 -6.23 -1.88 0 148.55 146.69 31631 +1920 330 2.5 -3.5 0.85 0 177.82 143.88 31522 +1920 331 3.83 -2.17 2.18 0 193.79 141.81 31417 +1920 332 4.49 -1.51 2.84 0 202.16 139.78 31316 +1920 333 6.31 0.31 4.66 0 226.89 137.53 31218 +1920 334 5.17 -0.83 3.52 0 211.12 137.17 31125 +1920 335 4.31 -1.69 2.66 0 199.85 136.51 31035 +1920 336 3.92 -2.08 2.27 0 194.91 135.66 30949 +1920 337 3.32 -2.68 1.67 0 187.52 134.33 30867 +1920 338 1.44 -4.56 -0.21 0 165.91 134.34 30790 +1920 339 1.42 -4.58 -0.23 0 165.69 133.55 30716 +1920 340 4.17 -1.83 2.52 0 198.07 131.39 30647 +1920 341 7.07 1.07 5.42 0 237.97 128.67 30582 +1920 342 7.38 1.38 5.73 0 242.61 127.7 30521 +1920 343 5.56 -0.44 3.91 0 216.41 128.06 30465 +1920 344 4.04 -1.96 2.39 0 196.42 127.82 30413 +1920 345 3.23 -2.77 1.58 0.23 186.44 95.87 30366 +1920 346 4.06 -1.94 2.41 0 196.67 126.83 30323 +1920 347 3.15 -2.85 1.5 0.06 185.47 95.04 30284 +1920 348 2.6 -3.4 0.95 0.3 178.98 94.98 30251 +1920 349 5.25 -0.75 3.6 0.37 212.19 93.62 30221 +1920 350 4.97 -1.03 3.32 0 208.45 124.66 30197 +1920 351 3.01 -2.99 1.36 0.17 183.8 94.13 30177 +1920 352 6.1 0.1 4.45 0.07 223.91 92.75 30162 +1920 353 4.6 -1.4 2.95 0.04 203.59 93.37 30151 +1920 354 0.53 -5.47 -1.12 0 156.25 126.47 30145 +1920 355 1.63 -4.37 -0.02 0.31 167.99 94.48 30144 +1920 356 2.91 -3.09 1.26 0.58 182.61 94.04 30147 +1920 357 1.5 -4.5 -0.15 1.09 166.57 94.59 30156 +1920 358 0.49 -5.51 -1.16 1.56 155.83 94.99 30169 +1920 359 3.91 -2.09 2.26 1.44 194.79 93.85 30186 +1920 360 5.05 -0.95 3.4 1.43 209.51 93.64 30208 +1920 361 7.32 1.32 5.67 1.71 241.71 92.82 30235 +1920 362 7.26 1.26 5.61 0.01 240.81 93.17 30267 +1920 363 2.8 -3.2 1.15 0 181.32 127.43 30303 +1920 364 6.38 0.38 4.73 0 227.89 125.78 30343 +1920 365 7.66 1.66 6.01 0 246.88 125.49 30388 +1921 1 6.47 0.47 4.82 0 229.19 127.17 30438 +1921 2 4.84 -1.16 3.19 0 206.73 128.91 30492 +1921 3 7.41 1.41 5.76 0 243.07 128.2 30551 +1921 4 7.59 1.59 5.94 1.09 245.81 96.74 30614 +1921 5 4.92 -1.08 3.27 0 207.79 131.35 30681 +1921 6 5.7 -0.3 4.05 0 218.33 131.76 30752 +1921 7 7.99 1.99 6.34 0 251.99 130.99 30828 +1921 8 4.46 -1.54 2.81 0 201.78 134.79 30907 +1921 9 6.95 0.95 5.3 0 236.19 134.45 30991 +1921 10 10.94 4.94 9.29 0 301.83 132.58 31079 +1921 11 11.23 5.23 9.58 0 307.16 133.27 31171 +1921 12 12.05 6.05 10.4 0 322.66 133.47 31266 +1921 13 9.82 3.82 8.17 0 282 137.08 31366 +1921 14 9.9 3.9 8.25 0 283.37 138.46 31469 +1921 15 8.5 2.5 6.85 0 260.06 141.04 31575 +1921 16 7.01 1.01 5.36 0 237.08 143.44 31686 +1921 17 3.31 -2.69 1.66 0 187.4 147.52 31800 +1921 18 1.96 -4.04 0.31 0 171.66 150.17 31917 +1921 19 3.85 -2.15 2.2 0 194.04 151.03 32038 +1921 20 5.76 -0.24 4.11 0 219.16 151.37 32161 +1921 21 6.47 0.47 4.82 0 229.19 152.86 32289 +1921 22 5.73 -0.27 4.08 0 218.75 155.13 32419 +1921 23 12.29 6.29 10.64 0.28 327.32 113.36 32552 +1921 24 11.86 5.86 10.21 0 319.01 153.61 32688 +1921 25 10.9 4.9 9.25 0 301.11 156.43 32827 +1921 26 7.73 1.73 6.08 0 247.95 161.19 32969 +1921 27 4.28 -1.72 2.63 0 199.47 165.76 33114 +1921 28 2.71 -3.29 1.06 0 180.26 168.97 33261 +1921 29 0.92 -5.08 -0.73 0 160.33 172.39 33411 +1921 30 0.39 -5.61 -1.26 0 154.8 174.94 33564 +1921 31 -0.72 -6.72 -2.37 0.6 143.77 174.28 33718 +1921 32 -2.25 -8.25 -3.9 0.01 129.67 176.26 33875 +1921 33 -1.75 -7.75 -3.4 0 134.14 223.69 34035 +1921 34 -0.7 -6.7 -2.35 0 143.96 225.23 34196 +1921 35 0.59 -5.41 -1.06 0.8 156.87 179.85 34360 +1921 36 2.72 -3.28 1.07 0 180.38 227.18 34526 +1921 37 4.26 -1.74 2.61 0.01 199.21 180.62 34694 +1921 38 7.16 1.16 5.51 0 239.31 189.41 34863 +1921 39 7.07 1.07 5.42 0 237.97 192.08 35035 +1921 40 9.06 3.06 7.41 0 269.18 192.78 35208 +1921 41 7.93 1.93 6.28 0 251.05 196.48 35383 +1921 42 8 2 6.35 0 252.14 198.94 35560 +1921 43 5.82 -0.18 4.17 0 219.99 203.61 35738 +1921 44 5.92 -0.08 4.27 0.24 221.39 154.56 35918 +1921 45 4.76 -1.24 3.11 0 205.68 209.67 36099 +1921 46 3.8 -2.2 2.15 1.62 193.42 159.84 36282 +1921 47 2.71 -3.29 1.06 0 180.26 216.76 36466 +1921 48 3.61 -2.39 1.96 0 191.06 218.91 36652 +1921 49 3.15 -2.85 1.5 0 185.47 222.06 36838 +1921 50 6.27 0.27 4.62 0 226.32 222.1 37026 +1921 51 6.63 0.63 4.98 0.39 231.5 168.54 37215 +1921 52 5.41 -0.59 3.76 0 214.36 228.68 37405 +1921 53 4.14 -1.86 2.49 0 197.68 232.74 37596 +1921 54 7.66 1.66 6.01 0 246.88 232.18 37788 +1921 55 6.9 0.9 5.25 0 235.45 235.95 37981 +1921 56 6.03 0.03 4.38 0.76 222.93 179.62 38175 +1921 57 1.65 -4.35 0 0.9 168.21 184.58 38370 +1921 58 1.95 -4.05 0.3 0 171.55 248.85 38565 +1921 59 5.21 -0.79 3.56 0 211.65 248.81 38761 +1921 60 11.12 5.12 9.47 0 305.13 244.88 38958 +1921 61 13.03 7.03 11.38 0 342.06 244.95 39156 +1921 62 15.55 9.55 13.9 0 396.58 243.37 39355 +1921 63 13.03 7.03 11.38 0.05 342.06 187.96 39553 +1921 64 8.7 2.7 7.05 0 263.29 259.54 39753 +1921 65 6.51 0.51 4.86 0 229.76 264.95 39953 +1921 66 7.47 1.47 5.82 0 243.98 266.62 40154 +1921 67 12.09 6.09 10.44 0 323.43 263.28 40355 +1921 68 9.73 3.73 8.08 0 280.45 269.53 40556 +1921 69 10.08 4.08 8.43 0 286.5 271.65 40758 +1921 70 10.04 4.04 8.39 0 285.8 274.53 40960 +1921 71 10.24 4.24 8.59 0 289.3 277.13 41163 +1921 72 10.84 4.84 9.19 0 300.02 279.05 41366 +1921 73 8.27 2.27 6.62 0 256.39 285.26 41569 +1921 74 11.02 5.02 9.37 0.13 303.3 213.1 41772 +1921 75 8.05 2.05 6.4 0 252.93 291.01 41976 +1921 76 11.67 5.67 10.02 0 315.4 288.4 42179 +1921 77 14.87 8.87 13.22 0.07 381.19 213.92 42383 +1921 78 9.41 3.41 7.76 0 275.02 297.06 42587 +1921 79 12.54 6.54 10.89 0 332.24 294.82 42791 +1921 80 10.93 4.93 9.28 0 301.65 300 42996 +1921 81 7.59 1.59 5.94 0 245.81 307.37 43200 +1921 82 8.62 2.62 6.97 0 261.99 308.65 43404 +1921 83 10.75 4.75 9.1 0 298.39 307.95 43608 +1921 84 8.48 2.48 6.83 0 259.74 313.88 43812 +1921 85 2.65 -3.35 1 0 179.56 323.21 44016 +1921 86 6.02 0.02 4.37 0 222.79 322.01 44220 +1921 87 5.74 -0.26 4.09 0 218.88 324.91 44424 +1921 88 7.17 1.17 5.52 0 239.46 325.49 44627 +1921 89 6.25 0.25 4.6 0 226.04 328.97 44831 +1921 90 6.64 0.64 4.99 0 231.65 330.87 45034 +1921 91 10.71 4.71 9.06 0.12 297.67 245.36 45237 +1921 92 14.87 8.87 13.22 0.05 381.19 241.08 45439 +1921 93 14.74 8.74 13.09 0.01 378.3 242.92 45642 +1921 94 13.74 7.74 12.09 0.91 356.73 246.08 45843 +1921 95 11.8 5.8 10.15 0.69 317.87 250.48 46045 +1921 96 9.4 3.4 7.75 0.24 274.85 255.12 46246 +1921 97 9.49 3.49 7.84 0.84 276.37 256.56 46446 +1921 98 8.42 2.42 6.77 0 258.78 345.71 46647 +1921 99 10.42 4.42 8.77 0.25 292.48 258.4 46846 +1921 100 15.1 9.1 13.45 0.63 386.34 252.92 47045 +1921 101 14.14 8.14 12.49 1.11 365.23 255.94 47243 +1921 102 11.85 5.85 10.2 0 318.82 347.76 47441 +1921 103 15.22 9.22 13.57 0 389.05 342.53 47638 +1921 104 12.8 6.8 11.15 0 337.42 349.57 47834 +1921 105 13.13 7.13 11.48 0 344.1 350.68 48030 +1921 106 13.7 7.7 12.05 0.1 355.89 263.34 48225 +1921 107 16.39 10.39 14.74 0 416.33 346.52 48419 +1921 108 14.06 8.06 12.41 0 363.52 353.73 48612 +1921 109 14.7 8.7 13.05 0.18 377.42 265.42 48804 +1921 110 12.81 6.81 11.16 1.57 337.62 269.56 48995 +1921 111 9.9 3.9 8.25 0 283.37 366.46 49185 +1921 112 7.77 1.77 6.12 0.59 248.57 278.59 49374 +1921 113 11.49 5.49 9.84 0.1 312.01 274.84 49561 +1921 114 10.95 4.95 9.3 0.15 302.02 276.73 49748 +1921 115 14.74 8.74 13.09 0 378.3 362.47 49933 +1921 116 12.21 6.21 10.56 0 325.76 369.21 50117 +1921 117 9.06 3.06 7.41 0 269.18 376.32 50300 +1921 118 7.67 1.67 6.02 0.1 247.03 284.92 50481 +1921 119 8.96 2.96 7.31 0.17 267.53 284.29 50661 +1921 120 5.75 -0.25 4.1 0.08 219.02 288.82 50840 +1921 121 18 12 16.35 0.11 456.53 270.91 51016 +1921 122 15.19 9.19 13.54 0.02 388.37 277.41 51191 +1921 123 17.39 11.39 15.74 0.08 440.93 273.85 51365 +1921 124 16.33 10.33 14.68 0.11 414.89 276.81 51536 +1921 125 12.99 6.99 11.34 0 341.25 378.06 51706 +1921 126 12.49 6.49 10.84 0 331.25 380.13 51874 +1921 127 17.09 11.09 15.44 0 433.42 369.86 52039 +1921 128 20.62 14.62 18.97 0.05 529.02 269.98 52203 +1921 129 19.48 13.48 17.83 0.4 496.36 273.42 52365 +1921 130 15.59 9.59 13.94 0 397.51 376.48 52524 +1921 131 19.28 13.28 17.63 0.16 490.81 275.06 52681 +1921 132 17.13 11.13 15.48 0 434.42 373.98 52836 +1921 133 15.56 9.56 13.91 0 396.81 378.89 52989 +1921 134 18.38 12.38 16.73 0.1 466.49 278.8 53138 +1921 135 17.19 11.19 15.54 0.76 435.91 281.93 53286 +1921 136 16.01 10.01 14.36 0 407.3 379.76 53430 +1921 137 11.74 5.74 10.09 0 316.72 390.43 53572 +1921 138 10.87 4.87 9.22 0 300.56 392.78 53711 +1921 139 19.89 13.89 18.24 0 507.9 370.24 53848 +1921 140 21.42 15.42 19.77 0 553.01 365.4 53981 +1921 141 26.93 20.93 25.28 0 744.72 342.46 54111 +1921 142 29.03 23.03 27.38 0 831.27 332 54238 +1921 143 27.02 21.02 25.37 0.1 748.27 257.24 54362 +1921 144 26.2 20.2 24.55 0 716.48 347.39 54483 +1921 145 23.78 17.78 22.13 0.59 629.24 268.93 54600 +1921 146 22.36 16.36 20.71 0.03 582.38 273.45 54714 +1921 147 22.94 16.94 21.29 0.99 601.15 272.1 54824 +1921 148 22.34 16.34 20.69 1.37 581.74 274.14 54931 +1921 149 20.85 14.85 19.2 1.16 535.82 278.48 55034 +1921 150 21.52 15.52 19.87 0.93 556.07 276.92 55134 +1921 151 20.07 14.07 18.42 0.22 513.04 281.04 55229 +1921 152 17.32 11.32 15.67 0.1 439.17 287.58 55321 +1921 153 17.25 11.25 15.6 0 437.41 383.89 55409 +1921 154 15.28 9.28 13.63 0 390.41 389.57 55492 +1921 155 16.86 10.86 15.21 0.52 427.74 289.14 55572 +1921 156 15.83 9.83 14.18 1.83 403.08 291.49 55648 +1921 157 17.26 11.26 15.61 0 437.66 384.87 55719 +1921 158 16.51 10.51 14.86 0 419.22 387.16 55786 +1921 159 18.92 12.92 17.27 0.47 480.96 285.19 55849 +1921 160 21.41 15.41 19.76 0.29 552.71 278.95 55908 +1921 161 20.4 14.4 18.75 0 522.58 375.59 55962 +1921 162 21.57 15.57 19.92 0.33 557.61 278.6 56011 +1921 163 22.53 16.53 20.88 0.98 587.83 276.02 56056 +1921 164 23.03 17.03 21.38 0.29 604.11 274.57 56097 +1921 165 24.23 18.23 22.58 0.38 644.75 270.9 56133 +1921 166 21.15 15.15 19.5 0.96 544.81 280.07 56165 +1921 167 23.35 17.35 21.7 0.04 614.73 273.68 56192 +1921 168 24.51 18.51 22.86 0.18 654.55 270.06 56214 +1921 169 22.94 16.94 21.29 2.21 601.15 274.99 56231 +1921 170 25.49 19.49 23.84 0.05 689.89 266.78 56244 +1921 171 23.45 17.45 21.8 0.02 618.08 273.48 56252 +1921 172 23.08 17.08 21.43 0.27 605.76 274.6 56256 +1921 173 20.3 14.3 18.65 0.24 519.67 282.37 56255 +1921 174 16.38 10.38 14.73 0 416.09 388.51 56249 +1921 175 16.74 10.74 15.09 0 424.8 387.48 56238 +1921 176 14.47 8.47 12.82 0 372.37 393.4 56223 +1921 177 16.32 10.32 14.67 0 414.65 388.5 56203 +1921 178 18.9 12.9 17.25 0 480.41 380.9 56179 +1921 179 20.86 14.86 19.21 0.26 536.12 280.65 56150 +1921 180 20.59 14.59 18.94 0.3 528.14 281.28 56116 +1921 181 22.76 16.76 21.11 0.06 595.27 275.17 56078 +1921 182 18.57 12.57 16.92 0 471.54 381.5 56035 +1921 183 15.73 9.73 14.08 0 400.75 389.48 55987 +1921 184 18.33 12.33 16.68 0 465.17 381.91 55935 +1921 185 16.85 10.85 15.2 0 427.5 386.17 55879 +1921 186 17.54 11.54 15.89 0 444.72 383.93 55818 +1921 187 22.38 16.38 20.73 0 583.02 367.39 55753 +1921 188 24.08 18.08 22.43 0 639.54 360.24 55684 +1921 189 23.23 17.23 21.58 0 610.73 363.59 55611 +1921 190 21.7 15.7 20.05 0 561.62 369.15 55533 +1921 191 25 19 23.35 0 672.02 355.45 55451 +1921 192 25.25 19.25 23.6 0 681.09 354.04 55366 +1921 193 21.68 15.68 20.03 0.43 561.01 276.3 55276 +1921 194 19.64 13.64 17.99 0.33 500.84 281.48 55182 +1921 195 20.27 14.27 18.62 1.7 518.8 279.69 55085 +1921 196 29.1 23.1 27.45 0 834.29 333.65 54984 +1921 197 25.92 19.92 24.27 0 705.89 349.4 54879 +1921 198 24.86 18.86 23.21 0 666.99 353.79 54770 +1921 199 24.46 18.46 22.81 0 652.79 355.2 54658 +1921 200 25.84 19.84 24.19 0 702.89 348.65 54542 +1921 201 24.54 18.54 22.89 0.01 655.61 265.51 54423 +1921 202 23.39 17.39 21.74 0 616.06 358.26 54301 +1921 203 27.14 21.14 25.49 0 753.02 340.95 54176 +1921 204 28.93 22.93 27.28 0.51 826.96 248.38 54047 +1921 205 27.98 21.98 26.33 0 786.99 335.74 53915 +1921 206 28.5 22.5 26.85 0 808.66 332.49 53780 +1921 207 28.44 22.44 26.79 0 806.14 332.2 53643 +1921 208 24.19 18.19 22.54 0 643.35 351.65 53502 +1921 209 30.56 24.56 28.91 0 899.53 319.15 53359 +1921 210 29.54 23.54 27.89 0 853.52 324.44 53213 +1921 211 28.01 22.01 26.36 0.14 788.23 248.94 53064 +1921 212 31.8 25.8 30.15 0.25 958.27 232.23 52913 +1921 213 26.2 20.2 24.55 0.9 716.48 254.48 52760 +1921 214 26.49 20.49 24.84 0 727.59 337.24 52604 +1921 215 22.28 16.28 20.63 0.03 579.83 265.73 52445 +1921 216 21.29 15.29 19.64 0.14 549.05 267.67 52285 +1921 217 19.73 13.73 18.08 1.79 503.37 270.95 52122 +1921 218 17.33 11.33 15.68 0 439.42 367.65 51958 +1921 219 18.73 12.73 17.08 0 475.82 362.52 51791 +1921 220 19.56 13.56 17.91 0 498.6 359 51622 +1921 221 20.71 14.71 19.06 0.09 531.67 265.67 51451 +1921 222 20.13 14.13 18.48 0.43 514.76 266.34 51279 +1921 223 22.44 16.44 20.79 0.23 584.94 259.46 51105 +1921 224 23.61 17.61 21.96 0 623.47 340.43 50929 +1921 225 25.05 19.05 23.4 0 673.83 333.42 50751 +1921 226 24.72 18.72 23.07 0 661.99 333.71 50572 +1921 227 29.56 23.56 27.91 0 854.4 309.45 50392 +1921 228 27.77 21.77 26.12 0.71 778.38 238.16 50210 +1921 229 24.43 18.43 22.78 0 651.74 331.32 50026 +1921 230 25.58 19.58 23.93 0 693.21 325.27 49842 +1921 231 23.42 17.42 21.77 0 617.07 332.66 49656 +1921 232 25.51 19.51 23.86 0 690.62 322.89 49469 +1921 233 24.28 18.28 22.63 0 646.49 326.62 49280 +1921 234 22.11 16.11 20.46 0.06 574.44 250.04 49091 +1921 235 24.41 18.41 22.76 0.17 651.04 242.48 48900 +1921 236 23.73 17.73 22.08 0.05 627.54 243.45 48709 +1921 237 22.61 16.61 20.96 0.95 590.41 245.37 48516 +1921 238 23.62 17.62 21.97 0 623.81 321.81 48323 +1921 239 26.26 20.26 24.61 0 718.77 309.64 48128 +1921 240 26.75 20.75 25.1 0 737.67 305.82 47933 +1921 241 27.34 21.34 25.69 0 760.99 301.55 47737 +1921 242 24.28 18.28 22.63 0.16 646.49 234.61 47541 +1921 243 24.79 18.79 23.14 0.6 664.49 231.78 47343 +1921 244 22.52 16.52 20.87 0.63 587.51 236.78 47145 +1921 245 17.6 11.6 15.95 0.11 446.25 246.6 46947 +1921 246 20.26 14.26 18.61 0 518.51 319.34 46747 +1921 247 21.56 15.56 19.91 0 557.3 313.43 46547 +1921 248 22.5 16.5 20.85 0 586.86 308.41 46347 +1921 249 18.75 12.75 17.1 0 476.36 317.89 46146 +1921 250 14.91 8.91 13.26 0 382.08 325.36 45945 +1921 251 14.73 8.73 13.08 0 378.08 323.6 45743 +1921 252 18.27 12.27 16.62 0 463.59 312.99 45541 +1921 253 21.41 15.41 19.76 0 552.71 301.88 45339 +1921 254 21.06 15.06 19.41 0 542.1 300.88 45136 +1921 255 18.82 12.82 17.17 0 478.25 305.07 44933 +1921 256 18.87 12.87 17.22 0.14 479.6 227.02 44730 +1921 257 14.74 8.74 13.09 0 378.3 310.29 44527 +1921 258 14.78 8.78 13.13 0 379.19 307.84 44323 +1921 259 14.73 8.73 13.08 0 378.08 305.49 44119 +1921 260 15.55 9.55 13.9 0 396.58 301.36 43915 +1921 261 22.44 16.44 20.79 0 584.94 280.83 43711 +1921 262 22.06 16.06 20.41 0 572.86 279.74 43507 +1921 263 16.49 10.49 14.84 0 418.74 292.01 43303 +1921 264 15.61 9.61 13.96 0 397.97 291.34 43099 +1921 265 15.32 9.32 13.67 0 391.32 289.56 42894 +1921 266 24.66 18.66 23.01 0 659.86 261.84 42690 +1921 267 20.77 14.77 19.12 0 533.45 271.4 42486 +1921 268 21.2 15.2 19.55 0 546.32 267.72 42282 +1921 269 21.69 15.69 20.04 0 561.31 263.91 42078 +1921 270 19.44 13.44 17.79 0 495.25 267.43 41875 +1921 271 18.27 12.27 16.62 0 463.59 267.72 41671 +1921 272 16.65 10.65 15 0.13 422.61 201.47 41468 +1921 273 19.07 13.07 17.42 0 485.04 260.67 41265 +1921 274 13.52 7.52 11.87 0.01 352.13 202.08 41062 +1921 275 17.22 11.22 15.57 0.92 436.66 194.66 40860 +1921 276 16.04 10.04 14.39 0.01 408 194.49 40658 +1921 277 18.73 12.73 17.08 0 475.82 250.96 40456 +1921 278 18.49 12.49 16.84 0.48 469.41 186.53 40255 +1921 279 17.04 11.04 15.39 0.27 432.18 186.81 40054 +1921 280 19.16 13.16 17.51 0.23 487.51 181.41 39854 +1921 281 18.95 12.95 17.3 0.11 481.77 179.8 39654 +1921 282 18.01 12.01 16.36 0.6 456.79 179.34 39455 +1921 283 16.61 10.61 14.96 0.01 421.64 179.4 39256 +1921 284 14.42 8.42 12.77 0.12 371.28 180.14 39058 +1921 285 12.4 6.4 10.75 1.3 329.48 180.56 38861 +1921 286 13.82 7.82 12.17 0.48 358.42 176.85 38664 +1921 287 12.64 6.64 10.99 0.1 334.22 176.02 38468 +1921 288 12.06 6.06 10.41 0.35 322.85 174.56 38273 +1921 289 16.01 10.01 14.36 0.34 407.3 167.89 38079 +1921 290 15.31 9.31 13.66 0 391.09 222.25 37885 +1921 291 14.55 8.55 12.9 0 374.12 220.84 37693 +1921 292 15.69 9.69 14.04 0 399.82 216.31 37501 +1921 293 15.96 9.96 14.31 0 406.12 213.17 37311 +1921 294 15.65 9.65 14 0 398.89 210.87 37121 +1921 295 16.91 10.91 15.26 0.01 428.97 154.45 36933 +1921 296 12.32 6.32 10.67 0 327.91 210.49 36745 +1921 297 11.58 5.58 9.93 0 313.7 208.74 36560 +1921 298 11.86 5.86 10.21 0 319.01 205.79 36375 +1921 299 10.17 4.17 8.52 0.19 288.07 153.79 36191 +1921 300 11.67 5.67 10.02 0 315.4 200.6 36009 +1921 301 12.22 6.22 10.57 0 325.96 197.41 35829 +1921 302 8.63 2.63 6.98 0 262.15 198.87 35650 +1921 303 13.38 7.38 11.73 0 349.23 190.76 35472 +1921 304 16.2 10.2 14.55 0 411.79 184.26 35296 +1921 305 1.66 -4.34 0.01 0.03 168.32 147.42 35122 +1921 306 2.42 -3.58 0.77 0.68 176.89 145.33 34950 +1921 307 -1.44 -7.44 -3.09 0.1 136.97 183.28 34779 +1921 308 1.66 -4.34 0.01 0 168.32 227.25 34610 +1921 309 4.57 -1.43 2.92 0 203.2 184.73 34444 +1921 310 4.86 -1.14 3.21 0 206.99 182.04 34279 +1921 311 9.25 3.25 7.6 0 272.34 176.14 34116 +1921 312 12 6 10.35 0 321.7 170.63 33956 +1921 313 7.15 1.15 5.5 0 239.16 173.26 33797 +1921 314 7.48 1.48 5.83 0.29 244.13 128.27 33641 +1921 315 4.12 -1.88 2.47 0 197.43 171.01 33488 +1921 316 5.95 -0.05 4.3 0 221.81 167.5 33337 +1921 317 7.66 1.66 6.01 0.01 246.88 122.97 33188 +1921 318 6.06 0.06 4.41 0 223.35 162.87 33042 +1921 319 2.62 -3.38 0.97 0.02 179.21 122.57 32899 +1921 320 2.14 -3.86 0.49 0 173.69 161.81 32758 +1921 321 6.53 0.53 4.88 0.01 230.05 117.62 32620 +1921 322 3.69 -2.31 2.04 0.15 192.05 117.69 32486 +1921 323 3.69 -2.31 2.04 0.01 192.05 116.47 32354 +1921 324 3.95 -2.05 2.3 0.39 195.29 114.8 32225 +1921 325 5.42 -0.58 3.77 0 214.49 150.39 32100 +1921 326 3.11 -2.89 1.46 0 184.99 150.36 31977 +1921 327 3.91 -2.09 2.26 0 194.79 148.03 31858 +1921 328 7.55 1.55 5.9 0 245.19 143.6 31743 +1921 329 8.9 2.9 7.25 0 266.55 141.06 31631 +1921 330 5.38 -0.62 3.73 1.4 213.95 106.64 31522 +1921 331 1.86 -4.14 0.21 1.87 170.54 107.17 31417 +1921 332 0.17 -5.83 -1.48 0.04 152.56 106.53 31316 +1921 333 3.34 -2.66 1.69 0 187.77 139.35 31218 +1921 334 2.48 -3.52 0.83 0 177.58 138.7 31125 +1921 335 -1.7 -7.7 -3.35 0 134.59 139.41 31035 +1921 336 -0.57 -6.57 -2.22 0 145.22 137.86 30949 +1921 337 -2.47 -8.47 -4.12 0 127.74 136.93 30867 +1921 338 0.58 -5.42 -1.07 0 156.76 134.73 30790 +1921 339 3.91 -2.09 2.26 0 194.79 132.27 30716 +1921 340 -0.3 -6.3 -1.95 0.12 147.86 143.63 30647 +1921 341 3.2 -2.8 1.55 0 186.07 130.99 30582 +1921 342 3.27 -2.73 1.62 0 186.92 130.19 30521 +1921 343 0.71 -5.29 -0.94 0 158.12 130.61 30465 +1921 344 3.74 -2.26 2.09 0 192.67 127.98 30413 +1921 345 -1.61 -7.61 -3.26 0 135.41 129.98 30366 +1921 346 -0.55 -6.55 -2.2 0 145.41 129.01 30323 +1921 347 1.97 -4.03 0.32 0 171.77 127.3 30284 +1921 348 4.55 -1.45 2.9 0 202.94 125.61 30251 +1921 349 2.02 -3.98 0.37 0 172.34 126.54 30221 +1921 350 -0.42 -6.42 -2.07 0 146.68 127.28 30197 +1921 351 1.61 -4.39 -0.04 0 167.77 126.18 30177 +1921 352 3.36 -2.64 1.71 0.07 188.01 93.92 30162 +1921 353 1.54 -4.46 -0.11 0 167 126.05 30151 +1921 354 3.35 -2.65 1.7 0.6 187.89 93.85 30145 +1921 355 3.23 -2.77 1.58 0.05 186.44 93.89 30144 +1921 356 4.84 -1.16 3.19 0.07 206.73 93.26 30147 +1921 357 3.32 -2.68 1.67 0 187.52 125.23 30156 +1921 358 -1.41 -7.41 -3.06 0 137.25 127.42 30169 +1921 359 1.13 -4.87 -0.52 0.09 162.56 94.87 30186 +1921 360 2.64 -3.36 0.99 0 179.44 126.15 30208 +1921 361 8.08 2.08 6.43 0 253.4 123.23 30235 +1921 362 6.36 0.36 4.71 0 227.61 124.82 30267 +1921 363 6.04 0.04 4.39 0 223.07 125.61 30303 +1921 364 11 5 9.35 0 302.93 122.35 30343 +1921 365 8.29 2.29 6.64 0 256.71 125.04 30388 +1922 1 7.59 1.59 5.94 0 245.81 126.42 30438 +1922 2 2.92 -3.08 1.27 0.88 182.73 97.47 30492 +1922 3 -0.47 -6.47 -2.12 0 146.19 132.48 30551 +1922 4 3.14 -2.86 1.49 0 185.35 131.71 30614 +1922 5 -0.11 -6.11 -1.76 0 149.74 133.9 30681 +1922 6 2.58 -3.42 0.93 0.39 178.74 100.15 30752 +1922 7 2.67 -3.33 1.02 0.43 179.79 100.72 30828 +1922 8 0.17 -5.83 -1.48 0.06 152.56 102.74 30907 +1922 9 0.03 -5.97 -1.62 0.61 151.15 103.73 30991 +1922 10 -6.87 -12.87 -8.52 0.08 94.11 149.25 31079 +1922 11 -8.87 -14.87 -10.52 0 81.57 186.16 31171 +1922 12 -6.73 -12.73 -8.38 0 95.05 186.52 31266 +1922 13 -5.24 -11.24 -6.89 0 105.54 187.59 31366 +1922 14 -4.2 -10.2 -5.85 0 113.45 188.62 31469 +1922 15 -3.87 -9.87 -5.52 0 116.06 189.83 31575 +1922 16 -3.14 -9.14 -4.79 0.05 122.03 153.67 31686 +1922 17 -5.4 -11.4 -7.05 0 104.37 193.21 31800 +1922 18 -0.16 -6.16 -1.81 0.5 149.25 156.66 31917 +1922 19 0.39 -5.61 -1.26 0 154.8 195.94 32038 +1922 20 7.48 1.48 5.83 0.04 244.13 154.52 32161 +1922 21 4.78 -1.22 3.13 0.87 205.94 156.7 32289 +1922 22 1.23 -4.77 -0.42 0 163.64 198.72 32419 +1922 23 2.19 -3.81 0.54 0 174.26 159.13 32552 +1922 24 2.66 -3.34 1.01 0.05 179.67 120.7 32688 +1922 25 5.04 -0.96 3.39 0 209.38 161.31 32827 +1922 26 5.34 -0.66 3.69 0.06 213.41 122.27 32969 +1922 27 6.81 0.81 5.16 1.01 234.13 122.95 33114 +1922 28 7.54 1.54 5.89 0 245.04 165.54 33261 +1922 29 0.97 -5.03 -0.68 0 160.86 172.36 33411 +1922 30 -1.84 -7.84 -3.49 0 133.32 176.03 33564 +1922 31 -2.48 -8.48 -4.13 0.05 127.66 173.33 33718 +1922 32 2.61 -3.39 0.96 0 179.09 178.18 33875 +1922 33 6.64 0.64 4.99 0 231.65 177.92 34035 +1922 34 4.63 -1.37 2.98 0 203.98 181.66 34196 +1922 35 3.43 -2.57 1.78 0.13 188.86 138.49 34360 +1922 36 0.88 -5.12 -0.77 0.52 159.9 141.58 34526 +1922 37 -1.53 -7.53 -3.18 0.14 136.15 182.81 34694 +1922 38 -4.05 -10.05 -5.7 0 114.63 234.68 34863 +1922 39 -1.26 -7.26 -2.91 0 138.65 235.85 35035 +1922 40 1.03 -4.97 -0.62 0 161.49 236.91 35208 +1922 41 2.66 -3.34 1.01 0 179.67 200.75 35383 +1922 42 2.25 -3.75 0.6 0 174.94 203.6 35560 +1922 43 3.25 -2.75 1.6 0 186.68 205.62 35738 +1922 44 3.5 -2.5 1.85 0 189.71 208.02 35918 +1922 45 2.9 -3.1 1.25 0 182.5 211.09 36099 +1922 46 1.53 -4.47 -0.12 0 166.89 214.74 36282 +1922 47 -1.76 -7.76 -3.41 0.06 134.05 201.01 36466 +1922 48 -2.88 -8.88 -4.53 0.62 124.22 205.02 36652 +1922 49 -3.33 -9.33 -4.98 0.13 120.46 207.46 36838 +1922 50 -4.03 -10.03 -5.68 0.31 114.79 210.36 37026 +1922 51 -3.81 -9.81 -5.46 0 116.55 270.35 37215 +1922 52 -3.93 -9.93 -5.58 0 115.59 273.1 37405 +1922 53 -3.12 -9.12 -4.77 0.09 122.2 216.36 37596 +1922 54 -5.14 -11.14 -6.79 0 106.28 279.33 37788 +1922 55 0.3 -5.7 -1.35 0 153.88 279.18 37981 +1922 56 3.01 -2.99 1.36 0 183.8 279.43 38175 +1922 57 3.14 -2.86 1.49 0.11 185.35 220.47 38370 +1922 58 5.72 -0.28 4.07 0 218.61 281.58 38565 +1922 59 7.43 1.43 5.78 0 243.37 281.58 38761 +1922 60 16.39 10.39 14.74 0 416.33 236.31 38958 +1922 61 13.1 7.1 11.45 0 343.48 244.84 39156 +1922 62 10.94 4.94 9.29 0.12 301.83 188.07 39355 +1922 63 11.32 5.32 9.67 0.15 308.83 189.89 39553 +1922 64 9.93 3.93 8.28 1.46 283.89 193.48 39753 +1922 65 12.84 6.84 11.19 0.09 338.22 192.43 39953 +1922 66 9.68 3.68 8.03 1.06 279.6 197.91 40154 +1922 67 10 4 8.35 1.31 285.11 199.74 40355 +1922 68 12.55 6.55 10.9 0.5 332.44 199.03 40556 +1922 69 13.9 7.9 12.25 0 360.11 265.66 40758 +1922 70 14.36 8.36 12.71 0.04 369.98 200.7 40960 +1922 71 8.15 2.15 6.5 0.01 254.5 209.95 41163 +1922 72 12.74 6.74 11.09 0 336.22 276.04 41366 +1922 73 9.16 3.16 7.51 0.01 270.84 213.06 41569 +1922 74 8.63 2.63 6.98 0.23 262.15 215.65 41772 +1922 75 7.63 1.63 5.98 0 246.42 291.54 41976 +1922 76 8.66 2.66 7.01 0 262.64 292.84 42179 +1922 77 12.58 6.58 10.93 0 333.03 289.45 42383 +1922 78 10.63 4.63 8.98 0 296.23 295.25 42587 +1922 79 8.98 2.98 7.33 0 267.86 300.38 42791 +1922 80 2.97 -3.03 1.32 0 183.33 309.93 42996 +1922 81 0.68 -5.32 -0.97 0 157.8 314.59 43200 +1922 82 -1.47 -7.47 -3.12 0 136.7 318.96 43404 +1922 83 1.69 -4.31 0.04 0.04 168.65 239.23 43608 +1922 84 3.09 -2.91 1.44 0 184.76 320.24 43812 +1922 85 5.89 -0.11 4.24 0 220.97 319.73 44016 +1922 86 11.1 5.1 9.45 0.26 304.76 236.08 44220 +1922 87 13.83 7.83 12.18 0.86 358.63 234.24 44424 +1922 88 14.18 8.18 12.53 0 366.09 313.92 44627 +1922 89 11.32 5.32 9.67 0 308.83 321.51 44831 +1922 90 14.2 8.2 12.55 0.06 366.52 238.83 45034 +1922 91 13.42 7.42 11.77 0.03 350.05 241.67 45237 +1922 92 13.53 7.53 11.88 0.87 352.34 243.17 45439 +1922 93 14.2 8.2 12.55 0.29 366.52 243.78 45642 +1922 94 13.26 7.26 11.61 0 346.76 329.07 45843 +1922 95 12.11 6.11 10.46 0 323.82 333.4 46045 +1922 96 14.21 8.21 12.56 0 366.73 331.32 46246 +1922 97 14.53 8.53 12.88 0 373.68 332.66 46446 +1922 98 12.11 6.11 10.46 0.01 323.82 254.62 46647 +1922 99 11.64 5.64 9.99 0 314.83 342.38 46846 +1922 100 16.89 10.89 15.24 0 428.48 332.93 47045 +1922 101 15.3 9.3 13.65 0.05 390.86 254 47243 +1922 102 12.64 6.64 10.99 0 334.22 346.24 47441 +1922 103 10.98 4.98 9.33 0 302.56 351.21 47638 +1922 104 8.48 2.48 6.83 1.83 259.74 267.91 47834 +1922 105 9.11 3.11 7.46 0.9 270.01 268.52 48030 +1922 106 7.05 1.05 5.4 1.85 237.67 272.11 48225 +1922 107 6.25 0.25 4.6 0.79 226.04 274.23 48419 +1922 108 5.49 -0.51 3.84 0.86 215.45 276.32 48612 +1922 109 10.01 4.01 8.36 1.24 285.28 272.46 48804 +1922 110 9.1 3.1 7.45 0.76 269.84 274.68 48995 +1922 111 7.85 1.85 6.2 0.02 249.81 277.34 49185 +1922 112 9.93 3.93 8.28 0 283.89 367.95 49374 +1922 113 12.14 6.14 10.49 0 324.4 365.19 49561 +1922 114 15.64 9.64 13.99 0.14 398.66 269.17 49748 +1922 115 15.82 9.82 14.17 0 402.84 359.85 49933 +1922 116 13.74 7.74 12.09 0.11 356.73 274.48 50117 +1922 117 10.54 4.54 8.89 0.05 294.62 280.3 50300 +1922 118 12.47 6.47 10.82 0 330.86 371.31 50481 +1922 119 8.09 2.09 6.44 0.01 253.55 285.34 50661 +1922 120 6.49 0.49 4.84 0 229.48 384.06 50840 +1922 121 14.63 8.63 12.98 0 375.88 370.04 51016 +1922 122 15.26 9.26 13.61 0.57 389.95 277.28 51191 +1922 123 15.68 9.68 14.03 0.3 399.59 277.26 51365 +1922 124 18.2 12.2 16.55 1.33 461.75 272.9 51536 +1922 125 17.51 11.51 15.86 0 443.96 366.83 51706 +1922 126 22.02 16.02 20.37 0.19 571.61 264.91 51874 +1922 127 24.67 18.67 23.02 0.03 660.22 257.67 52039 +1922 128 22.94 16.94 21.29 0 601.15 351.54 52203 +1922 129 20.92 14.92 19.27 0.03 537.91 269.83 52365 +1922 130 22.75 16.75 21.1 0 594.94 353.84 52524 +1922 131 22.02 16.02 20.37 0.46 571.61 268.02 52681 +1922 132 25.82 19.82 24.17 1.3 702.14 256.85 52836 +1922 133 21.9 15.9 20.25 0 567.85 359.27 52989 +1922 134 22.65 16.65 21 0.13 591.7 267.84 53138 +1922 135 14.87 8.87 13.22 0 381.19 382.03 53286 +1922 136 17.49 11.49 15.84 0.1 443.46 281.76 53430 +1922 137 18.07 12.07 16.42 0.76 458.35 281.01 53572 +1922 138 17.77 11.77 16.12 0 450.6 376.17 53711 +1922 139 19.48 13.48 17.83 0 496.36 371.58 53848 +1922 140 13.83 7.83 12.18 0.42 358.63 290.76 53981 +1922 141 13.27 7.27 11.62 0 346.96 389.4 54111 +1922 142 16.11 10.11 14.46 0 409.66 382.93 54238 +1922 143 15.81 9.81 14.16 0 402.61 384.26 54362 +1922 144 17.17 11.17 15.52 0.24 435.41 285.76 54483 +1922 145 15.28 9.28 13.63 0 390.41 386.59 54600 +1922 146 17.79 11.79 16.14 0.08 451.11 285.05 54714 +1922 147 14.98 8.98 13.33 0 383.64 388.21 54824 +1922 148 13.22 7.22 11.57 0 345.94 392.79 54931 +1922 149 13.79 7.79 12.14 0 357.78 391.8 55034 +1922 150 16.52 10.52 14.87 0 419.46 385.2 55134 +1922 151 16.43 10.43 14.78 0 417.29 385.84 55229 +1922 152 24.26 18.26 22.61 0.18 645.79 269.12 55321 +1922 153 22.97 16.97 21.32 0.28 602.13 273.3 55409 +1922 154 23.82 17.82 22.17 0 630.61 361.23 55492 +1922 155 28.54 22.54 26.89 0 810.35 338.89 55572 +1922 156 26.72 20.72 25.07 0 736.5 348.57 55648 +1922 157 24.74 18.74 23.09 0.06 662.71 268.45 55719 +1922 158 22.05 16.05 20.4 0 572.55 369.12 55786 +1922 159 22.17 16.17 20.52 0 576.34 368.9 55849 +1922 160 23.1 17.1 21.45 0.05 606.42 274.07 55908 +1922 161 24.39 18.39 22.74 0.79 650.34 270.08 55962 +1922 162 23.81 17.81 22.16 0.01 630.27 271.97 56011 +1922 163 26.37 20.37 24.72 0 722.97 351.32 56056 +1922 164 20.44 14.44 18.79 2.14 523.74 281.83 56097 +1922 165 16.34 10.34 14.69 0 415.13 388.55 56133 +1922 166 17.58 11.58 15.93 0.11 445.74 288.83 56165 +1922 167 16.64 10.64 14.99 0 422.37 387.75 56192 +1922 168 20.56 14.56 18.91 0 527.26 375.55 56214 +1922 169 21.71 15.71 20.06 0.41 561.93 278.55 56231 +1922 170 17.71 11.71 16.06 0 449.06 384.76 56244 +1922 171 15.04 9.04 13.39 0 384.99 392.16 56252 +1922 172 18.2 12.2 16.55 0 461.75 383.33 56256 +1922 173 20.29 14.29 18.64 0 519.38 376.53 56255 +1922 174 19.48 13.48 17.83 0.21 496.36 284.38 56249 +1922 175 20.99 14.99 19.34 0.36 540 280.47 56238 +1922 176 18.3 12.3 16.65 0.69 464.38 287.14 56223 +1922 177 20.82 14.82 19.17 0.04 534.93 280.82 56203 +1922 178 22.43 16.43 20.78 0 584.62 368.47 56179 +1922 179 21.87 15.87 20.22 0 566.91 370.51 56150 +1922 180 24.1 18.1 22.45 0 640.23 361.46 56116 +1922 181 20.58 14.58 18.93 0 527.84 375 56078 +1922 182 17.1 11.1 15.45 0 433.67 385.89 56035 +1922 183 19.77 13.77 18.12 0 504.5 377.45 55987 +1922 184 20.42 14.42 18.77 0 523.16 375.08 55935 +1922 185 16.82 10.82 15.17 0 426.76 386.26 55879 +1922 186 18.64 12.64 16.99 0 473.41 380.6 55818 +1922 187 22.21 16.21 20.56 0 577.6 368.04 55753 +1922 188 22.86 16.86 21.21 0.01 598.53 273.94 55684 +1922 189 21.44 15.44 19.79 0.53 553.62 277.86 55611 +1922 190 24.17 18.17 22.52 0.1 642.66 269.49 55533 +1922 191 24.32 18.32 22.67 0 647.88 358.42 55451 +1922 192 24.95 18.95 23.3 1.12 670.22 266.54 55366 +1922 193 25.09 19.09 23.44 0 675.27 354.5 55276 +1922 194 25.49 19.49 23.84 0 689.89 352.48 55182 +1922 195 24.14 18.14 22.49 0.07 641.62 268.62 55085 +1922 196 23.57 17.57 21.92 0 622.12 360.14 54984 +1922 197 22.91 16.91 21.26 0 600.17 362.35 54879 +1922 198 25.85 19.85 24.2 0 703.26 349.32 54770 +1922 199 25.61 19.61 23.96 0.39 694.32 262.57 54658 +1922 200 22.8 16.8 21.15 0.22 596.57 271.22 54542 +1922 201 23.48 17.48 21.83 0 619.08 358.45 54423 +1922 202 19.86 13.86 18.21 0 507.05 371.21 54301 +1922 203 23.25 17.25 21.6 0 611.39 358.33 54176 +1922 204 23.77 17.77 22.12 0 628.9 355.72 54047 +1922 205 28.6 22.6 26.95 0.8 812.89 249.36 53915 +1922 206 25.8 19.8 24.15 0 701.39 345.84 53780 +1922 207 22.2 16.2 20.55 0 577.29 360.2 53643 +1922 208 21.96 15.96 20.31 0.11 569.72 270.34 53502 +1922 209 22.52 16.52 20.87 0 587.51 357.7 53359 +1922 210 21.55 15.55 19.9 0 557 360.69 53213 +1922 211 23.15 17.15 21.5 0.65 608.07 265.41 53064 +1922 212 18.57 12.57 16.92 0 471.54 369.02 52913 +1922 213 19.87 13.87 18.22 0.55 507.33 273.11 52760 +1922 214 22.71 16.71 21.06 0.43 593.64 265.01 52604 +1922 215 22.84 16.84 21.19 0 597.88 352.18 52445 +1922 216 19.71 13.71 18.06 0.22 502.81 271.67 52285 +1922 217 19.76 13.76 18.11 0 504.22 361.17 52122 +1922 218 22.55 16.55 20.9 0 588.47 350.61 51958 +1922 219 24.53 18.53 22.88 0.2 655.26 256.28 51791 +1922 220 27.29 21.29 25.64 0.03 758.99 246.25 51622 +1922 221 25.54 19.54 23.89 0.54 691.73 251.62 51451 +1922 222 23.71 17.71 22.06 0 626.86 342.17 51279 +1922 223 23.49 17.49 21.84 0.13 619.42 256.45 51105 +1922 224 21.86 15.86 20.21 0 566.6 347.02 50929 +1922 225 21.43 15.43 19.78 0.01 553.32 260.55 50751 +1922 226 20.05 14.05 18.4 0 512.47 350.89 50572 +1922 227 20.86 14.86 19.21 0.08 536.12 260.22 50392 +1922 228 16.74 10.74 15.09 0.23 424.8 268.53 50210 +1922 229 21.45 15.45 19.8 0.57 553.93 256.89 50026 +1922 230 22.38 16.38 20.73 0.04 583.02 253.48 49842 +1922 231 24.34 18.34 22.69 0 648.58 329.04 49656 +1922 232 21.59 15.59 19.94 0.02 558.23 253.5 49469 +1922 233 22.87 16.87 21.22 0.39 598.86 249.03 49280 +1922 234 17.07 11.07 15.42 2.78 432.93 261.65 49091 +1922 235 17.96 11.96 16.31 0 455.5 344.94 48900 +1922 236 18.83 12.83 17.18 0.47 478.52 255.78 48709 +1922 237 21.96 15.96 20.31 0.74 569.72 247.09 48516 +1922 238 25.52 19.52 23.87 0.02 690.99 235.67 48323 +1922 239 27.26 21.26 25.61 0.03 757.79 228.87 48128 +1922 240 26.92 20.92 25.27 0 744.33 305.06 47933 +1922 241 25.49 19.49 23.84 0 689.89 309.62 47737 +1922 242 26.68 20.68 25.03 0 734.95 302.9 47541 +1922 243 26.09 20.09 24.44 0.06 712.3 227.78 47343 +1922 244 18.4 12.4 16.75 0.19 467.02 246.37 47145 +1922 245 16.7 10.7 15.05 1.75 423.83 248.32 46947 +1922 246 17.34 11.34 15.69 0.01 439.67 245.62 46747 +1922 247 17.7 11.7 16.05 0.16 448.8 243.53 46547 +1922 248 13.62 7.62 11.97 0.76 354.21 249.13 46347 +1922 249 15.76 9.76 14.11 0.52 401.44 244.07 46146 +1922 250 15.34 9.34 13.69 0.34 391.77 243.31 45945 +1922 251 15.41 9.41 13.76 0.37 393.37 241.58 45743 +1922 252 14.73 8.73 13.08 0.2 378.08 241.05 45541 +1922 253 11.71 5.71 10.06 0.01 316.16 243.85 45339 +1922 254 12.52 6.52 10.87 0.37 331.84 241.1 45136 +1922 255 15.95 9.95 14.3 0.29 405.89 234.1 44933 +1922 256 20.4 14.4 18.75 0.56 522.58 223.82 44730 +1922 257 20.48 14.48 18.83 0.53 524.91 222.06 44527 +1922 258 21.45 15.45 19.8 0.2 553.93 218.19 44323 +1922 259 21.32 15.32 19.67 0.02 549.96 216.71 44119 +1922 260 16.23 10.23 14.58 0.23 412.51 224.9 43915 +1922 261 17.93 11.93 16.28 2.29 454.72 220.09 43711 +1922 262 20.15 14.15 18.5 0.29 515.34 213.99 43507 +1922 263 16.8 10.8 15.15 0.55 426.27 218.48 43303 +1922 264 13.93 7.93 12.28 1.21 360.75 221.02 43099 +1922 265 11.46 5.46 9.81 2.39 311.44 222.48 42894 +1922 266 13.25 7.25 11.6 0.98 346.55 218.29 42690 +1922 267 13.62 7.62 11.97 0.22 354.21 215.75 42486 +1922 268 13.02 7.02 11.37 0.03 341.86 214.62 42282 +1922 269 15.65 9.65 14 0.69 398.89 208.99 42078 +1922 270 17.43 11.43 15.78 0 441.94 272.22 41875 +1922 271 21.55 15.55 19.9 0 557 259.27 41671 +1922 272 26.23 20.23 24.58 1.09 717.62 181.25 41468 +1922 273 19.35 13.35 17.7 0 492.75 259.99 41265 +1922 274 10.59 4.59 8.94 0.92 295.51 205.56 41062 +1922 275 11.44 5.44 9.79 0 311.07 270.02 40860 +1922 276 8.74 2.74 7.09 0.45 263.94 203.27 40658 +1922 277 11.23 5.23 9.58 0.01 307.16 198.68 40456 +1922 278 9.83 3.83 8.18 0.01 282.17 197.97 40255 +1922 279 14.5 8.5 12.85 0.11 373.03 190.44 40054 +1922 280 14.08 8.08 12.43 0 363.94 252.01 39854 +1922 281 15.25 9.25 13.6 1.25 389.73 185.43 39654 +1922 282 11.86 5.86 10.21 0.68 319.01 187.54 39455 +1922 283 12.58 6.58 10.93 0.33 333.03 184.61 39256 +1922 284 12.78 6.78 11.13 0.23 337.02 182.11 39058 +1922 285 11.17 5.17 9.52 0 306.05 242.5 38861 +1922 286 9.31 3.31 7.66 1.18 273.34 181.59 38664 +1922 287 14.57 8.57 12.92 0.88 374.56 173.75 38468 +1922 288 11.99 5.99 10.34 2.19 321.51 174.63 38273 +1922 289 8.78 2.78 7.13 1.1 264.59 175.7 38079 +1922 290 7.42 1.42 5.77 0 243.22 232.85 37885 +1922 291 9.01 3.01 7.36 0 268.36 228.37 37693 +1922 292 11.71 5.71 10.06 0.38 316.16 166.75 37501 +1922 293 9.69 3.69 8.04 0.09 279.77 166.58 37311 +1922 294 6.32 0.32 4.67 0.26 227.04 167.04 37121 +1922 295 4.82 -1.18 3.17 0.04 206.47 165.87 36933 +1922 296 9.33 3.33 7.68 0 273.67 214.15 36745 +1922 297 9.42 3.42 7.77 0.02 275.19 158.48 36560 +1922 298 13.72 7.72 12.07 0 356.31 203.27 36375 +1922 299 12.88 6.88 11.23 0.56 339.03 151.26 36191 +1922 300 13.59 7.59 11.94 1.58 353.59 148.56 36009 +1922 301 8.18 2.18 6.53 1 254.97 151.46 35829 +1922 302 10.21 4.21 8.56 0.02 288.77 147.9 35650 +1922 303 9.82 3.82 8.17 0.27 282 146.28 35472 +1922 304 9.8 3.8 8.15 0.33 281.65 144.45 35296 +1922 305 4.16 -1.84 2.51 0.09 197.94 146.15 35122 +1922 306 3.02 -2.98 1.37 0 183.92 193.37 34950 +1922 307 6.78 0.78 5.13 0 233.69 187.96 34779 +1922 308 8 2 6.35 0 252.14 184.25 34610 +1922 309 5.65 -0.35 4 0 217.64 183.91 34444 +1922 310 3.45 -2.55 1.8 0.13 189.1 137.28 34279 +1922 311 5.9 -0.1 4.25 0 221.11 179.05 34116 +1922 312 11.81 5.81 10.16 0.02 318.06 128.14 33956 +1922 313 9.96 3.96 8.31 0.17 284.41 128.03 33797 +1922 314 6.78 0.78 5.13 0 233.69 171.6 33641 +1922 315 7.23 1.23 5.58 0 240.35 168.69 33488 +1922 316 13.26 7.26 11.61 0 346.76 160.55 33337 +1922 317 10.28 4.28 8.63 0 290 161.6 33188 +1922 318 4.28 -1.72 2.63 0 199.47 164.12 33042 +1922 319 -0.12 -6.12 -1.77 0 149.64 164.9 32899 +1922 320 5.32 -0.68 3.67 0 213.14 159.82 32758 +1922 321 0.61 -5.39 -1.04 0.06 157.08 120.37 32620 +1922 322 6.17 0.17 4.52 0 224.9 155.27 32486 +1922 323 7.25 1.25 5.6 0 240.65 152.85 32354 +1922 324 3.35 -2.65 1.7 0.25 187.89 115.07 32225 +1922 325 2.69 -3.31 1.04 0.49 180.03 114.05 32100 +1922 326 2.06 -3.94 0.41 0.06 172.79 113.21 31977 +1922 327 4.15 -1.85 2.5 0.1 197.81 110.91 31858 +1922 328 -0.51 -6.51 -2.16 1.05 145.8 156.01 31743 +1922 329 2.77 -3.23 1.12 0 180.96 189.76 31631 +1922 330 8.8 2.8 7.15 0 264.91 183.3 31522 +1922 331 5.04 -0.96 3.39 0 209.38 184.17 31417 +1922 332 5.98 -0.02 4.33 0 222.23 181.3 31316 +1922 333 6.83 0.83 5.18 0 234.42 137.17 31218 +1922 334 4.74 -1.26 3.09 0 205.42 137.43 31125 +1922 335 9 3 7.35 0 268.19 133.31 31035 +1922 336 4.91 -1.09 3.26 0 207.65 135.08 30949 +1922 337 6.42 0.42 4.77 0 228.47 132.46 30867 +1922 338 3.86 -2.14 2.21 0 194.16 133.08 30790 +1922 339 -0.42 -6.42 -2.07 0 146.68 134.37 30716 +1922 340 -0.29 -6.29 -1.94 0 147.96 133.57 30647 +1922 341 -0.4 -6.4 -2.05 0 146.88 132.68 30582 +1922 342 0.67 -5.33 -0.98 0 157.7 131.46 30521 +1922 343 1.55 -4.45 -0.1 0.57 167.11 97.67 30465 +1922 344 1.14 -4.86 -0.51 0 162.67 129.28 30413 +1922 345 2.84 -3.16 1.19 0 181.79 128.02 30366 +1922 346 -0.09 -6.09 -1.74 0 149.94 128.82 30323 +1922 347 1.95 -4.05 0.3 0 171.55 127.31 30284 +1922 348 3.55 -2.45 1.9 0 190.33 126.16 30251 +1922 349 3.74 -2.26 2.09 0 192.67 125.67 30221 +1922 350 -0.39 -6.39 -2.04 0.02 146.97 139.23 30197 +1922 351 5.37 -0.63 3.72 0 213.82 124.2 30177 +1922 352 4.46 -1.54 2.81 0 201.78 124.63 30162 +1922 353 -0.46 -6.46 -2.11 0 146.29 126.91 30151 +1922 354 3.15 -2.85 1.5 0 185.47 125.24 30145 +1922 355 5.36 -0.64 3.71 0 213.68 124.02 30144 +1922 356 7.16 1.16 5.51 0 239.31 122.92 30147 +1922 357 6.68 0.68 5.03 0 232.23 123.29 30156 +1922 358 7.95 1.95 6.3 0 251.36 122.52 30169 +1922 359 5.84 -0.16 4.19 0 220.27 124.02 30186 +1922 360 6.46 0.46 4.81 0 229.04 123.99 30208 +1922 361 5.97 -0.03 4.32 0 222.09 124.63 30235 +1922 362 10.84 4.84 9.19 0 300.02 121.53 30267 +1922 363 9.61 3.61 7.96 0 278.4 123.1 30303 +1922 364 6.95 0.95 5.3 0 236.19 125.41 30343 +1922 365 7.31 1.31 5.66 0 241.56 125.73 30388 +1923 1 8.08 2.08 6.43 0 253.4 126.08 30438 +1923 2 3.35 -2.65 1.7 0 187.89 129.74 30492 +1923 3 4.43 -1.57 2.78 0 201.39 130.08 30551 +1923 4 7.3 1.3 5.65 0 241.41 129.19 30614 +1923 5 12.11 6.11 10.46 0.03 323.82 94.44 30681 +1923 6 10.31 4.31 8.66 0 290.53 128.39 30752 +1923 7 8.02 2.02 6.37 0 252.46 130.97 30828 +1923 8 4.23 -1.77 2.58 0 198.83 134.92 30907 +1923 9 3 -3 1.35 0 183.68 136.86 30991 +1923 10 2.62 -3.38 0.97 0 179.21 138.37 31079 +1923 11 0.85 -5.15 -0.8 0.14 159.59 105.18 31171 +1923 12 1.82 -4.18 0.17 0 170.1 140.79 31266 +1923 13 0.56 -5.44 -1.09 0.03 156.56 107.27 31366 +1923 14 -1.67 -7.67 -3.32 0.61 134.87 152.92 31469 +1923 15 1.09 -4.91 -0.56 0.1 162.13 152.81 31575 +1923 16 0.01 -5.99 -1.64 0.02 150.94 154.01 31686 +1923 17 2.61 -3.39 0.96 0.57 179.09 153.81 31800 +1923 18 -0.77 -6.77 -2.42 0.13 143.28 156.73 31917 +1923 19 -2.27 -8.27 -3.92 0.07 129.49 158.72 32038 +1923 20 1.6 -4.4 -0.05 0.22 167.66 158.22 32161 +1923 21 0.88 -5.12 -0.77 0.15 159.9 159.73 32289 +1923 22 3.67 -2.33 2.02 0 191.8 198.37 32419 +1923 23 3.37 -2.63 1.72 0 188.13 199.74 32552 +1923 24 5.02 -0.98 3.37 0.41 209.11 160.09 32688 +1923 25 5.76 -0.24 4.11 0.1 219.16 120.6 32827 +1923 26 2.26 -3.74 0.61 0 175.06 164.99 32969 +1923 27 4.81 -1.19 3.16 0 206.34 165.41 33114 +1923 28 7.87 1.87 6.22 0 250.12 165.26 33261 +1923 29 7.64 1.64 5.99 0 246.57 167.81 33411 +1923 30 3.49 -2.51 1.84 0.57 189.59 129.84 33564 +1923 31 1.7 -4.3 0.05 0.02 168.77 132.45 33718 +1923 32 2.1 -3.9 0.45 0 173.24 178.49 33875 +1923 33 -3.41 -9.41 -5.06 0.9 119.8 179.27 34035 +1923 34 -2.77 -8.77 -4.42 0.23 125.16 181.19 34196 +1923 35 -1.54 -7.54 -3.19 0.02 136.05 182.26 34360 +1923 36 -2.51 -8.51 -4.16 0 127.4 231.94 34526 +1923 37 1.23 -4.77 -0.42 0 163.64 232.1 34694 +1923 38 3.32 -2.68 1.67 0.01 187.52 184.82 34863 +1923 39 3.53 -2.47 1.88 0.03 190.08 186.07 35035 +1923 40 4.55 -1.45 2.9 0 202.94 235.95 35208 +1923 41 4.45 -1.55 2.8 0 201.65 237.94 35383 +1923 42 6.09 0.09 4.44 0 223.77 238.28 35560 +1923 43 4.44 -1.56 2.79 0 201.52 204.73 35738 +1923 44 3.69 -2.31 2.04 0 192.05 207.88 35918 +1923 45 7.25 1.25 5.6 0 240.65 207.49 36099 +1923 46 9.34 3.34 7.69 0.3 273.84 156.01 36282 +1923 47 6.88 0.88 5.23 0.81 235.16 159.99 36466 +1923 48 5.82 -0.18 4.17 0.26 219.99 162.81 36652 +1923 49 2.6 -3.4 0.95 0.02 178.98 166.85 36838 +1923 50 2.83 -3.17 1.18 1.19 181.67 168.73 37026 +1923 51 -1.07 -7.07 -2.72 0 140.43 230.55 37215 +1923 52 -1.48 -7.48 -3.13 0 136.61 233.65 37405 +1923 53 1.46 -4.54 -0.19 0.02 166.13 176.1 37596 +1923 54 0.61 -5.39 -1.04 0.47 157.08 178.62 37788 +1923 55 5.05 -0.95 3.4 0.07 209.51 178.29 37981 +1923 56 10.49 4.49 8.84 0.32 293.72 175.88 38175 +1923 57 11.98 5.98 10.33 0 321.31 235.32 38370 +1923 58 8.45 2.45 6.8 0 259.26 242.73 38565 +1923 59 10.86 4.86 9.21 0.25 300.38 181.8 38761 +1923 60 14.35 8.35 12.7 0.07 369.76 179.96 38958 +1923 61 9 3 7.35 0 268.19 250.53 39156 +1923 62 9.82 3.82 8.17 0.07 282 189.2 39355 +1923 63 10.35 4.35 8.7 0 291.24 254.54 39553 +1923 64 11.71 5.71 10.06 0.17 316.16 191.61 39753 +1923 65 11.48 5.48 9.83 0.28 311.82 193.99 39953 +1923 66 11.89 5.89 10.24 0.37 319.59 195.55 40154 +1923 67 7.28 1.28 5.63 0.11 241.11 202.3 40355 +1923 68 6.27 0.27 4.62 0 226.32 273.74 40556 +1923 69 7.8 1.8 6.15 0.24 249.03 205.96 40758 +1923 70 8.41 2.41 6.76 0 258.62 276.69 40960 +1923 71 10.47 4.47 8.82 0.28 293.37 207.6 41163 +1923 72 6.44 0.44 4.79 0 228.76 284.79 41366 +1923 73 8.87 2.87 7.22 0 266.06 284.47 41569 +1923 74 8.67 2.67 7.02 0 262.8 287.48 41772 +1923 75 9.18 3.18 7.53 0.04 271.17 217.13 41976 +1923 76 8.72 2.72 7.07 0.11 263.61 219.57 42179 +1923 77 8.65 2.65 7 0 262.48 295.45 42383 +1923 78 8.41 2.41 6.76 0 258.62 298.44 42587 +1923 79 6.81 0.81 5.16 0 234.13 303.21 42791 +1923 80 4.22 -1.78 2.57 0 198.7 308.68 42996 +1923 81 6.17 0.17 4.52 0 224.9 309.13 43200 +1923 82 8.16 2.16 6.51 0.21 254.65 231.96 43404 +1923 83 10.09 4.09 8.44 0 286.67 308.99 43608 +1923 84 8.4 2.4 6.75 0.08 258.46 235.49 43812 +1923 85 9.38 3.38 7.73 0.57 274.51 236.31 44016 +1923 86 10.93 4.93 9.28 0 301.65 315.05 44220 +1923 87 8.31 2.31 6.66 0.79 257.03 241.18 44424 +1923 88 5.36 -0.64 3.71 0.93 213.68 245.8 44627 +1923 89 3.46 -2.54 1.81 0.01 189.23 249.11 44831 +1923 90 0.95 -5.05 -0.7 0 160.64 336.98 45034 +1923 91 6.29 0.29 4.64 0.55 226.61 250.2 45237 +1923 92 4.91 -1.09 3.26 0 207.65 337.54 45439 +1923 93 5.5 -0.5 3.85 0 215.58 339.09 45642 +1923 94 4.1 -1.9 2.45 0 197.18 342.91 45843 +1923 95 9.29 3.29 7.64 0 273.01 338.2 46045 +1923 96 8.21 2.21 6.56 0 255.44 341.96 46246 +1923 97 8.93 2.93 7.28 0.29 267.04 257.22 46446 +1923 98 6.15 0.15 4.5 0 224.62 348.88 46647 +1923 99 6.77 0.77 5.12 0.62 233.54 262.57 46846 +1923 100 9.57 3.57 7.92 0.37 277.72 260.93 47045 +1923 101 5.31 -0.69 3.66 1.3 213 266.96 47243 +1923 102 9.33 3.33 7.68 0.96 273.67 264.12 47441 +1923 103 9.56 3.56 7.91 0 277.55 353.65 47638 +1923 104 6.73 0.73 5.08 0 232.96 359.76 47834 +1923 105 6.4 0.4 4.75 0 228.18 362.04 48030 +1923 106 10.72 4.72 9.07 0 297.85 356.96 48225 +1923 107 12.09 6.09 10.44 0 323.43 356.08 48419 +1923 108 12.74 6.74 11.09 0 336.22 356.53 48612 +1923 109 14.79 8.79 13.14 0.66 379.41 265.26 48804 +1923 110 15.79 9.79 14.14 0.82 402.14 264.52 48995 +1923 111 13.77 7.77 12.12 1.73 357.36 269.19 49185 +1923 112 16.88 10.88 15.23 0.64 428.23 264.7 49374 +1923 113 14.84 8.84 13.19 0 380.52 359.34 49561 +1923 114 17.3 11.3 15.65 0 438.67 354.58 49748 +1923 115 17.65 11.65 16 0.06 447.52 266.26 49933 +1923 116 21.52 15.52 19.87 0.04 556.07 258.08 50117 +1923 117 14.5 8.5 12.85 0.47 373.03 274.16 50300 +1923 118 16.77 10.77 15.12 0 425.54 361.19 50481 +1923 119 13.84 7.84 12.19 0.29 358.84 277.17 50661 +1923 120 12.82 6.82 11.17 1.26 337.82 279.72 50840 +1923 121 19.6 13.6 17.95 0.18 499.72 267.28 51016 +1923 122 19.79 13.79 18.14 0 505.07 356.93 51191 +1923 123 19.67 13.67 18.02 0 501.68 358.31 51365 +1923 124 16.88 10.88 15.23 0 428.23 367.6 51536 +1923 125 15.15 9.15 13.5 0.27 387.46 279.8 51706 +1923 126 20.12 14.12 18.47 0 514.48 359.82 51874 +1923 127 20.48 14.48 18.83 0.08 524.91 269.61 52039 +1923 128 20.27 14.27 18.62 0.32 518.8 270.87 52203 +1923 129 23.97 17.97 22.32 0 635.75 348.23 52365 +1923 130 25.76 19.76 24.11 0 699.9 341.23 52524 +1923 131 24.43 18.43 22.78 0 651.74 347.81 52681 +1923 132 20.27 14.27 18.62 0 518.8 364.33 52836 +1923 133 19.47 13.47 17.82 0 496.08 367.64 52989 +1923 134 19.01 13.01 17.36 0 483.41 369.8 53138 +1923 135 13.63 7.63 11.98 0 354.42 384.98 53286 +1923 136 10.4 4.4 8.75 0 292.12 392.34 53430 +1923 137 15.03 9.03 13.38 0.45 384.76 287.24 53572 +1923 138 14.77 8.77 13.12 0.01 378.97 288.18 53711 +1923 139 13.03 7.03 11.38 0.33 342.06 291.75 53848 +1923 140 12.49 6.49 10.84 0.03 331.25 293 53981 +1923 141 12.58 6.58 10.93 0.29 333.03 293.19 54111 +1923 142 19.1 13.1 17.45 0.72 485.86 280.65 54238 +1923 143 20.8 14.8 19.15 0.36 534.34 276.78 54362 +1923 144 22.01 16.01 20.36 0.75 571.29 273.84 54483 +1923 145 18.79 12.79 17.14 0 477.44 376.64 54600 +1923 146 19.67 13.67 18.02 0.09 501.68 280.64 54714 +1923 147 15.32 9.32 13.67 0.09 391.32 290.51 54824 +1923 148 22.33 16.33 20.68 0.36 581.42 274.17 54931 +1923 149 21.09 15.09 19.44 0.22 543 277.84 55034 +1923 150 18.56 12.56 16.91 1.13 471.27 284.42 55134 +1923 151 17.61 11.61 15.96 0 446.5 382.49 55229 +1923 152 16.89 10.89 15.24 0.76 428.48 288.5 55321 +1923 153 18.41 12.41 16.76 0.8 467.28 285.33 55409 +1923 154 15.04 9.04 13.39 0 384.99 390.18 55492 +1923 155 17.99 11.99 16.34 0 456.27 382.22 55572 +1923 156 15.9 9.9 14.25 0.06 404.71 291.35 55648 +1923 157 16.71 10.71 15.06 2.07 424.07 289.82 55719 +1923 158 13.85 7.85 12.2 1.49 359.05 295.47 55786 +1923 159 13.26 7.26 11.61 0 346.76 395.58 55849 +1923 160 16.11 10.11 14.46 0 409.66 388.69 55908 +1923 161 18.65 12.65 17 1.78 473.68 286.02 55962 +1923 162 19.68 13.68 18.03 0.35 501.96 283.57 56011 +1923 163 18.96 12.96 17.31 1.14 482.04 285.49 56056 +1923 164 14.26 8.26 12.61 0.31 367.81 295.36 56097 +1923 165 12.54 6.54 10.89 0.12 332.24 298.41 56133 +1923 166 8.86 2.86 7.21 0.29 265.89 303.86 56165 +1923 167 13.36 7.36 11.71 0 348.81 396.07 56192 +1923 168 19.8 13.8 18.15 0 505.35 378.15 56214 +1923 169 23.74 17.74 22.09 0 627.88 363.38 56231 +1923 170 21.77 15.77 20.12 2.12 563.79 278.39 56244 +1923 171 18.94 12.94 17.29 1.12 481.5 285.77 56252 +1923 172 23.01 17.01 21.36 0.35 603.45 274.82 56256 +1923 173 20.91 14.91 19.26 0.1 537.61 280.77 56255 +1923 174 17.25 11.25 15.6 0.01 437.41 289.54 56249 +1923 175 16.65 10.65 15 0.35 422.61 290.8 56238 +1923 176 15.75 9.75 14.1 0 401.21 390.14 56223 +1923 177 20.05 14.05 18.4 0.06 512.47 282.82 56203 +1923 178 17.73 11.73 16.08 0.02 449.57 288.38 56179 +1923 179 19.05 13.05 17.4 0 484.5 380.32 56150 +1923 180 19.16 13.16 17.51 0 487.51 379.85 56116 +1923 181 21.36 15.36 19.71 0 551.18 372.21 56078 +1923 182 23.3 17.3 21.65 0 613.06 364.58 56035 +1923 183 20.94 14.94 19.29 0 538.51 373.41 55987 +1923 184 23.17 17.17 21.52 0 608.73 364.79 55935 +1923 185 23.06 17.06 21.41 0 605.1 365.15 55879 +1923 186 22.61 16.61 20.96 0 590.41 366.68 55818 +1923 187 25 19 23.35 0 672.02 356.5 55753 +1923 188 22.78 16.78 21.13 0 595.92 365.56 55684 +1923 189 25.87 19.87 24.22 0 704.01 352.09 55611 +1923 190 22.03 16.03 20.38 0.53 571.92 275.94 55533 +1923 191 24.79 18.79 23.14 0.28 664.49 267.28 55451 +1923 192 26.93 20.93 25.28 0.08 744.72 259.57 55366 +1923 193 28.59 22.59 26.94 1.1 812.46 252.95 55276 +1923 194 28.16 22.16 26.51 0.19 794.43 254.52 55182 +1923 195 25.27 19.27 23.62 0.47 681.82 264.91 55085 +1923 196 22.96 16.96 21.31 0 601.8 362.6 54984 +1923 197 24.01 18.01 22.36 0.22 637.13 268.4 54879 +1923 198 24.37 18.37 22.72 0.66 649.63 266.94 54770 +1923 199 24.3 18.3 22.65 1.11 647.19 266.91 54658 +1923 200 24.21 18.21 22.56 0 644.05 355.87 54542 +1923 201 23.65 17.65 22 0 624.82 357.75 54423 +1923 202 23 17 21.35 0 603.12 359.82 54301 +1923 203 23.93 17.93 22.28 0 634.38 355.55 54176 +1923 204 23.19 17.19 21.54 0.2 609.4 268.56 54047 +1923 205 22.25 16.25 20.6 0 578.87 361.22 53915 +1923 206 20.81 14.81 19.16 0.37 534.64 274.42 53780 +1923 207 24.23 18.23 22.58 0 644.75 352.12 53643 +1923 208 22.51 16.51 20.86 0 587.18 358.38 53502 +1923 209 22.13 16.13 20.48 0 575.07 359.18 53359 +1923 210 22.79 16.79 21.14 1.01 596.25 267.04 53213 +1923 211 19.67 13.67 18.02 0 501.68 366.36 53064 +1923 212 19.68 13.68 18.03 0.48 501.96 274.15 52913 +1923 213 15.16 9.16 13.51 0.32 387.69 283.23 52760 +1923 214 17.17 11.17 15.52 0.29 435.41 278.68 52604 +1923 215 19.69 13.69 18.04 0 502.24 363.3 52445 +1923 216 19.21 13.21 17.56 0.12 488.88 272.86 52285 +1923 217 21.53 15.53 19.88 0 556.38 355.16 52122 +1923 218 19.7 13.7 18.05 0 502.53 360.54 51958 +1923 219 17.58 11.58 15.93 0 445.74 365.89 51791 +1923 220 21.99 15.99 20.34 0.07 570.66 263.05 51622 +1923 221 19.82 13.82 18.17 0.06 505.92 267.87 51451 +1923 222 19.4 13.4 17.75 0.02 494.14 268.09 51279 +1923 223 21.84 15.84 20.19 0.11 565.97 261.1 51105 +1923 224 20.85 14.85 19.2 0 535.82 350.53 50929 +1923 225 20.85 14.85 19.2 0.07 535.82 262.05 50751 +1923 226 22.82 16.82 21.17 1.66 597.22 255.93 50572 +1923 227 22.96 16.96 21.31 0 601.8 339.47 50392 +1923 228 23.72 17.72 22.07 1.03 627.2 251.52 50210 +1923 229 24.91 18.91 23.26 0.02 668.79 247 50026 +1923 230 26.18 20.18 24.53 0 715.72 322.63 49842 +1923 231 29.3 23.3 27.65 0 842.98 306.1 49656 +1923 232 31.28 25.28 29.63 0 933.26 293.91 49469 +1923 233 29.47 23.47 27.82 0 850.43 302.68 49280 +1923 234 28.61 22.61 26.96 0 813.31 305.82 49091 +1923 235 27.08 21.08 25.43 0.54 750.64 233.86 48900 +1923 236 22.67 16.67 21.02 1.06 592.35 246.41 48709 +1923 237 20.57 14.57 18.92 1.58 527.55 250.56 48516 +1923 238 19.38 13.38 17.73 0 493.58 336.1 48323 +1923 239 20.98 14.98 19.33 0 539.7 329.61 48128 +1923 240 24.34 18.34 22.69 0 648.58 315.89 47933 +1923 241 26.95 20.95 25.3 0 745.51 303.32 47737 +1923 242 27.25 21.25 25.6 0 757.39 300.35 47541 +1923 243 26.82 20.82 25.17 0 740.41 300.54 47343 +1923 244 22.29 16.29 20.64 0.36 580.15 237.38 47145 +1923 245 22.63 16.63 20.98 1.61 591.05 235.16 46947 +1923 246 23.78 17.78 22.13 0.28 629.24 230.64 46747 +1923 247 23.62 17.62 21.97 0 623.81 306.33 46547 +1923 248 19.38 13.38 17.73 0 493.58 318.18 46347 +1923 249 20.58 14.58 18.93 0.04 527.84 234.45 46146 +1923 250 18.42 12.42 16.77 0 467.55 316.85 45945 +1923 251 16.71 10.71 15.06 0.02 424.07 239.32 45743 +1923 252 19.64 13.64 17.99 0.99 500.84 231.93 45541 +1923 253 17.19 11.19 15.54 0 435.91 313.62 45339 +1923 254 19.4 13.4 17.75 0 494.14 305.72 45136 +1923 255 17.94 11.94 16.29 0.01 454.98 230.52 44933 +1923 256 15.14 9.14 13.49 0.13 387.24 233.73 44730 +1923 257 16.02 10.02 14.37 1.65 407.53 230.64 44527 +1923 258 16.58 10.58 14.93 0.17 420.91 227.92 44323 +1923 259 22.2 16.2 20.55 0.05 577.29 214.67 44119 +1923 260 16.13 10.13 14.48 0.09 410.13 225.07 43915 +1923 261 18.39 12.39 16.74 0.35 466.76 219.23 43711 +1923 262 18.57 12.57 16.92 0 471.54 289.51 43507 +1923 263 18.68 12.68 17.03 0.26 474.48 215.1 43303 +1923 264 20.02 14.02 18.37 0 511.61 280.77 43099 +1923 265 14.99 8.99 13.34 0 383.87 290.23 42894 +1923 266 15.77 9.77 14.12 0 401.68 286.15 42690 +1923 267 18.53 12.53 16.88 0 470.47 277.24 42486 +1923 268 18.64 12.64 16.99 0 473.41 274.46 42282 +1923 269 20.37 14.37 18.72 0 521.7 267.58 42078 +1923 270 17.38 11.38 15.73 0 440.68 272.33 41875 +1923 271 18.12 12.12 16.47 0 459.66 268.06 41671 +1923 272 16.43 10.43 14.78 0 417.29 269.09 41468 +1923 273 17.82 11.82 16.17 0.08 451.88 197.69 41265 +1923 274 14.65 8.65 13 0.06 376.32 200.56 41062 +1923 275 15.38 9.38 13.73 0.01 392.69 197.46 40860 +1923 276 12.6 6.6 10.95 0.15 333.43 199.11 40658 +1923 277 15.32 9.32 13.67 1.36 391.32 193.55 40456 +1923 278 14.68 8.68 13.03 0.08 376.98 192.3 40255 +1923 279 14.08 8.08 12.43 0 363.94 254.65 40054 +1923 280 15.36 9.36 13.71 0 392.23 249.73 39854 +1923 281 14.74 8.74 13.09 1.18 378.3 186.12 39654 +1923 282 15.67 9.67 14.02 0 399.35 243.76 39455 +1923 283 17.47 11.47 15.82 0.07 442.95 178.12 39256 +1923 284 18.55 12.55 16.9 0 471 232.29 39058 +1923 285 18.06 12.06 16.41 0.36 458.09 173.07 38861 +1923 286 19.17 13.17 17.52 0.23 487.78 169.3 38664 +1923 287 20.02 14.02 18.37 0.6 511.61 165.75 38468 +1923 288 20.78 14.78 19.13 1.47 533.75 162.43 38273 +1923 289 20.59 14.59 18.94 0.02 528.14 160.89 38079 +1923 290 14.81 8.81 13.16 0.03 379.85 167.31 37885 +1923 291 15.14 9.14 13.49 0.08 387.24 164.91 37693 +1923 292 13.43 7.43 11.78 0.46 350.26 164.93 37501 +1923 293 13.93 7.93 12.28 0 360.75 216.45 37311 +1923 294 14.95 8.95 13.3 0 382.97 212.01 37121 +1923 295 17.31 11.31 15.66 0 438.92 205.21 36933 +1923 296 16.1 10.1 14.45 0.06 409.42 153.61 36745 +1923 297 16.13 10.13 14.48 0.01 410.13 151.58 36560 +1923 298 16.85 10.85 15.2 0 427.5 198.35 36375 +1923 299 16.74 10.74 15.09 0.54 424.8 146.87 36191 +1923 300 17.21 11.21 15.56 0.45 436.41 144.33 36009 +1923 301 17.42 11.42 15.77 0 441.69 189.65 35829 +1923 302 17.19 11.19 15.54 0 435.91 187.52 35650 +1923 303 17.13 11.13 15.48 0.05 434.42 138.85 35472 +1923 304 15.71 9.71 14.06 0 400.28 185.02 35296 +1923 305 5.98 -0.02 4.33 0 222.23 193.44 35122 +1923 306 4.96 -1.04 3.31 0 208.32 191.97 34950 +1923 307 2.46 -3.54 0.81 0 177.35 191.18 34779 +1923 308 4.18 -1.82 2.53 0 198.19 187.36 34610 +1923 309 4.74 -1.26 3.09 0 205.42 184.61 34444 +1923 310 7.19 1.19 5.54 0 239.76 180.19 34279 +1923 311 9.82 3.82 8.17 0 282 175.58 34116 +1923 312 13.28 7.28 11.63 0 347.17 169.12 33956 +1923 313 10.97 4.97 9.32 0 302.38 169.67 33797 +1923 314 11.15 5.15 9.5 0 305.68 167.55 33641 +1923 315 15.71 9.71 14.06 0.07 400.28 119.65 33488 +1923 316 17.39 11.39 15.74 0.37 440.93 116.26 33337 +1923 317 20.56 14.56 18.91 0 527.26 147.71 33188 +1923 318 17.39 11.39 15.74 0.21 440.93 113.01 33042 +1923 319 14.91 8.91 13.26 0.4 382.08 114.35 32899 +1923 320 12.26 6.26 10.61 1.76 326.74 115.32 32758 +1923 321 11.05 5.05 9.4 0.01 303.84 114.7 32620 +1923 322 9.54 3.54 7.89 0 277.21 152.56 32486 +1923 323 6.84 0.84 5.19 0.29 234.57 114.87 32354 +1923 324 4.22 -1.78 2.57 0.68 198.7 114.67 32225 +1923 325 0.93 -5.07 -0.72 0 160.43 153.01 32100 +1923 326 6.81 0.81 5.16 0.28 234.13 110.97 31977 +1923 327 6.09 0.09 4.44 0 223.77 146.62 31858 +1923 328 5.66 -0.34 4.01 0.06 217.78 108.71 31743 +1923 329 3.37 -2.63 1.72 0.29 188.13 108.65 31631 +1923 330 7.57 1.57 5.92 0.01 245.5 105.5 31522 +1923 331 9.27 3.27 7.62 1.89 272.67 103.52 31417 +1923 332 10.59 4.59 8.94 1.15 295.51 101.46 31316 +1923 333 7.32 1.32 5.67 1.59 241.71 102.62 31218 +1923 334 6.72 0.72 5.07 0 232.81 136.15 31125 +1923 335 3.2 -2.8 1.55 0 186.07 137.14 31035 +1923 336 4.82 -1.18 3.17 0 206.47 135.14 30949 +1923 337 6.42 0.42 4.77 0 228.47 132.46 30867 +1923 338 7.32 1.32 5.67 0 241.71 130.92 30790 +1923 339 6.12 0.12 4.47 0.02 224.2 98.2 30716 +1923 340 6.28 0.28 4.63 0 226.47 130.11 30647 +1923 341 6.78 0.78 5.13 0 233.69 128.86 30582 +1923 342 8.57 2.57 6.92 0 261.19 126.85 30521 +1923 343 6.94 0.94 5.29 0.62 236.04 95.39 30465 +1923 344 6.2 0.2 4.55 1.16 225.33 94.9 30413 +1923 345 6.15 0.15 4.5 0.18 224.62 94.61 30366 +1923 346 9.01 3.01 7.36 0.63 268.36 92.72 30323 +1923 347 6.47 0.47 4.82 0.44 229.19 93.6 30284 +1923 348 6.45 0.45 4.8 0.96 228.9 93.35 30251 +1923 349 2.91 -3.09 1.26 0.01 182.61 94.58 30221 +1923 350 3.98 -2.02 2.33 0.05 195.67 93.91 30197 +1923 351 -3.16 -9.16 -4.81 0 121.87 128.07 30177 +1923 352 0.43 -5.57 -1.22 0.67 155.21 94.96 30162 +1923 353 2.01 -3.99 0.36 0.01 172.22 94.37 30151 +1923 354 1.93 -4.07 0.28 0.05 171.33 94.38 30145 +1923 355 -2.72 -8.72 -4.37 0.32 125.59 140.6 30144 +1923 356 -0.09 -6.09 -1.74 0 149.94 171.56 30147 +1923 357 3.24 -2.76 1.59 0 186.56 169.63 30156 +1923 358 0.86 -5.14 -0.79 0 159.69 170.72 30169 +1923 359 3.53 -2.47 1.88 0 190.08 125.33 30186 +1923 360 4.33 -1.67 2.68 0 200.11 125.26 30208 +1923 361 -1.49 -7.49 -3.14 0.2 136.51 140.5 30235 +1923 362 -5.11 -11.11 -6.76 0.49 106.5 143.25 30267 +1923 363 -7.22 -13.22 -8.87 0.27 91.8 144.93 30303 +1923 364 -7.22 -13.22 -8.87 0 91.8 178.05 30343 +1923 365 -3.08 -9.08 -4.73 0.16 122.54 145.13 30388 +1924 1 -8.41 -14.41 -10.06 0 84.31 180.18 30438 +1924 2 -4.66 -10.66 -6.31 0.08 109.89 146.83 30492 +1924 3 -3.79 -9.79 -5.44 0.24 116.71 148.01 30551 +1924 4 -2.58 -8.58 -4.23 0.37 126.79 149.45 30614 +1924 5 -5.74 -11.74 -7.39 0 101.91 184.58 30681 +1924 6 -1.21 -7.21 -2.86 0 139.11 183.83 30752 +1924 7 -3.54 -9.54 -5.19 0.26 118.73 151.96 30828 +1924 8 -1.31 -7.31 -2.96 0 138.18 186.74 30907 +1924 9 -5.62 -11.62 -7.27 0.01 102.78 154.31 30991 +1924 10 -3.56 -9.56 -5.21 0 118.57 189.92 31079 +1924 11 1.94 -4.06 0.29 0 171.44 188.21 31171 +1924 12 5.34 -0.66 3.69 0.04 213.41 151.76 31266 +1924 13 0.34 -5.66 -1.31 0.2 154.29 154.82 31366 +1924 14 0.62 -5.38 -1.03 0 157.18 191.73 31469 +1924 15 2.74 -3.26 1.09 0 180.61 191.59 31575 +1924 16 4.86 -1.14 3.21 0 206.99 190.85 31686 +1924 17 4.37 -1.63 2.72 0.23 200.62 155.39 31800 +1924 18 5.89 -0.11 4.24 0 220.97 192.1 31917 +1924 19 6.73 0.73 5.08 0 232.96 192.41 32038 +1924 20 4.54 -1.46 2.89 0 202.81 194.75 32161 +1924 21 2.1 -3.9 0.45 0 173.24 197.78 32289 +1924 22 1.84 -4.16 0.19 0 170.32 199.28 32419 +1924 23 0.39 -5.61 -1.26 0 154.8 201.6 32552 +1924 24 1.48 -4.52 -0.17 0 166.35 202.76 32688 +1924 25 0.08 -5.92 -1.57 0.1 151.65 164.14 32827 +1924 26 -1.14 -7.14 -2.79 0 139.77 207.55 32969 +1924 27 -3.68 -9.68 -5.33 0.01 117.59 168.06 33114 +1924 28 -4.16 -10.16 -5.81 0 113.76 212.77 33261 +1924 29 -7.64 -13.64 -9.29 0 89.1 216.18 33411 +1924 30 -4.02 -10.02 -5.67 0 114.87 217.05 33564 +1924 31 2.14 -3.86 0.49 0 173.69 216.01 33718 +1924 32 4.76 -1.24 3.11 0 205.68 176.74 33875 +1924 33 6.69 0.69 5.04 0 232.37 177.87 34035 +1924 34 5.88 -0.12 4.23 0.09 220.83 135.54 34196 +1924 35 6.46 0.46 4.81 0 229.04 182.38 34360 +1924 36 5.61 -0.39 3.96 0.15 217.09 139.18 34526 +1924 37 4.32 -1.68 2.67 0 199.98 188.97 34694 +1924 38 3.72 -2.28 2.07 0 192.42 192.14 34863 +1924 39 1.77 -4.23 0.12 0 169.54 196.07 35035 +1924 40 -0.89 -6.89 -2.54 0 142.14 200.24 35208 +1924 41 -0.89 -6.89 -2.54 0 142.14 202.89 35383 +1924 42 4.8 -1.2 3.15 0.01 206.2 151.31 35560 +1924 43 -0.58 -6.58 -2.23 2.37 145.12 199.34 35738 +1924 44 3.12 -2.88 1.47 0.03 185.11 198.96 35918 +1924 45 -1.54 -7.54 -3.19 0.37 136.05 203.88 36099 +1924 46 -0.41 -6.41 -2.06 0.11 146.78 205.53 36282 +1924 47 0.83 -5.17 -0.82 0 159.38 261.3 36466 +1924 48 -0.32 -6.32 -1.97 0 147.66 264.62 36652 +1924 49 -3.71 -9.71 -5.36 0 117.35 269.03 36838 +1924 50 0.55 -5.45 -1.1 0 156.45 269.11 37026 +1924 51 -1.08 -7.08 -2.73 0.03 140.33 215.33 37215 +1924 52 -1.5 -7.5 -3.15 0 136.42 275.86 37405 +1924 53 -4.39 -10.39 -6.04 0 111.97 280.15 37596 +1924 54 -0.32 -6.32 -1.97 0 147.66 280.53 37788 +1924 55 0.45 -5.55 -1.2 0.3 155.42 222.48 37981 +1924 56 1.25 -4.75 -0.4 0.75 163.85 223.77 38175 +1924 57 -0.04 -6.04 -1.69 0.35 150.44 227.29 38370 +1924 58 -2.42 -8.42 -4.07 0 128.18 293.32 38565 +1924 59 -2.35 -8.35 -4 0.39 128.79 233.19 38761 +1924 60 5.65 -0.35 4 0 217.64 292.86 38958 +1924 61 6.6 0.6 4.95 0.65 231.07 230.63 39156 +1924 62 5.21 -0.79 3.56 0 211.65 297.4 39355 +1924 63 3.79 -2.21 2.14 0 193.29 301.16 39553 +1924 64 7.84 1.84 6.19 0 249.65 298.94 39753 +1924 65 7.84 1.84 6.19 0 249.65 300.84 39953 +1924 66 9.84 3.84 8.19 0 282.34 299.87 40154 +1924 67 10.45 4.45 8.8 0 293.01 300.68 40355 +1924 68 8.32 2.32 6.67 0 257.19 305.34 40556 +1924 69 7.78 1.78 6.13 0 248.73 307.68 40758 +1924 70 5.13 -0.87 3.48 0 210.58 312.81 40960 +1924 71 8.18 2.18 6.53 0 254.97 279.89 41163 +1924 72 6.91 0.91 5.26 0 235.6 284.25 41366 +1924 73 8.91 2.91 7.26 0 266.71 284.42 41569 +1924 74 11.19 5.19 9.54 0 306.42 283.87 41772 +1924 75 9.83 3.83 8.18 0 282.17 288.59 41976 +1924 76 9.77 3.77 8.12 0 281.14 291.3 42179 +1924 77 10 4 8.35 0 285.11 293.55 42383 +1924 78 13.34 7.34 11.69 0.02 348.4 218.04 42587 +1924 79 8.98 2.98 7.33 0.36 267.86 225.29 42791 +1924 80 6.09 0.09 4.44 0 223.77 306.62 42996 +1924 81 2.84 -3.16 1.19 0 181.79 312.67 43200 +1924 82 3.48 -2.52 1.83 0.05 189.47 236.06 43404 +1924 83 4.12 -1.88 2.47 0 197.43 316.62 43608 +1924 84 4.83 -1.17 3.18 0 206.6 318.42 43812 +1924 85 4.13 -1.87 2.48 0 197.56 321.72 44016 +1924 86 2.21 -3.79 0.56 0.6 174.49 244.57 44220 +1924 87 0.99 -5.01 -0.66 0.2 161.07 247.33 44424 +1924 88 4.13 -1.87 2.48 0 197.56 329.12 44627 +1924 89 3.55 -2.45 1.9 0 190.33 332.06 44831 +1924 90 1.65 -4.35 0 0.75 168.21 252.26 45034 +1924 91 5.41 -0.59 3.76 0 214.36 334.68 45237 +1924 92 2.94 -3.06 1.29 0.05 182.97 254.77 45439 +1924 93 4.66 -1.34 3.01 0.32 204.37 255.06 45642 +1924 94 9.85 3.85 8.2 0 282.51 335.17 45843 +1924 95 12.58 6.58 10.93 0.02 333.03 249.38 46045 +1924 96 9.75 3.75 8.1 0 280.79 339.6 46246 +1924 97 9.98 3.98 8.33 0.05 284.76 255.96 46446 +1924 98 10.72 4.72 9.07 0 297.85 342.01 46647 +1924 99 10.68 4.68 9.03 0 297.12 344.09 46846 +1924 100 12.6 6.6 10.95 0 333.43 342.5 47045 +1924 101 19.31 13.31 17.66 0.1 491.64 246.16 47243 +1924 102 18.43 12.43 16.78 0 467.81 332.56 47441 +1924 103 17.35 11.35 15.7 0 439.92 337.27 47638 +1924 104 18.47 12.47 16.82 0.08 468.88 251.99 47834 +1924 105 21.71 15.71 20.06 0.38 561.93 245.75 48030 +1924 106 15.49 9.49 13.84 0.4 395.2 260.31 48225 +1924 107 15.97 9.97 14.32 0.31 406.36 260.67 48419 +1924 108 13.06 7.06 11.41 0.07 342.67 266.91 48612 +1924 109 10.78 4.78 9.13 0.58 298.93 271.43 48804 +1924 110 11.27 5.27 9.62 0 307.9 362.43 48995 +1924 111 10.78 4.78 9.13 0 298.93 364.9 49185 +1924 112 10.62 4.62 8.97 0 296.05 366.72 49374 +1924 113 9.99 3.99 8.34 0.9 284.93 276.9 49561 +1924 114 8.74 2.74 7.09 0 263.94 372.82 49748 +1924 115 11.47 5.47 9.82 0 311.63 369.44 49933 +1924 116 11.47 5.47 9.82 0.05 311.63 278 50117 +1924 117 10.92 4.92 9.27 1.61 301.47 279.78 50300 +1924 118 9.51 3.51 7.86 0.04 276.71 282.68 50481 +1924 119 8.89 2.89 7.24 0 266.38 379.16 50661 +1924 120 7.36 1.36 5.71 0.25 242.31 287.09 50840 +1924 121 20.79 14.79 19.14 0 534.04 352.47 51016 +1924 122 23.68 17.68 22.03 0.52 625.84 257.23 51191 +1924 123 19.83 13.83 18.18 0.03 506.2 268.35 51365 +1924 124 23.79 17.79 22.14 1.44 629.58 258.39 51536 +1924 125 25.97 19.97 24.32 2.06 707.77 252.07 51706 +1924 126 24.7 18.7 23.05 0.39 661.28 256.95 51874 +1924 127 24.8 18.8 23.15 0.26 664.85 257.26 52039 +1924 128 20.35 14.35 18.7 0 521.12 360.89 52203 +1924 129 22.52 16.52 20.87 1.02 587.51 265.47 52365 +1924 130 20.34 14.34 18.69 1.75 520.83 271.89 52524 +1924 131 17 11 15.35 0.23 431.19 280.14 52681 +1924 132 17 11 15.35 0.02 431.19 280.75 52836 +1924 133 15.54 9.54 13.89 0 396.35 378.94 52989 +1924 134 12.51 6.51 10.86 0.84 331.65 290.06 53138 +1924 135 14.61 8.61 12.96 0.21 375.44 287 53286 +1924 136 17.87 11.87 16.22 0.76 453.17 280.93 53430 +1924 137 21.21 15.21 19.56 0 546.63 364.43 53572 +1924 138 20.29 14.29 18.64 0 519.38 368.22 53711 +1924 139 16.5 10.5 14.85 0.03 418.98 285.34 53848 +1924 140 17.24 11.24 15.59 0.64 437.16 284.15 53981 +1924 141 13.96 7.96 12.31 0 361.38 387.81 54111 +1924 142 18.85 12.85 17.2 0 479.06 374.99 54238 +1924 143 16.96 10.96 15.31 0.64 430.2 285.85 54362 +1924 144 13.3 7.3 11.65 0.07 347.58 293.15 54483 +1924 145 13.82 7.82 12.17 0.69 358.42 292.62 54600 +1924 146 15.37 9.37 13.72 0.19 392.46 290.05 54714 +1924 147 13.61 7.61 11.96 0 354.01 391.51 54824 +1924 148 18.51 12.51 16.86 0 469.94 378.74 54931 +1924 149 21.12 15.12 19.47 0 543.91 370.35 55034 +1924 150 18.47 12.47 16.82 0.06 468.88 284.63 55134 +1924 151 20.28 14.28 18.63 0.34 519.09 280.51 55229 +1924 152 24.78 18.78 23.13 0.62 664.13 267.43 55321 +1924 153 20.9 14.9 19.25 0.66 537.31 279.15 55409 +1924 154 14.39 8.39 12.74 0.18 370.63 293.85 55492 +1924 155 15.59 9.59 13.94 0.29 397.51 291.72 55572 +1924 156 19.73 13.73 18.08 0.79 503.37 282.78 55648 +1924 157 16 10 14.35 0.55 407.06 291.28 55719 +1924 158 21.29 15.29 19.64 0 549.05 371.95 55786 +1924 159 22.6 16.6 20.95 1.14 590.08 275.43 55849 +1924 160 21.95 15.95 20.3 0.37 569.41 277.44 55908 +1924 161 21.16 15.16 19.51 0 545.11 372.9 55962 +1924 162 21.55 15.55 19.9 0 557 371.54 56011 +1924 163 20.14 14.14 18.49 0 515.05 376.76 56056 +1924 164 18.58 12.58 16.93 1.53 471.8 286.42 56097 +1924 165 17.72 11.72 16.07 0 449.31 384.61 56133 +1924 166 19.21 13.21 17.56 0.09 488.88 285.05 56165 +1924 167 20 14 18.35 0 511.04 377.4 56192 +1924 168 22.38 16.38 20.73 0 583.02 368.85 56214 +1924 169 19.92 13.92 18.27 0.29 508.76 283.32 56231 +1924 170 23.76 17.76 22.11 0.13 628.56 272.47 56244 +1924 171 21.9 15.9 20.25 0.03 567.85 278.06 56252 +1924 172 20.23 14.23 18.58 0.19 517.65 282.56 56256 +1924 173 18.82 12.82 17.17 0.51 478.25 286.04 56255 +1924 174 22.8 16.8 21.15 0 596.57 367.16 56249 +1924 175 22.91 16.91 21.26 0.08 600.17 275.02 56238 +1924 176 24.51 18.51 22.86 0.57 654.55 269.99 56223 +1924 177 19.76 13.76 18.11 0.01 504.22 283.56 56203 +1924 178 19.64 13.64 17.99 0.11 500.84 283.88 56179 +1924 179 18.75 12.75 17.1 0 476.36 381.27 56150 +1924 180 21.33 15.33 19.68 1.01 550.27 279.29 56116 +1924 181 22.44 16.44 20.79 1.23 584.94 276.11 56078 +1924 182 25.28 19.28 23.63 1.97 682.18 267.05 56035 +1924 183 23.72 17.72 22.07 0 627.2 362.68 55987 +1924 184 19.86 13.86 18.21 0.01 507.05 282.74 55935 +1924 185 17.06 11.06 15.41 0 432.68 385.58 55879 +1924 186 17.82 11.82 16.17 0 451.88 383.1 55818 +1924 187 22.56 16.56 20.91 0 588.79 366.69 55753 +1924 188 24.45 18.45 22.8 0.01 652.44 268.99 55684 +1924 189 22.03 16.03 20.38 0.75 571.92 276.21 55611 +1924 190 19.7 13.7 18.05 0.07 502.53 282.13 55533 +1924 191 23.56 17.56 21.91 0 621.78 361.62 55451 +1924 192 21.84 15.84 20.19 0 565.97 368.07 55366 +1924 193 21.12 15.12 19.47 0 543.91 370.44 55276 +1924 194 26.14 20.14 24.49 0 714.2 349.45 55182 +1924 195 23.08 17.08 21.43 0 605.76 362.52 55085 +1924 196 22.56 16.56 20.91 0 588.79 364.17 54984 +1924 197 19.89 13.89 18.24 0.02 507.9 280 54879 +1924 198 23.07 17.07 21.42 0 605.43 361.3 54770 +1924 199 20.85 14.85 19.2 0.07 535.82 276.95 54658 +1924 200 25.54 19.54 23.89 0.41 691.73 262.52 54542 +1924 201 23.52 17.52 21.87 1.55 620.43 268.71 54423 +1924 202 22.66 16.66 21.01 0 592.02 361.15 54301 +1924 203 22.28 16.28 20.63 0 579.83 362.12 54176 +1924 204 22.67 16.67 21.02 0 592.35 360.12 54047 +1924 205 24.44 18.44 22.79 0 652.09 352.41 53915 +1924 206 23.22 17.22 21.57 0.02 610.39 267.67 53780 +1924 207 24.37 18.37 22.72 0.43 649.63 263.64 53643 +1924 208 19.14 13.14 17.49 0.06 486.96 277.59 53502 +1924 209 19.77 13.77 18.12 0.05 504.5 275.58 53359 +1924 210 15.18 9.18 13.53 0 388.14 379.98 53213 +1924 211 18.55 12.55 16.9 0 471 369.88 53064 +1924 212 23.07 17.07 21.42 0 605.43 353.42 52913 +1924 213 22.4 16.4 20.75 0.42 583.66 266.44 52760 +1924 214 22.07 16.07 20.42 0 573.18 355.75 52604 +1924 215 24.39 18.39 22.74 0.05 650.34 259.46 52445 +1924 216 24.78 18.78 23.13 0 664.13 343.3 52285 +1924 217 25.47 19.47 23.82 0 689.15 339.44 52122 +1924 218 24.25 18.25 22.6 0.11 645.44 257.92 51958 +1924 219 24.77 18.77 23.12 0 663.78 340.7 51791 +1924 220 23.55 17.55 21.9 0.95 621.44 258.6 51622 +1924 221 21.58 15.58 19.93 1.04 557.92 263.41 51451 +1924 222 22.4 16.4 20.75 0 583.66 347.21 51279 +1924 223 21.74 15.74 20.09 0.01 562.86 261.37 51105 +1924 224 18.55 12.55 16.9 0 471 357.82 50929 +1924 225 19.73 13.73 18.08 0 503.37 353.06 50751 +1924 226 19.47 13.47 17.82 0.45 496.08 264.54 50572 +1924 227 18.11 12.11 16.46 0 459.4 355.5 50392 +1924 228 15.27 9.27 13.62 0 390.18 361.77 50210 +1924 229 19.2 13.2 17.55 0 488.61 349.81 50026 +1924 230 19.99 13.99 18.34 0 510.75 346.09 49842 +1924 231 20.47 14.47 18.82 0 524.62 343.08 49656 +1924 232 19.13 13.13 17.48 0 486.69 345.92 49469 +1924 233 19.46 13.46 17.81 0 495.8 343.5 49280 +1924 234 19.06 13.06 17.41 0.33 484.77 257.46 49091 +1924 235 22.71 16.71 21.06 0 593.64 329.79 48900 +1924 236 21.13 15.13 19.48 0.19 544.21 250.41 48709 +1924 237 18.23 12.23 16.58 0 462.54 341.1 48516 +1924 238 17.57 11.57 15.92 0.7 445.49 255.92 48323 +1924 239 15.09 9.09 13.44 1.14 386.11 259.41 48128 +1924 240 13.39 7.39 11.74 0.29 349.43 260.85 47933 +1924 241 15.05 9.05 13.4 2.08 385.21 256.81 47737 +1924 242 17.95 11.95 16.3 0 455.24 333.42 47541 +1924 243 17.95 11.95 16.3 0.01 455.24 248.66 47343 +1924 244 16.81 10.81 15.16 0 426.52 332.68 47145 +1924 245 19.41 13.41 17.76 0.2 494.41 242.85 46947 +1924 246 19.52 13.52 17.87 0.01 497.48 241.15 46747 +1924 247 24.18 18.18 22.53 0 643.01 304.26 46547 +1924 248 23.13 17.13 21.48 0.45 607.41 229.67 46347 +1924 249 19.84 13.84 18.19 0.01 506.48 236.1 46146 +1924 250 23.12 17.12 21.47 0.87 607.08 226.8 45945 +1924 251 19.06 13.06 17.41 0.02 484.77 234.75 45743 +1924 252 15.04 9.04 13.39 0 384.99 320.74 45541 +1924 253 15.67 9.67 14.02 0 399.35 317.2 45339 +1924 254 17.44 11.44 15.79 0 442.19 310.87 45136 +1924 255 18.88 12.88 17.23 0.01 479.87 228.68 44933 +1924 256 17.12 11.12 15.47 0.78 434.17 230.35 44730 +1924 257 19.35 13.35 17.7 0 492.75 299.27 44527 +1924 258 15.44 9.44 13.79 0 394.06 306.44 44323 +1924 259 17.34 11.34 15.69 0 439.67 299.68 44119 +1924 260 21.22 15.22 19.57 0.27 546.93 215.2 43915 +1924 261 24.15 18.15 22.5 0 641.97 275.14 43711 +1924 262 25.8 19.8 24.15 1.02 701.39 200.19 43507 +1924 263 27.65 21.65 26 0.54 773.49 192.97 43303 +1924 264 21.08 15.08 19.43 0.31 542.7 208.35 43099 +1924 265 18.03 12.03 16.38 0 457.31 283.53 42894 +1924 266 14.9 8.9 13.25 0 381.86 287.92 42690 +1924 267 16.95 10.95 15.3 0 429.96 280.93 42486 +1924 268 15.52 9.52 13.87 0.24 395.89 211.07 42282 +1924 269 13.27 7.27 11.62 0.08 346.96 212.38 42078 +1924 270 15.74 9.74 14.09 0 400.98 275.84 41875 +1924 271 20.25 14.25 18.6 0.01 518.22 197.1 41671 +1924 272 22.81 16.81 21.16 0.28 596.9 189.74 41468 +1924 273 21.65 15.65 20 0 560.08 253.95 41265 +1924 274 16.08 10.08 14.43 0 408.95 264.65 41062 +1924 275 16.7 10.7 15.05 0 423.83 260.65 40860 +1924 276 14.45 8.45 12.8 0.01 371.94 196.74 40658 +1924 277 13.15 7.15 11.5 0.01 344.5 196.43 40456 +1924 278 14.3 8.3 12.65 0 368.68 257.07 40255 +1924 279 12.63 6.63 10.98 0.02 334.03 192.78 40054 +1924 280 10.89 4.89 9.24 0 300.92 256.96 39854 +1924 281 10.16 4.16 8.51 0 287.9 255.21 39654 +1924 282 14.58 8.58 12.93 0 374.78 245.71 39455 +1924 283 13.83 7.83 12.18 0 358.63 244.17 39256 +1924 284 10.54 4.54 8.89 0.67 294.62 184.51 39058 +1924 285 9.44 3.44 7.79 0 275.52 244.75 38861 +1924 286 13.96 7.96 12.31 0 361.38 235.58 38664 +1924 287 14.36 8.36 12.71 0 369.98 232.01 38468 +1924 288 11.03 5.03 9.38 0 303.48 234.15 38273 +1924 289 12.48 6.48 10.83 0 331.05 229.51 38079 +1924 290 11.12 5.12 9.47 0 305.13 228.51 37885 +1924 291 9.74 3.74 8.09 0.41 280.62 170.64 37693 +1924 292 11.13 5.13 9.48 0 305.31 223.09 37501 +1924 293 14.66 8.66 13.01 0 376.54 215.31 37311 +1924 294 16.24 10.24 14.59 0 412.74 209.87 37121 +1924 295 14.43 8.43 12.78 0 371.5 210.03 36933 +1924 296 17.98 11.98 16.33 0 456.02 201.47 36745 +1924 297 16.07 10.07 14.42 0 408.71 202.2 36560 +1924 298 15.06 9.06 13.41 0.19 385.44 150.96 36375 +1924 299 15.64 9.64 13.99 0 398.66 197.64 36191 +1924 300 13.78 7.78 12.13 0 357.57 197.81 36009 +1924 301 14.52 8.52 12.87 0 373.46 194.27 35829 +1924 302 13.9 7.9 12.25 0 360.11 192.59 35650 +1924 303 12.32 6.32 10.67 0 327.91 192.13 35472 +1924 304 13.26 7.26 11.61 0.39 346.76 141.37 35296 +1924 305 2.07 -3.93 0.42 0 172.9 196.31 35122 +1924 306 5.48 -0.52 3.83 0 215.31 191.56 34950 +1924 307 1.04 -4.96 -0.61 0 161.6 192.06 34779 +1924 308 4.3 -1.7 2.65 0 199.72 187.28 34610 +1924 309 6.78 0.78 5.13 0 233.69 183 34444 +1924 310 3.46 -2.54 1.81 0 189.23 183.03 34279 +1924 311 2.95 -3.05 1.3 0 183.09 181.15 34116 +1924 312 3.79 -2.21 2.14 0 193.29 177.92 33956 +1924 313 2.25 -3.75 0.6 0 174.94 176.75 33797 +1924 314 1.42 -4.58 -0.23 0 165.69 175.24 33641 +1924 315 3.22 -2.78 1.57 0 186.32 171.59 33488 +1924 316 15.24 9.24 13.59 0 389.5 158.06 33337 +1924 317 15.63 9.63 13.98 0 398.43 155.42 33188 +1924 318 13.14 7.14 11.49 0 344.3 156.26 33042 +1924 319 9.41 3.41 7.76 0 275.02 158.42 32899 +1924 320 7.5 1.5 5.85 0 244.43 158.19 32758 +1924 321 6.15 0.15 4.5 0 224.62 157.11 32620 +1924 322 2.72 -3.28 1.07 0 180.38 157.5 32486 +1924 323 3.66 -2.34 2.01 0 191.68 155.31 32354 +1924 324 7.68 1.68 6.03 0 247.19 150.47 32225 +1924 325 6.97 0.97 5.32 0 236.48 149.29 32100 +1924 326 7.29 1.29 5.64 0 241.26 147.6 31977 +1924 327 6.67 0.67 5.02 0 232.08 146.22 31858 +1924 328 7.44 1.44 5.79 0 243.52 143.69 31743 +1924 329 8.21 2.21 6.56 0 255.44 141.61 31631 +1924 330 11.4 5.4 9.75 0 310.32 137.44 31522 +1924 331 10.75 4.75 9.1 0 298.39 136.75 31417 +1924 332 7.56 1.56 5.91 0 245.35 137.73 31316 +1924 333 5.08 -0.92 3.43 0 209.91 138.33 31218 +1924 334 3.81 -2.19 2.16 0 193.54 137.98 31125 +1924 335 1.07 -4.93 -0.58 0 161.92 138.22 31035 +1924 336 3.85 -2.15 2.2 0 194.04 135.7 30949 +1924 337 2.96 -3.04 1.31 0 183.21 134.52 30867 +1924 338 5.22 -0.78 3.57 0 211.79 132.29 30790 +1924 339 4.08 -1.92 2.43 0 196.93 132.17 30716 +1924 340 -0.87 -6.87 -2.52 0 142.33 133.81 30647 +1924 341 -1.63 -7.63 -3.28 0 135.23 133.17 30582 +1924 342 -1.35 -7.35 -3 0 137.81 132.29 30521 +1924 343 4.05 -1.95 2.4 0 196.55 128.94 30465 +1924 344 7.22 1.22 5.57 0 240.2 125.87 30413 +1924 345 7.61 1.61 5.96 0 246.11 125.18 30366 +1924 346 6.21 0.21 4.56 0.12 225.47 94.17 30323 +1924 347 3.45 -2.55 1.8 0 189.1 126.56 30284 +1924 348 -0.27 -6.27 -1.92 0 148.15 127.94 30251 +1924 349 -1.29 -7.29 -2.94 0 138.37 127.96 30221 +1924 350 1.88 -4.12 0.23 0 170.77 126.27 30197 +1924 351 1.41 -4.59 -0.24 0 165.58 126.27 30177 +1924 352 0.21 -5.79 -1.44 0 152.96 126.7 30162 +1924 353 -0.63 -6.63 -2.28 0 144.63 126.98 30151 +1924 354 -3.08 -9.08 -4.73 0 122.54 127.84 30145 +1924 355 -1.07 -7.07 -2.72 0 140.43 127.11 30144 +1924 356 2.24 -3.76 0.59 0 174.83 125.71 30147 +1924 357 4.79 -1.21 3.14 0 206.07 124.43 30156 +1924 358 3.87 -2.13 2.22 0 194.29 125.03 30169 +1924 359 3.49 -2.51 1.84 0 189.59 125.35 30186 +1924 360 3.28 -2.72 1.63 0.08 187.04 94.37 30208 +1924 361 2.87 -3.13 1.22 0.45 182.14 94.78 30235 +1924 362 0.48 -5.52 -1.17 0 155.73 127.93 30267 +1924 363 7.48 1.48 5.83 0 244.13 124.66 30303 +1924 364 7.96 1.96 6.31 0 251.52 124.72 30343 +1924 365 4.89 -1.11 3.24 0 207.39 127.26 30388 +1925 1 2.18 -3.82 0.53 0 174.15 129.6 30438 +1925 2 2.33 -3.67 0.68 0 175.86 130.26 30492 +1925 3 -2.79 -8.79 -4.44 0 124.99 133.36 30551 +1925 4 -0.75 -6.75 -2.4 0 143.48 133.52 30614 +1925 5 -0.31 -6.31 -1.96 0 147.76 133.99 30681 +1925 6 3.62 -2.38 1.97 0 191.19 132.99 30752 +1925 7 4.65 -1.35 3 0 204.24 133.19 30828 +1925 8 4.58 -1.42 2.93 0 203.33 134.72 30907 +1925 9 2.21 -3.79 0.56 0 174.49 137.28 30991 +1925 10 1.88 -4.12 0.23 0 170.77 138.75 31079 +1925 11 2.46 -3.54 0.81 0 177.35 139.44 31171 +1925 12 2.11 -3.89 0.46 0 173.35 140.64 31266 +1925 13 5.95 -0.05 4.3 0 221.81 140.01 31366 +1925 14 4.75 -1.25 3.1 0 205.55 142.25 31469 +1925 15 5.52 -0.48 3.87 0 215.86 143.19 31575 +1925 16 7.76 1.76 6.11 0 248.42 142.88 31686 +1925 17 7.91 1.91 6.26 0 250.74 144.43 31800 +1925 18 4.37 -1.63 2.72 0 200.62 148.78 31917 +1925 19 0.53 -5.47 -1.12 0 156.25 152.84 32038 +1925 20 6.21 0.21 4.56 0 225.47 151.06 32161 +1925 21 5.75 -0.25 4.1 0 219.02 153.38 32289 +1925 22 8.83 2.83 7.18 0 265.4 152.73 32419 +1925 23 7.61 1.61 5.96 0 246.11 155.48 32552 +1925 24 8.93 2.93 7.28 0 267.04 156.42 32688 +1925 25 8.28 2.28 6.63 0 256.55 158.83 32827 +1925 26 3.18 -2.82 1.53 0 185.83 164.44 32969 +1925 27 1.76 -4.24 0.11 0 169.43 167.31 33114 +1925 28 0.82 -5.18 -0.83 0 159.27 170.05 33261 +1925 29 -1.38 -7.38 -3.03 0 137.53 173.54 33411 +1925 30 -1.81 -7.81 -3.46 0 133.59 176.01 33564 +1925 31 -0.34 -6.34 -1.99 0 147.46 177.71 33718 +1925 32 9.13 3.13 7.48 0 270.34 173.12 33875 +1925 33 9.76 3.76 8.11 0.05 280.97 131.32 34035 +1925 34 8.42 2.42 6.77 1.56 258.78 133.91 34196 +1925 35 8.55 2.55 6.9 0.94 260.86 135.41 34360 +1925 36 11.12 5.12 9.47 0.82 305.13 135.29 34526 +1925 37 11.55 5.55 9.9 0 313.13 182.26 34694 +1925 38 8.98 2.98 7.33 0 267.86 187.71 34863 +1925 39 8.26 2.26 6.61 0.39 256.23 143.24 35035 +1925 40 7.63 1.63 5.98 0.24 246.42 145.63 35208 +1925 41 6.24 0.24 4.59 0 225.9 198.01 35383 +1925 42 3.16 -2.84 1.51 0.02 185.59 152.23 35560 +1925 43 4.96 -1.04 3.31 0.04 208.32 153.24 35738 +1925 44 3.87 -2.13 2.22 0 194.29 207.74 35918 +1925 45 4.79 -1.21 3.14 0 206.07 209.65 36099 +1925 46 7.41 1.41 5.76 0 243.07 210 36282 +1925 47 4.59 -1.41 2.94 0 203.46 215.32 36466 +1925 48 3.56 -2.44 1.91 0 190.45 218.95 36652 +1925 49 3.51 -2.49 1.86 0 189.84 221.78 36838 +1925 50 8.6 2.6 6.95 0.16 261.67 164.82 37026 +1925 51 7.34 1.34 5.69 0.25 242.01 168.01 37215 +1925 52 9.21 3.21 7.56 0.14 271.67 168.61 37405 +1925 53 10.73 4.73 9.08 0.03 298.03 169.42 37596 +1925 54 8.46 2.46 6.81 0 259.42 231.31 37788 +1925 55 6.95 0.95 5.3 0.19 236.19 176.92 37981 +1925 56 4.36 -1.64 2.71 0.06 200.49 180.77 38175 +1925 57 7.02 1.02 5.37 0 237.22 241.38 38370 +1925 58 6.87 0.87 5.22 0.05 235.01 183.35 38565 +1925 59 13.19 7.19 11.54 0 345.32 239.02 38761 +1925 60 12.46 6.46 10.81 0.14 330.66 182.22 38958 +1925 61 9.39 3.39 7.74 0 274.68 250.05 39156 +1925 62 9.91 3.91 8.26 0 283.55 252.15 39355 +1925 63 10.56 4.56 8.91 0 294.97 254.26 39553 +1925 64 5.35 -0.65 3.7 0 213.54 263.25 39753 +1925 65 5.44 -0.56 3.79 0.08 214.77 199.55 39953 +1925 66 6.33 0.33 4.68 0 227.18 267.88 40154 +1925 67 4.69 -1.31 3.04 0 204.76 272.48 40355 +1925 68 6.25 0.25 4.6 0 226.04 273.76 40556 +1925 69 5.64 -0.36 3.99 0 217.5 277.05 40758 +1925 70 4.55 -1.45 2.9 0 202.94 281.02 40960 +1925 71 7.58 1.58 5.93 0.34 245.65 210.47 41163 +1925 72 2.55 -3.45 0.9 0.22 178.39 216.51 41366 +1925 73 5.78 -0.22 4.13 0.01 219.44 216.15 41569 +1925 74 3.54 -2.46 1.89 0 190.2 293.26 41772 +1925 75 5.26 -0.74 3.61 0 212.33 294.28 41976 +1925 76 6.33 0.33 4.68 0 227.18 295.75 42179 +1925 77 6.84 0.84 5.19 0.14 234.57 223.32 42383 +1925 78 6.44 0.44 4.79 0 228.76 300.91 42587 +1925 79 4.27 -1.73 2.62 0 199.34 306.06 42791 +1925 80 6.22 0.22 4.57 0 225.61 306.47 42996 +1925 81 9.18 3.18 7.53 0 271.17 305.2 43200 +1925 82 9.94 3.94 8.29 0 284.07 306.73 43404 +1925 83 9.79 3.79 8.14 0 281.48 309.44 43608 +1925 84 5.74 -0.26 4.09 0 218.88 317.39 43812 +1925 85 4.21 -1.79 2.56 0 198.57 321.63 44016 +1925 86 1.86 -4.14 0.21 0 170.54 326.41 44220 +1925 87 3.19 -2.81 1.54 0 185.95 327.71 44424 +1925 88 5.86 -0.14 4.21 0.4 220.55 245.36 44627 +1925 89 3.04 -2.96 1.39 0.76 184.16 249.44 44831 +1925 90 4.89 -1.11 3.24 0.34 207.39 249.75 45034 +1925 91 9.16 3.16 7.51 0 270.84 329.61 45237 +1925 92 9.69 3.69 8.04 0.04 279.77 248.28 45439 +1925 93 13.34 7.34 11.69 0 348.4 326.78 45642 +1925 94 12.74 6.74 11.09 0 336.22 330.08 45843 +1925 95 12.34 6.34 10.69 0.05 328.3 249.73 46045 +1925 96 11.23 5.23 9.58 0 307.16 337.1 46246 +1925 97 12.85 6.85 11.2 0 338.42 336.12 46446 +1925 98 13.99 7.99 12.34 0.01 362.02 251.81 46647 +1925 99 15.74 9.74 14.09 0.08 400.98 250.37 46846 +1925 100 14.53 8.53 12.88 0.07 373.68 253.87 47045 +1925 101 17.17 11.17 15.52 0 435.41 334.09 47243 +1925 102 18.89 12.89 17.24 0.25 480.14 248.45 47441 +1925 103 16.57 10.57 14.92 0.05 420.67 254.45 47638 +1925 104 16.33 10.33 14.68 0 414.89 341.66 47834 +1925 105 12.19 6.19 10.54 0 325.37 352.57 48030 +1925 106 9.22 3.22 7.57 0 271.84 359.52 48225 +1925 107 11.57 5.57 9.92 1.23 313.51 267.81 48419 +1925 108 9.67 3.67 8.02 1.64 279.43 271.67 48612 +1925 109 11.83 5.83 10.18 0 318.44 359.95 48804 +1925 110 11.33 5.33 9.68 0 309.02 362.32 48995 +1925 111 13.22 7.22 11.57 0.38 345.94 270.07 49185 +1925 112 18.06 12.06 16.41 0.65 458.09 262.28 49374 +1925 113 13.78 7.78 12.13 0.02 357.57 271.31 49561 +1925 114 13.66 7.66 12.01 0.12 355.05 272.62 49748 +1925 115 12.99 6.99 11.34 0.29 341.25 274.78 49933 +1925 116 14.75 8.75 13.1 0 378.52 363.66 50117 +1925 117 14.6 8.6 12.95 0.03 375.22 273.99 50300 +1925 118 13.81 7.81 12.16 0.02 358.21 276.33 50481 +1925 119 10.83 4.83 9.18 0.97 299.83 281.81 50661 +1925 120 11.4 5.4 9.75 0.11 310.32 281.88 50840 +1925 121 18.15 12.15 16.5 0 460.44 360.77 51016 +1925 122 13.78 7.78 12.13 0 357.57 373.2 51191 +1925 123 15.08 9.08 13.43 0 385.89 371.17 51365 +1925 124 15.83 9.83 14.18 0 403.08 370.37 51536 +1925 125 19.19 13.19 17.54 0 488.33 361.83 51706 +1925 126 20.96 14.96 19.31 0.42 539.11 267.74 51874 +1925 127 21.13 15.13 19.48 0 544.21 357.25 52039 +1925 128 21.31 15.31 19.66 0.18 549.66 268.19 52203 +1925 129 21.12 15.12 19.47 0.74 543.91 269.3 52365 +1925 130 20.02 14.02 18.37 1.05 511.61 272.69 52524 +1925 131 18.73 12.73 17.08 1.42 475.82 276.35 52681 +1925 132 16.76 10.76 15.11 0.25 425.29 281.25 52836 +1925 133 17.14 11.14 15.49 0.23 434.67 280.99 52989 +1925 134 19.54 13.54 17.89 1.69 498.04 276.08 53138 +1925 135 18.79 12.79 17.14 0.08 477.44 278.38 53286 +1925 136 15.2 9.2 13.55 0.35 388.59 286.39 53430 +1925 137 14.84 8.84 13.19 0 380.52 383.46 53572 +1925 138 15.59 9.59 13.94 0.04 397.51 286.63 53711 +1925 139 18.02 12.02 16.37 0.16 457.05 282.09 53848 +1925 140 21.11 15.11 19.46 0.08 543.61 274.89 53981 +1925 141 20.44 14.44 18.79 0.01 523.74 276.96 54111 +1925 142 16.11 10.11 14.46 0.05 409.66 287.2 54238 +1925 143 19.37 13.37 17.72 0 493.3 373.86 54362 +1925 144 18.14 12.14 16.49 0.12 460.18 283.63 54483 +1925 145 17.25 11.25 15.6 0.03 437.41 285.94 54600 +1925 146 15.87 9.87 14.22 1.76 404.01 289.08 54714 +1925 147 16.85 10.85 15.2 0 427.5 383.25 54824 +1925 148 16.62 10.62 14.97 0 421.88 384.27 54931 +1925 149 18.46 12.46 16.81 0 468.61 379.21 55034 +1925 150 19.16 13.16 17.51 0 487.51 377.34 55134 +1925 151 19.61 13.61 17.96 0 500 376.26 55229 +1925 152 19.88 13.88 18.23 0 507.62 375.47 55321 +1925 153 17.1 11.1 15.45 0.09 433.67 288.24 55409 +1925 154 19.51 13.51 17.86 0.16 497.2 282.94 55492 +1925 155 21.4 15.4 19.75 0.37 552.4 278.17 55572 +1925 156 20.48 14.48 18.83 0.75 524.91 280.87 55648 +1925 157 17.88 11.88 16.23 0 453.43 383.05 55719 +1925 158 22.2 16.2 20.55 0.72 577.29 276.41 55786 +1925 159 22.66 16.66 21.01 0.15 592.02 275.25 55849 +1925 160 25.97 19.97 24.32 0.01 707.77 264.68 55908 +1925 161 27.92 21.92 26.27 0.76 784.52 257.45 55962 +1925 162 24.71 18.71 23.06 0.02 661.64 269.07 56011 +1925 163 21.37 15.37 19.72 0 551.49 372.41 56056 +1925 164 19.43 13.43 17.78 0.12 494.97 284.38 56097 +1925 165 20.76 14.76 19.11 0 533.15 374.74 56133 +1925 166 19.28 13.28 17.63 1.16 490.81 284.88 56165 +1925 167 18.17 12.17 16.52 0 460.97 383.29 56192 +1925 168 19.67 13.67 18.02 0 501.68 378.59 56214 +1925 169 19.76 13.76 18.11 0 504.22 378.3 56231 +1925 170 21.76 15.76 20.11 0.68 563.48 278.41 56244 +1925 171 21.46 15.46 19.81 0.02 554.23 279.29 56252 +1925 172 21.08 15.08 19.43 0.7 542.7 280.32 56256 +1925 173 18.29 12.29 16.64 2.32 464.12 287.28 56255 +1925 174 20.78 14.78 19.13 0.42 533.75 281.05 56249 +1925 175 16.95 10.95 15.3 0.42 429.96 290.16 56238 +1925 176 14.94 8.94 13.29 0 382.75 392.23 56223 +1925 177 12.77 6.77 11.12 0.16 336.82 297.94 56203 +1925 178 14.2 8.2 12.55 0 366.52 393.98 56179 +1925 179 19.46 13.46 17.81 0.57 495.8 284.24 56150 +1925 180 14.82 8.82 13.17 0.29 380.08 294.17 56116 +1925 181 16.99 10.99 15.34 0.97 430.95 289.76 56078 +1925 182 16.32 10.32 14.67 0 414.65 388.07 56035 +1925 183 19.6 13.6 17.95 0.49 499.72 283.51 55987 +1925 184 17.18 11.18 15.53 0.13 435.66 288.99 55935 +1925 185 21.39 15.39 19.74 0.19 552.1 278.66 55879 +1925 186 16.23 10.23 14.58 0.98 412.51 290.72 55818 +1925 187 19.79 13.79 18.14 0 505.07 376.7 55753 +1925 188 24.12 18.12 22.47 0 640.93 360.07 55684 +1925 189 25.37 19.37 23.72 0 685.47 354.4 55611 +1925 190 24.89 18.89 23.24 0 668.07 356.19 55533 +1925 191 24.78 18.78 23.13 0 664.13 356.42 55451 +1925 192 26.86 20.86 25.21 0.52 741.97 259.83 55366 +1925 193 23.96 17.96 22.31 1.16 635.41 269.55 55276 +1925 194 29.07 23.07 27.42 0.07 832.99 250.83 55182 +1925 195 30.78 24.78 29.13 0 909.73 324.3 55085 +1925 196 30.81 24.81 29.16 0 911.12 323.74 54984 +1925 197 27.56 21.56 25.91 0.23 769.85 256.05 54879 +1925 198 26.23 20.23 24.58 0.41 717.62 260.65 54770 +1925 199 25.66 19.66 24.01 0.14 696.18 262.4 54658 +1925 200 28.16 22.16 26.51 0.03 794.43 252.9 54542 +1925 201 23.09 17.09 21.44 0.94 606.09 270.01 54423 +1925 202 23.29 17.29 21.64 0.25 612.72 269 54301 +1925 203 24.79 18.79 23.14 0 664.49 351.89 54176 +1925 204 22.52 16.52 20.87 0 587.51 360.7 54047 +1925 205 20.85 14.85 19.2 0 535.82 366.31 53915 +1925 206 18.35 12.35 16.7 0.12 465.7 280.42 53780 +1925 207 16.53 10.53 14.88 0 419.7 378.45 53643 +1925 208 18.33 12.33 16.68 0.03 465.17 279.46 53502 +1925 209 15.07 9.07 13.42 0 385.66 380.9 53359 +1925 210 15.69 9.69 14.04 0.38 399.82 284.02 53213 +1925 211 18.67 12.67 17.02 0 474.21 369.51 53064 +1925 212 22.97 16.97 21.32 0 602.13 353.81 52913 +1925 213 19.16 13.16 17.51 0 487.51 366.43 52760 +1925 214 18.83 12.83 17.18 0 478.52 366.7 52604 +1925 215 20.3 14.3 18.65 0 519.67 361.3 52445 +1925 216 21.57 15.57 19.92 0.01 557.61 266.92 52285 +1925 217 21.62 15.62 19.97 1.36 559.15 266.13 52122 +1925 218 23.21 17.21 21.56 0.1 610.06 261.06 51958 +1925 219 22.14 16.14 20.49 0.39 575.39 263.33 51791 +1925 220 22.73 16.73 21.08 0 594.29 347.99 51622 +1925 221 21.31 15.31 19.66 0.14 549.66 264.13 51451 +1925 222 23.49 17.49 21.84 0 619.42 343.05 51279 +1925 223 25.23 19.23 23.58 0 680.36 334.76 51105 +1925 224 25.18 19.18 23.53 0 678.54 333.96 50929 +1925 225 23.64 17.64 21.99 0 624.48 339.2 50751 +1925 226 28.72 22.72 27.07 0.18 817.98 236.3 50572 +1925 227 27.3 21.3 25.65 0 759.39 320.95 50392 +1925 228 23.25 17.25 21.6 0.54 611.39 252.89 50210 +1925 229 22.12 16.12 20.47 0 574.76 340.16 50026 +1925 230 19.3 13.3 17.65 0 491.36 348.23 49842 +1925 231 22.85 16.85 21.2 0 598.2 334.81 49656 +1925 232 24.53 18.53 22.88 0.02 655.26 245.23 49469 +1925 233 22.08 16.08 20.43 1.22 573.49 251.17 49280 +1925 234 18.07 12.07 16.42 0.67 458.35 259.6 49091 +1925 235 17.14 11.14 15.49 0.12 434.67 260.38 48900 +1925 236 20.03 14.03 18.38 0 511.9 337.42 48709 +1925 237 21.81 15.81 20.16 0 565.04 329.97 48516 +1925 238 21.94 15.94 20.29 0 569.1 327.88 48323 +1925 239 17.83 11.83 16.18 0.02 452.14 254.25 48128 +1925 240 22.39 16.39 20.74 0.62 583.34 242.34 47933 +1925 241 20.41 14.41 18.76 0.02 522.87 245.99 47737 +1925 242 21.09 15.09 19.44 0 543 324.11 47541 +1925 243 21.33 15.33 19.68 0 550.27 321.5 47343 +1925 244 20.42 14.42 18.77 0 523.16 322.6 47145 +1925 245 18.93 12.93 17.28 0 481.23 325.18 46947 +1925 246 19.52 13.52 17.87 0 497.48 321.54 46747 +1925 247 17.37 11.37 15.72 0 440.43 325.56 46547 +1925 248 18.61 12.61 16.96 0 472.61 320.33 46347 +1925 249 17.78 11.78 16.13 0.33 450.85 240.36 46146 +1925 250 17.13 11.13 15.48 0.13 434.42 240.14 45945 +1925 251 12.46 6.46 10.81 0.34 330.66 246.12 45743 +1925 252 11.34 5.34 9.69 1.04 309.2 245.97 45541 +1925 253 10.2 4.2 8.55 3.54 288.6 245.76 45339 +1925 254 13 7 11.35 1.22 341.45 240.42 45136 +1925 255 15.22 9.22 13.57 0.72 389.05 235.32 44933 +1925 256 13.91 7.91 12.26 0.15 360.32 235.63 44730 +1925 257 18.47 12.47 16.82 0.25 468.88 226.2 44527 +1925 258 18.9 12.9 17.25 0.02 480.41 223.62 44323 +1925 259 16.75 10.75 15.1 0.21 425.05 225.8 44119 +1925 260 16.89 10.89 15.24 0 428.48 298.37 43915 +1925 261 17.8 11.8 16.15 0.05 451.37 220.32 43711 +1925 262 18.03 12.03 16.38 0.03 457.31 218.14 43507 +1925 263 13.44 7.44 11.79 0.18 350.47 223.67 43303 +1925 264 13.32 7.32 11.67 0.05 347.99 221.88 43099 +1925 265 17.45 11.45 15.8 0 442.44 284.9 42894 +1925 266 15.27 9.27 13.62 0.28 390.18 215.39 42690 +1925 267 20.6 14.6 18.95 0.17 528.43 203.9 42486 +1925 268 20.78 14.78 19.13 0 533.75 268.89 42282 +1925 269 20.32 14.32 18.67 0.02 520.25 200.78 42078 +1925 270 20.02 14.02 18.37 0.72 511.61 199.46 41875 +1925 271 19.33 13.33 17.68 0 492.19 265.16 41671 +1925 272 16.6 10.6 14.95 0.12 421.4 201.55 41468 +1925 273 18.54 12.54 16.89 0.95 470.74 196.45 41265 +1925 274 13.37 7.37 11.72 0 349.02 269.7 41062 +1925 275 17.71 11.71 16.06 0 449.06 258.49 40860 +1925 276 15.61 9.61 13.96 0.46 397.97 195.12 40658 +1925 277 14.89 8.89 13.24 0 381.63 258.87 40456 +1925 278 12.74 6.74 11.09 0 336.22 259.69 40255 +1925 279 13.79 7.79 12.14 0 357.78 255.15 40054 +1925 280 17.33 11.33 15.68 0.07 439.42 184.41 39854 +1925 281 14.26 8.26 12.61 0 367.81 248.99 39654 +1925 282 16.41 10.41 14.76 0.05 416.81 181.77 39455 +1925 283 17.63 11.63 15.98 0 447.01 237.17 39256 +1925 284 18.36 12.36 16.71 0 465.96 232.7 39058 +1925 285 14.32 8.32 12.67 0.41 369.11 178.3 38861 +1925 286 20.93 14.93 19.28 0 538.21 221.67 38664 +1925 287 16.24 10.24 14.59 0 412.74 228.75 38468 +1925 288 15.56 9.56 13.91 0 396.81 227.23 38273 +1925 289 15.42 9.42 13.77 0.11 393.6 168.66 38079 +1925 290 8.34 2.34 6.69 0 257.5 231.86 37885 +1925 291 7.28 1.28 5.63 0 241.11 230.24 37693 +1925 292 12.66 6.66 11.01 0 334.62 221.02 37501 +1925 293 14.54 8.54 12.89 0.87 373.9 161.63 37311 +1925 294 13.56 7.56 11.91 0 352.96 214.14 37121 +1925 295 13.86 7.86 12.21 0.01 359.26 158.17 36933 +1925 296 12.85 6.85 11.2 0 338.42 209.77 36745 +1925 297 14.59 8.59 12.94 0 375 204.55 36560 +1925 298 11.7 5.7 10.05 0 315.97 205.99 36375 +1925 299 9.89 3.89 8.24 0 283.2 205.36 36191 +1925 300 9.07 3.07 7.42 0 269.35 203.58 36009 +1925 301 9.32 3.32 7.67 0.48 273.51 150.59 35829 +1925 302 9.52 3.52 7.87 0.01 276.88 148.46 35650 +1925 303 8.81 2.81 7.16 0 265.08 196.1 35472 +1925 304 7.56 1.56 5.91 0 245.35 194.83 35296 +1925 305 5.91 -0.09 4.26 1.05 221.25 145.13 35122 +1925 306 5.64 -0.36 3.99 0 217.5 191.44 34950 +1925 307 3.18 -2.82 1.53 2.59 185.83 143.03 34779 +1925 308 2 -4 0.35 0.8 172.11 141.61 34610 +1925 309 -0.6 -6.6 -2.25 0.15 144.92 179.68 34444 +1925 310 -0.33 -6.33 -1.98 0.68 147.56 179.79 34279 +1925 311 4.02 -1.98 2.37 0.01 196.17 175.88 34116 +1925 312 4.9 -1.1 3.25 0.47 207.52 173.02 33956 +1925 313 8.79 2.79 7.14 0.19 264.75 168.17 33797 +1925 314 6.99 0.99 5.34 0.17 236.78 128.57 33641 +1925 315 3.49 -2.51 1.84 0.41 189.59 128.56 33488 +1925 316 3 -3 1.35 0 183.68 169.52 33337 +1925 317 5.98 -0.02 4.33 0 222.23 165.28 33188 +1925 318 9.28 3.28 7.63 0 272.84 160.22 33042 +1925 319 9.47 3.47 7.82 1.54 276.03 118.77 32899 +1925 320 13.84 7.84 12.19 0.57 358.84 113.98 32758 +1925 321 15.85 9.85 14.2 0.85 403.54 110.56 32620 +1925 322 17.74 11.74 16.09 0.25 449.83 107.28 32486 +1925 323 11.73 5.73 10.08 0 316.53 148.87 32354 +1925 324 7.82 1.82 6.17 0.1 249.34 112.77 32225 +1925 325 4.06 -1.94 2.41 0.72 196.67 113.45 32100 +1925 326 4.06 -1.94 2.41 0 196.67 149.8 31977 +1925 327 9.89 3.89 8.24 0 283.2 143.65 31858 +1925 328 8.85 2.85 7.2 0 265.73 142.58 31743 +1925 329 9.32 3.32 7.67 0.61 273.51 105.54 31631 +1925 330 7.13 1.13 5.48 0 238.86 140.99 31522 +1925 331 7.56 1.56 5.91 2.15 245.35 104.52 31417 +1925 332 6.7 0.7 5.05 0 232.52 138.34 31316 +1925 333 9.49 3.49 7.84 0.45 276.37 101.37 31218 +1925 334 12.27 6.27 10.62 0.23 326.93 98.69 31125 +1925 335 5.9 -0.1 4.25 0 221.11 135.53 31035 +1925 336 4.13 -1.87 2.48 0 197.56 135.54 30949 +1925 337 3.9 -2.1 2.25 0.36 194.66 100.51 30867 +1925 338 7.19 1.19 5.54 0.03 239.76 98.25 30790 +1925 339 2.92 -3.08 1.27 0.07 182.73 99.6 30716 +1925 340 5.32 -0.68 3.67 1.25 213.14 98.03 30647 +1925 341 4.08 -1.92 2.43 0.06 196.93 97.89 30582 +1925 342 1.88 -4.12 0.23 0 170.77 130.9 30521 +1925 343 -2.21 -8.21 -3.86 0.22 130.02 142.86 30465 +1925 344 -4.99 -10.99 -6.64 0.33 107.4 143.81 30413 +1925 345 -2.51 -8.51 -4.16 0 127.4 175.52 30366 +1925 346 0.36 -5.64 -1.29 0 154.5 173.86 30323 +1925 347 1.86 -4.14 0.21 0 170.54 172.39 30284 +1925 348 0.08 -5.92 -1.57 0 151.65 172.87 30251 +1925 349 3.28 -2.72 1.63 0 187.04 170.6 30221 +1925 350 2.15 -3.85 0.5 0 173.81 170.57 30197 +1925 351 2.26 -3.74 0.61 0.01 175.06 138.56 30177 +1925 352 2.04 -3.96 0.39 0 172.56 169.79 30162 +1925 353 3.1 -2.9 1.45 0 184.88 125.3 30151 +1925 354 1.3 -4.7 -0.35 0.06 164.39 94.6 30145 +1925 355 -0.97 -6.97 -2.62 0.31 141.38 140.08 30144 +1925 356 0.2 -5.8 -1.45 0 152.86 171.38 30147 +1925 357 -2.25 -8.25 -3.9 0.02 129.67 140.53 30156 +1925 358 -1.85 -7.85 -3.5 0 133.23 172.36 30169 +1925 359 -0.09 -6.09 -1.74 0 149.94 171.77 30186 +1925 360 3.21 -2.79 1.56 0 186.2 170.15 30208 +1925 361 1.12 -4.88 -0.53 0 162.45 171.31 30235 +1925 362 4.23 -1.77 2.58 0 198.83 126.09 30267 +1925 363 3.24 -2.76 1.59 0 186.56 127.21 30303 +1925 364 2.29 -3.71 0.64 0 175.4 128.08 30343 +1925 365 4.34 -1.66 2.69 0 200.23 127.57 30388 +1926 1 -0.26 -6.26 -1.91 0 148.25 130.7 30438 +1926 2 -0.68 -6.68 -2.33 0.02 144.15 142.06 30492 +1926 3 -2.18 -8.18 -3.83 0 130.29 176.41 30551 +1926 4 -0.33 -6.33 -1.98 0.07 147.56 143.41 30614 +1926 5 -0.16 -6.16 -1.81 0 149.25 177.23 30681 +1926 6 -1.67 -7.67 -3.32 0.94 134.87 147.72 30752 +1926 7 -0.63 -6.63 -2.28 0.34 144.63 148.95 30828 +1926 8 0.14 -5.86 -1.51 0.21 152.26 149.69 30907 +1926 9 -0.78 -6.78 -2.43 1.22 143.19 154.59 30991 +1926 10 -0.07 -6.07 -1.72 0 150.14 190.12 31079 +1926 11 1.15 -4.85 -0.5 0.37 162.78 155.23 31171 +1926 12 -1.12 -7.12 -2.77 0.19 139.96 157.19 31266 +1926 13 1.23 -4.77 -0.42 0 163.64 192.98 31366 +1926 14 4.92 -1.08 3.27 0 207.79 191.62 31469 +1926 15 5.35 -0.65 3.7 0.04 213.54 156.1 31575 +1926 16 2.78 -3.22 1.13 0.23 181.08 157.7 31686 +1926 17 4.89 -1.11 3.24 0.43 207.39 157.23 31800 +1926 18 4.09 -1.91 2.44 0.04 197.05 158.33 31917 +1926 19 5.16 -0.84 3.51 0 210.98 195.99 32038 +1926 20 2.64 -3.36 0.99 0 179.44 198.61 32161 +1926 21 1.65 -4.35 0 0.12 168.21 161.81 32289 +1926 22 -0.38 -6.38 -2.03 0 147.07 203.38 32419 +1926 23 0.24 -5.76 -1.41 0.1 153.27 164.62 32552 +1926 24 2.5 -3.5 0.85 0 177.82 205.04 32688 +1926 25 -0.37 -6.37 -2.02 0.28 147.17 167.97 32827 +1926 26 2.45 -3.55 0.8 0.51 177.24 167.82 32969 +1926 27 -0.56 -6.56 -2.21 0.01 145.31 170.38 33114 +1926 28 2.67 -3.33 1.02 0 179.79 212.47 33261 +1926 29 4.08 -1.92 2.43 0 196.93 213.27 33411 +1926 30 5.42 -0.58 3.77 0 214.49 213.72 33564 +1926 31 8.6 2.6 6.95 0 261.67 212.25 33718 +1926 32 11.77 5.77 10.12 0 317.3 209.53 33875 +1926 33 11.97 5.97 10.32 0 321.12 172.74 34035 +1926 34 8.55 2.55 6.9 0 260.86 178.43 34196 +1926 35 8.31 2.31 6.66 0 257.03 180.77 34360 +1926 36 8.1 2.1 6.45 0 253.71 183.45 34526 +1926 37 5.83 -0.17 4.18 0 220.13 187.81 34694 +1926 38 8.8 2.8 7.15 0 264.91 187.89 34863 +1926 39 4.79 -1.21 3.14 0.29 206.07 145.47 35035 +1926 40 7.2 1.2 5.55 0.04 239.91 145.92 35208 +1926 41 10.12 4.12 8.47 0.01 287.2 145.68 35383 +1926 42 10.78 4.78 9.13 0.14 298.93 147 35560 +1926 43 4.88 -1.12 3.23 0 207.26 204.39 35738 +1926 44 4.28 -1.72 2.63 0 199.47 207.43 35918 +1926 45 4.94 -1.06 3.29 0.22 208.05 157.14 36099 +1926 46 7.16 1.16 5.51 0.09 239.31 157.68 36282 +1926 47 9.52 3.52 7.87 0.28 276.88 157.95 36466 +1926 48 9.55 3.55 7.9 0 277.38 213.33 36652 +1926 49 7.65 1.65 6 0.02 246.72 163.58 36838 +1926 50 5.1 -0.9 3.45 0 210.18 223.15 37026 +1926 51 4.81 -1.19 3.16 0.4 206.34 169.78 37215 +1926 52 6.83 0.83 5.18 0.12 234.42 170.51 37405 +1926 53 7.21 1.21 5.56 0 240.06 229.91 37596 +1926 54 10.7 4.7 9.05 0.02 297.48 171.48 37788 +1926 55 6.94 0.94 5.29 0 236.04 235.91 37981 +1926 56 6.77 0.77 5.12 0.22 233.54 179.07 38175 +1926 57 10.72 4.72 9.07 0.06 297.85 177.78 38370 +1926 58 10 4 8.35 0.2 285.11 180.64 38565 +1926 59 9.48 3.48 7.83 0.75 276.2 183.14 38761 +1926 60 7.1 1.1 5.45 0.07 238.41 187.35 38958 +1926 61 6.5 0.5 4.85 0.08 229.62 190.02 39156 +1926 62 9.71 3.71 8.06 0 280.11 252.41 39355 +1926 63 13.67 7.67 12.02 0 355.26 249.57 39553 +1926 64 13.82 7.82 12.17 0 358.42 252.15 39753 +1926 65 15.6 9.6 13.95 0 397.74 251.77 39953 +1926 66 16.93 10.93 15.28 0 429.47 251.78 40154 +1926 67 14.25 8.25 12.6 0 367.6 259.7 40355 +1926 68 15.86 9.86 14.21 0 403.78 259.48 40556 +1926 69 16.71 10.71 15.06 0.15 424.07 195.21 40758 +1926 70 13.97 7.97 12.32 0 361.6 268.3 40960 +1926 71 12.49 6.49 10.84 0 331.25 273.68 41163 +1926 72 15.84 9.84 14.19 1.16 403.31 202.75 41366 +1926 73 9.08 3.08 7.43 0.07 269.51 213.14 41569 +1926 74 5.68 -0.32 4.03 0 218.05 291.08 41772 +1926 75 4.74 -1.26 3.09 0 205.42 294.83 41976 +1926 76 5.85 -0.15 4.2 0 220.41 296.29 42179 +1926 77 6.88 0.88 5.23 0.42 235.16 223.28 42383 +1926 78 5.86 -0.14 4.21 0.28 220.55 226.19 42587 +1926 79 2.18 -3.82 0.53 0 174.15 308.08 42791 +1926 80 0.85 -5.15 -0.8 0 159.59 311.82 42996 +1926 81 -0.1 -6.1 -1.75 0 149.84 315.21 43200 +1926 82 2.21 -3.79 0.56 0 174.49 315.96 43404 +1926 83 4.81 -1.19 3.16 0 206.34 315.88 43608 +1926 84 4.82 -1.18 3.17 0 206.47 318.43 43812 +1926 85 4.94 -1.06 3.29 0.23 208.05 240.62 44016 +1926 86 -1.06 -7.06 -2.71 0.11 140.52 276.73 44220 +1926 87 -3.14 -9.14 -4.79 0.65 122.03 281.05 44424 +1926 88 0.5 -5.5 -1.15 0 155.94 363.78 44627 +1926 89 0.21 -5.79 -1.44 0 152.96 366.2 44831 +1926 90 -1.11 -7.11 -2.76 0.01 140.05 284.9 45034 +1926 91 8.83 2.83 7.18 0 265.4 360.07 45237 +1926 92 12.33 6.33 10.68 0.35 328.11 244.89 45439 +1926 93 12.46 6.46 10.81 0 330.66 328.48 45642 +1926 94 13.21 7.21 11.56 0.38 345.73 246.88 45843 +1926 95 15.98 9.98 14.33 0.17 406.59 243.98 46045 +1926 96 14.83 8.83 13.18 0.18 380.3 247.49 46246 +1926 97 11.26 5.26 9.61 0 307.72 339.1 46446 +1926 98 11.29 5.29 9.64 0 308.27 341 46647 +1926 99 15.53 9.53 13.88 0.02 396.12 250.74 46846 +1926 100 15.1 9.1 13.45 0.55 386.34 252.92 47045 +1926 101 14.91 8.91 13.26 0 382.08 339.55 47243 +1926 102 12.14 6.14 10.49 0 324.4 347.21 47441 +1926 103 12.79 6.79 11.14 0 337.22 347.77 47638 +1926 104 16.83 10.83 15.18 0.07 427.01 255.3 47834 +1926 105 16.36 10.36 14.71 0.16 415.61 257.5 48030 +1926 106 20.1 14.1 18.45 0.83 513.9 250.85 48225 +1926 107 19.16 13.16 17.51 0.39 487.51 254.2 48419 +1926 108 14.92 8.92 13.27 0 382.3 351.79 48612 +1926 109 10 4 8.35 0 285.11 363.29 48804 +1926 110 15.9 9.9 14.25 0 404.71 352.42 48995 +1926 111 15.3 9.3 13.65 0 390.86 355.41 49185 +1926 112 14.66 8.66 13.01 0 376.54 358.42 49374 +1926 113 11.74 5.74 10.09 0 316.72 365.97 49561 +1926 114 12.07 6.07 10.42 0 323.05 366.82 49748 +1926 115 14.56 8.56 12.91 0 374.34 362.89 49933 +1926 116 14.61 8.61 12.96 0 375.44 363.99 50117 +1926 117 14.52 8.52 12.87 0 373.46 365.5 50300 +1926 118 14.8 8.8 13.15 0.02 379.63 274.61 50481 +1926 119 12.74 6.74 11.09 0 336.22 371.95 50661 +1926 120 12.18 6.18 10.53 0 325.18 374.29 50840 +1926 121 17.68 11.68 16.03 0.01 448.29 271.59 51016 +1926 122 13.47 7.47 11.82 0.18 351.09 280.42 51191 +1926 123 15.97 9.97 14.32 0 406.36 368.94 51365 +1926 124 19.06 13.06 17.41 0.07 484.77 270.96 51536 +1926 125 21.57 15.57 19.92 0.01 557.61 265.41 51706 +1926 126 22.21 16.21 20.56 0 577.6 352.51 51874 +1926 127 19.75 13.75 18.1 0 503.94 361.89 52039 +1926 128 21.41 15.41 19.76 0 552.71 357.23 52203 +1926 129 17.25 11.25 15.6 0 437.41 371.25 52365 +1926 130 17.77 11.77 16.12 0.71 450.6 277.91 52524 +1926 131 17.31 11.31 15.66 0.58 438.92 279.49 52681 +1926 132 18.75 12.75 17.1 0 476.36 369.22 52836 +1926 133 21.4 15.4 19.75 0 552.4 361.09 52989 +1926 134 19.5 13.5 17.85 0 496.92 368.24 53138 +1926 135 21.75 15.75 20.1 0 563.17 361.18 53286 +1926 136 20.65 14.65 19 0 529.9 365.71 53430 +1926 137 15.58 9.58 13.93 0 397.27 381.59 53572 +1926 138 18.75 12.75 17.1 0 476.36 373.21 53711 +1926 139 18.57 12.57 16.92 0.31 471.54 280.84 53848 +1926 140 17.84 11.84 16.19 0.23 452.4 282.85 53981 +1926 141 17.84 11.84 16.19 1.02 452.4 283.17 54111 +1926 142 18.09 12.09 16.44 0.69 458.88 282.99 54238 +1926 143 20.08 14.08 18.43 1.45 513.33 278.64 54362 +1926 144 16.74 10.74 15.09 0.05 424.8 286.67 54483 +1926 145 14.43 8.43 12.78 0.23 371.5 291.53 54600 +1926 146 10.4 4.4 8.75 0 292.12 397.77 54714 +1926 147 11.13 5.13 9.48 1.87 305.31 297.63 54824 +1926 148 8.08 2.08 6.43 0.41 253.4 302.07 54931 +1926 149 7.32 1.32 5.67 0.12 241.71 303.23 55034 +1926 150 7.06 1.06 5.41 0.59 237.82 303.8 55134 +1926 151 7.67 1.67 6.02 0.67 247.03 303.38 55229 +1926 152 13.15 7.15 11.5 0.05 344.5 295.6 55321 +1926 153 16.09 10.09 14.44 1.19 409.18 290.34 55409 +1926 154 17.37 11.37 15.72 1.92 440.43 287.9 55492 +1926 155 19.97 13.97 18.32 1.54 510.18 281.93 55572 +1926 156 22.23 16.23 20.58 0.47 578.24 276.07 55648 +1926 157 17.52 11.52 15.87 0 444.22 384.11 55719 +1926 158 14.29 8.29 12.64 0 368.46 392.91 55786 +1926 159 16.46 10.46 14.81 0 418.01 387.54 55849 +1926 160 18.16 12.16 16.51 0.05 460.7 287.1 55908 +1926 161 15.99 9.99 14.34 0 406.83 389.08 55962 +1926 162 16.52 10.52 14.87 0 419.46 387.7 56011 +1926 163 19.99 13.99 18.34 0 510.75 377.27 56056 +1926 164 19.37 13.37 17.72 0.02 493.3 284.53 56097 +1926 165 21.27 15.27 19.62 0.31 548.44 279.69 56133 +1926 166 18.11 12.11 16.46 0 459.4 383.52 56165 +1926 167 20.82 14.82 19.17 0.01 534.93 280.92 56192 +1926 168 20.86 14.86 19.21 0.06 536.12 280.87 56214 +1926 169 18.11 12.11 16.46 0.52 459.4 287.67 56231 +1926 170 14.45 8.45 12.8 0.65 371.94 295.18 56244 +1926 171 18.45 12.45 16.8 0.5 468.34 286.93 56252 +1926 172 20.16 14.16 18.51 0 515.63 376.99 56256 +1926 173 23.93 17.93 22.28 0 634.38 362.62 56255 +1926 174 25.5 19.5 23.85 1.18 690.25 266.71 56249 +1926 175 20.48 14.48 18.83 1.18 524.91 281.82 56238 +1926 176 20.01 14.01 18.36 0.03 511.32 283 56223 +1926 177 18.49 12.49 16.84 0.38 469.41 286.63 56203 +1926 178 18.06 12.06 16.41 0.09 458.09 287.63 56179 +1926 179 21.28 15.28 19.63 0.13 548.75 279.52 56150 +1926 180 21.92 15.92 20.27 0 568.47 370.2 56116 +1926 181 23.38 17.38 21.73 0 615.73 364.4 56078 +1926 182 26.77 20.77 25.12 0.07 738.45 261.76 56035 +1926 183 26.77 20.77 25.12 0.14 738.45 261.63 55987 +1926 184 26.67 20.67 25.02 0.19 734.56 261.89 55935 +1926 185 21.53 15.53 19.88 0.14 556.38 278.27 55879 +1926 186 24.76 18.76 23.11 0 663.42 357.74 55818 +1926 187 24.82 18.82 23.17 0.2 665.56 267.97 55753 +1926 188 21.49 15.49 19.84 2.51 555.15 277.86 55684 +1926 189 17.47 11.47 15.82 1.24 442.95 287.62 55611 +1926 190 16.88 10.88 15.23 1.59 428.23 288.6 55533 +1926 191 14.78 8.78 13.13 2.71 379.19 292.57 55451 +1926 192 14.54 8.54 12.89 0 373.9 390.38 55366 +1926 193 19.62 13.62 17.97 0 500.28 375.6 55276 +1926 194 23.88 17.88 22.23 0 632.66 359.51 55182 +1926 195 22.8 16.8 21.15 0 596.57 363.63 55085 +1926 196 21.43 15.43 19.78 0.02 553.32 276.31 54984 +1926 197 21.05 15.05 19.4 0 541.8 369.33 54879 +1926 198 20.1 14.1 18.45 0.48 513.9 279.15 54770 +1926 199 18.17 12.17 16.52 1.76 460.97 283.51 54658 +1926 200 17.98 11.98 16.33 0.22 456.02 283.63 54542 +1926 201 16.06 10.06 14.41 0.2 408.48 287.33 54423 +1926 202 18.07 12.07 16.42 0 458.35 376.86 54301 +1926 203 18.68 12.68 17.03 0.05 474.48 280.87 54176 +1926 204 17.05 11.05 15.4 0.44 432.43 284.09 54047 +1926 205 20.89 14.89 19.24 1.59 537.02 274.63 53915 +1926 206 21.8 15.8 20.15 0.43 564.73 271.76 53780 +1926 207 20.6 14.6 18.95 0.63 528.43 274.47 53643 +1926 208 19.48 13.48 17.83 0.23 496.36 276.78 53502 +1926 209 25 19 23.35 0 672.02 347.55 53359 +1926 210 26.6 20.6 24.95 0 731.84 339.64 53213 +1926 211 27.88 21.88 26.23 0.54 782.88 249.44 53064 +1926 212 31.05 25.05 29.4 0 922.37 314.25 52913 +1926 213 29.49 23.49 27.84 0 851.31 322.58 52760 +1926 214 25.9 19.9 24.25 0 705.14 339.97 52604 +1926 215 28.31 22.31 26.66 0 800.68 327.6 52445 +1926 216 27.26 21.26 25.61 0.16 757.79 248.95 52285 +1926 217 26.76 20.76 25.11 1.11 738.06 250.13 52122 +1926 218 26.1 20.1 24.45 0.05 712.68 251.87 51958 +1926 219 29.06 23.06 27.41 0.82 832.56 240.12 51791 +1926 220 24.94 18.94 23.29 0.21 669.86 254.3 51622 +1926 221 25.82 19.82 24.17 1.98 702.14 250.69 51451 +1926 222 23.25 17.25 21.6 1.97 611.39 257.99 51279 +1926 223 22.59 16.59 20.94 0.48 589.76 259.04 51105 +1926 224 18.5 12.5 16.85 0.07 469.67 268.48 50929 +1926 225 15.62 9.62 13.97 0 398.2 364.64 50751 +1926 226 15.71 9.71 14.06 0 400.28 363.24 50572 +1926 227 15.22 9.22 13.57 0 389.05 363.14 50392 +1926 228 18.37 12.37 16.72 0.05 466.23 265.14 50210 +1926 229 12.2 6.2 10.55 1.77 325.57 275.45 50026 +1926 230 16.88 10.88 15.23 0.21 428.23 266.34 49842 +1926 231 16.16 10.16 14.51 0.05 410.84 266.61 49656 +1926 232 19.76 13.76 18.11 0.02 504.22 258 49469 +1926 233 16.01 10.01 14.36 0.1 407.3 264.77 49280 +1926 234 18.16 12.16 16.51 0 460.7 345.89 49091 +1926 235 18.26 12.26 16.61 0 463.33 344.1 48900 +1926 236 20.22 14.22 18.57 0.22 517.36 252.62 48709 +1926 237 20.07 14.07 18.42 0 513.04 335.66 48516 +1926 238 18.17 12.17 16.52 0.22 460.97 254.69 48323 +1926 239 19.88 13.88 18.23 0.39 507.62 249.81 48128 +1926 240 18.53 12.53 16.88 0.19 470.47 251.47 47933 +1926 241 18.53 12.53 16.88 0 470.47 333.57 47737 +1926 242 19.64 13.64 17.99 0 500.84 328.62 47541 +1926 243 18.86 12.86 17.21 0 479.33 329.03 47343 +1926 244 14.62 8.62 12.97 0.61 375.66 253.37 47145 +1926 245 18.69 12.69 17.04 0.05 474.75 244.39 46947 +1926 246 16.17 10.17 14.52 0 411.08 330.4 46747 +1926 247 17.72 11.72 16.07 0 449.31 324.65 46547 +1926 248 16.75 10.75 15.1 0.43 425.05 243.87 46347 +1926 249 14.96 8.96 13.31 0.2 383.2 245.42 46146 +1926 250 20.16 14.16 18.51 0 515.63 311.94 45945 +1926 251 21.36 15.36 19.71 0 551.18 306.2 45743 +1926 252 20.8 14.8 19.15 0 534.34 305.83 45541 +1926 253 20.47 14.47 18.82 0.24 524.62 228.56 45339 +1926 254 25.98 19.98 24.33 0 708.15 283.6 45136 +1926 255 26.03 20.03 24.38 0 710.03 281.29 44933 +1926 256 22.89 16.89 21.24 0.84 599.51 217.99 44730 +1926 257 23.97 17.97 22.32 0.12 635.75 213.66 44527 +1926 258 26.05 20.05 24.4 0 710.79 274.91 44323 +1926 259 23.99 17.99 22.34 0 636.44 280.27 44119 +1926 260 20.21 14.21 18.56 0.68 517.07 217.4 43915 +1926 261 19.65 13.65 18 0.03 501.12 216.76 43711 +1926 262 20.85 14.85 19.2 0 535.82 283.35 43507 +1926 263 29.22 23.22 27.57 0.02 839.5 187.86 43303 +1926 264 22.65 16.65 21 0 591.7 273.07 43099 +1926 265 19.2 13.2 17.55 0 488.61 280.62 42894 +1926 266 17.32 11.32 15.67 0.05 439.17 212.06 42690 +1926 267 19.56 13.56 17.91 1.4 498.6 205.99 42486 +1926 268 18.09 12.09 16.44 0.19 458.88 206.83 42282 +1926 269 15.24 9.24 13.59 0 389.5 279.47 42078 +1926 270 18.44 12.44 16.79 0.41 468.08 202.41 41875 +1926 271 17.3 11.3 15.65 0 438.67 269.92 41671 +1926 272 17.69 11.69 16.04 0.25 448.55 199.77 41468 +1926 273 12.47 6.47 10.82 1.15 330.86 205.43 41265 +1926 274 10.4 4.4 8.75 0.18 292.12 205.77 41062 +1926 275 6.21 0.21 4.56 0 225.47 276.78 40860 +1926 276 10.19 4.19 8.54 1.36 288.42 201.82 40658 +1926 277 6.21 0.21 4.56 0.31 225.47 203.44 40456 +1926 278 10.35 4.35 8.7 0.7 291.24 197.44 40255 +1926 279 10.63 4.63 8.98 0 296.23 260.01 40054 +1926 280 11.16 5.16 9.51 0.53 305.87 192.44 39854 +1926 281 15.32 9.32 13.67 0.02 391.32 185.34 39654 +1926 282 13.77 7.77 12.12 0.01 357.36 185.31 39455 +1926 283 14.24 8.24 12.59 0.47 367.38 182.62 39256 +1926 284 16.16 10.16 14.51 0.92 410.84 177.82 39058 +1926 285 14.72 8.72 13.07 0.59 377.86 177.79 38861 +1926 286 18.21 12.21 16.56 0.61 462.01 170.83 38664 +1926 287 19.05 13.05 17.4 0.76 484.5 167.36 38468 +1926 288 13.34 7.34 11.69 0.02 348.4 173.14 38273 +1926 289 10.73 4.73 9.08 0 298.03 231.9 38079 +1926 290 12.66 6.66 11.01 0 334.62 226.39 37885 +1926 291 18.18 12.18 16.53 0.19 461.23 160.77 37693 +1926 292 18.91 12.91 17.26 0 480.69 210.29 37501 +1926 293 17.3 11.3 15.65 0.08 438.67 158.09 37311 +1926 294 17.21 11.21 15.56 0 436.41 208.15 37121 +1926 295 15.31 9.31 13.66 0.8 391.09 156.48 36933 +1926 296 17.85 11.85 16.2 0.6 452.65 151.29 36745 +1926 297 18.44 12.44 16.79 1.05 468.08 148.48 36560 +1926 298 17.28 11.28 15.63 0.16 438.16 148.2 36375 +1926 299 13.66 7.66 12.01 0 355.05 200.61 36191 +1926 300 17.75 11.75 16.1 0.07 450.08 143.62 36009 +1926 301 17.32 11.32 15.67 0 439.17 189.82 35829 +1926 302 17.43 11.43 15.78 0 441.94 187.11 35650 +1926 303 14.47 8.47 12.82 0.46 372.37 141.94 35472 +1926 304 13.86 7.86 12.21 0.09 359.26 140.77 35296 +1926 305 9.48 3.48 7.83 0 276.2 190.19 35122 +1926 306 6.28 0.28 4.63 0 226.47 190.91 34950 +1926 307 11.84 5.84 10.19 0.93 318.63 137.14 34779 +1926 308 12.86 6.86 11.21 0 338.63 179.05 34610 +1926 309 18.44 12.44 16.79 0.48 468.08 126.48 34444 +1926 310 18.96 12.96 17.31 0.27 482.04 124.07 34279 +1926 311 18.2 12.2 16.55 0.03 461.75 123.49 34116 +1926 312 15.87 9.87 14.22 0 404.01 165.69 33956 +1926 313 15.68 9.68 14.03 0 399.59 163.92 33797 +1926 314 14.64 8.64 12.99 0.01 376.1 122.58 33641 +1926 315 16.25 10.25 14.6 0.18 412.98 119.09 33488 +1926 316 15.67 9.67 14.02 0 399.35 157.49 33337 +1926 317 13.28 7.28 11.63 0 347.17 158.38 33188 +1926 318 18.55 12.55 16.9 0 471 148.9 33042 +1926 319 18.06 12.06 16.41 0 458.09 148.07 32899 +1926 320 15.44 9.44 13.79 0 394.06 149.99 32758 +1926 321 13.37 7.37 11.72 0.65 349.02 112.85 32620 +1926 322 14.02 8.02 12.37 0.38 362.66 110.96 32486 +1926 323 14.85 8.85 13.2 0.11 380.74 109.04 32354 +1926 324 14.7 8.7 13.05 0.6 377.42 107.68 32225 +1926 325 17.02 11.02 15.37 0.19 431.69 104.2 32100 +1926 326 12.18 6.18 10.53 0 325.18 143.3 31977 +1926 327 6.63 0.63 4.98 0 231.5 146.24 31858 +1926 328 7.03 1.03 5.38 0 237.37 143.99 31743 +1926 329 7.17 1.17 5.52 0 239.46 142.4 31631 +1926 330 8.34 2.34 6.69 0 257.5 140.08 31522 +1926 331 13.77 7.77 12.12 0 357.36 133.76 31417 +1926 332 12.22 6.22 10.57 0 325.96 133.76 31316 +1926 333 13.14 7.14 11.49 0 344.3 131.78 31218 +1926 334 12.71 6.71 11.06 0 335.62 131.15 31125 +1926 335 -0.65 -6.65 -2.3 0 144.44 138.99 31035 +1926 336 1.98 -4.02 0.33 0.85 171.89 102.52 30949 +1926 337 -0.86 -6.86 -2.51 0.17 142.42 145.52 30867 +1926 338 -1.35 -7.35 -3 0 137.81 178.95 30790 +1926 339 4.27 -1.73 2.62 0 199.34 132.06 30716 +1926 340 2.11 -3.89 0.46 0.01 173.35 99.36 30647 +1926 341 4.16 -1.84 2.51 0.21 197.94 97.85 30582 +1926 342 1.03 -4.97 -0.62 0 161.49 131.29 30521 +1926 343 -1.28 -7.28 -2.93 0.01 138.46 141.93 30465 +1926 344 -4.42 -10.42 -6.07 0 111.74 174.82 30413 +1926 345 -1.02 -7.02 -2.67 0 140.9 173.26 30366 +1926 346 2.5 -3.5 0.85 0 177.82 127.64 30323 +1926 347 2.94 -3.06 1.29 1.07 182.97 95.12 30284 +1926 348 3.67 -2.33 2.02 0 191.8 126.09 30251 +1926 349 5.86 -0.14 4.21 0.06 220.55 93.34 30221 +1926 350 2.89 -3.11 1.24 0.01 182.38 94.33 30197 +1926 351 6.72 0.72 5.07 0.28 232.81 92.53 30177 +1926 352 6.9 0.9 5.25 0 235.45 123.16 30162 +1926 353 7.24 1.24 5.59 0 240.5 122.87 30151 +1926 354 9.47 3.47 7.82 0 276.03 121.24 30145 +1926 355 6.7 0.7 5.05 0 232.52 123.19 30144 +1926 356 9.95 3.95 8.3 0.02 284.24 90.67 30147 +1926 357 9.25 3.25 7.6 0 272.34 121.49 30156 +1926 358 10.41 4.41 8.76 0 292.3 120.66 30169 +1926 359 5.55 -0.45 3.9 0 216.27 124.19 30186 +1926 360 5.44 -0.56 3.79 0.36 214.77 93.47 30208 +1926 361 5.85 -0.15 4.2 1.41 220.41 93.53 30235 +1926 362 0.39 -5.61 -1.26 0.21 154.8 95.97 30267 +1926 363 -1.08 -7.08 -2.73 0.51 140.33 142.04 30303 +1926 364 -3.79 -9.79 -5.44 0 116.71 175.64 30343 +1926 365 -3.91 -9.91 -5.56 0 115.74 176.19 30388 +1927 1 -2.7 -8.7 -4.35 0 125.76 176.61 30438 +1927 2 -4.13 -10.13 -5.78 0 114 177.75 30492 +1927 3 -2.42 -8.42 -4.07 0.03 128.18 144.83 30551 +1927 4 -3.89 -9.89 -5.54 0 115.9 179.47 30614 +1927 5 -1.44 -7.44 -3.09 0 136.97 179.16 30681 +1927 6 0.44 -5.56 -1.21 0 155.32 179.11 30752 +1927 7 4.23 -1.77 2.58 0 198.83 177.32 30828 +1927 8 3.36 -2.64 1.71 1.81 188.01 144.9 30907 +1927 9 3.49 -2.51 1.84 0.28 189.59 145.21 30991 +1927 10 6.94 0.94 5.29 0.05 236.04 101.81 31079 +1927 11 4.72 -1.28 3.07 0 205.16 138.17 31171 +1927 12 4.46 -1.54 2.81 0.17 201.78 104.5 31266 +1927 13 8.03 2.03 6.38 0.62 252.61 103.89 31366 +1927 14 6.3 0.3 4.65 0.31 226.75 105.93 31469 +1927 15 8.8 2.8 7.15 0.13 264.91 105.6 31575 +1927 16 7.85 1.85 6.2 0.02 249.81 107.11 31686 +1927 17 7.71 1.71 6.06 0.19 247.65 108.44 31800 +1927 18 5.06 -0.94 3.41 0 209.65 148.34 31917 +1927 19 5.4 -0.6 3.75 0.08 214.22 112.53 32038 +1927 20 4.69 -1.31 3.04 0.01 204.76 114.07 32161 +1927 21 5.46 -0.54 3.81 0 215.04 153.58 32289 +1927 22 6.16 0.16 4.51 0 224.76 154.83 32419 +1927 23 8.12 2.12 6.47 0.09 254.02 116.3 32552 +1927 24 4.03 -1.97 2.38 0 196.29 160.1 32688 +1927 25 5.53 -0.47 3.88 0 215.99 160.97 32827 +1927 26 7.29 1.29 5.64 0 241.26 161.55 32969 +1927 27 6.62 0.62 4.97 0.04 231.36 123.06 33114 +1927 28 4.65 -1.35 3 0.46 204.24 125.79 33261 +1927 29 2.06 -3.94 0.41 0.02 172.79 128.81 33411 +1927 30 5.48 -0.52 3.83 0.43 215.31 128.81 33564 +1927 31 6.53 0.53 4.88 0 230.05 173.3 33718 +1927 32 2.37 -3.63 0.72 0.01 176.32 133.74 33875 +1927 33 7.11 1.11 5.46 0 238.56 177.53 34035 +1927 34 6.27 0.27 4.62 0 226.32 180.41 34196 +1927 35 6.98 0.98 5.33 0.02 236.63 136.46 34360 +1927 36 9.03 3.03 7.38 0.01 268.69 136.92 34526 +1927 37 5.94 -0.06 4.29 0 221.67 187.72 34694 +1927 38 1.25 -4.75 -0.4 0 163.85 193.76 34863 +1927 39 4.8 -1.2 3.15 0 206.2 193.96 35035 +1927 40 3.28 -2.72 1.63 0 187.04 197.69 35208 +1927 41 4.71 -1.29 3.06 0 205.02 199.26 35383 +1927 42 1.39 -4.61 -0.26 0.26 165.37 153.12 35560 +1927 43 0.59 -5.41 -1.06 0.11 156.87 155.53 35738 +1927 44 2.78 -3.22 1.13 0 181.08 208.54 35918 +1927 45 2.7 -3.3 1.05 0 180.14 211.23 36099 +1927 46 4.33 -1.67 2.68 0.31 200.11 159.53 36282 +1927 47 8.91 2.91 7.26 0.03 266.71 158.45 36466 +1927 48 5.23 -0.77 3.58 0 211.92 217.6 36652 +1927 49 2.65 -3.35 1 0 179.56 222.43 36838 +1927 50 4.06 -1.94 2.41 0 196.67 224.02 37026 +1927 51 3.21 -2.79 1.56 0 186.2 227.67 37215 +1927 52 1.44 -4.56 -0.21 0 165.91 231.82 37405 +1927 53 3.54 -2.46 1.89 0 190.2 233.24 37596 +1927 54 2.74 -3.26 1.09 0 180.61 236.64 37788 +1927 55 -0.23 -6.23 -1.88 0 148.55 241.74 37981 +1927 56 1.43 -4.57 -0.22 0 165.8 243.35 38175 +1927 57 1.69 -4.31 0.04 0 168.65 246.08 38370 +1927 58 -0.46 -6.46 -2.11 0 146.29 250.52 38565 +1927 59 3.77 -2.23 2.12 0 193.04 250.11 38761 +1927 60 9.95 3.95 8.3 0.06 284.24 184.83 38958 +1927 61 7.68 1.68 6.03 0 247.19 252.08 39156 +1927 62 7.5 1.5 5.85 0 244.43 255.07 39355 +1927 63 7.08 1.08 5.43 0 238.11 258.53 39553 +1927 64 12.67 6.67 11.02 0.1 334.82 190.51 39753 +1927 65 13.68 7.68 12.03 0.73 355.47 191.4 39953 +1927 66 10.63 4.63 8.98 0.14 296.23 196.93 40154 +1927 67 9.27 3.27 7.62 0.32 272.67 200.47 40355 +1927 68 13.1 7.1 11.45 0 343.48 264.47 40556 +1927 69 17.26 11.26 15.61 0 437.66 259.12 40758 +1927 70 18.63 12.63 16.98 0 473.14 258.76 40960 +1927 71 14.06 8.06 12.41 1.26 363.52 203.24 41163 +1927 72 10.74 4.74 9.09 0 298.21 279.2 41366 +1927 73 11.3 5.3 9.65 0.11 308.46 210.74 41569 +1927 74 11.62 5.62 9.97 0.03 314.45 212.39 41772 +1927 75 9.95 3.95 8.3 0 284.24 288.42 41976 +1927 76 6.93 0.93 5.28 0 235.89 295.04 42179 +1927 77 9.43 3.43 7.78 0.04 275.36 220.78 42383 +1927 78 6.49 0.49 4.84 0.88 229.48 225.64 42587 +1927 79 7.71 1.71 6.06 0 247.65 302.09 42791 +1927 80 9.35 3.35 7.7 0 274.01 302.39 42996 +1927 81 8.8 2.8 7.15 0.17 264.91 229.31 43200 +1927 82 5.72 -0.28 4.07 0.96 218.61 234.25 43404 +1927 83 6.94 0.94 5.29 0 236.04 313.37 43608 +1927 84 6.89 0.89 5.24 0 235.3 315.99 43812 +1927 85 9.34 3.34 7.69 0 273.84 315.14 44016 +1927 86 13.87 7.87 12.22 0 359.47 309.75 44220 +1927 87 12.48 6.48 10.83 0.08 331.05 236.16 44424 +1927 88 6.41 0.41 4.76 0.06 228.32 244.85 44627 +1927 89 10.23 4.23 8.58 0.62 289.12 242.49 44831 +1927 90 7.89 1.89 6.24 1.07 250.43 246.9 45034 +1927 91 11.68 5.68 10.03 1.42 315.59 244.11 45237 +1927 92 12.89 6.89 11.24 0.2 339.23 244.1 45439 +1927 93 11.72 5.72 10.07 0 316.34 329.84 45642 +1927 94 10.97 4.97 9.32 0 302.38 333.3 45843 +1927 95 9.81 3.81 8.16 0 281.82 337.38 46045 +1927 96 11.03 5.03 9.38 0 303.48 337.45 46246 +1927 97 11.28 5.28 9.63 0 308.09 339.06 46446 +1927 98 12.46 6.46 10.81 0 330.66 338.83 46647 +1927 99 13.33 7.33 11.68 0 348.2 339.11 46846 +1927 100 11.76 5.76 10.11 0.02 317.1 258.08 47045 +1927 101 12.98 6.98 11.33 1.29 341.05 257.75 47243 +1927 102 12.54 6.54 10.89 0.66 332.24 259.83 47441 +1927 103 13.46 7.46 11.81 0.32 350.88 259.8 47638 +1927 104 14.59 8.59 12.94 0 375 345.77 47834 +1927 105 16.02 10.02 14.37 0 407.53 344.18 48030 +1927 106 14.05 8.05 12.4 0.63 363.3 262.77 48225 +1927 107 13.63 7.63 11.98 0.16 354.42 264.7 48419 +1927 108 10.32 4.32 8.67 0 290.71 361.11 48612 +1927 109 9.07 3.07 7.42 0 269.35 364.85 48804 +1927 110 12.01 6.01 10.36 0 321.89 361.01 48995 +1927 111 14.3 8.3 12.65 0 368.68 357.74 49185 +1927 112 14.34 8.34 12.69 0 369.54 359.16 49374 +1927 113 14.65 8.65 13 0 376.32 359.78 49561 +1927 114 14.35 8.35 12.7 0.09 369.76 271.46 49748 +1927 115 13.01 7.01 11.36 0.32 341.66 274.75 49933 +1927 116 13.6 7.6 11.95 0 353.8 366.28 50117 +1927 117 11.26 5.26 9.61 0.05 307.72 279.29 50300 +1927 118 11.76 5.76 10.11 0 317.1 372.75 50481 +1927 119 12.2 6.2 10.55 0 325.57 373.07 50661 +1927 120 18.57 12.57 16.92 0 471.54 358.43 50840 +1927 121 19.6 13.6 17.95 1.18 499.72 267.28 51016 +1927 122 19.41 13.41 17.76 0.32 494.41 268.6 51191 +1927 123 13.48 7.48 11.83 0.03 351.3 281.18 51365 +1927 124 10.63 4.63 8.98 0 296.23 381.81 51536 +1927 125 18.36 12.36 16.71 0 465.96 364.36 51706 +1927 126 16.11 10.11 14.46 0 409.66 371.62 51874 +1927 127 17.48 11.48 15.83 0 443.2 368.77 52039 +1927 128 17.91 11.91 16.26 0 454.2 368.52 52203 +1927 129 15.56 9.56 13.91 0 396.81 375.77 52365 +1927 130 18.96 12.96 17.31 0 482.04 366.98 52524 +1927 131 17.56 11.56 15.91 0 445.23 371.94 52681 +1927 132 18.54 12.54 16.89 0.7 470.74 277.39 52836 +1927 133 18.13 12.13 16.48 0.24 459.92 278.84 52989 +1927 134 14.54 8.54 12.89 1.46 373.9 286.6 53138 +1927 135 17.11 11.11 15.46 0.14 433.92 282.1 53286 +1927 136 17.86 11.86 16.21 0 452.91 374.61 53430 +1927 137 17.8 11.8 16.15 0 451.37 375.48 53572 +1927 138 17.02 11.02 15.37 0 431.69 378.32 53711 +1927 139 15.18 9.18 13.53 0.06 388.14 287.93 53848 +1927 140 18.54 12.54 16.89 1.11 470.74 281.27 53981 +1927 141 18.24 12.24 16.59 0 462.8 376.37 54111 +1927 142 16.09 10.09 14.44 0.01 409.18 287.24 54238 +1927 143 15.46 9.46 13.81 0.1 394.52 288.88 54362 +1927 144 16.23 10.23 14.58 0 412.51 383.62 54483 +1927 145 15.07 9.07 13.42 0 385.66 387.12 54600 +1927 146 15.73 9.73 14.08 0 400.75 385.8 54714 +1927 147 16.81 10.81 15.16 0 426.52 383.36 54824 +1927 148 12.09 6.09 10.44 0 323.43 395.26 54931 +1927 149 12.75 6.75 11.1 0 336.42 394.16 55034 +1927 150 18.34 12.34 16.69 0.06 465.43 284.93 55134 +1927 151 23.39 17.39 21.74 0.6 616.06 271.78 55229 +1927 152 22.84 16.84 21.19 0.13 597.88 273.51 55321 +1927 153 22.42 16.42 20.77 0.89 584.3 274.92 55409 +1927 154 17.94 11.94 16.29 2.21 454.98 286.64 55492 +1927 155 19.03 13.03 17.38 0.19 483.95 284.25 55572 +1927 156 17.93 11.93 16.28 0 454.72 382.73 55648 +1927 157 17.96 11.96 16.31 0 455.5 382.81 55719 +1927 158 23.26 17.26 21.61 0 611.72 364.37 55786 +1927 159 23.29 17.29 21.64 0.32 612.72 273.36 55849 +1927 160 22.52 16.52 20.87 0 587.51 367.73 55908 +1927 161 25.44 19.44 23.79 0 688.04 355.43 55962 +1927 162 25.69 19.69 24.04 0.76 697.29 265.75 56011 +1927 163 25.45 19.45 23.8 0 688.41 355.65 56056 +1927 164 23.48 17.48 21.83 0 619.08 364.26 56097 +1927 165 20.37 14.37 18.72 0 521.7 376.11 56133 +1927 166 24.3 18.3 22.65 0.42 647.19 270.73 56165 +1927 167 23.17 17.17 21.52 0 608.73 365.64 56192 +1927 168 26 20 24.35 0 708.9 353.32 56214 +1927 169 21.93 15.93 20.28 0 568.78 370.58 56231 +1927 170 26.08 20.08 24.43 0 711.92 352.95 56244 +1927 171 27.25 21.25 25.6 0.19 757.39 260.45 56252 +1927 172 25.65 19.65 24 0.07 695.8 266.26 56256 +1927 173 23.62 17.62 21.97 0 623.81 363.91 56255 +1927 174 23.76 17.76 22.11 0 628.56 363.25 56249 +1927 175 19.73 13.73 18.08 0 503.37 378.32 56238 +1927 176 21.96 15.96 20.31 0 569.72 370.35 56223 +1927 177 19.07 13.07 17.42 0 485.04 380.34 56203 +1927 178 19 13 17.35 0.21 483.13 285.44 56179 +1927 179 16.01 10.01 14.36 0.23 407.3 291.94 56150 +1927 180 13.74 7.74 12.09 0.36 356.73 296.13 56116 +1927 181 18.6 12.6 16.95 0.55 472.34 286.16 56078 +1927 182 21.93 15.93 20.28 0.06 568.78 277.47 56035 +1927 183 20.08 14.08 18.43 0 513.33 376.4 55987 +1927 184 25.58 19.58 23.93 0 693.21 354.37 55935 +1927 185 24.36 18.36 22.71 0.13 649.28 269.8 55879 +1927 186 27.27 21.27 25.62 0.54 758.19 259.42 55818 +1927 187 25.48 19.48 23.83 0.66 689.52 265.75 55753 +1927 188 24.61 18.61 22.96 0.69 658.09 268.47 55684 +1927 189 24.44 18.44 22.79 0 652.09 358.53 55611 +1927 190 26.19 20.19 24.54 0 716.1 350.22 55533 +1927 191 29.3 23.3 27.65 0 842.98 333.88 55451 +1927 192 25.16 19.16 23.51 0 677.81 354.44 55366 +1927 193 23.79 17.79 22.14 0 629.58 360.11 55276 +1927 194 25.21 19.21 23.56 0 679.63 353.74 55182 +1927 195 29.02 23.02 27.37 0.64 830.83 250.85 55085 +1927 196 26.82 20.82 25.17 0.51 740.41 259.15 54984 +1927 197 23.16 17.16 21.51 0 608.4 361.35 54879 +1927 198 20.47 14.47 18.82 0.15 524.62 278.21 54770 +1927 199 20.3 14.3 18.65 0 519.67 371.17 54658 +1927 200 23.11 17.11 21.46 0 606.75 360.4 54542 +1927 201 22.33 16.33 20.68 0.73 581.42 272.24 54423 +1927 202 26.34 20.34 24.69 0.02 721.82 258.98 54301 +1927 203 25.49 19.49 23.84 0 689.89 348.78 54176 +1927 204 24.81 18.81 23.16 0 665.2 351.31 54047 +1927 205 23.43 17.43 21.78 0 617.4 356.61 53915 +1927 206 24.01 18.01 22.36 0.37 637.13 265.26 53780 +1927 207 21.02 15.02 19.37 0.01 540.9 273.38 53643 +1927 208 19.34 13.34 17.69 0.97 492.47 277.11 53502 +1927 209 19.46 13.46 17.81 0.02 495.8 276.33 53359 +1927 210 23.2 17.2 21.55 0.71 609.73 265.84 53213 +1927 211 19.73 13.73 18.08 0 503.37 366.17 53064 +1927 212 22.73 16.73 21.08 0 594.29 354.74 52913 +1927 213 21.92 15.92 20.27 1.14 568.47 267.78 52760 +1927 214 20.51 14.51 18.86 0 525.79 361.27 52604 +1927 215 17.79 11.79 16.14 0.14 451.11 276.83 52445 +1927 216 18.59 12.59 16.94 0.45 472.07 274.29 52285 +1927 217 20.76 14.76 19.11 0 533.15 357.85 52122 +1927 218 20.5 14.5 18.85 0 525.5 357.91 51958 +1927 219 23.9 17.9 22.25 0 633.35 344.31 51791 +1927 220 24.45 18.45 22.8 0 652.44 341.14 51622 +1927 221 23.15 17.15 21.5 0.15 608.07 259.05 51451 +1927 222 22.35 16.35 20.7 0.27 582.06 260.55 51279 +1927 223 20.55 14.55 18.9 0 526.96 352.59 51105 +1927 224 22.37 16.37 20.72 0 582.7 345.16 50929 +1927 225 24.43 18.43 22.78 2.71 651.74 252.01 50751 +1927 226 24.29 18.29 22.64 0.58 646.84 251.62 50572 +1927 227 26.11 20.11 24.46 0.15 713.06 244.85 50392 +1927 228 23.66 17.66 22.01 0.54 625.16 251.69 50210 +1927 229 22.13 16.13 20.48 0 575.07 340.12 50026 +1927 230 22.41 16.41 20.76 0.04 583.98 253.4 49842 +1927 231 21.8 15.8 20.15 0.29 564.73 253.95 49656 +1927 232 25.26 19.26 23.61 0.61 681.45 242.96 49469 +1927 233 25.07 19.07 23.42 0 674.55 323.39 49280 +1927 234 24.84 18.84 23.19 0.1 666.28 242.24 49091 +1927 235 29.36 23.36 27.71 1.44 845.61 225.46 48900 +1927 236 26.96 20.96 25.31 0.08 745.9 233.28 48709 +1927 237 25.46 19.46 23.81 0.19 688.78 237.05 48516 +1927 238 22.24 16.24 20.59 0.4 578.56 245.13 48323 +1927 239 21.44 15.44 19.79 0.27 553.62 246.07 48128 +1927 240 19.78 13.78 18.13 0 504.78 331.64 47933 +1927 241 23.04 17.04 21.39 0.02 604.44 239.35 47737 +1927 242 23.22 17.22 21.57 0.12 610.39 237.59 47541 +1927 243 27.84 21.84 26.19 0.68 781.24 221.93 47343 +1927 244 25.53 19.53 23.88 0.28 691.36 228.24 47145 +1927 245 26.58 20.58 24.93 0 731.07 298.17 46947 +1927 246 25.3 19.3 23.65 0.02 682.91 226.24 46747 +1927 247 24.59 18.59 22.94 0 657.38 302.7 46547 +1927 248 23.78 17.78 22.13 0.01 629.24 227.91 46347 +1927 249 23.48 17.48 21.83 0.63 619.08 227.25 46146 +1927 250 26.02 20.02 24.37 0 709.66 291.4 45945 +1927 251 21.88 15.88 20.23 0 567.22 304.54 45743 +1927 252 19.2 13.2 17.55 0 488.61 310.48 45541 +1927 253 18.88 12.88 17.23 0 479.87 309.26 45339 +1927 254 19.81 13.81 18.16 0.12 505.63 228.43 45136 +1927 255 21.55 15.55 19.9 1.24 557 222.88 44933 +1927 256 18.29 12.29 16.64 0.49 464.12 228.16 44730 +1927 257 20.24 14.24 18.59 0.62 517.94 222.58 44527 +1927 258 19.65 13.65 18 0.76 501.12 222.1 44323 +1927 259 19.06 13.06 17.41 0.49 484.77 221.51 44119 +1927 260 15.51 9.51 13.86 2.7 395.66 226.08 43915 +1927 261 14.7 8.7 13.05 1.5 377.42 225.5 43711 +1927 262 15.14 9.14 13.49 0.69 387.24 223.03 43507 +1927 263 13.36 7.36 11.71 0.23 348.81 223.78 43303 +1927 264 16.68 10.68 15.03 0 423.34 289.02 43099 +1927 265 15.95 9.95 14.3 0.4 405.89 216.18 42894 +1927 266 11.17 5.17 9.52 0.42 306.05 220.93 42690 +1927 267 13.82 7.82 12.17 0.03 358.42 215.48 42486 +1927 268 15.52 9.52 13.87 0.03 395.89 211.07 42282 +1927 269 14.92 8.92 13.27 0.19 382.3 210.08 42078 +1927 270 17.33 11.33 15.68 0.26 439.42 204.33 41875 +1927 271 24.18 18.18 22.53 0 643.01 251.27 41671 +1927 272 25.44 19.44 23.79 0 688.04 244.48 41468 +1927 273 27.75 21.75 26.1 0.03 777.56 175.24 41265 +1927 274 21.83 15.83 20.18 0 565.66 250.9 41062 +1927 275 21.88 15.88 20.23 0.03 567.22 186.09 40860 +1927 276 22.66 16.66 21.01 0 592.02 243.34 40658 +1927 277 20.83 14.83 19.18 0.85 535.23 184.37 40456 +1927 278 13.04 7.04 11.39 0.48 342.26 194.41 40255 +1927 279 13.62 7.62 11.97 0 354.21 255.43 40054 +1927 280 12.5 6.5 10.85 0 331.45 254.58 39854 +1927 281 10.75 4.75 9.1 0 298.39 254.41 39654 +1927 282 10.47 4.47 8.82 0 293.37 252.02 39455 +1927 283 9.12 3.12 7.47 0.01 270.17 188.17 39256 +1927 284 9.79 3.79 8.14 0.01 281.48 185.25 39058 +1927 285 10.29 4.29 8.64 0 290.18 243.68 38861 +1927 286 11.89 5.89 10.24 0 319.59 238.72 38664 +1927 287 13.89 7.89 12.24 0 359.9 232.77 38468 +1927 288 14.08 8.08 12.43 0 363.94 229.7 38273 +1927 289 14.34 8.34 12.69 0 369.54 226.68 38079 +1927 290 14.6 8.6 12.95 0.62 375.22 167.57 37885 +1927 291 10.4 4.4 8.75 0 292.12 226.72 37693 +1927 292 6.41 0.41 4.76 0 228.32 228.36 37501 +1927 293 10.42 4.42 8.77 0.11 292.48 165.93 37311 +1927 294 14.93 8.93 13.28 0.02 382.52 159.03 37121 +1927 295 6.01 0.01 4.36 0 222.65 220.12 36933 +1927 296 8.36 2.36 6.71 0 257.82 215.2 36745 +1927 297 12.34 6.34 10.69 0.72 328.3 155.82 36560 +1927 298 11.36 5.36 9.71 0.13 309.57 154.81 36375 +1927 299 11.9 5.9 10.25 0.19 319.78 152.22 36191 +1927 300 10.49 4.49 8.84 0.11 293.72 151.51 36009 +1927 301 16.85 10.85 15.2 0 427.5 190.62 35829 +1927 302 16.99 10.99 15.34 0 430.95 187.86 35650 +1927 303 18.27 12.27 16.62 0 463.59 183.16 35472 +1927 304 13.43 7.43 11.78 0 350.26 188.27 35296 +1927 305 8.19 2.19 6.54 0.83 255.13 143.61 35122 +1927 306 8.28 2.28 6.63 0.01 256.55 141.84 34950 +1927 307 8.73 2.73 7.08 0 263.77 186.18 34779 +1927 308 6.29 0.29 4.64 0 226.61 185.74 34610 +1927 309 9.93 3.93 8.28 0 283.89 180.06 34444 +1927 310 8.5 2.5 6.85 0.05 260.06 134.27 34279 +1927 311 8.37 2.37 6.72 1 257.98 132.72 34116 +1927 312 9.13 3.13 7.48 0.31 270.34 130.21 33956 +1927 313 7.33 1.33 5.68 0.08 241.86 129.83 33797 +1927 314 8.8 2.8 7.15 0.04 264.91 127.4 33641 +1927 315 8.45 2.45 6.8 0.33 259.26 125.74 33488 +1927 316 8.06 2.06 6.41 0.13 253.08 124.36 33337 +1927 317 6.59 0.59 4.94 0.06 230.92 123.61 33188 +1927 318 4.98 -1.02 3.33 0 208.58 163.64 33042 +1927 319 7.91 1.91 6.26 0 250.74 159.72 32899 +1927 320 9.07 3.07 7.42 0 269.35 156.87 32758 +1927 321 11.47 5.47 9.82 0 311.63 152.51 32620 +1927 322 9.7 3.7 8.05 0 279.94 152.41 32486 +1927 323 7.23 1.23 5.58 0 240.35 152.86 32354 +1927 324 11.74 5.74 10.09 0.12 316.72 110.14 32225 +1927 325 8.16 2.16 6.51 0 254.65 148.37 32100 +1927 326 11.05 5.05 9.4 0.01 303.84 108.31 31977 +1927 327 8.06 2.06 6.41 0 253.08 145.17 31858 +1927 328 9.13 3.13 7.48 0 270.34 142.35 31743 +1927 329 12.27 6.27 10.62 0.24 326.93 103.5 31631 +1927 330 9 3 7.35 0.45 268.19 104.66 31522 +1927 331 4.86 -1.14 3.21 0.1 206.99 105.9 31417 +1927 332 4.39 -1.61 2.74 0 200.88 139.84 31316 +1927 333 5.34 -0.66 3.69 0.67 213.41 103.62 31218 +1927 334 6.62 0.62 4.97 0.09 231.36 102.17 31125 +1927 335 -3.5 -9.5 -5.15 0.16 119.06 148.08 31035 +1927 336 -5.21 -11.21 -6.86 0 105.76 182.68 30949 +1927 337 -2.37 -8.37 -4.02 0 128.62 180.16 30867 +1927 338 -4.47 -10.47 -6.12 0 111.35 180.02 30790 +1927 339 -2.45 -8.45 -4.1 0 127.92 178.63 30716 +1927 340 -2.43 -8.43 -4.08 0 128.09 177.98 30647 +1927 341 -2.53 -8.53 -4.18 0 127.22 177.17 30582 +1927 342 2.31 -3.69 0.66 0 175.63 174.13 30521 +1927 343 0.31 -5.69 -1.34 0 153.98 174.27 30465 +1927 344 -1.89 -7.89 -3.54 0 132.87 174.08 30413 +1927 345 -2.61 -8.61 -4.26 0.7 126.53 143.6 30366 +1927 346 -0.75 -6.75 -2.4 0.12 143.48 143.1 30323 +1927 347 3.01 -2.99 1.36 0 183.8 172.73 30284 +1927 348 2.66 -3.34 1.01 0 179.67 172.25 30251 +1927 349 6.28 0.28 4.63 0.2 226.47 138 30221 +1927 350 4.15 -1.85 2.5 0 197.81 169.45 30197 +1927 351 6.82 0.82 5.17 0 234.27 123.3 30177 +1927 352 4.51 -1.49 2.86 0 202.42 124.61 30162 +1927 353 4.02 -1.98 2.37 0 196.17 124.81 30151 +1927 354 -0.6 -6.6 -2.25 0 144.92 126.93 30145 +1927 355 -0.79 -6.79 -2.44 0 143.09 127.01 30144 +1927 356 -1.79 -7.79 -3.44 0 133.78 127.41 30147 +1927 357 0.25 -5.75 -1.4 0.04 153.37 95 30156 +1927 358 1.85 -4.15 0.2 1.17 170.43 94.53 30169 +1927 359 -2.79 -8.79 -4.44 0 124.99 128.04 30186 +1927 360 -1.65 -7.65 -3.3 0 135.05 128 30208 +1927 361 -4.52 -10.52 -6.17 0.02 110.96 140.7 30235 +1927 362 -4.03 -10.03 -5.68 0 114.79 173.28 30267 +1927 363 0.57 -5.43 -1.08 0 156.66 128.48 30303 +1927 364 -1.32 -7.32 -2.97 0 138.09 129.65 30343 +1927 365 -4.04 -10.04 -5.69 1.3 114.71 145.93 30388 +1928 1 -2.43 -8.43 -4.08 0 128.09 179.01 30438 +1928 2 3.41 -2.59 1.76 0 188.62 176.64 30492 +1928 3 5.07 -0.93 3.42 0 209.78 175.88 30551 +1928 4 5.62 -0.38 3.97 0 217.23 175.62 30614 +1928 5 0.14 -5.86 -1.51 0 152.26 179.02 30681 +1928 6 0.74 -5.26 -0.91 0 158.43 179.45 30752 +1928 7 -1.28 -7.28 -2.93 0 138.46 181 30828 +1928 8 0.65 -5.35 -1 0.03 157.49 147.28 30907 +1928 9 2.44 -3.56 0.79 0 177.12 181.43 30991 +1928 10 3.16 -2.84 1.51 0 185.59 181.81 31079 +1928 11 4.49 -1.51 2.84 0 202.16 181.33 31171 +1928 12 9.91 3.91 8.26 0 283.55 135.41 31266 +1928 13 8.27 2.27 6.62 0 256.39 138.34 31366 +1928 14 0.8 -5.2 -0.85 0 159.06 144.4 31469 +1928 15 -1.38 -7.38 -3.03 0 137.53 146.83 31575 +1928 16 -1.86 -7.86 -3.51 0 133.14 148.33 31686 +1928 17 1.6 -4.4 -0.05 0.34 167.66 111.34 31800 +1928 18 -1.95 -7.95 -3.6 0.04 132.33 155.47 31917 +1928 19 -0.02 -6.02 -1.67 0 150.64 194.42 32038 +1928 20 -0.78 -6.78 -2.43 0 143.19 196.21 32161 +1928 21 -2.2 -8.2 -3.85 0 130.11 198.69 32289 +1928 22 -1.23 -7.23 -2.88 0 138.93 199.88 32419 +1928 23 0.26 -5.74 -1.39 0 153.47 200.78 32552 +1928 24 0.87 -5.13 -0.78 0 159.8 161.92 32688 +1928 25 1.74 -4.26 0.09 0 169.21 163.35 32827 +1928 26 6.14 0.14 4.49 0 224.48 162.44 32969 +1928 27 5.88 -0.12 4.23 0 220.83 164.64 33114 +1928 28 7.05 1.05 5.4 0 237.67 165.94 33261 +1928 29 7.18 1.18 5.53 0 239.61 168.19 33411 +1928 30 6.66 0.66 5.01 0 231.94 170.83 33564 +1928 31 6.86 0.86 5.21 0 234.86 173.03 33718 +1928 32 8.95 2.95 7.3 0 267.37 173.29 33875 +1928 33 13.14 7.14 11.49 0 344.3 171.36 34035 +1928 34 11.84 5.84 10.19 0 318.63 175.03 34196 +1928 35 5.85 -0.15 4.2 0 220.41 182.88 34360 +1928 36 3.47 -2.53 1.82 0 189.35 187.14 34526 +1928 37 2.18 -3.82 0.53 0.25 174.15 142.82 34694 +1928 38 2.59 -3.41 0.94 0 178.86 192.91 34863 +1928 39 -0.49 -6.49 -2.14 0 145.99 197.38 35035 +1928 40 -2.02 -8.02 -3.67 0 131.71 200.82 35208 +1928 41 -2.48 -8.48 -4.13 0 127.66 203.7 35383 +1928 42 1.43 -4.57 -0.22 0.13 165.8 153.1 35560 +1928 43 -0.23 -6.23 -1.88 0 148.55 207.86 35738 +1928 44 -0.55 -6.55 -2.2 0.03 145.41 194.81 35918 +1928 45 4.26 -1.74 2.61 0 199.21 210.07 36099 +1928 46 2.09 -3.91 0.44 0.09 173.13 160.77 36282 +1928 47 -0.05 -6.05 -1.7 0 150.34 218.58 36466 +1928 48 -1.28 -7.28 -2.93 0 138.46 222.13 36652 +1928 49 -0.42 -6.42 -2.07 0 146.68 224.45 36838 +1928 50 2.97 -3.03 1.32 0 183.33 224.87 37026 +1928 51 7.22 1.22 5.57 1.92 240.2 168.1 37215 +1928 52 8.21 2.21 6.56 0.35 255.44 169.44 37405 +1928 53 8.93 2.93 7.28 0 267.04 228.06 37596 +1928 54 10.54 4.54 8.89 0.53 294.62 171.63 37788 +1928 55 9.41 3.41 7.76 0 275.02 233.19 37981 +1928 56 9.16 3.16 7.51 0 270.84 236.14 38175 +1928 57 10.93 4.93 9.28 0 301.65 236.77 38370 +1928 58 9.71 3.71 8.06 0 280.11 241.22 38565 +1928 59 8.66 2.66 7.01 0 262.64 245.17 38761 +1928 60 8.29 2.29 6.64 0 256.71 248.47 38958 +1928 61 6.66 0.66 5.01 0 231.94 253.19 39156 +1928 62 5.38 -0.62 3.73 0 213.95 257.29 39355 +1928 63 0.79 -5.21 -0.86 0 158.96 264.21 39553 +1928 64 6.25 0.25 4.6 0.56 226.04 196.75 39753 +1928 65 10.2 4.2 8.55 0.18 288.6 195.35 39953 +1928 66 9.53 3.53 7.88 0 277.05 264.07 40154 +1928 67 8.76 2.76 7.11 0.19 264.26 200.96 40355 +1928 68 8.28 2.28 6.63 0.3 256.55 203.56 40556 +1928 69 8.42 2.42 6.77 0 258.78 273.85 40758 +1928 70 6.97 0.97 5.32 0.74 236.48 208.83 40960 +1928 71 4.97 -1.03 3.32 0.69 208.45 212.65 41163 +1928 72 2.63 -3.37 0.98 0.21 179.33 216.46 41366 +1928 73 2.1 -3.9 0.45 0.38 173.24 218.84 41569 +1928 74 3.84 -2.16 2.19 0 193.91 292.98 41772 +1928 75 2.62 -3.38 0.97 0 179.21 296.88 41976 +1928 76 5.12 -0.88 3.47 0 210.45 297.09 42179 +1928 77 7.54 1.54 5.89 0 245.04 296.9 42383 +1928 78 10.9 4.9 9.25 0 301.11 294.83 42587 +1928 79 6.84 0.84 5.19 0 234.57 303.18 42791 +1928 80 4.66 -1.34 3.01 0 204.37 308.22 42996 +1928 81 8.12 2.12 6.47 0 254.02 306.67 43200 +1928 82 8.32 2.32 6.67 0 257.19 309.06 43404 +1928 83 10.33 4.33 8.68 0 290.89 308.61 43608 +1928 84 4.65 -1.35 3 0.28 204.24 238.97 43812 +1928 85 0.46 -5.54 -1.19 0.99 155.52 243.88 44016 +1928 86 4.09 -1.91 2.44 0.58 197.05 243.15 44220 +1928 87 5.05 -0.95 3.4 0 209.51 325.71 44424 +1928 88 1.36 -4.64 -0.29 0.3 165.04 248.89 44627 +1928 89 4.61 -1.39 2.96 0.02 203.72 248.18 44831 +1928 90 8.55 2.55 6.9 0 260.86 328.26 45034 +1928 91 16.31 10.31 14.66 0.09 414.42 237.01 45237 +1928 92 15.11 9.11 13.46 0 386.56 320.92 45439 +1928 93 16.74 10.74 15.09 1.21 424.8 239.49 45642 +1928 94 8.87 2.87 7.22 0 266.06 336.7 45843 +1928 95 7.58 1.58 5.93 0 245.65 340.73 46045 +1928 96 8.65 2.65 7 0 262.48 341.31 46246 +1928 97 7.73 1.73 6.08 0 247.95 344.73 46446 +1928 98 10.38 4.38 8.73 0 291.77 342.59 46647 +1928 99 9.79 3.79 8.14 0 281.48 345.59 46846 +1928 100 11.48 5.48 9.83 0 311.82 344.62 47045 +1928 101 12.42 6.42 10.77 0 329.87 344.77 47243 +1928 102 14.89 8.89 13.24 0 381.63 341.47 47441 +1928 103 17.64 11.64 15.99 0 447.27 336.5 47638 +1928 104 19.46 13.46 17.81 0 495.8 333.12 47834 +1928 105 19.66 13.66 18.01 0 501.4 334.25 48030 +1928 106 20.09 14.09 18.44 0.03 513.62 250.88 48225 +1928 107 18.16 12.16 16.51 0 460.7 341.81 48419 +1928 108 14.3 8.3 12.65 0 368.68 353.2 48612 +1928 109 17.26 11.26 15.61 1.43 437.66 260.65 48804 +1928 110 15.45 9.45 13.8 0 394.29 353.52 48995 +1928 111 17.15 11.15 15.5 0.16 434.92 263.04 49185 +1928 112 15.27 9.27 13.62 0.03 390.18 267.74 49374 +1928 113 10.58 4.58 8.93 0.73 295.33 276.11 49561 +1928 114 6.03 0.03 4.38 0.36 222.93 282.64 49748 +1928 115 6.17 0.17 4.52 0 224.9 378.13 49933 +1928 116 6.83 0.83 5.18 0 234.42 378.45 50117 +1928 117 12.84 6.84 11.19 0 338.22 369.22 50300 +1928 118 14.8 8.8 13.15 0 379.63 366.15 50481 +1928 119 11.36 5.36 9.71 0.48 309.57 281.05 50661 +1928 120 11.92 5.92 10.27 0 320.16 374.82 50840 +1928 121 14.84 8.84 13.19 0.02 380.52 277.15 51016 +1928 122 16.1 10.1 14.45 0 409.42 367.58 51191 +1928 123 17.55 11.55 15.9 1.14 444.98 273.51 51365 +1928 124 14.03 8.03 12.38 2.53 362.88 281.06 51536 +1928 125 12.79 6.79 11.14 1.37 337.22 283.86 51706 +1928 126 14.16 8.16 12.51 1.83 365.66 282.32 51874 +1928 127 13.79 7.79 12.14 0.87 357.78 283.63 52039 +1928 128 8.92 2.92 7.27 0.14 266.88 291.6 52203 +1928 129 8.36 2.36 6.71 0 257.82 390.61 52365 +1928 130 9.52 3.52 7.87 0 276.88 389.46 52524 +1928 131 7.97 1.97 6.32 0.63 251.67 294.66 52681 +1928 132 9.76 3.76 8.11 0 280.97 390.69 52836 +1928 133 9.27 3.27 7.62 0 272.67 392.28 52989 +1928 134 8.79 2.79 7.14 0 264.75 393.84 53138 +1928 135 9.85 3.85 8.2 0.01 282.51 294.52 53286 +1928 136 13.7 7.7 12.05 0 355.89 385.46 53430 +1928 137 15.18 9.18 13.53 0.39 388.14 286.96 53572 +1928 138 17.15 11.15 15.5 0.08 434.92 283.47 53711 +1928 139 18.91 12.91 17.26 0 480.69 373.4 53848 +1928 140 16.06 10.06 14.41 1 408.48 286.59 53981 +1928 141 14.76 8.76 13.11 0.15 378.75 289.42 54111 +1928 142 15.79 9.79 14.14 0.29 402.14 287.83 54238 +1928 143 13.84 7.84 12.19 0 358.84 389.15 54362 +1928 144 19.33 13.33 17.68 0.29 492.19 280.84 54483 +1928 145 18.09 12.09 16.44 0.71 458.88 284.09 54600 +1928 146 15.86 9.86 14.21 0.69 403.78 289.1 54714 +1928 147 17.16 11.16 15.51 0.05 435.17 286.78 54824 +1928 148 17.97 11.97 16.32 0.68 455.76 285.29 54931 +1928 149 16.16 10.16 14.51 0.02 410.84 289.38 55034 +1928 150 18.03 12.03 16.38 0.76 457.31 285.64 55134 +1928 151 21.4 15.4 19.75 0.1 552.4 277.54 55229 +1928 152 24.06 18.06 22.41 0.3 638.85 269.76 55321 +1928 153 27.84 21.84 26.19 0 781.24 342.13 55409 +1928 154 26.35 20.35 24.7 0.15 722.21 262.41 55492 +1928 155 21.64 15.64 19.99 0.01 559.77 277.5 55572 +1928 156 25.72 19.72 24.07 0.31 698.41 265.01 55648 +1928 157 20.48 14.48 18.83 0.07 524.91 280.99 55719 +1928 158 20.52 14.52 18.87 0.23 526.08 281.02 55786 +1928 159 15.99 9.99 14.34 0.04 406.83 291.62 55849 +1928 160 19.14 13.14 17.49 0.02 486.96 284.8 55908 +1928 161 18.96 12.96 17.31 0.1 482.04 285.28 55962 +1928 162 14.92 8.92 13.27 0.63 382.3 293.94 56011 +1928 163 15.64 9.64 13.99 0.8 398.66 292.72 56056 +1928 164 15.99 9.99 14.34 0 406.83 389.4 56097 +1928 165 13.45 7.45 11.8 0 350.68 395.83 56133 +1928 166 15.84 9.84 14.19 0.14 403.31 292.49 56165 +1928 167 15.68 9.68 14.03 0 399.59 390.35 56192 +1928 168 16.49 10.49 14.84 0.05 418.74 291.18 56214 +1928 169 18.76 12.76 17.11 0.8 476.63 286.16 56231 +1928 170 19.36 13.36 17.71 0.09 493.03 284.71 56244 +1928 171 19.83 13.83 18.18 0 506.2 378.12 56252 +1928 172 20.07 14.07 18.42 0.62 513.04 282.98 56256 +1928 173 22.82 16.82 21.17 1.76 597.22 275.37 56255 +1928 174 20.69 14.69 19.04 0.91 531.08 281.29 56249 +1928 175 17.95 11.95 16.3 0.94 455.24 287.97 56238 +1928 176 18.74 12.74 17.09 0.75 476.09 286.12 56223 +1928 177 20.39 14.39 18.74 1.38 522.29 281.95 56203 +1928 178 21.99 15.99 20.34 0 570.66 370.16 56179 +1928 179 18.69 12.69 17.04 0 474.75 381.46 56150 +1928 180 24.13 18.13 22.48 0 641.27 361.33 56116 +1928 181 22.42 16.42 20.77 1.1 584.3 276.17 56078 +1928 182 26.39 20.39 24.74 0.01 723.74 263.15 56035 +1928 183 21.45 15.45 19.8 0 553.93 371.56 55987 +1928 184 22.82 16.82 21.17 0.29 597.22 274.64 55935 +1928 185 20.82 14.82 19.17 0.41 534.93 280.2 55879 +1928 186 22.29 16.29 20.64 0.86 580.15 275.94 55818 +1928 187 19.59 13.59 17.94 0 499.44 377.36 55753 +1928 188 18.12 12.12 16.47 0 459.66 381.74 55684 +1928 189 20.24 14.24 18.59 0 517.94 374.73 55611 +1928 190 27.57 21.57 25.92 0.07 770.25 257.56 55533 +1928 191 29.09 23.09 27.44 0 833.86 335.06 55451 +1928 192 25.19 19.19 23.54 0 678.9 354.31 55366 +1928 193 24.79 18.79 23.14 0 664.49 355.83 55276 +1928 194 21.36 15.36 19.71 0.16 551.18 277.01 55182 +1928 195 17.4 11.4 15.75 0.69 441.18 286.46 55085 +1928 196 18.72 12.72 17.07 0 475.56 377.57 54984 +1928 197 19.83 13.83 18.18 0 506.2 373.53 54879 +1928 198 26.99 20.99 25.34 0 747.08 343.86 54770 +1928 199 28.2 22.2 26.55 0.63 796.1 253.02 54658 +1928 200 25.46 19.46 23.81 0 688.78 350.39 54542 +1928 201 28.88 22.88 27.23 0.12 824.81 249.68 54423 +1928 202 31.82 25.82 30.17 0.04 959.24 236.31 54301 +1928 203 26.23 20.23 24.58 0 717.62 345.35 54176 +1928 204 28.17 22.17 26.52 0 794.85 335.23 54047 +1928 205 30.25 24.25 28.6 0.02 885.33 242.45 53915 +1928 206 32.27 26.27 30.62 0 981.36 310.35 53780 +1928 207 30.73 24.73 29.08 0 907.4 319.32 53643 +1928 208 30.46 24.46 28.81 0 894.93 320.33 53502 +1928 209 30.96 24.96 29.31 0 918.14 316.77 53359 +1928 210 29.71 23.71 28.06 0 861.05 323.49 53213 +1928 211 31.69 25.69 30.04 0 952.93 311.04 53064 +1928 212 29.64 23.64 27.99 0 857.94 322.44 52913 +1928 213 27.79 21.79 26.14 0 779.19 331.58 52760 +1928 214 27.63 21.63 25.98 0.07 772.68 248.77 52604 +1928 215 25.94 19.94 24.29 0.15 706.64 254.36 52445 +1928 216 27.38 21.38 25.73 0 762.6 331.35 52285 +1928 217 27.79 21.79 26.14 0 779.19 328.47 52122 +1928 218 24.69 18.69 23.04 0.52 660.93 256.53 51958 +1928 219 23.27 17.27 21.62 0.01 612.06 260.12 51791 +1928 220 21.67 15.67 20.02 0.28 560.7 263.92 51622 +1928 221 23.02 17.02 21.37 0.33 603.78 259.42 51451 +1928 222 21.11 15.11 19.46 0.38 543.61 263.87 51279 +1928 223 21.82 15.82 20.17 0.75 565.35 261.15 51105 +1928 224 22.4 16.4 20.75 0.69 583.66 258.79 50929 +1928 225 24.09 18.09 22.44 0 639.89 337.41 50751 +1928 226 22.53 16.53 20.88 0 587.83 342.33 50572 +1928 227 19.49 13.49 17.84 0 496.64 351.38 50392 +1928 228 19.31 13.31 17.66 1.04 491.64 263.04 50210 +1928 229 21.82 15.82 20.17 0.08 565.35 255.92 50026 +1928 230 22.57 16.57 20.92 0.1 589.12 252.96 49842 +1928 231 23.83 17.83 22.18 0.8 630.95 248.3 49656 +1928 232 25.57 19.57 23.92 0 692.84 322.63 49469 +1928 233 24.19 18.19 22.54 0 643.35 326.97 49280 +1928 234 25.2 19.2 23.55 0 679.27 321.5 49091 +1928 235 26.91 20.91 25.26 0.4 743.94 234.45 48900 +1928 236 28.24 22.24 26.59 0.27 797.76 228.73 48709 +1928 237 28.9 22.9 27.25 1.16 825.67 225.13 48516 +1928 238 24.35 18.35 22.7 1.91 648.93 239.24 48323 +1928 239 21.59 15.59 19.94 0.05 558.23 245.69 48128 +1928 240 18.28 12.28 16.63 0.2 463.85 251.99 47933 +1928 241 18.02 12.02 16.37 0.44 457.05 251.23 47737 +1928 242 19.39 13.39 17.74 0.02 493.86 247.02 47541 +1928 243 20.36 14.36 18.71 0 521.41 324.59 47343 +1928 244 15.27 9.27 13.62 0.66 390.18 252.28 47145 +1928 245 18.02 12.02 16.37 0.77 457.05 245.76 46947 +1928 246 19.24 13.24 17.59 0.39 489.71 241.76 46747 +1928 247 18.36 12.36 16.71 2.04 465.96 242.21 46547 +1928 248 14.48 8.48 12.83 1.8 372.59 247.78 46347 +1928 249 17.03 11.03 15.38 0.07 431.94 241.79 46146 +1928 250 18.38 12.38 16.73 0 466.49 316.96 45945 +1928 251 21.9 15.9 20.25 0 567.85 304.47 45743 +1928 252 25.73 19.73 24.08 0.1 698.78 216.43 45541 +1928 253 25.84 19.84 24.19 0.94 702.89 214.61 45339 +1928 254 24.5 18.5 22.85 1.18 654.2 216.97 45136 +1928 255 21.11 15.11 19.46 1.22 543.61 223.9 44933 +1928 256 21.97 15.97 20.32 0.33 570.04 220.24 44730 +1928 257 22.67 16.67 21.02 0.34 592.35 216.98 44527 +1928 258 21.87 15.87 20.22 0.19 566.91 217.21 44323 +1928 259 16.79 10.79 15.14 0 426.03 300.98 44119 +1928 260 12.97 6.97 11.32 0 340.85 306.49 43915 +1928 261 14.61 8.61 12.96 0 375.44 300.85 43711 +1928 262 15.78 9.78 14.13 0.32 401.91 222.02 43507 +1928 263 18.6 12.6 16.95 0.26 472.34 215.25 43303 +1928 264 17.64 11.64 15.99 0.01 447.27 215.11 43099 +1928 265 15.6 9.6 13.95 0.7 397.74 216.74 42894 +1928 266 19.16 13.16 17.51 0 487.51 278.3 42690 +1928 267 17.96 11.96 16.31 0 455.5 278.61 42486 +1928 268 20.34 14.34 18.69 0 520.83 270.09 42282 +1928 269 18.06 12.06 16.41 0 458.09 273.37 42078 +1928 270 16.65 10.65 15 0 422.61 273.93 41875 +1928 271 20.34 14.34 18.69 0.43 520.83 196.93 41671 +1928 272 16.63 10.63 14.98 0.04 422.13 201.51 41468 +1928 273 14.7 8.7 13.05 0.01 377.42 202.5 41265 +1928 274 12.75 6.75 11.1 0 336.42 270.74 41062 +1928 275 16.13 10.13 14.48 0 410.13 261.81 40860 +1928 276 17.53 11.53 15.88 0 444.47 256.23 40658 +1928 277 12.17 6.17 10.52 0.5 324.99 197.61 40456 +1928 278 13.52 7.52 11.87 0.35 352.13 193.81 40255 +1928 279 15.97 9.97 14.32 0.1 406.36 188.4 40054 +1928 280 17.21 11.21 15.56 0.01 436.41 184.6 39854 +1928 281 14.25 8.25 12.6 0.02 367.6 186.75 39654 +1928 282 12.6 6.6 10.95 0 333.43 248.95 39455 +1928 283 15.74 9.74 14.09 0.01 400.98 180.63 39256 +1928 284 14.93 8.93 13.28 0 382.52 239.31 39058 +1928 285 13.9 7.9 12.25 0.15 360.11 178.81 38861 +1928 286 10.28 4.28 8.63 0 290 240.9 38664 +1928 287 12 6 10.35 0.58 321.7 176.71 38468 +1928 288 9.96 3.96 8.31 0.89 284.41 176.65 38273 +1928 289 9.78 3.78 8.13 0.34 281.31 174.82 38079 +1928 290 9.82 3.82 8.17 0.1 282 172.61 37885 +1928 291 6.63 0.63 4.98 0 231.5 230.89 37693 +1928 292 8.57 2.57 6.92 0 261.19 226.14 37501 +1928 293 8.23 2.23 6.58 0 255.76 223.74 37311 +1928 294 5.76 -0.24 4.11 0 219.16 223.24 37121 +1928 295 8.02 2.02 6.37 0 252.46 218.17 36933 +1928 296 14.24 8.24 12.59 0 367.38 207.77 36745 +1928 297 12.87 6.87 11.22 0.06 338.83 155.28 36560 +1928 298 17.46 11.46 15.81 0 442.7 197.28 36375 +1928 299 16.19 10.19 14.54 0 411.56 196.75 36191 +1928 300 20.41 14.41 18.76 0 522.87 186.37 36009 +1928 301 20.28 14.28 18.63 0.28 519.09 138.2 35829 +1928 302 18.85 12.85 17.2 0 479.06 184.57 35650 +1928 303 18.75 12.75 17.1 0.71 476.36 136.72 35472 +1928 304 17.45 11.45 15.8 0 442.44 182.22 35296 +1928 305 12.26 6.26 10.61 0.38 326.74 140.29 35122 +1928 306 9.41 3.41 7.76 0.03 275.02 141.01 34950 +1928 307 7.38 1.38 5.73 0.1 242.61 140.57 34779 +1928 308 11.1 5.1 9.45 0.23 304.76 135.84 34610 +1928 309 9.64 3.64 7.99 0.5 278.91 135.27 34444 +1928 310 10.01 4.01 8.36 0.17 285.28 133.16 34279 +1928 311 8.95 2.95 7.3 0 267.37 176.42 34116 +1928 312 9.96 3.96 8.31 0 284.41 172.81 33956 +1928 313 10.03 4.03 8.38 0.44 285.63 127.98 33797 +1928 314 9.91 3.91 8.26 0.06 283.55 126.61 33641 +1928 315 11.88 5.88 10.23 0 319.39 164.26 33488 +1928 316 12.58 6.58 10.93 0.61 333.03 121 33337 +1928 317 13.28 7.28 11.63 0 347.17 158.38 33188 +1928 318 12.14 6.14 10.49 0 324.4 157.37 33042 +1928 319 9.68 3.68 8.03 0 279.6 158.17 32899 +1928 320 9.47 3.47 7.82 0.13 276.03 117.38 32758 +1928 321 12.2 6.2 10.55 0 325.57 151.75 32620 +1928 322 13.65 7.65 12 0.03 354.84 111.28 32486 +1928 323 11.96 5.96 10.31 0 320.93 148.64 32354 +1928 324 8.54 2.54 6.89 0.5 260.7 112.33 32225 +1928 325 8.43 2.43 6.78 0.24 258.94 111.12 32100 +1928 326 9.79 3.79 8.14 1.14 281.48 109.17 31977 +1928 327 11.93 5.93 10.28 0.11 320.35 106.3 31858 +1928 328 11.68 5.68 10.03 0 315.59 140.05 31743 +1928 329 10.99 4.99 9.34 0 302.75 139.24 31631 +1928 330 11.85 5.85 10.2 0 318.82 137.01 31522 +1928 331 7.55 1.55 5.9 0.2 245.19 104.53 31417 +1928 332 7.11 1.11 5.46 0.49 238.56 103.54 31316 +1928 333 7.11 1.11 5.46 0 238.56 136.98 31218 +1928 334 9.92 3.92 8.27 0.02 283.72 100.29 31125 +1928 335 -1.37 -7.37 -3.02 0 137.62 139.28 31035 +1928 336 -5.74 -11.74 -7.39 0 101.91 139.69 30949 +1928 337 -1.26 -7.26 -2.91 0 138.65 136.47 30867 +1928 338 -0.79 -6.79 -2.44 0 143.09 135.32 30790 +1928 339 0.95 -5.05 -0.7 0 160.64 133.77 30716 +1928 340 -3.7 -9.7 -5.35 0.04 117.43 144.33 30647 +1928 341 0.68 -5.32 -0.97 0 157.8 175.42 30582 +1928 342 -0.24 -6.24 -1.89 0 148.45 175.13 30521 +1928 343 4.06 -1.94 2.41 0 196.67 128.94 30465 +1928 344 6.49 0.49 4.84 0 229.48 126.35 30413 +1928 345 6.05 0.05 4.4 0 223.21 126.21 30366 +1928 346 6.54 0.54 4.89 0 230.2 125.35 30323 +1928 347 4.11 -1.89 2.46 0 197.3 126.2 30284 +1928 348 6.28 0.28 4.63 0.53 226.47 93.43 30251 +1928 349 4.79 -1.21 3.14 0 206.07 125.09 30221 +1928 350 8.51 2.51 6.86 0 260.22 122.36 30197 +1928 351 5.86 -0.14 4.21 0 220.55 123.91 30177 +1928 352 3.03 -2.97 1.38 0.13 184.04 94.05 30162 +1928 353 1.82 -4.18 0.17 0 170.1 125.92 30151 +1928 354 0.18 -5.82 -1.47 0 152.66 126.62 30145 +1928 355 3.36 -2.64 1.71 0 188.01 125.13 30144 +1928 356 3.22 -2.78 1.57 0 186.32 125.23 30147 +1928 357 4.78 -1.22 3.13 0 205.94 124.44 30156 +1928 358 6.43 0.43 4.78 0 228.61 123.53 30169 +1928 359 7.64 1.64 5.99 0.39 246.57 92.14 30186 +1928 360 4.91 -1.09 3.26 0.58 207.65 93.7 30208 +1928 361 3.81 -2.19 2.16 0.25 193.54 94.41 30235 +1928 362 3.76 -2.24 2.11 0 192.92 126.34 30267 +1928 363 3.59 -2.41 1.94 0.21 190.82 95.27 30303 +1928 364 2.42 -3.58 0.77 0.48 176.89 96.01 30343 +1928 365 -1.06 -7.06 -2.71 0 140.52 130.13 30388 +1929 1 -5.47 -11.47 -7.12 0 103.86 132.52 30438 +1929 2 -4.98 -10.98 -6.63 0.16 107.47 143.63 30492 +1929 3 -2.91 -8.91 -4.56 0 123.97 177.11 30551 +1929 4 -1.24 -7.24 -2.89 0 138.83 177.33 30614 +1929 5 -0.89 -6.89 -2.54 0.13 142.14 144.6 30681 +1929 6 0.77 -5.23 -0.88 0.61 158.75 144.54 30752 +1929 7 -0.41 -6.41 -2.06 0 146.78 179.35 30828 +1929 8 -5.32 -11.32 -6.97 0 104.95 182.51 30907 +1929 9 -6.35 -12.35 -8 0 97.63 183.97 30991 +1929 10 -7.21 -13.21 -8.86 0 91.87 185.4 31079 +1929 11 -6.39 -12.39 -8.04 0.65 97.36 152.33 31171 +1929 12 -7.69 -13.69 -9.34 0.09 88.78 153.51 31266 +1929 13 -7.58 -13.58 -9.23 0 89.48 191.07 31366 +1929 14 -4.05 -10.05 -5.7 0 114.63 191.36 31469 +1929 15 -1.65 -7.65 -3.3 0 135.05 191.78 31575 +1929 16 -2.97 -8.97 -4.62 0 123.46 193.45 31686 +1929 17 -1.55 -7.55 -3.2 0.61 135.96 158.79 31800 +1929 18 -1.62 -7.62 -3.27 0.7 135.32 162.19 31917 +1929 19 -0.91 -6.91 -2.56 1.53 141.95 167.83 32038 +1929 20 -1.71 -7.71 -3.36 0.95 134.5 171.92 32161 +1929 21 -0.25 -6.25 -1.9 0.35 148.35 173.78 32289 +1929 22 -3.32 -9.32 -4.97 0 120.54 215.83 32419 +1929 23 -0.22 -6.22 -1.87 0 148.65 216.08 32552 +1929 24 -3.83 -9.83 -5.48 0 116.38 219.47 32688 +1929 25 -5.6 -11.6 -7.25 0 102.92 221.78 32827 +1929 26 -3.13 -9.13 -4.78 0 122.12 222.6 32969 +1929 27 -0.2 -6.2 -1.85 0 148.85 223.1 33114 +1929 28 1.21 -4.79 -0.44 0.1 163.42 181.75 33261 +1929 29 0.06 -5.94 -1.59 0 151.45 226.96 33411 +1929 30 2 -4 0.35 0.61 172.11 184.16 33564 +1929 31 -0.87 -6.87 -2.52 0 142.33 231.36 33718 +1929 32 -6.3 -12.3 -7.95 0 97.98 235.47 33875 +1929 33 -6.3 -12.3 -7.95 0 97.98 237.9 34035 +1929 34 -6.3 -12.3 -7.95 0 97.98 239.9 34196 +1929 35 -6.3 -12.3 -7.95 0 97.98 241.85 34360 +1929 36 -6.3 -12.3 -7.95 0 97.98 244.16 34526 +1929 37 -6.3 -12.3 -7.95 1.06 97.98 200.7 34694 +1929 38 -6.3 -12.3 -7.95 1.27 97.98 206.02 34863 +1929 39 -6.3 -12.3 -7.95 0.33 97.98 208.64 35035 +1929 40 -6.3 -12.3 -7.95 0 97.98 261.01 35208 +1929 41 -6.3 -12.3 -7.95 0 97.98 263.39 35383 +1929 42 -6.3 -12.3 -7.95 0 97.98 265.72 35560 +1929 43 -6.3 -12.3 -7.95 0.04 97.98 215.63 35738 +1929 44 -6.3 -12.3 -7.95 0 97.98 270.63 35918 +1929 45 -6.3 -12.3 -7.95 0.01 97.98 219.06 36099 +1929 46 -6.3 -12.3 -7.95 0 97.98 275.51 36282 +1929 47 -6.3 -12.3 -7.95 0.02 97.98 222.76 36466 +1929 48 -6.3 -12.3 -7.95 0 97.98 280.74 36652 +1929 49 -6.3 -12.3 -7.95 0.01 97.98 226.49 36838 +1929 50 -6.3 -12.3 -7.95 1 97.98 230.85 37026 +1929 51 -6.3 -12.3 -7.95 0.19 97.98 233.32 37215 +1929 52 -6.3 -12.3 -7.95 0 97.98 294.19 37405 +1929 53 -6.3 -12.3 -7.95 0.14 97.98 237.52 37596 +1929 54 -6.3 -12.3 -7.95 0 97.98 299.8 37788 +1929 55 -6.3 -12.3 -7.95 0.67 97.98 243.04 37981 +1929 56 -6.3 -12.3 -7.95 0 97.98 306.72 38175 +1929 57 -6.3 -12.3 -7.95 0 97.98 309.37 38370 +1929 58 -6.3 -12.3 -7.95 0.02 97.98 248.73 38565 +1929 59 -6.3 -12.3 -7.95 0.42 97.98 251.56 38761 +1929 60 1.94 -4.06 0.29 0 171.44 313.28 38958 +1929 61 4.87 -1.13 3.22 0 207.13 312.94 39156 +1929 62 3.68 -2.32 2.03 0 191.93 316.16 39355 +1929 63 1.3 -4.7 -0.35 0 164.39 320.72 39553 +1929 64 3.46 -2.54 1.81 0 189.23 321.26 39753 +1929 65 -0.23 -6.23 -1.88 0 148.55 326.79 39953 +1929 66 0.64 -5.36 -1.01 0 157.39 328.61 40154 +1929 67 4.82 -1.18 3.17 0 206.47 327.21 40355 +1929 68 6.15 0.15 4.5 0 224.62 327.84 40556 +1929 69 4.62 -1.38 2.97 0 203.85 331.33 40758 +1929 70 2.63 -3.37 0.98 0 179.33 335.53 40960 +1929 71 6.96 0.96 5.31 0 236.34 333.15 41163 +1929 72 6.18 0.18 4.53 0 225.05 336.01 41366 +1929 73 6.63 0.63 4.98 0 231.5 337.29 41569 +1929 74 4.64 -1.36 2.99 0 204.11 341.53 41772 +1929 75 3.01 -2.99 1.36 0 183.8 345.34 41976 +1929 76 6.29 0.29 4.64 0 226.61 343.77 42179 +1929 77 5.64 -0.36 3.99 0 217.5 346.36 42383 +1929 78 6.93 0.93 5.28 0 235.89 346.66 42587 +1929 79 10.49 4.49 8.84 0 293.72 343.29 42791 +1929 80 7.68 1.68 6.03 0 247.19 348.86 42996 +1929 81 7.58 1.58 5.93 0 245.65 350.66 43200 +1929 82 10.34 4.34 8.69 0 291.06 348.23 43404 +1929 83 6.44 0.44 4.79 0 228.76 355.31 43608 +1929 84 6.89 0.89 5.24 0 235.3 356.48 43812 +1929 85 7.07 1.07 5.42 0 237.97 357.93 44016 +1929 86 8.35 2.35 6.7 0 257.66 357.69 44220 +1929 87 5.13 -0.87 3.48 0 210.58 363.69 44424 +1929 88 3.25 -2.75 1.6 0 186.68 367.64 44627 +1929 89 4.44 -1.56 2.79 0 201.52 368.13 44831 +1929 90 7.61 1.61 5.96 0 246.11 365.76 45034 +1929 91 10.42 4.42 8.77 0.24 292.48 280.81 45237 +1929 92 6.97 0.97 5.32 0.06 236.48 285.55 45439 +1929 93 5.99 -0.01 4.34 0 222.37 372.12 45642 +1929 94 2.77 -3.23 1.12 0 180.96 377.57 45843 +1929 95 4.73 -1.27 3.08 0.08 205.29 290.97 46045 +1929 96 5.64 -0.36 3.99 0 217.5 377.49 46246 +1929 97 11.15 5.15 9.5 0.09 305.68 285.41 46446 +1929 98 10.04 4.04 8.39 0.09 285.8 287.31 46647 +1929 99 5.1 -0.9 3.45 0 210.18 381.62 46846 +1929 100 6.33 0.33 4.68 0 227.18 381.38 47045 +1929 101 9.87 3.87 8.22 0.02 282.86 262.02 47243 +1929 102 10.54 4.54 8.89 0.05 294.62 262.6 47441 +1929 103 9.7 3.7 8.05 0 279.94 353.41 47638 +1929 104 6.99 0.99 5.34 0.58 236.78 269.55 47834 +1929 105 4.35 -1.65 2.7 0 200.36 364.64 48030 +1929 106 7.59 1.59 5.94 0 245.81 362.04 48225 +1929 107 6.13 0.13 4.48 0 224.34 365.8 48419 +1929 108 10.15 4.15 8.5 0.32 287.72 271.06 48612 +1929 109 10.78 4.78 9.13 1.08 298.93 271.43 48804 +1929 110 15.77 9.77 14.12 0.04 401.68 264.56 48995 +1929 111 14.88 8.88 13.23 0.09 381.41 267.3 49185 +1929 112 11.85 5.85 10.2 0.37 318.82 273.31 49374 +1929 113 11.94 5.94 10.29 0.73 320.54 274.19 49561 +1929 114 10.33 4.33 8.68 0.02 290.89 277.58 49748 +1929 115 13.17 7.17 11.52 0 344.91 365.99 49933 +1929 116 14.08 8.08 12.43 0.01 363.94 273.9 50117 +1929 117 12.32 6.32 10.67 0.66 327.91 277.72 50300 +1929 118 14.95 8.95 13.3 0.41 382.97 274.35 50481 +1929 119 7.14 1.14 5.49 1.03 239.01 286.43 50661 +1929 120 8.2 2.2 6.55 0.04 255.28 286.11 50840 +1929 121 20.18 14.18 18.53 0 516.2 354.5 51016 +1929 122 18.58 12.58 16.93 0 471.8 360.67 51191 +1929 123 22.73 16.73 21.08 0.09 594.29 260.73 51365 +1929 124 26.6 20.6 24.95 0.08 731.84 249.2 51536 +1929 125 23.07 17.07 21.42 0.32 605.43 261.22 51706 +1929 126 25.13 19.13 23.48 0.06 676.72 255.57 51874 +1929 127 23.61 17.61 21.96 2.13 623.47 260.96 52039 +1929 128 19.18 13.18 17.53 0.36 488.06 273.51 52203 +1929 129 18.06 12.06 16.41 0 458.09 368.92 52365 +1929 130 18.06 12.06 16.41 0 458.09 369.7 52524 +1929 131 15.23 9.23 13.58 0.03 389.27 283.64 52681 +1929 132 12.99 6.99 11.34 0.72 341.25 288.2 52836 +1929 133 12.83 6.83 11.18 0.1 338.02 289 52989 +1929 134 14.8 8.8 13.15 0 379.63 381.5 53138 +1929 135 13.65 7.65 12 0.36 354.84 288.7 53286 +1929 136 15.31 9.31 13.66 1.37 391.09 286.18 53430 +1929 137 16.58 10.58 14.93 0.2 420.91 284.2 53572 +1929 138 18.48 12.48 16.83 0 469.14 374.05 53711 +1929 139 21.84 15.84 20.19 0 565.97 363.4 53848 +1929 140 24.14 18.14 22.49 0 641.62 354.76 53981 +1929 141 22.74 16.74 21.09 0 594.62 360.86 54111 +1929 142 21.62 15.62 19.97 0.33 559.15 274.18 54238 +1929 143 15.92 9.92 14.27 0.01 405.18 287.98 54362 +1929 144 18.47 12.47 16.82 0 468.88 377.17 54483 +1929 145 14.97 8.97 13.32 0 383.42 387.37 54600 +1929 146 11.46 5.46 9.81 0 311.44 395.68 54714 +1929 147 12.12 6.12 10.47 0 324.02 394.81 54824 +1929 148 15 9 13.35 0 384.09 388.55 54931 +1929 149 16.73 10.73 15.08 0 424.56 384.28 55034 +1929 150 18.26 12.26 16.61 0 463.33 380.15 55134 +1929 151 19.57 13.57 17.92 0 498.88 376.39 55229 +1929 152 18.41 12.41 16.76 1.66 467.28 285.15 55321 +1929 153 19.72 13.72 18.07 1.84 503.09 282.19 55409 +1929 154 20.15 14.15 18.5 0.94 515.34 281.34 55492 +1929 155 18.71 12.71 17.06 0.14 475.29 285.01 55572 +1929 156 19.45 13.45 17.8 0.01 495.53 283.47 55648 +1929 157 18.12 12.12 16.47 0 459.66 382.32 55719 +1929 158 19.25 13.25 17.6 0 489.98 378.95 55786 +1929 159 23.34 17.34 21.69 0.43 614.39 273.21 55849 +1929 160 24.11 18.11 22.46 0.19 640.58 270.93 55908 +1929 161 26.77 20.77 25.12 0.04 738.45 261.83 55962 +1929 162 24.69 18.69 23.04 0.07 660.93 269.14 56011 +1929 163 25.72 19.72 24.07 0.13 698.41 265.8 56056 +1929 164 23.93 17.93 22.28 0.01 634.38 271.79 56097 +1929 165 20.18 14.18 18.53 0.72 516.2 282.57 56133 +1929 166 18.69 12.69 17.04 0.6 474.75 286.3 56165 +1929 167 19.84 13.84 18.19 0.93 506.48 283.45 56192 +1929 168 19.22 13.22 17.57 1.03 489.16 285.05 56214 +1929 169 20.17 14.17 18.52 0.91 515.92 282.68 56231 +1929 170 16.75 10.75 15.1 0.61 425.05 290.65 56244 +1929 171 18.45 12.45 16.8 1.65 468.34 286.93 56252 +1929 172 23.07 17.07 21.42 0.31 605.43 274.63 56256 +1929 173 20.79 14.79 19.14 0.01 534.04 281.09 56255 +1929 174 19.63 13.63 17.98 0 500.56 378.68 56249 +1929 175 20.32 14.32 18.67 0.01 520.25 282.24 56238 +1929 176 20.87 14.87 19.22 0 536.42 374.35 56223 +1929 177 14.22 8.22 12.57 0 366.95 393.9 56203 +1929 178 16.45 10.45 14.8 0 417.77 388.17 56179 +1929 179 18.46 12.46 16.81 0 468.61 382.18 56150 +1929 180 18.47 12.47 16.82 0.05 468.88 286.52 56116 +1929 181 20.31 14.31 18.66 0 519.96 375.94 56078 +1929 182 23.71 17.71 22.06 0 626.86 362.89 56035 +1929 183 19.29 13.29 17.64 0 491.09 379.03 55987 +1929 184 20.8 14.8 19.15 0 534.34 373.75 55935 +1929 185 21.15 15.15 19.5 0 544.81 372.42 55879 +1929 186 20.77 14.77 19.12 1.91 533.45 280.14 55818 +1929 187 19.5 13.5 17.85 0.57 496.92 283.24 55753 +1929 188 20.14 14.14 18.49 0.03 515.05 281.44 55684 +1929 189 19.17 13.17 17.52 0 487.78 378.28 55611 +1929 190 19.03 13.03 17.38 0 483.95 378.36 55533 +1929 191 18.51 12.51 16.86 0 469.94 379.72 55451 +1929 192 20.22 14.22 18.57 0 517.36 373.86 55366 +1929 193 22.61 16.61 20.96 0 590.41 364.86 55276 +1929 194 24.65 18.65 23 0 659.51 356.23 55182 +1929 195 25.91 19.91 24.26 0 705.51 350.28 55085 +1929 196 22.62 16.62 20.97 0 590.73 363.94 54984 +1929 197 24.67 18.67 23.02 0.33 660.22 266.28 54879 +1929 198 22.6 16.6 20.95 0.38 590.08 272.36 54770 +1929 199 23.33 17.33 21.68 0 614.06 359.91 54658 +1929 200 27.67 21.67 26.02 0 774.3 339.74 54542 +1929 201 29.07 23.07 27.42 0 832.99 331.87 54423 +1929 202 27.9 21.9 26.25 0 783.7 337.58 54301 +1929 203 24.04 18.04 22.39 0 638.16 355.1 54176 +1929 204 26.05 20.05 24.4 0.01 710.79 259.29 54047 +1929 205 25.22 19.22 23.57 0.37 679.99 261.75 53915 +1929 206 22.59 16.59 20.94 0 589.76 359.37 53780 +1929 207 21.04 15.04 19.39 0 541.5 364.43 53643 +1929 208 21.43 15.43 19.78 0 553.32 362.39 53502 +1929 209 24.09 18.09 22.44 0 639.89 351.44 53359 +1929 210 28.56 22.56 26.91 0 811.19 329.77 53213 +1929 211 26.41 20.41 24.76 0 724.51 339.8 53064 +1929 212 25.55 19.55 23.9 0 692.1 343 52913 +1929 213 26.21 20.21 24.56 0 716.86 339.26 52760 +1929 214 25.14 19.14 23.49 0.01 677.09 257.53 52604 +1929 215 24.53 18.53 22.88 0 655.26 345.35 52445 +1929 216 22.38 16.38 20.73 0.07 583.02 264.7 52285 +1929 217 20.54 14.54 18.89 0 526.67 358.59 52122 +1929 218 23.75 17.75 22.1 0 628.22 345.93 51958 +1929 219 23.74 17.74 22.09 0 627.88 344.96 51791 +1929 220 20.85 14.85 19.2 0.32 535.82 266.07 51622 +1929 221 17.4 11.4 15.75 0.06 441.18 273.32 51451 +1929 222 17.16 11.16 15.51 0 435.17 364.02 51279 +1929 223 21.46 15.46 19.81 0.06 554.23 262.11 51105 +1929 224 23.19 17.19 21.54 0.36 609.4 256.55 50929 +1929 225 23.19 17.19 21.54 0 609.4 340.96 50751 +1929 226 21.68 15.68 20.03 0.02 561.01 259.05 50572 +1929 227 18.66 12.66 17.01 0 473.94 353.9 50392 +1929 228 22.54 16.54 20.89 0 588.15 339.85 50210 +1929 229 25.69 19.69 24.04 0.18 697.29 244.5 50026 +1929 230 23.43 17.43 21.78 2.7 617.4 250.54 49842 +1929 231 24.2 18.2 22.55 0.55 643.7 247.2 49656 +1929 232 23.06 17.06 21.41 0 605.1 332.71 49469 +1929 233 20.45 14.45 18.8 0 524.04 340.39 49280 +1929 234 19.75 13.75 18.1 0 503.94 341.19 49091 +1929 235 19.45 13.45 17.8 0.03 495.53 255.47 48900 +1929 236 17.77 11.77 16.12 0 450.6 344.03 48709 +1929 237 24.99 18.99 23.34 0 671.66 318.02 48516 +1929 238 28.16 22.16 26.51 0 794.43 302.3 48323 +1929 239 31.52 25.52 29.87 0 944.73 283.18 48128 +1929 240 30.64 24.64 28.99 0.03 903.23 214.92 47933 +1929 241 32.29 26.29 30.64 0 982.36 275.62 47737 +1929 242 32.02 26.02 30.37 0.06 969.02 206.77 47541 +1929 243 26.58 20.58 24.93 0.16 731.07 226.19 47343 +1929 244 22.38 16.38 20.73 0.98 583.02 237.15 47145 +1929 245 24.22 18.22 22.57 1.19 644.4 230.81 46947 +1929 246 17.46 11.46 15.81 0.11 442.7 245.39 46747 +1929 247 19.64 13.64 17.99 0 500.84 319.35 46547 +1929 248 18.88 12.88 17.23 0 479.87 319.59 46347 +1929 249 25.43 19.43 23.78 0 687.68 295.61 46146 +1929 250 22 16 20.35 0 570.98 306.2 45945 +1929 251 17.88 11.88 16.23 0.01 453.43 237.12 45743 +1929 252 20.3 14.3 18.65 0 519.67 307.32 45541 +1929 253 21.33 15.33 19.68 0 550.27 302.13 45339 +1929 254 23.22 17.22 21.57 0 610.39 293.87 45136 +1929 255 24.5 18.5 22.85 0 654.2 287.16 44933 +1929 256 25.49 19.49 23.84 0 689.89 281.29 44730 +1929 257 23.73 17.73 22.08 0.69 627.54 214.29 44527 +1929 258 21.94 15.94 20.29 0.17 569.1 217.05 44323 +1929 259 26.2 20.2 24.55 0.17 716.48 204.04 44119 +1929 260 21.07 15.07 19.42 0.48 542.4 215.54 43915 +1929 261 18.83 12.83 17.18 0 478.52 291.18 43711 +1929 262 15.25 9.25 13.6 0 389.73 297.15 43507 +1929 263 14.31 8.31 12.66 0.26 368.89 222.42 43303 +1929 264 11.31 5.31 9.66 0.02 308.64 224.48 43099 +1929 265 15.33 9.33 13.68 0 391.55 289.54 42894 +1929 266 21.73 15.73 20.08 0 562.55 271.24 42690 +1929 267 20.05 14.05 18.4 0 512.47 273.36 42486 +1929 268 18.84 12.84 17.19 0 478.79 273.96 42282 +1929 269 17.11 11.11 15.46 0 433.92 275.54 42078 +1929 270 18.51 12.51 16.86 0 469.94 269.72 41875 +1929 271 14.19 8.19 12.54 0 366.3 276.21 41671 +1929 272 17.94 11.94 16.29 0 454.98 265.8 41468 +1929 273 18.05 12.05 16.4 0 457.83 263.06 41265 +1929 274 12.1 6.1 10.45 0 323.63 271.8 41062 +1929 275 13.27 7.27 11.62 0 346.96 267.09 40860 +1929 276 15.6 9.6 13.95 0.28 397.74 195.13 40658 +1929 277 14.47 8.47 12.82 0.17 372.37 194.72 40456 +1929 278 13 7 11.35 0.03 341.45 194.45 40255 +1929 279 10.63 4.63 8.98 0 296.23 260.01 40054 +1929 280 13.31 7.31 11.66 0.03 347.78 189.97 39854 +1929 281 8.35 2.35 6.7 0 257.66 257.49 39654 +1929 282 11.26 5.26 9.61 0 307.72 250.92 39455 +1929 283 10.15 4.15 8.5 0.24 287.72 187.19 39256 +1929 284 10.16 4.16 8.51 0.39 287.9 184.89 39058 +1929 285 12.48 6.48 10.83 0 331.05 240.62 38861 +1929 286 10.94 4.94 9.29 1.03 301.83 180.02 38664 +1929 287 10.2 4.2 8.55 1.06 288.6 178.53 38468 +1929 288 13.72 7.72 12.07 0.25 356.31 172.7 38273 +1929 289 15.5 9.5 13.85 0.25 395.43 168.56 38079 +1929 290 16.54 10.54 14.89 0.05 419.95 165.07 37885 +1929 291 15.35 9.35 13.7 1.49 392 164.64 37693 +1929 292 13.83 7.83 12.18 0 358.63 219.3 37501 +1929 293 14.32 8.32 12.67 0.5 369.11 161.89 37311 +1929 294 18.21 12.21 16.56 1.35 462.01 154.7 37121 +1929 295 19.4 13.4 17.75 0.34 494.14 150.88 36933 +1929 296 21.38 15.38 19.73 0.65 551.79 145.83 36745 +1929 297 14.93 8.93 13.28 1.03 382.52 153.02 36560 +1929 298 15.97 9.97 14.32 0 406.36 199.82 36375 +1929 299 14.04 8.04 12.39 0.19 363.09 150.05 36191 +1929 300 12.71 6.71 11.06 0 335.62 199.27 36009 +1929 301 17.44 11.44 15.79 0.31 442.19 142.21 35829 +1929 302 19.25 13.25 17.6 0 489.98 183.81 35650 +1929 303 18.2 12.2 16.55 0.07 461.75 137.46 35472 +1929 304 20.62 14.62 18.97 0 529.02 176.35 35296 +1929 305 15.55 9.55 13.9 0 396.58 182.59 35122 +1929 306 14.21 8.21 12.56 0.04 366.73 136.73 34950 +1929 307 11.4 5.4 9.75 0.13 310.32 137.52 34779 +1929 308 9.05 3.05 7.4 0 269.02 183.26 34610 +1929 309 8.95 2.95 7.3 0 267.37 181.04 34444 +1929 310 10.29 4.29 8.64 0.01 290.18 132.95 34279 +1929 311 8.89 2.89 7.24 0.07 266.38 132.36 34116 +1929 312 6.97 0.97 5.32 1.23 236.48 131.65 33956 +1929 313 9.08 3.08 7.43 0.8 269.51 128.66 33797 +1929 314 6.1 0.1 4.45 0.01 223.91 129.1 33641 +1929 315 7.32 1.32 5.67 0.1 241.71 126.46 33488 +1929 316 9.3 3.3 7.65 0.02 273.17 123.53 33337 +1929 317 9.6 3.6 7.95 0 278.23 162.25 33188 +1929 318 12.41 6.41 10.76 0 329.68 157.08 33042 +1929 319 10.44 4.44 8.79 0 292.83 157.45 32899 +1929 320 10.75 4.75 9.1 0 298.39 155.31 32758 +1929 321 13.81 7.81 12.16 0.5 358.21 112.47 32620 +1929 322 10.69 4.69 9.04 0.38 297.3 113.62 32486 +1929 323 11.83 5.83 10.18 0 318.44 148.77 32354 +1929 324 15.35 9.35 13.7 0.92 392 107.08 32225 +1929 325 14.84 8.84 13.19 0.29 380.52 106.31 32100 +1929 326 14.58 8.58 12.93 1.22 374.78 105.5 31977 +1929 327 7.8 1.8 6.15 0.33 249.03 109.03 31858 +1929 328 4.24 -1.76 2.59 0.33 198.96 109.39 31743 +1929 329 2.27 -3.73 0.62 0.01 175.17 109.1 31631 +1929 330 5.1 -0.9 3.45 0.04 210.18 106.77 31522 +1929 331 6.1 0.1 4.45 0.79 223.91 105.29 31417 +1929 332 2.99 -3.01 1.34 0.48 183.56 105.48 31316 +1929 333 3.82 -2.18 2.17 0 193.66 139.08 31218 +1929 334 6.58 0.58 4.93 0.16 230.78 102.19 31125 +1929 335 0.47 -5.53 -1.18 0 155.63 138.5 31035 +1929 336 1.86 -4.14 0.21 0 170.54 136.75 30949 +1929 337 2.49 -3.51 0.84 0 177.7 134.77 30867 +1929 338 6.18 0.18 4.53 0 225.05 131.68 30790 +1929 339 4.43 -1.57 2.78 0.52 201.39 98.98 30716 +1929 340 1.99 -4.01 0.34 0 172 132.53 30647 +1929 341 3.64 -2.36 1.99 0.51 191.43 98.07 30582 +1929 342 2.27 -3.73 0.62 0.72 175.17 98.03 30521 +1929 343 1.32 -4.68 -0.33 0 164.61 130.33 30465 +1929 344 10.9 4.9 9.25 0 301.11 123.06 30413 +1929 345 9.4 3.4 7.75 0 274.85 123.86 30366 +1929 346 5.8 -0.2 4.15 0 219.72 125.81 30323 +1929 347 6.95 0.95 5.3 0 236.19 124.49 30284 +1929 348 8.24 2.24 6.59 0 255.92 123.26 30251 +1929 349 4.63 -1.37 2.98 0.2 203.98 93.89 30221 +1929 350 5.32 -0.68 3.67 0 213.14 124.45 30197 +1929 351 6.96 0.96 5.31 0.01 236.34 92.41 30177 +1929 352 8.36 2.36 6.71 0 257.82 122.16 30162 +1929 353 7.47 1.47 5.82 0.11 243.98 92.04 30151 +1929 354 5.27 -0.73 3.62 0 212.46 124.07 30145 +1929 355 5.5 -0.5 3.85 0.36 215.58 92.95 30144 +1929 356 4.67 -1.33 3.02 0.43 204.5 93.33 30147 +1929 357 6.38 0.38 4.73 0 227.89 123.48 30156 +1929 358 6.3 0.3 4.65 0 226.75 123.62 30169 +1929 359 5.88 -0.12 4.23 0 220.83 123.99 30186 +1929 360 9.42 3.42 7.77 0 275.19 121.92 30208 +1929 361 7.04 1.04 5.39 0 237.52 123.95 30235 +1929 362 5.22 -0.78 3.57 0 211.79 125.52 30267 +1929 363 5.43 -0.57 3.78 0 214.63 125.98 30303 +1929 364 5.82 -0.18 4.17 0 219.99 126.14 30343 +1929 365 0.01 -5.99 -1.64 0 150.94 129.69 30388 +1930 1 -0.49 -6.49 -2.14 0 145.99 130.8 30438 +1930 2 -3.01 -9.01 -4.66 0 123.12 132.49 30492 +1930 3 -2.84 -8.84 -4.49 0.24 124.56 144 30551 +1930 4 -1.94 -7.94 -3.59 0.18 132.42 144.92 30614 +1930 5 -4.03 -10.03 -5.68 0 114.79 179.71 30681 +1930 6 -2.42 -8.42 -4.07 0.01 128.18 146.05 30752 +1930 7 -0.6 -6.6 -2.25 0 144.92 179.97 30828 +1930 8 5.06 -0.94 3.41 0 209.65 177.81 30907 +1930 9 7.7 1.7 6.05 0 247.49 133.92 30991 +1930 10 2.76 -3.24 1.11 0 180.85 138.3 31079 +1930 11 8.04 2.04 6.39 0 252.77 135.92 31171 +1930 12 4.24 -1.76 2.59 0 198.96 139.46 31266 +1930 13 2.52 -3.48 0.87 0 178.05 142.05 31366 +1930 14 6.31 0.31 4.66 0 226.89 141.23 31469 +1930 15 2.37 -3.63 0.72 0 176.32 145.06 31575 +1930 16 4.15 -1.85 2.5 0 197.81 145.34 31686 +1930 17 1.65 -4.35 0 0 168.21 148.42 31800 +1930 18 0.62 -5.38 -1.03 0 157.18 150.85 31917 +1930 19 3.23 -2.77 1.58 0 186.44 151.4 32038 +1930 20 2.95 -3.05 1.3 0.43 183.09 114.86 32161 +1930 21 2.34 -3.66 0.69 0 175.97 155.51 32289 +1930 22 4.44 -1.56 2.79 0 201.52 156 32419 +1930 23 8.04 2.04 6.39 0.22 252.77 116.35 32552 +1930 24 5.75 -0.25 4.1 0 219.02 158.93 32688 +1930 25 5.27 -0.73 3.62 0.05 212.46 120.86 32827 +1930 26 2.13 -3.87 0.48 0 173.58 165.07 32969 +1930 27 3.56 -2.44 1.91 0.14 190.45 124.67 33114 +1930 28 3.86 -2.14 2.21 0.37 194.16 126.19 33261 +1930 29 1.51 -4.49 -0.14 0 166.68 172.06 33411 +1930 30 4.89 -1.11 3.24 0.02 207.39 129.13 33564 +1930 31 1.3 -4.7 -0.35 0.25 164.39 132.62 33718 +1930 32 -3.25 -9.25 -4.9 0.55 121.12 176.42 33875 +1930 33 -1.71 -7.71 -3.36 0 134.5 223.51 34035 +1930 34 -1.29 -7.29 -2.94 0.2 138.37 179.61 34196 +1930 35 -0.45 -6.45 -2.1 0.17 146.39 181.21 34360 +1930 36 -2.55 -8.55 -4.2 0.03 127.05 183.77 34526 +1930 37 -3.83 -9.83 -5.48 1.69 116.38 190.52 34694 +1930 38 -4.39 -10.39 -6.04 0 111.97 241.7 34863 +1930 39 -7.15 -13.15 -8.8 0 92.26 245.17 35035 +1930 40 -1.22 -7.22 -2.87 0.01 139.02 195.03 35208 +1930 41 3.39 -2.61 1.74 0 188.37 244.35 35383 +1930 42 4.21 -1.79 2.56 0 198.57 245.61 35560 +1930 43 3.21 -2.79 1.56 0 186.2 248.49 35738 +1930 44 2.84 -3.16 1.19 0 181.79 250.8 35918 +1930 45 0.48 -5.52 -1.17 0.04 155.73 201.55 36099 +1930 46 5 -1 3.35 0 208.85 253.43 36282 +1930 47 8.12 2.12 6.47 0.1 254.02 199.23 36466 +1930 48 12.21 6.21 10.56 0 325.76 248.69 36652 +1930 49 10.9 4.9 9.25 0.28 301.11 198.08 36838 +1930 50 9.28 3.28 7.63 0.84 272.84 200.28 37026 +1930 51 5.01 -0.99 3.36 0 208.98 226.2 37215 +1930 52 6.09 0.09 4.44 0 223.77 228.05 37405 +1930 53 2.42 -3.58 0.77 0 176.89 234.1 37596 +1930 54 4.16 -1.84 2.51 0.52 197.94 176.62 37788 +1930 55 3.58 -2.42 1.93 0 190.7 238.98 37981 +1930 56 6.39 0.39 4.74 0 228.04 239.15 38175 +1930 57 7.3 1.3 5.65 0 241.41 241.09 38370 +1930 58 9.43 3.43 7.78 0 275.36 241.57 38565 +1930 59 12.65 6.65 11 0.01 334.42 179.89 38761 +1930 60 14.35 8.35 12.7 0.05 369.76 179.96 38958 +1930 61 13.06 7.06 11.41 0.92 342.67 183.67 39156 +1930 62 9.18 3.18 7.53 0.59 271.17 189.81 39355 +1930 63 7.6 1.6 5.95 0.25 245.96 193.47 39553 +1930 64 10.65 4.65 9 0 296.59 257 39753 +1930 65 8.09 2.09 6.44 0 253.55 263.16 39953 +1930 66 5.88 -0.12 4.23 0.24 220.83 201.27 40154 +1930 67 8.01 2.01 6.36 0 252.3 268.87 40355 +1930 68 10.93 4.93 9.28 0 301.65 267.85 40556 +1930 69 9.06 3.06 7.41 0.44 269.18 204.77 40758 +1930 70 10.26 4.26 8.61 0.07 289.65 205.66 40960 +1930 71 11.94 5.94 10.29 0.01 320.54 205.93 41163 +1930 72 13.08 7.08 11.43 0.32 343.08 206.6 41366 +1930 73 12.76 6.76 11.11 0 336.62 278.62 41569 +1930 74 9.26 3.26 7.61 0 272.5 286.68 41772 +1930 75 5.47 -0.53 3.82 0 215.17 294.05 41976 +1930 76 7.3 1.3 5.65 0 241.41 294.59 42179 +1930 77 10.53 4.53 8.88 0 294.44 292.76 42383 +1930 78 3.85 -2.15 2.2 0 194.04 303.73 42587 +1930 79 5.99 -0.01 4.34 0 222.37 304.18 42791 +1930 80 5.2 -0.8 3.55 0.11 211.52 230.73 42996 +1930 81 7.8 1.8 6.15 0 249.03 307.1 43200 +1930 82 14.03 8.03 12.38 0.14 362.88 224.78 43404 +1930 83 14.83 8.83 13.18 0 380.3 300.55 43608 +1930 84 11.56 5.56 9.91 0 313.32 309.13 43812 +1930 85 5.99 -0.01 4.34 0.4 222.37 239.71 44016 +1930 86 7.34 1.34 5.69 1.54 242.01 240.26 44220 +1930 87 8.12 2.12 6.47 1.42 254.02 241.38 44424 +1930 88 15.54 9.54 13.89 0 396.35 311.05 44627 +1930 89 15.19 9.19 13.54 0.01 388.37 235.52 44831 +1930 90 16.74 10.74 15.09 0 424.8 312.81 45034 +1930 91 19.49 13.49 17.84 0.65 496.64 230.88 45237 +1930 92 19.22 13.22 17.57 0.22 489.16 233.05 45439 +1930 93 17.49 11.49 15.84 0 443.46 317.46 45642 +1930 94 12.85 6.85 11.2 0.18 338.42 247.4 45843 +1930 95 9.91 3.91 8.26 0.31 283.55 252.91 46045 +1930 96 8.62 2.62 6.97 0.05 261.99 256.02 46246 +1930 97 11.72 5.72 10.07 0 316.34 338.27 46446 +1930 98 9.32 3.32 7.67 0.05 273.51 258.24 46647 +1930 99 8.28 2.28 6.63 0 256.55 347.95 46846 +1930 100 14 8 12.35 0.03 362.24 254.73 47045 +1930 101 14.17 8.17 12.52 0 365.87 341.19 47243 +1930 102 13.02 7.02 11.37 0.02 341.86 259.11 47441 +1930 103 12.95 6.95 11.3 0 340.44 347.45 47638 +1930 104 10.43 4.43 8.78 0.35 292.66 265.51 47834 +1930 105 11.15 5.15 9.5 0 305.68 354.53 48030 +1930 106 17.45 11.45 15.8 0.09 442.44 256.6 48225 +1930 107 17.35 11.35 15.7 0.31 439.92 258.02 48419 +1930 108 16.59 10.59 14.94 0.1 421.16 260.79 48612 +1930 109 10.22 4.22 8.57 1.92 288.95 272.18 48804 +1930 110 12.89 6.89 11.24 0.04 339.23 269.43 48995 +1930 111 15.89 9.89 14.24 0.35 404.48 265.48 49185 +1930 112 13.54 7.54 11.89 0.68 352.55 270.7 49374 +1930 113 13.16 7.16 11.51 0.76 344.71 272.31 49561 +1930 114 9.81 3.81 8.16 0.08 281.82 278.27 49748 +1930 115 13.04 7.04 11.39 0.46 342.26 274.7 49933 +1930 116 16.04 10.04 14.39 0 408 360.5 50117 +1930 117 15.6 9.6 13.95 0 397.74 362.9 50300 +1930 118 16.78 10.78 15.13 0.14 425.78 270.87 50481 +1930 119 17.53 11.53 15.88 0.4 444.47 270.21 50661 +1930 120 20.49 14.49 18.84 0.03 525.2 264.29 50840 +1930 121 19.05 13.05 17.4 0 484.5 358.08 51016 +1930 122 16.66 10.66 15.01 0.55 422.85 274.58 51191 +1930 123 21.65 15.65 20 0.26 560.08 263.71 51365 +1930 124 16.27 10.27 14.62 0 413.46 369.23 51536 +1930 125 15.88 9.88 14.23 0 404.24 371.23 51706 +1930 126 14.11 8.11 12.46 0 364.59 376.55 51874 +1930 127 16.66 10.66 15.01 0 422.85 371.04 52039 +1930 128 21.86 15.86 20.21 0.01 566.6 266.7 52203 +1930 129 20.58 14.58 18.93 0 527.84 360.93 52365 +1930 130 17.55 11.55 15.9 0 444.98 371.18 52524 +1930 131 17.77 11.77 16.12 0 450.6 371.33 52681 +1930 132 11.14 5.14 9.49 0 305.5 388.1 52836 +1930 133 11.9 5.9 10.25 0 319.78 387.3 52989 +1930 134 13.42 7.42 11.77 0 350.05 384.75 53138 +1930 135 9.85 3.85 8.2 0 282.51 392.7 53286 +1930 136 9.12 3.12 7.47 0.04 270.17 295.99 53430 +1930 137 17.35 11.35 15.7 0.05 439.92 282.59 53572 +1930 138 20.54 14.54 18.89 0 526.67 367.36 53711 +1930 139 23.72 17.72 22.07 0.05 627.2 267.04 53848 +1930 140 19.71 13.71 18.06 0.13 502.81 278.48 53981 +1930 141 21.43 15.43 19.78 0.02 553.32 274.34 54111 +1930 142 14.59 8.59 12.94 0 375 386.81 54238 +1930 143 15.38 9.38 13.73 0.32 392.69 289.03 54362 +1930 144 16.5 10.5 14.85 0.47 418.98 287.17 54483 +1930 145 17.1 11.1 15.45 0.49 433.67 286.26 54600 +1930 146 13.6 7.6 11.95 0.88 353.8 293.29 54714 +1930 147 14.47 8.47 12.82 0.84 372.37 292.1 54824 +1930 148 16.16 10.16 14.51 0.6 410.84 289.15 54931 +1930 149 18.35 12.35 16.7 0 465.7 379.55 55034 +1930 150 16.56 10.56 14.91 0.16 420.43 288.82 55134 +1930 151 18.31 12.31 16.66 0 464.64 380.39 55229 +1930 152 25.94 19.94 24.29 0 706.64 351.3 55321 +1930 153 23.14 17.14 21.49 0 607.74 363.72 55409 +1930 154 28.14 22.14 26.49 0 793.6 340.86 55492 +1930 155 22.85 16.85 21.2 0.69 598.2 274.02 55572 +1930 156 19.68 13.68 18.03 0 501.96 377.2 55648 +1930 157 19.74 13.74 18.09 0 503.65 377.17 55719 +1930 158 23.69 17.69 22.04 0.04 626.18 271.95 55786 +1930 159 22.52 16.52 20.87 0.39 587.51 275.66 55849 +1930 160 26.11 20.11 24.46 0.14 713.06 264.18 55908 +1930 161 26.37 20.37 24.72 0.05 722.97 263.29 55962 +1930 162 25.41 19.41 23.76 0.4 686.94 266.72 56011 +1930 163 21.36 15.36 19.71 0 551.18 372.45 56056 +1930 164 23.76 17.76 22.11 0 628.56 363.09 56097 +1930 165 29 23 27.35 0.22 829.97 253.37 56133 +1930 166 24.36 18.36 22.71 0.05 649.28 270.53 56165 +1930 167 27.71 21.71 26.06 0 775.93 344.77 56192 +1930 168 26.94 20.94 25.29 0.89 745.11 261.57 56214 +1930 169 25.26 19.26 23.61 0.21 681.45 267.57 56231 +1930 170 24.81 18.81 23.16 0.15 665.2 269.08 56244 +1930 171 22.7 16.7 21.05 0.37 593.32 275.75 56252 +1930 172 21.8 15.8 20.15 0 564.73 371.12 56256 +1930 173 22.07 16.07 20.42 1.47 573.18 277.56 56255 +1930 174 22.21 16.21 20.56 0.29 577.6 277.1 56249 +1930 175 24.34 18.34 22.69 0.06 648.58 270.57 56238 +1930 176 21.77 15.77 20.12 0 563.79 371.07 56223 +1930 177 19.61 13.61 17.96 0 500 378.57 56203 +1930 178 22.17 16.17 20.52 0.71 576.34 277.11 56179 +1930 179 18.79 12.79 17.14 0.12 477.44 285.86 56150 +1930 180 17.55 11.55 15.9 0 444.98 384.81 56116 +1930 181 22.83 16.83 21.18 0.07 597.55 274.96 56078 +1930 182 21.16 15.16 19.51 0 545.11 372.8 56035 +1930 183 23.18 17.18 21.53 0.27 609.06 273.67 55987 +1930 184 21.52 15.52 19.87 0.03 556.07 278.37 55935 +1930 185 21.15 15.15 19.5 0.9 544.81 279.31 55879 +1930 186 22.73 16.73 21.08 0.06 594.29 274.65 55818 +1930 187 26.61 20.61 24.96 0 732.23 348.99 55753 +1930 188 25.38 19.38 23.73 0 685.84 354.53 55684 +1930 189 25.68 19.68 24.03 0.13 696.92 264.73 55611 +1930 190 24.09 18.09 22.44 2.03 639.89 269.75 55533 +1930 191 25.5 19.5 23.85 0.28 690.25 264.89 55451 +1930 192 22.68 16.68 21.03 0 592.67 364.86 55366 +1930 193 23.07 17.07 21.42 0 605.43 363.05 55276 +1930 194 22.48 16.48 20.83 1.94 586.22 273.86 55182 +1930 195 16.35 10.35 14.7 0.05 415.37 288.67 55085 +1930 196 20.85 14.85 19.2 0.44 535.82 277.87 54984 +1930 197 21.73 15.73 20.08 0.14 562.55 275.15 54879 +1930 198 23.25 17.25 21.6 0.42 611.39 270.43 54770 +1930 199 20.27 14.27 18.62 0.79 518.8 278.46 54658 +1930 200 19.09 13.09 17.44 0 485.59 374.75 54542 +1930 201 19.75 13.75 18.1 0 503.94 372.14 54423 +1930 202 20 14 18.35 0.07 511.04 278.06 54301 +1930 203 18.37 12.37 16.72 0 466.23 375.44 54176 +1930 204 22.51 16.51 20.86 0.07 587.18 270.55 54047 +1930 205 19.12 13.12 17.47 1.08 486.41 279.05 53915 +1930 206 17.02 11.02 15.37 0.01 431.69 283.32 53780 +1930 207 18.82 12.82 17.17 0 478.25 371.78 53643 +1930 208 22.6 16.6 20.95 0 590.08 358.04 53502 +1930 209 22.71 16.71 21.06 0.38 593.64 267.73 53359 +1930 210 21.99 15.99 20.34 0.06 570.66 269.31 53213 +1930 211 25.76 19.76 24.11 0.06 699.9 257.11 53064 +1930 212 26.22 20.22 24.57 0.43 717.24 254.95 52913 +1930 213 23.35 17.35 21.7 1.09 614.73 263.68 52760 +1930 214 22.85 16.85 21.2 0.59 598.2 264.6 52604 +1930 215 22.89 16.89 21.24 0 599.51 351.99 52445 +1930 216 21.87 15.87 20.22 0.15 566.91 266.11 52285 +1930 217 23.92 17.92 22.27 0.09 634.03 259.53 52122 +1930 218 26.76 20.76 25.11 0 738.06 332.75 51958 +1930 219 27.68 21.68 26.03 0.76 774.71 245.46 51791 +1930 220 22.77 16.77 21.12 0.38 595.59 260.87 51622 +1930 221 24.82 18.82 23.17 0 665.56 338.62 51451 +1930 222 22.97 16.97 21.32 0.03 602.13 258.8 51279 +1930 223 21.58 15.58 19.93 0 557.92 349.06 51105 +1930 224 23.36 17.36 21.71 0 615.06 341.41 50929 +1930 225 22.79 16.79 21.14 0 596.25 342.48 50751 +1930 226 26.7 20.7 25.05 0 735.72 324.99 50572 +1930 227 26.86 20.86 25.21 0.38 741.97 242.28 50392 +1930 228 24.85 18.85 23.2 0.52 666.63 248.08 50210 +1930 229 19.27 13.27 17.62 0 490.54 349.6 50026 +1930 230 21.45 15.45 19.8 0 553.93 341.26 49842 +1930 231 18.59 12.59 16.94 0.15 472.07 261.66 49656 +1930 232 22.28 16.28 20.63 0 579.83 335.57 49469 +1930 233 21.24 15.24 19.59 0 547.53 337.79 49280 +1930 234 19.95 13.95 18.3 0.68 509.61 255.43 49091 +1930 235 20.13 14.13 18.48 0.77 514.76 253.89 48900 +1930 236 15.78 9.78 14.13 0.35 401.91 261.88 48709 +1930 237 13.22 7.22 11.57 0.85 345.94 264.94 48516 +1930 238 13.06 7.06 11.41 0 342.67 351.86 48323 +1930 239 16.75 10.75 15.1 0.1 425.05 256.38 48128 +1930 240 20.61 14.61 18.96 0.09 528.72 246.8 47933 +1930 241 21.14 15.14 19.49 2.52 544.51 244.25 47737 +1930 242 22.01 16.01 20.36 1.12 571.29 240.79 47541 +1930 243 16.05 10.05 14.4 0.23 408.24 252.3 47343 +1930 244 18.46 12.46 16.81 0 468.61 328.33 47145 +1930 245 20.73 14.73 19.08 0 532.26 319.82 46947 +1930 246 22.08 16.08 20.43 0.93 573.49 235.14 46747 +1930 247 24.31 18.31 22.66 0.06 647.54 227.82 46547 +1930 248 18.24 12.24 16.59 0.31 462.8 241 46347 +1930 249 16.57 10.57 14.92 0.04 420.67 242.64 46146 +1930 250 15.37 9.37 13.72 0 392.46 324.34 45945 +1930 251 16.22 10.22 14.57 1.09 412.27 240.19 45743 +1930 252 14.23 8.23 12.58 0.05 367.17 241.84 45541 +1930 253 15 9 13.35 0.03 384.09 239.01 45339 +1930 254 18.42 12.42 16.77 0.35 467.55 231.28 45136 +1930 255 18.65 12.65 17 0 473.68 305.52 44933 +1930 256 24.33 18.33 22.68 0.23 648.23 214.22 44730 +1930 257 19.93 13.93 18.28 0.5 509.04 223.25 44527 +1930 258 18.6 12.6 16.95 0 472.34 298.95 44323 +1930 259 20.94 14.94 19.29 0.51 538.51 217.56 44119 +1930 260 16.84 10.84 15.19 0.63 427.25 223.86 43915 +1930 261 19.72 13.72 18.07 0.05 503.09 216.62 43711 +1930 262 19.75 13.75 18.1 0 503.94 286.42 43507 +1930 263 19.25 13.25 17.6 0 489.98 285.34 43303 +1930 264 22.2 16.2 20.55 0 577.29 274.47 43099 +1930 265 24.17 18.17 22.52 0.11 642.66 199.39 42894 +1930 266 21.4 15.4 19.75 0.83 552.4 204.15 42690 +1930 267 20.13 14.13 18.48 0.44 514.76 204.86 42486 +1930 268 21.79 15.79 20.14 0.22 564.42 199.52 42282 +1930 269 19.83 13.83 18.18 0.77 506.2 201.75 42078 +1930 270 17.91 11.91 16.26 0.58 454.2 203.35 41875 +1930 271 19.51 13.51 17.86 0 497.2 264.71 41671 +1930 272 20.16 14.16 18.51 0 515.63 260.4 41468 +1930 273 25.27 19.27 23.62 0.77 681.82 182.05 41265 +1930 274 19.42 13.42 17.77 0.6 494.69 192.91 41062 +1930 275 12.74 6.74 11.09 0.16 336.22 200.98 40860 +1930 276 14.03 8.03 12.38 0 362.88 263.07 40658 +1930 277 19.71 13.71 18.06 0 502.81 248.64 40456 +1930 278 15.8 9.8 14.15 0 402.38 254.31 40255 +1930 279 11.77 5.77 10.12 0 317.3 258.36 40054 +1930 280 11.42 5.42 9.77 0 310.69 256.21 39854 +1930 281 15.82 9.82 14.17 0 402.84 246.19 39654 +1930 282 13.72 7.72 12.07 0.92 356.31 185.37 39455 +1930 283 15.58 9.58 13.93 0.42 397.27 180.85 39256 +1930 284 15.57 9.57 13.92 0.75 397.04 178.63 39058 +1930 285 15.96 9.96 14.31 0.61 406.12 176.15 38861 +1930 286 15.93 9.93 14.28 0.99 405.42 174.15 38664 +1930 287 16.65 10.65 15 0.23 422.61 170.99 38468 +1930 288 18.01 12.01 16.36 1.81 456.79 166.97 38273 +1930 289 15.1 9.1 13.45 0.39 386.34 169.07 38079 +1930 290 12.06 6.06 10.41 0.18 322.85 170.43 37885 +1930 291 10.22 4.22 8.57 0.64 288.95 170.2 37693 +1930 292 9.25 3.25 7.6 0.47 272.34 169.03 37501 +1930 293 8.5 2.5 6.85 0.27 260.06 167.59 37311 +1930 294 10.61 4.61 8.96 0 295.87 218.11 37121 +1930 295 12.17 6.17 10.52 0.25 324.99 159.95 36933 +1930 296 12.69 6.69 11.04 0.18 335.22 157.49 36745 +1930 297 12.05 6.05 10.4 1.34 322.66 156.1 36560 +1930 298 11.37 5.37 9.72 2.63 309.76 154.8 36375 +1930 299 10.06 4.06 8.41 0.86 286.15 153.88 36191 +1930 300 10.9 4.9 9.25 0.6 301.11 151.15 36009 +1930 301 12.07 6.07 10.42 0.28 323.05 148.2 35829 +1930 302 13.12 7.12 11.47 0.07 343.89 145.24 35650 +1930 303 11.28 5.28 9.63 0 308.09 193.4 35472 +1930 304 14.54 8.54 12.89 0.01 373.9 140.06 35296 +1930 305 10.19 4.19 8.54 0.47 288.42 142.08 35122 +1930 306 11.92 5.92 10.27 0.18 320.16 138.93 34950 +1930 307 15.94 9.94 14.29 0.07 405.65 133.04 34779 +1930 308 14.13 8.13 12.48 0.71 365.02 133.06 34610 +1930 309 9.79 3.79 8.14 1.88 281.48 135.16 34444 +1930 310 7.38 1.38 5.73 0 242.61 180.03 34279 +1930 311 12.75 6.75 11.1 0 336.42 172.36 34116 +1930 312 14.39 8.39 12.74 0 370.63 167.72 33956 +1930 313 11.55 5.55 9.9 0 313.13 169.05 33797 +1930 314 11.51 5.51 9.86 0 312.38 167.17 33641 +1930 315 9.49 3.49 7.84 0.15 276.37 125.03 33488 +1930 316 9.42 3.42 7.77 0 275.19 164.6 33337 +1930 317 10.56 4.56 8.91 0.19 294.97 120.99 33188 +1930 318 8.04 2.04 6.39 0 252.77 161.31 33042 +1930 319 11.13 5.13 9.48 0 305.31 156.77 32899 +1930 320 8.83 2.83 7.18 0.06 265.4 117.81 32758 +1930 321 8.45 2.45 6.8 0 259.26 155.31 32620 +1930 322 10.53 4.53 8.88 0.01 294.44 113.73 32486 +1930 323 10.18 4.18 8.53 0 288.25 150.38 32354 +1930 324 13.27 7.27 11.62 0.29 346.96 108.92 32225 +1930 325 15.13 9.13 13.48 0 387.01 141.39 32100 +1930 326 15.45 9.45 13.8 0 394.29 139.61 31977 +1930 327 14.67 8.67 13.02 0.05 376.76 104.07 31858 +1930 328 10.24 4.24 8.59 0.1 289.3 106.04 31743 +1930 329 7.92 1.92 6.27 0 250.9 141.84 31631 +1930 330 5.7 -0.3 4.05 0 218.33 141.98 31522 +1930 331 7.42 1.42 5.77 0.01 243.22 104.6 31417 +1930 332 8.3 2.3 6.65 0.25 256.87 102.88 31316 +1930 333 10.03 4.03 8.38 0.07 285.63 101.03 31218 +1930 334 12.46 6.46 10.81 0 330.66 131.4 31125 +1930 335 4.52 -1.48 2.87 0 202.55 136.39 31035 +1930 336 6.55 0.55 4.9 0 230.34 134.03 30949 +1930 337 4.69 -1.31 3.04 0.53 204.76 100.16 30867 +1930 338 3.42 -2.58 1.77 0.17 188.74 100 30790 +1930 339 3.43 -2.57 1.78 0.14 188.86 99.4 30716 +1930 340 1.16 -4.84 -0.49 0.04 162.88 99.7 30647 +1930 341 -2.27 -8.27 -3.92 0 129.49 133.41 30582 +1930 342 -0.96 -6.96 -2.61 0.01 141.47 142.39 30521 +1930 343 2.25 -3.75 0.6 0.35 174.94 97.41 30465 +1930 344 4.71 -1.29 3.06 0.02 205.02 95.58 30413 +1930 345 4.35 -1.65 2.7 0.02 200.36 95.41 30366 +1930 346 6.25 0.25 4.6 0.2 226.04 94.15 30323 +1930 347 5.83 -0.17 4.18 0.2 220.13 93.9 30284 +1930 348 5.4 -0.6 3.75 0.21 214.22 93.84 30251 +1930 349 9.25 3.25 7.6 1.64 272.34 91.6 30221 +1930 350 9.24 3.24 7.59 0.32 272.17 91.36 30197 +1930 351 9.86 3.86 8.21 0 282.68 121.12 30177 +1930 352 3.71 -2.29 2.06 0.25 192.3 93.78 30162 +1930 353 3.95 -2.05 2.3 0 195.29 124.85 30151 +1930 354 2.2 -3.8 0.55 0 174.37 125.71 30145 +1930 355 5.49 -0.51 3.84 0 215.45 123.94 30144 +1930 356 6.54 0.54 4.89 0 230.2 123.32 30147 +1930 357 5.42 -0.58 3.77 0 214.49 124.07 30156 +1930 358 4.14 -1.86 2.49 1.31 197.68 93.66 30169 +1930 359 2.69 -3.31 1.04 0.69 180.03 94.32 30186 +1930 360 2.82 -3.18 1.17 0.17 181.55 94.55 30208 +1930 361 2.41 -3.59 0.76 0.48 176.78 94.95 30235 +1930 362 -0.93 -6.93 -2.58 1.44 141.76 144.56 30267 +1930 363 -2.68 -8.68 -4.33 0 125.93 177.87 30303 +1930 364 -2.05 -8.05 -3.7 0 131.44 177.98 30343 +1930 365 -2.32 -8.32 -3.97 0 129.05 178.59 30388 +1931 1 -4.12 -10.12 -5.77 0 114.08 180.02 30438 +1931 2 -3.31 -9.31 -4.96 0 120.62 180.41 30492 +1931 3 0.39 -5.61 -1.26 0 154.8 179.79 30551 +1931 4 -2.05 -8.05 -3.7 0 131.44 181.6 30614 +1931 5 0.11 -5.89 -1.54 1.14 151.95 147.82 30681 +1931 6 2.2 -3.8 0.55 0.32 174.37 147.36 30752 +1931 7 0.88 -5.12 -0.77 0.13 159.9 148.21 30828 +1931 8 0.55 -5.45 -1.1 0.44 156.45 149.25 30907 +1931 9 5.78 -0.22 4.13 0 219.44 180.99 30991 +1931 10 4.96 -1.04 3.31 0 208.32 182.03 31079 +1931 11 5.9 -0.1 4.25 0 221.11 181.52 31171 +1931 12 3.72 -2.28 2.07 0 192.42 183.25 31266 +1931 13 2.66 -3.34 1.01 0 179.67 184.98 31366 +1931 14 1.11 -4.89 -0.54 0 162.35 186.97 31469 +1931 15 2.64 -3.36 0.99 0.04 179.44 150.92 31575 +1931 16 6.79 0.79 5.14 0 233.83 143.6 31686 +1931 17 9.38 3.38 7.73 0 274.51 143.23 31800 +1931 18 8.49 2.49 6.84 0.14 259.9 109.38 31917 +1931 19 9.11 3.11 7.46 0.03 270.01 110.43 32038 +1931 20 10.06 4.06 8.41 0.11 286.15 110.97 32161 +1931 21 8.77 2.77 7.12 0.36 264.42 113.29 32289 +1931 22 8.44 2.44 6.79 0 259.1 153.06 32419 +1931 23 2.78 -3.22 1.13 0.41 181.08 119.09 32552 +1931 24 -1.73 -7.73 -3.38 0.19 134.32 163.3 32688 +1931 25 -1.01 -7.01 -2.66 0 141 205.5 32827 +1931 26 2.04 -3.96 0.39 0 172.56 205.46 32969 +1931 27 1.89 -4.11 0.24 0 170.88 207.17 33114 +1931 28 0.5 -5.5 -1.15 0 155.94 209.91 33261 +1931 29 3.96 -2.04 2.31 0 195.41 170.56 33411 +1931 30 3.12 -2.88 1.47 0 185.11 173.36 33564 +1931 31 6.21 0.21 4.56 0 225.47 173.55 33718 +1931 32 8.38 2.38 6.73 0 258.14 173.81 33875 +1931 33 6 0 4.35 0.14 222.51 133.82 34035 +1931 34 5.34 -0.66 3.69 0 213.41 181.13 34196 +1931 35 1.7 -4.3 0.05 0 168.77 185.75 34360 +1931 36 3.56 -2.44 1.91 0.55 190.45 140.31 34526 +1931 37 6.28 0.28 4.63 0 226.47 187.44 34694 +1931 38 4.78 -1.22 3.13 0.13 205.94 143.52 34863 +1931 39 5.09 -0.91 3.44 0 210.05 193.73 35035 +1931 40 0.22 -5.78 -1.43 0.67 153.07 149.72 35208 +1931 41 0.19 -5.81 -1.46 0 152.76 202.3 35383 +1931 42 -0.6 -6.6 -2.25 0.58 144.92 192.68 35560 +1931 43 -4.57 -10.57 -6.22 0 110.58 248.49 35738 +1931 44 -3.84 -9.84 -5.49 0 116.3 250.59 35918 +1931 45 3.38 -2.62 1.73 0.02 188.25 195.79 36099 +1931 46 4.79 -1.21 3.14 0 206.07 249.34 36282 +1931 47 4.7 -1.3 3.05 0.04 204.89 197.73 36466 +1931 48 5.94 -0.06 4.29 0.54 221.67 162.73 36652 +1931 49 8.07 2.07 6.42 0.04 253.24 163.26 36838 +1931 50 6.5 0.5 4.85 1.67 229.62 166.41 37026 +1931 51 4.2 -1.8 2.55 0 198.45 226.89 37215 +1931 52 2 -4 0.35 0.06 172.11 173.57 37405 +1931 53 2.37 -3.63 0.72 0.73 176.32 175.6 37596 +1931 54 1.83 -4.17 0.18 1.09 170.21 177.99 37788 +1931 55 4.72 -1.28 3.07 0.01 205.16 178.51 37981 +1931 56 3.95 -2.05 2.3 0.02 195.29 181.04 38175 +1931 57 0.44 -5.56 -1.21 0.19 155.32 185.22 38370 +1931 58 -1.33 -7.33 -2.98 0.8 137.99 224.52 38565 +1931 59 -0.25 -6.25 -1.9 0 148.35 289.18 38761 +1931 60 -0.54 -6.54 -2.19 0 145.51 292.11 38958 +1931 61 -1.31 -7.31 -2.96 0.33 138.18 231.28 39156 +1931 62 -0.09 -6.09 -1.74 0.18 149.94 233.07 39355 +1931 63 -0.19 -6.19 -1.84 0.38 148.95 236.15 39553 +1931 64 2.45 -3.55 0.8 0 177.24 302.91 39753 +1931 65 1.39 -4.61 -0.26 0.51 165.37 238.94 39953 +1931 66 4.98 -1.02 3.33 0.03 208.58 237.98 40154 +1931 67 3.34 -2.66 1.69 0 187.77 309.25 40355 +1931 68 2.92 -3.08 1.27 0.02 182.73 242.81 40556 +1931 69 0.33 -5.67 -1.32 0 154.19 316.6 40758 +1931 70 1.18 -4.82 -0.47 0.36 163.1 247.56 40960 +1931 71 1.66 -4.34 0.01 0.05 168.32 249.15 41163 +1931 72 -0.79 -6.79 -2.44 0 143.09 325.36 41366 +1931 73 4.14 -1.86 2.49 0 197.68 323.39 41569 +1931 74 6.8 0.8 5.15 0 233.98 322.48 41772 +1931 75 7.77 1.77 6.12 0 248.57 323.12 41976 +1931 76 11.58 5.58 9.93 0 313.7 288.55 42179 +1931 77 11.83 5.83 10.18 0 318.44 290.71 42383 +1931 78 13.46 7.46 11.81 0.35 350.88 217.88 42587 +1931 79 13.53 7.53 11.88 0 352.34 293.05 42791 +1931 80 8.95 2.95 7.3 0 267.37 302.95 42996 +1931 81 6.58 0.58 4.93 0 230.78 308.64 43200 +1931 82 6.69 0.69 5.04 0.21 232.37 233.38 43404 +1931 83 4.56 -1.44 2.91 0.22 203.07 237.11 43608 +1931 84 4.09 -1.91 2.44 0 197.05 319.22 43812 +1931 85 3.52 -2.48 1.87 2.29 189.96 241.76 44016 +1931 86 2.91 -3.09 1.26 0.01 182.61 244.06 44220 +1931 87 -1.32 -7.32 -2.97 0 138.09 331.64 44424 +1931 88 1.08 -4.92 -0.57 0 162.03 332.11 44627 +1931 89 2.78 -3.22 1.13 0 181.08 332.84 44831 +1931 90 7.33 1.33 5.68 0 241.86 329.96 45034 +1931 91 13.92 7.92 12.27 0.13 360.53 240.92 45237 +1931 92 15.18 9.18 13.53 0 388.14 320.76 45439 +1931 93 12.69 6.69 11.04 0.05 335.22 246.03 45642 +1931 94 12.12 6.12 10.47 0 324.02 331.25 45843 +1931 95 12.22 6.22 10.57 0.13 325.96 249.89 46045 +1931 96 12.13 6.13 10.48 0.28 324.21 251.6 46246 +1931 97 12.48 6.48 10.83 0 331.05 336.84 46446 +1931 98 13.91 7.91 12.26 0.15 360.32 251.94 46647 +1931 99 12.66 6.66 11.01 0.5 334.62 255.33 46846 +1931 100 13.4 7.4 11.75 0 349.64 340.9 47045 +1931 101 16.68 10.68 15.03 0 423.34 335.34 47243 +1931 102 16.86 10.86 15.21 0.13 427.74 252.56 47441 +1931 103 13.29 7.29 11.64 0 347.37 346.76 47638 +1931 104 8.64 2.64 6.99 0 262.32 356.96 47834 +1931 105 8.28 2.28 6.63 0.39 256.55 269.5 48030 +1931 106 7.82 1.82 6.17 0 249.34 361.7 48225 +1931 107 10.08 4.08 8.43 0.47 286.5 269.83 48419 +1931 108 7.56 1.56 5.91 0 245.35 365.56 48612 +1931 109 6.87 0.87 5.22 0.2 235.01 276.15 48804 +1931 110 7.16 1.16 5.51 0 239.31 369.23 48995 +1931 111 9.71 3.71 8.06 0 280.11 366.79 49185 +1931 112 11.86 5.86 10.21 0.68 319.01 273.29 49374 +1931 113 9.56 3.56 7.91 0 277.55 369.94 49561 +1931 114 11.12 5.12 9.47 0 305.13 368.66 49748 +1931 115 9.48 3.48 7.83 0.24 276.2 279.78 49933 +1931 116 5.6 -0.4 3.95 0.07 216.95 285.12 50117 +1931 117 6.88 0.88 5.23 1.05 235.16 284.79 50300 +1931 118 8.87 2.87 7.22 0.89 266.06 283.48 50481 +1931 119 7.16 1.16 5.51 0 239.31 381.88 50661 +1931 120 5.02 -0.98 3.37 0.61 209.11 289.55 50840 +1931 121 17.79 11.79 16.14 0.03 451.11 271.36 51016 +1931 122 16.16 10.16 14.51 0.37 410.84 275.57 51191 +1931 123 17.09 11.09 15.44 0 433.42 365.96 51365 +1931 124 20.92 14.92 19.27 0 537.91 355.21 51536 +1931 125 22.77 16.77 21.12 0.32 595.59 262.09 51706 +1931 126 18.25 12.25 16.6 0 463.06 365.66 51874 +1931 127 19.42 13.42 17.77 0 494.69 362.95 52039 +1931 128 22.05 16.05 20.4 0 572.55 354.91 52203 +1931 129 20.39 14.39 18.74 0.19 522.29 271.18 52365 +1931 130 22.96 16.96 21.31 0.33 601.8 264.77 52524 +1931 131 26.24 20.24 24.59 0.46 718 254.82 52681 +1931 132 24.29 18.29 22.64 0.32 646.84 261.88 52836 +1931 133 26.71 20.71 25.06 0.19 736.11 254.21 52989 +1931 134 24.75 18.75 23.1 0 663.06 348.55 53138 +1931 135 24.69 18.69 23.04 0 660.93 349.46 53286 +1931 136 21.24 15.24 19.59 0 547.53 363.64 53430 +1931 137 21.65 15.65 20 0 560.08 362.84 53572 +1931 138 19.41 13.41 17.76 0.11 494.41 278.34 53711 +1931 139 17.9 11.9 16.25 0.29 453.94 282.35 53848 +1931 140 17.54 11.54 15.89 1.11 444.72 283.51 53981 +1931 141 18.45 12.45 16.8 0.05 468.34 281.8 54111 +1931 142 19.65 13.65 18 0 501.12 372.42 54238 +1931 143 16.77 10.77 15.12 0 425.54 381.66 54362 +1931 144 15.02 9.02 13.37 0 384.54 386.77 54483 +1931 145 17.92 11.92 16.27 0 454.46 379.3 54600 +1931 146 16.84 10.84 15.19 0 427.25 382.8 54714 +1931 147 16.51 10.51 14.86 0 419.22 384.19 54824 +1931 148 18.09 12.09 16.44 0 458.88 380.02 54931 +1931 149 18.96 12.96 17.31 0.08 482.04 283.23 55034 +1931 150 22.8 16.8 21.15 0 596.57 364.35 55134 +1931 151 19.18 13.18 17.53 0.01 488.06 283.25 55229 +1931 152 19.25 13.25 17.6 0 489.98 377.54 55321 +1931 153 17.24 11.24 15.59 0 437.16 383.92 55409 +1931 154 17.89 11.89 16.24 0 453.69 382.33 55492 +1931 155 19.23 13.23 17.58 0 489.43 378.36 55572 +1931 156 18.91 12.91 17.26 0.4 480.69 284.78 55648 +1931 157 15.83 9.83 14.18 0.45 403.08 291.62 55719 +1931 158 19.17 13.17 17.52 0.41 487.78 284.41 55786 +1931 159 20.81 14.81 19.16 0.03 534.64 280.43 55849 +1931 160 19.91 13.91 18.26 0 508.47 377.2 55908 +1931 161 17.22 11.22 15.57 0.11 436.66 289.24 55962 +1931 162 16.03 10.03 14.38 0 407.77 389.03 56011 +1931 163 18.3 12.3 16.65 0 464.38 382.72 56056 +1931 164 21.58 15.58 19.93 0 557.92 371.68 56097 +1931 165 25.99 19.99 24.34 0 708.52 353.27 56133 +1931 166 25.49 19.49 23.84 0.16 689.89 266.75 56165 +1931 167 26.58 20.58 24.93 0 731.07 350.45 56192 +1931 168 24.72 18.72 23.07 0.34 661.99 269.37 56214 +1931 169 27.51 21.51 25.86 1.16 767.83 259.41 56231 +1931 170 23.29 17.29 21.64 0.27 612.72 273.93 56244 +1931 171 23.99 17.99 22.34 0.12 636.44 271.79 56252 +1931 172 24.67 18.67 23.02 0 660.22 359.44 56256 +1931 173 25.06 19.06 23.41 0 674.19 357.69 56255 +1931 174 25.58 19.58 23.93 0 693.21 355.24 56249 +1931 175 27.13 21.13 25.48 0.11 752.62 260.81 56238 +1931 176 25.31 19.31 23.66 0 683.28 356.42 56223 +1931 177 25.69 19.69 24.04 0.18 697.29 265.93 56203 +1931 178 26.32 20.32 24.67 0.52 721.06 263.72 56179 +1931 179 28.44 22.44 26.79 1.41 806.14 255.54 56150 +1931 180 28.49 22.49 26.84 0.61 808.24 255.26 56116 +1931 181 26.45 20.45 24.8 0.03 726.05 263.04 56078 +1931 182 22.8 16.8 21.15 0 596.57 366.59 56035 +1931 183 20.25 14.25 18.6 0 518.22 375.82 55987 +1931 184 22.01 16.01 20.36 0.01 571.29 276.99 55935 +1931 185 23.78 17.78 22.13 0.11 629.24 271.65 55879 +1931 186 22.31 16.31 20.66 0 580.78 367.84 55818 +1931 187 25.32 19.32 23.67 0 683.64 355.06 55753 +1931 188 24.81 18.81 23.16 0 665.2 357.08 55684 +1931 189 25.8 19.8 24.15 0 701.39 352.42 55611 +1931 190 26.42 20.42 24.77 0.09 724.89 261.84 55533 +1931 191 23.31 17.31 21.66 0 613.39 362.64 55451 +1931 192 21.6 15.6 19.95 0 558.54 368.96 55366 +1931 193 23.26 17.26 21.61 0 611.72 362.28 55276 +1931 194 25.13 19.13 23.48 0 676.72 354.1 55182 +1931 195 25.32 19.32 23.67 0 683.64 352.99 55085 +1931 196 25.29 19.29 23.64 0 682.55 352.73 54984 +1931 197 21.33 15.33 19.68 0.02 550.27 276.25 54879 +1931 198 21.3 15.3 19.65 0.07 549.35 276.01 54770 +1931 199 24.33 18.33 22.68 1.77 648.23 266.81 54658 +1931 200 24.09 18.09 22.44 0 639.89 356.38 54542 +1931 201 25.65 19.65 24 0 695.8 349.07 54423 +1931 202 24.39 18.39 22.74 0.02 650.34 265.58 54301 +1931 203 23.81 17.81 22.16 0.12 630.27 267.04 54176 +1931 204 27.67 21.67 26.02 0 774.3 337.81 54047 +1931 205 26.06 20.06 24.41 0 711.17 345.18 53915 +1931 206 23.36 17.36 21.71 0.43 615.06 267.25 53780 +1931 207 20.31 14.31 18.66 0.38 519.96 275.21 53643 +1931 208 24.65 18.65 23 0.49 659.51 262.27 53502 +1931 209 23.97 17.97 22.32 0.17 635.75 263.95 53359 +1931 210 24.02 18.02 22.37 0.43 637.47 263.34 53213 +1931 211 24.12 18.12 22.47 0 640.93 349.95 53064 +1931 212 24.81 18.81 23.16 0 665.2 346.26 52913 +1931 213 22.47 16.47 20.82 0.46 585.9 266.24 52760 +1931 214 25.46 19.46 23.81 0.4 688.78 256.47 52604 +1931 215 26.98 20.98 25.33 0.39 746.69 250.7 52445 +1931 216 30.04 24.04 28.39 0 875.82 317.27 52285 +1931 217 30.32 24.32 28.67 0.06 888.52 236.14 52122 +1931 218 26 20 24.35 1.03 708.9 252.21 51958 +1931 219 26.23 20.23 24.58 1.65 717.62 250.67 51791 +1931 220 26.84 20.84 25.19 0.06 741.19 247.87 51622 +1931 221 25.82 19.82 24.17 0.46 702.14 250.69 51451 +1931 222 21.37 15.37 19.72 0.26 551.49 263.19 51279 +1931 223 24.64 18.64 22.99 0.02 659.15 252.95 51105 +1931 224 22.99 16.99 21.34 0.76 602.79 257.13 50929 +1931 225 19.21 13.21 17.56 0 488.88 354.68 50751 +1931 226 21.32 15.32 19.67 0 549.96 346.66 50572 +1931 227 24.19 18.19 22.54 0.63 643.35 251 50392 +1931 228 20.88 14.88 19.23 0.3 536.72 259.26 50210 +1931 229 19.57 13.57 17.92 1.42 498.88 261.51 50026 +1931 230 17.95 11.95 16.3 0.14 455.24 264.14 49842 +1931 231 13.64 7.64 11.99 0.27 354.63 271.06 49656 +1931 232 18.74 12.74 17.09 0 476.09 347.08 49469 +1931 233 17.06 11.06 15.41 0.4 432.68 262.75 49280 +1931 234 17.16 11.16 15.51 0.36 435.17 261.47 49091 +1931 235 19.34 13.34 17.69 0.07 492.47 255.72 48900 +1931 236 20.7 14.7 19.05 0.16 531.38 251.47 48709 +1931 237 20.98 14.98 19.33 0.13 539.7 249.56 48516 +1931 238 17.6 11.6 15.95 0.09 446.25 255.86 48323 +1931 239 16.36 10.36 14.71 0 415.61 342.82 48128 +1931 240 19.07 13.07 17.42 0 485.04 333.75 47933 +1931 241 20.2 14.2 18.55 0 516.78 328.65 47737 +1931 242 22.59 16.59 20.94 0 589.76 319.05 47541 +1931 243 20.81 14.81 19.16 0.15 534.64 242.38 47343 +1931 244 15.25 9.25 13.6 0 389.73 336.42 47145 +1931 245 15.36 9.36 13.71 0 392.23 334.29 46947 +1931 246 15.87 9.87 14.22 0 404.01 331.11 46747 +1931 247 19 13 17.35 0 483.13 321.18 46547 +1931 248 25.25 19.25 23.6 0 681.09 298.28 46347 +1931 249 23.02 17.02 21.37 0 603.78 304.62 46146 +1931 250 22.93 16.93 21.28 0.21 600.82 227.29 45945 +1931 251 17.82 11.82 16.17 0.93 451.88 237.24 45743 +1931 252 17.78 11.78 16.13 1.4 450.85 235.7 45541 +1931 253 13.23 7.23 11.58 0.04 346.14 241.73 45339 +1931 254 13.86 7.86 12.21 0.19 359.26 239.16 45136 +1931 255 13.72 7.72 12.07 0 356.31 316.86 44933 +1931 256 13.44 7.44 11.79 0 350.47 315.1 44730 +1931 257 10.67 4.67 9.02 0 296.95 317.81 44527 +1931 258 12.6 6.6 10.95 0.83 333.43 234.06 44323 +1931 259 12.59 6.59 10.94 0.87 333.23 232.21 44119 +1931 260 12.25 6.25 10.6 0 326.54 307.79 43915 +1931 261 10.35 4.35 8.7 0.01 291.24 231.32 43711 +1931 262 10.07 4.07 8.42 0 286.32 306.42 43507 +1931 263 15.68 9.68 14.03 0.15 399.59 220.33 43303 +1931 264 15.55 9.55 13.9 1.34 396.58 218.6 43099 +1931 265 13.4 7.4 11.75 0.14 349.64 219.96 42894 +1931 266 17 11 15.35 0 431.19 283.48 42690 +1931 267 15.52 9.52 13.87 0 395.89 283.99 42486 +1931 268 14.69 8.69 13.04 0.01 377.2 212.31 42282 +1931 269 13.25 7.25 11.6 0 346.55 283.2 42078 +1931 270 10.24 4.24 8.59 0.34 289.3 214.02 41875 +1931 271 14.87 8.87 13.22 0.7 381.19 206.2 41671 +1931 272 13.66 7.66 12.01 1.65 355.05 205.82 41468 +1931 273 16.45 10.45 14.8 0.05 417.77 199.91 41265 +1931 274 15.65 9.65 14 0 398.89 265.51 41062 +1931 275 18.13 12.13 16.48 0 459.92 257.55 40860 +1931 276 16.84 10.84 15.19 0.19 427.25 193.27 40658 +1931 277 17.34 11.34 15.69 0 439.67 254.03 40456 +1931 278 15.07 9.07 13.42 0 385.66 255.69 40255 +1931 279 16.16 10.16 14.51 0 410.84 250.84 40054 +1931 280 12.12 6.12 10.47 0 324.02 255.17 39854 +1931 281 13.31 7.31 11.66 0.05 347.78 187.93 39654 +1931 282 11.94 5.94 10.29 0 320.54 249.94 39455 +1931 283 14.19 8.19 12.54 0 366.3 243.57 39256 +1931 284 13.66 7.66 12.01 0 355.05 241.44 39058 +1931 285 10.86 4.86 9.21 0.06 300.38 182.19 38861 +1931 286 11.42 5.42 9.77 0.14 310.69 179.53 38664 +1931 287 9.74 3.74 8.09 0 280.62 238.61 38468 +1931 288 10.19 4.19 8.54 0 288.42 235.24 38273 +1931 289 7.46 1.46 5.81 0 243.83 235.72 38079 +1931 290 9.1 3.1 7.45 0 269.84 231 37885 +1931 291 8.61 2.61 6.96 0 261.83 228.82 37693 +1931 292 10.38 4.38 8.73 0.77 291.77 168.03 37501 +1931 293 10.27 4.27 8.62 0.01 289.83 166.07 37311 +1931 294 9.66 3.66 8.01 0.93 279.26 164.43 37121 +1931 295 7.76 1.76 6.11 0.48 248.42 163.83 36933 +1931 296 9.61 3.61 7.96 0.06 278.4 160.38 36745 +1931 297 9.87 3.87 8.22 0 282.86 210.8 36560 +1931 298 12.33 6.33 10.68 0.04 328.11 153.88 36375 +1931 299 12.64 6.64 10.99 0 334.22 202 36191 +1931 300 14.39 8.39 12.74 0.01 370.63 147.7 36009 +1931 301 17.6 11.6 15.95 1.57 446.25 142 35829 +1931 302 16.12 10.12 14.47 0 409.89 189.28 35650 +1931 303 14.66 8.66 13.01 0 376.54 188.98 35472 +1931 304 15.65 9.65 14 0 398.89 185.11 35296 +1931 305 12.86 6.86 11.21 0 338.63 186.3 35122 +1931 306 13.04 7.04 11.39 0 342.26 183.86 34950 +1931 307 9.22 3.22 7.57 0 271.84 185.69 34779 +1931 308 11.93 5.93 10.28 0 320.35 180.17 34610 +1931 309 6.5 0.5 4.85 0 229.62 183.23 34444 +1931 310 5.25 -0.75 3.6 0.03 212.19 136.32 34279 +1931 311 2.38 -3.62 0.73 0.02 176.43 136.13 34116 +1931 312 7.1 1.1 5.45 0 238.41 175.43 33956 +1931 313 6.34 0.34 4.69 0.07 227.32 130.44 33797 +1931 314 5.82 -0.18 4.17 0.15 219.99 129.26 33641 +1931 315 10.01 4.01 8.36 0 285.28 166.2 33488 +1931 316 12.53 6.53 10.88 0 332.04 161.39 33337 +1931 317 11.72 5.72 10.07 0.25 316.34 120.1 33188 +1931 318 8.51 2.51 6.86 0 260.22 160.9 33042 +1931 319 7.43 1.43 5.78 0.58 243.37 120.08 32899 +1931 320 6.09 0.09 4.44 1.16 223.77 119.45 32758 +1931 321 4.18 -1.82 2.53 0.38 198.19 118.84 32620 +1931 322 1.96 -4.04 0.31 0 171.66 157.93 32486 +1931 323 4.77 -1.23 3.12 0.01 205.81 115.96 32354 +1931 324 5.06 -0.94 3.41 0.21 209.65 114.27 32225 +1931 325 3.46 -2.54 1.81 1.03 189.23 113.72 32100 +1931 326 3.11 -2.89 1.46 0.02 184.99 112.77 31977 +1931 327 4.18 -1.82 2.53 0.15 198.19 110.9 31858 +1931 328 7.71 1.71 6.06 0.35 247.65 107.61 31743 +1931 329 6.52 0.52 4.87 0.12 229.91 107.15 31631 +1931 330 6.33 0.33 4.68 0 227.18 141.55 31522 +1931 331 7.08 1.08 5.43 0 238.11 139.71 31417 +1931 332 6.35 0.35 4.7 0.01 227.47 103.94 31316 +1931 333 8.6 2.6 6.95 0 261.67 135.87 31218 +1931 334 8.55 2.55 6.9 0 260.86 134.82 31125 +1931 335 4.55 -1.45 2.9 0 202.94 136.37 31035 +1931 336 4.74 -1.26 3.09 0 205.42 135.18 30949 +1931 337 3.59 -2.41 1.94 0.78 190.82 100.64 30867 +1931 338 -1.88 -7.88 -3.53 0.33 132.96 145.71 30790 +1931 339 0.4 -5.6 -1.25 0 154.91 177.97 30716 +1931 340 1.21 -4.79 -0.44 0 163.42 176.8 30647 +1931 341 3.11 -2.89 1.46 0 184.99 174.62 30582 +1931 342 -0.1 -6.1 -1.75 0 149.84 175.45 30521 +1931 343 -1.78 -7.78 -3.43 0 133.87 175.37 30465 +1931 344 -1.64 -7.64 -3.29 0 135.14 174.25 30413 +1931 345 0.67 -5.33 -0.98 0 157.7 172.85 30366 +1931 346 2.89 -3.11 1.24 0.03 182.38 95.58 30323 +1931 347 7.08 1.08 5.43 0 238.11 124.4 30284 +1931 348 4.36 -1.64 2.71 0.65 200.49 94.29 30251 +1931 349 3.43 -2.57 1.78 0 188.86 125.84 30221 +1931 350 1.64 -4.36 -0.01 0 168.1 126.39 30197 +1931 351 2.64 -3.36 0.99 0 179.44 125.69 30177 +1931 352 6.11 0.11 4.46 0 224.06 123.66 30162 +1931 353 7.37 1.37 5.72 0 242.46 122.78 30151 +1931 354 3.82 -2.18 2.17 0 193.66 124.89 30145 +1931 355 2.44 -3.56 0.79 0 177.12 125.59 30144 +1931 356 0.07 -5.93 -1.58 0 151.55 126.69 30147 +1931 357 3.34 -2.66 1.69 0 187.77 125.22 30156 +1931 358 -0.06 -6.06 -1.71 0 150.24 126.89 30169 +1931 359 -1.62 -7.62 -3.27 0 135.32 127.62 30186 +1931 360 0.23 -5.77 -1.42 0.01 153.17 95.44 30208 +1931 361 3.81 -2.19 2.16 0 193.54 125.88 30235 +1931 362 1.8 -4.2 0.15 0 169.87 127.33 30267 +1931 363 0.47 -5.53 -1.18 0 155.63 128.52 30303 +1931 364 -0.92 -6.92 -2.57 0 141.85 129.5 30343 +1931 365 2.99 -3.01 1.34 0 183.56 128.3 30388 +1932 1 1.11 -4.89 -0.54 0 162.35 130.11 30438 +1932 2 1.39 -4.61 -0.26 0 165.37 130.71 30492 +1932 3 1.54 -4.46 -0.11 0 167 131.59 30551 +1932 4 0.35 -5.65 -1.3 0 154.39 133.05 30614 +1932 5 -0.35 -6.35 -2 0 147.37 134.01 30681 +1932 6 -0.54 -6.54 -2.19 0 145.51 134.98 30752 +1932 7 -1.13 -7.13 -2.78 0 139.86 136.03 30828 +1932 8 1.15 -4.85 -0.5 0 162.78 136.53 30907 +1932 9 0.73 -5.27 -0.92 0 158.33 137.99 30991 +1932 10 5.49 -0.51 3.84 0 215.45 136.71 31079 +1932 11 4.09 -1.91 2.44 0.06 197.05 103.91 31171 +1932 12 3.45 -2.55 1.8 0.01 189.1 104.94 31266 +1932 13 1.93 -4.07 0.28 0 171.33 142.36 31366 +1932 14 3.99 -2.01 2.34 0.17 195.79 107.03 31469 +1932 15 4.65 -1.35 3 0.28 204.24 107.81 31575 +1932 16 2.35 -3.65 0.7 0 176.09 146.37 31686 +1932 17 5.26 -0.74 3.61 0.3 212.33 109.74 31800 +1932 18 2.44 -3.56 0.79 0 177.12 149.91 31917 +1932 19 2.78 -3.22 1.13 0 181.08 151.66 32038 +1932 20 3.3 -2.7 1.65 0 187.28 152.95 32161 +1932 21 5.36 -0.64 3.71 0 213.68 153.65 32289 +1932 22 -1.99 -7.99 -3.64 0 131.98 159.37 32419 +1932 23 -5.11 -11.11 -6.76 0 106.5 162.35 32552 +1932 24 -2.63 -8.63 -4.28 0.39 126.36 164.17 32688 +1932 25 1.59 -4.41 -0.06 0 167.55 204.59 32827 +1932 26 1.7 -4.3 0.05 0.09 168.77 164.75 32969 +1932 27 1.94 -4.06 0.29 0.19 171.44 165.76 33114 +1932 28 4.52 -1.48 2.87 0 202.55 167.81 33261 +1932 29 3.76 -2.24 2.11 0 192.92 170.7 33411 +1932 30 6.98 0.98 5.33 0 236.63 170.58 33564 +1932 31 7.35 1.35 5.7 0 242.16 172.62 33718 +1932 32 4.4 -1.6 2.75 0 201 176.99 33875 +1932 33 7.22 1.22 5.57 0 240.2 177.43 34035 +1932 34 1.66 -4.34 0.01 0 168.32 183.61 34196 +1932 35 0.6 -5.4 -1.05 0 156.97 186.39 34360 +1932 36 0.53 -5.47 -1.12 0 156.25 188.97 34526 +1932 37 0.5 -5.5 -1.15 0.14 155.94 143.57 34694 +1932 38 -3.2 -9.2 -4.85 0.01 121.53 184.94 34863 +1932 39 -3.53 -9.53 -5.18 0 118.81 236.56 35035 +1932 40 -4.79 -10.79 -6.44 0.04 108.9 189.17 35208 +1932 41 -4.79 -10.79 -6.44 0.1 108.9 191.25 35383 +1932 42 -1.96 -7.96 -3.61 0.05 132.25 192.19 35560 +1932 43 0.15 -5.85 -1.5 0 152.36 245.09 35738 +1932 44 1.46 -4.54 -0.19 0.18 166.13 194.17 35918 +1932 45 1.66 -4.34 0.01 0 168.32 248.67 36099 +1932 46 3.82 -2.18 2.17 0.1 193.66 159.83 36282 +1932 47 -0.82 -6.82 -2.47 0 142.8 219.03 36466 +1932 48 -1.46 -7.46 -3.11 0 136.79 222.23 36652 +1932 49 0.36 -5.64 -1.29 0.35 154.5 167.98 36838 +1932 50 -0.48 -6.48 -2.13 0 146.09 227.19 37026 +1932 51 -0.63 -6.63 -2.28 0 144.63 230.29 37215 +1932 52 -1.19 -7.19 -2.84 0 139.3 233.49 37405 +1932 53 -4.36 -10.36 -6.01 0 112.2 238.15 37596 +1932 54 -6.59 -12.59 -8.24 0 95.99 241.94 37788 +1932 55 -9.54 -15.54 -11.19 0 77.7 246.09 37981 +1932 56 -6.39 -12.39 -8.04 0 97.36 247.69 38175 +1932 57 -3.45 -9.45 -5.1 0 119.47 249.27 38370 +1932 58 -2.33 -8.33 -3.98 0 128.97 251.65 38565 +1932 59 -1.5 -7.5 -3.15 0 136.42 253.93 38761 +1932 60 7.3 1.3 5.65 0 241.41 249.58 38958 +1932 61 7.08 1.08 5.43 0.1 238.11 189.56 39156 +1932 62 7.6 1.6 5.95 0 245.96 254.95 39355 +1932 63 8.89 2.89 7.24 0 266.38 256.43 39553 +1932 64 13.35 7.35 11.7 0.27 348.61 189.69 39753 +1932 65 10.43 4.43 8.78 0 292.66 260.15 39953 +1932 66 3.94 -2.06 2.29 0.08 195.16 202.7 40154 +1932 67 0.35 -5.65 -1.3 0.85 154.39 207.11 40355 +1932 68 2.13 -3.87 0.48 0.09 173.58 208.26 40556 +1932 69 -1.49 -7.49 -3.14 0 136.51 283.03 40758 +1932 70 1.05 -4.95 -0.6 0 161.71 284.11 40960 +1932 71 3.37 -2.63 1.72 0.01 188.13 213.82 41163 +1932 72 4.68 -1.32 3.03 0 204.63 286.67 41366 +1932 73 0.36 -5.64 -1.29 0 154.5 293.19 41569 +1932 74 -1.04 -7.04 -2.69 0 140.71 297.02 41772 +1932 75 0.46 -5.54 -1.19 0.04 155.52 224.02 41976 +1932 76 0.61 -5.39 -1.04 0 157.08 301.27 42179 +1932 77 6.42 0.42 4.77 0.01 228.47 223.69 42383 +1932 78 5.81 -0.19 4.16 0.5 219.85 226.23 42587 +1932 79 5.56 -0.44 3.91 0 216.41 304.67 42791 +1932 80 6.01 0.01 4.36 0.18 222.65 230.04 42996 +1932 81 6.34 0.34 4.69 1.04 227.32 231.7 43200 +1932 82 1.34 -4.66 -0.31 0.05 164.82 237.55 43404 +1932 83 0.97 -5.03 -0.68 0.22 160.86 239.7 43608 +1932 84 1.42 -4.58 -0.23 0.07 165.69 241.35 43812 +1932 85 2.54 -3.46 0.89 0 178.28 323.32 44016 +1932 86 -0.31 -6.31 -1.96 0 147.76 328.27 44220 +1932 87 -3.09 -9.09 -4.74 0 122.45 332.89 44424 +1932 88 -4.64 -10.64 -6.29 0.39 110.04 282.63 44627 +1932 89 -5.77 -11.77 -7.42 0 101.7 369.57 44831 +1932 90 -2.52 -8.52 -4.17 0.29 127.31 285.55 45034 +1932 91 5.05 -0.95 3.4 0.02 209.51 281.5 45237 +1932 92 6.54 0.54 4.89 0 230.2 365 45439 +1932 93 8.86 2.86 7.21 0 265.89 334.54 45642 +1932 94 9.8 3.8 8.15 0.11 281.65 251.44 45843 +1932 95 12 6 10.35 0 321.7 333.6 46045 +1932 96 14.92 8.92 13.27 0 382.3 329.79 46246 +1932 97 17.63 11.63 15.98 0 447.01 325.28 46446 +1932 98 17.9 11.9 16.25 0 453.94 326.47 46647 +1932 99 17.43 11.43 15.78 0.36 441.94 247.24 46846 +1932 100 14.39 8.39 12.74 0.1 370.63 254.1 47045 +1932 101 15.82 9.82 14.17 0.03 402.84 253.08 47243 +1932 102 12.78 6.78 11.13 0.03 337.02 259.47 47441 +1932 103 11.26 5.26 9.61 0.1 307.72 263.03 47638 +1932 104 7.92 1.92 6.27 0.83 250.9 268.54 47834 +1932 105 8.35 2.35 6.7 0.8 257.66 269.42 48030 +1932 106 12.45 6.45 10.8 0 330.46 353.7 48225 +1932 107 13.93 7.93 12.28 0 360.75 352.29 48419 +1932 108 12.86 6.86 11.21 0 338.63 356.29 48612 +1932 109 12.77 6.77 11.12 0 336.82 358.08 48804 +1932 110 11.88 5.88 10.23 0 319.39 361.27 48995 +1932 111 14.68 8.68 13.03 0 376.98 356.87 49185 +1932 112 13.94 7.94 12.29 0 360.96 360.06 49374 +1932 113 10.29 4.29 8.64 0 290.18 368.67 49561 +1932 114 12.91 6.91 11.26 0 339.63 365.11 49748 +1932 115 13.73 7.73 12.08 0 356.52 364.77 49933 +1932 116 17.61 11.61 15.96 0 446.5 356.32 50117 +1932 117 16.87 10.87 15.22 0.49 427.99 269.72 50300 +1932 118 10.77 4.77 9.12 0 298.75 374.65 50481 +1932 119 9.39 3.39 7.74 0 274.68 378.32 50661 +1932 120 8.72 2.72 7.07 0 263.61 380.64 50840 +1932 121 13.99 7.99 12.34 0.01 362.02 278.64 51016 +1932 122 13.95 7.95 12.3 0 361.17 372.81 51191 +1932 123 10.77 4.77 9.12 1.21 298.75 285.34 51365 +1932 124 9.7 3.7 8.05 0.12 279.94 287.62 51536 +1932 125 10.61 4.61 8.96 0 295.87 382.85 51706 +1932 126 13.2 7.2 11.55 0.45 345.53 283.95 51874 +1932 127 18.33 12.33 16.68 0.11 465.17 274.73 52039 +1932 128 21.24 15.24 19.59 0 547.53 357.83 52203 +1932 129 18.61 12.61 16.96 0.03 472.61 275.45 52365 +1932 130 19.23 13.23 17.58 0.38 489.43 274.6 52524 +1932 131 20.42 14.42 18.77 0.03 523.16 272.26 52681 +1932 132 19.22 13.22 17.57 0 489.16 367.75 52836 +1932 133 16.67 10.67 15.02 0.4 423.1 281.96 52989 +1932 134 15.47 9.47 13.82 0 394.74 379.83 53138 +1932 135 21.92 15.92 20.27 0.13 568.47 270.41 53286 +1932 136 18.98 12.98 17.33 1.66 482.59 278.4 53430 +1932 137 21.74 15.74 20.09 0 562.86 362.51 53572 +1932 138 19.91 13.91 18.26 1.09 508.47 277.12 53711 +1932 139 21.37 15.37 19.72 0.77 551.49 273.84 53848 +1932 140 23.57 17.57 21.92 0.13 622.12 267.85 53981 +1932 141 22.81 16.81 21.16 0.03 596.9 270.44 54111 +1932 142 19.4 13.4 17.75 0.22 494.14 279.93 54238 +1932 143 18.87 12.87 17.22 0.44 479.6 281.59 54362 +1932 144 19.05 13.05 17.4 0 484.5 375.36 54483 +1932 145 19.68 13.68 18.03 0.78 501.96 280.34 54600 +1932 146 16.84 10.84 15.19 0.2 427.25 287.1 54714 +1932 147 19.51 13.51 17.86 0 497.2 375.18 54824 +1932 148 19.66 13.66 18.01 0 501.4 375.07 54931 +1932 149 19.55 13.55 17.9 0.09 498.32 281.81 55034 +1932 150 19.7 13.7 18.05 0.26 502.53 281.68 55134 +1932 151 16.8 10.8 15.15 0.33 426.27 288.61 55229 +1932 152 18.35 12.35 16.7 0 465.7 380.38 55321 +1932 153 20 14 18.35 0 511.04 375.31 55409 +1932 154 18.03 12.03 16.38 0 457.31 381.91 55492 +1932 155 19.13 13.13 17.48 0 486.69 378.68 55572 +1932 156 20.35 14.35 18.7 0 521.12 374.94 55648 +1932 157 21.77 15.77 20.12 0 563.79 370 55719 +1932 158 23.55 17.55 21.9 0 621.44 363.18 55786 +1932 159 24.11 18.11 22.46 0 640.58 361.07 55849 +1932 160 21.14 15.14 19.49 0 544.51 372.91 55908 +1932 161 18.19 12.19 16.54 0.11 461.49 287.09 55962 +1932 162 14.02 8.02 12.37 0.48 362.66 295.6 56011 +1932 163 16.04 10.04 14.39 0 408 389.22 56056 +1932 164 17.74 11.74 16.09 0 449.83 384.46 56097 +1932 165 23.4 17.4 21.75 0 616.4 364.68 56133 +1932 166 22.69 16.69 21.04 0 593 367.61 56165 +1932 167 23.86 17.86 22.21 0.28 631.98 272.09 56192 +1932 168 18.19 12.19 16.54 0.04 461.49 287.48 56214 +1932 169 21.49 15.49 19.84 0 555.15 372.22 56231 +1932 170 17.57 11.57 15.92 0 445.49 385.18 56244 +1932 171 15.18 9.18 13.53 0 388.14 391.8 56252 +1932 172 16.56 10.56 14.91 0.11 420.43 291.08 56256 +1932 173 20.8 14.8 19.15 0 534.34 374.75 56255 +1932 174 22.39 16.39 20.74 0 583.34 368.77 56249 +1932 175 21.74 15.74 20.09 0 562.86 371.21 56238 +1932 176 19.52 13.52 17.87 0.04 497.48 284.23 56223 +1932 177 18.62 12.62 16.97 0 472.87 381.76 56203 +1932 178 16.38 10.38 14.73 0 416.09 388.36 56179 +1932 179 19.5 13.5 17.85 0.79 496.92 284.14 56150 +1932 180 21.29 15.29 19.64 0 549.05 372.54 56116 +1932 181 17.4 11.4 15.75 0.01 441.18 288.88 56078 +1932 182 18.6 12.6 16.95 0.18 472.34 286.05 56035 +1932 183 21.1 15.1 19.45 1.29 543.31 279.63 55987 +1932 184 20.34 14.34 18.69 0 520.83 375.36 55935 +1932 185 21.69 15.69 20.04 0 561.31 370.44 55879 +1932 186 23.52 17.52 21.87 0 620.43 363.02 55818 +1932 187 25.77 19.77 24.12 0.24 700.27 264.74 55753 +1932 188 23.66 17.66 22.01 0 625.16 362 55684 +1932 189 22.5 16.5 20.85 0.04 586.86 274.86 55611 +1932 190 21.87 15.87 20.22 0 566.91 368.52 55533 +1932 191 25.58 19.58 23.93 0 693.21 352.82 55451 +1932 192 28.78 22.78 27.13 0 820.54 336.48 55366 +1932 193 29.1 23.1 27.45 0 834.29 334.47 55276 +1932 194 24.41 18.41 22.76 0 651.04 357.27 55182 +1932 195 20.26 14.26 18.61 0 518.51 372.95 55085 +1932 196 23.38 17.38 21.73 0 615.73 360.91 54984 +1932 197 26.56 20.56 24.91 0 730.29 346.36 54879 +1932 198 24.48 18.48 22.83 0.94 653.5 266.59 54770 +1932 199 27.42 21.42 25.77 0.58 764.2 256.04 54658 +1932 200 23.07 17.07 21.42 0.83 605.43 270.42 54542 +1932 201 20.12 14.12 18.47 0.06 514.48 278.18 54423 +1932 202 20.86 14.86 19.21 0 536.12 367.8 54301 +1932 203 24.4 18.4 22.75 0.06 650.69 265.18 54176 +1932 204 28.09 22.09 26.44 0 791.53 335.65 54047 +1932 205 26.42 20.42 24.77 0 724.89 343.48 53915 +1932 206 20.28 14.28 18.63 0 519.09 367.71 53780 +1932 207 19.84 13.84 18.19 0 506.48 368.52 53643 +1932 208 25.14 19.14 23.49 0 677.09 347.56 53502 +1932 209 26.68 20.68 25.03 0 734.95 339.84 53359 +1932 210 23.58 17.58 21.93 0 622.45 352.93 53213 +1932 211 23.2 17.2 21.55 0.03 609.73 265.27 53064 +1932 212 23.17 17.17 21.52 0 608.73 353.03 52913 +1932 213 24.7 18.7 23.05 0 661.28 346 52760 +1932 214 24.53 18.53 22.88 0 655.26 346 52604 +1932 215 27.71 21.71 26.06 1.11 775.93 248 52445 +1932 216 28.38 22.38 26.73 0.64 803.62 244.71 52285 +1932 217 22.33 16.33 20.68 0 581.42 352.24 52122 +1932 218 21.14 15.14 19.49 0 544.51 355.72 51958 +1932 219 23.68 17.68 22.03 0 625.84 345.2 51791 +1932 220 23.73 17.73 22.08 0.84 627.54 258.06 51622 +1932 221 25.75 19.75 24.1 0.07 699.53 250.92 51451 +1932 222 20.18 14.18 18.53 0.24 516.2 266.21 51279 +1932 223 22.7 16.7 21.05 0.05 593.32 258.73 51105 +1932 224 22.11 16.11 20.46 0.01 574.44 259.59 50929 +1932 225 22.64 16.64 20.99 0.47 591.38 257.28 50751 +1932 226 24.14 18.14 22.49 0 641.62 336.1 50572 +1932 227 25.84 19.84 24.19 0 702.89 327.68 50392 +1932 228 27.23 21.23 25.58 0 756.6 320.15 50210 +1932 229 24.92 18.92 23.27 0 669.14 329.3 50026 +1932 230 23.86 17.86 22.21 0 631.98 332.38 49842 +1932 231 26.6 20.6 24.95 0 731.84 319.34 49656 +1932 232 23.7 17.7 22.05 0 626.52 330.27 49469 +1932 233 18.84 12.84 17.19 0.01 478.79 259.02 49280 +1932 234 22.53 16.53 20.88 0 587.83 331.89 49091 +1932 235 22.75 16.75 21.1 0 594.94 329.64 48900 +1932 236 21.62 15.62 19.97 0.32 559.15 249.17 48709 +1932 237 23.52 17.52 21.87 0 620.43 323.8 48516 +1932 238 22.79 16.79 21.14 0 596.25 324.88 48323 +1932 239 23.6 17.6 21.95 0 623.13 320.43 48128 +1932 240 25.35 19.35 23.7 0 684.74 311.83 47933 +1932 241 26.56 20.56 24.91 0 730.29 305.05 47737 +1932 242 30.07 24.07 28.42 0 877.17 286.52 47541 +1932 243 28.84 22.84 27.19 0 823.1 291.11 47343 +1932 244 21.78 15.78 20.13 0 564.11 318.23 47145 +1932 245 19.82 13.82 18.17 0.25 505.92 241.95 46947 +1932 246 23.32 17.32 21.67 0 613.72 309.2 46747 +1932 247 21.59 15.59 19.94 0 558.23 313.33 46547 +1932 248 19.58 13.58 17.93 0.01 499.16 238.2 46347 +1932 249 17.91 11.91 16.26 0 454.2 320.15 46146 +1932 250 20.76 14.76 19.11 0 533.15 310.13 45945 +1932 251 25 19 23.35 0.04 672.02 220.1 45743 +1932 252 28.09 22.09 26.44 0 791.53 278.51 45541 +1932 253 31.68 25.68 30.03 0 952.45 258.73 45339 +1932 254 32.01 26.01 30.36 0 968.53 255.08 45136 +1932 255 24.5 18.5 22.85 0 654.2 287.16 44933 +1932 256 26.35 20.35 24.7 0 722.21 277.89 44730 +1932 257 25.17 19.17 23.52 0 678.18 280.49 44527 +1932 258 25.85 19.85 24.2 0.4 703.26 206.77 44323 +1932 259 23.33 17.33 21.68 0.07 614.06 211.9 44119 +1932 260 27.39 21.39 25.74 0.01 763 198.77 43915 +1932 261 25.13 19.13 23.48 1.15 676.72 203.72 43711 +1932 262 25 19 23.35 0.36 672.02 202.41 43507 +1932 263 19.91 13.91 18.26 0.16 508.47 212.68 43303 +1932 264 20.29 14.29 18.64 0.79 519.38 210.02 43099 +1932 265 18.13 12.13 16.48 0 459.92 283.29 42894 +1932 266 20.7 14.7 19.05 0 531.38 274.19 42690 +1932 267 22.17 16.17 20.52 0.17 576.34 200.52 42486 +1932 268 18.98 12.98 17.33 0.29 482.59 205.21 42282 +1932 269 19.14 13.14 17.49 0.01 486.96 203.07 42078 +1932 270 19.83 13.83 18.18 0 506.2 266.44 41875 +1932 271 17.25 11.25 15.6 0 437.41 270.03 41671 +1932 272 15.44 9.44 13.79 0 394.06 271.1 41468 +1932 273 14.36 8.36 12.71 0 369.98 270.63 41265 +1932 274 7.32 1.32 5.67 0 241.71 278.37 41062 +1932 275 5.76 -0.24 4.11 0.21 219.16 207.94 40860 +1932 276 9.35 3.35 7.7 0.26 274.01 202.67 40658 +1932 277 12.16 6.16 10.51 0.4 324.79 197.62 40456 +1932 278 8.94 2.94 7.29 0.24 267.2 198.84 40255 +1932 279 12.97 6.97 11.32 0.43 340.85 192.37 40054 +1932 280 13.8 7.8 12.15 0.25 357.99 189.36 39854 +1932 281 9.47 3.47 7.82 0.43 276.03 192.08 39654 +1932 282 13.83 7.83 12.18 0.53 358.63 185.24 39455 +1932 283 16.54 10.54 14.89 0.65 419.95 179.5 39256 +1932 284 17.98 11.98 16.33 0.29 456.02 175.12 39058 +1932 285 13.95 7.95 12.3 0.31 361.17 178.75 38861 +1932 286 15 9 13.35 0.51 384.09 175.38 38664 +1932 287 15.9 9.9 14.25 0.08 404.71 172.02 38468 +1932 288 10.59 4.59 8.94 0.08 295.51 176.05 38273 +1932 289 11.18 5.18 9.53 0 306.24 231.31 38079 +1932 290 13.18 7.18 11.53 0.68 345.12 169.22 37885 +1932 291 12.2 6.2 10.55 2.19 325.57 168.26 37693 +1932 292 13.31 7.31 11.66 0.45 347.78 165.06 37501 +1932 293 14.2 8.2 12.55 0 366.52 216.03 37311 +1932 294 17.63 11.63 15.98 0.55 447.01 155.53 37121 +1932 295 15.47 9.47 13.82 0.42 394.74 156.29 36933 +1932 296 18.82 12.82 17.17 0.91 478.25 149.9 36745 +1932 297 16.66 10.66 15.01 0.34 422.85 150.9 36560 +1932 298 17.4 11.4 15.75 0 441.18 197.38 36375 +1932 299 15.34 9.34 13.69 0 391.77 198.11 36191 +1932 300 18.33 12.33 16.68 0.25 465.17 142.84 36009 +1932 301 18.62 12.62 16.97 0.47 472.87 140.62 35829 +1932 302 21.12 15.12 19.47 0.91 543.91 135.04 35650 +1932 303 21.14 15.14 19.49 0.22 544.51 133.19 35472 +1932 304 23 17 21.35 0.04 603.12 128.39 35296 +1932 305 16.14 10.14 14.49 0 410.37 181.69 35122 +1932 306 13.98 7.98 12.33 0 361.81 182.62 34950 +1932 307 7.47 1.47 5.82 0.12 243.98 140.51 34779 +1932 308 7.92 1.92 6.27 0.35 250.9 138.25 34610 +1932 309 3.66 -2.34 2.01 0 191.68 185.37 34444 +1932 310 5.17 -0.83 3.52 0 211.12 181.81 34279 +1932 311 3.05 -2.95 1.4 0.49 184.28 135.81 34116 +1932 312 5.89 -0.11 4.24 0 220.97 176.4 33956 +1932 313 6.99 0.99 5.34 0 236.78 173.39 33797 +1932 314 9.87 3.87 8.22 0 282.86 168.85 33641 +1932 315 9.3 3.3 7.65 0 273.17 166.88 33488 +1932 316 6.19 0.19 4.54 0.05 225.19 125.49 33337 +1932 317 7.23 1.23 5.58 0.61 240.35 123.23 33188 +1932 318 7.44 1.44 5.79 0 243.52 161.8 33042 +1932 319 8.39 2.39 6.74 0 258.3 159.32 32899 +1932 320 7.39 1.39 5.74 0 242.76 158.28 32758 +1932 321 4.14 -1.86 2.49 0 197.68 158.48 32620 +1932 322 7.59 1.59 5.94 0 245.81 154.2 32486 +1932 323 3.12 -2.88 1.47 0 185.11 155.63 32354 +1932 324 7.4 1.4 5.75 0.35 242.92 113.01 32225 +1932 325 9.06 3.06 7.41 0.02 269.18 110.72 32100 +1932 326 9.72 3.72 8.07 0.01 280.28 109.22 31977 +1932 327 9.61 3.61 7.96 0 278.4 143.9 31858 +1932 328 9.38 3.38 7.73 0 274.51 142.14 31743 +1932 329 10.2 4.2 8.55 0 288.6 139.96 31631 +1932 330 7.4 1.4 5.75 0 242.92 140.79 31522 +1932 331 5.3 -0.7 3.65 0 212.87 140.92 31417 +1932 332 4.65 -1.35 3 0 204.24 139.68 31316 +1932 333 2.78 -3.22 1.13 0 181.08 139.66 31218 +1932 334 7.58 1.58 5.93 0 245.65 135.55 31125 +1932 335 0.27 -5.73 -1.38 0 153.58 138.59 31035 +1932 336 3.9 -2.1 2.25 0.03 194.66 101.75 30949 +1932 337 4.47 -1.53 2.82 0 201.91 133.68 30867 +1932 338 2.46 -3.54 0.81 0 177.35 133.83 30790 +1932 339 2.78 -3.22 1.13 0.03 181.08 99.66 30716 +1932 340 2.59 -3.41 0.94 0 178.86 132.23 30647 +1932 341 -1.05 -7.05 -2.7 0 140.62 132.95 30582 +1932 342 -1.8 -7.8 -3.45 0 133.69 132.47 30521 +1932 343 1.74 -4.26 0.09 0 169.21 130.13 30465 +1932 344 1.67 -4.33 0.02 0 168.43 129.03 30413 +1932 345 -0.12 -6.12 -1.77 0.12 149.64 140.89 30366 +1932 346 -1.92 -7.92 -3.57 0 132.6 173.45 30323 +1932 347 0.81 -5.19 -0.84 0.03 159.17 139.74 30284 +1932 348 0.23 -5.77 -1.42 0 153.17 171.61 30251 +1932 349 2.09 -3.91 0.44 0 173.13 126.51 30221 +1932 350 3.56 -2.44 1.91 0 190.45 125.43 30197 +1932 351 -0.13 -6.13 -1.78 0 149.54 126.94 30177 +1932 352 3.69 -2.31 2.04 0 192.05 125.05 30162 +1932 353 7.56 1.56 5.91 0 245.35 122.66 30151 +1932 354 7.91 1.91 6.26 0.44 250.74 91.79 30145 +1932 355 9.09 3.09 7.44 0 269.68 121.53 30144 +1932 356 8.73 2.73 7.08 0.33 263.77 91.36 30147 +1932 357 5.08 -0.92 3.43 0 209.91 124.27 30156 +1932 358 2.62 -3.38 0.97 0.02 179.21 94.26 30169 +1932 359 0.36 -5.64 -1.29 0.01 154.5 95.13 30186 +1932 360 1.65 -4.35 0 0 168.21 126.63 30208 +1932 361 2.99 -3.01 1.34 0.26 183.56 94.73 30235 +1932 362 2.29 -3.71 0.64 0 175.4 127.1 30267 +1932 363 0.73 -5.27 -0.92 0.17 158.33 96.31 30303 +1932 364 -0.48 -6.48 -2.13 0 146.09 129.32 30343 +1932 365 9.64 3.64 7.99 0 278.91 124.02 30388 +1933 1 3.66 -2.34 2.01 0 191.68 128.84 30438 +1933 2 0.92 -5.08 -0.73 0 160.33 130.93 30492 +1933 3 -2.65 -8.65 -4.3 0.23 126.19 143.91 30551 +1933 4 -4.03 -10.03 -5.68 0.1 114.79 145.18 30614 +1933 5 -6.12 -12.12 -7.77 0 99.23 180.06 30681 +1933 6 -4.14 -10.14 -5.79 0 113.92 180.26 30752 +1933 7 -4.75 -10.75 -6.4 0 109.21 181.16 30828 +1933 8 -1.85 -7.85 -3.5 0 133.23 181.55 30907 +1933 9 -2.37 -8.37 -4.02 0.44 128.62 149.44 30991 +1933 10 -4.03 -10.03 -5.68 0 114.79 186.04 31079 +1933 11 -0.01 -6.01 -1.66 0 150.74 185.35 31171 +1933 12 1.7 -4.3 0.05 0 168.77 185.21 31266 +1933 13 -2.34 -8.34 -3.99 0.17 128.88 152.94 31366 +1933 14 0.54 -5.46 -1.11 0.33 156.35 152.92 31469 +1933 15 -1.36 -7.36 -3.01 0 137.72 191.2 31575 +1933 16 -1.22 -7.22 -2.87 0 139.02 192.29 31686 +1933 17 -4.8 -10.8 -6.45 0 108.83 195.18 31800 +1933 18 -7.93 -13.93 -9.58 0 87.27 197.88 31917 +1933 19 -3.72 -9.72 -5.37 0 117.27 198.36 32038 +1933 20 -4.11 -10.11 -5.76 0 114.16 199.95 32161 +1933 21 -1.71 -7.71 -3.36 0.01 134.5 161.54 32289 +1933 22 0.9 -5.1 -0.75 0 160.12 201.17 32419 +1933 23 0.49 -5.51 -1.16 0 155.83 202.93 32552 +1933 24 5.62 -0.38 3.97 0 217.23 201.06 32688 +1933 25 6.88 0.88 5.23 0 235.16 200.98 32827 +1933 26 2.81 -3.19 1.16 0 181.43 205.16 32969 +1933 27 -0.3 -6.3 -1.95 0.68 147.86 168.58 33114 +1933 28 -1.55 -7.55 -3.2 0.32 135.96 171.43 33261 +1933 29 1.89 -4.11 0.24 0 170.88 214.44 33411 +1933 30 2.39 -3.61 0.74 0 176.55 215.92 33564 +1933 31 -0.32 -6.32 -1.97 0.02 147.66 175.25 33718 +1933 32 3.58 -2.42 1.93 0.64 190.7 174.52 33875 +1933 33 2.46 -3.54 0.81 0.79 177.35 176.56 34035 +1933 34 2.02 -3.98 0.37 0 172.34 223.84 34196 +1933 35 1.1 -4.9 -0.55 0 162.24 226.23 34360 +1933 36 0.12 -5.88 -1.53 0 152.05 229.11 34526 +1933 37 -0.16 -6.16 -1.81 0 149.25 231.52 34694 +1933 38 -0.08 -6.08 -1.73 0 150.04 234.05 34863 +1933 39 1.11 -4.89 -0.54 0 162.35 235.68 35035 +1933 40 4.53 -1.47 2.88 0 202.68 235.27 35208 +1933 41 3.99 -2.01 2.34 0.06 195.79 187.71 35383 +1933 42 6.28 0.28 4.63 0.22 226.47 150.39 35560 +1933 43 6.34 0.34 4.69 0.03 227.32 152.37 35738 +1933 44 5.24 -0.76 3.59 0 212.06 206.66 35918 +1933 45 6.81 0.81 5.16 0 234.13 207.9 36099 +1933 46 10.73 4.73 9.08 0 298.03 206.43 36282 +1933 47 8.33 2.33 6.68 0.02 257.34 158.91 36466 +1933 48 4.37 -1.63 2.72 0 200.62 218.31 36652 +1933 49 4.49 -1.51 2.84 0 202.16 221 36838 +1933 50 2.41 -3.59 0.76 0 176.78 225.29 37026 +1933 51 4.65 -1.35 3 0 204.24 226.51 37215 +1933 52 3.93 -2.07 2.28 0.31 195.04 172.46 37405 +1933 53 4.33 -1.67 2.68 0 200.11 232.58 37596 +1933 54 4.37 -1.63 2.72 0 200.62 235.32 37788 +1933 55 3.47 -2.53 1.82 0.33 189.35 179.31 37981 +1933 56 3.57 -2.43 1.92 0 190.57 241.7 38175 +1933 57 7.47 1.47 5.82 0 243.98 240.91 38370 +1933 58 3.4 -2.6 1.75 0.64 188.49 185.77 38565 +1933 59 3.64 -2.36 1.99 0 191.43 250.22 38761 +1933 60 7.09 1.09 5.44 0 238.26 249.81 38958 +1933 61 7.58 1.58 5.93 0 245.65 252.19 39156 +1933 62 9.88 3.88 8.23 0 283.03 252.19 39355 +1933 63 9.37 3.37 7.72 0 274.35 255.83 39553 +1933 64 8.38 2.38 6.73 0 258.14 259.93 39753 +1933 65 13.03 7.03 11.38 0 342.06 256.27 39953 +1933 66 11.12 5.12 9.47 0 305.13 261.88 40154 +1933 67 11.76 5.76 10.11 0 317.1 263.78 40355 +1933 68 12.17 6.17 10.52 0 324.99 265.97 40556 +1933 69 6.59 0.59 4.94 0.26 230.92 207.01 40758 +1933 70 10.18 4.18 8.53 0.03 288.25 205.75 40960 +1933 71 7.64 1.64 5.99 0 246.57 280.56 41163 +1933 72 6.51 0.51 4.86 0.03 229.76 213.53 41366 +1933 73 8.64 2.64 6.99 0 262.32 284.78 41569 +1933 74 2.96 -3.04 1.31 0 183.21 293.81 41772 +1933 75 4.89 -1.11 3.24 0 207.39 294.67 41976 +1933 76 5.85 -0.15 4.2 0 220.41 296.29 42179 +1933 77 10.5 4.5 8.85 0 293.9 292.81 42383 +1933 78 12.25 6.25 10.6 0.96 326.54 219.48 42587 +1933 79 10.43 4.43 8.78 0.02 292.66 223.7 42791 +1933 80 7.35 1.35 5.7 0 242.16 305.09 42996 +1933 81 6.32 0.32 4.67 0 227.04 308.95 43200 +1933 82 5.53 -0.47 3.88 0 215.99 312.55 43404 +1933 83 8.35 2.35 6.7 0 257.66 311.52 43608 +1933 84 10.12 4.12 8.47 0.07 287.2 233.6 43812 +1933 85 10.76 4.76 9.11 0.57 298.57 234.7 44016 +1933 86 9.43 3.43 7.78 0.66 275.36 238.06 44220 +1933 87 8.3 2.3 6.65 0.22 256.87 241.19 44424 +1933 88 7.93 1.93 6.28 0.04 251.05 243.35 44627 +1933 89 4.8 -1.2 3.15 0 206.2 330.69 44831 +1933 90 9.94 3.94 8.29 0 284.07 326.15 45034 +1933 91 11.96 5.96 10.31 0.66 320.93 243.73 45237 +1933 92 13.23 7.23 11.58 0.12 346.14 243.61 45439 +1933 93 15.54 9.54 13.89 0 396.35 322.13 45642 +1933 94 11.18 5.18 9.53 0 306.24 332.94 45843 +1933 95 12.74 6.74 11.09 0 336.22 332.21 46045 +1933 96 11.31 5.31 9.66 0 308.64 336.96 46246 +1933 97 11.67 5.67 10.02 0.12 315.4 253.77 46446 +1933 98 9.82 3.82 8.17 0.36 282 257.64 46647 +1933 99 7.94 1.94 6.29 0.08 251.21 261.34 46846 +1933 100 7.78 1.78 6.13 0.33 248.73 262.99 47045 +1933 101 9.35 3.35 7.7 0 274.01 350.21 47243 +1933 102 14.99 8.99 13.34 0 383.87 341.25 47441 +1933 103 13.67 7.67 12.02 0 355.26 345.96 47638 +1933 104 15.62 9.62 13.97 0.36 398.2 257.54 47834 +1933 105 12.77 6.77 11.12 0 336.82 351.42 48030 +1933 106 13.48 7.48 11.83 0 351.3 351.59 48225 +1933 107 14.45 8.45 12.8 0 371.94 351.14 48419 +1933 108 12.36 6.36 10.71 0 328.69 357.3 48612 +1933 109 16.33 10.33 14.68 0.05 414.89 262.47 48804 +1933 110 11.48 5.48 9.83 0.1 311.82 271.53 48995 +1933 111 11.66 5.66 10.01 0 315.21 363.25 49185 +1933 112 8.28 2.28 6.63 0 256.55 370.67 49374 +1933 113 6.45 0.45 4.8 0.04 228.9 281.06 49561 +1933 114 6.42 0.42 4.77 0.61 228.47 282.24 49748 +1933 115 9.31 3.31 7.66 0.7 273.34 280 49933 +1933 116 7.01 1.01 5.36 0 237.08 378.19 50117 +1933 117 8.07 2.07 6.42 0 253.24 377.93 50300 +1933 118 7.7 1.7 6.05 0 247.49 379.84 50481 +1933 119 7.98 1.98 6.33 0 251.83 380.63 50661 +1933 120 10.36 4.36 8.71 0.08 291.42 283.35 50840 +1933 121 12.99 6.99 11.34 0.18 341.25 280.3 51016 +1933 122 16.05 10.05 14.4 0.09 408.24 275.79 51191 +1933 123 15.34 9.34 13.69 0.14 391.77 277.9 51365 +1933 124 15.05 9.05 13.4 0 385.21 372.33 51536 +1933 125 18.55 12.55 16.9 0 471 363.79 51706 +1933 126 17.36 11.36 15.71 1 440.17 276.17 51874 +1933 127 16.03 10.03 14.38 0.21 407.77 279.54 52039 +1933 128 18.22 12.22 16.57 0.3 462.28 275.71 52203 +1933 129 16.49 10.49 14.84 0.03 418.74 280 52365 +1933 130 16.62 10.62 14.97 0 421.88 373.77 52524 +1933 131 14.83 8.83 13.18 0.02 380.3 284.38 52681 +1933 132 15.92 9.92 14.27 0.06 405.18 282.94 52836 +1933 133 12.36 6.36 10.71 1.06 328.69 289.75 52989 +1933 134 16.71 10.71 15.06 0.87 424.07 282.41 53138 +1933 135 15.86 9.86 14.21 1.44 403.78 284.64 53286 +1933 136 19.86 13.86 18.21 0.05 507.05 276.28 53430 +1933 137 17.34 11.34 15.69 0.15 439.67 282.61 53572 +1933 138 17.03 11.03 15.38 0.87 431.94 283.72 53711 +1933 139 18.58 12.58 16.93 0.99 471.8 280.82 53848 +1933 140 15.13 9.13 13.48 0 387.01 384.53 53981 +1933 141 16.88 10.88 15.23 0 428.23 380.32 54111 +1933 142 16.43 10.43 14.78 0.87 417.29 286.55 54238 +1933 143 18.24 12.24 16.59 1.51 462.8 283.05 54362 +1933 144 16.09 10.09 14.44 0.56 409.18 288 54483 +1933 145 13.08 7.08 11.43 1.46 343.08 293.89 54600 +1933 146 14.99 8.99 13.34 0.05 383.87 290.78 54714 +1933 147 14.67 8.67 13.02 0 376.76 388.98 54824 +1933 148 14.95 8.95 13.3 0.14 382.97 291.5 54931 +1933 149 13.98 7.98 12.33 0 361.81 391.36 55034 +1933 150 17.02 11.02 15.37 0 431.69 383.8 55134 +1933 151 16.48 10.48 14.83 0.1 418.5 289.28 55229 +1933 152 17.49 11.49 15.84 0 443.46 382.95 55321 +1933 153 18.52 12.52 16.87 0.63 470.21 285.07 55409 +1933 154 21.26 15.26 19.61 0.07 548.14 278.41 55492 +1933 155 20.35 14.35 18.7 0.17 521.12 280.96 55572 +1933 156 19.02 13.02 17.37 0.13 483.68 284.51 55648 +1933 157 16.11 10.11 14.46 0 409.66 388.08 55719 +1933 158 16.53 10.53 14.88 0 419.7 387.11 55786 +1933 159 13.83 7.83 12.18 0 358.63 394.26 55849 +1933 160 15.31 9.31 13.66 0.04 391.09 293.1 55908 +1933 161 15.15 9.15 13.5 0.17 387.46 293.46 55962 +1933 162 15.45 9.45 13.8 0.2 394.29 292.93 56011 +1933 163 16.89 10.89 15.24 4.51 428.48 290.16 56056 +1933 164 19.45 13.45 17.8 0.62 495.53 284.33 56097 +1933 165 18.19 12.19 16.54 0 461.49 383.2 56133 +1933 166 18.23 12.23 16.58 0.12 462.54 287.37 56165 +1933 167 14.71 8.71 13.06 0.59 377.64 294.63 56192 +1933 168 14.65 8.65 13 0 376.32 393.07 56214 +1933 169 14.67 8.67 13.02 0 376.76 393.03 56231 +1933 170 16.74 10.74 15.09 0.04 424.8 290.67 56244 +1933 171 19.92 13.92 18.27 0.05 508.76 283.36 56252 +1933 172 23.42 17.42 21.77 0 617.07 364.76 56256 +1933 173 24.87 18.87 23.22 0.01 667.35 268.91 56255 +1933 174 22.34 16.34 20.69 0.16 581.74 276.72 56249 +1933 175 24.33 18.33 22.68 0.17 648.23 270.6 56238 +1933 176 20.38 14.38 18.73 0.49 522 282.05 56223 +1933 177 20.26 14.26 18.61 0.1 518.51 282.29 56203 +1933 178 18.6 12.6 16.95 0.3 472.34 286.39 56179 +1933 179 21.08 15.08 19.43 0.5 542.7 280.06 56150 +1933 180 20.56 14.56 18.91 0 527.26 375.14 56116 +1933 181 18.49 12.49 16.84 0 469.41 381.89 56078 +1933 182 21.07 15.07 19.42 0.08 542.4 279.84 56035 +1933 183 21.08 15.08 19.43 0 542.7 372.91 55987 +1933 184 21.13 15.13 19.48 0.31 544.21 279.43 55935 +1933 185 20.98 14.98 19.33 0.3 539.7 279.77 55879 +1933 186 21.9 15.9 20.25 0.1 567.85 277.05 55818 +1933 187 20.67 14.67 19.02 0.28 530.49 280.27 55753 +1933 188 22.71 16.71 21.06 0 593.64 365.84 55684 +1933 189 23.24 17.24 21.59 0.01 611.06 272.66 55611 +1933 190 23.23 17.23 21.58 0 610.73 363.22 55533 +1933 191 23.19 17.19 21.54 0 609.4 363.13 55451 +1933 192 25.99 19.99 24.34 0.23 708.52 262.97 55366 +1933 193 26.91 20.91 25.26 0 743.94 345.94 55276 +1933 194 26.81 20.81 25.16 0.06 740.02 259.67 55182 +1933 195 26.18 20.18 24.53 0.42 715.72 261.75 55085 +1933 196 25.35 19.35 23.7 0 684.74 352.46 54984 +1933 197 25.96 19.96 24.31 0 707.39 349.21 54879 +1933 198 25.11 19.11 23.46 0 676 352.69 54770 +1933 199 23.59 17.59 21.94 0 622.79 358.85 54658 +1933 200 25.99 19.99 24.34 0 708.52 347.95 54542 +1933 201 24.65 18.65 23 0.48 659.51 265.15 54423 +1933 202 22.51 16.51 20.86 0 587.18 361.73 54301 +1933 203 20.28 14.28 18.63 0.11 519.09 276.98 54176 +1933 204 21.83 15.83 20.18 1.05 565.66 272.48 54047 +1933 205 22.53 16.53 20.88 0 587.83 360.15 53915 +1933 206 16.01 10.01 14.36 0 407.3 380.51 53780 +1933 207 21.19 15.19 19.54 0 546.02 363.9 53643 +1933 208 21.33 15.33 19.68 0 550.27 362.75 53502 +1933 209 24.41 18.41 22.76 0 651.04 350.09 53359 +1933 210 22.78 16.78 21.13 0 595.92 356.09 53213 +1933 211 22.89 16.89 21.24 0.56 599.51 266.18 53064 +1933 212 20.34 14.34 18.69 0.69 520.83 272.51 52913 +1933 213 18.32 12.32 16.67 0.05 464.91 276.75 52760 +1933 214 16.25 10.25 14.6 0.16 412.98 280.55 52604 +1933 215 18.69 12.69 17.04 0 474.75 366.44 52445 +1933 216 21.21 15.21 19.56 1.12 546.63 267.88 52285 +1933 217 23.51 17.51 21.86 0.02 620.09 260.77 52122 +1933 218 23.72 17.72 22.07 0.01 627.2 259.54 51958 +1933 219 19.82 13.82 18.17 0.68 505.92 269.33 51791 +1933 220 17.19 11.19 15.54 0.04 435.91 274.52 51622 +1933 221 19.35 13.35 17.7 0.17 492.75 268.99 51451 +1933 222 17.45 11.45 15.8 0.11 442.44 272.41 51279 +1933 223 18.53 12.53 16.88 0.01 470.47 269.21 51105 +1933 224 22.09 16.09 20.44 1.02 573.81 259.64 50929 +1933 225 23.39 17.39 21.74 0 616.06 340.18 50751 +1933 226 22.03 16.03 20.38 0.56 571.92 258.11 50572 +1933 227 24.59 18.59 22.94 0.03 657.38 249.77 50392 +1933 228 24.72 18.72 23.07 0 661.99 331.32 50210 +1933 229 22.26 16.26 20.61 0 579.19 339.65 50026 +1933 230 22.73 16.73 21.08 0.04 594.29 252.52 49842 +1933 231 22.57 16.57 20.92 0.87 589.12 251.88 49656 +1933 232 24.18 18.18 22.53 1.37 643.01 246.29 49469 +1933 233 22.4 16.4 20.75 0.46 583.66 250.31 49280 +1933 234 23.16 17.16 21.51 0.14 608.4 247.18 49091 +1933 235 18.96 12.96 17.31 0.82 482.04 256.56 48900 +1933 236 24.9 18.9 23.25 1.84 668.43 239.97 48709 +1933 237 24.6 18.6 22.95 0.08 657.73 239.7 48516 +1933 238 25.89 19.89 24.24 0.6 704.76 234.49 48323 +1933 239 24.32 18.32 22.67 0.44 647.88 238.24 48128 +1933 240 25.59 19.59 23.94 0.35 693.58 233.13 47933 +1933 241 30.89 24.89 29.24 0.31 914.86 212.73 47737 +1933 242 29.83 23.83 28.18 0.94 866.39 215.84 47541 +1933 243 28.87 22.87 27.22 0.62 824.39 218.22 47343 +1933 244 22.92 16.92 21.27 0.03 600.49 235.73 47145 +1933 245 22.35 16.35 20.7 0.03 582.06 235.88 46947 +1933 246 19.87 13.87 18.22 0.05 507.33 240.38 46747 +1933 247 17.19 11.19 15.54 0 435.91 326.01 46547 +1933 248 17.03 11.03 15.38 0.05 431.94 243.35 46347 +1933 249 18.41 12.41 16.76 0 467.28 318.82 46146 +1933 250 15.74 9.74 14.09 0.07 400.98 242.63 45945 +1933 251 18.32 12.32 16.67 0.49 464.91 236.26 45743 +1933 252 19.27 13.27 17.62 1.16 490.54 232.71 45541 +1933 253 19.1 13.1 17.45 0.26 485.86 231.49 45339 +1933 254 17.17 11.17 15.52 0.44 435.41 233.65 45136 +1933 255 16.98 10.98 15.33 0.52 430.7 232.3 44933 +1933 256 20.83 14.83 19.18 0.69 535.23 222.87 44730 +1933 257 18.09 12.09 16.44 0.04 458.88 226.94 44527 +1933 258 19.58 13.58 17.93 0.35 499.16 222.25 44323 +1933 259 19.21 13.21 17.56 0 488.88 294.94 44119 +1933 260 19.02 13.02 17.37 0 483.68 293.1 43915 +1933 261 20.43 14.43 18.78 0.02 523.45 215.14 43711 +1933 262 20.1 14.1 18.45 0 513.9 285.46 43507 +1933 263 19.81 13.81 18.16 0 505.63 283.85 43303 +1933 264 17.09 11.09 15.44 0 433.42 288.09 43099 +1933 265 11.28 5.28 9.63 0 308.09 296.93 42894 +1933 266 12.59 6.59 10.94 0 333.23 292.21 42690 +1933 267 10.97 4.97 9.32 0 302.38 292.15 42486 +1933 268 15.01 9.01 13.36 0 384.31 282.45 42282 +1933 269 13.9 7.9 12.25 0 360.11 282.03 42078 +1933 270 17.66 11.66 16.01 0.27 447.78 203.78 41875 +1933 271 17.49 11.49 15.84 0 443.46 269.5 41671 +1933 272 21.64 15.64 19.99 0.02 559.77 192.3 41468 +1933 273 22.52 16.52 20.87 0.29 587.51 188.59 41265 +1933 274 19.3 13.3 17.65 0.14 491.36 193.13 41062 +1933 275 17.77 11.77 16.12 0.57 450.6 193.77 40860 +1933 276 13.85 7.85 12.2 0.42 359.05 197.54 40658 +1933 277 14.61 8.61 12.96 0 375.44 259.38 40456 +1933 278 15.06 9.06 13.41 0 385.44 255.71 40255 +1933 279 14.61 8.61 12.96 0.11 375.44 190.29 40054 +1933 280 14.11 8.11 12.46 0.05 364.59 188.97 39854 +1933 281 19.36 13.36 17.71 0.4 493.03 179.1 39654 +1933 282 19.41 13.41 17.76 0.16 494.41 177.03 39455 +1933 283 18.72 12.72 17.07 0.48 475.56 176.14 39256 +1933 284 14.04 8.04 12.39 0.62 363.09 180.61 39058 +1933 285 16.48 10.48 14.83 0.08 418.5 175.42 38861 +1933 286 16.69 10.69 15.04 0 423.59 230.79 38664 +1933 287 18.81 12.81 17.16 0 477.98 223.67 38468 +1933 288 18.89 12.89 17.24 0 480.14 220.81 38273 +1933 289 15.83 9.83 14.18 0.02 403.08 168.13 38079 +1933 290 12.24 6.24 10.59 0.32 326.35 170.24 37885 +1933 291 12.2 6.2 10.55 0.07 325.57 168.26 37693 +1933 292 10.95 4.95 9.3 0 302.02 223.32 37501 +1933 293 12.78 6.78 11.13 0 337.02 218.13 37311 +1933 294 16.38 10.38 14.73 0.29 416.09 157.22 37121 +1933 295 13.34 7.34 11.69 1.09 348.4 158.74 36933 +1933 296 12.27 6.27 10.62 0.24 326.93 157.92 36745 +1933 297 12.56 6.56 10.91 0 332.64 207.46 36560 +1933 298 7.63 1.63 5.98 0.41 246.42 157.91 36375 +1933 299 9.32 3.32 7.67 1.71 273.51 154.49 36191 +1933 300 5.02 -0.98 3.37 1.88 209.11 155.51 36009 +1933 301 6.4 0.4 4.75 0 228.18 203.62 35829 +1933 302 6.78 0.78 5.13 0.29 233.69 150.47 35650 +1933 303 3.71 -2.29 2.06 0.05 192.3 150.37 35472 +1933 304 6.8 0.8 5.15 0 233.98 195.51 35296 +1933 305 4.23 -1.77 2.58 0 198.83 194.82 35122 +1933 306 6.1 0.1 4.45 0 223.91 191.06 34950 +1933 307 3.48 -2.52 1.83 0.06 189.47 142.88 34779 +1933 308 4.45 -1.55 2.8 0.56 201.65 140.38 34610 +1933 309 4.71 -1.29 3.06 0.51 205.02 138.47 34444 +1933 310 6.63 0.63 4.98 0.46 231.5 135.5 34279 +1933 311 8.67 2.67 7.02 0 262.8 176.69 34116 +1933 312 6.43 0.43 4.78 0 228.61 175.98 33956 +1933 313 5.87 -0.13 4.22 0 220.69 174.28 33797 +1933 314 5.49 -0.51 3.84 0 215.45 172.59 33641 +1933 315 6.48 0.48 4.83 0.02 229.33 126.97 33488 +1933 316 5.69 -0.31 4.04 1.9 218.19 125.77 33337 +1933 317 7.73 1.73 6.08 1.45 247.95 122.92 33188 +1933 318 8.95 2.95 7.3 0.29 267.37 120.39 33042 +1933 319 7.1 1.1 5.45 0.02 238.41 120.28 32899 +1933 320 3.85 -2.15 2.2 0 194.04 160.79 32758 +1933 321 3.93 -2.07 2.28 0 195.04 158.62 32620 +1933 322 2.61 -3.39 0.96 0.28 179.09 118.18 32486 +1933 323 7.05 1.05 5.4 0.21 237.67 114.75 32354 +1933 324 8.48 2.48 6.83 0.03 259.74 112.37 32225 +1933 325 7.39 1.39 5.74 0.1 242.76 111.73 32100 +1933 326 8.25 2.25 6.6 0 256.08 146.86 31977 +1933 327 11.39 5.39 9.74 0.01 310.13 106.7 31858 +1933 328 8.66 2.66 7.01 0.05 262.64 107.05 31743 +1933 329 8.66 2.66 7.01 0.39 262.64 105.94 31631 +1933 330 13.94 7.94 12.29 0.94 360.96 101.13 31522 +1933 331 6.86 0.86 5.21 0.14 234.86 104.9 31417 +1933 332 12.01 6.01 10.36 1.11 321.89 100.47 31316 +1933 333 11.17 5.17 9.52 0 306.05 133.7 31218 +1933 334 14.9 8.9 13.25 0.66 381.86 96.61 31125 +1933 335 2.37 -3.63 0.72 0.2 176.32 103.18 31035 +1933 336 0.55 -5.45 -1.1 0.85 156.45 103.03 30949 +1933 337 1.06 -4.94 -0.59 0.67 161.81 101.6 30867 +1933 338 -0.19 -6.19 -1.84 0.11 148.95 144.52 30790 +1933 339 -0.38 -6.38 -2.03 0 147.07 177.67 30716 +1933 340 -0.26 -6.26 -1.91 0 148.25 176.97 30647 +1933 341 -0.53 -6.53 -2.18 0 145.6 176.25 30582 +1933 342 -2.47 -8.47 -4.12 0.02 127.74 143.19 30521 +1933 343 -1.37 -7.37 -3.02 0 137.62 175.21 30465 +1933 344 -0.13 -6.13 -1.78 0 149.54 173.64 30413 +1933 345 1.7 -4.3 0.05 0 168.77 172.24 30366 +1933 346 -1.61 -7.61 -3.26 0.84 135.41 143.44 30323 +1933 347 -5.02 -11.02 -6.67 0.15 107.17 144.38 30284 +1933 348 -5.17 -11.17 -6.82 0 106.06 176.61 30251 +1933 349 -7.3 -13.3 -8.95 0 91.28 176.84 30221 +1933 350 -3.76 -9.76 -5.41 0 116.95 175.53 30197 +1933 351 -3.32 -9.32 -4.97 0 120.54 175.2 30177 +1933 352 -3 -9 -4.65 0 123.21 175.02 30162 +1933 353 -3.05 -9.05 -4.7 0.03 122.79 143.11 30151 +1933 354 -0.59 -6.59 -2.24 0.19 145.02 143.03 30145 +1933 355 -0.5 -6.5 -2.15 0.02 145.9 143.06 30144 +1933 356 -3.88 -9.88 -5.53 0 115.98 176.01 30147 +1933 357 -3.44 -9.44 -5.09 0 119.55 175.92 30156 +1933 358 -1.88 -7.88 -3.53 0.09 132.96 143.84 30169 +1933 359 -0.98 -6.98 -2.63 0.02 141.28 143.71 30186 +1933 360 -0.27 -6.27 -1.92 0.15 148.15 144.22 30208 +1933 361 -5.22 -11.22 -6.87 0.17 105.69 146.25 30235 +1933 362 -2.01 -8.01 -3.66 1.8 131.8 151.46 30267 +1933 363 -2.95 -8.95 -4.6 0.38 123.63 153.29 30303 +1933 364 -2.7 -8.7 -4.35 0 125.76 185.99 30343 +1933 365 0.06 -5.94 -1.59 0.03 151.45 153 30388 +1934 1 3.96 -2.04 2.31 0 195.41 183.81 30438 +1934 2 4.9 -1.1 3.25 0 207.52 183.26 30492 +1934 3 1.83 -4.17 0.18 0.1 170.21 152.63 30551 +1934 4 1.64 -4.36 -0.01 0 168.1 186.17 30614 +1934 5 0.5 -5.5 -1.15 0.35 155.94 153.76 30681 +1934 6 1.84 -4.16 0.19 0 170.32 187.07 30752 +1934 7 4.38 -1.62 2.73 0.03 200.75 152.47 30828 +1934 8 3.24 -2.76 1.59 0.98 186.56 153.51 30907 +1934 9 -3.59 -9.59 -5.24 0.45 118.32 157.94 30991 +1934 10 -2.44 -8.44 -4.09 0 128.01 193.63 31079 +1934 11 -1.19 -7.19 -2.84 0 139.3 193.99 31171 +1934 12 -3.27 -9.27 -4.92 0 120.95 195.65 31266 +1934 13 -0.35 -6.35 -2 0.04 147.37 160.22 31366 +1934 14 -5.02 -11.02 -6.67 0.61 107.17 164.35 31469 +1934 15 -2.32 -8.32 -3.97 0 129.05 201.36 31575 +1934 16 1.27 -4.73 -0.38 0 164.07 200.72 31686 +1934 17 0.55 -5.45 -1.1 0 156.45 202.51 31800 +1934 18 -1.67 -7.67 -3.32 0 134.87 205.21 31917 +1934 19 -0.38 -6.38 -2.03 0 147.07 206.4 32038 +1934 20 4.57 -1.43 2.92 0 203.2 204.53 32161 +1934 21 5.81 -0.19 4.16 0 219.85 204.76 32289 +1934 22 4.02 -1.98 2.37 0 196.17 206.99 32419 +1934 23 2.3 -3.7 0.65 0 175.51 209.29 32552 +1934 24 -0.59 -6.59 -2.24 0 145.02 212.66 32688 +1934 25 -1.63 -7.63 -3.28 0 135.23 214.83 32827 +1934 26 1.06 -4.94 -0.59 0 161.81 215.12 32969 +1934 27 3.7 -2.3 2.05 0.01 192.17 173.41 33114 +1934 28 4.64 -1.36 2.99 0 204.11 215.75 33261 +1934 29 4.33 -1.67 2.68 0 200.11 217.6 33411 +1934 30 2.41 -3.59 0.76 0 176.78 220.57 33564 +1934 31 5.45 -0.55 3.8 0.18 214.9 176.51 33718 +1934 32 6.88 0.88 5.23 0 235.16 219.99 33875 +1934 33 6.57 0.57 4.92 0 230.63 221.86 34035 +1934 34 5.9 -0.1 4.25 0 221.11 223.69 34196 +1934 35 3.73 -2.27 2.08 0.01 192.55 180.68 34360 +1934 36 4.06 -1.94 2.41 0 196.67 228.4 34526 +1934 37 6.66 0.66 5.01 0 231.94 227.82 34694 +1934 38 4.63 -1.37 2.98 0.13 203.98 183.57 34863 +1934 39 1.23 -4.77 -0.42 0 163.64 236.02 35035 +1934 40 -0.68 -6.68 -2.33 0.31 144.15 190.37 35208 +1934 41 3.6 -2.4 1.95 0 190.94 239.75 35383 +1934 42 6.73 0.73 5.08 0 232.96 238.83 35560 +1934 43 2.93 -3.07 1.28 0 182.85 244.03 35738 +1934 44 7.19 1.19 5.54 0 239.76 242.12 35918 +1934 45 8.7 2.7 7.05 0 263.29 206.05 36099 +1934 46 3.72 -2.28 2.07 0 192.42 213.18 36282 +1934 47 2.38 -3.62 0.73 0.3 176.43 162.75 36466 +1934 48 7.76 1.76 6.11 0 248.42 215.24 36652 +1934 49 8.99 2.99 7.34 0 268.03 216.7 36838 +1934 50 5.92 -0.08 4.27 0.03 221.39 166.82 37026 +1934 51 1.51 -4.49 -0.14 0.17 166.68 171.69 37215 +1934 52 2.4 -3.6 0.75 0.07 176.66 173.35 37405 +1934 53 0.49 -5.51 -1.16 0 155.83 235.45 37596 +1934 54 -0.68 -6.68 -2.33 0 144.15 238.98 37788 +1934 55 3.72 -2.28 2.07 0 192.42 238.87 37981 +1934 56 0.23 -5.77 -1.42 0 153.17 244.18 38175 +1934 57 2.09 -3.91 0.44 0 173.13 245.78 38370 +1934 58 2.47 -3.53 0.82 0 177.47 248.45 38565 +1934 59 6.31 0.31 4.66 0.07 226.89 185.8 38761 +1934 60 11 5 9.35 0 302.93 245.05 38958 +1934 61 10.39 4.39 8.74 0 291.95 248.76 39156 +1934 62 7.12 1.12 5.47 0 238.71 255.49 39355 +1934 63 4.07 -1.93 2.42 0.06 196.8 196.16 39553 +1934 64 4.87 -1.13 3.22 0.01 207.13 197.79 39753 +1934 65 4.17 -1.83 2.52 0 198.07 267.29 39953 +1934 66 4.23 -1.77 2.58 0 198.83 269.99 40154 +1934 67 5.98 -0.02 4.33 0.15 222.23 203.38 40355 +1934 68 9.12 3.12 7.47 0 270.17 270.34 40556 +1934 69 10.58 4.58 8.93 0 295.33 270.94 40758 +1934 70 7.71 1.71 6.06 0.03 247.65 208.17 40960 +1934 71 8 2 6.35 0 252.14 280.12 41163 +1934 72 8.03 2.03 6.38 0 252.61 282.9 41366 +1934 73 5.19 -0.81 3.54 0 211.39 288.84 41569 +1934 74 8.9 2.9 7.25 0 266.55 287.17 41772 +1934 75 9.93 3.93 8.28 0 283.89 288.45 41976 +1934 76 9.67 3.67 8.02 0 279.43 291.44 42179 +1934 77 13.44 7.44 11.79 0 350.47 287.93 42383 +1934 78 15.31 9.31 13.66 0.02 391.09 215.2 42587 +1934 79 13.36 7.36 11.71 0.22 348.81 220.02 42791 +1934 80 14.67 8.67 13.02 0.05 376.76 220 42996 +1934 81 13.97 7.97 12.32 0 361.6 297.22 43200 +1934 82 16.08 10.08 14.43 0 408.95 295.48 43404 +1934 83 16.65 10.65 15 0 422.61 296.61 43608 +1934 84 13.06 7.06 11.41 0 342.67 306.48 43812 +1934 85 11.75 5.75 10.1 0 316.91 311.28 44016 +1934 86 12.66 6.66 11.01 0 334.62 312.05 44220 +1934 87 11.09 5.09 9.44 0 304.58 317.3 44424 +1934 88 10.45 4.45 8.8 0 293.01 320.69 44627 +1934 89 15.93 9.93 14.28 0 405.42 312.39 44831 +1934 90 16.98 10.98 15.33 0 430.7 312.24 45034 +1934 91 19.92 13.92 18.27 0 508.76 306.62 45237 +1934 92 20.6 14.6 18.95 0 528.43 306.74 45439 +1934 93 17.1 11.1 15.45 0 433.67 318.44 45642 +1934 94 20.6 14.6 18.95 0 528.43 310.87 45843 +1934 95 20.54 14.54 18.89 0 526.67 313.08 46045 +1934 96 15.34 9.34 13.69 0 391.77 328.85 46246 +1934 97 14.13 8.13 12.48 0 365.02 333.52 46446 +1934 98 10.12 4.12 8.47 0 287.2 343.03 46647 +1934 99 12.99 6.99 11.34 0.12 341.25 254.84 46846 +1934 100 14.98 8.98 13.33 0.49 383.64 253.12 47045 +1934 101 11.79 5.79 10.14 0 317.68 345.97 47243 +1934 102 13.93 7.93 12.28 0 360.75 343.59 47441 +1934 103 11.01 5.01 9.36 0 303.11 351.15 47638 +1934 104 10.54 4.54 8.89 0 294.62 353.82 47834 +1934 105 11.02 5.02 9.37 0 303.3 354.77 48030 +1934 106 12.76 6.76 11.11 0 336.62 353.08 48225 +1934 107 15.46 9.46 13.81 0 394.52 348.8 48419 +1934 108 16.24 10.24 14.59 0 412.74 348.6 48612 +1934 109 19.61 13.61 17.96 0 500 340.81 48804 +1934 110 17.42 11.42 15.77 0 441.69 348.48 48995 +1934 111 16 10 14.35 0 407.06 353.7 49185 +1934 112 18.34 12.34 16.69 0 465.43 348.91 49374 +1934 113 15.82 9.82 14.17 0 402.84 356.97 49561 +1934 114 17.76 11.76 16.11 0 450.34 353.31 49748 +1934 115 15.28 9.28 13.63 0 390.41 361.18 49933 +1934 116 11.94 5.94 10.29 0.36 320.54 277.31 50117 +1934 117 16.91 10.91 15.26 0 428.97 359.52 50300 +1934 118 15.7 9.7 14.05 0 400.05 363.96 50481 +1934 119 17.47 11.47 15.82 0 442.95 360.45 50661 +1934 120 15.79 9.79 14.14 0 402.14 366.07 50840 +1934 121 19.44 13.44 17.79 0.13 495.25 267.66 51016 +1934 122 17.38 11.38 15.73 0.78 440.68 273.11 51191 +1934 123 17.11 11.11 15.46 0.54 433.92 274.43 51365 +1934 124 19.25 13.25 17.6 0 489.98 360.69 51536 +1934 125 18.55 12.55 16.9 0.11 471 272.84 51706 +1934 126 16.25 10.25 14.6 0.25 412.98 278.44 51874 +1934 127 18.06 12.06 16.41 0.05 458.09 275.32 52039 +1934 128 13.87 7.87 12.22 0.06 359.47 284.25 52203 +1934 129 12.5 6.5 10.85 0.02 331.45 287.16 52365 +1934 130 14.95 8.95 13.3 0.01 382.97 283.56 52524 +1934 131 17.49 11.49 15.84 0 443.46 372.14 52681 +1934 132 19.87 13.87 18.22 0 507.33 365.65 52836 +1934 133 22.45 16.45 20.8 0.79 585.26 267.91 52989 +1934 134 22.52 16.52 20.87 0.29 587.51 268.22 53138 +1934 135 25.66 19.66 24.01 0.03 696.18 258.87 53286 +1934 136 28.47 22.47 26.82 0.34 807.4 248.95 53430 +1934 137 25.73 19.73 24.08 0.53 698.78 259.57 53572 +1934 138 21.03 15.03 19.38 0.4 541.2 274.24 53711 +1934 139 19.17 13.17 17.52 1.25 487.78 279.43 53848 +1934 140 21.57 15.57 19.92 0.28 557.61 273.64 53981 +1934 141 19.63 13.63 17.98 0 500.56 371.99 54111 +1934 142 22.97 16.97 21.32 0 602.13 360.43 54238 +1934 143 22.82 16.82 21.17 0.62 597.22 271.16 54362 +1934 144 22.7 16.7 21.05 0 593.32 362.47 54483 +1934 145 23.85 17.85 22.2 0.03 631.63 268.71 54600 +1934 146 20.99 14.99 19.34 0.19 540 277.25 54714 +1934 147 19.53 13.53 17.88 0.08 497.76 281.34 54824 +1934 148 15.06 9.06 13.41 0.02 385.44 291.3 54931 +1934 149 15.36 9.36 13.71 0 392.23 387.95 55034 +1934 150 15.76 9.76 14.11 0 401.44 387.25 55134 +1934 151 14.55 8.55 12.9 0 374.12 390.72 55229 +1934 152 16.04 10.04 14.39 0.05 408 290.26 55321 +1934 153 16.64 10.64 14.99 0.21 422.37 289.21 55409 +1934 154 21.22 15.22 19.57 0.12 546.93 278.52 55492 +1934 155 16.78 10.78 15.13 0.19 425.78 289.3 55572 +1934 156 17.78 11.78 16.13 0.22 450.85 287.38 55648 +1934 157 19.17 13.17 17.52 0 487.78 379.04 55719 +1934 158 20.4 14.4 18.75 0.64 522.58 281.33 55786 +1934 159 18.32 12.32 16.67 0.33 464.91 286.6 55849 +1934 160 22.78 16.78 21.13 0.32 595.92 275.03 55908 +1934 161 24.26 18.26 22.61 0.27 645.79 270.5 55962 +1934 162 20.33 14.33 18.68 0.86 520.54 281.92 56011 +1934 163 18.19 12.19 16.54 0.06 461.49 287.29 56056 +1934 164 18.39 12.39 16.74 0 466.76 382.49 56097 +1934 165 17.83 11.83 16.18 0.01 452.14 288.21 56133 +1934 166 17.64 11.64 15.99 0.4 447.27 288.7 56165 +1934 167 19.35 13.35 17.7 0 492.75 379.56 56192 +1934 168 16.91 10.91 15.26 1.46 428.97 290.3 56214 +1934 169 13.75 7.75 12.1 0.28 356.94 296.44 56231 +1934 170 18.53 12.53 16.88 0.32 470.47 286.7 56244 +1934 171 21.96 15.96 20.31 1.28 569.72 277.89 56252 +1934 172 20.03 14.03 18.38 1.25 511.9 283.08 56256 +1934 173 21.79 15.79 20.14 0 564.42 371.14 56255 +1934 174 20.15 14.15 18.5 0.57 515.34 282.7 56249 +1934 175 23.27 17.27 21.62 0.92 612.06 273.93 56238 +1934 176 24.51 18.51 22.86 0.26 654.55 269.99 56223 +1934 177 25.15 19.15 23.5 0 677.45 357.04 56203 +1934 178 25.99 19.99 24.34 0.03 708.52 264.89 56179 +1934 179 23.87 17.87 22.22 0.37 632.32 271.91 56150 +1934 180 21.56 15.56 19.91 0.29 557.3 278.66 56116 +1934 181 21.34 15.34 19.69 1.06 550.57 279.22 56078 +1934 182 28.24 22.24 26.59 0 797.76 341.49 56035 +1934 183 25.7 19.7 24.05 0.19 697.66 265.47 55987 +1934 184 25.15 19.15 23.5 0.2 677.45 267.25 55935 +1934 185 24.21 18.21 22.56 0.4 644.05 270.28 55879 +1934 186 20.19 14.19 18.54 1 516.49 281.65 55818 +1934 187 21.13 15.13 19.48 0.08 544.21 279.04 55753 +1934 188 26.53 20.53 24.88 0.33 729.13 261.84 55684 +1934 189 21.7 15.7 20.05 0 561.62 369.52 55611 +1934 190 22 16 20.35 0 570.98 368.03 55533 +1934 191 25.55 19.55 23.9 0 692.1 352.96 55451 +1934 192 30.01 24.01 28.36 0.09 874.47 247.16 55366 +1934 193 25.76 19.76 24.11 0.14 699.9 263.58 55276 +1934 194 26.27 20.27 24.62 0.16 719.15 261.63 55182 +1934 195 27.71 21.71 26.06 0 775.93 341.45 55085 +1934 196 25.53 19.53 23.88 0 691.36 351.64 54984 +1934 197 21.81 15.81 20.16 1.3 565.04 274.93 54879 +1934 198 22.02 16.02 20.37 1.36 571.61 274.02 54770 +1934 199 23.91 17.91 22.26 1.74 633.69 268.14 54658 +1934 200 20.24 14.24 18.59 0.77 517.94 278.23 54542 +1934 201 19.32 13.32 17.67 0 491.92 373.54 54423 +1934 202 17.04 11.04 15.39 0 432.18 379.85 54301 +1934 203 21.06 15.06 19.41 0 542.1 366.59 54176 +1934 204 23.06 17.06 21.41 0 605.1 358.59 54047 +1934 205 22.35 16.35 20.7 0.09 582.06 270.63 53915 +1934 206 23.61 17.61 21.96 0 623.47 355.33 53780 +1934 207 24.39 18.39 22.74 0.02 650.34 263.58 53643 +1934 208 20.33 14.33 18.68 0 520.54 366.23 53502 +1934 209 23.97 17.97 22.32 0.12 635.75 263.95 53359 +1934 210 22.73 16.73 21.08 0 594.29 356.29 53213 +1934 211 24.64 18.64 22.99 0 659.15 347.76 53064 +1934 212 22.99 16.99 21.34 0.1 602.79 265.3 52913 +1934 213 21.44 15.44 19.79 0.04 553.62 269.08 52760 +1934 214 22.72 16.72 21.07 0.04 593.97 264.98 52604 +1934 215 25.62 19.62 23.97 0.53 694.69 255.45 52445 +1934 216 19.97 13.97 18.32 0.93 510.18 271.03 52285 +1934 217 17.82 11.82 16.17 0 451.88 367.09 52122 +1934 218 19.87 13.87 18.22 0.85 507.33 270 51958 +1934 219 17.94 11.94 16.29 0 454.98 364.86 51791 +1934 220 17.09 11.09 15.44 0.28 433.42 274.73 51622 +1934 221 16.54 10.54 14.89 0.88 419.95 275.07 51451 +1934 222 16.57 10.57 14.92 1.56 420.67 274.21 51279 +1934 223 18.86 12.86 17.21 0.36 479.33 268.47 51105 +1934 224 23.49 17.49 21.84 0 619.42 340.91 50929 +1934 225 26.31 20.31 24.66 0 720.68 327.86 50751 +1934 226 25.98 19.98 24.33 0.06 708.15 246.2 50572 +1934 227 24.54 18.54 22.89 0 655.61 333.23 50392 +1934 228 25.93 19.93 24.28 0.27 706.27 244.59 50210 +1934 229 21.09 15.09 19.44 1.2 543 257.81 50026 +1934 230 23.24 17.24 21.59 0.73 611.06 251.08 49842 +1934 231 21.66 15.66 20.01 0.76 560.39 254.31 49656 +1934 232 20.9 14.9 19.25 0.14 537.31 255.25 49469 +1934 233 23.28 17.28 21.63 0.07 612.39 247.88 49280 +1934 234 25.02 19.02 23.37 0.3 672.74 241.68 49091 +1934 235 22.87 16.87 21.22 0.05 598.86 246.9 48900 +1934 236 21.42 15.42 19.77 0.08 553.01 249.68 48709 +1934 237 24.35 18.35 22.7 0.48 648.93 240.44 48516 +1934 238 26.05 20.05 24.4 0.09 710.79 233.97 48323 +1934 239 27.27 21.27 25.62 0.02 758.19 228.83 48128 +1934 240 24.52 18.52 22.87 0.14 654.91 236.39 47933 +1934 241 23.39 17.39 21.74 0 616.06 317.85 47737 +1934 242 24.66 18.66 23.01 0 659.86 311.33 47541 +1934 243 24.43 18.43 22.78 0 651.74 310.45 47343 +1934 244 26.06 20.06 24.41 0.01 711.17 226.58 47145 +1934 245 23.77 17.77 22.12 0 628.9 309.44 46947 +1934 246 25.43 19.43 23.78 0 687.68 301.13 46747 +1934 247 21.78 15.78 20.13 0 564.11 312.71 46547 +1934 248 19.13 13.13 17.48 0.07 486.69 239.17 46347 +1934 249 20.13 14.13 18.48 0 514.76 313.95 46146 +1934 250 21.75 15.75 20.1 0.4 563.17 230.26 45945 +1934 251 20.71 14.71 19.06 0 531.67 308.22 45743 +1934 252 22.03 16.03 20.38 0 571.92 301.95 45541 +1934 253 21.35 15.35 19.7 0.59 550.88 226.55 45339 +1934 254 20.18 14.18 18.53 0.29 516.2 227.63 45136 +1934 255 25 19 23.35 0.95 672.02 213.97 44933 +1934 256 24.45 18.45 22.8 0.18 652.44 213.9 44730 +1934 257 18.99 12.99 17.34 0 482.86 300.24 44527 +1934 258 18.42 12.42 16.77 0.12 467.55 224.56 44323 +1934 259 19.22 13.22 17.57 0 489.16 294.92 44119 +1934 260 21.31 15.31 19.66 0 549.66 286.67 43915 +1934 261 25.81 19.81 24.16 0.25 701.77 201.81 43711 +1934 262 24.23 18.23 22.58 0.61 644.75 204.46 43507 +1934 263 24.87 18.87 23.22 0 667.35 268.04 43303 +1934 264 24.06 18.06 22.41 0.01 638.85 201.34 43099 +1934 265 17.83 11.83 16.18 0.69 452.14 213.01 42894 +1934 266 13.86 7.86 12.21 0.15 359.26 217.45 42690 +1934 267 16.08 10.08 14.43 0.55 408.95 212.12 42486 +1934 268 15.79 9.79 14.14 0 402.14 280.87 42282 +1934 269 17.25 11.25 15.6 0 437.41 275.23 42078 +1934 270 13.41 7.41 11.76 0.05 349.85 210.2 41875 +1934 271 13.45 7.45 11.8 0.5 350.68 208.16 41671 +1934 272 10.95 4.95 9.3 0.03 302.02 209.14 41468 +1934 273 12.39 6.39 10.74 0 329.28 274.03 41265 +1934 274 6.9 0.9 5.25 0 235.45 278.86 41062 +1934 275 8.92 2.92 7.27 0.2 266.88 205.16 40860 +1934 276 9.64 3.64 7.99 0 278.91 269.84 40658 +1934 277 13.82 7.82 12.17 0.25 358.42 195.58 40456 +1934 278 11.4 5.4 9.75 0 310.32 261.75 40255 +1934 279 15.19 9.19 13.54 0.03 388.37 189.51 40054 +1934 280 16.46 10.46 14.81 0 418.01 247.64 39854 +1934 281 15.42 9.42 13.77 0.85 393.6 185.2 39654 +1934 282 12.39 6.39 10.74 0.08 329.28 186.95 39455 +1934 283 11.96 5.96 10.31 0.03 320.93 185.31 39256 +1934 284 12.57 6.57 10.92 0 332.83 243.14 39058 +1934 285 14.45 8.45 12.8 0 371.94 237.51 38861 +1934 286 16.02 10.02 14.37 0.53 407.53 174.03 38664 +1934 287 15.13 9.13 13.48 0 387.01 230.72 38468 +1934 288 14.77 8.77 13.12 0.46 378.97 171.43 38273 +1934 289 13.92 7.92 12.27 0.49 360.53 170.51 38079 +1934 290 11.78 5.78 10.13 0.04 317.49 170.72 37885 +1934 291 13.34 7.34 11.69 0.23 348.4 167.03 37693 +1934 292 17.2 11.2 15.55 1.56 436.16 160.22 37501 +1934 293 16.83 10.83 15.18 0.93 427.01 158.74 37311 +1934 294 13.27 7.27 11.62 0.01 346.96 160.92 37121 +1934 295 12.36 6.36 10.71 0.4 328.69 159.76 36933 +1934 296 8.14 2.14 6.49 0.49 254.34 161.57 36745 +1934 297 8.38 2.38 6.73 0.16 258.14 159.32 36560 +1934 298 10.51 4.51 8.86 0.06 294.08 155.58 36375 +1934 299 10.93 4.93 9.28 0 301.65 204.16 36191 +1934 300 10.66 4.66 9.01 0 296.77 201.82 36009 +1934 301 13.23 7.23 11.58 0 346.14 196.08 35829 +1934 302 16.02 10.02 14.37 0.13 407.53 142.08 35650 +1934 303 21.23 15.23 19.58 0 547.23 177.4 35472 +1934 304 18.29 12.29 16.64 0 464.12 180.77 35296 +1934 305 12.69 6.69 11.04 0 335.22 186.52 35122 +1934 306 14.54 8.54 12.89 0 373.9 181.86 34950 +1934 307 13.94 7.94 12.29 0 360.96 180.22 34779 +1934 308 11.74 5.74 10.09 0 316.72 180.39 34610 +1934 309 11.1 5.1 9.45 0.13 304.76 134.12 34444 +1934 310 5.51 -0.49 3.86 0.17 215.72 136.17 34279 +1934 311 3.58 -2.42 1.93 0 190.7 180.73 34116 +1934 312 5.91 -0.09 4.26 0 221.25 176.39 33956 +1934 313 8.95 2.95 7.3 0.03 267.37 128.76 33797 +1934 314 10.01 4.01 8.36 0.46 285.28 126.54 33641 +1934 315 9.94 3.94 8.29 0.41 284.07 124.7 33488 +1934 316 7.35 1.35 5.7 0.25 242.16 124.81 33337 +1934 317 6.46 0.46 4.81 0.7 229.04 123.69 33188 +1934 318 4.36 -1.64 2.71 0.12 200.49 123.05 33042 +1934 319 6.3 0.3 4.65 0 226.75 160.99 32899 +1934 320 11.96 5.96 10.31 0.75 320.93 115.56 32758 +1934 321 10.03 4.03 8.38 0.68 285.63 115.43 32620 +1934 322 9.43 3.43 7.78 0.2 275.36 114.49 32486 +1934 323 7.94 1.94 6.29 0.26 251.21 114.23 32354 +1934 324 9.53 3.53 7.88 0.14 277.05 111.7 32225 +1934 325 6.88 0.88 5.23 0 235.16 149.36 32100 +1934 326 10.61 4.61 8.96 0.04 295.87 108.62 31977 +1934 327 8.08 2.08 6.43 0 253.4 145.16 31858 +1934 328 7.82 1.82 6.17 0.83 249.34 107.55 31743 +1934 329 7.13 1.13 5.48 0 238.86 142.43 31631 +1934 330 6.69 0.69 5.04 0 232.37 141.3 31522 +1934 331 11.51 5.51 9.86 0.01 312.38 102.04 31417 +1934 332 13.65 7.65 12 0 354.84 132.29 31316 +1934 333 10.79 4.79 9.14 0.27 299.11 100.53 31218 +1934 334 12.15 6.15 10.5 0 324.6 131.7 31125 +1934 335 13.5 7.5 11.85 0 351.71 129.21 31035 +1934 336 12.14 6.14 10.49 0 324.4 129.53 30949 +1934 337 8.03 2.03 6.38 0.05 252.61 98.5 30867 +1934 338 10.27 4.27 8.62 0.06 289.83 96.49 30790 +1934 339 6.31 0.31 4.66 0.03 226.89 98.11 30716 +1934 340 6.3 0.3 4.65 0.68 226.75 97.57 30647 +1934 341 3.31 -2.69 1.66 0 187.4 130.94 30582 +1934 342 3.42 -2.58 1.77 0 188.74 130.11 30521 +1934 343 4.94 -1.06 3.29 0 208.05 128.44 30465 +1934 344 2.92 -3.08 1.27 0.33 182.73 96.31 30413 +1934 345 2.81 -3.19 1.16 0.08 181.43 96.03 30366 +1934 346 3.74 -2.26 2.09 0 192.67 127 30323 +1934 347 8.61 2.61 6.96 0.01 261.83 92.5 30284 +1934 348 8.94 2.94 7.29 0.01 267.2 92.06 30251 +1934 349 9.34 3.34 7.69 0.01 273.84 91.55 30221 +1934 350 5.04 -0.96 3.39 0.32 209.38 93.46 30197 +1934 351 4.24 -1.76 2.59 1.85 198.96 93.64 30177 +1934 352 2.24 -3.76 0.59 0.01 174.83 94.34 30162 +1934 353 6.65 0.65 5 0.24 231.79 92.44 30151 +1934 354 12.6 6.6 10.95 0 333.43 118.59 30145 +1934 355 11.1 5.1 9.45 0.17 304.76 89.94 30144 +1934 356 12.51 6.51 10.86 0.04 331.65 89.02 30147 +1934 357 17.14 11.14 15.49 0.04 434.67 85.35 30156 +1934 358 13.92 7.92 12.27 0 360.53 117.47 30169 +1934 359 13.88 7.88 12.23 0 359.69 117.62 30186 +1934 360 12.49 6.49 10.84 0 331.25 119.32 30208 +1934 361 6.93 0.93 5.28 0 235.89 124.02 30235 +1934 362 5.21 -0.79 3.56 0 211.65 125.53 30267 +1934 363 4.76 -1.24 3.11 0.5 205.68 94.78 30303 +1934 364 3.9 -2.1 2.25 0 194.66 127.25 30343 +1934 365 3.41 -2.59 1.76 0 188.62 128.08 30388 +1935 1 -3.85 -9.85 -5.5 0 116.22 132.02 30438 +1935 2 2.93 -3.07 1.28 0 182.85 129.96 30492 +1935 3 2.95 -3.05 1.3 0 183.09 130.89 30551 +1935 4 3.62 -2.38 1.97 0 191.19 131.45 30614 +1935 5 3.01 -2.99 1.36 0.03 183.8 99.32 30681 +1935 6 2.64 -3.36 0.99 0.1 179.44 100.13 30752 +1935 7 2.22 -3.78 0.57 0 174.6 134.52 30828 +1935 8 1.21 -4.79 -0.44 0 163.42 136.51 30907 +1935 9 -1.53 -7.53 -3.18 0 136.15 138.96 30991 +1935 10 -2.34 -8.34 -3.99 0 128.88 140.59 31079 +1935 11 0.28 -5.72 -1.37 0 153.68 140.51 31171 +1935 12 1.47 -4.53 -0.18 0 166.24 140.96 31266 +1935 13 1.6 -4.4 -0.05 0 167.66 142.53 31366 +1935 14 0.28 -5.72 -1.37 0 153.68 144.65 31469 +1935 15 0.61 -5.39 -1.04 0.7 157.08 109.46 31575 +1935 16 -2.79 -8.79 -4.44 0 124.99 148.7 31686 +1935 17 -0.55 -6.55 -2.2 0.32 145.41 154.58 31800 +1935 18 -2.08 -8.08 -3.73 0 131.17 194.36 31917 +1935 19 -0.9 -6.9 -2.55 0 142.04 195.66 32038 +1935 20 -4.04 -10.04 -5.69 0.3 114.71 160.16 32161 +1935 21 -1.58 -7.58 -3.23 0.45 135.69 162.13 32289 +1935 22 -1.65 -7.65 -3.3 0.55 135.05 164.94 32419 +1935 23 -6.42 -12.42 -8.07 0.01 97.15 167.44 32552 +1935 24 -2.2 -8.2 -3.85 0 130.11 208.52 32688 +1935 25 -0.35 -6.35 -2 0.06 147.37 168.47 32827 +1935 26 2.47 -3.53 0.82 0 177.47 209.53 32969 +1935 27 0.96 -5.04 -0.69 0.18 160.75 170.16 33114 +1935 28 1.1 -4.9 -0.55 0 162.24 213.91 33261 +1935 29 -0.48 -6.48 -2.13 0 146.09 216.93 33411 +1935 30 -4.53 -10.53 -6.18 0 110.89 220.75 33564 +1935 31 -0.82 -6.82 -2.47 0 142.8 221.36 33718 +1935 32 8.03 2.03 6.38 0 252.61 216.39 33875 +1935 33 9.93 3.93 8.28 0 283.89 215.81 34035 +1935 34 8.22 2.22 6.57 0 255.6 218.46 34196 +1935 35 7.35 1.35 5.7 0.22 242.16 174.89 34360 +1935 36 7.83 1.83 6.18 0.47 249.5 137.77 34526 +1935 37 6.02 0.02 4.37 0 222.79 187.66 34694 +1935 38 1.72 -4.28 0.07 0 168.99 193.47 34863 +1935 39 6.42 0.42 4.77 0.46 228.47 144.49 35035 +1935 40 3.78 -2.22 2.13 1.96 193.17 148 35208 +1935 41 4.32 -1.68 2.67 0.19 199.98 149.67 35383 +1935 42 2.27 -3.73 0.62 0 175.17 203.58 35560 +1935 43 3.15 -2.85 1.5 0 185.47 205.69 35738 +1935 44 4.66 -1.34 3.01 0 204.37 207.13 35918 +1935 45 -1.38 -7.38 -3.03 0.01 137.53 196.91 36099 +1935 46 2.56 -3.44 0.91 0.14 178.51 160.52 36282 +1935 47 4.3 -1.7 2.65 0 199.72 215.56 36466 +1935 48 7.29 1.29 5.64 0.01 241.26 161.78 36652 +1935 49 7.24 1.24 5.59 0 240.5 218.52 36838 +1935 50 8.34 2.34 6.69 0 257.5 220.04 37026 +1935 51 2.38 -3.62 0.73 0 176.43 228.3 37215 +1935 52 3.25 -2.75 1.6 0.01 186.68 172.87 37405 +1935 53 2.19 -3.81 0.54 0 174.26 234.27 37596 +1935 54 1.79 -4.21 0.14 0 169.76 237.34 37788 +1935 55 6.19 0.19 4.54 0.04 225.19 177.49 37981 +1935 56 2.66 -3.34 1.01 0 179.67 242.43 38175 +1935 57 2.92 -3.08 1.27 0 182.73 245.13 38370 +1935 58 1.25 -4.75 -0.4 0.23 163.85 187.02 38565 +1935 59 0.34 -5.66 -1.31 0.01 154.29 189.56 38761 +1935 60 2.03 -3.97 0.38 0 172.45 254.44 38958 +1935 61 4.53 -1.47 2.88 0 202.68 255.29 39156 +1935 62 2.34 -3.66 0.69 0.25 175.97 194.99 39355 +1935 63 7.41 1.41 5.76 0.7 243.07 193.63 39553 +1935 64 5.42 -0.58 3.77 0.35 214.49 197.39 39753 +1935 65 4.3 -1.7 2.65 0.01 199.72 200.38 39953 +1935 66 7.31 1.31 5.66 0 241.56 266.8 40154 +1935 67 8.57 2.57 6.92 0 261.19 268.19 40355 +1935 68 9.14 3.14 7.49 0 270.51 270.32 40556 +1935 69 9.98 3.98 8.33 0 284.76 271.79 40758 +1935 70 9.62 3.62 7.97 0.14 278.57 206.33 40960 +1935 71 10.27 4.27 8.62 0 289.83 277.09 41163 +1935 72 10.53 4.53 8.88 0 294.44 279.51 41366 +1935 73 11.86 5.86 10.21 0 319.01 280.1 41569 +1935 74 10.3 4.3 8.65 0.35 290.36 213.9 41772 +1935 75 6.55 0.55 4.9 0 230.34 292.84 41976 +1935 76 6 0 4.35 0 222.51 296.12 42179 +1935 77 7.92 1.92 6.27 0.15 250.9 222.31 42383 +1935 78 11.13 5.13 9.48 0 305.31 294.47 42587 +1935 79 7.62 1.62 5.97 0.35 246.26 226.65 42791 +1935 80 5.21 -0.79 3.56 0.01 211.65 230.72 42996 +1935 81 2.63 -3.37 0.98 0 179.33 312.87 43200 +1935 82 2.06 -3.94 0.41 0 172.79 316.1 43404 +1935 83 6.26 0.26 4.61 0 226.18 314.21 43608 +1935 84 6.51 0.51 4.86 0 229.76 316.46 43812 +1935 85 5.09 -0.91 3.44 0 210.05 320.66 44016 +1935 86 2.81 -3.19 1.16 0 181.43 325.51 44220 +1935 87 5.31 -0.69 3.66 0 213 325.41 44424 +1935 88 3.79 -2.21 2.14 0 193.29 329.48 44627 +1935 89 6.15 0.15 4.5 0 224.62 329.09 44831 +1935 90 5.52 -0.48 3.87 1.12 215.86 249.19 45034 +1935 91 10.01 4.01 8.36 0.09 285.28 246.22 45237 +1935 92 13.22 7.22 11.57 0 345.94 324.83 45439 +1935 93 12.72 6.72 11.07 0 335.82 327.99 45642 +1935 94 14.17 8.17 12.52 0.08 365.87 245.41 45843 +1935 95 11.87 5.87 10.22 0.22 319.2 250.38 46045 +1935 96 8.13 2.13 6.48 0.64 254.18 256.56 46246 +1935 97 12.34 6.34 10.69 0.15 328.3 252.83 46446 +1935 98 11.59 5.59 9.94 0 313.89 340.46 46647 +1935 99 13.84 7.84 12.19 0.55 358.84 253.54 46846 +1935 100 13.57 7.57 11.92 0.65 353.17 255.41 47045 +1935 101 12.45 6.45 10.8 0.54 330.46 258.54 47243 +1935 102 8.73 2.73 7.08 0.09 263.77 264.83 47441 +1935 103 6.39 0.39 4.74 0.24 228.04 268.78 47638 +1935 104 10.16 4.16 8.51 0 287.9 354.48 47834 +1935 105 9.37 3.37 7.72 0.08 274.35 268.21 48030 +1935 106 11.34 5.34 9.69 0.09 309.2 266.87 48225 +1935 107 8.85 2.85 7.2 0.42 265.73 271.36 48419 +1935 108 10.91 4.91 9.26 0.02 301.29 270.04 48612 +1935 109 12.18 6.18 10.53 0 325.18 359.26 48804 +1935 110 15.47 9.47 13.82 0 394.74 353.47 48995 +1935 111 14.9 8.9 13.25 0 381.86 356.36 49185 +1935 112 18.07 12.07 16.42 0 458.35 349.68 49374 +1935 113 16.83 10.83 15.18 0 427.01 354.38 49561 +1935 114 18.03 12.03 16.38 0 457.31 352.55 49748 +1935 115 21.23 15.23 19.58 1.48 547.23 257.96 49933 +1935 116 18.25 12.25 16.6 0.44 463.06 265.88 50117 +1935 117 10.85 4.85 9.2 0.07 300.2 279.88 50300 +1935 118 11.61 5.61 9.96 0 314.26 373.04 50481 +1935 119 12.78 6.78 11.13 0.08 337.02 278.9 50661 +1935 120 13.69 7.69 12.04 0 355.68 371.07 50840 +1935 121 17.47 11.47 15.82 0 442.95 362.71 51016 +1935 122 17.5 11.5 15.85 0.29 443.71 272.86 51191 +1935 123 15.67 9.67 14.02 0 399.35 369.71 51365 +1935 124 16.94 10.94 15.29 0.21 429.71 275.58 51536 +1935 125 16.01 10.01 14.36 0.54 407.3 278.17 51706 +1935 126 15 9 13.35 0.15 384.09 280.82 51874 +1935 127 19.43 13.43 17.78 0.33 494.97 272.19 52039 +1935 128 18.08 12.08 16.43 2.82 458.62 276.02 52203 +1935 129 11.87 5.87 10.22 0.03 319.2 288.14 52365 +1935 130 14.02 8.02 12.37 0.11 362.66 285.23 52524 +1935 131 13.99 7.99 12.34 0.01 362.02 285.88 52681 +1935 132 15.42 9.42 13.77 0.11 393.6 283.9 52836 +1935 133 16.83 10.83 15.18 0.01 427.01 281.63 52989 +1935 134 14.75 8.75 13.1 0.36 378.52 286.22 53138 +1935 135 12.31 6.31 10.66 0.74 327.71 290.91 53286 +1935 136 10.45 4.45 8.8 0 293.01 392.24 53430 +1935 137 14.21 8.21 12.56 0.01 366.73 288.73 53572 +1935 138 12.41 6.41 10.76 0 329.68 389.65 53711 +1935 139 16.92 10.92 15.27 0.02 429.22 284.47 53848 +1935 140 19.18 13.18 17.53 0 488.06 373.02 53981 +1935 141 17.18 11.18 15.53 0 435.66 379.48 54111 +1935 142 16.59 10.59 14.94 0.8 421.16 286.22 54238 +1935 143 19.1 13.1 17.45 2.19 485.86 281.04 54362 +1935 144 15.62 9.62 13.97 0.07 398.2 288.93 54483 +1935 145 15.36 9.36 13.71 0 392.23 386.38 54600 +1935 146 16.99 10.99 15.34 0 430.95 382.37 54714 +1935 147 17.49 11.49 15.84 0.11 443.46 286.06 54824 +1935 148 16.88 10.88 15.23 0 428.23 383.55 54931 +1935 149 15.94 9.94 14.29 0 405.65 386.43 55034 +1935 150 15.12 9.12 13.47 1.44 386.79 291.68 55134 +1935 151 11.87 5.87 10.22 0.24 319.2 297.59 55229 +1935 152 18.43 12.43 16.78 0 467.81 380.13 55321 +1935 153 17.19 11.19 15.54 0.03 435.91 288.05 55409 +1935 154 18.66 12.66 17.01 0.08 473.94 284.98 55492 +1935 155 18.39 12.39 16.74 0 466.76 381.01 55572 +1935 156 19.96 13.96 18.31 0 509.9 376.27 55648 +1935 157 21.19 15.19 19.54 0.06 546.02 279.1 55719 +1935 158 22.16 16.16 20.51 0 576.02 368.7 55786 +1935 159 26.14 20.14 24.49 0 714.2 351.93 55849 +1935 160 29.7 23.7 28.05 0 860.6 333.44 55908 +1935 161 31.44 25.44 29.79 0 940.89 323.01 55962 +1935 162 28.43 22.43 26.78 0 805.71 340.61 56011 +1935 163 26.57 20.57 24.92 0 730.68 350.35 56056 +1935 164 24.1 18.1 22.45 0 640.23 361.66 56097 +1935 165 22.16 16.16 20.51 0 576.02 369.59 56133 +1935 166 23.05 17.05 21.4 0 604.77 366.18 56165 +1935 167 25.22 19.22 23.57 0 679.99 356.85 56192 +1935 168 23.83 17.83 22.18 0 630.95 362.99 56214 +1935 169 22.22 16.22 20.57 0.67 577.92 277.1 56231 +1935 170 20.86 14.86 19.21 2.37 536.12 280.88 56244 +1935 171 19.8 13.8 18.15 0.01 505.35 283.67 56252 +1935 172 19.16 13.16 17.51 0 487.51 380.32 56256 +1935 173 20.89 14.89 19.24 0 537.02 374.43 56255 +1935 174 25.54 19.54 23.89 0 691.73 355.43 56249 +1935 175 26.33 20.33 24.68 0 721.44 351.68 56238 +1935 176 25.87 19.87 24.22 0 704.01 353.83 56223 +1935 177 27.02 21.02 25.37 0 748.27 348.16 56203 +1935 178 24.89 18.89 23.24 0.21 668.07 268.68 56179 +1935 179 21.82 15.82 20.17 0 565.35 370.7 56150 +1935 180 18.64 12.64 16.99 1.08 473.41 286.12 56116 +1935 181 18.04 12.04 16.39 0 457.57 383.27 56078 +1935 182 20.64 14.64 18.99 0 529.61 374.65 56035 +1935 183 20.73 14.73 19.08 0 532.26 374.16 55987 +1935 184 23.14 17.14 21.49 0.35 607.74 273.68 55935 +1935 185 22.94 16.94 21.29 0 601.15 365.63 55879 +1935 186 22.68 16.68 21.03 0 592.67 366.4 55818 +1935 187 22.99 16.99 21.34 0 602.79 364.99 55753 +1935 188 27.73 21.73 26.08 0 776.75 343.11 55684 +1935 189 27.94 21.94 26.29 0 785.34 341.85 55611 +1935 190 22.51 16.51 20.86 0 587.18 366.08 55533 +1935 191 24.59 18.59 22.94 1.22 657.38 267.94 55451 +1935 192 22.49 16.49 20.84 0.01 586.54 274.2 55366 +1935 193 26.1 20.1 24.45 0.01 712.68 262.39 55276 +1935 194 23.02 17.02 21.37 0 603.78 363.03 55182 +1935 195 22.07 16.07 20.42 0.02 573.18 274.84 55085 +1935 196 21.29 15.29 19.64 0 549.05 368.93 54984 +1935 197 21.48 15.48 19.83 0 554.85 367.78 54879 +1935 198 19.67 13.67 18.02 0 501.68 373.64 54770 +1935 199 20.76 14.76 19.11 0 533.15 369.58 54658 +1935 200 19.53 13.53 17.88 0 497.76 373.34 54542 +1935 201 22.09 16.09 20.44 0 573.81 363.89 54423 +1935 202 18.5 12.5 16.85 0.19 469.67 281.66 54301 +1935 203 19.74 13.74 18.09 0.58 503.65 278.33 54176 +1935 204 17.12 11.12 15.47 0 434.17 378.59 54047 +1935 205 13.47 7.47 11.82 0.11 351.09 290.49 53915 +1935 206 19.86 13.86 18.21 0 507.05 369.11 53780 +1935 207 22.03 16.03 20.38 0 571.92 360.84 53643 +1935 208 30.46 24.46 28.81 0 894.93 320.33 53502 +1935 209 31.57 25.57 29.92 0 947.14 313.04 53359 +1935 210 32.07 26.07 30.42 0 971.48 309.34 53213 +1935 211 26.44 20.44 24.79 0 725.66 339.65 53064 +1935 212 25.89 19.89 24.24 0 704.76 341.46 52913 +1935 213 23.11 17.11 21.46 0.04 606.75 264.39 52760 +1935 214 21.25 15.25 19.6 0.23 547.84 269.04 52604 +1935 215 22.76 16.76 21.11 0 595.27 352.49 52445 +1935 216 23.82 17.82 22.17 0 630.61 347.31 52285 +1935 217 20.13 14.13 18.48 0 514.76 359.96 52122 +1935 218 17 11 15.35 0 431.19 368.57 51958 +1935 219 19.82 13.82 18.17 0 505.92 359.11 51791 +1935 220 18.95 12.95 17.3 0 481.77 360.9 51622 +1935 221 18.16 12.16 16.51 0 460.7 362.25 51451 +1935 222 24.42 18.42 22.77 0 651.39 339.29 51279 +1935 223 28.42 22.42 26.77 0 805.29 319.7 51105 +1935 224 26.08 20.08 24.43 0 711.92 329.99 50929 +1935 225 23 17 21.35 0.42 603.12 256.26 50751 +1935 226 21.93 15.93 20.28 1.46 568.78 258.38 50572 +1935 227 20.51 14.51 18.86 0.22 525.79 261.09 50392 +1935 228 17.29 11.29 15.64 2.19 438.42 267.43 50210 +1935 229 15.83 9.83 14.18 0 403.08 359.12 50026 +1935 230 16.67 10.67 15.02 0.35 423.1 266.75 49842 +1935 231 23.32 17.32 21.67 0.01 613.72 249.78 49656 +1935 232 21.56 15.56 19.91 0.09 557.3 253.58 49469 +1935 233 20.11 14.11 18.46 0 514.19 341.48 49280 +1935 234 22.46 16.46 20.81 0.59 585.58 249.11 49091 +1935 235 24 18 22.35 0.04 636.78 243.69 48900 +1935 236 25.45 19.45 23.8 0.01 688.41 238.26 48709 +1935 237 26.46 20.46 24.81 0 726.43 311.75 48516 +1935 238 21.98 15.98 20.33 0 570.35 327.74 48323 +1935 239 22.25 16.25 20.6 0.4 578.87 244 48128 +1935 240 21.73 15.73 20.08 0.03 562.55 244.05 47933 +1935 241 22.4 16.4 20.75 0 583.66 321.41 47737 +1935 242 20.45 14.45 18.8 0 524.04 326.15 47541 +1935 243 22.61 16.61 20.96 0 590.41 317.17 47343 +1935 244 18.49 12.49 16.84 0 469.41 328.25 47145 +1935 245 19.56 13.56 17.91 0 498.6 323.37 46947 +1935 246 19.17 13.17 17.52 0.1 487.78 241.91 46747 +1935 247 18.27 12.27 16.62 0.74 463.59 242.39 46547 +1935 248 16.62 10.62 14.97 0 421.88 325.48 46347 +1935 249 15.7 9.7 14.05 0 400.05 325.57 46146 +1935 250 19.32 13.32 17.67 0 491.92 314.37 45945 +1935 251 17.57 11.57 15.92 0.06 445.49 237.72 45743 +1935 252 20.75 14.75 19.1 0.01 532.86 229.48 45541 +1935 253 20.01 14.01 18.36 0 511.32 306.09 45339 +1935 254 19.81 13.81 18.16 0.17 505.63 228.43 45136 +1935 255 21.75 15.75 20.1 0.07 563.17 222.41 44933 +1935 256 23.77 17.77 22.12 0 628.9 287.63 44730 +1935 257 20.43 14.43 18.78 0 523.45 296.23 44527 +1935 258 19.3 13.3 17.65 0 491.36 297.09 44323 +1935 259 22.21 16.21 20.56 0.79 577.6 214.65 44119 +1935 260 21.87 15.87 20.22 0.78 566.91 213.72 43915 +1935 261 22.09 16.09 20.44 0.12 573.81 211.44 43711 +1935 262 19.29 13.29 17.64 0.08 491.09 215.74 43507 +1935 263 19.46 13.46 17.81 0 495.8 284.78 43303 +1935 264 20.71 14.71 19.06 0.62 531.67 209.14 43099 +1935 265 20.29 14.29 18.64 0.44 519.38 208.29 42894 +1935 266 19.83 13.83 18.18 0 506.2 276.55 42690 +1935 267 17.28 11.28 15.63 0 438.16 280.19 42486 +1935 268 15.78 9.78 14.13 0 401.91 280.89 42282 +1935 269 13.86 7.86 12.21 0 359.26 282.11 42078 +1935 270 14.21 8.21 12.56 0.01 366.73 209.11 41875 +1935 271 17.68 11.68 16.03 0.54 448.29 201.81 41671 +1935 272 17.05 11.05 15.4 0 432.43 267.78 41468 +1935 273 14.2 8.2 12.55 0 366.52 270.92 41265 +1935 274 10.74 4.74 9.09 0 298.21 273.87 41062 +1935 275 10.94 4.94 9.29 0 301.83 270.76 40860 +1935 276 11.79 5.79 10.14 0 317.68 266.75 40658 +1935 277 13.87 7.87 12.22 0.58 359.47 195.52 40456 +1935 278 15.52 9.52 13.87 0.53 395.89 191.14 40255 +1935 279 19.63 13.63 17.98 0.04 500.56 182.51 40054 +1935 280 17.69 11.69 16.04 0.31 448.55 183.85 39854 +1935 281 18.32 12.32 16.67 0.32 464.91 180.84 39654 +1935 282 16.16 10.16 14.51 0.07 410.84 182.13 39455 +1935 283 13.55 7.55 11.9 0.32 352.75 183.47 39256 +1935 284 11.77 5.77 10.12 0.51 317.3 183.24 39058 +1935 285 12.78 6.78 11.13 0.01 337.02 180.13 38861 +1935 286 13.69 7.69 12.04 0 355.68 236.01 38664 +1935 287 20.85 14.85 19.2 0.02 535.82 164.3 38468 +1935 288 19.96 13.96 18.31 0.99 509.9 163.85 38273 +1935 289 18.22 12.22 16.57 0.29 462.28 164.74 38079 +1935 290 20.02 14.02 18.37 0.01 511.61 159.81 37885 +1935 291 17.54 11.54 15.89 0 444.72 215.6 37693 +1935 292 17.98 11.98 16.33 0 456.02 212.15 37501 +1935 293 17.92 11.92 16.27 0 454.46 209.62 37311 +1935 294 14.9 8.9 13.25 0 381.86 212.09 37121 +1935 295 14.68 8.68 13.03 0 376.98 209.64 36933 +1935 296 14.02 8.02 12.37 0 362.66 208.1 36745 +1935 297 13.79 7.79 12.14 0 357.78 205.74 36560 +1935 298 15.22 9.22 13.57 0 389.05 201.02 36375 +1935 299 16.08 10.08 14.43 0.18 408.95 147.7 36191 +1935 300 13.75 7.75 12.1 2.98 356.94 148.39 36009 +1935 301 12.63 6.63 10.98 0.4 334.03 147.66 35829 +1935 302 16 10 14.35 0 407.06 189.47 35650 +1935 303 14.81 8.81 13.16 0 379.85 188.76 35472 +1935 304 17.15 11.15 15.5 0 434.92 182.73 35296 +1935 305 5.71 -0.29 4.06 0.24 218.47 145.25 35122 +1935 306 9.41 3.41 7.76 0 275.02 188.01 34950 +1935 307 3.05 -2.95 1.4 0 184.28 190.79 34779 +1935 308 8.23 2.23 6.58 0 255.76 184.04 34610 +1935 309 6.81 0.81 5.16 0 234.13 182.97 34444 +1935 310 6.8 0.8 5.15 0 233.98 180.52 34279 +1935 311 12.17 6.17 10.52 0 324.99 173.05 34116 +1935 312 10.54 4.54 8.89 0 294.62 172.22 33956 +1935 313 12.86 6.86 11.21 0.09 338.63 125.67 33797 +1935 314 8.55 2.55 6.9 0 260.86 170.09 33641 +1935 315 9.62 3.62 7.97 0 278.57 166.58 33488 +1935 316 6.93 0.93 5.28 0 235.89 166.75 33337 +1935 317 12.04 6.04 10.39 0.19 322.47 119.84 33188 +1935 318 12.86 6.86 11.21 0.12 338.63 117.43 33042 +1935 319 11.04 5.04 9.39 0.43 303.66 117.64 32899 +1935 320 6.55 0.55 4.9 0 230.34 158.93 32758 +1935 321 4.67 -1.33 3.02 0 204.5 158.14 32620 +1935 322 3.75 -2.25 2.1 0 192.79 156.89 32486 +1935 323 4.29 -1.71 2.64 0.02 199.59 116.19 32354 +1935 324 11.1 5.1 9.45 0.07 304.76 110.61 32225 +1935 325 10.55 4.55 8.9 0.24 294.79 109.73 32100 +1935 326 10.38 4.38 8.73 0 291.77 145.04 31977 +1935 327 5.47 -0.53 3.82 1.32 215.17 110.28 31858 +1935 328 4.91 -1.09 3.26 1.4 207.65 109.08 31743 +1935 329 3.72 -2.28 2.07 0 192.42 144.66 31631 +1935 330 3.09 -2.91 1.44 0 184.76 143.56 31522 +1935 331 4.86 -1.14 3.21 0 206.99 141.2 31417 +1935 332 11.16 5.16 9.51 0 305.87 134.76 31316 +1935 333 8.97 2.97 7.32 0 267.7 135.58 31218 +1935 334 6.45 0.45 4.8 0 228.9 136.34 31125 +1935 335 3.1 -2.9 1.45 0 184.88 137.19 31035 +1935 336 4.57 -1.43 2.92 0 203.2 135.29 30949 +1935 337 5.3 -0.7 3.65 0.18 212.87 99.89 30867 +1935 338 6.48 0.48 4.83 0 229.33 131.49 30790 +1935 339 7.74 1.74 6.09 0 248.11 129.84 30716 +1935 340 7.83 1.83 6.18 0 249.5 129.05 30647 +1935 341 6.75 0.75 5.1 0.2 233.25 96.66 30582 +1935 342 2.49 -3.51 0.84 2.75 177.7 97.95 30521 +1935 343 2.79 -3.21 1.14 0.73 181.2 97.21 30465 +1935 344 -0.27 -6.27 -1.92 1.62 148.15 145.93 30413 +1935 345 1.33 -4.67 -0.32 0.1 164.72 144.98 30366 +1935 346 -2.52 -8.52 -4.17 0 127.31 178.24 30323 +1935 347 -2.72 -8.72 -4.37 0 125.59 177.77 30284 +1935 348 -1.23 -7.23 -2.88 0 138.93 176.92 30251 +1935 349 -1.54 -7.54 -3.19 0.04 136.05 144.81 30221 +1935 350 2.9 -3.1 1.25 0 182.5 174.2 30197 +1935 351 1.48 -4.52 -0.17 0.29 166.35 142.94 30177 +1935 352 1.42 -4.58 -0.23 1.98 165.69 142.72 30162 +1935 353 2.13 -3.87 0.48 0.67 173.58 142.16 30151 +1935 354 3.78 -2.22 2.13 0 193.17 172.24 30145 +1935 355 2.67 -3.33 1.02 0.06 179.79 141.08 30144 +1935 356 3.08 -2.92 1.43 0 184.64 171.85 30147 +1935 357 5.59 -0.41 3.94 0 216.82 169.76 30156 +1935 358 6.91 0.91 5.26 0 235.6 168.08 30169 +1935 359 10.57 4.57 8.92 0 295.15 120.64 30186 +1935 360 7.04 1.04 5.39 0.04 237.52 92.71 30208 +1935 361 5.03 -0.97 3.38 0 209.25 125.2 30235 +1935 362 9.11 3.11 7.46 0 270.01 122.91 30267 +1935 363 3.43 -2.57 1.78 0.03 188.86 95.33 30303 +1935 364 5.05 -0.95 3.4 0.07 209.51 94.95 30343 +1935 365 6.07 0.07 4.42 0 223.49 126.54 30388 +1936 1 8.28 2.28 6.63 0 256.55 125.93 30438 +1936 2 7.6 1.6 5.95 0 245.96 127.14 30492 +1936 3 9.16 3.16 7.51 0 270.84 126.92 30551 +1936 4 9.71 3.71 8.06 0.24 280.11 95.54 30614 +1936 5 10.42 4.42 8.77 0.4 292.48 95.57 30681 +1936 6 9.85 3.85 8.2 0.49 282.51 96.58 30752 +1936 7 7.83 1.83 6.18 0.49 249.5 98.33 30828 +1936 8 8.65 2.65 7 1.47 262.48 98.97 30907 +1936 9 7.07 1.07 5.42 0.1 237.97 100.77 30991 +1936 10 3.75 -2.25 2.1 0 192.79 137.75 31079 +1936 11 3.88 -2.12 2.23 0.08 194.41 104 31171 +1936 12 2.96 -3.04 1.31 0.56 183.21 105.14 31266 +1936 13 9.8 3.8 8.15 0.2 281.65 102.83 31366 +1936 14 8.07 2.07 6.42 0 253.24 139.95 31469 +1936 15 7.25 1.25 5.6 0.27 240.65 106.49 31575 +1936 16 9.99 3.99 8.34 0 284.93 141.05 31686 +1936 17 9.25 3.25 7.6 0.21 272.34 107.51 31800 +1936 18 9.78 3.78 8.13 0 281.31 144.75 31917 +1936 19 8.72 2.72 7.07 0.33 263.61 110.67 32038 +1936 20 8.21 2.21 6.56 0 255.44 149.54 32161 +1936 21 4.57 -1.43 2.92 0 203.2 154.17 32289 +1936 22 5.25 -0.75 3.6 0.03 212.19 116.6 32419 +1936 23 3.9 -2.1 2.25 0.06 194.66 118.58 32552 +1936 24 5.21 -0.79 3.56 0 211.65 159.31 32688 +1936 25 2.23 -3.77 0.58 0 174.72 163.07 32827 +1936 26 3.91 -2.09 2.26 0 194.79 163.99 32969 +1936 27 1.59 -4.41 -0.06 0 167.55 167.41 33114 +1936 28 1.45 -4.55 -0.2 2.39 166.02 127.28 33261 +1936 29 2.8 -3.2 1.15 0 181.32 171.3 33411 +1936 30 3.2 -2.8 1.55 0 186.07 173.3 33564 +1936 31 8.38 2.38 6.73 0 258.14 171.73 33718 +1936 32 6.25 0.25 4.6 0.03 226.04 131.71 33875 +1936 33 7.71 1.71 6.06 0 247.65 177.01 34035 +1936 34 9.34 3.34 7.69 0 273.84 177.68 34196 +1936 35 9.24 3.24 7.59 1.14 272.17 134.91 34360 +1936 36 1.81 -4.19 0.16 0 169.99 188.22 34526 +1936 37 1.55 -4.45 -0.1 0.34 167.11 143.11 34694 +1936 38 1.01 -4.99 -0.64 0.64 161.28 145.42 34863 +1936 39 -0.29 -6.29 -1.94 0.38 147.96 186.67 35035 +1936 40 2.94 -3.06 1.29 0.01 182.97 186.64 35208 +1936 41 5.91 -0.09 4.26 0 221.25 235.62 35383 +1936 42 3.95 -2.05 2.3 0.71 195.29 151.8 35560 +1936 43 6.86 0.86 5.21 0 234.86 202.7 35738 +1936 44 6.56 0.56 4.91 0 230.49 205.52 35918 +1936 45 7.34 1.34 5.69 0 242.01 207.4 36099 +1936 46 6.08 0.08 4.43 1.55 223.63 158.43 36282 +1936 47 5.27 -0.73 3.62 0.32 212.46 161.07 36466 +1936 48 2.23 -3.77 0.58 0.39 174.72 164.95 36652 +1936 49 1.42 -4.58 -0.23 0.2 165.69 167.47 36838 +1936 50 -2.43 -8.43 -4.08 0 128.09 228.28 37026 +1936 51 3.89 -2.11 2.24 0.05 194.54 170.35 37215 +1936 52 4.04 -1.96 2.39 0.36 196.42 172.39 37405 +1936 53 3.35 -2.65 1.7 0.11 187.89 175.04 37596 +1936 54 6.52 0.52 4.87 0.05 229.91 175.01 37788 +1936 55 9.34 3.34 7.69 0.02 273.84 174.95 37981 +1936 56 6.51 0.51 4.86 0.29 229.76 179.27 38175 +1936 57 5.22 -0.78 3.57 0 211.79 243.15 38370 +1936 58 7.19 1.19 5.54 0 239.76 244.12 38565 +1936 59 7.96 1.96 6.31 0.7 251.52 184.48 38761 +1936 60 13.55 7.55 11.9 0.19 352.75 180.95 38958 +1936 61 12.62 6.62 10.97 0 333.83 245.58 39156 +1936 62 13.28 7.28 11.63 0 347.17 247.27 39355 +1936 63 10.7 4.7 9.05 0 297.48 254.06 39553 +1936 64 12.55 6.55 10.9 0 332.44 254.2 39753 +1936 65 10.45 4.45 8.8 0 293.01 260.13 39953 +1936 66 13.08 7.08 11.43 0 343.08 258.86 40154 +1936 67 8.45 2.45 6.8 0.02 259.26 201.25 40355 +1936 68 10.48 4.48 8.83 1.22 293.55 201.37 40556 +1936 69 12.1 6.1 10.45 0.04 323.63 201.49 40758 +1936 70 12.38 6.38 10.73 0 329.09 271 40960 +1936 71 10.99 4.99 9.34 0.09 302.75 207.03 41163 +1936 72 10.2 4.2 8.55 0.2 288.6 209.99 41366 +1936 73 11.27 5.27 9.62 0 307.9 281.03 41569 +1936 74 10.88 4.88 9.23 0 300.74 284.34 41772 +1936 75 12.27 6.27 10.62 0 326.93 284.82 41976 +1936 76 11.85 5.85 10.2 0 318.82 288.11 42179 +1936 77 9.64 3.64 7.99 0.44 278.91 220.56 42383 +1936 78 8.24 2.24 6.59 0.09 255.92 224 42587 +1936 79 9.59 3.59 7.94 0 278.06 299.51 42791 +1936 80 9.67 3.67 8.02 0 279.43 301.92 42996 +1936 81 7.96 1.96 6.31 0 251.52 306.89 43200 +1936 82 5.21 -0.79 3.56 0 211.65 312.91 43404 +1936 83 7.84 1.84 6.19 0 249.65 312.21 43608 +1936 84 7.64 1.64 5.99 0 246.57 315.02 43812 +1936 85 9.56 3.56 7.91 0.32 277.55 236.11 44016 +1936 86 8.33 2.33 6.68 0.58 257.34 239.25 44220 +1936 87 7.73 1.73 6.08 0.06 247.95 241.78 44424 +1936 88 7.21 1.21 5.56 0 240.06 325.43 44627 +1936 89 7.92 1.92 6.27 0 250.9 326.77 44831 +1936 90 9.64 3.64 7.99 0 278.91 326.62 45034 +1936 91 12.05 6.05 10.4 0 322.66 324.82 45237 +1936 92 8.9 2.9 7.25 0 266.55 332.26 45439 +1936 93 9.88 3.88 8.23 0 283.03 332.96 45642 +1936 94 8.6 2.6 6.95 0 261.67 337.1 45843 +1936 95 8.07 2.07 6.42 0.09 253.24 255.03 46045 +1936 96 12.03 6.03 10.38 0 322.28 335.65 46246 +1936 97 13.39 7.39 11.74 0 349.43 335.05 46446 +1936 98 12.04 6.04 10.39 0.44 322.47 254.72 46647 +1936 99 11.9 5.9 10.25 0.38 319.78 256.42 46846 +1936 100 12.26 6.26 10.61 0 326.74 343.16 47045 +1936 101 19.86 13.86 18.21 0 507.05 326.59 47243 +1936 102 18.29 12.29 16.64 1.33 464.12 249.71 47441 +1936 103 12.7 6.7 11.05 0.04 335.42 260.96 47638 +1936 104 13.74 7.74 12.09 0 356.73 347.62 47834 +1936 105 13.98 7.98 12.33 0 361.81 348.89 48030 +1936 106 14.95 8.95 13.3 0.99 382.97 261.26 48225 +1936 107 16.02 10.02 14.37 0 407.53 347.44 48419 +1936 108 17.17 11.17 15.52 0 435.41 346.21 48612 +1936 109 15.44 9.44 13.79 0 394.06 352.15 48804 +1936 110 17.85 11.85 16.2 0 452.65 347.31 48995 +1936 111 16.66 10.66 15.01 0.07 422.85 264.01 49185 +1936 112 18.03 12.03 16.38 0.7 457.31 262.34 49374 +1936 113 19.37 13.37 17.72 0.67 493.3 260.37 49561 +1936 114 14.71 8.71 13.06 0.03 377.64 270.84 49748 +1936 115 9.97 3.97 8.32 0.34 284.59 279.15 49933 +1936 116 7.73 1.73 6.08 0.08 247.95 282.84 50117 +1936 117 12.49 6.49 10.84 0.29 331.25 277.46 50300 +1936 118 7.56 1.56 5.91 0 245.35 380.06 50481 +1936 119 8.72 2.72 7.07 0 263.61 379.44 50661 +1936 120 5.5 -0.5 3.85 0 215.58 385.43 50840 +1936 121 14.32 8.32 12.67 0 369.11 370.76 51016 +1936 122 16.64 10.64 14.99 0.04 422.37 274.62 51191 +1936 123 20.04 14.04 18.39 0.15 512.18 267.84 51365 +1936 124 19.2 13.2 17.55 0.39 488.61 270.63 51536 +1936 125 14 8 12.35 0.02 362.24 281.85 51706 +1936 126 20.46 14.46 18.81 0.08 524.33 269.02 51874 +1936 127 23.7 17.7 22.05 1.26 626.52 260.69 52039 +1936 128 25.6 19.6 23.95 0.29 693.95 255.33 52203 +1936 129 22.38 16.38 20.73 1.11 583.02 265.87 52365 +1936 130 22.97 16.97 21.32 0.1 602.13 264.74 52524 +1936 131 22.18 16.18 20.53 0.44 576.65 267.57 52681 +1936 132 20.85 14.85 19.2 0.6 535.82 271.76 52836 +1936 133 20.78 14.78 19.13 2.87 533.75 272.45 52989 +1936 134 21.12 15.12 19.47 0.49 543.91 272.08 53138 +1936 135 18.26 12.26 16.61 0.23 463.33 279.59 53286 +1936 136 14.07 8.07 12.42 0 363.73 384.6 53430 +1936 137 15.41 9.41 13.76 0.03 393.37 286.52 53572 +1936 138 15.87 9.87 14.22 0 404.01 381.44 53711 +1936 139 15.24 9.24 13.59 0 389.5 383.76 53848 +1936 140 16.17 10.17 14.52 0.11 411.08 286.37 53981 +1936 141 13.67 7.67 12.02 1.38 355.26 291.37 54111 +1936 142 15.78 9.78 14.13 2.01 401.91 287.85 54238 +1936 143 12.39 6.39 10.74 1.42 329.28 294.29 54362 +1936 144 17.23 11.23 15.58 0.25 436.91 285.63 54483 +1936 145 11.52 5.52 9.87 2.1 312.57 296.38 54600 +1936 146 13.45 7.45 11.8 1.65 350.68 293.55 54714 +1936 147 15.57 9.57 13.92 0 397.04 386.7 54824 +1936 148 13.52 7.52 11.87 0.03 352.13 294.08 54931 +1936 149 17.39 11.39 15.74 0 440.93 382.41 55034 +1936 150 24.5 18.5 22.85 0 654.2 357.32 55134 +1936 151 24.22 18.22 22.57 0 644.4 358.9 55229 +1936 152 23.14 17.14 21.49 0.1 607.74 272.61 55321 +1936 153 24.96 18.96 23.31 0 670.58 356.01 55409 +1936 154 20.95 14.95 19.3 0.18 538.81 279.25 55492 +1936 155 21.49 15.49 19.84 0.04 555.15 277.92 55572 +1936 156 15.34 9.34 13.69 0 391.77 389.94 55648 +1936 157 15.17 9.17 13.52 0 387.92 390.55 55719 +1936 158 16.18 10.18 14.53 0.06 411.32 291.05 55786 +1936 159 16.54 10.54 14.89 0 419.95 387.32 55849 +1936 160 19.06 13.06 17.41 0.42 484.77 284.99 55908 +1936 161 20.19 14.19 18.54 0 516.49 376.31 55962 +1936 162 19.57 13.57 17.92 0.01 498.88 283.84 56011 +1936 163 18.49 12.49 16.84 0.08 469.41 286.6 56056 +1936 164 16.84 10.84 15.19 0 427.25 387.06 56097 +1936 165 16.93 10.93 15.28 0 429.47 386.91 56133 +1936 166 20.75 14.75 19.1 0.71 532.86 281.14 56165 +1936 167 22.43 16.43 20.78 0.16 584.62 276.43 56192 +1936 168 21.2 15.2 19.55 0.6 546.32 279.95 56214 +1936 169 23.57 17.57 21.92 0 622.12 364.09 56231 +1936 170 25.66 19.66 24.01 0.11 696.18 266.19 56244 +1936 171 23.79 17.79 22.14 0.74 629.58 272.42 56252 +1936 172 24.56 18.56 22.91 0.31 656.32 269.94 56256 +1936 173 20.75 14.75 19.1 0.02 532.86 281.19 56255 +1936 174 21.81 15.81 20.16 0 565.04 370.98 56249 +1936 175 27 21 25.35 0 747.48 348.39 56238 +1936 176 25.75 19.75 24.1 0 699.53 354.39 56223 +1936 177 22.24 16.24 20.59 0.17 578.56 276.88 56203 +1936 178 23.33 17.33 21.68 0.51 614.06 273.67 56179 +1936 179 21.43 15.43 19.78 0.9 553.32 279.11 56150 +1936 180 19.3 13.3 17.65 0.85 491.36 284.54 56116 +1936 181 16.6 10.6 14.95 0.23 421.4 290.59 56078 +1936 182 22.57 16.57 20.92 0 589.12 367.5 56035 +1936 183 23.91 17.91 22.26 0.05 633.69 271.41 55987 +1936 184 24.3 18.3 22.65 0.07 647.19 270.05 55935 +1936 185 28.3 22.3 26.65 0.36 800.27 255.59 55879 +1936 186 28.44 22.44 26.79 0.01 806.14 254.84 55818 +1936 187 29.52 23.52 27.87 2.32 852.64 250.24 55753 +1936 188 29.45 23.45 27.8 0 849.56 333.8 55684 +1936 189 24.39 18.39 22.74 0 650.34 358.74 55611 +1936 190 24.36 18.36 22.71 0 649.28 358.51 55533 +1936 191 18.18 12.18 16.53 0 461.23 380.73 55451 +1936 192 18.51 12.51 16.86 0 469.94 379.42 55366 +1936 193 19.98 13.98 18.33 0.11 510.47 280.8 55276 +1936 194 21.74 15.74 20.09 0.31 562.86 275.96 55182 +1936 195 23.26 17.26 21.61 0.14 611.72 271.35 55085 +1936 196 22.79 16.79 21.14 0.27 596.25 272.45 54984 +1936 197 20.73 14.73 19.08 0 532.26 370.46 54879 +1936 198 21.39 15.39 19.74 0 552.1 367.69 54770 +1936 199 20.98 14.98 19.33 0 539.7 368.81 54658 +1936 200 22.02 16.02 20.37 1.92 571.61 273.46 54542 +1936 201 24.75 18.75 23.1 0.03 663.06 264.82 54423 +1936 202 22.05 16.05 20.4 0.02 572.55 272.61 54301 +1936 203 19.41 13.41 17.76 0.03 494.41 279.13 54176 +1936 204 18.14 12.14 16.49 0 460.18 375.62 54047 +1936 205 21.04 15.04 19.39 0 541.5 365.64 53915 +1936 206 22.68 16.68 21.03 0 592.67 359.02 53780 +1936 207 22.48 16.48 20.83 0.45 586.22 269.36 53643 +1936 208 24.55 18.55 22.9 0 655.97 350.12 53502 +1936 209 27.34 21.34 25.69 0 760.99 336.62 53359 +1936 210 26.56 20.56 24.91 0.29 730.29 254.87 53213 +1936 211 27.82 21.82 26.17 0.48 780.42 249.66 53064 +1936 212 26.52 20.52 24.87 0 728.75 338.52 52913 +1936 213 28.05 22.05 26.4 0 789.88 330.26 52760 +1936 214 27.01 21.01 25.36 0 747.87 334.75 52604 +1936 215 25.13 19.13 23.48 0.06 676.72 257.08 52445 +1936 216 23.16 17.16 21.51 0 608.4 349.94 52285 +1936 217 20.09 14.09 18.44 0 513.62 360.09 52122 +1936 218 18.83 12.83 17.18 0 478.52 363.27 51958 +1936 219 21.05 15.05 19.4 0 541.8 355 51791 +1936 220 21.97 15.97 20.32 0 570.04 350.81 51622 +1936 221 20.23 14.23 18.58 0.95 517.65 266.87 51451 +1936 222 17.84 11.84 16.19 0 452.4 362.12 51279 +1936 223 21.68 15.68 20.03 0.2 561.01 261.53 51105 +1936 224 21.87 15.87 20.22 0.03 566.91 260.23 50929 +1936 225 21.72 15.72 20.07 0 562.24 346.39 50751 +1936 226 22.32 16.32 20.67 0 581.1 343.1 50572 +1936 227 21.02 15.02 19.37 0 540.9 346.42 50392 +1936 228 22.93 16.93 21.28 0 600.82 338.4 50210 +1936 229 17.93 11.93 16.28 0 454.72 353.53 50026 +1936 230 17.85 11.85 16.2 0.12 452.65 264.35 49842 +1936 231 22.56 16.56 20.91 0 588.79 335.88 49656 +1936 232 21.56 15.56 19.91 0.26 557.3 253.58 49469 +1936 233 19.31 13.31 17.66 0 491.64 343.95 49280 +1936 234 20.74 14.74 19.09 0.4 532.56 253.54 49091 +1936 235 22.78 16.78 21.13 0.07 595.92 247.15 48900 +1936 236 19.81 13.81 18.16 0 505.63 338.1 48709 +1936 237 14.99 8.99 13.34 0 383.87 349.36 48516 +1936 238 16.59 10.59 14.94 0 421.16 343.78 48323 +1936 239 20.23 14.23 18.58 0 517.65 332 48128 +1936 240 23.07 17.07 21.42 0.06 605.43 240.52 47933 +1936 241 24.1 18.1 22.45 0.16 640.23 236.38 47737 +1936 242 22.84 16.84 21.19 0.6 597.88 238.62 47541 +1936 243 23.03 17.03 21.38 0.45 604.11 236.76 47343 +1936 244 22.55 16.55 20.9 0.41 588.47 236.7 47145 +1936 245 24.73 18.73 23.08 0.1 662.35 229.34 46947 +1936 246 21.27 15.27 19.62 0.07 548.44 237.14 46747 +1936 247 20.33 14.33 18.68 0.75 520.54 237.97 46547 +1936 248 17.68 11.68 16.03 0 448.29 322.81 46347 +1936 249 19.58 13.58 17.93 0.04 499.16 236.67 46146 +1936 250 21.1 15.1 19.45 0.28 543.31 231.81 45945 +1936 251 23.28 17.28 21.63 0 612.39 299.81 45743 +1936 252 19.2 13.2 17.55 0 488.61 310.48 45541 +1936 253 19.69 13.69 18.04 0 502.24 307.01 45339 +1936 254 17.64 11.64 15.99 0 447.27 310.37 45136 +1936 255 16.27 10.27 14.62 0 413.46 311.41 44933 +1936 256 18.49 12.49 16.84 0 469.41 303.7 44730 +1936 257 19.68 13.68 18.03 0.11 501.96 223.77 44527 +1936 258 15.06 9.06 13.41 0 385.44 307.25 44323 +1936 259 15.3 9.3 13.65 0.48 390.86 228.22 44119 +1936 260 13.74 7.74 12.09 0.23 356.73 228.78 43915 +1936 261 12.47 6.47 10.82 0.01 330.86 228.68 43711 +1936 262 15.92 9.92 14.27 0 405.18 295.72 43507 +1936 263 14.22 8.22 12.57 0 366.95 296.74 43303 +1936 264 17.13 11.13 15.48 0 434.42 288 43099 +1936 265 17.78 11.78 16.13 0 450.85 284.13 42894 +1936 266 21.67 15.67 20.02 0.26 560.7 203.56 42690 +1936 267 19.38 13.38 17.73 0.21 493.58 206.33 42486 +1936 268 21.46 15.46 19.81 0.33 554.23 200.24 42282 +1936 269 17.43 11.43 15.78 0.51 441.94 206.12 42078 +1936 270 17.67 11.67 16.02 1.02 448.04 203.76 41875 +1936 271 19.44 13.44 17.79 1.67 495.25 198.66 41671 +1936 272 16.63 10.63 14.98 0.65 422.13 201.51 41468 +1936 273 17.43 11.43 15.78 0 441.94 264.45 41265 +1936 274 11.21 5.21 9.56 0.15 306.79 204.88 41062 +1936 275 8.81 2.81 7.16 0.02 265.08 205.27 40860 +1936 276 5.24 -0.76 3.59 1.36 212.06 206.26 40658 +1936 277 5.57 -0.43 3.92 0.61 216.54 203.94 40456 +1936 278 3.31 -2.69 1.66 0 187.4 271.11 40255 +1936 279 4.93 -1.07 3.28 0.42 207.92 200.03 40054 +1936 280 6.02 0.02 4.37 0 222.79 262.87 39854 +1936 281 7.61 1.61 5.96 0 246.11 258.35 39654 +1936 282 10.76 4.76 9.11 0 298.57 251.62 39455 +1936 283 7.88 1.88 6.23 1.09 250.27 189.27 39256 +1936 284 6.43 0.43 4.78 0.01 228.61 188.14 39058 +1936 285 13.38 7.38 11.73 0 349.23 239.25 38861 +1936 286 13.98 7.98 12.33 0.05 361.81 176.66 38664 +1936 287 15.13 9.13 13.48 0.27 387.01 173.04 38468 +1936 288 13.46 7.46 11.81 0.98 350.88 173.01 38273 +1936 289 18.24 12.24 16.59 0 462.8 219.62 38079 +1936 290 17.4 11.4 15.75 0.88 441.18 163.87 37885 +1936 291 12.87 6.87 11.22 1.35 338.83 167.55 37693 +1936 292 14.43 8.43 12.78 0 371.5 218.37 37501 +1936 293 12.01 6.01 10.36 0.03 321.89 164.4 37311 +1936 294 11.87 5.87 10.22 1.1 319.2 162.37 37121 +1936 295 8.45 2.45 6.8 0.09 259.26 163.29 36933 +1936 296 7.21 1.21 5.56 0.52 240.06 162.27 36745 +1936 297 9.44 3.44 7.79 2.1 275.52 158.46 36560 +1936 298 10.45 4.45 8.8 0.72 293.01 155.63 36375 +1936 299 6.2 0.2 4.55 0 225.33 209.06 36191 +1936 300 4.74 -1.26 3.09 0 205.42 207.58 36009 +1936 301 4.22 -1.78 2.57 0 198.7 205.41 35829 +1936 302 7.92 1.92 6.27 0 250.9 199.57 35650 +1936 303 11.41 5.41 9.76 0 310.51 193.24 35472 +1936 304 10.53 4.53 8.88 0.02 294.44 143.85 35296 +1936 305 9.78 3.78 8.13 0 281.31 189.88 35122 +1936 306 8.34 2.34 6.69 0 257.5 189.07 34950 +1936 307 3.64 -2.36 1.99 0 191.43 190.39 34779 +1936 308 4.45 -1.55 2.8 0 201.65 187.17 34610 +1936 309 8.04 2.04 6.39 0 252.77 181.89 34444 +1936 310 8.47 2.47 6.82 0 259.58 179.05 34279 +1936 311 1.31 -4.69 -0.34 0 164.5 182.15 34116 +1936 312 1.28 -4.72 -0.37 0.05 164.17 134.61 33956 +1936 313 -0.5 -6.5 -2.15 0.13 145.9 173.12 33797 +1936 314 1.4 -4.6 -0.25 0 165.48 214.69 33641 +1936 315 3.76 -2.24 2.11 0.05 192.92 128.43 33488 +1936 316 5.77 -0.23 4.12 0.79 219.3 125.73 33337 +1936 317 2.48 -3.52 0.83 0.01 177.58 125.71 33188 +1936 318 9.43 3.43 7.78 0.39 275.36 120.06 33042 +1936 319 7.87 1.87 6.22 0 250.12 159.75 32899 +1936 320 5.13 -0.87 3.48 0 210.58 159.95 32758 +1936 321 7.34 1.34 5.69 0 242.01 156.21 32620 +1936 322 10.52 4.52 8.87 0 294.26 151.65 32486 +1936 323 10.41 4.41 8.76 0 292.3 150.16 32354 +1936 324 12.32 6.32 10.67 0 327.91 146.25 32225 +1936 325 10.29 4.29 8.64 0 290.18 146.55 32100 +1936 326 10.42 4.42 8.77 0 292.48 145 31977 +1936 327 8.36 2.36 6.71 0 257.82 144.93 31858 +1936 328 10.15 4.15 8.5 0 287.72 141.47 31743 +1936 329 8.37 2.37 6.72 0 257.98 141.49 31631 +1936 330 11.24 5.24 9.59 0.03 307.35 103.19 31522 +1936 331 8.87 2.87 7.22 0.59 266.06 103.76 31417 +1936 332 11.08 5.08 9.43 0 304.4 134.84 31316 +1936 333 8.92 2.92 7.27 0 266.88 135.62 31218 +1936 334 9.2 3.2 7.55 0 271.5 134.31 31125 +1936 335 5.27 -0.73 3.62 0 212.46 135.93 31035 +1936 336 6.02 0.02 4.37 0.17 222.79 100.79 30949 +1936 337 1.28 -4.72 -0.37 0.14 164.17 101.52 30867 +1936 338 4.35 -1.65 2.7 0.04 200.36 99.6 30790 +1936 339 4.34 -1.66 2.69 0 200.23 132.02 30716 +1936 340 8.36 2.36 6.71 0.02 257.82 96.5 30647 +1936 341 4.16 -1.84 2.51 0.37 197.94 97.85 30582 +1936 342 4.6 -1.4 2.95 0.1 203.59 97.09 30521 +1936 343 3.13 -2.87 1.48 0 185.23 129.44 30465 +1936 344 4.83 -1.17 3.18 0 206.6 127.37 30413 +1936 345 7.59 1.59 5.94 0 245.81 125.19 30366 +1936 346 3.9 -2.1 2.25 0.33 194.66 95.19 30323 +1936 347 1.13 -4.87 -0.52 0.31 162.56 95.77 30284 +1936 348 0.96 -5.04 -0.69 0 160.75 127.42 30251 +1936 349 1.02 -4.98 -0.63 0 161.39 127.01 30221 +1936 350 2.34 -3.66 0.69 0.02 175.97 94.54 30197 +1936 351 2.71 -3.29 1.06 0 180.26 125.65 30177 +1936 352 3.58 -2.42 1.93 0.3 190.7 93.83 30162 +1936 353 -0.66 -6.66 -2.31 0.56 144.34 140.81 30151 +1936 354 2.33 -3.67 0.68 0 175.86 170.9 30145 +1936 355 2.62 -3.38 0.97 0 179.21 170.41 30144 +1936 356 1.14 -4.86 -0.51 0 162.67 170.98 30147 +1936 357 1.69 -4.31 0.04 0 168.65 170.55 30156 +1936 358 2.78 -3.22 1.13 0 181.08 169.72 30169 +1936 359 3.35 -2.65 1.7 0 187.89 125.42 30186 +1936 360 3.11 -2.89 1.46 0 184.99 125.91 30208 +1936 361 4.95 -1.05 3.3 0 208.18 125.24 30235 +1936 362 6.5 0.5 4.85 0.06 229.62 93.55 30267 +1936 363 6.28 0.28 4.63 0.03 226.47 94.09 30303 +1936 364 0.28 -5.72 -1.37 0.14 153.68 96.75 30343 +1936 365 -5.84 -11.84 -7.49 0 101.2 131.72 30388 +1937 1 -8.45 -14.45 -10.1 0.2 84.07 143.97 30438 +1937 2 -10.26 -16.26 -11.91 0.04 73.73 144.87 30492 +1937 3 -5.63 -11.63 -7.28 0 102.7 178.23 30551 +1937 4 -5 -11 -6.65 0 107.32 178.88 30614 +1937 5 1.58 -4.42 -0.07 0 167.44 176.71 30681 +1937 6 0.2 -5.8 -1.45 0 152.86 178.11 30752 +1937 7 0.19 -5.81 -1.46 0 152.76 178.78 30828 +1937 8 1.56 -4.44 -0.09 0.07 167.22 145.25 30907 +1937 9 1.68 -4.32 0.03 0 168.54 180.2 30991 +1937 10 0.33 -5.67 -1.32 0 154.19 181.98 31079 +1937 11 -1.21 -7.21 -2.86 0 139.11 183.52 31171 +1937 12 -3.43 -9.43 -5.08 0 119.63 185.26 31266 +1937 13 -1.23 -7.23 -2.88 0.96 138.93 152.91 31366 +1937 14 0.01 -5.99 -1.64 0.76 150.94 153.48 31469 +1937 15 0 -6 -1.65 0 150.84 190.98 31575 +1937 16 -0.9 -6.9 -2.55 0.46 142.04 156.93 31686 +1937 17 -0.18 -6.18 -1.83 0.18 149.05 158.34 31800 +1937 18 2.32 -3.68 0.67 0 175.74 195.87 31917 +1937 19 5.02 -0.98 3.37 0 209.11 195.39 32038 +1937 20 5.37 -0.63 3.72 0 213.82 195.89 32161 +1937 21 3.19 -2.81 1.54 0 185.95 198.69 32289 +1937 22 3.13 -2.87 1.48 0.58 185.23 160.71 32419 +1937 23 3.26 -2.74 1.61 0 186.8 201.03 32552 +1937 24 3.37 -2.63 1.72 0 188.13 202.44 32688 +1937 25 2.63 -3.37 0.98 0 179.33 204.28 32827 +1937 26 2.16 -3.84 0.51 0 173.92 206.04 32969 +1937 27 0.1 -5.9 -1.55 0.46 151.85 166.95 33114 +1937 28 -0.7 -6.7 -2.35 0 143.96 211.44 33261 +1937 29 -1.56 -7.56 -3.21 0.18 135.87 171.18 33411 +1937 30 2.24 -3.76 0.59 0.63 174.83 170.92 33564 +1937 31 3 -3 1.35 0.04 183.68 171.81 33718 +1937 32 7.44 1.44 5.79 0 243.52 174.64 33875 +1937 33 2.5 -3.5 0.85 0.31 177.82 135.66 34035 +1937 34 4.44 -1.56 2.79 0 201.52 181.8 34196 +1937 35 1.03 -4.97 -0.62 0 161.49 186.15 34360 +1937 36 2.25 -3.75 0.6 0 174.94 187.94 34526 +1937 37 1.26 -4.74 -0.39 0 163.96 190.99 34694 +1937 38 4.01 -1.99 2.36 0 196.04 191.94 34863 +1937 39 -1 -7 -2.65 0 141.09 197.65 35035 +1937 40 -1.59 -7.59 -3.24 0 135.6 200.6 35208 +1937 41 -0.59 -6.59 -2.24 0 145.02 202.73 35383 +1937 42 2.23 -3.77 0.58 0 174.72 203.61 35560 +1937 43 -1.07 -7.07 -2.72 0 140.43 208.32 35738 +1937 44 0.7 -5.3 -0.95 0 158.01 209.9 35918 +1937 45 2.4 -3.6 0.75 0 176.66 211.44 36099 +1937 46 5.51 -0.49 3.86 0.34 215.72 158.8 36282 +1937 47 4.54 -1.46 2.89 0 202.81 215.36 36466 +1937 48 8.1 2.1 6.45 0 253.71 214.9 36652 +1937 49 9.1 3.1 7.45 0 269.84 216.58 36838 +1937 50 10.85 4.85 9.2 0 300.2 217.14 37026 +1937 51 12.53 6.53 10.88 0 332.04 217.84 37215 +1937 52 8.58 2.58 6.93 0 261.35 225.52 37405 +1937 53 13.1 7.1 11.45 0.03 343.48 166.99 37596 +1937 54 8.67 2.67 7.02 0.22 262.8 173.31 37788 +1937 55 10.75 4.75 9.1 0.44 298.39 173.64 37981 +1937 56 7.08 1.08 5.43 0.09 238.11 178.83 38175 +1937 57 6.17 0.17 4.52 0.79 224.9 181.68 38370 +1937 58 6.6 0.6 4.95 0 231.07 244.74 38565 +1937 59 5.58 -0.42 3.93 0 216.68 248.46 38761 +1937 60 9.53 3.53 7.88 0.37 277.05 185.23 38958 +1937 61 15.17 9.17 13.52 0.06 387.92 181.03 39156 +1937 62 11.52 5.52 9.87 1.25 312.57 187.46 39355 +1937 63 11.12 5.12 9.47 1.35 305.13 190.11 39553 +1937 64 10.32 4.32 8.67 1.23 290.71 193.09 39753 +1937 65 7.77 1.77 6.12 1.85 248.57 197.65 39953 +1937 66 8.06 2.06 6.41 0 253.08 265.92 40154 +1937 67 7.03 1.03 5.38 0 237.37 270.02 40355 +1937 68 9.51 3.51 7.86 0.07 276.71 202.37 40556 +1937 69 10.19 4.19 8.54 0.47 288.42 203.62 40758 +1937 70 11.13 5.13 9.48 0.55 305.31 204.71 40960 +1937 71 7.75 1.75 6.1 1.22 248.26 210.32 41163 +1937 72 9.37 3.37 7.72 0.02 274.35 210.86 41366 +1937 73 6.33 0.33 4.68 0.05 227.18 215.7 41569 +1937 74 7.98 1.98 6.33 0 251.83 288.37 41772 +1937 75 8.9 2.9 7.25 0 266.55 289.89 41976 +1937 76 8.85 2.85 7.2 0 265.73 292.59 42179 +1937 77 10.77 4.77 9.12 0.27 298.75 219.3 42383 +1937 78 9.77 3.77 8.12 0.06 281.14 222.4 42587 +1937 79 11.11 5.11 9.46 0 304.95 297.2 42791 +1937 80 11.76 5.76 10.11 0 317.1 298.65 42996 +1937 81 9.81 3.81 8.16 0.01 281.82 228.21 43200 +1937 82 11.95 5.95 10.3 0.29 320.74 227.62 43404 +1937 83 14.98 8.98 13.33 0.3 383.64 225.18 43608 +1937 84 11.16 5.16 9.51 0.66 305.87 232.35 43812 +1937 85 10.65 4.65 9 0 296.59 313.11 44016 +1937 86 9.52 3.52 7.87 0.4 276.88 237.96 44220 +1937 87 6.06 0.06 4.41 0 223.35 324.52 44424 +1937 88 2.32 -3.68 0.67 0.13 175.74 248.22 44627 +1937 89 1.72 -4.28 0.07 0 168.99 333.86 44831 +1937 90 2.22 -3.78 0.57 0 174.6 335.81 45034 +1937 91 8.63 2.63 6.98 0 262.15 330.4 45237 +1937 92 8.99 2.99 7.34 0 268.03 332.12 45439 +1937 93 8.57 2.57 6.92 0 261.19 334.97 45642 +1937 94 11.12 5.12 9.47 0 305.13 333.04 45843 +1937 95 16.14 10.14 14.49 0.12 410.37 243.7 46045 +1937 96 16.16 10.16 14.51 0.32 410.84 245.21 46246 +1937 97 19.19 13.19 17.54 1.7 488.33 240.77 46446 +1937 98 14.35 8.35 12.7 0 369.76 334.98 46647 +1937 99 17.11 11.11 15.46 1.53 433.92 247.86 46846 +1937 100 14.92 8.92 13.27 0.73 382.3 253.22 47045 +1937 101 15.81 9.81 14.16 0.1 402.61 253.1 47243 +1937 102 12.72 6.72 11.07 0.16 335.82 259.56 47441 +1937 103 8.66 2.66 7.01 0.43 262.64 266.31 47638 +1937 104 11.15 5.15 9.5 0.49 305.68 264.55 47834 +1937 105 11.95 5.95 10.3 0 320.74 353.03 48030 +1937 106 12.15 6.15 10.5 0.19 324.6 265.72 48225 +1937 107 13.37 7.37 11.72 0 349.02 353.49 48419 +1937 108 14.88 8.88 13.23 0 381.41 351.88 48612 +1937 109 12.85 6.85 11.2 0 338.42 357.91 48804 +1937 110 12.16 6.16 10.51 0 324.79 360.72 48995 +1937 111 13.9 7.9 12.25 0 360.11 358.63 49185 +1937 112 17.61 11.61 15.96 0.88 446.5 263.22 49374 +1937 113 14.37 8.37 12.72 0.52 370.19 270.32 49561 +1937 114 12.88 6.88 11.23 0.23 339.03 273.88 49748 +1937 115 11.53 5.53 9.88 0 312.76 369.32 49933 +1937 116 7 1 5.35 0.26 236.93 283.65 50117 +1937 117 5.97 -0.03 4.32 0 222.09 381.01 50300 +1937 118 5.19 -0.81 3.54 0.21 211.39 287.55 50481 +1937 119 5.89 -0.11 4.24 0 220.97 383.7 50661 +1937 120 9.64 3.64 7.99 0 278.91 379.08 50840 +1937 121 18.96 12.96 17.31 0 482.04 358.36 51016 +1937 122 21.68 15.68 20.03 0.18 561.01 262.9 51191 +1937 123 23.05 17.05 21.4 0.01 604.77 259.81 51365 +1937 124 23.02 17.02 21.37 0.01 603.78 260.67 51536 +1937 125 19.43 13.43 17.78 0.43 494.97 270.81 51706 +1937 126 16.15 10.15 14.5 0.17 410.61 278.64 51874 +1937 127 20.01 14.01 18.36 0 511.32 361.04 52039 +1937 128 23.03 17.03 21.38 0 604.11 351.19 52203 +1937 129 20.68 14.68 19.03 0.01 530.79 270.44 52365 +1937 130 14.27 8.27 12.62 1.08 368.03 284.79 52524 +1937 131 14.49 8.49 12.84 0 372.81 380 52681 +1937 132 14.04 8.04 12.39 0.22 363.09 286.42 52836 +1937 133 13.16 7.16 11.51 0 344.71 384.61 52989 +1937 134 18.92 12.92 17.27 0 480.96 370.08 53138 +1937 135 21.8 15.8 20.15 0.72 564.73 270.75 53286 +1937 136 18.08 12.08 16.43 0.06 458.62 280.47 53430 +1937 137 16.15 10.15 14.5 0 410.61 380.1 53572 +1937 138 13.29 7.29 11.64 0 347.37 387.72 53711 +1937 139 14.16 8.16 12.51 0.16 365.66 289.81 53848 +1937 140 19.13 13.13 17.48 0 486.69 373.18 53981 +1937 141 19.45 13.45 17.8 0.44 495.53 279.43 54111 +1937 142 23.78 17.78 22.13 0.24 629.24 267.87 54238 +1937 143 21.35 15.35 19.7 0 550.88 367.08 54362 +1937 144 21.5 15.5 19.85 0 555.46 367 54483 +1937 145 24.76 18.76 23.11 0 663.42 354.4 54600 +1937 146 21.32 15.32 19.67 0 549.96 368.48 54714 +1937 147 23.49 17.49 21.84 0 619.42 360.59 54824 +1937 148 21.91 15.91 20.26 0.08 568.16 275.36 54931 +1937 149 23.72 17.72 22.07 0.1 627.2 270.23 55034 +1937 150 24.55 18.55 22.9 0 655.97 357.11 55134 +1937 151 21.27 15.27 19.62 0 548.44 370.52 55229 +1937 152 25.07 19.07 23.42 0.12 674.55 266.46 55321 +1937 153 26.09 20.09 24.44 0.77 712.3 263.11 55409 +1937 154 24.07 18.07 22.42 0.37 639.2 270.14 55492 +1937 155 22.45 16.45 20.8 1.24 585.26 275.2 55572 +1937 156 22.87 16.87 21.22 0.33 598.86 274.2 55648 +1937 157 21.28 15.28 19.63 0 548.75 371.81 55719 +1937 158 18.62 12.62 16.97 0 472.87 380.96 55786 +1937 159 20.93 14.93 19.28 0.25 538.21 280.11 55849 +1937 160 22.14 16.14 20.49 0 575.39 369.2 55908 +1937 161 20.75 14.75 19.1 0.06 532.86 280.78 55962 +1937 162 20.5 14.5 18.85 0.22 525.5 281.48 56011 +1937 163 22.58 16.58 20.93 0.01 589.44 275.87 56056 +1937 164 25.16 19.16 23.51 0.3 677.81 267.76 56097 +1937 165 28.68 22.68 27.03 0.21 816.28 254.69 56133 +1937 166 27.86 21.86 26.21 0 782.06 344.04 56165 +1937 167 29.71 23.71 28.06 1.73 861.05 250.37 56192 +1937 168 24.53 18.53 22.88 1.84 655.26 270 56214 +1937 169 21 15 19.35 0.84 540.3 280.5 56231 +1937 170 19.11 13.11 17.46 1.2 486.14 285.32 56244 +1937 171 19.59 13.59 17.94 0.17 499.44 284.19 56252 +1937 172 22.14 16.14 20.49 0.71 575.39 277.37 56256 +1937 173 19.96 13.96 18.31 0.31 509.9 283.24 56255 +1937 174 21.58 15.58 19.93 0.01 557.92 278.88 56249 +1937 175 21.52 15.52 19.87 0.01 556.07 279.02 56238 +1937 176 21.69 15.69 20.04 0.21 561.31 278.52 56223 +1937 177 17.4 11.4 15.75 0.54 441.18 289.09 56203 +1937 178 19.17 13.17 17.52 0.15 487.78 285.03 56179 +1937 179 19.76 13.76 18.11 0 504.22 378 56150 +1937 180 17.74 11.74 16.09 0.01 449.83 288.18 56116 +1937 181 18.57 12.57 16.92 0.78 471.54 286.23 56078 +1937 182 21.18 15.18 19.53 0.06 545.72 279.54 56035 +1937 183 22.29 16.29 20.64 0.01 580.15 276.31 55987 +1937 184 23.52 17.52 21.87 0.62 620.43 272.52 55935 +1937 185 25.63 19.63 23.98 0 695.06 354.06 55879 +1937 186 23.05 17.05 21.4 0 604.77 364.93 55818 +1937 187 24.81 18.81 23.16 0.07 665.2 268.01 55753 +1937 188 25.78 19.78 24.13 0.19 700.65 264.51 55684 +1937 189 24.88 18.88 23.23 0.24 667.71 267.45 55611 +1937 190 24.97 18.97 23.32 0.06 670.94 266.88 55533 +1937 191 23.46 17.46 21.81 0.07 618.41 271.52 55451 +1937 192 20.02 14.02 18.37 0 511.61 374.54 55366 +1937 193 25.31 19.31 23.66 0 683.28 353.51 55276 +1937 194 28.2 22.2 26.55 0.62 796.1 254.36 55182 +1937 195 23.9 17.9 22.25 0.2 633.35 269.37 55085 +1937 196 21.15 15.15 19.5 0.09 544.81 277.07 54984 +1937 197 17.77 11.77 16.12 1.13 450.6 285 54879 +1937 198 17.01 11.01 15.36 1.24 431.44 286.32 54770 +1937 199 20.93 14.93 19.28 0.86 538.21 276.74 54658 +1937 200 24.54 18.54 22.89 0.72 655.61 265.85 54542 +1937 201 25.55 19.55 23.9 0.02 692.1 262.15 54423 +1937 202 25.89 19.89 24.24 0.16 704.76 260.57 54301 +1937 203 24.73 18.73 23.08 0.53 662.35 264.11 54176 +1937 204 25.16 19.16 23.51 1.51 677.81 262.33 54047 +1937 205 25.3 19.3 23.65 0.11 682.91 261.49 53915 +1937 206 21.53 15.53 19.88 0 556.38 363.33 53780 +1937 207 18.77 12.77 17.12 0.69 476.9 278.95 53643 +1937 208 16.48 10.48 14.83 0.8 418.5 283.43 53502 +1937 209 22.69 16.69 21.04 0.71 593 267.79 53359 +1937 210 20 14 18.35 1.1 511.04 274.54 53213 +1937 211 21.74 15.74 20.09 1.28 562.86 269.43 53064 +1937 212 19.78 13.78 18.13 1.29 504.78 273.91 52913 +1937 213 20.93 14.93 19.28 0.28 538.21 270.43 52760 +1937 214 16.33 10.33 14.68 0.14 414.89 280.39 52604 +1937 215 20.06 14.06 18.41 0.92 512.76 271.57 52445 +1937 216 21.69 15.69 20.04 0 561.31 355.47 52285 +1937 217 20 14 18.35 0.03 511.04 270.29 52122 +1937 218 21.64 15.64 19.99 0 559.77 353.96 51958 +1937 219 24.18 18.18 22.53 0 643.01 343.17 51791 +1937 220 23.44 17.44 21.79 0.03 617.74 258.93 51622 +1937 221 29.29 23.29 27.64 0.28 842.55 237.85 51451 +1937 222 25.46 19.46 23.81 0.04 688.78 251.14 51279 +1937 223 24.54 18.54 22.89 0.01 655.61 253.26 51105 +1937 224 23.77 17.77 22.12 0.02 628.9 254.85 50929 +1937 225 24.71 18.71 23.06 0.85 661.64 251.14 50751 +1937 226 23.8 17.8 22.15 1.94 629.93 253.1 50572 +1937 227 23.74 17.74 22.09 0.03 627.88 252.34 50392 +1937 228 22.76 16.76 21.11 0.09 595.27 254.27 50210 +1937 229 22.47 16.47 20.82 1.29 585.9 254.17 50026 +1937 230 20.33 14.33 18.68 0 520.54 345 49842 +1937 231 17.74 11.74 16.09 0 449.83 351.29 49656 +1937 232 22.9 16.9 21.25 0 599.84 333.31 49469 +1937 233 24.32 18.32 22.67 0.16 647.88 244.84 49280 +1937 234 23.58 17.58 21.93 1.69 622.45 245.99 49091 +1937 235 23.64 17.64 21.99 0.56 624.48 244.74 48900 +1937 236 22.76 16.76 21.11 0.02 595.27 246.16 48709 +1937 237 22.74 16.74 21.09 0.39 594.62 245.01 48516 +1937 238 22.87 16.87 21.22 0.16 598.86 243.44 48323 +1937 239 19.32 13.32 17.67 0.06 491.92 251.08 48128 +1937 240 15.38 9.38 13.73 1.43 392.69 257.55 47933 +1937 241 19.27 13.27 17.62 2.33 490.54 248.58 47737 +1937 242 18.81 12.81 17.16 2.72 477.98 248.28 47541 +1937 243 21.51 15.51 19.86 0.89 555.77 240.69 47343 +1937 244 18.46 12.46 16.81 0.87 468.61 246.25 47145 +1937 245 16.41 10.41 14.76 0.24 416.81 248.85 46947 +1937 246 18.77 12.77 17.12 0.68 476.9 242.75 46747 +1937 247 16.74 10.74 15.09 1.06 424.8 245.35 46547 +1937 248 18.87 12.87 17.22 0.25 479.6 239.71 46347 +1937 249 22.64 16.64 20.99 0.05 591.38 229.45 46146 +1937 250 20.1 14.1 18.45 0.25 513.9 234.09 45945 +1937 251 20.71 14.71 19.06 0.62 531.67 231.16 45743 +1937 252 19.08 13.08 17.43 0.1 485.32 233.11 45541 +1937 253 18.87 12.87 17.22 0.72 479.6 231.96 45339 +1937 254 19.67 13.67 18.02 0.14 501.68 228.72 45136 +1937 255 18.22 12.22 16.57 0.7 462.28 229.99 44933 +1937 256 20.67 14.67 19.02 0 530.49 297.64 44730 +1937 257 17.8 11.8 16.15 0 451.37 303.31 44527 +1937 258 11.66 5.66 10.01 0.96 315.21 235.31 44323 +1937 259 14.03 8.03 12.38 0.41 362.88 230.17 44119 +1937 260 12.36 6.36 10.71 0.09 328.69 230.7 43915 +1937 261 15.24 9.24 13.59 1.5 389.5 224.67 43711 +1937 262 17.55 11.55 15.9 0.36 444.98 219.01 43507 +1937 263 17.46 11.46 15.81 0 442.7 289.78 43303 +1937 264 19.45 13.45 17.8 0 495.53 282.29 43099 +1937 265 21.82 15.82 20.17 0.31 565.35 205.01 42894 +1937 266 19.93 13.93 18.28 0 509.04 276.29 42690 +1937 267 22.52 16.52 20.87 0.02 587.51 199.72 42486 +1937 268 24.13 18.13 22.48 0.22 641.27 194.04 42282 +1937 269 23 17 21.35 0.45 603.12 194.99 42078 +1937 270 24.03 18.03 22.38 0.42 637.82 190.66 41875 +1937 271 21.84 15.84 20.19 0.75 565.97 193.83 41671 +1937 272 19.22 13.22 17.57 0 489.16 262.77 41468 +1937 273 16.6 10.6 14.95 0.04 421.4 199.67 41265 +1937 274 14.83 8.83 13.18 0 380.3 267.08 41062 +1937 275 16.35 10.35 14.7 0 415.37 261.37 40860 +1937 276 11.43 5.43 9.78 0 310.88 267.3 40658 +1937 277 14.23 8.23 12.58 0 367.17 260.06 40456 +1937 278 14.58 8.58 12.93 0.91 374.78 192.43 40255 +1937 279 12.66 6.66 11.01 0.75 334.62 192.75 40054 +1937 280 12.53 6.53 10.88 0.02 332.04 190.9 39854 +1937 281 16.32 10.32 14.67 0.05 414.65 183.93 39654 +1937 282 16.8 10.8 15.15 0 426.27 241.6 39455 +1937 283 16.71 10.71 15.06 0.02 424.07 179.26 39256 +1937 284 16.64 10.64 14.99 0 422.37 236.18 39058 +1937 285 14.99 8.99 13.34 0 383.87 236.59 38861 +1937 286 15.18 9.18 13.53 0.09 388.14 175.15 38664 +1937 287 12.56 6.56 10.91 0 332.64 234.81 38468 +1937 288 14.25 8.25 12.6 0 367.6 229.43 38273 +1937 289 15.58 9.58 13.93 0 397.27 224.6 38079 +1937 290 15.68 9.68 14.03 0 399.59 221.62 37885 +1937 291 16.95 10.95 15.3 0.26 429.96 162.53 37693 +1937 292 10.31 4.31 8.66 0 290.53 224.12 37501 +1937 293 9.21 3.21 7.56 0.4 271.67 167 37311 +1937 294 11.16 5.16 9.51 0.03 305.87 163.06 37121 +1937 295 13.41 7.41 11.76 0 349.85 211.55 36933 +1937 296 11.37 5.37 9.72 0.25 309.76 158.8 36745 +1937 297 11.76 5.76 10.11 0 317.1 208.51 36560 +1937 298 14.93 8.93 13.28 0 382.52 201.47 36375 +1937 299 15.41 9.41 13.76 0.16 393.37 148.5 36191 +1937 300 16 10 14.35 0.11 407.06 145.85 36009 +1937 301 15.6 9.6 13.95 0 397.74 192.64 35829 +1937 302 17.47 11.47 15.82 0 442.95 187.04 35650 +1937 303 16.57 10.57 14.92 0.46 420.67 139.54 35472 +1937 304 12.02 6.02 10.37 0 322.08 190.07 35296 +1937 305 1.27 -4.73 -0.38 0 164.07 196.81 35122 +1937 306 7.21 1.21 5.56 0.23 240.06 142.58 34950 +1937 307 7.67 1.67 6.02 0.17 247.03 140.38 34779 +1937 308 2.92 -3.08 1.27 0 182.73 188.23 34610 +1937 309 2.41 -3.59 0.76 1.35 176.78 139.65 34444 +1937 310 5.35 -0.65 3.7 0.78 213.54 136.26 34279 +1937 311 3.7 -2.3 2.05 0.77 192.17 135.49 34116 +1937 312 4.9 -1.1 3.25 0.04 207.52 132.86 33956 +1937 313 6 0 4.35 0 222.51 174.18 33797 +1937 314 9.47 3.47 7.82 0 276.03 169.24 33641 +1937 315 9.92 3.92 8.27 0 283.72 166.29 33488 +1937 316 11.77 5.77 10.12 0.08 317.3 121.67 33337 +1937 317 13.01 7.01 11.36 0.37 341.66 119.02 33188 +1937 318 8.49 2.49 6.84 0 259.9 160.92 33042 +1937 319 11.59 5.59 9.94 0.15 313.89 117.22 32899 +1937 320 3.91 -2.09 2.26 0 194.79 160.75 32758 +1937 321 4.34 -1.66 2.69 0 200.23 158.35 32620 +1937 322 6.7 0.7 5.05 0 232.52 154.88 32486 +1937 323 8.24 2.24 6.59 0 255.92 152.06 32354 +1937 324 7.41 1.41 5.76 0 243.07 150.68 32225 +1937 325 6.96 0.96 5.31 0 236.34 149.3 32100 +1937 326 8 2 6.35 0 252.14 147.06 31977 +1937 327 6.18 0.18 4.53 0 225.05 146.56 31858 +1937 328 2.69 -3.31 1.04 0 180.03 146.75 31743 +1937 329 9.93 3.93 8.28 0 283.89 140.19 31631 +1937 330 9.82 3.82 8.17 2.96 282 104.15 31522 +1937 331 14.17 8.17 12.52 0.87 365.87 99.99 31417 +1937 332 10.08 4.08 8.43 0.27 286.5 101.79 31316 +1937 333 7.51 1.51 5.86 0.41 244.59 102.52 31218 +1937 334 11.04 5.04 9.39 0 303.66 132.74 31125 +1937 335 9.25 3.25 7.6 0.05 272.34 99.83 31035 +1937 336 9.04 3.04 7.39 0.09 268.85 99.16 30949 +1937 337 11.24 5.24 9.59 0.29 307.35 96.54 30867 +1937 338 9.83 3.83 8.18 0 282.17 129.01 30790 +1937 339 10.43 4.43 8.78 0.56 292.66 95.81 30716 +1937 340 6.37 0.37 4.72 0 227.75 130.05 30647 +1937 341 8.21 2.21 6.56 0 255.44 127.87 30582 +1937 342 6.21 0.21 4.56 0.16 225.47 96.36 30521 +1937 343 3.5 -2.5 1.85 0 189.71 129.24 30465 +1937 344 0.96 -5.04 -0.69 0.06 160.75 97.02 30413 +1937 345 0.6 -5.4 -1.05 0 156.97 129.08 30366 +1937 346 1.07 -4.93 -0.58 3.54 161.92 96.24 30323 +1937 347 2.18 -3.82 0.53 0.51 174.15 95.4 30284 +1937 348 1.03 -4.97 -0.62 3.49 161.49 95.54 30251 +1937 349 1.25 -4.75 -0.4 0.57 163.85 95.18 30221 +1937 350 0.56 -5.44 -1.09 0.01 156.56 95.15 30197 +1937 351 3.15 -2.85 1.5 0.01 185.47 94.07 30177 +1937 352 1.24 -4.76 -0.41 0 163.74 126.25 30162 +1937 353 7.17 1.17 5.52 0.01 239.46 92.19 30151 +1937 354 2.31 -3.69 0.66 0 175.63 125.65 30145 +1937 355 0.39 -5.61 -1.26 0.53 154.8 94.89 30144 +1937 356 2.95 -3.05 1.3 0.03 183.09 94.02 30147 +1937 357 5.31 -0.69 3.66 0 213 124.13 30156 +1937 358 5.21 -0.79 3.56 0 211.65 124.28 30169 +1937 359 -0.3 -6.3 -1.95 0 147.86 127.11 30186 +1937 360 -1.96 -7.96 -3.61 0 132.25 128.12 30208 +1937 361 -1.15 -7.15 -2.8 0.47 139.68 141.26 30235 +1937 362 -2.68 -8.68 -4.33 0 125.93 174.26 30267 +1937 363 -0.02 -6.02 -1.67 0.06 150.64 141.79 30303 +1937 364 -1.37 -7.37 -3.02 0 137.62 174.85 30343 +1937 365 -2.91 -8.91 -4.56 0 123.97 175.92 30388 +1938 1 -2.88 -8.88 -4.53 0 124.22 176.74 30438 +1938 2 -2.91 -8.91 -4.56 0 123.97 177.41 30492 +1938 3 -3.57 -9.57 -5.22 0 118.49 178.5 30551 +1938 4 -1.56 -7.56 -3.21 0 135.87 178.62 30614 +1938 5 -2.63 -8.63 -4.28 0 126.36 179.57 30681 +1938 6 3.54 -2.46 1.89 0 190.2 177.14 30752 +1938 7 2.79 -3.21 1.14 0 181.2 177.87 30828 +1938 8 2.14 -3.86 0.49 0 173.69 179.3 30907 +1938 9 0.25 -5.75 -1.4 0 153.37 181.31 30991 +1938 10 2.19 -3.81 0.54 0 174.26 181.29 31079 +1938 11 5.29 -0.71 3.64 0.89 212.73 103.36 31171 +1938 12 2.56 -3.44 0.91 0 178.51 140.4 31266 +1938 13 0.3 -5.7 -1.35 0.83 153.88 107.36 31366 +1938 14 0.18 -5.82 -1.47 0 152.66 144.69 31469 +1938 15 2.2 -3.8 0.55 0 174.37 145.15 31575 +1938 16 2.37 -3.63 0.72 1.24 176.32 109.77 31686 +1938 17 5.02 -0.98 3.37 0 209.11 146.48 31800 +1938 18 4.51 -1.49 2.86 0 202.42 148.69 31917 +1938 19 2.97 -3.03 1.32 0.07 183.33 113.66 32038 +1938 20 3.23 -2.77 1.58 0 186.44 152.99 32161 +1938 21 4.11 -1.89 2.46 0 197.3 154.46 32289 +1938 22 7.34 1.34 5.69 0 242.01 153.94 32419 +1938 23 6.28 0.28 4.63 0 226.47 156.5 32552 +1938 24 6.34 0.34 4.69 0 227.32 158.51 32688 +1938 25 6.45 0.45 4.8 0 228.9 160.3 32827 +1938 26 8.52 2.52 6.87 0 260.38 160.53 32969 +1938 27 7.44 1.44 5.79 0 243.52 163.43 33114 +1938 28 7.96 1.96 6.31 0.01 251.52 123.89 33261 +1938 29 4.12 -1.88 2.47 0 197.43 170.46 33411 +1938 30 2.29 -3.71 0.64 0 175.4 173.87 33564 +1938 31 -1.13 -7.13 -2.78 0 139.86 178.1 33718 +1938 32 -3.05 -9.05 -4.7 0 122.79 181.11 33875 +1938 33 -1.41 -7.41 -3.06 0 137.25 183.03 34035 +1938 34 2.16 -3.84 0.51 0 173.92 183.31 34196 +1938 35 2.13 -3.87 0.48 0 173.58 185.49 34360 +1938 36 5.72 -0.28 4.07 0 218.61 185.48 34526 +1938 37 7.13 1.13 5.48 0.15 238.86 140.04 34694 +1938 38 3.86 -2.14 2.21 0.25 194.16 144.03 34863 +1938 39 5.45 -0.55 3.8 0 214.9 193.45 35035 +1938 40 2.53 -3.47 0.88 0 178.16 198.21 35208 +1938 41 0.89 -5.11 -0.76 0.16 160.01 151.41 35383 +1938 42 1.51 -4.49 -0.14 0.34 166.68 153.06 35560 +1938 43 2.81 -3.19 1.16 0.11 181.43 154.45 35738 +1938 44 4.97 -1.03 3.32 0 208.45 206.88 35918 +1938 45 6.2 0.2 4.55 0.02 225.33 156.34 36099 +1938 46 4.31 -1.69 2.66 0 199.85 212.72 36282 +1938 47 8.46 2.46 6.81 0 259.42 211.74 36466 +1938 48 7.95 1.95 6.3 0.07 251.36 161.29 36652 +1938 49 10.01 4.01 8.36 0 285.28 215.54 36838 +1938 50 8.82 2.82 7.17 0 265.24 219.52 37026 +1938 51 11.32 5.32 9.67 0 308.83 219.46 37215 +1938 52 6.55 0.55 4.9 0 230.34 227.61 37405 +1938 53 1.37 -4.63 -0.28 0 165.15 234.86 37596 +1938 54 1.63 -4.37 -0.02 0 167.99 237.46 37788 +1938 55 3.11 -2.89 1.46 0 184.99 239.36 37981 +1938 56 2.43 -3.57 0.78 0.3 177.01 181.96 38175 +1938 57 5.57 -0.43 3.92 0 216.54 242.83 38370 +1938 58 5.25 -0.75 3.6 0 212.19 246.06 38565 +1938 59 6.1 0.1 4.45 0 223.91 247.95 38761 +1938 60 6.94 0.94 5.29 0.05 236.04 187.48 38958 +1938 61 5.37 -0.63 3.72 0 213.82 254.5 39156 +1938 62 6.36 0.36 4.71 0.24 227.61 192.22 39355 +1938 63 6.95 0.95 5.3 0 236.19 258.68 39553 +1938 64 7.78 1.78 6.13 0.09 248.73 195.48 39753 +1938 65 6.98 0.98 5.33 0 236.63 264.43 39953 +1938 66 11.35 5.35 9.7 0 309.39 261.54 40154 +1938 67 10.28 4.28 8.63 0.52 290 199.45 40355 +1938 68 7.21 1.21 5.56 0.22 240.06 204.51 40556 +1938 69 7.51 1.51 5.86 0.28 244.59 206.22 40758 +1938 70 6.74 0.74 5.09 0.37 233.1 209.02 40960 +1938 71 6.49 0.49 4.84 0.08 229.48 211.43 41163 +1938 72 8.54 2.54 6.89 0.03 260.7 211.69 41366 +1938 73 9.3 3.3 7.65 0.02 273.17 212.92 41569 +1938 74 10.39 4.39 8.74 0 291.95 285.07 41772 +1938 75 12.86 6.86 11.21 0 338.63 283.82 41976 +1938 76 13.29 7.29 11.64 0 347.37 285.65 42179 +1938 77 12.9 6.9 11.25 0 339.43 288.89 42383 +1938 78 15.71 9.71 14.06 0.04 400.28 214.58 42587 +1938 79 17.4 11.4 15.75 0 441.18 285.01 42791 +1938 80 12.69 6.69 11.04 0 335.22 297.05 42996 +1938 81 15.65 9.65 14 0 398.89 293.83 43200 +1938 82 14.05 8.05 12.4 0 363.3 299.67 43404 +1938 83 6.89 0.89 5.24 0 235.3 313.44 43608 +1938 84 9.03 3.03 7.38 0 268.69 313.09 43812 +1938 85 17.35 11.35 15.7 0.23 439.92 224.87 44016 +1938 86 17.5 11.5 15.85 0 443.71 301.78 44220 +1938 87 15.73 9.73 14.08 0 400.75 308.35 44424 +1938 88 16.93 10.93 15.28 0 429.47 307.86 44627 +1938 89 21.17 15.17 19.52 0 545.42 298.53 44831 +1938 90 19.67 13.67 18.02 0.52 501.68 228.89 45034 +1938 91 10.82 4.82 9.17 0 299.65 326.96 45237 +1938 92 11.8 5.8 10.15 0.02 317.87 245.62 45439 +1938 93 11.15 5.15 9.5 0.34 305.68 248.13 45642 +1938 94 10.44 4.44 8.79 0 292.83 334.2 45843 +1938 95 12.61 6.61 10.96 0 333.63 332.46 46045 +1938 96 10.22 4.22 8.57 0 288.95 338.83 46246 +1938 97 10.12 4.12 8.47 0 287.2 341.05 46446 +1938 98 12.67 6.67 11.02 0 334.82 338.43 46647 +1938 99 10.76 4.76 9.11 0 298.57 343.95 46846 +1938 100 10.53 4.53 8.88 0 294.44 346.3 47045 +1938 101 11.63 5.63 9.98 0 314.64 346.27 47243 +1938 102 12.31 6.31 10.66 0 327.71 346.88 47441 +1938 103 13.44 7.44 11.79 0.12 350.47 259.83 47638 +1938 104 12.57 6.57 10.92 0.32 332.83 262.52 47834 +1938 105 15.51 9.51 13.86 0.77 395.66 259.06 48030 +1938 106 14.85 8.85 13.2 0.54 380.74 261.43 48225 +1938 107 13.46 7.46 11.81 0.16 350.88 264.97 48419 +1938 108 14.83 8.83 13.18 0 380.3 352 48612 +1938 109 11.61 5.61 9.96 0.06 314.26 270.28 48804 +1938 110 9.24 3.24 7.59 0 272.17 366.01 48995 +1938 111 8.42 2.42 6.77 0.04 258.78 276.68 49185 +1938 112 8.76 2.76 7.11 0 264.26 369.91 49374 +1938 113 9.07 3.07 7.42 0 269.35 370.77 49561 +1938 114 9.3 3.3 7.65 0.15 273.17 278.92 49748 +1938 115 4.42 -1.58 2.77 0 201.26 380.41 49933 +1938 116 4.45 -1.55 2.8 0 201.65 381.64 50117 +1938 117 3.32 -2.68 1.67 0.64 187.52 288.26 50300 +1938 118 4.09 -1.91 2.44 0 197.05 384.79 50481 +1938 119 3.68 -2.32 2.03 0 191.93 386.52 50661 +1938 120 7.26 1.26 5.61 0 240.81 382.94 50840 +1938 121 15.93 9.93 14.28 0 405.42 366.84 51016 +1938 122 15.02 9.02 13.37 0.02 384.54 277.72 51191 +1938 123 14.48 8.48 12.83 0 372.59 372.61 51365 +1938 124 15.74 9.74 14.09 0 400.98 370.6 51536 +1938 125 19.07 13.07 17.42 0 485.04 362.21 51706 +1938 126 23.82 17.82 22.17 0 630.61 346.26 51874 +1938 127 25.79 19.79 24.14 0 701.02 338.65 52039 +1938 128 21.97 15.97 20.32 0.1 570.04 266.4 52203 +1938 129 19.79 13.79 18.14 0.58 505.07 272.67 52365 +1938 130 19.67 13.67 18.02 0 501.68 364.72 52524 +1938 131 14.99 8.99 13.34 0 383.87 378.79 52681 +1938 132 10.53 4.53 8.88 0.15 294.44 291.95 52836 +1938 133 12.1 6.1 10.45 0 323.63 386.88 52989 +1938 134 15.85 9.85 14.2 0.02 403.54 284.13 53138 +1938 135 17.69 11.69 16.04 0 448.55 374.47 53286 +1938 136 13.36 7.36 11.71 0.05 348.81 289.68 53430 +1938 137 12.03 6.03 10.38 1.12 322.28 292.37 53572 +1938 138 8.48 2.48 6.83 0.02 259.74 297.82 53711 +1938 139 11.45 5.45 9.8 1.15 311.26 294.25 53848 +1938 140 9.51 3.51 7.86 2.54 276.71 297.39 53981 +1938 141 10.29 4.29 8.64 0.92 290.18 296.66 54111 +1938 142 11.5 5.5 9.85 0.53 312.19 295.27 54238 +1938 143 14.22 8.22 12.57 0.17 366.95 291.19 54362 +1938 144 11.87 5.87 10.22 0 319.2 393.97 54483 +1938 145 15.12 9.12 13.47 0 386.79 386.99 54600 +1938 146 16.13 10.13 14.48 0 410.13 384.74 54714 +1938 147 18.24 12.24 16.59 1.21 462.8 284.39 54824 +1938 148 17.46 11.46 15.81 1.01 442.7 286.42 54931 +1938 149 19.83 13.83 18.18 1.58 506.2 281.11 55034 +1938 150 18.33 12.33 16.68 0.01 465.17 284.95 55134 +1938 151 21.01 15.01 19.36 0 540.6 371.46 55229 +1938 152 25.84 19.84 24.19 0 702.89 351.77 55321 +1938 153 23.96 17.96 22.31 0 635.41 360.34 55409 +1938 154 23.53 17.53 21.88 0.02 620.77 271.83 55492 +1938 155 23.59 17.59 21.94 0 622.79 362.37 55572 +1938 156 22.84 16.84 21.19 0 597.88 365.72 55648 +1938 157 23.38 17.38 21.73 0.01 615.73 272.78 55719 +1938 158 23.16 17.16 21.51 0 608.4 364.77 55786 +1938 159 26.95 20.95 25.3 0.03 745.51 260.99 55849 +1938 160 23.82 17.82 22.17 0.58 630.61 271.85 55908 +1938 161 24.04 18.04 22.39 0.01 638.16 271.21 55962 +1938 162 24.14 18.14 22.49 0.07 641.62 270.93 56011 +1938 163 24.38 18.38 22.73 0 649.98 360.42 56056 +1938 164 25.15 19.15 23.5 0 677.45 357.05 56097 +1938 165 23.9 17.9 22.25 0 633.35 362.6 56133 +1938 166 23.75 17.75 22.1 1.28 628.22 272.48 56165 +1938 167 27.53 21.53 25.88 0.67 768.63 259.27 56192 +1938 168 21.56 15.56 19.91 0.02 557.3 278.96 56214 +1938 169 24.71 18.71 23.06 0.11 661.64 269.41 56231 +1938 170 24.99 18.99 23.34 0.49 671.66 268.48 56244 +1938 171 21.7 15.7 20.05 0.39 561.62 278.63 56252 +1938 172 19.73 13.73 18.08 0.28 503.37 283.83 56256 +1938 173 20.12 14.12 18.47 0 514.48 377.11 56255 +1938 174 20.93 14.93 19.28 0 538.21 374.2 56249 +1938 175 24.88 18.88 23.23 0 667.71 358.39 56238 +1938 176 22.25 16.25 20.6 0.56 578.87 276.93 56223 +1938 177 19.53 13.53 17.88 0.05 497.76 284.13 56203 +1938 178 19.1 13.1 17.45 0.01 485.86 285.2 56179 +1938 179 14.71 8.71 13.06 0 377.64 392.62 56150 +1938 180 17.98 11.98 16.33 0 456.02 383.53 56116 +1938 181 16.28 10.28 14.63 0 413.7 388.33 56078 +1938 182 18.4 12.4 16.75 0.02 467.02 286.52 56035 +1938 183 17.66 11.66 16.01 0 447.78 384.08 55987 +1938 184 19.08 13.08 17.43 0 485.32 379.55 55935 +1938 185 22.87 16.87 21.22 0 598.86 365.9 55879 +1938 186 25.6 19.6 23.95 0.01 693.95 265.46 55818 +1938 187 22.58 16.58 20.93 0 589.44 366.61 55753 +1938 188 22.51 16.51 20.86 0 587.18 366.62 55684 +1938 189 24.49 18.49 22.84 0 653.85 358.31 55611 +1938 190 23.28 17.28 21.63 0 612.39 363.02 55533 +1938 191 23.74 17.74 22.09 0 627.88 360.87 55451 +1938 192 24.1 18.1 22.45 0 640.23 359.07 55366 +1938 193 24.56 18.56 22.91 0 656.32 356.83 55276 +1938 194 24.77 18.77 23.12 0 663.78 355.7 55182 +1938 195 24.08 18.08 22.43 0 639.54 358.41 55085 +1938 196 22.86 16.86 21.21 0 598.53 362.99 54984 +1938 197 25.53 19.53 23.88 0.03 691.36 263.4 54879 +1938 198 30.85 24.85 29.2 0 912.99 322.7 54770 +1938 199 28.41 22.41 26.76 0 804.87 336.25 54658 +1938 200 19.88 13.88 18.23 0.19 507.62 279.14 54542 +1938 201 13.69 7.69 12.04 0.29 355.68 291.74 54423 +1938 202 16.02 10.02 14.37 0 407.53 382.64 54301 +1938 203 17.47 11.47 15.82 0 442.95 378.1 54176 +1938 204 21.15 15.15 19.5 0.25 544.81 274.33 54047 +1938 205 21.56 15.56 19.91 0.43 557.3 272.83 53915 +1938 206 27.55 21.55 25.9 0.02 769.44 253.06 53780 +1938 207 24.37 18.37 22.72 1.08 649.63 263.64 53643 +1938 208 29.28 23.28 27.63 0.29 842.11 245.29 53502 +1938 209 26.74 20.74 25.09 2.1 737.28 254.66 53359 +1938 210 26.44 20.44 24.79 0.02 725.66 255.3 53213 +1938 211 24.79 18.79 23.14 0.28 664.49 260.33 53064 +1938 212 27.57 21.57 25.92 0 770.25 333.4 52913 +1938 213 30.05 24.05 28.4 0 876.27 319.43 52760 +1938 214 26.5 20.5 24.85 0 727.97 337.19 52604 +1938 215 27.49 21.49 25.84 0 767.02 331.77 52445 +1938 216 26.97 20.97 25.32 0 746.3 333.35 52285 +1938 217 22.32 16.32 20.67 0.28 581.1 264.21 52122 +1938 218 24.49 18.49 22.84 0.84 653.85 257.17 51958 +1938 219 24.85 18.85 23.2 1.7 666.63 255.27 51791 +1938 220 19.28 13.28 17.63 0.35 490.81 269.91 51622 +1938 221 20.76 14.76 19.11 0.01 533.15 265.55 51451 +1938 222 20.75 14.75 19.1 0.01 532.86 264.79 51279 +1938 223 22.33 16.33 20.68 0 581.42 346.35 51105 +1938 224 20.53 14.53 18.88 1.35 526.38 263.7 50929 +1938 225 23.5 17.5 21.85 1.36 619.76 254.81 50751 +1938 226 22.4 16.4 20.75 0.34 583.66 257.11 50572 +1938 227 20.29 14.29 18.64 0.43 519.38 261.63 50392 +1938 228 21.75 15.75 20.1 0.04 563.17 257.02 50210 +1938 229 18 12 16.35 0.03 456.53 265 50026 +1938 230 18.46 12.46 16.81 3.13 468.61 263.05 49842 +1938 231 19.46 13.46 17.81 0.51 495.8 259.7 49656 +1938 232 20.6 14.6 18.95 0.98 528.43 255.99 49469 +1938 233 25.03 19.03 23.38 0.28 673.11 242.67 49280 +1938 234 21.72 15.72 20.07 1.08 562.24 251.07 49091 +1938 235 20.03 14.03 18.38 0.8 511.9 254.13 48900 +1938 236 20.77 14.77 19.12 0.43 533.45 251.3 48709 +1938 237 20.18 14.18 18.53 0.26 516.2 251.49 48516 +1938 238 22.99 16.99 21.34 0.28 602.79 243.11 48323 +1938 239 20.38 14.38 18.73 0.21 522 248.65 48128 +1938 240 18.76 12.76 17.11 0.84 476.63 250.98 47933 +1938 241 20.63 14.63 18.98 0 529.31 327.3 47737 +1938 242 21.9 15.9 20.25 0.31 567.85 241.07 47541 +1938 243 21.95 15.95 20.3 0.04 569.41 239.58 47343 +1938 244 18.99 12.99 17.34 0 482.86 326.84 47145 +1938 245 19.29 13.29 17.64 0 491.09 324.15 46947 +1938 246 17.52 11.52 15.87 0.03 444.22 245.27 46747 +1938 247 16.06 10.06 14.41 0.57 408.48 246.59 46547 +1938 248 13.82 7.82 12.17 0.27 358.42 248.82 46347 +1938 249 14.26 8.26 12.61 0 367.81 328.74 46146 +1938 250 11.48 5.48 9.83 0 311.82 332.12 45945 +1938 251 12 6 10.35 0 321.7 329.01 45743 +1938 252 15.72 9.72 14.07 0 400.51 319.23 45541 +1938 253 18.59 12.59 16.94 0.01 472.07 232.53 45339 +1938 254 15.71 9.71 14.06 0.12 400.28 236.22 45136 +1938 255 15.58 9.58 13.93 0 397.27 312.97 44933 +1938 256 15.84 9.84 14.19 0 403.31 310.1 44730 +1938 257 15.16 9.16 13.51 0 387.69 309.41 44527 +1938 258 15.18 9.18 13.53 0 388.14 307 44323 +1938 259 16.39 10.39 14.74 0 416.33 301.9 44119 +1938 260 19.25 13.25 17.6 0 489.98 292.49 43915 +1938 261 19.57 13.57 17.92 0 498.88 289.23 43711 +1938 262 17.62 11.62 15.97 0.7 446.76 218.88 43507 +1938 263 16.88 10.88 15.23 0 428.23 291.13 43303 +1938 264 18.59 12.59 16.94 0 472.07 284.5 43099 +1938 265 19.64 13.64 17.99 0 500.84 279.47 42894 +1938 266 20.46 14.46 18.81 0 524.33 274.85 42690 +1938 267 19.81 13.81 18.16 0 505.63 274 42486 +1938 268 23.07 17.07 21.42 0 605.43 262.15 42282 +1938 269 25.62 19.62 23.97 0 694.69 251.23 42078 +1938 270 22.92 16.92 21.27 0 600.49 257.73 41875 +1938 271 20.65 14.65 19 0.09 529.9 196.31 41671 +1938 272 21.7 15.7 20.05 0 561.62 256.23 41468 +1938 273 18.4 12.4 16.75 0 467.02 262.26 41265 +1938 274 18.63 12.63 16.98 0 473.14 259.11 41062 +1938 275 20.44 14.44 18.79 0.12 523.74 188.99 40860 +1938 276 17.11 11.11 15.46 0.27 433.92 192.85 40658 +1938 277 14.84 8.84 13.19 0.74 380.52 194.22 40456 +1938 278 14.22 8.22 12.57 0.3 366.95 192.91 40255 +1938 279 19.39 13.39 17.74 0.53 493.86 182.93 40054 +1938 280 19.25 13.25 17.6 0.77 489.98 181.26 39854 +1938 281 15.61 9.61 13.96 0.04 397.97 184.93 39654 +1938 282 9.86 3.86 8.21 0.48 282.68 189.62 39455 +1938 283 12.51 6.51 10.86 0 331.65 246.25 39256 +1938 284 12.33 6.33 10.68 0 328.11 243.5 39058 +1938 285 13.53 7.53 11.88 0.01 352.34 179.26 38861 +1938 286 14.21 8.21 12.56 0 366.73 235.17 38664 +1938 287 15.37 9.37 13.72 0.57 392.46 172.73 38468 +1938 288 13.57 7.57 11.92 0 353.17 230.51 38273 +1938 289 10.45 4.45 8.8 0 293.01 232.25 38079 +1938 290 11.59 5.59 9.94 0 313.89 227.89 37885 +1938 291 12.19 6.19 10.54 0.06 325.37 168.27 37693 +1938 292 12.73 6.73 11.08 0.66 336.02 165.69 37501 +1938 293 13.25 7.25 11.6 0 346.55 217.46 37311 +1938 294 14.69 8.69 13.04 0 377.2 212.42 37121 +1938 295 9.34 3.34 7.69 0 273.84 216.75 36933 +1938 296 13.63 7.63 11.98 0 354.42 208.67 36745 +1938 297 11.51 5.51 9.86 0 312.38 208.83 36560 +1938 298 15.18 9.18 13.53 0.22 388.14 150.82 36375 +1938 299 14.52 8.52 12.87 0.04 373.46 149.52 36191 +1938 300 12.28 6.28 10.63 0 327.13 199.83 36009 +1938 301 14.03 8.03 12.38 0 362.88 194.97 35829 +1938 302 17.28 11.28 15.63 0.22 438.16 140.53 35650 +1938 303 13.07 7.07 11.42 0.04 342.87 143.38 35472 +1938 304 15.12 9.12 13.47 0 386.79 185.9 35296 +1938 305 14.5 8.5 12.85 0.25 373.03 138.08 35122 +1938 306 13.27 7.27 11.62 0.29 346.96 137.67 34950 +1938 307 8.24 2.24 6.59 0.01 255.92 139.98 34779 +1938 308 10.06 4.06 8.41 0 286.15 182.24 34610 +1938 309 10.29 4.29 8.64 0 290.18 179.69 34444 +1938 310 11.64 5.64 9.99 0 314.83 175.8 34279 +1938 311 8.64 2.64 6.99 0.15 262.32 132.54 34116 +1938 312 7.16 1.16 5.51 0 239.31 175.38 33956 +1938 313 8.09 2.09 6.44 0 253.55 172.45 33797 +1938 314 8.88 2.88 7.23 0 266.22 169.79 33641 +1938 315 7.61 1.61 5.96 0.17 246.11 126.28 33488 +1938 316 7.09 1.09 5.44 0.52 238.26 124.96 33337 +1938 317 4.77 -1.23 3.12 0.07 205.81 124.61 33188 +1938 318 2.03 -3.97 0.38 0 172.45 165.5 33042 +1938 319 3.02 -2.98 1.37 0 183.92 163.19 32899 +1938 320 2.46 -3.54 0.81 0 177.35 161.63 32758 +1938 321 4.23 -1.77 2.58 0 198.83 158.42 32620 +1938 322 4.99 -1.01 3.34 0 208.72 156.09 32486 +1938 323 7.35 1.35 5.7 0 242.16 152.77 32354 +1938 324 11.39 5.39 9.74 0 310.13 147.2 32225 +1938 325 12.82 6.82 11.17 0 337.82 144.04 32100 +1938 326 13.7 7.7 12.05 0.26 355.89 106.25 31977 +1938 327 9.95 3.95 8.3 0.02 284.24 107.7 31858 +1938 328 12.57 6.57 10.92 0 332.83 139.16 31743 +1938 329 9.01 3.01 7.36 0 268.36 140.97 31631 +1938 330 11.67 5.67 10.02 0.24 315.4 102.89 31522 +1938 331 13.12 7.12 11.47 0 343.89 134.45 31417 +1938 332 15.63 9.63 13.98 0 398.43 130.04 31316 +1938 333 14.15 8.15 12.5 0.06 365.44 98.03 31218 +1938 334 14.4 8.4 12.75 0 370.85 129.38 31125 +1938 335 5.77 -0.23 4.12 0 219.3 135.62 31035 +1938 336 7.41 1.41 5.76 0 243.07 133.44 30949 +1938 337 3.43 -2.57 1.78 0.43 188.86 100.7 30867 +1938 338 1.12 -4.88 -0.53 0 162.45 134.49 30790 +1938 339 3.5 -2.5 1.85 0 189.71 132.49 30716 +1938 340 2.78 -3.22 1.13 0 181.08 132.14 30647 +1938 341 2.41 -3.59 0.76 0 176.78 131.4 30582 +1938 342 3.34 -2.66 1.69 0 187.77 130.16 30521 +1938 343 1.75 -4.25 0.1 0.16 169.32 97.6 30465 +1938 344 5.57 -0.43 3.92 0.12 216.54 95.2 30413 +1938 345 7.09 1.09 5.44 0 238.26 125.53 30366 +1938 346 3.61 -2.39 1.96 0 191.06 127.07 30323 +1938 347 0.79 -5.21 -0.86 0.59 158.96 95.88 30284 +1938 348 -1.95 -7.95 -3.6 0.21 132.33 140.75 30251 +1938 349 -0.84 -6.84 -2.49 0 142.61 172.13 30221 +1938 350 2.75 -3.25 1.1 0.12 180.73 138.4 30197 +1938 351 2.26 -3.74 0.61 0.15 175.06 94.4 30177 +1938 352 4.35 -1.65 2.7 0.69 200.36 93.52 30162 +1938 353 1.33 -4.67 -0.32 0.65 164.72 94.61 30151 +1938 354 -1.83 -7.83 -3.48 0.78 133.41 141.82 30145 +1938 355 -2.95 -8.95 -4.6 0.37 123.63 143.3 30144 +1938 356 -1.48 -7.48 -3.13 0 136.61 174.75 30147 +1938 357 -0.26 -6.26 -1.91 0 148.25 174.32 30156 +1938 358 -1.58 -7.58 -3.23 0 135.69 174.9 30169 +1938 359 -3.5 -9.5 -5.15 0 119.06 175.66 30186 +1938 360 0.65 -5.35 -1 0 157.49 174.34 30208 +1938 361 0.99 -5.01 -0.66 0 161.07 174.35 30235 +1938 362 2.27 -3.73 0.62 0 175.17 173.84 30267 +1938 363 -1.53 -7.53 -3.18 0.24 136.15 144.44 30303 +1938 364 -2.78 -8.78 -4.43 0.18 125.07 145.59 30343 +1938 365 2.69 -3.31 1.04 0.05 180.03 143.86 30388 +1939 1 4.32 -1.68 2.67 0 199.98 175.35 30438 +1939 2 3.83 -2.17 2.18 0.04 193.79 143.39 30492 +1939 3 2.99 -3.01 1.34 0 183.56 176.67 30551 +1939 4 3.91 -2.09 2.26 0 194.79 176.48 30614 +1939 5 6.47 0.47 4.82 0 229.19 174.62 30681 +1939 6 5.95 -0.05 4.3 0 221.81 174.96 30752 +1939 7 6.5 0.5 4.85 0 229.62 132.03 30828 +1939 8 7.58 1.58 5.93 1.42 245.65 99.57 30907 +1939 9 6.54 0.54 4.89 0 230.2 134.73 30991 +1939 10 6.62 0.62 4.97 0 231.36 135.96 31079 +1939 11 6.15 0.15 4.5 0 224.62 137.26 31171 +1939 12 6.07 0.07 4.42 0 223.49 138.31 31266 +1939 13 1.98 -4.02 0.33 0 171.89 142.33 31366 +1939 14 1.37 -4.63 -0.28 0 165.15 144.13 31469 +1939 15 -0.9 -6.9 -2.55 0 142.04 146.63 31575 +1939 16 5.62 -0.38 3.97 0.19 217.23 108.31 31686 +1939 17 4.16 -1.84 2.51 0 197.94 147.01 31800 +1939 18 6.19 0.19 4.54 0 225.19 147.58 31917 +1939 19 10.51 4.51 8.86 0.28 294.08 109.49 32038 +1939 20 10.59 4.59 8.94 0 295.51 147.46 32161 +1939 21 4.88 -1.12 3.23 0 207.26 153.97 32289 +1939 22 6.8 0.8 5.15 0 233.98 154.35 32419 +1939 23 7.75 1.75 6.1 0 248.26 155.37 32552 +1939 24 10.4 4.4 8.75 0 292.12 155.07 32688 +1939 25 6.97 0.97 5.32 0.1 236.48 119.92 32827 +1939 26 1.41 -4.59 -0.24 1.32 165.58 124.1 32969 +1939 27 -1.45 -7.45 -3.1 0.05 136.88 166.71 33114 +1939 28 -0.87 -6.87 -2.52 0.03 142.33 168.09 33261 +1939 29 -0.86 -6.86 -2.51 0.18 142.42 170.23 33411 +1939 30 -2.59 -8.59 -4.24 0 126.7 216.43 33564 +1939 31 -2.37 -8.37 -4.02 0 128.62 218.55 33718 +1939 32 4.74 -1.26 3.09 0 205.42 215.89 33875 +1939 33 4.65 -1.35 3 0 204.24 179.44 34035 +1939 34 8.59 2.59 6.94 0 261.51 178.39 34196 +1939 35 7.36 1.36 5.71 0 242.31 181.62 34360 +1939 36 7.83 1.83 6.18 0 249.5 183.69 34526 +1939 37 4.11 -1.89 2.46 0 197.3 189.12 34694 +1939 38 2.89 -3.11 1.24 0 182.38 192.72 34863 +1939 39 2.73 -3.27 1.08 0.1 180.49 146.58 35035 +1939 40 -1.38 -7.38 -3.03 0 137.53 200.5 35208 +1939 41 -0.38 -6.38 -2.03 0 147.07 202.62 35383 +1939 42 -1.93 -7.93 -3.58 0 132.51 206.03 35560 +1939 43 2.67 -3.33 1.02 0.23 179.79 154.52 35738 +1939 44 1.33 -4.67 -0.32 0.32 164.72 157.13 35918 +1939 45 5.59 -0.41 3.94 0 216.82 208.98 36099 +1939 46 6.5 0.5 4.85 0 229.62 210.86 36282 +1939 47 1.13 -4.87 -0.52 0 162.56 217.84 36466 +1939 48 1.88 -4.12 0.23 0.15 170.77 165.13 36652 +1939 49 5.14 -0.86 3.49 0 210.72 220.45 36838 +1939 50 3.97 -2.03 2.32 0 195.54 224.1 37026 +1939 51 9.27 3.27 7.62 0 272.67 221.95 37215 +1939 52 9.12 3.12 7.47 0 270.17 224.91 37405 +1939 53 9.73 3.73 8.08 0 280.45 227.13 37596 +1939 54 11.36 5.36 9.71 0 309.57 227.78 37788 +1939 55 9.48 3.48 7.83 0.38 276.2 174.83 37981 +1939 56 7.32 1.32 5.67 0.33 241.71 178.65 38175 +1939 57 11.05 5.05 9.4 0 303.84 236.61 38370 +1939 58 17.24 11.24 15.59 0 437.16 229.33 38565 +1939 59 13.36 7.36 11.71 0 348.81 238.76 38761 +1939 60 11.63 5.63 9.98 0 314.64 244.17 38958 +1939 61 9.63 3.63 7.98 0 278.74 249.75 39156 +1939 62 7.72 1.72 6.07 0 247.8 254.82 39355 +1939 63 4.75 -1.25 3.1 0.05 205.55 195.69 39553 +1939 64 7.68 1.68 6.03 0 247.19 260.76 39753 +1939 65 5.91 -0.09 4.26 0 221.25 265.58 39953 +1939 66 5.64 -0.36 3.99 0 217.5 268.61 40154 +1939 67 4.52 -1.48 2.87 0.09 202.55 204.48 40355 +1939 68 4 -2 2.35 0 195.92 276.03 40556 +1939 69 6.08 0.08 4.43 0.4 223.63 207.43 40758 +1939 70 6.92 0.92 5.27 0.12 235.74 208.87 40960 +1939 71 3.08 -2.92 1.43 0 184.64 285.35 41163 +1939 72 3.35 -2.65 1.7 0 187.89 287.96 41366 +1939 73 3.83 -2.17 2.18 0 193.79 290.21 41569 +1939 74 3.39 -2.61 1.74 0 188.37 293.41 41772 +1939 75 5.21 -0.79 3.56 0.02 211.65 220.75 41976 +1939 76 5 -1 3.35 0 208.85 297.22 42179 +1939 77 5.78 -0.22 4.13 0 219.44 298.99 42383 +1939 78 7.08 1.08 5.43 0 238.11 300.14 42587 +1939 79 9.71 3.71 8.06 0 280.11 299.34 42791 +1939 80 10.41 4.41 8.76 0.03 292.3 225.61 42996 +1939 81 10.4 4.4 8.75 0.01 292.12 227.54 43200 +1939 82 7.83 1.83 6.18 0.05 249.5 232.29 43404 +1939 83 5.61 -0.39 3.96 0.05 217.09 236.23 43608 +1939 84 6.77 0.77 5.12 0 233.54 316.14 43812 +1939 85 10.2 4.2 8.55 0.26 288.6 235.37 44016 +1939 86 5.3 -0.7 3.65 0.37 212.87 242.15 44220 +1939 87 1.59 -4.41 -0.06 0.75 167.55 246.93 44424 +1939 88 -0.23 -6.23 -1.88 0 148.55 333.21 44627 +1939 89 -0.51 -6.51 -2.16 0.02 145.8 281.32 44831 +1939 90 -1.46 -7.46 -3.11 0.44 136.79 284.5 45034 +1939 91 10.56 4.56 8.91 0.01 294.97 274.76 45237 +1939 92 7.78 1.78 6.13 0 248.73 333.88 45439 +1939 93 4.43 -1.57 2.78 0 201.39 340.35 45642 +1939 94 5.66 -0.34 4.01 0 217.78 341.09 45843 +1939 95 8.53 2.53 6.88 0 260.54 339.36 46045 +1939 96 10.07 4.07 8.42 0 286.32 339.08 46246 +1939 97 11.63 5.63 9.98 0 314.64 338.43 46446 +1939 98 11.19 5.19 9.54 0 306.42 341.18 46647 +1939 99 13.31 7.31 11.66 0 347.78 339.15 46846 +1939 100 14.66 8.66 13.01 0 376.54 338.21 47045 +1939 101 18.82 12.82 17.17 0 478.25 329.63 47243 +1939 102 17.57 11.57 15.92 0 445.49 334.9 47441 +1939 103 15.87 9.87 14.22 0 404.01 340.99 47638 +1939 104 17.9 11.9 16.25 0 453.94 337.57 47834 +1939 105 17.51 11.51 15.86 0 443.96 340.37 48030 +1939 106 21.94 15.94 20.29 0 569.1 328.43 48225 +1939 107 25.11 19.11 23.46 0 676 317.99 48419 +1939 108 23.81 17.81 22.16 0 630.27 324.81 48612 +1939 109 26.12 20.12 24.47 0 713.44 316.76 48804 +1939 110 26.35 20.35 24.7 0 722.21 317.01 48995 +1939 111 23.29 17.29 21.64 0 612.72 331.05 49185 +1939 112 21.64 15.64 19.99 0 559.77 338.47 49374 +1939 113 20.7 14.7 19.05 0 531.38 342.93 49561 +1939 114 19.86 13.86 18.21 0.43 507.05 260.31 49748 +1939 115 17.52 11.52 15.87 0.16 444.22 266.54 49933 +1939 116 14.22 8.22 12.57 0 366.95 364.89 50117 +1939 117 14.59 8.59 12.94 0 375 365.34 50300 +1939 118 10.96 4.96 9.31 0 302.2 374.29 50481 +1939 119 14.12 8.12 12.47 0 364.8 368.92 50661 +1939 120 13.81 7.81 12.16 0 358.21 370.8 50840 +1939 121 12.72 6.72 11.07 2.58 335.82 280.73 51016 +1939 122 10.2 4.2 8.55 0.36 288.6 285.34 51191 +1939 123 13.75 7.75 12.1 0.05 356.94 280.72 51365 +1939 124 15.25 9.25 13.6 0.24 389.73 278.88 51536 +1939 125 13.4 7.4 11.75 0 349.64 377.16 51706 +1939 126 16.73 10.73 15.08 0.57 424.56 277.48 51874 +1939 127 16.73 10.73 15.08 0.31 424.56 278.14 52039 +1939 128 18.11 12.11 16.46 0.77 459.4 275.95 52203 +1939 129 16.43 10.43 14.78 0.5 417.29 280.12 52365 +1939 130 13.78 7.78 12.13 0 357.57 380.86 52524 +1939 131 11.93 5.93 10.28 1.2 320.35 289.26 52681 +1939 132 13.35 7.35 11.7 0.27 348.61 287.6 52836 +1939 133 19.81 13.81 18.16 0 505.63 366.54 52989 +1939 134 19.17 13.17 17.52 1.59 487.78 276.97 53138 +1939 135 18.25 12.25 16.6 0.16 463.06 279.61 53286 +1939 136 20.14 14.14 18.49 0.49 515.05 275.58 53430 +1939 137 18.95 12.95 17.3 0.27 481.77 278.99 53572 +1939 138 18.56 12.56 16.91 1.34 471.27 280.35 53711 +1939 139 18.22 12.22 16.57 0.07 462.28 281.64 53848 +1939 140 18.83 12.83 17.18 0.32 478.52 280.59 53981 +1939 141 17.75 11.75 16.1 0.64 450.08 283.37 54111 +1939 142 17.16 11.16 15.51 0.98 435.17 285.02 54238 +1939 143 14.46 8.46 12.81 0.11 372.15 290.75 54362 +1939 144 17.6 11.6 15.95 0.19 446.25 284.83 54483 +1939 145 15.98 9.98 14.33 0.51 406.59 288.57 54600 +1939 146 13.77 7.77 12.12 0.44 357.36 292.99 54714 +1939 147 14.36 8.36 12.71 0.34 369.98 292.3 54824 +1939 148 13.62 7.62 11.97 0.18 354.21 293.91 54931 +1939 149 17.47 11.47 15.82 0.09 442.95 286.63 55034 +1939 150 16.98 10.98 15.33 0.03 430.7 287.94 55134 +1939 151 17.84 11.84 16.19 0.68 452.4 286.36 55229 +1939 152 17.17 11.17 15.52 0 435.41 383.88 55321 +1939 153 15.53 9.53 13.88 0.01 396.12 291.45 55409 +1939 154 14.47 8.47 12.82 0.44 372.37 293.7 55492 +1939 155 16.78 10.78 15.13 0.01 425.78 289.3 55572 +1939 156 21.26 15.26 19.61 0.14 548.14 278.79 55648 +1939 157 20.98 14.98 19.33 1.08 539.7 279.67 55719 +1939 158 21.07 15.07 19.42 0 542.4 372.74 55786 +1939 159 19.3 13.3 17.65 0.17 491.36 284.27 55849 +1939 160 19.95 13.95 18.3 0.56 509.61 282.8 55908 +1939 161 16.42 10.42 14.77 0 417.05 387.91 55962 +1939 162 21.6 15.6 19.95 0.18 558.54 278.51 56011 +1939 163 23.37 17.37 21.72 0 615.39 364.67 56056 +1939 164 21.47 15.47 19.82 0.01 554.54 279.07 56097 +1939 165 23.92 17.92 22.27 0.2 634.03 271.89 56133 +1939 166 25.98 19.98 24.33 0 708.15 353.39 56165 +1939 167 25.51 19.51 23.86 0 690.62 355.53 56192 +1939 168 23.81 17.81 22.16 0.62 630.27 272.31 56214 +1939 169 23.27 17.27 21.62 0.95 612.06 273.99 56231 +1939 170 23.68 17.68 22.03 0 625.84 363.63 56244 +1939 171 23.71 17.71 22.06 0.87 626.86 272.67 56252 +1939 172 24.69 18.69 23.04 0 660.93 359.35 56256 +1939 173 20.6 14.6 18.95 0.38 528.43 281.59 56255 +1939 174 21.71 15.71 20.06 0.42 561.93 278.52 56249 +1939 175 21.14 15.14 19.49 0.23 544.51 280.06 56238 +1939 176 23.11 17.11 21.46 0 606.75 365.86 56223 +1939 177 22.3 16.3 20.65 0.38 580.46 276.71 56203 +1939 178 21.37 15.37 19.72 0 551.49 372.47 56179 +1939 179 19.43 13.43 17.78 0 494.97 379.09 56150 +1939 180 18.56 12.56 16.91 0 471.27 381.75 56116 +1939 181 19.84 13.84 18.19 0 506.48 377.54 56078 +1939 182 26.77 20.77 25.12 0 738.45 349.01 56035 +1939 183 27.41 21.41 25.76 0 763.8 345.64 55987 +1939 184 28.5 22.5 26.85 0 808.66 339.78 55935 +1939 185 24.73 18.73 23.08 0 662.35 358.12 55879 +1939 186 24.53 18.53 22.88 0 655.26 358.75 55818 +1939 187 26.05 20.05 24.4 0.41 710.79 263.76 55753 +1939 188 26.47 20.47 24.82 0.87 726.82 262.06 55684 +1939 189 26.56 20.56 24.91 0 730.29 348.8 55611 +1939 190 25.31 19.31 23.66 0 683.28 354.31 55533 +1939 191 24.47 18.47 22.82 0.04 653.15 268.33 55451 +1939 192 22.73 16.73 21.08 0.08 594.29 273.5 55366 +1939 193 22.51 16.51 20.86 0.06 587.18 273.94 55276 +1939 194 24.67 18.67 23.02 0.32 660.22 267.1 55182 +1939 195 22.99 16.99 21.34 0 602.79 362.88 55085 +1939 196 24.51 18.51 22.86 0 654.55 356.18 54984 +1939 197 27.29 21.29 25.64 0 758.99 342.76 54879 +1939 198 25.34 19.34 23.69 0.11 684.38 263.74 54770 +1939 199 25.41 19.41 23.76 0 686.94 351 54658 +1939 200 27.48 21.48 25.83 0 766.62 340.7 54542 +1939 201 25.69 19.69 24.04 0 697.29 348.89 54423 +1939 202 23.34 17.34 21.69 0 614.39 358.46 54301 +1939 203 21.19 15.19 19.54 0 546.02 366.13 54176 +1939 204 21.79 15.79 20.14 0 564.42 363.45 54047 +1939 205 19.15 13.15 17.5 0 487.23 371.98 53915 +1939 206 17.06 11.06 15.41 0 432.68 377.65 53780 +1939 207 15.32 9.32 13.67 0 391.32 381.62 53643 +1939 208 16.15 10.15 14.5 0 410.61 378.79 53502 +1939 209 20.33 14.33 18.68 0 520.54 365.58 53359 +1939 210 24.71 18.71 23.06 0 661.64 348.21 53213 +1939 211 20.17 14.17 18.52 0 515.92 364.71 53064 +1939 212 22.09 16.09 20.44 0.16 573.81 267.87 52913 +1939 213 24.7 18.7 23.05 0 661.28 346 52760 +1939 214 25.87 19.87 24.22 0.4 704.01 255.08 52604 +1939 215 26.57 20.57 24.92 0.25 730.68 252.17 52445 +1939 216 27.77 21.77 26.12 0 778.38 329.41 52285 +1939 217 26.55 20.55 24.9 0 729.9 334.51 52122 +1939 218 26 20 24.35 0.01 708.9 252.21 51958 +1939 219 26.59 20.59 24.94 0 731.45 332.56 51791 +1939 220 18.55 12.55 16.9 0 471 362.11 51622 +1939 221 20.6 14.6 18.95 0 528.43 354.6 51451 +1939 222 21.49 15.49 19.84 0 555.15 350.5 51279 +1939 223 18.61 12.61 16.96 0.01 472.61 269.03 51105 +1939 224 21.71 15.71 20.06 0 561.93 347.55 50929 +1939 225 20.06 14.06 18.41 0 512.76 352 50751 +1939 226 18.15 12.15 16.5 1.61 460.44 267.51 50572 +1939 227 21.87 15.87 20.22 1.8 566.91 257.6 50392 +1939 228 20.75 14.75 19.1 1.38 532.86 259.59 50210 +1939 229 21.95 15.95 20.3 0.4 569.41 255.57 50026 +1939 230 20.6 14.6 18.95 0 528.43 344.12 49842 +1939 231 22.74 16.74 21.09 0 594.62 335.22 49656 +1939 232 23.87 17.87 22.22 0.06 632.32 247.21 49469 +1939 233 28.01 22.01 26.36 0.14 788.23 232.57 49280 +1939 234 26.63 20.63 24.98 0.12 733 236.45 49091 +1939 235 29.92 23.92 28.27 0 870.42 297.65 48900 +1939 236 26.23 20.23 24.58 0 717.62 314.32 48709 +1939 237 23.27 17.27 21.62 0 612.06 324.74 48516 +1939 238 19.17 13.17 17.52 0.11 487.78 252.54 48323 +1939 239 20.79 14.79 19.14 0.41 534.04 247.67 48128 +1939 240 20.57 14.57 18.92 0.86 527.55 246.89 47933 +1939 241 22.15 16.15 20.5 0.99 575.7 241.71 47737 +1939 242 20.97 14.97 19.32 0.25 539.4 243.38 47541 +1939 243 21.11 15.11 19.46 0 543.61 322.22 47343 +1939 244 18.56 12.56 16.91 0 471.27 328.05 47145 +1939 245 18.8 12.8 17.15 0 477.71 325.54 46947 +1939 246 18.32 12.32 16.67 0.01 464.91 243.68 46747 +1939 247 19.11 13.11 17.46 1.13 486.14 240.65 46547 +1939 248 21.4 15.4 19.75 0.04 552.4 234.04 46347 +1939 249 18.13 12.13 16.48 0.94 459.92 239.67 46146 +1939 250 22.2 16.2 20.55 0 577.29 305.54 45945 +1939 251 21.25 15.25 19.6 0 547.84 306.55 45743 +1939 252 19.24 13.24 17.59 0 489.71 310.37 45541 +1939 253 19.88 13.88 18.23 0 507.62 306.47 45339 +1939 254 19.05 13.05 17.4 0.26 484.5 230.01 45136 +1939 255 17.42 11.42 15.77 0 441.69 308.67 44933 +1939 256 16.43 10.43 14.78 0.64 417.29 231.57 44730 +1939 257 17.66 11.66 16.01 0 447.78 303.66 44527 +1939 258 14.68 8.68 13.03 0.03 376.98 231.03 44323 +1939 259 20.28 14.28 18.63 0 519.09 291.99 44119 +1939 260 23.51 17.51 21.86 0 620.09 279.66 43915 +1939 261 19.6 13.6 17.95 0.65 499.72 216.86 43711 +1939 262 19.81 13.81 18.16 0 505.63 286.26 43507 +1939 263 15.42 9.42 13.77 0 393.6 294.32 43303 +1939 264 15.74 9.74 14.09 0 400.98 291.06 43099 +1939 265 10.18 4.18 8.53 0.21 288.25 223.98 42894 +1939 266 17.13 11.13 15.48 0.34 434.42 212.39 42690 +1939 267 16.33 10.33 14.68 0.02 414.89 211.72 42486 +1939 268 17 11 15.35 0 431.19 278.28 42282 +1939 269 19.85 13.85 18.2 0 506.77 268.95 42078 +1939 270 17.92 11.92 16.27 0 454.46 271.11 41875 +1939 271 19 13 17.35 0.61 483.13 199.48 41671 +1939 272 20.13 14.13 18.48 0.96 514.76 195.36 41468 +1939 273 20.4 14.4 18.75 0.51 522.58 193 41265 +1939 274 12.76 6.76 11.11 0.07 336.62 203.04 41062 +1939 275 13.12 7.12 11.47 0.25 343.89 200.51 40860 +1939 276 14.33 8.33 12.68 0.43 369.33 196.9 40658 +1939 277 12.15 6.15 10.5 0.06 324.6 197.63 40456 +1939 278 10.99 4.99 9.34 0 302.75 262.35 40255 +1939 279 11.8 5.8 10.15 0.15 317.87 193.74 40054 +1939 280 17.33 11.33 15.68 0.02 439.42 184.41 39854 +1939 281 17.44 11.44 15.79 0 442.19 242.99 39654 +1939 282 18.66 12.66 17.01 0.5 473.94 178.29 39455 +1939 283 14.33 8.33 12.68 0.9 369.33 182.5 39256 +1939 284 15.73 9.73 14.08 0.3 400.75 178.41 39058 +1939 285 11.8 5.8 10.15 0 317.87 241.62 38861 +1939 286 12.75 6.75 11.1 0 336.42 237.46 38664 +1939 287 8.6 2.6 6.95 0.82 261.67 179.98 38468 +1939 288 11.36 5.36 9.71 0.22 309.57 175.28 38273 +1939 289 7.55 1.55 5.9 0 245.19 235.62 38079 +1939 290 9.69 3.69 8.04 0 279.77 230.31 37885 +1939 291 11.13 5.13 9.48 0.5 305.31 169.34 37693 +1939 292 12.59 6.59 10.94 1.13 333.23 165.84 37501 +1939 293 13.61 7.61 11.96 1.15 354.01 162.69 37311 +1939 294 11.16 5.16 9.51 1.5 305.87 163.06 37121 +1939 295 8.02 2.02 6.37 0.17 252.46 163.63 36933 +1939 296 7.67 1.67 6.02 0 247.03 215.9 36745 +1939 297 9.54 3.54 7.89 0 277.21 211.17 36560 +1939 298 8.97 2.97 7.32 0.22 267.7 156.88 36375 +1939 299 10.93 4.93 9.28 0 301.65 204.16 36191 +1939 300 13.82 7.82 12.17 0.17 358.42 148.31 36009 +1939 301 16.17 10.17 14.52 0.09 411.08 143.8 35829 +1939 302 13.39 7.39 11.74 0 349.43 193.29 35650 +1939 303 13.55 7.55 11.9 0.54 352.75 142.9 35472 +1939 304 13.12 7.12 11.47 1.88 343.89 141.51 35296 +1939 305 7.21 1.21 5.56 0.07 240.06 144.29 35122 +1939 306 1.2 -4.8 -0.45 0 163.31 194.53 34950 +1939 307 5.59 -0.41 3.94 0 216.82 188.94 34779 +1939 308 3.59 -2.41 1.94 0.16 190.82 140.83 34610 +1939 309 4.39 -1.61 2.74 0 200.88 184.86 34444 +1939 310 9.97 3.97 8.32 0 284.59 177.59 34279 +1939 311 8.83 2.83 7.18 0 265.4 176.54 34116 +1939 312 8.56 2.56 6.91 0 261.02 174.15 33956 +1939 313 8.49 2.49 6.84 0 259.9 172.1 33797 +1939 314 11.23 5.23 9.58 0 307.16 167.47 33641 +1939 315 11.42 5.42 9.77 0 310.69 164.76 33488 +1939 316 13.61 7.61 11.96 0 354.01 160.13 33337 +1939 317 13.12 7.12 11.47 0 343.89 158.57 33188 +1939 318 12.37 6.37 10.72 0 328.89 157.12 33042 +1939 319 10.47 4.47 8.82 0 293.37 157.42 32899 +1939 320 8.63 2.63 6.98 0.08 262.15 117.94 32758 +1939 321 10.06 4.06 8.41 0.01 286.15 115.41 32620 +1939 322 7.18 1.18 5.53 0.15 239.61 115.89 32486 +1939 323 8.99 2.99 7.34 2.05 268.03 113.58 32354 +1939 324 11.97 5.97 10.32 0.99 321.12 109.96 32225 +1939 325 14.29 8.29 12.64 0.13 368.46 106.8 32100 +1939 326 13.68 7.68 12.03 0.35 355.47 106.27 31977 +1939 327 9.56 3.56 7.91 0.24 277.55 107.95 31858 +1939 328 11.63 5.63 9.98 0.23 314.64 105.07 31743 +1939 329 6.86 0.86 5.21 0.36 234.86 106.97 31631 +1939 330 6.4 0.4 4.75 0.66 228.18 106.13 31522 +1939 331 6.92 0.92 5.27 0.01 235.74 104.87 31417 +1939 332 5.93 -0.07 4.28 0 221.53 138.87 31316 +1939 333 6.74 0.74 5.09 0 233.1 137.24 31218 +1939 334 7.2 1.2 5.55 0.02 239.91 101.86 31125 +1939 335 2.62 -3.38 0.97 0.09 179.21 103.09 31035 +1939 336 2.57 -3.43 0.92 0.38 178.63 102.3 30949 +1939 337 3.64 -2.36 1.99 0 191.43 134.15 30867 +1939 338 2.88 -3.12 1.23 0 182.26 133.62 30790 +1939 339 2.47 -3.53 0.82 0.2 177.47 99.78 30716 +1939 340 3.4 -2.6 1.75 0 188.49 131.81 30647 +1939 341 0.82 -5.18 -0.83 0.03 159.27 99.12 30582 +1939 342 -0.59 -6.59 -2.24 0 145.02 131.99 30521 +1939 343 4.43 -1.57 2.78 0 201.39 128.73 30465 +1939 344 5.7 -0.3 4.05 0 218.33 126.85 30413 +1939 345 3.39 -2.61 1.74 0.02 188.37 95.8 30366 +1939 346 6.2 0.2 4.55 0 225.33 125.57 30323 +1939 347 7.66 1.66 6.01 0 246.88 124.01 30284 +1939 348 6.47 0.47 4.82 0 229.19 124.45 30251 +1939 349 7.31 1.31 5.66 0.01 241.56 92.65 30221 +1939 350 1.66 -4.34 0.01 0 168.32 126.38 30197 +1939 351 2.12 -3.88 0.47 0.53 173.47 94.45 30177 +1939 352 2.93 -3.07 1.28 0.41 182.85 94.08 30162 +1939 353 -0.3 -6.3 -1.95 0 147.86 126.85 30151 +1939 354 -3.03 -9.03 -4.68 0.44 122.96 141.06 30145 +1939 355 -5.38 -11.38 -7.03 0.42 104.52 142.94 30144 +1939 356 -4.3 -10.3 -5.95 0 112.67 174.78 30147 +1939 357 -2.6 -8.6 -4.25 0 126.62 174.27 30156 +1939 358 0.26 -5.74 -1.39 0.07 153.47 141.52 30169 +1939 359 -1.32 -7.32 -2.97 0 138.09 173.94 30186 +1939 360 1.34 -4.66 -0.31 0.11 164.82 141.29 30208 +1939 361 1.38 -4.62 -0.27 0 165.26 173.08 30235 +1939 362 5.38 -0.62 3.73 0 213.95 170.65 30267 +1939 363 7.01 1.01 5.36 0 237.08 169.22 30303 +1939 364 1.3 -4.7 -0.35 0 164.39 172.56 30343 +1939 365 3.49 -2.51 1.84 0 189.59 171.52 30388 +1940 1 -5.2 -11.2 -6.85 0 105.84 175.85 30438 +1940 2 -5.2 -11.2 -6.85 0 105.84 176.52 30492 +1940 3 -5.2 -11.2 -6.85 0 105.84 177.39 30551 +1940 4 -5.2 -11.2 -6.85 0 105.84 178.23 30614 +1940 5 -5.2 -11.2 -6.85 0.03 105.84 144.96 30681 +1940 6 -5.2 -11.2 -6.85 0 105.84 179.7 30752 +1940 7 -5.2 -11.2 -6.85 0 105.84 180.41 30828 +1940 8 -5.2 -11.2 -6.85 0 105.84 181.8 30907 +1940 9 -5.2 -11.2 -6.85 0 105.84 182.96 30991 +1940 10 -5.2 -11.2 -6.85 0 105.84 184.17 31079 +1940 11 -5.2 -11.2 -6.85 0 105.84 185.05 31171 +1940 12 -5.2 -11.2 -6.85 0 105.84 185.95 31266 +1940 13 -5.2 -11.2 -6.85 0 105.84 187.47 31366 +1940 14 -5.2 -11.2 -6.85 0 105.84 188.83 31469 +1940 15 -5.2 -11.2 -6.85 0 105.84 190.16 31575 +1940 16 -5.2 -11.2 -6.85 0.37 105.84 155.06 31686 +1940 17 -5.2 -11.2 -6.85 0.62 105.84 158.06 31800 +1940 18 -5.2 -11.2 -6.85 0.01 105.84 159.38 31917 +1940 19 -5.2 -11.2 -6.85 0 105.84 199.46 32038 +1940 20 -5.2 -11.2 -6.85 0 105.84 200.91 32161 +1940 21 -5.2 -11.2 -6.85 0 105.84 202.78 32289 +1940 22 -5.2 -11.2 -6.85 0.27 105.84 165.04 32419 +1940 23 -5.2 -11.2 -6.85 1.22 105.84 169.81 32552 +1940 24 -5.2 -11.2 -6.85 0.08 105.84 171.42 32688 +1940 25 -5.2 -11.2 -6.85 0.47 105.84 174.03 32827 +1940 26 -5.2 -11.2 -6.85 0 105.84 217.38 32969 +1940 27 -5.2 -11.2 -6.85 0 105.84 219.23 33114 +1940 28 -5.2 -11.2 -6.85 0.43 105.84 179.33 33261 +1940 29 -5.2 -11.2 -6.85 0 105.84 224.7 33411 +1940 30 -5.2 -11.2 -6.85 0.43 105.84 183.64 33564 +1940 31 -5.2 -11.2 -6.85 0.83 105.84 187.59 33718 +1940 32 -3.1 -9.1 -4.75 0.55 122.37 189.9 33875 +1940 33 -4.76 -10.76 -6.41 0 109.13 238.26 34035 +1940 34 -3.32 -9.32 -4.97 0 120.54 239.67 34196 +1940 35 -5.58 -11.58 -7.23 0 103.06 242.5 34360 +1940 36 -9.31 -15.31 -10.96 0.02 79.01 197.82 34526 +1940 37 -4.2 -10.2 -5.85 0.6 113.45 199.77 34694 +1940 38 -4.78 -10.78 -6.43 0 108.98 250.95 34863 +1940 39 -3.16 -9.16 -4.81 0 121.87 252.66 35035 +1940 40 -2.39 -8.39 -4.04 0 128.44 254.69 35208 +1940 41 -1.54 -7.54 -3.19 0.75 136.05 207.89 35383 +1940 42 -2.31 -8.31 -3.96 0 129.14 261.4 35560 +1940 43 -3.68 -9.68 -5.33 0 117.59 264.52 35738 +1940 44 -3.91 -9.91 -5.56 0 115.74 266.96 35918 +1940 45 -1.37 -7.37 -3.02 0.02 137.62 214.73 36099 +1940 46 -2.48 -8.48 -4.13 0.05 127.66 217.06 36282 +1940 47 -5.36 -11.36 -7.01 0.05 104.66 220.06 36466 +1940 48 -6.61 -12.61 -8.26 0 95.86 278.46 36652 +1940 49 -4.6 -10.6 -6.25 0.14 110.35 223.91 36838 +1940 50 -1.79 -7.79 -3.44 0 133.78 281.62 37026 +1940 51 1.94 -4.06 0.29 0.21 171.44 224.66 37215 +1940 52 1.7 -4.3 0.05 0.44 168.77 226.47 37405 +1940 53 1.04 -4.96 -0.61 0.02 161.6 228.68 37596 +1940 54 3.01 -2.99 1.36 0.28 183.8 229.1 37788 +1940 55 6.34 0.34 4.69 0 227.32 287.35 37981 +1940 56 2.45 -3.55 0.8 0 177.24 292.92 38175 +1940 57 1.94 -4.06 0.29 0 171.44 295.76 38370 +1940 58 -3.19 -9.19 -4.84 0.33 121.62 239.52 38565 +1940 59 -2.03 -8.03 -3.68 0.31 131.62 241.62 38761 +1940 60 7.42 1.42 5.77 0.31 243.22 237.01 38958 +1940 61 7.9 1.9 6.25 0 250.58 300.69 39156 +1940 62 7.94 1.94 6.29 0.89 251.21 238.72 39355 +1940 63 4.19 -1.81 2.54 0 198.32 308.56 39553 +1940 64 4.41 -1.59 2.76 0 201.13 310.6 39753 +1940 65 6.5 0.5 4.85 0 229.62 310.51 39953 +1940 66 5.84 -0.16 4.19 0 220.27 313.14 40154 +1940 67 4.48 -1.52 2.83 0 202.04 316.75 40355 +1940 68 3.2 -2.8 1.55 0 186.07 320.29 40556 +1940 69 6.71 0.71 5.06 0 232.66 318.53 40758 +1940 70 3.92 -2.08 2.27 0 194.91 323.69 40960 +1940 71 6.26 0.26 4.61 0.34 226.18 252.86 41163 +1940 72 7.87 1.87 6.22 0.28 250.12 252.59 41366 +1940 73 6.99 0.99 5.34 0 236.78 326.22 41569 +1940 74 5.04 -0.96 3.39 0.08 209.38 257.54 41772 +1940 75 5.39 -0.61 3.74 0 214.09 332.15 41976 +1940 76 6.28 0.28 4.63 0.18 226.47 259.08 42179 +1940 77 9.84 3.84 8.19 0 282.34 329.89 42383 +1940 78 8.29 2.29 6.64 0 256.71 333.75 42587 +1940 79 7.1 1.1 5.45 0 238.41 337.17 42791 +1940 80 9.67 3.67 8.02 0 279.43 335.17 42996 +1940 81 7.86 1.86 6.21 0 249.96 339.37 43200 +1940 82 4.97 -1.03 3.32 0.06 208.45 266.63 43404 +1940 83 -0.16 -6.16 -1.81 0 149.25 352.12 43608 +1940 84 1.25 -4.75 -0.4 0 163.85 353.28 43812 +1940 85 4.35 -1.65 2.7 0 200.36 352.27 44016 +1940 86 3.41 -2.59 1.76 0 188.62 355.25 44220 +1940 87 5.2 -0.8 3.55 0.89 211.52 273.88 44424 +1940 88 10.6 4.6 8.95 0.01 295.69 240.34 44627 +1940 89 5.77 -0.23 4.12 0.09 219.3 247.17 44831 +1940 90 7.22 1.22 5.57 0 240.2 330.11 45034 +1940 91 13.49 7.49 11.84 0 351.51 322.09 45237 +1940 92 16.29 10.29 14.64 0 413.94 318.24 45439 +1940 93 17.09 11.09 15.44 0.01 433.42 238.85 45642 +1940 94 14.64 8.64 12.99 0.15 376.1 244.67 45843 +1940 95 15.89 9.89 14.24 0.48 404.48 244.14 46045 +1940 96 12.16 6.16 10.51 0 324.79 335.41 46246 +1940 97 11.48 5.48 9.83 0.01 311.82 254.03 46446 +1940 98 11.24 5.24 9.59 0 307.35 341.09 46647 +1940 99 12.76 6.76 11.11 0.59 336.62 255.19 46846 +1940 100 15.53 9.53 13.88 0 396.12 336.23 47045 +1940 101 14.39 8.39 12.74 0 370.63 340.71 47243 +1940 102 14.67 8.67 13.02 0 376.76 341.97 47441 +1940 103 14.15 8.15 12.5 0.18 365.44 258.7 47638 +1940 104 10.21 4.21 8.56 0 288.77 354.39 47834 +1940 105 12.02 6.02 10.37 0 322.08 352.9 48030 +1940 106 12.73 6.73 11.08 0 336.02 353.14 48225 +1940 107 9.96 3.96 8.31 0.66 284.41 269.98 48419 +1940 108 9.15 3.15 7.5 0 270.67 363.09 48612 +1940 109 8.46 2.46 6.81 0 259.42 365.83 48804 +1940 110 8.44 2.44 6.79 0.16 259.1 275.47 48995 +1940 111 5.59 -0.41 3.94 0 216.82 372.98 49185 +1940 112 6.22 0.22 4.57 0 225.61 373.69 49374 +1940 113 8.11 2.11 6.46 0 253.87 372.3 49561 +1940 114 8.99 2.99 7.34 0 268.03 372.41 49748 +1940 115 13.08 7.08 11.43 0 343.08 366.18 49933 +1940 116 16.8 10.8 15.15 0 426.27 358.53 50117 +1940 117 16.34 10.34 14.69 0.02 415.13 270.77 50300 +1940 118 17.08 11.08 15.43 0.33 433.18 270.27 50481 +1940 119 18.41 12.41 16.76 0 467.28 357.76 50661 +1940 120 16.42 10.42 14.77 0 417.05 364.45 50840 +1940 121 14.59 8.59 12.94 0.12 375 277.6 51016 +1940 122 16.22 10.22 14.57 0 412.27 367.27 51191 +1940 123 15.82 9.82 14.17 0.11 402.84 276.99 51365 +1940 124 14.6 8.6 12.95 0.04 375.22 280.06 51536 +1940 125 17.77 11.77 16.12 0.01 450.6 274.56 51706 +1940 126 15.95 9.95 14.3 1.21 405.89 279.03 51874 +1940 127 20.78 14.78 19.13 0.75 533.75 268.85 52039 +1940 128 21.36 15.36 19.71 0.58 551.18 268.05 52203 +1940 129 16.66 10.66 15.01 0.2 422.85 279.66 52365 +1940 130 17.84 11.84 16.19 0.24 452.4 277.76 52524 +1940 131 15.44 9.44 13.79 0.07 394.06 283.25 52681 +1940 132 19.23 13.23 17.58 0 489.43 367.72 52836 +1940 133 20.03 14.03 18.38 0 511.9 365.81 52989 +1940 134 16.48 10.48 14.83 0.35 418.5 282.88 53138 +1940 135 16.69 10.69 15.04 0.25 423.59 282.97 53286 +1940 136 11.81 5.81 10.16 0 318.06 389.57 53430 +1940 137 12.91 6.91 11.26 0.69 339.63 290.96 53572 +1940 138 17.74 11.74 16.09 1.33 449.83 282.19 53711 +1940 139 12.53 6.53 10.88 1.7 332.04 292.57 53848 +1940 140 15.19 9.19 13.54 1.81 388.37 288.28 53981 +1940 141 12.31 6.31 10.66 1.2 327.71 293.63 54111 +1940 142 13.27 7.27 11.62 0.31 346.96 292.43 54238 +1940 143 12.69 6.69 11.04 0 335.22 391.74 54362 +1940 144 10.93 4.93 9.28 0.36 301.65 296.9 54483 +1940 145 11.28 5.28 9.63 0.37 308.09 296.75 54600 +1940 146 13.61 7.61 11.96 0 354.01 391.03 54714 +1940 147 14.97 8.97 13.32 0.78 383.42 291.18 54824 +1940 148 14.14 8.14 12.49 0.16 365.23 292.99 54931 +1940 149 18.73 12.73 17.08 0.04 475.82 283.78 55034 +1940 150 18.48 12.48 16.83 1.94 469.14 284.61 55134 +1940 151 16.75 10.75 15.1 3.43 425.05 288.72 55229 +1940 152 20.72 14.72 19.07 1.14 531.97 279.44 55321 +1940 153 23.23 17.23 21.58 0.52 610.73 272.51 55409 +1940 154 24.16 18.16 22.51 0.73 642.31 269.85 55492 +1940 155 25.28 19.28 23.63 0.07 682.18 266.29 55572 +1940 156 19.12 13.12 17.47 0.01 486.41 284.27 55648 +1940 157 18.9 12.9 17.25 0.21 480.41 284.93 55719 +1940 158 19.85 13.85 18.2 0.14 506.77 282.73 55786 +1940 159 20.48 14.48 18.83 0.22 524.91 281.3 55849 +1940 160 25.03 19.03 23.38 0.08 673.11 267.92 55908 +1940 161 26.31 20.31 24.66 0 720.68 351.35 55962 +1940 162 22.72 16.72 21.07 0 593.97 367.07 56011 +1940 163 22.24 16.24 20.59 0.01 578.56 276.86 56056 +1940 164 19.24 13.24 17.59 2.02 489.71 284.85 56097 +1940 165 17.82 11.82 16.17 1.33 451.88 288.24 56133 +1940 166 19.67 13.67 18.02 0 501.68 378.56 56165 +1940 167 17.63 11.63 15.98 0.53 447.01 288.68 56192 +1940 168 15.3 9.3 13.65 0.6 390.86 293.57 56214 +1940 169 14.58 8.58 12.93 0.3 374.78 294.94 56231 +1940 170 18.24 12.24 16.59 0 462.8 383.16 56244 +1940 171 21.37 15.37 19.72 0 551.49 372.72 56252 +1940 172 22.71 16.71 21.06 0 593.64 367.61 56256 +1940 173 23.08 17.08 21.43 0.06 605.76 274.59 56255 +1940 174 23.43 17.43 21.78 0 617.4 364.62 56249 +1940 175 26.51 20.51 24.86 0 728.36 350.81 56238 +1940 176 21.12 15.12 19.47 0.28 543.91 280.09 56223 +1940 177 20.92 14.92 19.27 0.33 537.91 280.55 56203 +1940 178 18.41 12.41 16.76 0.25 467.28 286.83 56179 +1940 179 17.22 11.22 15.57 0.89 436.66 289.42 56150 +1940 180 16.95 10.95 15.3 0 429.96 386.54 56116 +1940 181 17.92 11.92 16.27 0.79 454.46 287.73 56078 +1940 182 14.11 8.11 12.46 0.33 364.59 295.3 56035 +1940 183 14.63 8.63 12.98 0 375.88 392.29 55987 +1940 184 18.79 12.79 17.14 0 477.44 380.47 55935 +1940 185 23.52 17.52 21.87 3.52 620.43 272.46 55879 +1940 186 30.38 24.38 28.73 1.27 891.26 246.61 55818 +1940 187 25.57 19.57 23.92 0.21 692.84 265.44 55753 +1940 188 24.77 18.77 23.12 0 663.78 357.26 55684 +1940 189 21.27 15.27 19.62 0 548.44 371.1 55611 +1940 190 23.67 17.67 22.02 0 625.5 361.42 55533 +1940 191 25.6 19.6 23.95 0.01 693.95 264.55 55451 +1940 192 23.64 17.64 21.99 1.67 624.48 270.75 55366 +1940 193 20.64 14.64 18.99 0 529.61 372.14 55276 +1940 194 22.12 16.12 20.47 0.58 574.76 274.9 55182 +1940 195 23.78 17.78 22.13 0 629.24 359.67 55085 +1940 196 23.61 17.61 21.96 0 623.47 359.97 54984 +1940 197 23.49 17.49 21.84 0.57 619.42 270.01 54879 +1940 198 17.25 11.25 15.6 0.16 437.41 285.81 54770 +1940 199 19.33 13.33 17.68 0.61 492.19 280.79 54658 +1940 200 19.1 13.1 17.45 0.48 485.86 281.04 54542 +1940 201 17.7 11.7 16.05 0.38 448.8 283.89 54423 +1940 202 18.76 12.76 17.11 0 476.63 374.75 54301 +1940 203 18.99 12.99 17.34 0 482.86 373.52 54176 +1940 204 24.77 18.77 23.12 0 663.78 351.49 54047 +1940 205 23.66 17.66 22.01 0.08 625.16 266.75 53915 +1940 206 21.79 15.79 20.14 0.45 564.42 271.79 53780 +1940 207 17.44 11.44 15.79 0 442.19 375.9 53643 +1940 208 23.62 17.62 21.97 0 623.81 354 53502 +1940 209 23.97 17.97 22.32 0.32 635.75 263.95 53359 +1940 210 21.27 15.27 19.62 0.09 548.44 271.27 53213 +1940 211 22.88 16.88 21.23 0.02 599.18 266.21 53064 +1940 212 23.41 17.41 21.76 0 616.73 352.08 52913 +1940 213 22.59 16.59 20.94 0.23 589.76 265.9 52760 +1940 214 18.72 12.72 17.07 0.6 475.56 275.28 52604 +1940 215 21.54 15.54 19.89 0.7 556.69 267.76 52445 +1940 216 17.42 11.42 15.77 0.54 441.69 276.86 52285 +1940 217 20.8 14.8 19.15 2.13 534.34 268.28 52122 +1940 218 16.86 10.86 15.21 0.34 427.74 276.71 51958 +1940 219 14.9 8.9 13.25 2.46 381.86 279.69 51791 +1940 220 18.42 12.42 16.77 1.34 467.55 271.87 51622 +1940 221 19.3 13.3 17.65 1.57 491.36 269.11 51451 +1940 222 21.02 15.02 19.37 0.28 540.9 264.1 51279 +1940 223 21.25 15.25 19.6 1.19 547.84 262.66 51105 +1940 224 23.71 17.71 22.06 0 626.86 340.04 50929 +1940 225 19.86 13.86 18.21 0 507.05 352.64 50751 +1940 226 20.39 14.39 18.74 0 522.29 349.79 50572 +1940 227 18.03 12.03 16.38 0.01 457.31 266.8 50392 +1940 228 15.82 9.82 14.17 0.59 402.84 270.31 50210 +1940 229 15.64 9.64 13.99 0.29 398.66 269.69 50026 +1940 230 17.53 11.53 15.88 0.06 444.47 265.02 49842 +1940 231 21.95 15.95 20.3 0.03 569.41 253.55 49656 +1940 232 18.94 12.94 17.29 0.29 481.5 259.87 49469 +1940 233 19.07 13.07 17.42 0.19 485.04 258.51 49280 +1940 234 20.98 14.98 19.33 0.08 539.7 252.94 49091 +1940 235 20.11 14.11 18.46 0.91 514.19 253.94 48900 +1940 236 20.76 14.76 19.11 2.17 533.15 251.32 48709 +1940 237 22.21 16.21 20.56 0.03 577.6 246.43 48516 +1940 238 18.94 12.94 17.29 0.45 481.5 253.05 48323 +1940 239 20.26 14.26 18.61 0.78 518.51 248.93 48128 +1940 240 20.18 14.18 18.53 0.43 516.2 247.81 47933 +1940 241 19.93 13.93 18.28 0 509.04 329.47 47737 +1940 242 20.37 14.37 18.72 0.07 521.7 244.8 47541 +1940 243 17.79 11.79 16.14 0.05 451.11 248.98 47343 +1940 244 12.72 6.72 11.07 1.72 335.82 256.34 47145 +1940 245 10.62 4.62 8.97 0.37 296.05 257.81 46947 +1940 246 9.89 3.89 8.24 0 283.2 342.94 46747 +1940 247 9.57 3.57 7.92 0 277.72 341.52 46547 +1940 248 12.2 6.2 10.55 0 325.57 334.95 46347 +1940 249 16.45 10.45 14.8 0 417.77 323.81 46146 +1940 250 17.15 11.15 15.5 0.04 434.92 240.1 45945 +1940 251 18.16 12.16 16.51 0 460.7 315.43 45743 +1940 252 21.41 15.41 19.76 0 552.71 303.94 45541 +1940 253 19.19 13.19 17.54 1.65 488.33 231.31 45339 +1940 254 15.44 9.44 13.79 0.32 394.06 236.67 45136 +1940 255 16.01 10.01 14.36 0.01 407.3 234 44933 +1940 256 21.22 15.22 19.57 0 546.93 295.99 44730 +1940 257 20.9 14.9 19.25 0.26 537.31 221.14 44527 +1940 258 15.31 9.31 13.66 0.31 391.09 230.04 44323 +1940 259 17.7 11.7 16.05 0.24 448.8 224.11 44119 +1940 260 16.99 10.99 15.34 0.24 430.95 223.6 43915 +1940 261 22.36 16.36 20.71 2.19 582.38 210.81 43711 +1940 262 19.94 13.94 18.29 0.2 509.33 214.43 43507 +1940 263 22.48 16.48 20.83 0.44 586.22 207.05 43303 +1940 264 20.28 14.28 18.63 0.7 519.09 210.04 43099 +1940 265 22.14 16.14 20.49 0.42 575.39 204.29 42894 +1940 266 20.04 14.04 18.39 0.31 512.18 207 42690 +1940 267 22.06 16.06 20.41 1.17 572.86 200.76 42486 +1940 268 23.43 17.43 21.78 0.68 617.4 195.75 42282 +1940 269 22 16 20.35 0 570.98 263 42078 +1940 270 21.13 15.13 19.48 0.28 544.21 197.22 41875 +1940 271 21.09 15.09 19.44 0 543 260.55 41671 +1940 272 22.23 16.23 20.58 0 578.24 254.71 41468 +1940 273 19.53 13.53 17.88 0.03 497.76 194.66 41265 +1940 274 12.24 6.24 10.59 0.22 326.35 203.68 41062 +1940 275 10.43 4.43 8.78 0 292.66 271.5 40860 +1940 276 8.87 2.87 7.22 0 266.06 270.85 40658 +1940 277 10.99 4.99 9.34 0.18 302.75 198.94 40456 +1940 278 13.18 7.18 11.53 0 345.12 258.98 40255 +1940 279 16.21 10.21 14.56 0 412.03 250.74 40054 +1940 280 13.23 7.23 11.58 0.18 346.14 190.07 39854 +1940 281 15.84 9.84 14.19 0 403.31 246.15 39654 +1940 282 15.03 9.03 13.38 0.41 384.76 183.69 39455 +1940 283 14.4 8.4 12.75 0.27 370.85 182.41 39256 +1940 284 12.31 6.31 10.66 1.74 327.71 182.64 39058 +1940 285 10.16 4.16 8.51 0 287.9 243.85 38861 +1940 286 13.53 7.53 11.88 0 352.34 236.26 38664 +1940 287 15.55 9.55 13.9 0.16 396.58 172.49 38468 +1940 288 9.42 3.42 7.77 0.88 275.19 177.14 38273 +1940 289 8.72 2.72 7.07 0.24 263.61 175.75 38079 +1940 290 7.3 1.3 5.65 0.18 241.41 174.73 37885 +1940 291 9.11 3.11 7.46 0.74 270.01 171.19 37693 +1940 292 6.86 0.86 5.21 0.63 234.86 170.94 37501 +1940 293 8.42 2.42 6.77 1.61 258.78 167.65 37311 +1940 294 8.85 2.85 7.2 0.01 265.73 165.11 37121 +1940 295 10.13 4.13 8.48 0.01 287.37 161.88 36933 +1940 296 13.93 7.93 12.28 0.13 360.75 156.17 36745 +1940 297 14.27 8.27 12.62 0.03 368.03 153.78 36560 +1940 298 14.09 8.09 12.44 0.42 364.16 152.05 36375 +1940 299 13.17 7.17 11.52 0 344.91 201.29 36191 +1940 300 17.16 11.16 15.51 0 435.17 192.53 36009 +1940 301 16.67 10.67 15.02 0 423.1 190.92 35829 +1940 302 18.01 12.01 16.36 0 456.79 186.1 35650 +1940 303 20.1 14.1 18.45 0 513.9 179.71 35472 +1940 304 17.95 11.95 16.3 3.74 455.24 136.03 35296 +1940 305 13.81 7.81 12.16 0.56 358.21 138.79 35122 +1940 306 16.86 10.86 15.21 0 427.74 178.38 34950 +1940 307 12.6 6.6 10.95 0 333.43 181.94 34779 +1940 308 14.54 8.54 12.89 0.1 373.9 132.64 34610 +1940 309 12.12 6.12 10.47 0 324.02 177.66 34444 +1940 310 12.21 6.21 10.56 0 325.76 175.14 34279 +1940 311 10.36 4.36 8.71 0 291.42 175.03 34116 +1940 312 10.92 4.92 9.27 0.2 301.47 128.86 33956 +1940 313 12.33 6.33 10.68 0.01 328.11 126.13 33797 +1940 314 10.5 4.5 8.85 1.21 293.9 126.17 33641 +1940 315 8.19 2.19 6.54 0.35 255.13 125.91 33488 +1940 316 10.6 4.6 8.95 0.78 295.69 122.59 33337 +1940 317 10.53 4.53 8.88 0.43 294.44 121.01 33188 +1940 318 13.15 7.15 11.5 0 344.5 156.24 33042 +1940 319 11.18 5.18 9.53 0 306.24 156.72 32899 +1940 320 13.18 7.18 11.53 0 345.12 152.74 32758 +1940 321 11.75 5.75 10.1 0 316.91 152.22 32620 +1940 322 9.62 3.62 7.97 0 278.57 152.48 32486 +1940 323 9.25 3.25 7.6 0.15 272.34 113.41 32354 +1940 324 8.01 2.01 6.36 0 252.3 150.21 32225 +1940 325 6.36 0.36 4.71 0 227.61 149.74 32100 +1940 326 5.14 -0.86 3.49 0 210.72 149.11 31977 +1940 327 6.08 0.08 4.43 0 223.63 146.63 31858 +1940 328 7.29 1.29 5.64 0 241.26 143.8 31743 +1940 329 7.93 1.93 6.28 0 251.05 141.83 31631 +1940 330 8.4 2.4 6.75 0.01 258.46 105.02 31522 +1940 331 11.29 5.29 9.64 0 308.27 136.26 31417 +1940 332 7.22 1.22 5.57 0.13 240.2 103.48 31316 +1940 333 5.6 -0.4 3.95 0 216.95 138 31218 +1940 334 4.92 -1.08 3.27 0 207.79 137.32 31125 +1940 335 -3.9 -9.9 -5.55 0 115.82 140.21 31035 +1940 336 -5.88 -11.88 -7.53 0 100.92 139.73 30949 +1940 337 -3.13 -9.13 -4.78 0 122.12 137.17 30867 +1940 338 -3.6 -9.6 -5.25 0 118.24 136.37 30790 +1940 339 -2.67 -8.67 -4.32 0.18 126.02 144.97 30716 +1940 340 -0.08 -6.08 -1.73 0.53 150.04 145.4 30647 +1940 341 1.03 -4.97 -0.62 0 161.49 177.32 30582 +1940 342 -1.6 -7.6 -3.25 0.06 135.5 144.83 30521 +1940 343 0.39 -5.61 -1.26 0 154.8 176.31 30465 +1940 344 -2.35 -8.35 -4 0 128.79 176.34 30413 +1940 345 -1.73 -7.73 -3.38 0 134.32 175.74 30366 +1940 346 -4.06 -10.06 -5.71 0 114.55 176.05 30323 +1940 347 -5.41 -11.41 -7.06 0 104.3 175.91 30284 +1940 348 -4.19 -10.19 -5.84 0 113.53 175.24 30251 +1940 349 -2.76 -8.76 -4.41 0.14 125.24 142.75 30221 +1940 350 -0.07 -6.07 -1.72 0.03 150.14 141.86 30197 +1940 351 4.67 -1.33 3.02 0 204.5 170.53 30177 +1940 352 2.61 -3.39 0.96 0.03 179.09 139.8 30162 +1940 353 0.53 -5.47 -1.12 0 156.25 172.04 30151 +1940 354 -1.5 -7.5 -3.15 0 136.42 172.83 30145 +1940 355 2.31 -3.69 0.66 0.2 175.63 139.48 30144 +1940 356 -0.19 -6.19 -1.84 0.15 148.95 140.81 30147 +1940 357 -3 -9 -4.65 0.14 123.21 142.07 30156 +1940 358 -5.52 -11.52 -7.17 0 103.5 174.9 30169 +1940 359 -3.13 -9.13 -4.78 0 122.12 174.25 30186 +1940 360 -2.03 -8.03 -3.68 0 131.62 174.21 30208 +1940 361 -1.74 -7.74 -3.39 0 134.23 174.4 30235 +1940 362 3.92 -2.08 2.27 0 194.91 171.71 30267 +1940 363 1.91 -4.09 0.26 0 171.1 173.01 30303 +1940 364 1.61 -4.39 -0.04 0 167.77 173.28 30343 +1940 365 0.21 -5.79 -1.44 0 152.96 174.38 30388 +1941 1 -0.11 -6.11 -1.76 0.28 149.74 143.57 30438 +1941 2 1.77 -4.23 0.12 0 169.54 175.81 30492 +1941 3 1.24 -4.76 -0.41 0 163.74 176.75 30551 +1941 4 0.18 -5.82 -1.47 0.8 152.66 144.75 30614 +1941 5 -1.04 -7.04 -2.69 0.04 140.71 145.65 30681 +1941 6 -2.38 -8.38 -4.03 0 128.53 180.53 30752 +1941 7 0.33 -5.67 -1.32 0 154.19 180.09 30828 +1941 8 -2.44 -8.44 -4.09 0.08 128.01 148.34 30907 +1941 9 -4.43 -10.43 -6.08 0.01 111.66 149.72 30991 +1941 10 -9.33 -15.33 -10.98 0.63 78.9 153.53 31079 +1941 11 -6.4 -12.4 -8.05 0.2 97.29 154.21 31171 +1941 12 -3.45 -9.45 -5.1 0.5 119.47 155.68 31266 +1941 13 -2.95 -8.95 -4.6 0.28 123.63 157.48 31366 +1941 14 -1.33 -7.33 -2.98 0.4 137.99 159.19 31469 +1941 15 -0.24 -6.24 -1.89 0.16 148.45 160.24 31575 +1941 16 -1.13 -7.13 -2.78 0 139.86 198.34 31686 +1941 17 4.87 -1.13 3.22 1.1 207.13 159.44 31800 +1941 18 2.44 -3.56 0.79 0 177.12 198.93 31917 +1941 19 4.41 -1.59 2.76 0 201.13 198.97 32038 +1941 20 3.48 -2.52 1.83 0.13 189.47 162.29 32161 +1941 21 6.2 0.2 4.55 0 225.33 199.76 32289 +1941 22 4.82 -1.18 3.17 0 206.47 201.66 32419 +1941 23 5.82 -0.18 4.17 0 219.99 201.83 32552 +1941 24 3.12 -2.88 1.47 0 185.11 205.09 32688 +1941 25 1.34 -4.66 -0.31 0 164.82 207.65 32827 +1941 26 -2.43 -8.43 -4.08 0 128.09 211.2 32969 +1941 27 -5.22 -11.22 -6.87 0 105.69 214.14 33114 +1941 28 -3.26 -9.26 -4.91 0 121.03 215.45 33261 +1941 29 -2.53 -8.53 -4.18 0 127.22 217.37 33411 +1941 30 -3.04 -9.04 -4.69 0.08 122.87 175.75 33564 +1941 31 -5.58 -11.58 -7.23 0 103.06 223.08 33718 +1941 32 0.2 -5.8 -1.45 0 152.86 222.48 33875 +1941 33 4.09 -1.91 2.44 0 197.05 222.07 34035 +1941 34 4.81 -1.19 3.16 0 206.34 223 34196 +1941 35 4.55 -1.45 2.9 0 202.94 224.6 34360 +1941 36 5.38 -0.62 3.73 1.05 213.95 179.22 34526 +1941 37 5.67 -0.33 4.02 0.05 217.92 180.01 34694 +1941 38 9.01 3.01 7.36 0.28 268.36 140.76 34863 +1941 39 8.4 2.4 6.75 0.01 258.46 143.14 35035 +1941 40 7.78 1.78 6.13 1 248.73 145.52 35208 +1941 41 6.96 0.96 5.31 1.01 236.34 148.04 35383 +1941 42 5.22 -0.78 3.57 0.02 211.79 151.06 35560 +1941 43 6.57 0.57 4.92 0 230.63 202.96 35738 +1941 44 6.93 0.93 5.28 0 235.89 205.18 35918 +1941 45 8.32 2.32 6.67 0 257.19 206.44 36099 +1941 46 7.08 1.08 5.43 0.36 238.11 157.74 36282 +1941 47 2.37 -3.63 0.72 0.24 176.32 162.76 36466 +1941 48 2.57 -3.43 0.92 0 178.63 219.69 36652 +1941 49 3.36 -2.64 1.71 0.01 188.01 166.42 36838 +1941 50 5.54 -0.46 3.89 0 216.13 222.77 37026 +1941 51 4.78 -1.22 3.13 0 205.94 226.4 37215 +1941 52 -0.98 -6.98 -2.63 1.12 141.28 213.19 37405 +1941 53 0.1 -5.9 -1.55 0.48 151.85 214.74 37596 +1941 54 0.34 -5.66 -1.31 0 154.29 276.07 37788 +1941 55 2.9 -3.1 1.25 0 182.5 276.76 37981 +1941 56 3.45 -2.55 1.8 0 189.1 278.48 38175 +1941 57 3.1 -2.9 1.45 0 184.88 281.16 38370 +1941 58 4.87 -1.13 3.22 0.43 207.13 220.28 38565 +1941 59 6.02 0.02 4.37 0.2 222.79 220.69 38761 +1941 60 6.8 0.8 5.15 0.42 233.98 187.59 38958 +1941 61 7.49 1.49 5.84 0.32 244.28 189.22 39156 +1941 62 2.81 -3.19 1.16 0 181.43 259.6 39355 +1941 63 5.51 -0.49 3.86 0 215.72 260.18 39553 +1941 64 9.32 3.32 7.67 0.13 273.51 194.08 39753 +1941 65 11.21 5.21 9.56 1.81 306.79 194.29 39953 +1941 66 11.27 5.27 9.62 0.41 307.9 196.24 40154 +1941 67 12.82 6.82 11.17 0 337.82 262.12 40355 +1941 68 9.57 3.57 7.92 0.41 277.72 202.31 40556 +1941 69 6.14 0.14 4.49 0.74 224.48 207.38 40758 +1941 70 10.71 4.71 9.06 0.05 297.67 205.18 40960 +1941 71 9.3 3.3 7.65 0.45 273.17 208.83 41163 +1941 72 7.58 1.58 5.93 0.21 245.65 212.59 41366 +1941 73 7.71 1.71 6.06 0.27 247.65 214.47 41569 +1941 74 10.73 4.73 9.08 0 298.03 284.57 41772 +1941 75 5.09 -0.91 3.44 0 210.05 294.46 41976 +1941 76 1.4 -4.6 -0.25 0 165.48 300.62 42179 +1941 77 4.62 -1.38 2.97 0.26 203.85 225.19 42383 +1941 78 4.64 -1.36 2.99 0 204.11 302.92 42587 +1941 79 4.41 -1.59 2.76 0 201.13 305.92 42791 +1941 80 6.31 0.31 4.66 0 226.89 306.37 42996 +1941 81 4.11 -1.89 2.46 0.1 197.3 233.56 43200 +1941 82 5.04 -0.96 3.39 0.71 209.38 234.83 43404 +1941 83 7.59 1.59 5.94 0 245.81 312.54 43608 +1941 84 11.72 5.72 10.07 0.02 316.34 231.65 43812 +1941 85 11.63 5.63 9.98 0 314.64 311.49 44016 +1941 86 12.39 6.39 10.74 0 329.28 312.54 44220 +1941 87 13.54 7.54 11.89 0 352.55 312.89 44424 +1941 88 13.57 7.57 11.92 0.01 353.17 236.35 44627 +1941 89 9.91 3.91 8.26 0.02 283.55 242.87 44831 +1941 90 6.61 0.61 4.96 0.78 231.21 248.18 45034 +1941 91 7.07 1.07 5.42 1.75 237.97 249.44 45237 +1941 92 8.03 2.03 6.38 0.18 252.61 250.15 45439 +1941 93 8.25 2.25 6.6 0.57 256.08 251.58 45642 +1941 94 4.87 -1.13 3.22 0.05 207.13 256.53 45843 +1941 95 7.36 1.36 5.71 0.28 242.31 255.78 46045 +1941 96 5.99 -0.01 4.34 0 222.37 345 46246 +1941 97 7.96 1.96 6.31 0.05 251.52 258.3 46446 +1941 98 8.29 2.29 6.64 0.6 256.71 259.43 46647 +1941 99 9.3 3.3 7.65 0 273.17 346.38 46846 +1941 100 8.81 2.81 7.16 0 265.08 349.11 47045 +1941 101 14.1 8.1 12.45 0 364.37 341.34 47243 +1941 102 12.41 6.41 10.76 0 329.68 346.69 47441 +1941 103 10.92 4.92 9.27 0 301.47 351.31 47638 +1941 104 11.89 5.89 10.24 0 319.59 351.35 47834 +1941 105 14.43 8.43 12.78 0 371.5 347.9 48030 +1941 106 12.36 6.36 10.71 1.44 328.69 265.41 48225 +1941 107 11.73 5.73 10.08 0 316.53 356.78 48419 +1941 108 8.86 2.86 7.21 0 265.89 363.56 48612 +1941 109 7.74 1.74 6.09 0 248.11 366.93 48804 +1941 110 11.59 5.59 9.94 0 313.89 361.83 48995 +1941 111 15.19 9.19 13.54 0 388.37 355.67 49185 +1941 112 14.07 8.07 12.42 0.31 363.73 269.82 49374 +1941 113 15.13 9.13 13.48 0 387.01 358.65 49561 +1941 114 14.08 8.08 12.43 0 363.94 362.56 49748 +1941 115 15.77 9.77 14.12 0.62 401.68 269.98 49933 +1941 116 17.9 11.9 16.25 0 453.94 355.51 50117 +1941 117 15.81 9.81 14.16 0.25 402.61 271.78 50300 +1941 118 15.16 9.16 13.51 0.05 387.69 273.97 50481 +1941 119 14.75 8.75 13.1 0 378.52 367.46 50661 +1941 120 17.77 11.77 16.12 0.67 450.6 270.57 50840 +1941 121 18.89 12.89 17.24 0.33 480.14 268.93 51016 +1941 122 18.04 12.04 16.39 0.31 457.57 271.7 51191 +1941 123 18.39 12.39 16.74 1.49 466.76 271.69 51365 +1941 124 15.02 9.02 13.37 0.23 384.54 279.3 51536 +1941 125 12.37 6.37 10.72 0.23 328.89 284.53 51706 +1941 126 14.06 8.06 12.41 0.63 363.52 282.5 51874 +1941 127 11.47 5.47 9.82 0 311.63 383.11 52039 +1941 128 11.87 5.87 10.22 0 319.2 383.32 52203 +1941 129 11.09 5.09 9.44 0 304.58 385.74 52365 +1941 130 12.55 6.55 10.9 0 332.44 383.58 52524 +1941 131 10.39 4.39 8.74 0.02 291.95 291.52 52681 +1941 132 9.88 3.88 8.23 0 283.03 390.47 52836 +1941 133 11.92 5.92 10.27 0 320.16 387.26 52989 +1941 134 13.3 7.3 11.65 0.63 347.58 288.76 53138 +1941 135 17.45 11.45 15.8 0.31 442.44 281.37 53286 +1941 136 16.94 10.94 15.29 0.21 429.71 282.93 53430 +1941 137 17.87 11.87 16.22 0.46 453.17 281.46 53572 +1941 138 18.09 12.09 16.44 0.18 458.88 281.42 53711 +1941 139 16.19 10.19 14.54 0.02 411.56 285.97 53848 +1941 140 16.67 10.67 15.02 0.17 423.1 285.35 53981 +1941 141 16.77 10.77 15.12 0 425.54 380.63 54111 +1941 142 17 11 15.35 0 431.19 380.48 54238 +1941 143 15.9 9.9 14.25 0 404.71 384.02 54362 +1941 144 18.73 12.73 17.08 0 475.82 376.36 54483 +1941 145 21.15 15.15 19.5 0.14 544.81 276.55 54600 +1941 146 14.53 8.53 12.88 0.65 373.68 291.63 54714 +1941 147 15.12 9.12 13.47 0.23 386.79 290.89 54824 +1941 148 12.52 6.52 10.87 0.15 331.84 295.76 54931 +1941 149 11.51 5.51 9.86 0.61 312.38 297.59 55034 +1941 150 8.63 2.63 6.98 0.18 262.15 301.88 55134 +1941 151 12.37 6.37 10.72 0.38 328.89 296.8 55229 +1941 152 21.92 15.92 20.27 0 568.47 368.23 55321 +1941 153 18.69 12.69 17.04 0 474.75 379.57 55409 +1941 154 16.78 10.78 15.13 0 425.78 385.55 55492 +1941 155 17.6 11.6 15.95 0.54 446.25 287.54 55572 +1941 156 14.47 8.47 12.82 0.03 372.37 294.09 55648 +1941 157 16.29 10.29 14.64 0.38 413.94 290.69 55719 +1941 158 17.62 11.62 15.97 1.17 446.76 288 55786 +1941 159 18.24 12.24 16.59 0.02 462.8 286.78 55849 +1941 160 17.65 11.65 16 0 447.52 384.33 55908 +1941 161 17.72 11.72 16.07 0 449.31 384.19 55962 +1941 162 17.03 11.03 15.38 0.56 431.94 289.7 56011 +1941 163 19.86 13.86 18.21 0 507.05 377.71 56056 +1941 164 17.64 11.64 15.99 0.7 447.27 288.57 56097 +1941 165 19.79 13.79 18.14 0.18 505.07 283.56 56133 +1941 166 20.67 14.67 19.02 0.05 530.49 281.35 56165 +1941 167 25.17 19.17 23.52 0.09 678.18 267.81 56192 +1941 168 22.32 16.32 20.67 0.01 581.1 276.81 56214 +1941 169 25.12 19.12 23.47 0 676.36 357.39 56231 +1941 170 23.04 17.04 21.39 0 604.44 366.25 56244 +1941 171 23.63 17.63 21.98 0 624.15 363.9 56252 +1941 172 23.2 17.2 21.55 0.14 609.73 274.24 56256 +1941 173 23.76 17.76 22.11 0.06 628.56 272.5 56255 +1941 174 24.06 18.06 22.41 0 638.85 361.98 56249 +1941 175 22.5 16.5 20.85 0 586.86 368.31 56238 +1941 176 26.96 20.96 25.31 0.01 745.9 261.42 56223 +1941 177 26.57 20.57 24.92 0.04 730.68 262.78 56203 +1941 178 24.14 18.14 22.49 0.16 641.62 271.13 56179 +1941 179 20.12 14.12 18.47 0.11 514.48 282.59 56150 +1941 180 17.39 11.39 15.74 0.35 440.93 288.96 56116 +1941 181 17.1 11.1 15.45 0.15 433.67 289.53 56078 +1941 182 23.09 17.09 21.44 0 606.09 365.43 56035 +1941 183 25.36 19.36 23.71 0.08 685.11 266.64 55987 +1941 184 23.16 17.16 21.51 0 608.4 364.83 55935 +1941 185 27.71 21.71 26.06 0 775.93 343.88 55879 +1941 186 27.98 21.98 26.33 0 786.99 342.23 55818 +1941 187 29.17 23.17 27.52 0 837.32 335.62 55753 +1941 188 25.3 19.3 23.65 0.03 682.91 266.17 55684 +1941 189 23.5 17.5 21.85 0.25 619.76 271.87 55611 +1941 190 18.39 12.39 16.74 0.07 466.76 285.27 55533 +1941 191 18.91 12.91 17.26 0.02 480.69 283.85 55451 +1941 192 18.05 12.05 16.4 0.45 457.83 285.61 55366 +1941 193 21.85 15.85 20.2 0.76 566.28 275.82 55276 +1941 194 23.11 17.11 21.46 0.44 606.75 272 55182 +1941 195 20.43 14.43 18.78 0.74 523.45 279.28 55085 +1941 196 19.46 13.46 17.81 1.01 495.8 281.41 54984 +1941 197 20.98 14.98 19.33 0.04 539.7 277.19 54879 +1941 198 18.77 12.77 17.12 0.05 476.9 282.39 54770 +1941 199 18.33 12.33 16.68 0 465.17 377.52 54658 +1941 200 20.42 14.42 18.77 0 523.16 370.36 54542 +1941 201 15.71 9.71 14.06 0.18 400.28 288.02 54423 +1941 202 20.34 14.34 18.69 0 520.83 369.6 54301 +1941 203 21.22 15.22 19.57 0.46 546.93 274.52 54176 +1941 204 26.18 20.18 24.53 0.01 715.72 258.83 54047 +1941 205 25.11 19.11 23.46 0 676 349.5 53915 +1941 206 24.72 18.72 23.07 0 661.99 350.66 53780 +1941 207 25.22 19.22 23.57 0.01 679.99 260.88 53643 +1941 208 23.57 17.57 21.92 0 622.12 354.21 53502 +1941 209 21.27 15.27 19.62 0 548.44 362.32 53359 +1941 210 22.58 16.58 20.93 0 589.44 356.86 53213 +1941 211 19.53 13.53 17.88 0.28 497.76 275.11 53064 +1941 212 21.19 15.19 19.54 0 546.02 360.42 52913 +1941 213 19.54 13.54 17.89 0 498.04 365.22 52760 +1941 214 19.63 13.63 17.98 0 500.56 364.18 52604 +1941 215 18.22 12.22 16.57 0 462.28 367.85 52445 +1941 216 20.39 14.39 18.74 0 522.29 359.99 52285 +1941 217 17.97 11.97 16.32 0 455.76 366.66 52122 +1941 218 18.34 12.34 16.69 0.71 465.43 273.56 51958 +1941 219 18.3 12.3 16.65 0.02 464.38 272.85 51791 +1941 220 17.04 11.04 15.39 0.09 432.18 274.83 51622 +1941 221 18.34 12.34 16.69 0 465.43 361.72 51451 +1941 222 19.91 13.91 18.26 0.61 508.47 266.87 51279 +1941 223 22.87 16.87 21.22 0.45 598.86 258.25 51105 +1941 224 19.16 13.16 17.51 0.62 487.51 266.99 50929 +1941 225 18.81 12.81 17.16 0.55 477.98 266.92 50751 +1941 226 22.34 16.34 20.69 0 581.74 343.03 50572 +1941 227 25.61 19.61 23.96 0 694.32 328.69 50392 +1941 228 26.24 20.24 24.59 1.14 718 243.55 50210 +1941 229 22.6 16.6 20.95 0 590.08 338.41 50026 +1941 230 19.31 13.31 17.66 0 491.64 348.2 49842 +1941 231 19.47 13.47 17.82 0.23 496.08 259.68 49656 +1941 232 22.28 16.28 20.63 0.11 579.83 251.68 49469 +1941 233 25.11 19.11 23.46 0 676 323.22 49280 +1941 234 23.61 17.61 21.96 0 623.47 327.87 49091 +1941 235 23.78 17.78 22.13 0.15 629.24 244.33 48900 +1941 236 21.23 15.23 19.58 0.77 547.23 250.16 48709 +1941 237 20.2 14.2 18.55 0.51 516.78 251.44 48516 +1941 238 19.2 13.2 17.55 0.1 488.61 252.47 48323 +1941 239 22.46 16.46 20.81 0 585.58 324.59 48128 +1941 240 17.91 11.91 16.26 0.03 454.2 252.76 47933 +1941 241 23.42 17.42 21.77 0.78 617.07 238.3 47737 +1941 242 20.83 14.83 19.18 1.51 535.23 243.71 47541 +1941 243 23.18 17.18 21.53 1.19 609.06 236.35 47343 +1941 244 16.19 10.19 14.54 0 411.56 334.2 47145 +1941 245 15.56 9.56 13.91 0 396.81 333.83 46947 +1941 246 13.82 7.82 12.17 0 358.42 335.65 46747 +1941 247 11.45 5.45 9.8 0 311.26 338.33 46547 +1941 248 16.19 10.19 14.54 0 411.56 326.51 46347 +1941 249 13.98 7.98 12.33 0 361.81 329.33 46146 +1941 250 12.9 6.9 11.25 0.05 339.43 247.12 45945 +1941 251 14.38 8.38 12.73 0.86 370.41 243.26 45743 +1941 252 19.12 13.12 17.47 0 486.41 310.7 45541 +1941 253 16.62 10.62 14.97 0 421.88 315 45339 +1941 254 17.78 11.78 16.13 0 450.85 310.02 45136 +1941 255 17.9 11.9 16.25 0 453.94 307.47 44933 +1941 256 17.11 11.11 15.46 0 433.92 307.16 44730 +1941 257 20.23 14.23 18.58 0 517.65 296.81 44527 +1941 258 17.91 11.91 16.26 0 454.2 300.7 44323 +1941 259 18.35 12.35 16.7 0 465.7 297.19 44119 +1941 260 19.9 13.9 18.25 0 508.19 290.73 43915 +1941 261 19.01 13.01 17.36 0 483.41 290.72 43711 +1941 262 19.35 13.35 17.7 0.05 492.75 215.62 43507 +1941 263 23.14 17.14 21.49 0 607.74 273.96 43303 +1941 264 20.76 14.76 19.11 0 533.15 278.72 43099 +1941 265 21.74 15.74 20.09 0 562.86 273.59 42894 +1941 266 20.11 14.11 18.46 0 514.19 275.81 42690 +1941 267 15.25 9.25 13.6 0.52 389.73 213.4 42486 +1941 268 13.06 7.06 11.41 0 342.67 286.08 42282 +1941 269 15.7 9.7 14.05 0 400.05 278.55 42078 +1941 270 14.49 8.49 12.84 0 372.81 278.29 41875 +1941 271 12.62 6.62 10.97 0 333.83 278.97 41671 +1941 272 13.17 7.17 11.52 0.04 344.91 206.46 41468 +1941 273 12.48 6.48 10.83 0.57 331.05 205.41 41265 +1941 274 8.12 2.12 6.47 0 254.02 277.4 41062 +1941 275 11.47 5.47 9.82 0 311.63 269.97 40860 +1941 276 8.78 2.78 7.13 0.26 264.59 203.23 40658 +1941 277 11.87 5.87 10.22 0.07 319.2 197.96 40456 +1941 278 14.22 8.22 12.57 0 366.95 257.21 40255 +1941 279 15.54 9.54 13.89 0 396.35 252.02 40054 +1941 280 16.12 10.12 14.47 0.37 409.89 186.22 39854 +1941 281 19.26 13.26 17.61 0 490.26 239.03 39654 +1941 282 17.11 11.11 15.46 0.17 433.92 180.74 39455 +1941 283 14.29 8.29 12.64 0.04 368.46 182.55 39256 +1941 284 12.12 6.12 10.47 0 324.02 243.81 39058 +1941 285 10.18 4.18 8.53 0 288.25 243.82 38861 +1941 286 8.6 2.6 6.95 0.01 261.67 182.22 38664 +1941 287 13.12 7.12 11.47 1.45 343.89 175.48 38468 +1941 288 10.43 4.43 8.78 0.34 292.66 176.2 38273 +1941 289 10.26 4.26 8.61 0.56 289.65 174.37 38079 +1941 290 10.97 4.97 9.32 0.06 302.38 171.53 37885 +1941 291 11.89 5.89 10.24 0 319.59 224.77 37693 +1941 292 14.09 8.09 12.44 0 364.16 218.9 37501 +1941 293 13.4 7.4 11.75 2.3 349.64 162.93 37311 +1941 294 13.54 7.54 11.89 0.05 352.55 160.63 37121 +1941 295 12.64 6.64 10.99 0.03 334.22 159.47 36933 +1941 296 13.29 7.29 11.64 0 347.37 209.16 36745 +1941 297 9.26 3.26 7.61 0 272.5 211.48 36560 +1941 298 10.97 4.97 9.32 0.06 302.38 155.17 36375 +1941 299 13.93 7.93 12.28 0 360.75 200.22 36191 +1941 300 10.3 4.3 8.65 0.07 290.36 151.67 36009 +1941 301 11.44 5.44 9.79 0 311.07 198.37 35829 +1941 302 11.01 5.01 9.36 0 303.11 196.28 35650 +1941 303 11.38 5.38 9.73 0 309.95 193.28 35472 +1941 304 14.71 8.71 13.06 0 377.64 186.5 35296 +1941 305 9.45 3.45 7.8 0 275.69 190.22 35122 +1941 306 14.11 8.11 12.46 0 364.59 182.45 34950 +1941 307 12.35 6.35 10.7 0.01 328.5 136.68 34779 +1941 308 8.65 2.65 7 0.66 262.48 137.73 34610 +1941 309 4.92 -1.08 3.27 0.44 207.79 138.35 34444 +1941 310 3.43 -2.57 1.78 0.23 188.86 137.29 34279 +1941 311 3.97 -2.03 2.32 0 195.54 180.47 34116 +1941 312 3.62 -2.38 1.97 0 191.19 178.03 33956 +1941 313 1.53 -4.47 -0.12 0 166.89 177.17 33797 +1941 314 5.69 -0.31 4.04 0 218.19 172.45 33641 +1941 315 3.73 -2.27 2.08 0 192.55 171.26 33488 +1941 316 3.54 -2.46 1.89 0.9 190.2 126.88 33337 +1941 317 2.79 -3.21 1.14 0.95 181.2 125.57 33188 +1941 318 1.98 -4.02 0.33 0.05 171.89 124.15 33042 +1941 319 -1.39 -7.39 -3.04 1.27 137.44 167.95 32899 +1941 320 0.38 -5.62 -1.27 0.52 154.7 166.03 32758 +1941 321 3.92 -2.08 2.27 0.13 194.91 162.64 32620 +1941 322 5.62 -0.38 3.97 0.01 217.23 159.9 32486 +1941 323 8.39 2.39 6.74 0 258.3 194.23 32354 +1941 324 5.32 -0.68 3.67 0.23 213.14 155.93 32225 +1941 325 3.4 -2.6 1.75 0.08 188.49 155.27 32100 +1941 326 -0.16 -6.16 -1.81 0.25 149.25 156.47 31977 +1941 327 0.18 -5.82 -1.47 0 152.66 192.59 31858 +1941 328 -0.53 -6.53 -2.18 0 145.6 191.07 31743 +1941 329 -0.17 -6.17 -1.82 0.58 149.15 154.63 31631 +1941 330 3.14 -2.86 1.49 0.14 185.35 152.04 31522 +1941 331 6.04 0.04 4.39 0.26 223.07 149.09 31417 +1941 332 9.95 3.95 8.3 0.98 284.24 144.5 31316 +1941 333 6.61 0.61 4.96 2.09 231.21 102.99 31218 +1941 334 7.08 1.08 5.43 0.03 238.11 101.93 31125 +1941 335 0.45 -5.55 -1.2 0 155.42 138.51 31035 +1941 336 -0.23 -6.23 -1.88 0 148.55 137.72 30949 +1941 337 0.18 -5.82 -1.47 0.1 152.66 101.9 30867 +1941 338 2.53 -3.47 0.88 0 178.16 133.8 30790 +1941 339 2.87 -3.13 1.22 0 182.14 132.83 30716 +1941 340 2.53 -3.47 0.88 0 178.16 132.26 30647 +1941 341 4.45 -1.55 2.8 0 201.65 130.31 30582 +1941 342 3.93 -2.07 2.28 0 195.04 129.84 30521 +1941 343 8.77 2.77 7.12 0 264.42 125.89 30465 +1941 344 6.08 0.08 4.43 0 223.63 126.61 30413 +1941 345 6.24 0.24 4.59 0 225.9 126.09 30366 +1941 346 5.46 -0.54 3.81 0.38 215.04 94.52 30323 +1941 347 6.68 0.68 5.03 0.23 232.23 93.5 30284 +1941 348 7.06 1.06 5.41 0 237.82 124.07 30251 +1941 349 4.13 -1.87 2.48 0.05 197.56 94.1 30221 +1941 350 7.28 1.28 5.63 0 241.11 123.21 30197 +1941 351 4.27 -1.73 2.62 0 199.34 124.83 30177 +1941 352 3.14 -2.86 1.49 0.76 185.35 94 30162 +1941 353 4.88 -1.12 3.23 0.43 207.26 93.25 30151 +1941 354 4.27 -1.73 2.62 0.12 199.34 93.48 30145 +1941 355 1.69 -4.31 0.04 0.45 168.65 94.46 30144 +1941 356 -2.29 -8.29 -3.94 0.39 129.32 140.72 30147 +1941 357 1.17 -4.83 -0.48 0 162.99 171.13 30156 +1941 358 -0.55 -6.55 -2.2 0 145.41 171.93 30169 +1941 359 -0.51 -6.51 -2.16 0 145.8 172.01 30186 +1941 360 3.48 -2.52 1.83 0 189.47 170.04 30208 +1941 361 1.65 -4.35 0 0 168.21 171.02 30235 +1941 362 3.37 -2.63 1.72 0 188.13 126.55 30267 +1941 363 8.05 2.05 6.4 0 252.93 124.27 30303 +1941 364 6.24 0.24 4.59 0 225.9 125.87 30343 +1941 365 5.03 -0.97 3.38 0 209.25 127.18 30388 +1942 1 -6 -12 -7.65 0 100.07 132.67 30438 +1942 2 -6 -12 -7.65 0 100.07 133.42 30492 +1942 3 -6 -12 -7.65 0 100.07 134.37 30551 +1942 4 -6 -12 -7.65 0.55 100.07 146.32 30614 +1942 5 -6 -12 -7.65 0 100.07 180.71 30681 +1942 6 -6 -12 -7.65 0.08 100.07 147.55 30752 +1942 7 -6 -12 -7.65 0 100.07 182.47 30828 +1942 8 -6 -12 -7.65 0.2 100.07 149.68 30907 +1942 9 -6 -12 -7.65 0.6 100.07 152.38 30991 +1942 10 -6 -12 -7.65 0 100.07 188.69 31079 +1942 11 -6 -12 -7.65 0 100.07 189.56 31171 +1942 12 -6 -12 -7.65 0 100.07 190.45 31266 +1942 13 -6 -12 -7.65 0.07 100.07 155.79 31366 +1942 14 -6 -12 -7.65 0.28 100.07 157.62 31469 +1942 15 -6 -12 -7.65 0 100.07 195.68 31575 +1942 16 -6 -12 -7.65 0.45 100.07 160.75 31686 +1942 17 -6 -12 -7.65 0 100.07 199.74 31800 +1942 18 -6 -12 -7.65 0.08 100.07 163.37 31917 +1942 19 -6 -12 -7.65 0 100.07 203.51 32038 +1942 20 -6 -12 -7.65 0 100.07 204.95 32161 +1942 21 -6 -12 -7.65 0.09 100.07 167.31 32289 +1942 22 -6 -12 -7.65 0 100.07 208.66 32419 +1942 23 -6 -12 -7.65 0 100.07 210.27 32552 +1942 24 -6 -12 -7.65 0 100.07 212.18 32688 +1942 25 -6 -12 -7.65 0.41 100.07 173.43 32827 +1942 26 -6 -12 -7.65 0 100.07 216.86 32969 +1942 27 -6 -12 -7.65 0 100.07 218.71 33114 +1942 28 -6 -12 -7.65 0.02 100.07 177.57 33261 +1942 29 -6 -12 -7.65 0.01 100.07 179.2 33411 +1942 30 -6 -12 -7.65 0 100.07 225.11 33564 +1942 31 -6 -12 -7.65 0 100.07 227.31 33718 +1942 32 -6.5 -12.5 -8.15 0 96.61 229.42 33875 +1942 33 -3.81 -9.81 -5.46 0.14 116.55 185.26 34035 +1942 34 -5.39 -11.39 -7.04 0.01 104.44 187.2 34196 +1942 35 -3.42 -9.42 -5.07 0.01 119.71 188.07 34360 +1942 36 -2.11 -8.11 -3.76 0.5 130.91 190.71 34526 +1942 37 -1.61 -7.61 -3.26 0.28 135.41 192.92 34694 +1942 38 -5.55 -11.55 -7.2 0 103.28 245.29 34863 +1942 39 -4.74 -10.74 -6.39 0.52 109.28 198.98 35035 +1942 40 -4.06 -10.06 -5.71 1.57 114.55 204.81 35208 +1942 41 -3.94 -9.94 -5.59 0.93 115.51 209.03 35383 +1942 42 -3.78 -9.78 -5.43 1.07 116.79 213.54 35560 +1942 43 0.22 -5.78 -1.43 0 153.07 265.65 35738 +1942 44 0.55 -5.45 -1.1 0.04 156.45 215.19 35918 +1942 45 0.66 -5.34 -0.99 0.03 157.6 216.77 36099 +1942 46 3.89 -2.11 2.24 0.45 194.54 216.4 36282 +1942 47 1.02 -4.98 -0.63 0.25 161.39 219.65 36466 +1942 48 -0.77 -6.77 -2.42 0 143.28 277.77 36652 +1942 49 0.57 -5.43 -1.08 0.07 156.66 223.47 36838 +1942 50 0.37 -5.63 -1.28 0 154.6 281.93 37026 +1942 51 1.49 -4.51 -0.16 0.68 166.46 226.52 37215 +1942 52 0.44 -5.56 -1.21 0 155.32 286.98 37405 +1942 53 0.32 -5.68 -1.33 0.1 154.09 230.86 37596 +1942 54 2.44 -3.56 0.79 0.72 177.12 231.3 37788 +1942 55 -1.48 -7.48 -3.13 0.09 136.61 235.48 37981 +1942 56 1.11 -4.89 -0.54 0 162.35 296.79 38175 +1942 57 3.79 -2.21 2.14 0 193.29 296.97 38370 +1942 58 4.62 -1.38 2.97 0.24 203.85 236.78 38565 +1942 59 7.8 1.8 6.15 0 249.03 296.88 38761 +1942 60 10.23 4.23 8.58 0.13 289.12 233.97 38958 +1942 61 12.79 6.79 11.14 0 337.22 293.16 39156 +1942 62 12.1 6.1 10.45 0 323.63 295.45 39355 +1942 63 9.31 3.31 7.66 0 273.34 301.08 39553 +1942 64 6.52 0.52 4.87 0.08 229.91 240.82 39753 +1942 65 7.11 1.11 5.46 0 238.56 307.64 39953 +1942 66 9.37 3.37 7.72 0 274.35 306.48 40154 +1942 67 6.36 0.36 4.71 0.66 227.61 244.42 40355 +1942 68 2.6 -3.4 0.95 0 178.98 318.17 40556 +1942 69 1.38 -4.62 -0.27 0 165.26 321.5 40758 +1942 70 3.99 -2.01 2.34 0 195.79 321.51 40960 +1942 71 11.17 5.17 9.52 0.02 306.05 245.48 41163 +1942 72 5.06 -0.94 3.41 0 209.65 324.26 41366 +1942 73 3.27 -2.73 1.62 0.08 186.92 255.53 41569 +1942 74 5.23 -0.77 3.58 0 211.92 328.35 41772 +1942 75 2.95 -3.05 1.3 0 183.09 332.91 41976 +1942 76 1 -5 -0.65 0 161.18 337.01 42179 +1942 77 -1.28 -7.28 -2.93 0.01 138.46 264.91 42383 +1942 78 -1.41 -7.41 -3.06 0 137.25 343.89 42587 +1942 79 -0.86 -6.86 -2.51 0 142.42 346.12 42791 +1942 80 1.61 -4.39 -0.04 0 167.77 346.41 42996 +1942 81 1.71 -4.29 0.06 0 168.88 348.62 43200 +1942 82 5.36 -0.64 3.71 0 213.68 347 43404 +1942 83 4.64 -1.36 2.99 0.08 204.11 270.71 43608 +1942 84 1.72 -4.28 0.07 0.01 168.99 274.5 43812 +1942 85 1.78 -4.22 0.13 0.37 169.65 276.05 44016 +1942 86 2.81 -3.19 1.16 0.38 181.43 276.76 44220 +1942 87 5.66 -0.34 4.01 0 217.78 356.96 44424 +1942 88 6.54 0.54 4.89 0 230.2 357.52 44627 +1942 89 8.43 2.43 6.78 0 258.94 356.37 44831 +1942 90 8.99 2.99 7.34 0 268.03 356.99 45034 +1942 91 14.77 8.77 13.12 0 378.97 319.46 45237 +1942 92 17.72 11.72 16.07 0 449.31 314.74 45439 +1942 93 16.55 10.55 14.9 0.01 420.19 239.83 45642 +1942 94 14.82 8.82 13.17 0.77 380.08 244.37 45843 +1942 95 15.93 9.93 14.28 0 405.42 325.42 46045 +1942 96 13.19 7.19 11.54 0.2 345.32 250.06 46246 +1942 97 10.22 4.22 8.57 0.02 288.95 255.67 46446 +1942 98 10.43 4.43 8.78 0.29 292.66 256.88 46647 +1942 99 4.74 -1.26 3.09 0 205.42 352.68 46846 +1942 100 2.33 -3.67 0.68 0 175.86 357.33 47045 +1942 101 5.6 -0.4 3.95 0.82 216.95 266.69 47243 +1942 102 3.91 -2.09 2.26 0.07 194.79 269.67 47441 +1942 103 5.32 -0.68 3.67 0 213.14 359.76 47638 +1942 104 6.03 0.03 4.38 0 222.93 360.71 47834 +1942 105 15.36 9.36 13.71 0 392.23 345.77 48030 +1942 106 16.82 10.82 15.17 0.45 426.76 257.84 48225 +1942 107 18.46 12.46 16.81 0.91 468.61 255.72 48419 +1942 108 18.01 12.01 16.36 0 456.79 343.93 48612 +1942 109 16.87 10.87 15.22 0 427.99 348.57 48804 +1942 110 15.06 9.06 13.41 0.06 385.44 265.84 48995 +1942 111 12.83 6.83 11.18 0.02 338.02 270.69 49185 +1942 112 14 8 12.35 0 362.24 359.92 49374 +1942 113 13.42 7.42 11.77 0.09 350.05 271.9 49561 +1942 114 10.38 4.38 8.73 0.16 291.77 277.51 49748 +1942 115 9.28 3.28 7.63 2.66 272.84 280.04 49933 +1942 116 10.48 4.48 8.83 0.7 293.55 279.39 50117 +1942 117 8.88 2.88 7.23 1.04 266.22 282.47 50300 +1942 118 8.6 2.6 6.95 0.24 261.67 283.82 50481 +1942 119 8.34 2.34 6.69 0.14 257.5 285.05 50661 +1942 120 5.66 -0.34 4.01 0.05 217.78 288.91 50840 +1942 121 11.06 5.06 9.41 0.2 304.03 283.23 51016 +1942 122 13 7 11.35 0.11 341.45 281.19 51191 +1942 123 15.56 9.56 13.91 0.61 396.81 277.49 51365 +1942 124 15.3 9.3 13.65 0.17 390.86 278.78 51536 +1942 125 15.5 9.5 13.85 0.01 395.43 279.14 51706 +1942 126 12.8 6.8 11.15 0.22 337.42 284.6 51874 +1942 127 12.15 6.15 10.5 1.88 324.6 286.3 52039 +1942 128 14.1 8.1 12.45 0.03 364.37 283.85 52203 +1942 129 10.71 4.71 9.06 1.23 297.67 289.85 52365 +1942 130 16.56 10.56 14.91 0.48 420.43 280.45 52524 +1942 131 18.93 12.93 17.28 0.31 481.23 275.89 52681 +1942 132 18.62 12.62 16.97 0.2 472.87 277.21 52836 +1942 133 17.42 11.42 15.77 0 441.69 373.85 52989 +1942 134 15.08 9.08 13.43 0.87 385.89 285.61 53138 +1942 135 17.03 11.03 15.38 0 431.94 376.36 53286 +1942 136 18.06 12.06 16.41 0 458.09 374.02 53430 +1942 137 22.91 16.91 21.26 0 600.17 358.07 53572 +1942 138 21.48 15.48 19.83 0.16 554.85 273.03 53711 +1942 139 24.58 18.58 22.93 0 657.03 352.43 53848 +1942 140 22.75 16.75 21.1 0 594.94 360.4 53981 +1942 141 24.05 18.05 22.4 0.14 638.51 266.66 54111 +1942 142 18.44 12.44 16.79 0.37 468.08 282.19 54238 +1942 143 17.44 11.44 15.79 0 442.19 379.76 54362 +1942 144 15.8 9.8 14.15 0 402.38 384.77 54483 +1942 145 21.24 15.24 19.59 0 547.53 368.41 54600 +1942 146 19.97 13.97 18.32 0.9 510.18 279.89 54714 +1942 147 19.87 13.87 18.22 0.5 507.33 280.5 54824 +1942 148 19.61 13.61 17.96 0.11 500 281.43 54931 +1942 149 23.13 17.13 21.48 0.29 607.41 272.04 55034 +1942 150 22.89 16.89 21.24 0.31 599.51 273 55134 +1942 151 19.66 13.66 18.01 0.09 501.4 282.07 55229 +1942 152 23.19 17.19 21.54 0.04 609.4 272.46 55321 +1942 153 23.18 17.18 21.53 0.88 609.06 272.67 55409 +1942 154 22.84 16.84 21.19 0.1 597.88 273.92 55492 +1942 155 21.56 15.56 19.91 0 557.3 370.3 55572 +1942 156 24.34 18.34 22.69 0 648.58 359.52 55648 +1942 157 24.25 18.25 22.6 0 645.44 360.07 55719 +1942 158 21.99 15.99 20.34 0.07 570.66 277.01 55786 +1942 159 21.92 15.92 20.27 0.68 568.47 277.39 55849 +1942 160 16.74 10.74 15.09 0.02 424.8 290.21 55908 +1942 161 14.26 8.26 12.61 0 367.81 393.49 55962 +1942 162 20.09 14.09 18.44 0.23 513.62 282.54 56011 +1942 163 21.01 15.01 19.36 0.11 540.6 280.29 56056 +1942 164 20.3 14.3 18.65 0.24 519.67 282.19 56097 +1942 165 19.21 13.21 17.56 0.85 488.88 284.99 56133 +1942 166 22.31 16.31 20.66 0.3 580.78 276.82 56165 +1942 167 15.44 9.44 13.79 0.54 394.06 293.24 56192 +1942 168 11.56 5.56 9.91 0.16 313.32 300.05 56214 +1942 169 12.13 6.13 10.48 0 324.21 398.88 56231 +1942 170 19.35 13.35 17.7 0.11 492.75 284.74 56244 +1942 171 21.57 15.57 19.92 0.04 557.61 278.99 56252 +1942 172 23.83 17.83 22.18 0.07 630.95 272.29 56256 +1942 173 20.93 14.93 19.28 0 538.21 374.29 56255 +1942 174 22.41 16.41 20.76 2.3 583.98 276.52 56249 +1942 175 18.92 12.92 17.27 0.33 480.96 285.72 56238 +1942 176 20.32 14.32 18.67 0.72 520.25 282.21 56223 +1942 177 19.22 13.22 17.57 0.62 489.16 284.89 56203 +1942 178 22.07 16.07 20.42 0.16 573.18 277.39 56179 +1942 179 21.82 15.82 20.17 0 565.35 370.7 56150 +1942 180 21.38 15.38 19.73 0.04 551.79 279.16 56116 +1942 181 19.67 13.67 18.02 0 501.68 378.11 56078 +1942 182 21.76 15.76 20.11 0 563.48 370.59 56035 +1942 183 24.9 18.9 23.25 0.07 668.43 268.2 55987 +1942 184 24.38 18.38 22.73 0.04 649.98 269.8 55935 +1942 185 25.2 19.2 23.55 0.04 679.27 267.02 55879 +1942 186 26.05 20.05 24.4 0 710.79 351.85 55818 +1942 187 26.97 20.97 25.32 0 746.3 347.22 55753 +1942 188 26.46 20.46 24.81 0 726.43 349.46 55684 +1942 189 27.9 21.9 26.25 0.84 783.7 256.55 55611 +1942 190 26.77 20.77 25.12 0 738.45 347.42 55533 +1942 191 23.76 17.76 22.11 0 628.56 360.79 55451 +1942 192 22.77 16.77 21.12 0 595.59 364.5 55366 +1942 193 21.34 15.34 19.69 0.11 550.57 277.23 55276 +1942 194 24.5 18.5 22.85 0 654.2 356.88 55182 +1942 195 21.17 15.17 19.52 0.18 545.42 277.32 55085 +1942 196 23.12 17.12 21.47 0 607.08 361.96 54984 +1942 197 27.59 21.59 25.94 0.26 771.06 255.93 54879 +1942 198 25.18 19.18 23.53 0 678.54 352.37 54770 +1942 199 26.09 20.09 24.44 0.02 712.3 260.9 54658 +1942 200 21.79 15.79 20.14 0.17 564.42 274.11 54542 +1942 201 19.96 13.96 18.31 0.67 509.9 278.59 54423 +1942 202 18.48 12.48 16.83 0 469.14 375.61 54301 +1942 203 15.06 9.06 13.41 0.17 385.44 288.44 54176 +1942 204 12.38 6.38 10.73 0.12 329.09 292.69 54047 +1942 205 13.63 7.63 11.98 0.61 354.42 290.22 53915 +1942 206 16.35 10.35 14.7 0.55 415.37 284.7 53780 +1942 207 14.42 8.42 12.77 0.33 371.28 287.88 53643 +1942 208 15.08 9.08 13.43 1.85 385.89 286.16 53502 +1942 209 15.72 9.72 14.07 0.16 400.51 284.44 53359 +1942 210 17.88 11.88 16.23 0.63 453.43 279.5 53213 +1942 211 21.42 15.42 19.77 0 553.01 360.39 53064 +1942 212 21.5 15.5 19.85 0.12 555.46 269.49 52913 +1942 213 21.84 15.84 20.19 0 565.97 357.33 52760 +1942 214 22.56 16.56 20.91 0.08 588.79 265.44 52604 +1942 215 22.45 16.45 20.8 0 585.26 353.67 52445 +1942 216 20.5 14.5 18.85 0.09 525.5 269.71 52285 +1942 217 18.99 12.99 17.34 0 482.86 363.6 52122 +1942 218 20.3 14.3 18.65 0.18 519.67 268.94 51958 +1942 219 18.98 12.98 17.33 0.65 482.59 271.32 51791 +1942 220 18.95 12.95 17.3 0.18 481.77 270.68 51622 +1942 221 22.33 16.33 20.68 0 581.42 348.5 51451 +1942 222 23.4 17.4 21.75 0 616.4 343.4 51279 +1942 223 22.1 16.1 20.45 0 574.13 347.19 51105 +1942 224 26.91 20.91 25.26 0 743.94 326.16 50929 +1942 225 29.61 23.61 27.96 0 856.61 311.39 50751 +1942 226 29.83 23.83 28.18 0 866.39 309.15 50572 +1942 227 29.92 23.92 28.27 0 870.42 307.49 50392 +1942 228 28.97 22.97 27.32 0 828.68 311.47 50210 +1942 229 28.67 22.67 27.02 0.06 815.85 233.92 50026 +1942 230 27.74 21.74 26.09 0.09 777.15 236.52 49842 +1942 231 26.82 20.82 25.17 0.55 740.41 238.75 49656 +1942 232 22.09 16.09 20.44 0 573.81 336.25 49469 +1942 233 22.15 16.15 20.5 0 575.7 334.64 49280 +1942 234 19.66 13.66 18.01 0 501.4 341.47 49091 +1942 235 22.26 16.26 20.61 0 579.19 331.4 48900 +1942 236 21.94 15.94 20.29 0.1 569.1 248.35 48709 +1942 237 18.25 12.25 16.6 0 463.06 341.04 48516 +1942 238 17.09 11.09 15.44 0.02 433.42 256.87 48323 +1942 239 18.43 12.43 16.78 0.16 467.81 253 48128 +1942 240 21.5 15.5 19.85 0.69 555.46 244.63 47933 +1942 241 23.21 17.21 21.56 0.26 610.06 238.88 47737 +1942 242 24.34 18.34 22.69 0 648.58 312.58 47541 +1942 243 23.89 17.89 22.24 0 633 312.51 47343 +1942 244 23.42 17.42 21.77 0 617.07 312.5 47145 +1942 245 21.96 15.96 20.31 0 569.72 315.83 46947 +1942 246 18.69 12.69 17.04 0 474.75 323.89 46747 +1942 247 21.26 15.26 19.61 0 548.14 314.4 46547 +1942 248 20.98 14.98 19.33 0 539.7 313.39 46347 +1942 249 19.93 13.93 18.28 0 509.04 314.54 46146 +1942 250 17.21 11.21 15.56 0.12 436.41 239.99 45945 +1942 251 19.47 13.47 17.82 0 496.08 311.86 45743 +1942 252 22.29 16.29 20.64 0.01 580.15 225.82 45541 +1942 253 20.89 14.89 19.24 0 537.02 303.48 45339 +1942 254 18.21 12.21 16.56 0 462.01 308.92 45136 +1942 255 20.88 14.88 19.23 0 536.72 299.23 44933 +1942 256 26.64 20.64 24.99 0 733.39 276.71 44730 +1942 257 25.73 19.73 24.08 0 698.78 278.35 44527 +1942 258 23.88 17.88 22.23 0.42 632.66 212.22 44323 +1942 259 28.86 22.86 27.21 0.1 823.96 195.58 44119 +1942 260 28.35 22.35 26.7 0.42 802.36 195.68 43915 +1942 261 25.57 19.57 23.92 0 692.84 269.99 43711 +1942 262 24.51 18.51 22.86 0.04 654.55 203.73 43507 +1942 263 23.91 17.91 22.26 0.21 633.69 203.55 43303 +1942 264 18.98 12.98 17.33 0.1 482.59 212.63 43099 +1942 265 19.17 13.17 17.52 0 487.78 280.7 42894 +1942 266 22.45 16.45 20.8 0.13 585.26 201.8 42690 +1942 267 23.46 17.46 21.81 0 618.41 263.33 42486 +1942 268 21.86 15.86 20.21 0 566.6 265.82 42282 +1942 269 22.73 16.73 21.08 0.01 594.29 195.61 42078 +1942 270 23.95 17.95 22.3 0 635.06 254.48 41875 +1942 271 22.61 16.61 20.96 0 590.41 256.18 41671 +1942 272 20.61 14.61 18.96 0.16 528.72 194.41 41468 +1942 273 25.46 19.46 23.81 0 688.78 242.08 41265 +1942 274 21.04 15.04 19.39 0.08 541.5 189.8 41062 +1942 275 18.29 12.29 16.64 0 464.12 257.19 40860 +1942 276 17.75 11.75 16.1 0.74 450.08 191.82 40658 +1942 277 15.44 9.44 13.79 0 394.06 257.84 40456 +1942 278 14.46 8.46 12.81 0 372.15 256.79 40255 +1942 279 17.07 11.07 15.42 0 432.93 249.01 40054 +1942 280 15.99 9.99 14.34 0 406.83 248.55 39854 +1942 281 14.06 8.06 12.41 0 363.52 249.33 39654 +1942 282 15.11 9.11 13.46 0.11 386.56 183.58 39455 +1942 283 17.02 11.02 15.37 0 431.69 238.4 39256 +1942 284 15.96 9.96 14.31 0.25 406.12 178.1 39058 +1942 285 18.29 12.29 16.64 0 464.12 230.28 38861 +1942 286 18.17 12.17 16.52 0.54 460.97 170.89 38664 +1942 287 15.87 9.87 14.22 0 404.01 229.42 38468 +1942 288 16.98 10.98 15.33 0 430.7 224.64 38273 +1942 289 14.27 8.27 12.62 0 368.03 226.79 38079 +1942 290 11.63 5.63 9.98 0 314.64 227.83 37885 +1942 291 11.99 5.99 10.34 0 321.51 224.64 37693 +1942 292 15.4 9.4 13.75 0 393.14 216.8 37501 +1942 293 15.5 9.5 13.85 0.01 395.43 160.46 37311 +1942 294 16.32 10.32 14.67 0.12 414.65 157.3 37121 +1942 295 19.69 13.69 18.04 0.16 502.24 150.43 36933 +1942 296 17.42 11.42 15.77 0 441.69 202.51 36745 +1942 297 16.09 10.09 14.44 0 409.18 202.17 36560 +1942 298 10.73 4.73 9.08 0.49 298.03 155.39 36375 +1942 299 12.15 6.15 10.5 0.45 324.6 151.98 36191 +1942 300 13.17 7.17 11.52 0 344.91 198.65 36009 +1942 301 15.63 9.63 13.98 0 398.43 192.59 35829 +1942 302 12.61 6.61 10.96 0 333.63 194.32 35650 +1942 303 11.42 5.42 9.77 0 310.69 193.23 35472 +1942 304 13.06 7.06 11.41 0 342.67 188.75 35296 +1942 305 5.99 -0.01 4.34 0.12 222.37 145.08 35122 +1942 306 8.63 2.63 6.98 0 262.15 188.79 34950 +1942 307 7.8 1.8 6.15 0 249.03 187.05 34779 +1942 308 8.02 2.02 6.37 0 252.46 184.24 34610 +1942 309 11.32 5.32 9.67 0 308.83 178.58 34444 +1942 310 5.71 -0.29 4.06 0.91 218.47 136.05 34279 +1942 311 4.35 -1.65 2.7 0 200.36 180.2 34116 +1942 312 5.18 -0.82 3.53 0 211.25 176.94 33956 +1942 313 3.53 -2.47 1.88 0 190.08 175.94 33797 +1942 314 0.32 -5.68 -1.33 0 154.09 175.84 33641 +1942 315 1.42 -4.58 -0.23 0 165.69 172.67 33488 +1942 316 1.32 -4.68 -0.33 0.07 164.61 127.87 33337 +1942 317 5.7 -0.3 4.05 0 218.33 165.48 33188 +1942 318 3.43 -2.57 1.78 0 188.86 164.66 33042 +1942 319 6.06 0.06 4.41 0 223.35 161.16 32899 +1942 320 8.09 2.09 6.44 0 253.55 157.71 32758 +1942 321 7.07 1.07 5.42 0 237.97 156.42 32620 +1942 322 9.21 3.21 7.56 0.07 271.67 114.64 32486 +1942 323 9.35 3.35 7.7 0 274.01 151.12 32354 +1942 324 13.55 7.55 11.9 0 352.75 144.92 32225 +1942 325 11.1 5.1 9.45 0 304.76 145.79 32100 +1942 326 10.9 4.9 9.25 0 301.11 144.55 31977 +1942 327 8.19 2.19 6.54 0 255.13 145.07 31858 +1942 328 9.97 3.97 8.32 0 284.59 141.63 31743 +1942 329 9.45 3.45 7.8 0 275.69 140.6 31631 +1942 330 9.63 3.63 7.98 0 278.74 139.03 31522 +1942 331 5.8 -0.2 4.15 0 219.72 140.59 31417 +1942 332 5.35 -0.65 3.7 0 213.54 139.24 31316 +1942 333 2.57 -3.43 0.92 0.08 178.63 104.83 31218 +1942 334 4.21 -1.79 2.56 0.3 198.57 103.31 31125 +1942 335 -0.01 -6.01 -1.66 0 150.74 138.71 31035 +1942 336 3.66 -2.34 2.01 0 191.68 135.81 30949 +1942 337 4.36 -1.64 2.71 0 200.49 133.74 30867 +1942 338 3.75 -2.25 2.1 0 192.79 133.15 30790 +1942 339 7.57 1.57 5.92 0.01 245.5 97.47 30716 +1942 340 7.56 1.56 5.91 0.07 245.35 96.93 30647 +1942 341 7.2 1.2 5.55 0 239.91 128.58 30582 +1942 342 6.53 0.53 4.88 0.36 230.05 96.2 30521 +1942 343 7.45 1.45 5.8 0 243.67 126.84 30465 +1942 344 7.13 1.13 5.48 0 238.86 125.93 30413 +1942 345 8.13 2.13 6.48 0 254.18 124.81 30366 +1942 346 10 4 8.35 0.06 285.11 92.14 30323 +1942 347 8.02 2.02 6.37 0.05 252.46 92.82 30284 +1942 348 8.1 2.1 6.45 0.01 253.71 92.52 30251 +1942 349 11.05 5.05 9.4 0.03 303.84 90.52 30221 +1942 350 10.39 4.39 8.74 0 291.95 120.91 30197 +1942 351 7.58 1.58 5.93 0 245.65 122.8 30177 +1942 352 9.94 3.94 8.29 0.74 284.07 90.73 30162 +1942 353 5.41 -0.59 3.76 0 214.36 124.02 30151 +1942 354 3.92 -2.08 2.27 0 194.91 124.83 30145 +1942 355 3.3 -2.7 1.65 0 187.28 125.16 30144 +1942 356 2.61 -3.39 0.96 0.05 179.09 94.15 30147 +1942 357 -3.52 -9.52 -5.17 0.63 118.89 141.83 30156 +1942 358 0.34 -5.66 -1.31 0 154.29 172.44 30169 +1942 359 2.75 -3.25 1.1 0 180.73 171.05 30186 +1942 360 3.39 -2.61 1.74 0.28 188.37 139.16 30208 +1942 361 1.46 -4.54 -0.19 0 166.13 171.65 30235 +1942 362 2.09 -3.91 0.44 0.23 173.13 139.67 30267 +1942 363 1.99 -4.01 0.34 0 172 171.79 30303 +1942 364 0.57 -5.43 -1.08 0 156.66 172.7 30343 +1942 365 -0.19 -6.19 -1.84 0 148.95 173.53 30388 +1943 1 -3.1 -9.1 -4.75 0.12 122.37 142.89 30438 +1943 2 -3.65 -9.65 -5.3 0.83 117.84 146.13 30492 +1943 3 -5.54 -11.54 -7.19 0.21 103.35 147.85 30551 +1943 4 -7.06 -13.06 -8.71 0 92.85 182.66 30614 +1943 5 -8.45 -14.45 -10.1 0 84.07 183.57 30681 +1943 6 -2.97 -8.97 -4.62 0 123.46 182.78 30752 +1943 7 -2.22 -8.22 -3.87 0 129.93 183.2 30828 +1943 8 -2.6 -8.6 -4.25 0.19 126.62 150.79 30907 +1943 9 -1.95 -7.95 -3.6 0.06 132.33 151.62 30991 +1943 10 -3.68 -9.68 -5.33 0 117.59 188.21 31079 +1943 11 -2.86 -8.86 -4.51 0 124.39 188.78 31171 +1943 12 -1.72 -7.72 -3.37 0.02 134.41 153.7 31266 +1943 13 3.37 -2.63 1.72 0.01 188.13 152.53 31366 +1943 14 6.39 0.39 4.74 0.08 228.04 151.25 31469 +1943 15 7.45 1.45 5.8 0 243.67 186.11 31575 +1943 16 3.37 -2.63 1.72 0.02 188.13 153.03 31686 +1943 17 1.68 -4.32 0.03 0 168.54 191.72 31800 +1943 18 2.21 -3.79 0.56 0.37 174.49 155.4 31917 +1943 19 -3.31 -9.31 -4.96 0 120.62 197.19 32038 +1943 20 -2.96 -8.96 -4.61 0.07 123.55 159.72 32161 +1943 21 -1.04 -7.04 -2.69 0 140.71 199.78 32289 +1943 22 -0.9 -6.9 -2.55 0 142.04 201.31 32419 +1943 23 -1.6 -7.6 -3.25 0 135.5 203.24 32552 +1943 24 0 -6 -1.65 0 150.84 204.42 32688 +1943 25 2.35 -3.65 0.7 0 176.09 204.6 32827 +1943 26 5.46 -0.54 3.81 0.12 215.04 162.95 32969 +1943 27 -1.31 -7.31 -2.96 1.19 138.18 170.68 33114 +1943 28 -0.27 -6.27 -1.92 0 148.15 214.44 33261 +1943 29 -1.24 -7.24 -2.89 0 138.83 217.11 33411 +1943 30 -3.08 -9.08 -4.73 0 122.54 220 33564 +1943 31 -1.18 -7.18 -2.83 0 139.39 221.36 33718 +1943 32 5.62 -0.38 3.97 0 217.23 218.47 33875 +1943 33 8.39 2.39 6.74 0 258.3 217.58 34035 +1943 34 6.47 0.47 4.82 0 229.19 220.46 34196 +1943 35 8.77 2.77 7.12 0.28 264.42 174.25 34360 +1943 36 6.41 0.41 4.76 0.55 228.32 138.69 34526 +1943 37 6.96 0.96 5.31 0 236.34 186.87 34694 +1943 38 9.59 3.59 7.94 0.13 278.06 140.32 34863 +1943 39 11.41 5.41 9.76 0 310.51 187.65 35035 +1943 40 4.02 -1.98 2.37 0 196.17 197.16 35208 +1943 41 7.34 1.34 5.69 0.38 242.01 147.78 35383 +1943 42 8.39 2.39 6.74 0 258.3 198.56 35560 +1943 43 7.76 1.76 6.11 0.2 248.42 151.39 35738 +1943 44 8.41 2.41 6.76 0 258.62 203.75 35918 +1943 45 7.77 1.77 6.12 0 248.57 206.99 36099 +1943 46 6.07 0.07 4.42 0 223.49 211.25 36282 +1943 47 1.31 -4.69 -0.34 0 164.5 217.73 36466 +1943 48 -0.06 -6.06 -1.71 0 150.24 221.42 36652 +1943 49 5.28 -0.72 3.63 0.01 212.6 165.25 36838 +1943 50 3.19 -2.81 1.54 0 185.95 224.71 37026 +1943 51 5.3 -0.7 3.65 0 212.87 225.95 37215 +1943 52 6.36 0.36 4.71 1.1 227.61 170.85 37405 +1943 53 3.83 -2.17 2.18 0.29 193.79 174.75 37596 +1943 54 4.63 -1.37 2.98 0 203.98 235.09 37788 +1943 55 8.02 2.02 6.37 0.08 252.46 176.08 37981 +1943 56 7.78 1.78 6.13 0 248.73 237.7 38175 +1943 57 7.45 1.45 5.8 0 243.67 240.93 38370 +1943 58 8.32 2.32 6.67 0.41 257.19 182.16 38565 +1943 59 5.17 -0.83 3.52 0 211.12 248.85 38761 +1943 60 5.39 -0.61 3.74 0 214.09 251.54 38958 +1943 61 9.99 3.99 8.34 0 284.93 249.29 39156 +1943 62 5.98 -0.02 4.33 0 222.23 256.69 39355 +1943 63 9.01 3.01 7.36 0 268.36 256.28 39553 +1943 64 9.29 3.29 7.64 0 273.01 258.81 39753 +1943 65 10.55 4.55 8.9 0 294.79 259.99 39953 +1943 66 7.42 1.42 5.77 0 243.22 266.67 40154 +1943 67 7.92 1.92 6.27 0 250.9 268.98 40355 +1943 68 5.53 -0.47 3.88 0.02 215.99 205.89 40556 +1943 69 7 1 5.35 0.07 236.93 206.66 40758 +1943 70 6.72 0.72 5.07 0 232.81 278.72 40960 +1943 71 10.17 4.17 8.52 0 288.07 277.23 41163 +1943 72 10.92 4.92 9.27 0.04 301.47 209.2 41366 +1943 73 11.78 5.78 10.13 0 317.49 280.23 41569 +1943 74 10.46 4.46 8.81 0 293.19 284.97 41772 +1943 75 5.34 -0.66 3.69 0 213.41 294.2 41976 +1943 76 8.57 2.57 6.92 0.03 261.19 219.72 42179 +1943 77 9.55 3.55 7.9 0 277.38 294.2 42383 +1943 78 9.53 3.53 7.88 0 277.05 296.88 42587 +1943 79 8.34 2.34 6.69 0 257.5 301.26 42791 +1943 80 8.59 2.59 6.94 0 261.51 303.45 42996 +1943 81 8.77 2.77 7.12 0.01 264.42 229.34 43200 +1943 82 7.02 1.02 5.37 0 237.22 310.76 43404 +1943 83 8.44 2.44 6.79 0 259.1 311.39 43608 +1943 84 11.69 5.69 10.04 0 315.78 308.91 43812 +1943 85 8.68 2.68 7.03 0.01 262.96 237.07 44016 +1943 86 12.66 6.66 11.01 0.07 334.62 234.04 44220 +1943 87 10.02 4.02 8.37 0 285.45 319.04 44424 +1943 88 11.42 5.42 9.77 0 310.69 319.08 44627 +1943 89 11.24 5.24 9.59 0 307.35 321.65 44831 +1943 90 11.51 5.51 9.86 0 312.38 323.54 45034 +1943 91 15.16 9.16 13.51 0 387.69 318.62 45237 +1943 92 15.69 9.69 14.04 0 399.82 319.63 45439 +1943 93 16.47 10.47 14.82 0 418.26 319.97 45642 +1943 94 19.88 13.88 18.23 0 507.62 313.02 45843 +1943 95 20.34 14.34 18.69 0 520.83 313.69 46045 +1943 96 16.8 10.8 15.15 0.1 426.27 244.05 46246 +1943 97 17.89 11.89 16.24 0.03 453.69 243.45 46446 +1943 98 18.04 12.04 16.39 0 457.57 326.1 46647 +1943 99 16.91 10.91 15.26 0 428.97 330.98 46846 +1943 100 16.85 10.85 15.2 0 427.5 333.03 47045 +1943 101 18.46 12.46 16.81 0.02 468.61 247.98 47243 +1943 102 20.54 14.54 18.89 0 526.67 326.31 47441 +1943 103 16.88 10.88 15.23 0 428.23 338.49 47638 +1943 104 19.15 13.15 17.5 0 487.23 334.04 47834 +1943 105 22.74 16.74 21.09 0 594.62 324.07 48030 +1943 106 17.04 11.04 15.39 0 432.18 343.21 48225 +1943 107 15.68 9.68 14.03 0.22 399.59 261.2 48419 +1943 108 16.76 10.76 15.11 0.93 425.29 260.46 48612 +1943 109 12.81 6.81 11.16 1.12 337.62 268.5 48804 +1943 110 12.63 6.63 10.98 0.24 334.03 269.83 48995 +1943 111 5.37 -0.63 3.72 0 213.82 373.27 49185 +1943 112 5.4 -0.6 3.75 0 214.22 374.79 49374 +1943 113 5.01 -0.99 3.36 0 208.98 376.67 49561 +1943 114 5.77 -0.23 4.12 0 219.3 377.21 49748 +1943 115 7.38 1.38 5.73 0 242.61 376.39 49933 +1943 116 12.04 6.04 10.39 0 322.47 369.55 50117 +1943 117 12.74 6.74 11.09 0 336.22 369.43 50300 +1943 118 11.73 5.73 10.08 0 316.53 372.81 50481 +1943 119 11.65 5.65 10 0.03 315.02 280.63 50661 +1943 120 12.65 6.65 11 0.01 334.42 279.99 50840 +1943 121 11.77 5.77 10.12 0 317.3 376.26 51016 +1943 122 10.32 4.32 8.67 0.01 290.71 285.18 51191 +1943 123 9.03 3.03 7.38 1.7 268.69 287.66 51365 +1943 124 12.08 6.08 10.43 0 323.24 378.97 51536 +1943 125 12.04 6.04 10.39 0 322.47 380.05 51706 +1943 126 15.9 9.9 14.25 0 404.71 372.16 51874 +1943 127 14.83 8.83 13.18 0 380.3 375.73 52039 +1943 128 18.75 12.75 17.1 0 476.36 366.01 52203 +1943 129 18.12 12.12 16.47 0.51 459.66 276.56 52365 +1943 130 18.14 12.14 16.49 0.65 460.18 277.1 52524 +1943 131 21.98 15.98 20.33 0 570.35 357.5 52681 +1943 132 21.94 15.94 20.29 0.15 569.1 268.83 52836 +1943 133 21.33 15.33 19.68 0.3 550.27 271 52989 +1943 134 20.64 14.64 18.99 0 529.61 364.44 53138 +1943 135 16.41 10.41 14.76 0 416.81 378.06 53286 +1943 136 16.09 10.09 14.44 0.88 409.18 284.66 53430 +1943 137 17.18 11.18 15.53 0.21 435.66 282.95 53572 +1943 138 16.74 10.74 15.09 0.1 424.8 284.33 53711 +1943 139 15.65 9.65 14 0 398.89 382.71 53848 +1943 140 16.7 10.7 15.05 0.04 423.83 285.29 53981 +1943 141 17.69 11.69 16.04 0 448.55 378 54111 +1943 142 17.79 11.79 16.14 0.16 451.11 283.66 54238 +1943 143 14.76 8.76 13.11 0.2 378.75 290.2 54362 +1943 144 13.6 7.6 11.95 0.35 353.8 292.64 54483 +1943 145 12.47 6.47 10.82 0.97 330.86 294.89 54600 +1943 146 17.55 11.55 15.9 0.66 444.98 285.57 54714 +1943 147 16.2 10.2 14.55 0 411.79 385.03 54824 +1943 148 22.92 16.92 21.27 0 600.49 363.25 54931 +1943 149 16.67 10.67 15.02 0.06 423.1 288.34 55034 +1943 150 16.36 10.36 14.71 0.4 415.61 289.23 55134 +1943 151 18.8 12.8 17.15 0 477.71 378.87 55229 +1943 152 23.55 17.55 21.9 0.53 621.44 271.36 55321 +1943 153 24.24 18.24 22.59 0.15 645.09 269.36 55409 +1943 154 20.49 14.49 18.84 0 525.2 373.95 55492 +1943 155 23.57 17.57 21.92 0.08 622.12 271.84 55572 +1943 156 25.89 19.89 24.24 0.44 704.76 264.41 55648 +1943 157 22.2 16.2 20.55 0.92 577.29 276.28 55719 +1943 158 24.59 18.59 22.94 0 657.38 358.76 55786 +1943 159 20.11 14.11 18.46 0.97 514.19 282.25 55849 +1943 160 14.79 8.79 13.14 0.86 379.41 294.09 55908 +1943 161 17.66 11.66 16.01 0.1 447.78 288.28 55962 +1943 162 20.91 14.91 19.26 0.83 537.61 280.39 56011 +1943 163 17.77 11.77 16.12 1.08 450.6 288.24 56056 +1943 164 11.18 5.18 9.53 0.77 306.24 300.47 56097 +1943 165 18.11 12.11 16.46 0.06 459.4 287.58 56133 +1943 166 18.23 12.23 16.58 0 462.54 383.15 56165 +1943 167 19.43 13.43 17.78 0 494.97 379.3 56192 +1943 168 20.31 14.31 18.66 0.43 519.96 282.31 56214 +1943 169 17.84 11.84 16.19 0.16 452.4 288.28 56231 +1943 170 16.24 10.24 14.59 0.33 412.74 291.71 56244 +1943 171 19.19 13.19 17.54 0 488.33 380.23 56252 +1943 172 19.49 13.49 17.84 0 496.64 379.24 56256 +1943 173 17.88 11.88 16.23 0.01 453.43 288.21 56255 +1943 174 19.21 13.21 17.56 0.36 488.88 285.04 56249 +1943 175 16.07 10.07 14.42 2.16 408.71 291.99 56238 +1943 176 17.59 11.59 15.94 2.23 446 288.75 56223 +1943 177 18.51 12.51 16.86 0.66 469.94 286.58 56203 +1943 178 19.28 13.28 17.63 0.18 490.81 284.76 56179 +1943 179 19.94 13.94 18.29 0.11 509.33 283.04 56150 +1943 180 19.67 13.67 18.02 0.41 501.68 283.63 56116 +1943 181 18.69 12.69 17.04 0.08 474.75 285.95 56078 +1943 182 19.11 13.11 17.46 0.42 486.14 284.84 56035 +1943 183 20.92 14.92 19.27 0.32 537.91 280.11 55987 +1943 184 23.41 17.41 21.76 0.01 616.73 272.86 55935 +1943 185 24.01 18.01 22.36 0.41 637.13 270.92 55879 +1943 186 24.37 18.37 22.72 0.07 649.63 269.58 55818 +1943 187 20.8 14.8 19.15 0.28 534.34 279.92 55753 +1943 188 20.73 14.73 19.08 1.39 532.26 279.91 55684 +1943 189 20.53 14.53 18.88 0.21 526.38 280.3 55611 +1943 190 18.77 12.77 17.12 0 476.9 379.18 55533 +1943 191 20.21 14.21 18.56 0 517.07 374.19 55451 +1943 192 23.73 17.73 22.08 0 627.54 360.62 55366 +1943 193 22.55 16.55 20.9 1.61 588.47 273.82 55276 +1943 194 23.15 17.15 21.5 0.09 608.07 271.88 55182 +1943 195 23.41 17.41 21.76 0.01 616.73 270.89 55085 +1943 196 21.4 15.4 19.75 0 552.4 368.53 54984 +1943 197 22.04 16.04 20.39 0 572.24 365.71 54879 +1943 198 25.15 19.15 23.5 0.21 677.45 264.38 54770 +1943 199 20.01 14.01 18.36 0.21 511.32 279.11 54658 +1943 200 17.88 11.88 16.23 0.18 453.43 283.85 54542 +1943 201 17.12 11.12 15.47 0 434.17 380.19 54423 +1943 202 19.77 13.77 18.12 0.65 504.5 278.63 54301 +1943 203 21.71 15.71 20.06 1.02 561.93 273.19 54176 +1943 204 25.23 19.23 23.58 0 680.36 349.46 54047 +1943 205 25.12 19.12 23.47 0 676.36 349.45 53915 +1943 206 26.84 20.84 25.19 0.19 741.19 255.7 53780 +1943 207 25.9 19.9 24.25 0 705.14 344.75 53643 +1943 208 27.09 21.09 25.44 0.05 751.04 253.85 53502 +1943 209 25.27 19.27 23.62 0 681.82 346.36 53359 +1943 210 27.25 21.25 25.6 0 757.39 336.48 53213 +1943 211 26.17 20.17 24.52 0 715.34 340.92 53064 +1943 212 21.96 15.96 20.31 1.49 569.72 268.23 52913 +1943 213 26.1 20.1 24.45 0 712.68 339.77 52760 +1943 214 27.21 21.21 25.56 0 755.8 333.78 52604 +1943 215 26.44 20.44 24.79 0 725.66 336.84 52445 +1943 216 27.06 21.06 25.41 0 749.85 332.91 52285 +1943 217 27.95 21.95 26.3 0 785.75 327.67 52122 +1943 218 27.5 21.5 25.85 0.08 767.42 246.87 51958 +1943 219 25.77 19.77 24.12 0 700.27 336.32 51791 +1943 220 27.86 21.86 26.21 0.6 782.06 244.13 51622 +1943 221 23.82 17.82 22.17 0 630.61 342.75 51451 +1943 222 23.92 17.92 22.27 0 634.03 341.33 51279 +1943 223 23.65 17.65 22 0 624.82 341.3 51105 +1943 224 21.74 15.74 20.09 1.89 562.86 260.58 50929 +1943 225 25.74 19.74 24.09 0 699.15 330.42 50751 +1943 226 31.11 25.11 29.46 0.16 925.2 226.41 50572 +1943 227 28.63 22.63 26.98 0.07 814.16 235.76 50392 +1943 228 21.34 15.34 19.69 0 550.57 344.12 50210 +1943 229 19.31 13.31 17.66 0.39 491.64 262.11 50026 +1943 230 17.92 11.92 16.27 0 454.46 352.27 49842 +1943 231 19.5 13.5 17.85 0.03 496.92 259.61 49656 +1943 232 22 16 20.35 0.02 570.98 252.42 49469 +1943 233 20.75 14.75 19.1 0.18 532.86 254.56 49280 +1943 234 24 18 22.35 0.11 636.78 244.77 49091 +1943 235 22.97 16.97 21.32 0 602.13 328.83 48900 +1943 236 24.3 18.3 22.65 0 647.19 322.37 48709 +1943 237 24.28 18.28 22.63 0.04 646.49 240.65 48516 +1943 238 25.22 19.22 23.57 0 679.99 315.47 48323 +1943 239 25.81 19.81 24.16 0.56 701.77 233.68 48128 +1943 240 25.59 19.59 23.94 0.01 693.58 233.13 47933 +1943 241 25.65 19.65 24 0.24 695.8 231.72 47737 +1943 242 25.93 19.93 24.28 0.12 706.27 229.6 47541 +1943 243 24.89 18.89 23.24 0 668.07 308.64 47343 +1943 244 16.17 10.17 14.52 1.08 411.08 250.69 47145 +1943 245 18.71 12.71 17.06 0 475.29 325.8 46947 +1943 246 19.68 13.68 18.03 0.01 501.96 240.8 46747 +1943 247 17.07 11.07 15.42 0 432.93 326.32 46547 +1943 248 16.93 10.93 15.28 0.22 429.47 243.53 46347 +1943 249 22.59 16.59 20.94 0.23 589.76 229.58 46146 +1943 250 24.61 18.61 22.96 0.06 658.09 222.72 45945 +1943 251 23.54 17.54 21.89 0 621.1 298.89 45743 +1943 252 20.19 14.19 18.54 0 516.49 307.65 45541 +1943 253 20.51 14.51 18.86 0 525.79 304.63 45339 +1943 254 18.49 12.49 16.84 0 469.41 308.18 45136 +1943 255 18.75 12.75 17.1 0 476.36 305.26 44933 +1943 256 19.63 13.63 17.98 0.43 500.56 225.47 44730 +1943 257 19.15 13.15 17.5 0.58 487.23 224.86 44527 +1943 258 21.29 15.29 19.64 0.02 549.05 218.55 44323 +1943 259 19.11 13.11 17.46 0.32 486.14 221.41 44119 +1943 260 17.4 11.4 15.75 1.59 441.18 222.87 43915 +1943 261 19.77 13.77 18.12 0.24 504.5 216.52 43711 +1943 262 20.82 14.82 19.17 0 534.93 283.43 43507 +1943 263 24.03 18.03 22.38 0 637.82 270.98 43303 +1943 264 22.14 16.14 20.49 0.03 575.39 205.99 43099 +1943 265 25.2 19.2 23.55 0 679.27 262.24 42894 +1943 266 20.48 14.48 18.83 0 524.91 274.8 42690 +1943 267 13.15 7.15 11.5 0 344.5 288.52 42486 +1943 268 15.71 9.71 14.06 0.22 400.28 210.78 42282 +1943 269 18.69 12.69 17.04 0 474.75 271.87 42078 +1943 270 24.81 18.81 23.16 0.05 665.2 188.71 41875 +1943 271 23.64 17.64 21.99 0 624.48 253.01 41671 +1943 272 23.14 17.14 21.49 0 607.74 251.99 41468 +1943 273 25.3 19.3 23.65 0.24 682.91 181.97 41265 +1943 274 20.96 14.96 19.31 0 539.11 253.28 41062 +1943 275 18.52 12.52 16.87 0 470.21 256.66 40860 +1943 276 18.72 12.72 17.07 0 475.56 253.57 40658 +1943 277 18.81 12.81 17.16 0 477.98 250.77 40456 +1943 278 16.51 10.51 14.86 0.01 419.22 189.69 40255 +1943 279 18.14 12.14 16.49 0 460.18 246.75 40054 +1943 280 15.53 9.53 13.88 0.52 396.12 187.06 39854 +1943 281 17.98 11.98 16.33 0.15 456.02 181.39 39654 +1943 282 18.01 12.01 16.36 0 456.79 239.13 39455 +1943 283 20.48 14.48 18.83 0 524.91 230.8 39256 +1943 284 21.78 15.78 20.13 0 564.11 224.66 39058 +1943 285 16.53 10.53 14.88 0 419.7 233.8 38861 +1943 286 14.3 8.3 12.65 0 368.68 235.02 38664 +1943 287 14.86 8.86 13.21 0 380.96 231.18 38468 +1943 288 16.32 10.32 14.67 0 414.65 225.87 38273 +1943 289 17.36 11.36 15.71 0 440.17 221.35 38079 +1943 290 14.97 8.97 13.32 0 383.42 222.82 37885 +1943 291 15.09 9.09 13.44 0 386.11 219.96 37693 +1943 292 16.12 10.12 14.47 0 409.89 215.57 37501 +1943 293 15.73 9.73 14.08 0 400.75 213.57 37311 +1943 294 13.78 7.78 12.13 0.14 357.57 160.36 37121 +1943 295 12.62 6.62 10.97 0.12 333.83 159.49 36933 +1943 296 11.97 5.97 10.32 0.03 321.12 158.22 36745 +1943 297 10.89 4.89 9.24 0 300.92 209.6 36560 +1943 298 12.89 6.89 11.24 0 339.23 204.43 36375 +1943 299 14.55 8.55 12.9 0 374.12 199.31 36191 +1943 300 11.7 5.7 10.05 0 315.97 200.56 36009 +1943 301 9.54 3.54 7.89 0 277.21 200.55 35829 +1943 302 8.35 2.35 6.7 0.04 257.66 149.36 35650 +1943 303 13.31 7.31 11.66 0 347.78 190.85 35472 +1943 304 14.62 8.62 12.97 0 375.66 186.63 35296 +1943 305 10.11 4.11 8.46 0 287.02 189.53 35122 +1943 306 7.47 1.47 5.82 0 243.98 189.88 34950 +1943 307 8.3 2.3 6.65 0.02 256.87 139.94 34779 +1943 308 8.66 2.66 7.01 0 262.64 183.64 34610 +1943 309 9.27 3.27 7.62 0 272.67 180.73 34444 +1943 310 9.05 3.05 7.4 0.01 269.02 133.88 34279 +1943 311 6.28 0.28 4.63 0 226.47 178.75 34116 +1943 312 6.63 0.63 4.98 0.36 231.5 131.86 33956 +1943 313 5.48 -0.52 3.83 1.65 215.31 130.93 33797 +1943 314 4.92 -1.08 3.27 0.92 207.79 129.76 33641 +1943 315 4.35 -1.65 2.7 0.16 200.36 128.14 33488 +1943 316 3.24 -2.76 1.59 0 186.56 169.37 33337 +1943 317 4.59 -1.41 2.94 0.65 203.46 124.7 33188 +1943 318 4.32 -1.68 2.67 0 199.98 164.09 33042 +1943 319 5.16 -0.84 3.51 0 210.98 161.81 32899 +1943 320 9.23 3.23 7.58 0 272 156.73 32758 +1943 321 6.59 0.59 4.94 0 230.92 156.79 32620 +1943 322 5.8 -0.2 4.15 0 219.72 155.54 32486 +1943 323 6.79 0.79 5.14 0.33 233.83 114.9 32354 +1943 324 6.99 0.99 5.34 0.74 236.78 113.25 32225 +1943 325 7.45 1.45 5.8 0 243.67 148.93 32100 +1943 326 5.51 -0.49 3.86 0.53 215.72 111.65 31977 +1943 327 9.21 3.21 7.56 1.88 271.67 108.18 31858 +1943 328 7.85 1.85 6.2 0.35 249.81 107.53 31743 +1943 329 9.47 3.47 7.82 0 276.03 140.59 31631 +1943 330 6.41 0.41 4.76 0 228.32 141.5 31522 +1943 331 8.01 2.01 6.36 0 252.3 139.02 31417 +1943 332 4.62 -1.38 2.97 0.69 203.85 104.77 31316 +1943 333 3.92 -2.08 2.27 0 194.91 139.02 31218 +1943 334 4.73 -1.27 3.08 0 205.29 137.44 31125 +1943 335 1.87 -4.13 0.22 0.01 170.65 103.37 31035 +1943 336 4.94 -1.06 3.29 0 208.05 135.06 30949 +1943 337 6.96 0.96 5.31 0 236.34 132.1 30867 +1943 338 6.41 0.41 4.76 0.58 228.32 98.65 30790 +1943 339 0.74 -5.26 -0.91 0.21 158.43 100.4 30716 +1943 340 0.52 -5.48 -1.13 0 156.14 133.22 30647 +1943 341 0.92 -5.08 -0.73 1.15 160.33 99.08 30582 +1943 342 -2.41 -8.41 -4.06 0.04 128.27 142.89 30521 +1943 343 -2.96 -8.96 -4.61 0.17 123.55 143.03 30465 +1943 344 -1.74 -7.74 -3.39 0 134.23 174.53 30413 +1943 345 0.67 -5.33 -0.98 0.03 157.7 140.83 30366 +1943 346 0.69 -5.31 -0.96 0 157.91 172.5 30323 +1943 347 3.02 -2.98 1.37 0.03 183.92 138.76 30284 +1943 348 2.72 -3.28 1.07 0 180.38 126.58 30251 +1943 349 1.35 -4.65 -0.3 0.54 164.93 95.14 30221 +1943 350 3.06 -2.94 1.41 1.01 184.4 94.27 30197 +1943 351 2.64 -3.36 0.99 0.06 179.44 94.26 30177 +1943 352 4.04 -1.96 2.39 0 196.42 124.86 30162 +1943 353 0.69 -5.31 -0.96 0 157.91 126.43 30151 +1943 354 4.24 -1.76 2.59 0 198.96 124.66 30145 +1943 355 8.34 2.34 6.69 0.03 257.5 91.56 30144 +1943 356 7.27 1.27 5.62 0.18 240.96 92.13 30147 +1943 357 9.64 3.64 7.99 0.2 278.91 90.89 30156 +1943 358 5.67 -0.33 4.02 0 217.92 124 30169 +1943 359 3.86 -2.14 2.21 0 194.16 125.15 30186 +1943 360 8.16 2.16 6.51 0 254.65 122.85 30208 +1943 361 8.33 2.33 6.68 0 257.34 123.05 30235 +1943 362 8.8 2.8 7.15 0.28 264.91 92.36 30267 +1943 363 8.3 2.3 6.65 0 256.87 124.09 30303 +1943 364 7.97 1.97 6.32 0.83 251.67 93.53 30343 +1943 365 5.07 -0.93 3.42 0 209.78 127.15 30388 +1944 1 2.24 -3.76 0.59 0 174.83 129.57 30438 +1944 2 4.69 -1.31 3.04 0 204.76 128.99 30492 +1944 3 8.46 2.46 6.81 0 259.42 127.45 30551 +1944 4 6.84 0.84 5.19 0 234.57 129.5 30614 +1944 5 10.28 4.28 8.63 0.15 290 95.66 30681 +1944 6 6.97 0.97 5.32 0.06 236.48 98.2 30752 +1944 7 3.4 -2.6 1.75 0.15 188.49 100.43 30828 +1944 8 6.06 0.06 4.41 0.52 223.35 100.35 30907 +1944 9 1.24 -4.76 -0.41 0 163.74 137.75 30991 +1944 10 7.77 1.77 6.12 0 248.57 135.15 31079 +1944 11 6.4 0.4 4.75 0 228.18 137.09 31171 +1944 12 6.72 0.72 5.07 0.08 232.81 103.4 31266 +1944 13 6.22 0.22 4.57 0.02 225.61 104.87 31366 +1944 14 4.14 -1.86 2.49 0.13 197.68 106.96 31469 +1944 15 5.3 -0.7 3.65 0 212.87 143.34 31575 +1944 16 3.77 -2.23 2.12 0 193.04 145.57 31686 +1944 17 2.74 -3.26 1.09 0 180.61 147.84 31800 +1944 18 3.1 -2.9 1.45 0 184.88 149.54 31917 +1944 19 5.28 -0.72 3.63 0 212.6 150.12 32038 +1944 20 11.61 5.61 9.96 0 314.26 146.48 32161 +1944 21 8.59 2.59 6.94 0 261.51 151.21 32289 +1944 22 11.34 5.34 9.69 0 309.2 150.41 32419 +1944 23 8.01 2.01 6.36 0.32 252.3 116.37 32552 +1944 24 4.24 -1.76 2.59 0 198.96 159.96 32688 +1944 25 1.95 -4.05 0.3 0 171.55 163.23 32827 +1944 26 0.23 -5.77 -1.42 0 153.17 166.09 32969 +1944 27 4.11 -1.89 2.46 0 197.3 165.88 33114 +1944 28 2.16 -3.84 0.51 0 173.92 169.3 33261 +1944 29 -2.1 -8.1 -3.75 0 131 173.87 33411 +1944 30 -1.22 -7.22 -2.87 0 139.02 175.74 33564 +1944 31 3.87 -2.13 2.22 0 194.29 175.24 33718 +1944 32 4.07 -1.93 2.42 0.05 196.8 132.92 33875 +1944 33 1.91 -4.09 0.26 0 171.1 181.24 34035 +1944 34 2.58 -3.42 0.93 0 178.74 183.05 34196 +1944 35 4.56 -1.44 2.91 0 203.07 183.85 34360 +1944 36 0.68 -5.32 -0.97 0.82 157.8 141.66 34526 +1944 37 3.35 -2.65 1.7 0.16 187.89 142.24 34694 +1944 38 -0.87 -6.87 -2.52 0.38 142.33 185.12 34863 +1944 39 -0.33 -6.33 -1.98 0.58 147.56 188.28 35035 +1944 40 -1.51 -7.51 -3.16 0 136.33 240.67 35208 +1944 41 -0.09 -6.09 -1.74 0 149.94 242.37 35383 +1944 42 -3.3 -9.3 -4.95 0 120.7 246.39 35560 +1944 43 2.19 -3.81 0.54 0 174.26 245.63 35738 +1944 44 6.53 0.53 4.88 0 230.05 243.88 35918 +1944 45 6.36 0.36 4.71 0 227.61 245.74 36099 +1944 46 4.12 -1.88 2.47 0 197.43 249.66 36282 +1944 47 4 -2 2.35 0 195.92 215.8 36466 +1944 48 2.17 -3.83 0.52 0 174.03 219.97 36652 +1944 49 3.59 -2.41 1.94 0.05 190.82 166.29 36838 +1944 50 0.98 -5.02 -0.67 0 160.96 226.28 37026 +1944 51 4.18 -1.82 2.53 0 198.19 226.9 37215 +1944 52 2.01 -3.99 0.36 0.78 172.22 173.56 37405 +1944 53 -0.81 -6.81 -2.46 0.06 142.9 212.46 37596 +1944 54 3.78 -2.22 2.13 0 193.17 235.81 37788 +1944 55 4.62 -1.38 2.97 0.05 203.85 178.58 37981 +1944 56 2 -4 0.35 0.26 172.11 182.2 38175 +1944 57 3.3 -2.7 1.65 0.52 187.28 183.62 38370 +1944 58 3.87 -2.13 2.22 0 194.29 247.3 38565 +1944 59 2.04 -3.96 0.39 0 172.56 251.51 38761 +1944 60 4.72 -1.28 3.07 0.01 205.16 189.12 38958 +1944 61 2.22 -3.78 0.57 0.09 174.6 192.94 39156 +1944 62 1.33 -4.67 -0.32 0.09 164.72 195.58 39355 +1944 63 1.02 -4.98 -0.63 0.4 161.39 198.03 39553 +1944 64 1.62 -4.38 -0.03 0.97 167.88 199.9 39753 +1944 65 2.25 -3.75 0.6 0.01 174.94 201.72 39953 +1944 66 5.12 -0.88 3.47 0 210.45 269.13 40154 +1944 67 6.34 0.34 4.69 0 227.32 270.78 40355 +1944 68 5.58 -0.42 3.93 0 216.68 274.47 40556 +1944 69 9.19 3.19 7.54 0.16 271.34 204.64 40758 +1944 70 8.91 2.91 7.26 0.03 266.71 207.04 40960 +1944 71 6.25 0.25 4.6 0.06 226.04 211.63 41163 +1944 72 9.09 3.09 7.44 0 269.68 281.52 41366 +1944 73 13.78 7.78 12.13 0 357.57 276.84 41569 +1944 74 13.37 7.37 11.72 0.1 349.02 210.19 41772 +1944 75 9.02 3.02 7.37 0 268.52 289.72 41976 +1944 76 6.44 0.44 4.79 0.02 228.76 221.71 42179 +1944 77 7.97 1.97 6.32 0.19 251.67 222.26 42383 +1944 78 6.71 0.71 5.06 0.65 232.66 225.45 42587 +1944 79 4.26 -1.74 2.61 0 199.21 306.07 42791 +1944 80 3.05 -2.95 1.4 0.22 184.28 232.39 42996 +1944 81 0.24 -5.76 -1.41 2.72 153.27 236.21 43200 +1944 82 0.2 -5.8 -1.45 0.34 152.86 238.27 43404 +1944 83 1.02 -4.98 -0.63 0.41 161.39 239.67 43608 +1944 84 1.38 -4.62 -0.27 0 165.26 321.84 43812 +1944 85 3.12 -2.88 1.47 0 185.11 322.75 44016 +1944 86 0.54 -5.46 -1.11 0 156.35 327.58 44220 +1944 87 1.35 -4.65 -0.3 0 164.93 329.46 44424 +1944 88 2.77 -3.23 1.12 0 180.96 330.53 44627 +1944 89 2.35 -3.65 0.7 0 176.09 333.26 44831 +1944 90 4.31 -1.69 2.66 0 199.85 333.65 45034 +1944 91 16.05 10.05 14.4 0 408.24 316.62 45237 +1944 92 15.31 9.31 13.66 0 391.09 320.48 45439 +1944 93 14 8 12.35 0.04 362.24 244.09 45642 +1944 94 12.12 6.12 10.47 0 324.02 331.25 45843 +1944 95 10.97 4.97 9.32 0 302.38 335.44 46045 +1944 96 13.25 7.25 11.6 0 346.55 333.3 46246 +1944 97 12.32 6.32 10.67 0 327.91 337.15 46446 +1944 98 17.13 11.13 15.48 0 434.42 328.47 46647 +1944 99 16.49 10.49 14.84 0 418.74 332.03 46846 +1944 100 19.63 13.63 17.98 0.04 500.56 244.07 47045 +1944 101 18.85 12.85 17.2 0.12 479.06 247.16 47243 +1944 102 17.06 11.06 15.41 0 432.68 336.23 47441 +1944 103 13.25 7.25 11.6 0 346.55 346.84 47638 +1944 104 15.74 9.74 14.09 0 400.98 343.1 47834 +1944 105 13.81 7.81 12.16 0 358.21 349.25 48030 +1944 106 11.79 5.79 10.14 0 317.68 354.99 48225 +1944 107 10.43 4.43 8.78 0.05 292.66 269.37 48419 +1944 108 13.31 7.31 11.66 0.16 347.78 266.51 48612 +1944 109 11.51 5.51 9.86 0.09 312.38 270.42 48804 +1944 110 10.1 4.1 8.45 0 286.85 364.55 48995 +1944 111 10.15 4.15 8.5 0.02 287.72 274.52 49185 +1944 112 5.65 -0.35 4 0.42 217.64 280.84 49374 +1944 113 8.96 2.96 7.31 0 267.53 370.95 49561 +1944 114 12.19 6.19 10.54 0.86 325.37 274.94 49748 +1944 115 10.82 4.82 9.17 0.47 299.65 278 49933 +1944 116 15.85 9.85 14.2 0.08 403.54 270.74 50117 +1944 117 14.5 8.5 12.85 0.15 373.03 274.16 50300 +1944 118 11.18 5.18 9.53 0.39 306.24 280.41 50481 +1944 119 15.65 9.65 14 0 398.89 365.26 50661 +1944 120 13.79 7.79 12.14 0 357.78 370.85 50840 +1944 121 13.92 7.92 12.27 0 360.53 371.68 51016 +1944 122 13.5 7.5 11.85 0 351.71 373.82 51191 +1944 123 11.38 5.38 9.73 1.32 309.95 284.46 51365 +1944 124 11.41 5.41 9.76 1.97 310.51 285.24 51536 +1944 125 13.33 7.33 11.68 0.41 348.2 282.98 51706 +1944 126 13.56 7.56 11.91 0 352.96 377.8 51874 +1944 127 16 10 14.35 0 407.06 372.79 52039 +1944 128 16.78 10.78 15.13 0.34 425.78 278.78 52203 +1944 129 15.52 9.52 13.87 0 395.89 375.87 52365 +1944 130 17.96 11.96 16.31 0 455.5 369.99 52524 +1944 131 18.16 12.16 16.51 0.02 460.7 277.64 52681 +1944 132 16.09 10.09 14.44 0.29 409.18 282.6 52836 +1944 133 16.56 10.56 14.91 0.29 420.43 282.19 52989 +1944 134 21.79 15.79 20.14 0 564.42 360.36 53138 +1944 135 21.37 15.37 19.72 0.07 551.49 271.92 53286 +1944 136 17.97 11.97 16.32 0 455.76 374.28 53430 +1944 137 13.27 7.27 11.62 0.08 346.96 290.36 53572 +1944 138 13.97 7.97 12.32 0 361.6 386.16 53711 +1944 139 15.14 9.14 13.49 0 387.24 384.01 53848 +1944 140 15.9 9.9 14.25 0 404.71 382.54 53981 +1944 141 16.58 10.58 14.93 1.07 420.91 285.86 54111 +1944 142 14.3 8.3 12.65 1.62 368.68 290.64 54238 +1944 143 15.48 9.48 13.83 0 394.97 385.12 54362 +1944 144 20.81 14.81 19.16 0.06 534.64 277.11 54483 +1944 145 19.39 13.39 17.74 0 493.86 374.73 54600 +1944 146 14.57 8.57 12.92 0.99 374.56 291.56 54714 +1944 147 12.94 6.94 11.29 0 340.24 393.03 54824 +1944 148 13.92 7.92 12.27 0 360.53 391.18 54931 +1944 149 16.5 10.5 14.85 0 418.98 384.92 55034 +1944 150 16.97 10.97 15.32 0 430.45 383.94 55134 +1944 151 16.1 10.1 14.45 0 409.42 386.74 55229 +1944 152 22.45 16.45 20.8 0 585.26 366.2 55321 +1944 153 21.23 15.23 19.58 0.22 547.23 278.26 55409 +1944 154 22.24 16.24 20.59 0.41 578.56 275.67 55492 +1944 155 23.74 17.74 22.09 0.86 627.88 271.31 55572 +1944 156 19.34 13.34 17.69 0.46 492.47 283.74 55648 +1944 157 17.85 11.85 16.2 1.12 452.65 287.35 55719 +1944 158 17.03 11.03 15.38 0.68 431.94 289.28 55786 +1944 159 14.07 8.07 12.42 0 363.73 393.69 55849 +1944 160 17.1 11.1 15.45 0.18 433.67 289.45 55908 +1944 161 17.8 11.8 16.15 2 451.37 287.97 55962 +1944 162 21.67 15.67 20.02 0.02 560.7 278.32 56011 +1944 163 18.68 12.68 17.03 0 474.48 381.54 56056 +1944 164 17.01 11.01 15.36 0.11 431.44 289.94 56097 +1944 165 15.47 9.47 13.82 0.14 394.74 293.16 56133 +1944 166 16.86 10.86 15.21 0 427.74 387.18 56165 +1944 167 23.1 17.1 21.45 0 606.42 365.92 56192 +1944 168 22.39 16.39 20.74 0 583.34 368.81 56214 +1944 169 23.48 17.48 21.83 0 619.08 364.46 56231 +1944 170 22.81 16.81 21.16 1.18 596.9 275.38 56244 +1944 171 21.01 15.01 19.36 0.26 540.6 280.52 56252 +1944 172 17.76 11.76 16.11 1.65 450.34 288.5 56256 +1944 173 18.6 12.6 16.95 0 472.34 382.08 56255 +1944 174 22.25 16.25 20.6 0 578.87 369.31 56249 +1944 175 20.82 14.82 19.17 1.46 534.93 280.92 56238 +1944 176 18.58 12.58 16.93 0.03 471.8 286.49 56223 +1944 177 21.02 15.02 19.37 0.37 540.9 280.28 56203 +1944 178 17.94 11.94 16.29 0.76 454.98 287.91 56179 +1944 179 19.2 13.2 17.55 0.34 488.61 284.88 56150 +1944 180 18.23 12.23 16.58 0.02 462.54 287.08 56116 +1944 181 15.07 9.07 13.42 0.14 385.66 293.64 56078 +1944 182 22.29 16.29 20.64 1.5 580.15 276.44 56035 +1944 183 22.77 16.77 21.12 0 595.59 366.53 55987 +1944 184 24.27 18.27 22.62 0 646.14 360.2 55935 +1944 185 24.79 18.79 23.14 0.58 664.49 268.39 55879 +1944 186 21.99 15.99 20.34 0.16 570.66 276.8 55818 +1944 187 24.42 18.42 22.77 0 651.39 359.05 55753 +1944 188 23.77 17.77 22.12 0 628.9 361.55 55684 +1944 189 25.21 19.21 23.56 0 679.63 355.12 55611 +1944 190 22.99 16.99 21.34 0.62 602.79 273.14 55533 +1944 191 23.3 17.3 21.65 0 613.06 362.68 55451 +1944 192 25.16 19.16 23.51 0 677.81 354.44 55366 +1944 193 27.15 21.15 25.5 0.02 753.41 258.56 55276 +1944 194 26.85 20.85 25.2 1.14 741.58 259.52 55182 +1944 195 22.39 16.39 20.74 0.25 583.34 273.92 55085 +1944 196 21.26 15.26 19.61 0 548.14 369.03 54984 +1944 197 21.82 15.82 20.17 0.01 565.35 274.9 54879 +1944 198 19.87 13.87 18.22 0 507.33 372.98 54770 +1944 199 19.42 13.42 17.77 0 494.69 374.1 54658 +1944 200 22.37 16.37 20.72 0.11 582.7 272.47 54542 +1944 201 22.33 16.33 20.68 0 581.42 362.98 54423 +1944 202 22.98 16.98 21.33 0 602.46 359.9 54301 +1944 203 25.15 19.15 23.5 0 677.45 350.3 54176 +1944 204 23.76 17.76 22.11 0 628.56 355.77 54047 +1944 205 19.42 13.42 17.77 0 494.69 371.11 53915 +1944 206 17.54 11.54 15.89 0 444.72 376.28 53780 +1944 207 19.15 13.15 17.5 0.31 487.23 278.06 53643 +1944 208 18.64 12.64 16.99 0.04 473.41 278.76 53502 +1944 209 18.79 12.79 17.14 0.3 477.44 277.92 53359 +1944 210 16.65 10.65 15 0.18 422.61 282.11 53213 +1944 211 15.86 9.86 14.21 0 403.78 377.45 53064 +1944 212 17.35 11.35 15.7 0 439.92 372.6 52913 +1944 213 20.83 14.83 19.18 0.03 535.23 270.69 52760 +1944 214 20.82 14.82 19.17 0.31 534.93 270.16 52604 +1944 215 23.25 17.25 21.6 0.25 611.39 262.94 52445 +1944 216 23.76 17.76 22.11 0.7 628.56 260.66 52285 +1944 217 24.93 18.93 23.28 0 669.5 341.8 52122 +1944 218 28.73 22.73 27.08 0 818.41 322.88 51958 +1944 219 31.5 25.5 29.85 0 943.77 306.2 51791 +1944 220 31.47 25.47 29.82 0 942.33 305.56 51622 +1944 221 25.93 19.93 24.28 0 706.27 333.76 51451 +1944 222 25.22 19.22 23.57 0 679.99 335.9 51279 +1944 223 24.22 18.22 22.57 0 644.4 339.01 51105 +1944 224 21.62 15.62 19.97 0 559.15 347.87 50929 +1944 225 23.02 17.02 21.37 0 603.78 341.61 50751 +1944 226 25.39 19.39 23.74 0 686.21 330.87 50572 +1944 227 23.12 17.12 21.47 0.14 607.08 254.15 50392 +1944 228 27.88 21.88 26.23 0.15 782.88 237.75 50210 +1944 229 22.99 16.99 21.34 0.03 602.79 252.72 50026 +1944 230 19.88 13.88 18.23 0.29 507.62 259.83 49842 +1944 231 23.7 17.7 22.05 0.31 626.52 248.68 49656 +1944 232 21.16 15.16 19.51 0 545.11 339.46 49469 +1944 233 21.5 15.5 19.85 0 555.46 336.91 49280 +1944 234 23.07 17.07 21.42 0 605.43 329.91 49091 +1944 235 23.67 17.67 22.02 0 625.5 326.2 48900 +1944 236 24.04 18.04 22.39 0 638.16 323.4 48709 +1944 237 25.32 19.32 23.67 0 683.64 316.65 48516 +1944 238 23.32 17.32 21.67 0.63 613.72 242.2 48323 +1944 239 24.34 18.34 22.69 0.05 648.58 238.19 48128 +1944 240 24.1 18.1 22.45 0 640.23 316.83 47933 +1944 241 25.3 19.3 23.65 0 682.91 310.4 47737 +1944 242 27.38 21.38 25.73 0.15 762.6 224.82 47541 +1944 243 23.15 17.15 21.5 0.23 608.07 236.43 47343 +1944 244 19.43 13.43 17.78 0.14 494.97 244.18 47145 +1944 245 19.75 13.75 18.1 0.01 503.94 242.1 46947 +1944 246 22.59 16.59 20.94 0.04 589.76 233.83 46747 +1944 247 25.78 19.78 24.13 0.09 700.65 223.47 46547 +1944 248 25.16 19.16 23.51 1.5 677.81 223.98 46347 +1944 249 25.07 19.07 23.42 0 674.55 297.04 46146 +1944 250 21.95 15.95 20.3 0.88 569.41 229.77 45945 +1944 251 16.01 10.01 14.36 0.36 407.3 240.56 45743 +1944 252 14.91 8.91 13.26 0.09 382.08 240.76 45541 +1944 253 16.08 10.08 14.43 0 408.95 316.27 45339 +1944 254 15.24 9.24 13.59 0 389.5 315.99 45136 +1944 255 13.86 7.86 12.21 0 359.26 316.58 44933 +1944 256 13.9 7.9 12.25 0 360.11 314.2 44730 +1944 257 20.28 14.28 18.63 0 519.09 296.66 44527 +1944 258 18.7 12.7 17.05 0 475.02 298.69 44323 +1944 259 16.2 10.2 14.55 0.66 411.79 226.75 44119 +1944 260 17 11 15.35 0.08 431.19 223.58 43915 +1944 261 12.62 6.62 10.97 0 333.83 304.64 43711 +1944 262 16.72 10.72 15.07 0 424.32 293.95 43507 +1944 263 16.35 10.35 14.7 0 415.37 292.32 43303 +1944 264 17.83 11.83 16.18 0 452.14 286.36 43099 +1944 265 20.31 14.31 18.66 0.16 519.96 208.25 42894 +1944 266 20.88 14.88 19.23 0.64 536.72 205.26 42690 +1944 267 18.53 12.53 16.88 0.62 470.47 207.93 42486 +1944 268 13.98 7.98 12.33 0 361.81 284.42 42282 +1944 269 15.32 9.32 13.67 0.02 391.32 209.49 42078 +1944 270 15.61 9.61 13.96 0.39 397.97 207.07 41875 +1944 271 15.61 9.61 13.96 0 397.97 273.49 41671 +1944 272 20.1 14.1 18.45 0 513.9 260.55 41468 +1944 273 18.79 12.79 17.14 0.03 477.44 196.01 41265 +1944 274 13.23 7.23 11.58 0.49 346.14 202.45 41062 +1944 275 10.01 4.01 8.36 0.03 285.28 204.07 40860 +1944 276 10.44 4.44 8.79 1.06 292.83 201.56 40658 +1944 277 8.28 2.28 6.63 0.56 256.55 201.65 40456 +1944 278 10.85 4.85 9.2 0.11 300.2 196.91 40255 +1944 279 11.26 5.26 9.61 0.81 307.72 194.34 40054 +1944 280 17.71 11.71 16.06 0.78 449.06 183.81 39854 +1944 281 17.12 11.12 15.47 0.43 434.17 182.74 39654 +1944 282 13.91 7.91 12.26 2.6 360.32 185.14 39455 +1944 283 15.7 9.7 14.05 0.27 400.05 180.69 39256 +1944 284 15.82 9.82 14.17 0.36 402.84 178.29 39058 +1944 285 14.74 8.74 13.09 0.02 378.3 177.76 38861 +1944 286 15.07 9.07 13.42 0.91 385.66 175.29 38664 +1944 287 13.92 7.92 12.27 0.85 360.53 174.54 38468 +1944 288 10 4 8.35 0.75 285.11 176.61 38273 +1944 289 11.19 5.19 9.54 0.37 306.42 173.47 38079 +1944 290 13.95 7.95 12.3 0.68 361.17 168.34 37885 +1944 291 14.03 8.03 12.38 0.41 362.88 166.24 37693 +1944 292 13.97 7.97 12.32 0.54 361.6 164.32 37501 +1944 293 13.4 7.4 11.75 0.87 349.64 162.93 37311 +1944 294 13.2 7.2 11.55 0.15 345.53 161 37121 +1944 295 14.38 8.38 12.73 0 370.41 210.11 36933 +1944 296 14.54 8.54 12.89 0.66 373.9 155.48 36745 +1944 297 14.02 8.02 12.37 0.03 362.66 154.05 36560 +1944 298 15.57 9.57 13.92 0 397.04 200.47 36375 +1944 299 15.31 9.31 13.66 0 391.09 198.16 36191 +1944 300 12.71 6.71 11.06 0.93 335.62 149.45 36009 +1944 301 14.29 8.29 12.64 0 368.46 194.6 35829 +1944 302 15.3 9.3 13.65 0.44 390.86 142.91 35650 +1944 303 21.96 15.96 20.31 0 569.72 175.82 35472 +1944 304 19.27 13.27 17.62 0.13 490.54 134.24 35296 +1944 305 13.08 7.08 11.43 0 343.08 186.02 35122 +1944 306 13.26 7.26 11.61 0 346.76 183.58 34950 +1944 307 11.12 5.12 9.47 0.03 305.13 137.76 34779 +1944 308 8.4 2.4 6.75 0 258.46 183.88 34610 +1944 309 5.82 -0.18 4.17 0 219.99 183.78 34444 +1944 310 6.51 0.51 4.86 0.63 229.76 135.57 34279 +1944 311 4.15 -1.85 2.5 1.76 197.81 135.26 34116 +1944 312 -0.08 -6.08 -1.73 0 150.04 180.22 33956 +1944 313 1.47 -4.53 -0.18 0 166.24 177.21 33797 +1944 314 7.07 1.07 5.42 0 237.97 171.36 33641 +1944 315 6.35 0.35 4.7 1.34 227.47 127.05 33488 +1944 316 6.69 0.69 5.04 0.38 232.37 125.2 33337 +1944 317 6.86 0.86 5.21 0.83 234.86 123.45 33188 +1944 318 5.95 -0.05 4.3 1.51 221.81 122.21 33042 +1944 319 3 -3 1.35 1.1 183.68 122.4 32899 +1944 320 2.76 -3.24 1.11 0 180.85 161.46 32758 +1944 321 2.54 -3.46 0.89 0 178.28 159.45 32620 +1944 322 6.97 0.97 5.32 0 236.48 154.68 32486 +1944 323 6.89 0.89 5.24 0 235.3 153.12 32354 +1944 324 5.37 -0.63 3.72 0.21 213.82 114.11 32225 +1944 325 5.79 -0.21 4.14 0.44 219.58 112.6 32100 +1944 326 5.13 -0.87 3.48 0 210.58 149.12 31977 +1944 327 4.13 -1.87 2.48 0.15 197.56 110.92 31858 +1944 328 5.45 -0.55 3.8 0.03 214.9 108.81 31743 +1944 329 8.02 2.02 6.37 0.24 252.46 106.32 31631 +1944 330 12.28 6.28 10.63 0.01 327.13 102.44 31522 +1944 331 16 10 14.35 0 407.06 131.17 31417 +1944 332 14.58 8.58 12.93 0 374.78 131.27 31316 +1944 333 16.18 10.18 14.53 0.01 411.32 96.26 31218 +1944 334 14.25 8.25 12.6 0.37 367.6 97.16 31125 +1944 335 10.77 4.77 9.12 0.29 298.75 98.87 31035 +1944 336 5.19 -0.81 3.54 0.4 211.39 101.18 30949 +1944 337 1.93 -4.07 0.28 0 171.33 135.05 30867 +1944 338 5.01 -0.99 3.36 0 208.98 132.42 30790 +1944 339 3.06 -2.94 1.41 0 184.4 132.73 30716 +1944 340 2.92 -3.08 1.27 0.01 182.73 99.05 30647 +1944 341 3.54 -2.46 1.89 0.01 190.2 98.11 30582 +1944 342 1.57 -4.43 -0.08 0 167.33 131.04 30521 +1944 343 2.58 -3.42 0.93 0 178.74 129.72 30465 +1944 344 5.39 -0.61 3.74 0 214.09 127.04 30413 +1944 345 2.11 -3.89 0.46 0 173.35 128.39 30366 +1944 346 1.47 -4.53 -0.18 0 166.24 128.14 30323 +1944 347 -3.14 -9.14 -4.79 0 122.03 129.36 30284 +1944 348 1.7 -4.3 0.05 0 168.77 127.08 30251 +1944 349 0.59 -5.41 -1.06 0.07 156.87 95.4 30221 +1944 350 2.53 -3.47 0.88 1.03 178.16 94.47 30197 +1944 351 1.05 -4.95 -0.6 0.9 161.71 94.83 30177 +1944 352 3.66 -2.34 2.01 0.15 191.68 93.8 30162 +1944 353 3.86 -2.14 2.21 1.22 194.16 93.67 30151 +1944 354 5.41 -0.59 3.76 0.56 214.36 92.99 30145 +1944 355 5.22 -0.78 3.57 0.07 211.79 93.07 30144 +1944 356 5 -1 3.35 0 208.85 124.25 30147 +1944 357 4.82 -1.18 3.17 0 206.47 124.42 30156 +1944 358 5.75 -0.25 4.1 0 219.02 123.96 30169 +1944 359 1.5 -4.5 -0.15 0 166.57 126.33 30186 +1944 360 -1.47 -7.47 -3.12 0 136.7 127.93 30208 +1944 361 1.86 -4.14 0.21 0 170.54 126.86 30235 +1944 362 2.88 -3.12 1.23 0.31 182.26 95.1 30267 +1944 363 -0.21 -6.21 -1.86 0.13 148.75 140.58 30303 +1944 364 -12.01 -18.01 -13.66 0.02 64.8 143.37 30343 +1944 365 -12.68 -18.68 -14.33 0 61.64 177.14 30388 +1945 1 -7.98 -13.98 -9.63 0 86.96 177.02 30438 +1945 2 -6.47 -12.47 -8.12 0 96.81 177.31 30492 +1945 3 -4.09 -10.09 -5.74 0 114.32 177.48 30551 +1945 4 -3.25 -9.25 -4.9 0 121.12 178.04 30614 +1945 5 -0.49 -6.49 -2.14 0 145.99 177.56 30681 +1945 6 0.23 -5.77 -1.42 0.96 153.17 144.35 30752 +1945 7 -0.72 -6.72 -2.37 0 143.77 179.12 30828 +1945 8 -1.24 -7.24 -2.89 0 138.83 180.72 30907 +1945 9 -0.29 -6.29 -1.94 0.34 147.96 147.92 30991 +1945 10 1.68 -4.32 0.03 0.93 168.54 147.87 31079 +1945 11 0.58 -5.42 -1.07 0 156.76 183.9 31171 +1945 12 1.65 -4.35 0 0 168.21 184.06 31266 +1945 13 4.29 -1.71 2.64 0.38 199.59 148.29 31366 +1945 14 3.34 -2.66 1.69 0.56 187.77 107.31 31469 +1945 15 0.28 -5.72 -1.37 0 153.68 146.1 31575 +1945 16 -4.24 -10.24 -5.89 0 113.14 149.22 31686 +1945 17 -1.44 -7.44 -3.09 1.31 136.97 157.86 31800 +1945 18 -5.38 -11.38 -7.03 0.53 104.52 161.82 31917 +1945 19 -3.71 -9.71 -5.36 0 117.35 201.34 32038 +1945 20 -1.84 -7.84 -3.49 0.02 133.32 163.23 32161 +1945 21 -5.23 -11.23 -6.88 0.04 105.62 165.63 32289 +1945 22 -4.82 -10.82 -6.47 0.08 108.68 166.92 32419 +1945 23 -3.67 -9.67 -5.32 0.03 117.67 167.86 32552 +1945 24 -8.09 -14.09 -9.74 0 86.27 211.66 32688 +1945 25 -6.18 -12.18 -7.83 0.03 98.81 171.22 32827 +1945 26 -4.42 -10.42 -6.07 0 111.74 214.07 32969 +1945 27 -1.31 -7.31 -2.96 0.08 138.18 172.66 33114 +1945 28 -3.38 -9.38 -5.03 0 120.04 217.8 33261 +1945 29 -0.32 -6.32 -1.97 0 147.66 218.63 33411 +1945 30 0.55 -5.45 -1.1 0 156.45 220.18 33564 +1945 31 4.68 -1.32 3.03 0 204.63 219.24 33718 +1945 32 7.57 1.57 5.92 0.01 245.5 174.35 33875 +1945 33 5.1 -0.9 3.45 0 210.18 221.76 34035 +1945 34 7.78 1.78 6.13 0 248.73 220.65 34196 +1945 35 2.77 -3.23 1.12 0 180.96 226.09 34360 +1945 36 2.12 -3.88 0.47 0 173.47 228.58 34526 +1945 37 -0.92 -6.92 -2.57 0 141.85 232.56 34694 +1945 38 -1.61 -7.61 -3.26 0 135.41 235.48 34863 +1945 39 1.88 -4.12 0.23 0 170.77 235.75 35035 +1945 40 5.76 -0.24 4.11 0 219.16 234.7 35208 +1945 41 8.7 2.7 7.05 0 263.29 233.44 35383 +1945 42 5.86 -0.14 4.21 0 220.55 200.88 35560 +1945 43 7.68 1.68 6.03 0 247.19 201.93 35738 +1945 44 8.74 2.74 7.09 0.51 263.94 152.56 35918 +1945 45 6.12 0.12 4.47 0 224.2 208.52 36099 +1945 46 3.83 -2.17 2.18 0 193.79 213.1 36282 +1945 47 2.79 -3.21 1.14 0.02 181.2 162.53 36466 +1945 48 4.9 -1.1 3.25 0.23 207.52 163.41 36652 +1945 49 3.98 -2.02 2.33 0 195.67 221.41 36838 +1945 50 5.79 -0.21 4.14 0 219.58 222.54 37026 +1945 51 4.13 -1.87 2.48 0.08 197.56 170.21 37215 +1945 52 5.67 -0.33 4.02 0 217.92 228.44 37405 +1945 53 3.54 -2.46 1.89 0 190.2 233.24 37596 +1945 54 10.24 4.24 8.59 0 289.3 229.22 37788 +1945 55 9.51 3.51 7.86 0 276.71 233.07 37981 +1945 56 8.68 2.68 7.03 0 262.96 236.7 38175 +1945 57 11.4 5.4 9.75 0 310.32 236.13 38370 +1945 58 10.61 4.61 8.96 0.04 295.87 180.05 38565 +1945 59 6.54 0.54 4.89 0 230.2 247.5 38761 +1945 60 9.12 3.12 7.47 0.03 270.17 185.61 38958 +1945 61 12.79 6.79 11.14 0 337.22 245.32 39156 +1945 62 11.39 5.39 9.74 0 310.13 250.13 39355 +1945 63 8.59 2.59 6.94 0 261.51 256.79 39553 +1945 64 9.35 3.35 7.7 0 274.01 258.73 39753 +1945 65 11.74 5.74 10.09 0 316.72 258.27 39953 +1945 66 6.78 0.78 5.13 0.41 233.69 200.55 40154 +1945 67 7.19 1.19 5.54 0 239.76 269.84 40355 +1945 68 4.83 -1.17 3.18 0 206.6 275.23 40556 +1945 69 0.84 -5.16 -0.81 0 159.48 281.38 40758 +1945 70 4.22 -1.78 2.57 0 198.7 281.34 40960 +1945 71 6.12 0.12 4.47 0 224.2 282.31 41163 +1945 72 7.82 1.82 6.17 0 249.34 283.16 41366 +1945 73 5.92 -0.08 4.27 0 221.39 288.05 41569 +1945 74 11.33 5.33 9.68 0 309.02 283.65 41772 +1945 75 10.84 4.84 9.19 0 300.02 287.1 41976 +1945 76 11.13 5.13 9.48 0 305.31 289.26 42179 +1945 77 10.8 4.8 9.15 0 299.29 292.35 42383 +1945 78 9.43 3.43 7.78 0 275.36 297.03 42587 +1945 79 6.51 0.51 4.86 0.14 229.76 227.68 42791 +1945 80 4.74 -1.26 3.09 0.01 205.42 231.1 42996 +1945 81 7.96 1.96 6.31 0 251.52 306.89 43200 +1945 82 12.3 6.3 10.65 0 327.52 302.89 43404 +1945 83 12.52 6.52 10.87 0 331.84 304.96 43608 +1945 84 11.48 5.48 9.83 0 311.82 309.27 43812 +1945 85 14.83 8.83 13.18 0 380.3 305.46 44016 +1945 86 11.48 5.48 9.83 0 311.82 314.13 44220 +1945 87 12.32 6.32 10.67 0 327.91 315.17 44424 +1945 88 11.7 5.7 10.05 0 315.97 318.59 44627 +1945 89 16.72 10.72 15.07 0 424.32 310.56 44831 +1945 90 15.77 9.77 14.12 0 401.68 315.06 45034 +1945 91 14.66 8.66 13.01 0.6 376.54 239.77 45237 +1945 92 16.86 10.86 15.21 0.03 427.74 237.66 45439 +1945 93 18.74 12.74 17.09 0.06 476.09 235.63 45642 +1945 94 12.77 6.77 11.12 0.06 336.82 247.52 45843 +1945 95 15.87 9.87 14.22 0 404.01 325.56 46045 +1945 96 14.61 8.61 12.96 0.08 375.44 247.85 46246 +1945 97 11.75 5.75 10.1 0 316.91 338.21 46446 +1945 98 13.5 7.5 11.85 0 351.71 336.77 46647 +1945 99 15.7 9.7 14.05 0 400.05 333.92 46846 +1945 100 13.63 7.63 11.98 0 354.42 340.42 47045 +1945 101 13.32 7.32 11.67 0.09 347.99 257.23 47243 +1945 102 12.74 6.74 11.09 0 336.22 346.04 47441 +1945 103 13.91 7.91 12.26 0 360.32 345.45 47638 +1945 104 13.72 7.72 12.07 0 356.31 347.67 47834 +1945 105 12.22 6.22 10.57 0 325.96 352.51 48030 +1945 106 11.24 5.24 9.59 0 307.35 356.02 48225 +1945 107 8.32 2.32 6.67 0 257.19 362.64 48419 +1945 108 11.57 5.57 9.92 0.46 313.51 269.12 48612 +1945 109 9.89 3.89 8.24 0 283.2 363.48 48804 +1945 110 9.5 3.5 7.85 0 276.54 365.57 48995 +1945 111 12.79 6.79 11.14 0 337.22 361 49185 +1945 112 13.56 7.56 11.91 0.27 352.96 270.67 49374 +1945 113 14.75 8.75 13.1 0.52 378.52 269.66 49561 +1945 114 13.88 7.88 12.23 0 359.69 363.01 49748 +1945 115 12.51 6.51 10.86 0 331.65 367.37 49933 +1945 116 13.06 7.06 11.41 0 342.67 367.44 50117 +1945 117 17.16 11.16 15.51 0 435.17 358.85 50300 +1945 118 17.87 11.87 16.22 0 453.17 358.16 50481 +1945 119 14.78 8.78 13.13 0 379.19 367.39 50661 +1945 120 14.11 8.11 12.46 0.33 364.59 277.59 50840 +1945 121 23.65 17.65 22 0 624.82 341.97 51016 +1945 122 20.64 14.64 18.99 0 529.61 354.13 51191 +1945 123 19.61 13.61 17.96 0.01 500 268.87 51365 +1945 124 20.78 14.78 19.13 0.04 533.75 266.77 51536 +1945 125 18.91 12.91 17.26 0.34 480.69 272.02 51706 +1945 126 19.32 13.32 17.67 0 491.92 362.4 51874 +1945 127 18.69 12.69 17.04 0.06 474.75 273.91 52039 +1945 128 19.57 13.57 17.92 0.48 498.88 272.58 52203 +1945 129 20.52 14.52 18.87 0 526.08 361.14 52365 +1945 130 21.91 15.91 20.26 0.15 568.16 267.75 52524 +1945 131 21.82 15.82 20.17 0 565.35 358.09 52681 +1945 132 24.06 18.06 22.41 0.01 638.85 262.61 52836 +1945 133 20.78 14.78 19.13 0 533.75 363.27 52989 +1945 134 21.99 15.99 20.34 1.42 570.66 269.71 53138 +1945 135 24.67 18.67 23.02 0 660.22 349.55 53286 +1945 136 23.46 17.46 21.81 0 618.41 355.2 53430 +1945 137 24.88 18.88 23.23 0.01 667.71 262.43 53572 +1945 138 21.72 15.72 20.07 0.13 562.24 272.38 53711 +1945 139 19.61 13.61 17.96 0 500 371.16 53848 +1945 140 18.37 12.37 16.72 0.15 466.23 281.66 53981 +1945 141 16.77 10.77 15.12 1.48 425.54 285.47 54111 +1945 142 16.94 10.94 15.29 0.57 429.71 285.49 54238 +1945 143 14.7 8.7 13.05 0.08 377.42 290.31 54362 +1945 144 13.6 7.6 11.95 0.08 353.8 292.64 54483 +1945 145 16 10 14.35 0.03 407.06 288.53 54600 +1945 146 14.76 8.76 13.11 0.17 378.75 291.21 54714 +1945 147 16.53 10.53 14.88 0 419.7 384.14 54824 +1945 148 16.72 10.72 15.07 0 424.32 383.99 54931 +1945 149 19.17 13.17 17.52 0 487.78 376.97 55034 +1945 150 19.23 13.23 17.58 0.04 489.43 282.83 55134 +1945 151 23.92 17.92 22.27 0 634.03 360.17 55229 +1945 152 24.26 18.26 22.61 0.75 645.79 269.12 55321 +1945 153 25.8 19.8 24.15 0.32 701.39 264.14 55409 +1945 154 24.75 18.75 23.1 1.71 663.06 267.93 55492 +1945 155 20.82 14.82 19.17 0.44 534.93 279.73 55572 +1945 156 21.84 15.84 20.19 0.09 565.97 277.18 55648 +1945 157 20.44 14.44 18.79 0 523.74 374.79 55719 +1945 158 20.17 14.17 18.52 0 515.92 375.89 55786 +1945 159 16.34 10.34 14.69 0.04 415.13 290.91 55849 +1945 160 18.69 12.69 17.04 0.56 474.75 285.87 55908 +1945 161 21.82 15.82 20.17 1 565.35 277.85 55962 +1945 162 18.3 12.3 16.65 0.51 464.38 286.88 56011 +1945 163 20.44 14.44 18.79 0.02 523.74 281.79 56056 +1945 164 18.65 12.65 17 0.38 473.68 286.26 56097 +1945 165 17.55 11.55 15.9 0.05 444.98 288.84 56133 +1945 166 17.03 11.03 15.38 0 431.94 386.7 56165 +1945 167 21.24 15.24 19.59 0 547.53 373.05 56192 +1945 168 24.85 18.85 23.2 0 666.63 358.59 56214 +1945 169 24.51 18.51 22.86 0.1 654.55 270.07 56231 +1945 170 25.03 19.03 23.38 0 673.11 357.8 56244 +1945 171 20.62 14.62 18.97 0 529.02 375.41 56252 +1945 172 25.27 19.27 23.62 0 681.82 356.76 56256 +1945 173 22.55 16.55 20.9 0 588.47 368.23 56255 +1945 174 23.06 17.06 21.41 0.25 605.1 274.59 56249 +1945 175 24.58 18.58 22.93 0.14 657.03 269.78 56238 +1945 176 27.18 21.18 25.53 0 754.61 347.46 56223 +1945 177 27.5 21.5 25.85 0 767.42 345.73 56203 +1945 178 24.42 18.42 22.77 0.06 651.39 270.23 56179 +1945 179 22.28 16.28 20.63 0 579.83 368.95 56150 +1945 180 22.62 16.62 20.97 0 590.73 367.51 56116 +1945 181 25.27 19.27 23.62 0 681.82 356.25 56078 +1945 182 25.71 19.71 24.06 0.26 698.04 265.56 56035 +1945 183 24.95 18.95 23.3 0.03 670.22 268.03 55987 +1945 184 24.48 18.48 22.83 0 653.5 359.3 55935 +1945 185 28.36 22.36 26.71 0 802.78 340.46 55879 +1945 186 24.74 18.74 23.09 0.22 662.71 268.37 55818 +1945 187 26.38 20.38 24.73 0.01 723.36 262.58 55753 +1945 188 28 22 26.35 0.01 787.81 256.28 55684 +1945 189 24.97 18.97 23.32 0 670.94 356.2 55611 +1945 190 24.48 18.48 22.83 0 653.5 357.99 55533 +1945 191 24.08 18.08 22.43 0 639.54 359.45 55451 +1945 192 25.51 19.51 23.86 0.14 690.62 264.64 55366 +1945 193 25.38 19.38 23.73 0 685.84 353.19 55276 +1945 194 25.9 19.9 24.25 0 705.14 350.58 55182 +1945 195 27.6 21.6 25.95 0 771.46 342.01 55085 +1945 196 28.4 22.4 26.75 0 804.45 337.45 54984 +1945 197 27.15 21.15 25.5 0.16 753.41 257.6 54879 +1945 198 28.65 22.65 27 1.05 815.01 251.46 54770 +1945 199 25.07 19.07 23.42 0 674.55 352.53 54658 +1945 200 21.51 15.51 19.86 0 555.77 366.5 54542 +1945 201 23.53 17.53 21.88 1.16 620.77 268.68 54423 +1945 202 23.77 17.77 22.12 0.1 628.9 267.53 54301 +1945 203 18.43 12.43 16.78 0.01 467.81 281.44 54176 +1945 204 17.61 11.61 15.96 0 446.5 377.18 54047 +1945 205 18.93 12.93 17.28 1.11 481.23 279.5 53915 +1945 206 17.28 11.28 15.63 0.06 438.16 282.77 53780 +1945 207 21.35 15.35 19.7 0.77 550.88 272.5 53643 +1945 208 18.58 12.58 16.93 0 471.8 371.86 53502 +1945 209 18.67 12.67 17.02 0 474.21 370.93 53359 +1945 210 22.22 16.22 20.57 0 577.92 358.23 53213 +1945 211 22.77 16.77 21.12 0.13 595.59 266.53 53064 +1945 212 22.16 16.16 20.51 0.18 576.02 267.68 52913 +1945 213 18.8 12.8 17.15 0.03 477.71 275.66 52760 +1945 214 21.58 15.58 19.93 0 557.92 357.54 52604 +1945 215 25 19 23.35 0.03 672.02 257.5 52445 +1945 216 24.38 18.38 22.73 0.1 649.98 258.75 52285 +1945 217 25.41 19.41 23.76 0 686.94 339.71 52122 +1945 218 28.27 22.27 26.62 0 799.01 325.28 51958 +1945 219 25.3 19.3 23.65 0 682.91 338.41 51791 +1945 220 21.54 15.54 19.89 0 556.69 352.35 51622 +1945 221 19.09 13.09 17.44 0.04 485.59 269.6 51451 +1945 222 19.7 13.7 18.05 0 502.53 356.5 51279 +1945 223 18.69 12.69 17.04 0.28 474.75 268.86 51105 +1945 224 18.1 12.1 16.45 0.05 459.14 269.36 50929 +1945 225 19.71 13.71 18.06 0.62 502.81 264.84 50751 +1945 226 14.81 8.81 13.16 0 379.85 365.43 50572 +1945 227 20.72 14.72 19.07 0 531.97 347.42 50392 +1945 228 20.2 14.2 18.55 0 516.78 347.92 50210 +1945 229 23.4 17.4 21.75 0 616.4 335.4 50026 +1945 230 28.45 22.45 26.8 0 806.56 311.84 49842 +1945 231 27.92 21.92 26.27 0.05 784.52 234.83 49656 +1945 232 24.77 18.77 23.12 0.91 663.78 244.5 49469 +1945 233 23.3 17.3 21.65 0.59 613.06 247.82 49280 +1945 234 21.69 15.69 20.04 0 561.31 334.86 49091 +1945 235 22.18 16.18 20.53 0.01 576.65 248.77 48900 +1945 236 22.57 16.57 20.92 0 589.12 328.9 48709 +1945 237 26.35 20.35 24.7 0.29 722.21 234.17 48516 +1945 238 24.4 18.4 22.75 0.3 650.69 239.09 48323 +1945 239 22.29 16.29 20.64 0.11 580.15 243.89 48128 +1945 240 20.92 14.92 19.27 0.42 537.91 246.05 47933 +1945 241 24.4 18.4 22.75 0.22 650.69 235.51 47737 +1945 242 24.9 18.9 23.25 0 668.43 310.37 47541 +1945 243 23.74 17.74 22.09 0 627.88 313.08 47343 +1945 244 21.23 15.23 19.58 0 547.23 320.04 47145 +1945 245 25.28 19.28 23.63 0.21 682.18 227.7 46947 +1945 246 18.85 12.85 17.2 0 479.06 323.45 46747 +1945 247 20.16 14.16 18.51 0.14 515.63 238.36 46547 +1945 248 18.44 12.44 16.79 0.19 468.08 240.6 46347 +1945 249 11.76 5.76 10.11 0.46 317.1 250.23 46146 +1945 250 12.44 6.44 10.79 0.67 330.27 247.78 45945 +1945 251 11.34 5.34 9.69 0 309.2 330.19 45743 +1945 252 14.57 8.57 12.92 0.01 374.56 241.31 45541 +1945 253 11.58 5.58 9.93 0 313.7 325.36 45339 +1945 254 15.9 9.9 14.25 0 404.71 314.53 45136 +1945 255 13.58 7.58 11.93 0.38 353.38 237.85 44933 +1945 256 12.65 6.65 11 0 334.42 316.6 44730 +1945 257 14.36 8.36 12.71 0 369.98 311.07 44527 +1945 258 18.66 12.66 17.01 0 473.94 298.79 44323 +1945 259 22.3 16.3 20.65 0 580.46 285.91 44119 +1945 260 23.79 17.79 22.14 0 629.58 278.7 43915 +1945 261 23.97 17.97 22.32 0 635.75 275.76 43711 +1945 262 15.6 9.6 13.95 0 397.74 296.41 43507 +1945 263 15.88 9.88 14.23 0.76 404.24 220.01 43303 +1945 264 17.75 11.75 16.1 0 450.08 286.55 43099 +1945 265 22.23 16.23 20.58 0 578.24 272.11 42894 +1945 266 25.35 19.35 23.7 0.83 684.74 194.55 42690 +1945 267 28.95 22.95 27.3 0.36 827.82 182 42486 +1945 268 24.62 18.62 22.97 0.03 658.44 192.8 42282 +1945 269 21.16 15.16 19.51 0 545.11 265.41 42078 +1945 270 23.75 17.75 22.1 0.62 628.22 191.34 41875 +1945 271 24.11 18.11 22.46 0.06 640.58 188.62 41671 +1945 272 22.08 16.08 20.43 0 573.49 255.14 41468 +1945 273 19.63 13.63 17.98 1 500.56 194.47 41265 +1945 274 10.49 4.49 8.84 1.78 293.72 205.67 41062 +1945 275 13.12 7.12 11.47 0.34 343.89 200.51 40860 +1945 276 13.24 7.24 11.59 0.22 346.35 198.32 40658 +1945 277 8.34 2.34 6.69 0 257.5 268.8 40456 +1945 278 8.78 2.78 7.13 0 264.59 265.32 40255 +1945 279 11.63 5.63 9.98 0 314.64 258.57 40054 +1945 280 13.71 7.71 12.06 0 356.1 252.63 39854 +1945 281 14.9 8.9 13.25 0.04 381.86 185.9 39654 +1945 282 18.88 12.88 17.23 0.21 479.87 177.93 39455 +1945 283 17.18 11.18 15.53 0 435.66 238.08 39256 +1945 284 16.05 10.05 14.4 0.29 408.24 177.97 39058 +1945 285 14.15 8.15 12.5 0 365.44 238.01 38861 +1945 286 16.65 10.65 15 0 422.61 230.87 38664 +1945 287 14.79 8.79 13.14 0 379.41 231.29 38468 +1945 288 14.25 8.25 12.6 0 367.6 229.43 38273 +1945 289 14.13 8.13 12.48 0.02 365.02 170.26 38079 +1945 290 19.57 13.57 17.92 0 498.88 214.07 37885 +1945 291 18.29 12.29 16.64 0.38 464.12 160.6 37693 +1945 292 18.21 12.21 16.56 0.81 462.01 158.77 37501 +1945 293 12.88 6.88 11.23 0.1 339.03 163.49 37311 +1945 294 10.59 4.59 8.94 0.06 295.51 163.6 37121 +1945 295 11.26 5.26 9.61 0 307.72 214.46 36933 +1945 296 15.49 9.49 13.84 0 395.2 205.82 36745 +1945 297 12.83 6.83 11.18 0 338.02 207.09 36560 +1945 298 15.14 9.14 13.49 0 387.24 201.15 36375 +1945 299 11.79 5.79 10.14 0 317.68 203.1 36191 +1945 300 9.07 3.07 7.42 0 269.35 203.58 36009 +1945 301 10.44 4.44 8.79 0.05 292.83 149.66 35829 +1945 302 9.19 3.19 7.54 0 271.34 198.3 35650 +1945 303 9.65 3.65 8 0 279.08 195.23 35472 +1945 304 10.77 4.77 9.12 0 298.75 191.54 35296 +1945 305 4.23 -1.77 2.58 0.24 198.83 146.11 35122 +1945 306 3.62 -2.38 1.97 0 191.19 192.96 34950 +1945 307 2.34 -3.66 0.69 0.12 175.97 143.45 34779 +1945 308 5.63 -0.37 3.98 0 217.37 186.27 34610 +1945 309 4.04 -1.96 2.39 0.28 196.42 138.83 34444 +1945 310 3.67 -2.33 2.02 0.5 191.8 137.17 34279 +1945 311 3.41 -2.59 1.76 0.38 188.62 135.64 34116 +1945 312 3.77 -2.23 2.12 0.17 193.04 133.45 33956 +1945 313 2.82 -3.18 1.17 0.46 181.55 132.3 33797 +1945 314 -3.62 -9.62 -5.27 0 118.08 177.65 33641 +1945 315 1.13 -4.87 -0.52 0.12 162.56 129.62 33488 +1945 316 3.46 -2.54 1.81 0 189.23 169.23 33337 +1945 317 3.72 -2.28 2.07 0 192.42 166.84 33188 +1945 318 7.35 1.35 5.7 0 242.16 161.87 33042 +1945 319 8.32 2.32 6.67 0.01 257.19 119.53 32899 +1945 320 8.51 2.51 6.86 0 260.22 157.36 32758 +1945 321 15.16 9.16 13.51 0.94 387.69 111.23 32620 +1945 322 13.83 7.83 12.18 0.75 358.63 111.12 32486 +1945 323 12.77 6.77 11.12 1.46 336.82 110.84 32354 +1945 324 10.92 4.92 9.27 0 301.47 147.66 32225 +1945 325 11.09 5.09 9.44 0.16 304.58 109.35 32100 +1945 326 7.53 1.53 5.88 0 244.89 147.42 31977 +1945 327 7.64 1.64 5.99 0.96 246.57 109.12 31858 +1945 328 7.01 1.01 5.36 0.69 237.08 108 31743 +1945 329 5.67 -0.33 4.02 0.48 217.92 107.58 31631 +1945 330 6.61 0.61 4.96 0 231.21 141.36 31522 +1945 331 9.56 3.56 7.91 0 277.55 137.79 31417 +1945 332 11.86 5.86 10.21 0.22 319.01 100.58 31316 +1945 333 14.49 8.49 12.84 0.01 372.81 97.75 31218 +1945 334 10.78 4.78 9.13 0.08 298.93 99.73 31125 +1945 335 4.97 -1.03 3.32 0 208.45 136.12 31035 +1945 336 5.18 -0.82 3.53 0 211.25 134.92 30949 +1945 337 5.51 -0.49 3.86 0 215.72 133.05 30867 +1945 338 4.23 -1.77 2.58 0 198.83 132.88 30790 +1945 339 0.23 -5.77 -1.42 0 153.17 134.09 30716 +1945 340 2.38 -3.62 0.73 0.01 176.43 99.26 30647 +1945 341 3.94 -2.06 2.29 0 195.16 130.59 30582 +1945 342 8.4 2.4 6.75 0 258.46 126.98 30521 +1945 343 5.25 -0.75 3.6 0 212.19 128.25 30465 +1945 344 4.31 -1.69 2.66 0 199.85 127.67 30413 +1945 345 2.99 -3.01 1.34 0.01 183.56 95.96 30366 +1945 346 1.29 -4.71 -0.36 0 164.28 128.22 30323 +1945 347 3.55 -2.45 1.9 0 190.33 126.51 30284 +1945 348 7.65 1.65 6 0 246.72 123.67 30251 +1945 349 9.62 3.62 7.97 0 278.57 121.85 30221 +1945 350 10.58 4.58 8.93 0 295.33 120.75 30197 +1945 351 6.11 0.11 4.46 0 224.06 123.75 30177 +1945 352 4.86 -1.14 3.21 0 206.99 124.41 30162 +1945 353 0.68 -5.32 -0.97 0 157.8 126.44 30151 +1945 354 0.04 -5.96 -1.61 0 151.25 126.67 30145 +1945 355 3.61 -2.39 1.96 0 191.06 124.99 30144 +1945 356 1.38 -4.62 -0.27 0.14 165.26 94.59 30147 +1945 357 0.04 -5.96 -1.61 0 151.25 126.76 30156 +1945 358 3.75 -2.25 2.1 0.54 192.79 93.82 30169 +1945 359 3.72 -2.28 2.07 0.54 192.42 93.92 30186 +1945 360 7.76 1.76 6.11 0.96 248.42 92.35 30208 +1945 361 4.07 -1.93 2.42 0.01 196.8 94.3 30235 +1945 362 0.94 -5.06 -0.71 0 160.54 127.73 30267 +1945 363 1.15 -4.85 -0.5 0.19 162.78 96.17 30303 +1945 364 2.45 -3.55 0.8 0.07 177.24 96 30343 +1945 365 8.75 2.75 7.1 0 264.1 124.7 30388 +1946 1 -0.9 -6.9 -2.55 0 142.04 130.96 30438 +1946 2 -1.43 -7.43 -3.08 0 137.07 131.91 30492 +1946 3 -5.05 -11.05 -6.7 0 106.95 134.1 30551 +1946 4 -1.82 -7.82 -3.47 0 133.5 133.93 30614 +1946 5 -2.1 -8.1 -3.75 0 131 134.7 30681 +1946 6 0.4 -5.6 -1.25 0 154.91 134.58 30752 +1946 7 1.1 -4.9 -0.55 0 162.24 135.06 30828 +1946 8 1.49 -4.51 -0.16 0 166.46 136.37 30907 +1946 9 -1.27 -7.27 -2.92 0 138.55 138.86 30991 +1946 10 -1.03 -7.03 -2.68 0 140.81 140.07 31079 +1946 11 -0.11 -6.11 -1.76 0 149.74 140.68 31171 +1946 12 -2.05 -8.05 -3.7 0 131.44 142.51 31266 +1946 13 -0.47 -6.47 -2.12 0 146.19 143.49 31366 +1946 14 0.95 -5.05 -0.7 0 160.64 144.33 31469 +1946 15 -5.47 -11.47 -7.12 0 103.86 148.31 31575 +1946 16 -2.51 -8.51 -4.16 0 127.4 148.59 31686 +1946 17 2.95 -3.05 1.3 0 183.09 147.72 31800 +1946 18 2.89 -3.11 1.24 0 182.38 149.66 31917 +1946 19 2.05 -3.95 0.4 0.26 172.67 114.04 32038 +1946 20 -3.03 -9.03 -4.68 0 122.96 155.98 32161 +1946 21 -1.05 -7.05 -2.7 0 140.62 157.2 32289 +1946 22 -0.31 -6.31 -1.96 0 147.76 158.63 32419 +1946 23 -2.96 -8.96 -4.61 0 123.55 161.56 32552 +1946 24 -1.64 -7.64 -3.29 0.11 135.14 163.04 32688 +1946 25 0.64 -5.36 -1.01 0 157.39 204.39 32827 +1946 26 0.91 -5.09 -0.74 0.09 160.22 164.47 32969 +1946 27 -0.94 -6.94 -2.59 0.07 141.66 166.72 33114 +1946 28 -2.27 -8.27 -3.92 0 129.49 211.55 33261 +1946 29 -3.05 -9.05 -4.7 0 122.79 214.11 33411 +1946 30 -3.03 -9.03 -4.68 0 122.96 216.2 33564 +1946 31 -1.3 -7.3 -2.95 0 138.27 217.65 33718 +1946 32 11.03 5.03 9.38 0 303.48 171.21 33875 +1946 33 9.37 3.37 7.72 0 274.35 175.48 34035 +1946 34 5.82 -0.18 4.17 0 219.99 180.76 34196 +1946 35 3.78 -2.22 2.13 0.21 193.17 138.31 34360 +1946 36 9.87 3.87 8.22 0 282.86 181.72 34526 +1946 37 5.23 -0.77 3.58 0.1 211.92 141.21 34694 +1946 38 8.32 2.32 6.67 0 257.19 188.35 34863 +1946 39 4.62 -1.38 2.97 0 203.85 194.1 35035 +1946 40 1 -5 -0.65 0 161.18 199.18 35208 +1946 41 1.27 -4.73 -0.38 0 164.07 201.65 35383 +1946 42 1.62 -4.38 -0.03 1.05 167.88 153.01 35560 +1946 43 4.11 -1.89 2.46 0 197.3 204.99 35738 +1946 44 3.07 -2.93 1.42 0 184.52 208.33 35918 +1946 45 3.03 -2.97 1.38 0 184.04 211 36099 +1946 46 4.73 -1.27 3.08 0 205.29 212.39 36282 +1946 47 5.27 -0.73 3.62 0.19 212.46 161.07 36466 +1946 48 2.17 -3.83 0.52 0.26 174.03 164.98 36652 +1946 49 2.03 -3.97 0.38 0.07 172.45 167.15 36838 +1946 50 5.2 -0.8 3.55 0 211.52 223.07 37026 +1946 51 6.19 0.19 4.54 0.17 225.19 168.85 37215 +1946 52 7.32 1.32 5.67 0 241.71 226.85 37405 +1946 53 6.95 0.95 5.3 0 236.19 230.17 37596 +1946 54 7.46 1.46 5.81 0 243.83 232.39 37788 +1946 55 7.7 1.7 6.05 0 247.49 235.12 37981 +1946 56 7.78 1.78 6.13 0.22 248.73 178.28 38175 +1946 57 8.53 2.53 6.88 0 260.54 239.73 38370 +1946 58 10.87 4.87 9.22 0.15 300.56 179.8 38565 +1946 59 4.81 -1.19 3.16 0 206.34 249.19 38761 +1946 60 4.97 -1.03 3.32 0.02 208.45 188.95 38958 +1946 61 7.88 1.88 6.23 0 250.27 251.86 39156 +1946 62 9.11 3.11 7.46 0 270.01 253.17 39355 +1946 63 10.93 4.93 9.28 0.13 301.65 190.31 39553 +1946 64 10.07 4.07 8.42 0 286.32 257.79 39753 +1946 65 12.25 6.25 10.6 0 326.54 257.5 39953 +1946 66 13.15 7.15 11.5 0 344.5 258.74 40154 +1946 67 9.8 3.8 8.15 0 281.65 266.59 40355 +1946 68 9.37 3.37 7.72 0 274.35 270.01 40556 +1946 69 9.96 3.96 8.31 0 284.41 271.82 40758 +1946 70 7.64 1.64 5.99 0 246.57 277.64 40960 +1946 71 2.85 -3.15 1.2 0 181.9 285.56 41163 +1946 72 2.5 -3.5 0.85 0 177.82 288.73 41366 +1946 73 3.99 -2.01 2.34 0 195.79 290.05 41569 +1946 74 5.41 -0.59 3.76 0 214.36 291.37 41772 +1946 75 7.57 1.57 5.92 0 245.5 291.61 41976 +1946 76 9.07 3.07 7.42 0 269.35 292.28 42179 +1946 77 7.07 1.07 5.42 0.2 237.97 223.11 42383 +1946 78 9.86 3.86 8.21 0 282.68 296.41 42587 +1946 79 8.61 2.61 6.96 0 261.83 300.89 42791 +1946 80 11.76 5.76 10.11 0.11 317.1 223.99 42996 +1946 81 9.98 3.98 8.33 0 284.76 304.03 43200 +1946 82 13.59 7.59 11.94 0.26 353.59 225.41 43404 +1946 83 11.73 5.73 10.08 0 316.53 306.34 43608 +1946 84 13.01 7.01 11.36 0 341.66 306.57 43812 +1946 85 12.73 6.73 11.08 0.72 336.02 232.16 44016 +1946 86 11.31 5.31 9.66 0 308.64 314.42 44220 +1946 87 6.87 0.87 5.22 0 235.01 323.51 44424 +1946 88 11.85 5.85 10.2 0 318.82 318.33 44627 +1946 89 11.67 5.67 10.02 0.4 315.4 240.68 44831 +1946 90 9.67 3.67 8.02 0.24 279.43 244.93 45034 +1946 91 18.02 12.02 16.37 0 457.05 311.81 45237 +1946 92 15.34 9.34 13.69 0 391.77 320.41 45439 +1946 93 13.41 7.41 11.76 0 349.85 326.64 45642 +1946 94 17.02 11.02 15.37 0 431.69 320.72 45843 +1946 95 15.76 9.76 14.11 0 401.44 325.82 46045 +1946 96 15.05 9.05 13.4 0 385.21 329.5 46246 +1946 97 12.66 6.66 11.01 0 334.62 336.5 46446 +1946 98 13.68 7.68 12.03 0 355.47 336.4 46647 +1946 99 17.65 11.65 16 0 447.52 329.08 46846 +1946 100 16.09 10.09 14.44 0 409.18 334.9 47045 +1946 101 19.44 13.44 17.79 0 495.25 327.84 47243 +1946 102 17.67 11.67 16.02 0 448.04 334.63 47441 +1946 103 15.63 9.63 13.98 0 398.43 341.57 47638 +1946 104 17.69 11.69 16.04 0 448.55 338.14 47834 +1946 105 17.82 11.82 16.17 0 451.88 339.53 48030 +1946 106 19.35 13.35 17.7 0 492.75 336.76 48225 +1946 107 23.26 17.26 21.61 0 611.72 325.26 48419 +1946 108 19.86 13.86 18.21 0 507.05 338.5 48612 +1946 109 16.05 10.05 14.4 0 408.24 350.66 48804 +1946 110 14.24 8.24 12.59 0 367.38 356.33 48995 +1946 111 13.82 7.82 12.17 0 358.42 358.81 49185 +1946 112 15.84 9.84 14.19 0 403.31 355.59 49374 +1946 113 17.14 11.14 15.49 0 434.67 353.55 49561 +1946 114 15.64 9.64 13.99 0 398.66 358.89 49748 +1946 115 14.85 8.85 13.2 0 380.74 362.21 49933 +1946 116 15.97 9.97 14.32 0 406.36 360.68 50117 +1946 117 12.86 6.86 11.21 0 338.63 369.18 50300 +1946 118 11.52 5.52 9.87 0 312.57 373.22 50481 +1946 119 10.06 4.06 8.41 0 286.15 377.15 50661 +1946 120 12.82 6.82 11.17 0 337.82 372.96 50840 +1946 121 16.21 10.21 14.56 0 412.03 366.11 51016 +1946 122 17.54 11.54 15.89 0 444.72 363.69 51191 +1946 123 17.55 11.55 15.9 0 444.98 364.68 51365 +1946 124 17.14 11.14 15.49 0 434.67 366.89 51536 +1946 125 21.78 15.78 20.13 0.15 564.11 264.85 51706 +1946 126 24.12 18.12 22.47 0.53 640.93 258.78 51874 +1946 127 23.28 17.28 21.63 0.07 612.39 261.95 52039 +1946 128 21.94 15.94 20.29 0.78 569.1 266.48 52203 +1946 129 22.25 16.25 20.6 0.57 578.87 266.23 52365 +1946 130 22.32 16.32 20.67 0 581.1 355.47 52524 +1946 131 20.94 14.94 19.29 0 538.51 361.23 52681 +1946 132 20.88 14.88 19.23 0 536.72 362.24 52836 +1946 133 26.35 20.35 24.7 0 722.21 340.66 52989 +1946 134 20.51 14.51 18.86 0.08 525.79 273.67 53138 +1946 135 19.02 13.02 17.37 0.07 483.68 277.84 53286 +1946 136 16.44 10.44 14.79 0 417.53 378.61 53430 +1946 137 16.6 10.6 14.95 0 421.4 378.88 53572 +1946 138 17.77 11.77 16.12 0 450.6 376.17 53711 +1946 139 17.14 11.14 15.49 0 434.67 378.67 53848 +1946 140 16.85 10.85 15.2 0 427.5 379.97 53981 +1946 141 19.36 13.36 17.71 0 493.03 372.87 54111 +1946 142 21.54 15.54 19.89 0 556.69 365.87 54238 +1946 143 22.35 16.35 20.7 0 582.06 363.36 54362 +1946 144 24.56 18.56 22.91 0 656.32 354.82 54483 +1946 145 20.73 14.73 19.08 0 532.26 370.22 54600 +1946 146 18.51 12.51 16.86 0.1 469.94 283.41 54714 +1946 147 16.16 10.16 14.51 0 410.84 385.14 54824 +1946 148 20.88 14.88 19.23 0.05 536.72 278.18 54931 +1946 149 18.82 12.82 17.17 0.66 478.25 283.57 55034 +1946 150 18.81 12.81 17.16 2.14 477.98 283.84 55134 +1946 151 18.5 12.5 16.85 0.65 469.67 284.85 55229 +1946 152 19.37 13.37 17.72 0 493.3 377.16 55321 +1946 153 23.55 17.55 21.9 0.32 621.44 271.53 55409 +1946 154 24.18 18.18 22.53 0.35 643.01 269.78 55492 +1946 155 23.22 17.22 21.57 0.02 610.39 272.91 55572 +1946 156 23.22 17.22 21.57 0 610.39 364.2 55648 +1946 157 20.59 14.59 18.94 0.2 528.14 280.7 55719 +1946 158 21.41 15.41 19.76 0.09 552.71 278.63 55786 +1946 159 24.64 18.64 22.99 0 659.15 358.78 55849 +1946 160 24.5 18.5 22.85 0.05 654.2 269.68 55908 +1946 161 25.82 19.82 24.17 0.11 702.14 265.25 55962 +1946 162 21.43 15.43 19.78 0 553.32 371.98 56011 +1946 163 22.89 16.89 21.24 0 599.51 366.6 56056 +1946 164 21.2 15.2 19.55 0 546.32 373.07 56097 +1946 165 19.43 13.43 17.78 0 494.97 379.27 56133 +1946 166 21.42 15.42 19.77 0 553.01 372.44 56165 +1946 167 20.52 14.52 18.87 0.8 526.08 281.71 56192 +1946 168 19.76 13.76 18.11 0.11 504.22 283.71 56214 +1946 169 20.68 14.68 19.03 0.15 530.79 281.35 56231 +1946 170 19.69 13.69 18.04 0 502.24 378.53 56244 +1946 171 18.11 12.11 16.46 0 459.4 383.62 56252 +1946 172 21.41 15.41 19.76 0 552.71 372.56 56256 +1946 173 22.49 16.49 20.84 0 586.54 368.46 56255 +1946 174 24.74 18.74 23.09 0.1 662.71 269.28 56249 +1946 175 23.25 17.25 21.6 2.31 611.39 273.99 56238 +1946 176 24.31 18.31 22.66 0.58 647.54 270.64 56223 +1946 177 22.3 16.3 20.65 0.56 580.46 276.71 56203 +1946 178 19.47 13.47 17.82 0 496.08 379.06 56179 +1946 179 17.66 11.66 16.01 0.86 447.78 288.45 56150 +1946 180 19.18 13.18 17.53 0 488.06 379.78 56116 +1946 181 14.05 8.05 12.4 0 363.3 394.03 56078 +1946 182 18.28 12.28 16.63 0 463.85 382.4 56035 +1946 183 23.25 17.25 21.6 0 611.39 364.61 55987 +1946 184 25.48 19.48 23.83 0.11 689.52 266.12 55935 +1946 185 26.22 20.22 24.57 0.22 717.24 263.47 55879 +1946 186 30.17 24.17 28.52 0 881.7 330.05 55818 +1946 187 28.91 22.91 27.26 0 826.1 337.06 55753 +1946 188 31.12 25.12 29.47 0.78 925.67 242.93 55684 +1946 189 31.01 25.01 29.36 0 920.49 324.43 55611 +1946 190 33.1 27.1 31.45 0 1023.28 310.53 55533 +1946 191 31.47 25.47 29.82 0 942.33 320.99 55451 +1946 192 29.49 23.49 27.84 0.58 851.31 249.4 55366 +1946 193 27.62 21.62 25.97 2.55 772.27 256.78 55276 +1946 194 25.21 19.21 23.56 0.42 679.63 265.31 55182 +1946 195 24.87 18.87 23.22 0.09 667.35 266.25 55085 +1946 196 23.14 17.14 21.49 0 607.74 361.88 54984 +1946 197 19.95 13.95 18.3 0.55 509.61 279.85 54879 +1946 198 17.53 11.53 15.88 0.04 444.47 285.2 54770 +1946 199 17.23 11.23 15.58 0.48 436.91 285.58 54658 +1946 200 20 14 18.35 0.18 511.04 278.84 54542 +1946 201 22.61 16.61 20.96 0.07 590.41 271.43 54423 +1946 202 21.82 15.82 20.17 0.09 565.35 273.26 54301 +1946 203 22.85 16.85 21.2 0 598.2 359.92 54176 +1946 204 22.07 16.07 20.42 0 573.18 362.41 54047 +1946 205 20.58 14.58 18.93 0.01 527.84 275.44 53915 +1946 206 26.05 20.05 24.4 0 710.79 344.69 53780 +1946 207 27.2 21.2 25.55 0 755.4 338.54 53643 +1946 208 27.4 21.4 25.75 0 763.4 336.93 53502 +1946 209 24.14 18.14 22.49 0.22 641.62 263.42 53359 +1946 210 20.76 14.76 19.11 0 533.15 363.49 53213 +1946 211 18.57 12.57 16.92 0 471.54 369.82 53064 +1946 212 19.61 13.61 17.96 0 500 365.76 52913 +1946 213 19.88 13.88 18.23 0 507.62 364.12 52760 +1946 214 24.26 18.26 22.61 0 645.79 347.14 52604 +1946 215 23.77 17.77 22.12 0 628.9 348.5 52445 +1946 216 26.78 20.78 25.13 0 738.84 334.26 52285 +1946 217 28.59 22.59 26.94 0.08 812.46 243.27 52122 +1946 218 26.16 20.16 24.51 2.67 714.96 251.66 51958 +1946 219 27.13 21.13 25.48 0.25 752.62 247.49 51791 +1946 220 22.66 16.66 21.01 1.18 592.02 261.19 51622 +1946 221 20.4 14.4 18.75 0.03 522.58 266.45 51451 +1946 222 20.37 14.37 18.72 0.36 521.7 265.75 51279 +1946 223 23.14 17.14 21.49 0.32 607.74 257.47 51105 +1946 224 22.26 16.26 20.61 0.1 579.19 259.18 50929 +1946 225 26.51 20.51 24.86 0.13 728.36 245.21 50751 +1946 226 26.36 20.36 24.71 0.51 722.59 244.91 50572 +1946 227 22.68 16.68 21.03 0.17 592.67 255.39 50392 +1946 228 22.66 16.66 21.01 0 592.02 339.4 50210 +1946 229 25.25 19.25 23.6 0 681.09 327.9 50026 +1946 230 23.42 17.42 21.77 0.74 617.07 250.57 49842 +1946 231 24.81 18.81 23.16 0 665.2 327.12 49656 +1946 232 21.21 15.21 19.56 0 546.63 339.29 49469 +1946 233 18.96 12.96 17.31 0 482.04 345 49280 +1946 234 16.25 10.25 14.6 0.06 412.98 263.24 49091 +1946 235 20.35 14.35 18.7 0.13 521.12 253.37 48900 +1946 236 21.22 15.22 19.57 0 546.93 333.58 48709 +1946 237 24.96 18.96 23.31 0 670.58 318.14 48516 +1946 238 27.04 21.04 25.39 0 749.06 307.57 48323 +1946 239 29.01 23.01 27.36 0 830.4 296.72 48128 +1946 240 29.88 23.88 28.23 0 868.63 290.64 47933 +1946 241 28.63 22.63 26.98 0 814.16 295.43 47737 +1946 242 27.6 21.6 25.95 0.32 771.46 224.06 47541 +1946 243 27 21 25.35 0 747.48 299.74 47343 +1946 244 19.53 13.53 17.88 0.04 497.76 243.96 47145 +1946 245 19.75 13.75 18.1 0 503.94 322.81 46947 +1946 246 24.98 18.98 23.33 0.02 671.3 227.2 46747 +1946 247 22.99 16.99 21.34 0 602.79 308.59 46547 +1946 248 22.1 16.1 20.45 0 574.13 309.76 46347 +1946 249 23.34 17.34 21.69 0.05 614.39 227.62 46146 +1946 250 21.15 15.15 19.5 0 544.81 308.93 45945 +1946 251 18.83 12.83 17.18 0.93 478.52 235.23 45743 +1946 252 17.41 11.41 15.76 0.86 441.43 236.4 45541 +1946 253 19.92 13.92 18.27 0 508.76 306.35 45339 +1946 254 20.03 14.03 18.38 0 511.9 303.94 45136 +1946 255 18.4 12.4 16.75 0 467.02 306.18 44933 +1946 256 18.82 12.82 17.17 0 478.25 302.83 44730 +1946 257 20.78 14.78 19.13 0 533.75 295.21 44527 +1946 258 17.35 11.35 15.7 0 439.92 302.08 44323 +1946 259 22.96 16.96 21.31 0 601.8 283.77 44119 +1946 260 22.74 16.74 21.09 0 594.62 282.21 43915 +1946 261 23.36 17.36 21.71 0.06 615.06 208.37 43711 +1946 262 22.74 16.74 21.09 0.43 594.62 208.2 43507 +1946 263 22.27 16.27 20.62 0.04 579.51 207.54 43303 +1946 264 22.03 16.03 20.38 0.05 571.92 206.24 43099 +1946 265 22.03 16.03 20.38 0.03 571.92 204.54 42894 +1946 266 18.83 12.83 17.18 0.08 478.52 209.35 42690 +1946 267 20.13 14.13 18.48 0.12 514.76 204.86 42486 +1946 268 19.74 13.74 18.09 0 503.65 271.68 42282 +1946 269 19.51 13.51 17.86 0 497.2 269.83 42078 +1946 270 20.48 14.48 18.83 0 524.91 264.73 41875 +1946 271 21.76 15.76 20.11 0 563.48 258.67 41671 +1946 272 21.2 15.2 19.55 0 546.32 257.62 41468 +1946 273 18.45 12.45 16.8 0 468.34 262.14 41265 +1946 274 7.33 1.33 5.68 0.31 241.86 208.77 41062 +1946 275 7.25 1.25 5.6 0.68 240.65 206.7 40860 +1946 276 8.77 2.77 7.12 0.71 264.42 203.24 40658 +1946 277 8.27 2.27 6.62 0 256.39 268.88 40456 +1946 278 9.68 3.68 8.03 0 279.6 264.16 40255 +1946 279 13.47 7.47 11.82 0.27 351.09 191.76 40054 +1946 280 14.39 8.39 12.74 0 370.63 251.47 39854 +1946 281 14.34 8.34 12.69 0 369.54 248.85 39654 +1946 282 14.3 8.3 12.65 0.04 368.68 184.64 39455 +1946 283 12.64 6.64 10.99 0 334.22 246.06 39256 +1946 284 14.57 8.57 12.92 0.08 374.56 179.95 39058 +1946 285 16.08 10.08 14.43 1.14 408.95 175.98 38861 +1946 286 11.68 5.68 10.03 0.34 315.59 179.26 38664 +1946 287 10.42 4.42 8.77 0.02 292.48 178.32 38468 +1946 288 8.6 2.6 6.95 0 261.67 237.15 38273 +1946 289 9.94 3.94 8.29 0.05 284.07 174.67 38079 +1946 290 10.39 4.39 8.74 0 291.95 229.45 37885 +1946 291 14.14 8.14 12.49 0 365.23 221.49 37693 +1946 292 12.62 6.62 10.97 0 333.83 221.08 37501 +1946 293 9.76 3.76 8.11 0.09 280.97 166.52 37311 +1946 294 9.31 3.31 7.66 0 273.34 219.64 37121 +1946 295 5.18 -0.82 3.53 0.11 211.25 165.64 36933 +1946 296 9.39 3.39 7.74 0.86 274.68 160.56 36745 +1946 297 7.67 1.67 6.02 0 247.03 213.14 36560 +1946 298 4.77 -1.23 3.12 0 205.81 213.11 36375 +1946 299 6.93 0.93 5.28 0 235.89 208.39 36191 +1946 300 10.59 4.59 8.94 0.06 295.51 151.42 36009 +1946 301 13.27 7.27 11.62 0 346.96 196.03 35829 +1946 302 10.44 4.44 8.79 1.37 292.83 147.7 35650 +1946 303 10.22 4.22 8.57 0.22 288.95 145.96 35472 +1946 304 10.1 4.1 8.45 0 286.85 192.28 35296 +1946 305 5.01 -0.99 3.36 0 208.98 194.22 35122 +1946 306 7.28 1.28 5.63 0.15 241.11 142.54 34950 +1946 307 6.29 0.29 4.64 0 226.61 188.37 34779 +1946 308 9.73 3.73 8.08 0 280.45 182.58 34610 +1946 309 11.19 5.19 9.54 0 306.42 178.72 34444 +1946 310 10.44 4.44 8.79 0.19 292.83 132.83 34279 +1946 311 5.08 -0.92 3.43 0.51 209.91 134.76 34116 +1946 312 6.77 0.77 5.12 0.42 233.54 131.78 33956 +1946 313 9.94 3.94 8.29 0.04 284.07 128.04 33797 +1946 314 9.19 3.19 7.54 0.46 271.34 127.13 33641 +1946 315 8.32 2.32 6.67 0.27 257.19 125.83 33488 +1946 316 7.12 1.12 5.47 0 238.71 166.59 33337 +1946 317 7.42 1.42 5.77 0.06 243.22 123.12 33188 +1946 318 7.09 1.09 5.44 0.49 238.26 121.56 33042 +1946 319 9.65 3.65 8 0 279.08 158.2 32899 +1946 320 10.07 4.07 8.42 0 286.32 155.96 32758 +1946 321 11.14 5.14 9.49 0 305.5 152.84 32620 +1946 322 7.2 1.2 5.55 0 239.91 154.5 32486 +1946 323 7.5 1.5 5.85 0 244.43 152.65 32354 +1946 324 6.83 0.83 5.18 0 234.42 151.12 32225 +1946 325 7.86 1.86 6.21 0 249.96 148.61 32100 +1946 326 8.23 2.23 6.58 0.05 255.76 110.16 31977 +1946 327 11.15 5.15 9.5 0.08 305.68 106.87 31858 +1946 328 7.67 1.67 6.02 0.17 247.03 107.63 31743 +1946 329 3.7 -2.3 2.05 0.18 192.17 108.5 31631 +1946 330 7.06 1.06 5.41 0.11 237.82 105.78 31522 +1946 331 9.37 3.37 7.72 0.9 274.35 103.46 31417 +1946 332 5.36 -0.64 3.71 0.02 213.68 104.43 31316 +1946 333 2.12 -3.88 0.47 1.64 173.47 105 31218 +1946 334 5.17 -0.83 3.52 0.38 211.12 102.88 31125 +1946 335 -4.82 -10.82 -6.47 0.37 108.68 149.06 31035 +1946 336 1.15 -4.85 -0.5 1.55 162.78 146.47 30949 +1946 337 1.34 -4.66 -0.31 0.94 164.82 145.09 30867 +1946 338 -0.62 -6.62 -2.27 0.03 144.73 145.23 30790 +1946 339 0.97 -5.03 -0.68 0.14 160.86 144.09 30716 +1946 340 0.49 -5.51 -1.16 0 155.83 177.04 30647 +1946 341 1.09 -4.91 -0.56 0 162.13 175.79 30582 +1946 342 1.36 -4.64 -0.29 0 165.04 174.8 30521 +1946 343 1.92 -4.08 0.27 0 171.21 173.53 30465 +1946 344 3.46 -2.54 1.81 0 189.23 128.13 30413 +1946 345 0.71 -5.29 -0.94 0 158.12 129.03 30366 +1946 346 -2.77 -8.77 -4.42 0 125.16 129.84 30323 +1946 347 -3.08 -9.08 -4.73 0.45 122.54 142.02 30284 +1946 348 -3.4 -9.4 -5.05 0 119.88 174.16 30251 +1946 349 1.37 -4.63 -0.28 0 165.15 171.77 30221 +1946 350 0.31 -5.69 -1.34 0.06 153.98 140.15 30197 +1946 351 0.07 -5.93 -1.58 0 151.55 171.8 30177 +1946 352 -2.05 -8.05 -3.7 0.15 131.44 141.13 30162 +1946 353 -2.84 -8.84 -4.49 0 124.56 173.25 30151 +1946 354 -0.45 -6.45 -2.1 0 146.39 172.34 30145 +1946 355 -0.53 -6.53 -2.18 0.22 145.6 141.34 30144 +1946 356 -1.49 -7.49 -3.14 0 136.51 173.46 30147 +1946 357 -0.06 -6.06 -1.71 0 150.24 172.95 30156 +1946 358 3.23 -2.77 1.58 0 186.44 171.06 30169 +1946 359 5.23 -0.77 3.58 0.64 211.92 138.26 30186 +1946 360 2 -4 0.35 0.08 172.11 139.52 30208 +1946 361 5.51 -0.49 3.86 0.01 215.72 137.58 30235 +1946 362 5.27 -0.73 3.62 0.22 212.46 94.12 30267 +1946 363 5.16 -0.84 3.51 0.61 210.98 94.61 30303 +1946 364 1.98 -4.02 0.33 0 171.89 128.23 30343 +1946 365 0.39 -5.61 -1.26 0.14 154.8 97.15 30388 +1947 1 -3.6 -9.6 -5.25 0 118.24 131.94 30438 +1947 2 -3.6 -9.6 -5.25 0.34 118.24 143.87 30492 +1947 3 -3.6 -9.6 -5.25 0 118.24 177.91 30551 +1947 4 -3.6 -9.6 -5.25 0 118.24 178.75 30614 +1947 5 -3.6 -9.6 -5.25 0 118.24 179.32 30681 +1947 6 -3.6 -9.6 -5.25 0.3 118.24 147.02 30752 +1947 7 -3.6 -9.6 -5.25 0.12 118.24 147.89 30828 +1947 8 -3.6 -9.6 -5.25 0.28 118.24 149.77 30907 +1947 9 -3.6 -9.6 -5.25 0.22 118.24 151.29 30991 +1947 10 -3.6 -9.6 -5.25 0 118.24 187.4 31079 +1947 11 -3.6 -9.6 -5.25 0 118.24 188.27 31171 +1947 12 -3.6 -9.6 -5.25 0 118.24 189.16 31266 +1947 13 -3.6 -9.6 -5.25 0.54 118.24 156.13 31366 +1947 14 -3.6 -9.6 -5.25 0.19 118.24 157.68 31469 +1947 15 -3.6 -9.6 -5.25 0 118.24 195.54 31575 +1947 16 -3.6 -9.6 -5.25 0 118.24 196.68 31686 +1947 17 -3.6 -9.6 -5.25 0.24 118.24 161.27 31800 +1947 18 -3.6 -9.6 -5.25 0.52 118.24 164.1 31917 +1947 19 -3.6 -9.6 -5.25 0 118.24 204.03 32038 +1947 20 -3.6 -9.6 -5.25 0.25 118.24 167.15 32161 +1947 21 -3.6 -9.6 -5.25 0 118.24 208.03 32289 +1947 22 -3.6 -9.6 -5.25 0 118.24 209.61 32419 +1947 23 -3.6 -9.6 -5.25 0.05 118.24 170.9 32552 +1947 24 -3.6 -9.6 -5.25 0.61 118.24 174.06 32688 +1947 25 -3.6 -9.6 -5.25 0 118.24 216.74 32827 +1947 26 -3.6 -9.6 -5.25 0 118.24 218.48 32969 +1947 27 -3.6 -9.6 -5.25 0.04 118.24 177.97 33114 +1947 28 -3.6 -9.6 -5.25 0 118.24 222.45 33261 +1947 29 -3.6 -9.6 -5.25 0 118.24 224.64 33411 +1947 30 -3.6 -9.6 -5.25 0 118.24 226.69 33564 +1947 31 -3.6 -9.6 -5.25 0 118.24 228.87 33718 +1947 32 1.03 -4.97 -0.62 0.25 161.49 183.66 33875 +1947 33 -0.05 -6.05 -1.7 0.13 150.34 186.22 34035 +1947 34 -0.11 -6.11 -1.76 0.65 149.74 189.51 34196 +1947 35 -0.24 -6.24 -1.89 0.57 148.45 192.54 34360 +1947 36 -0.91 -6.91 -2.56 1.62 141.95 198.96 34526 +1947 37 -1.12 -7.12 -2.77 0.57 139.96 202.19 34694 +1947 38 -4.56 -10.56 -6.21 0.94 110.66 207.75 34863 +1947 39 -3.67 -9.67 -5.32 0.35 117.67 210.12 35035 +1947 40 -4.24 -10.24 -5.89 0.1 113.14 212.27 35208 +1947 41 -2.96 -8.96 -4.61 0 123.55 264.53 35383 +1947 42 -4.1 -10.1 -5.75 0.04 114.24 215.69 35560 +1947 43 -3.72 -9.72 -5.37 0.57 117.27 218.86 35738 +1947 44 -6.75 -12.75 -8.4 0 94.91 274.8 35918 +1947 45 -5.35 -11.35 -7 0 104.73 276.63 36099 +1947 46 -4.92 -10.92 -6.57 0.03 107.92 224.43 36282 +1947 47 -3.36 -9.36 -5.01 0 120.21 280.84 36466 +1947 48 -2.14 -8.14 -3.79 0.45 130.64 228.31 36652 +1947 49 -1.17 -7.17 -2.82 0.92 139.49 232.11 36838 +1947 50 0.4 -5.6 -1.25 1.41 154.91 233.07 37026 +1947 51 1.8 -4.2 0.15 1.25 169.87 234.1 37215 +1947 52 -1.04 -7.04 -2.69 0.08 140.71 237.5 37405 +1947 53 -0.24 -6.24 -1.89 0 148.45 298.06 37596 +1947 54 0.03 -5.97 -1.62 0 151.15 300.36 37788 +1947 55 2.45 -3.55 0.8 0.16 177.24 241.15 37981 +1947 56 2.83 -3.17 1.18 0.43 181.67 242.36 38175 +1947 57 7.23 1.23 5.58 0.67 240.35 240.44 38370 +1947 58 2.86 -3.14 1.21 0.89 182.02 245.07 38565 +1947 59 3.78 -2.22 2.13 0.1 193.17 245.85 38761 +1947 60 7.12 1.12 5.47 0.69 238.71 244.57 38958 +1947 61 8.72 2.72 7.07 0 263.61 306.93 39156 +1947 62 8.53 2.53 6.88 0.01 260.54 245.3 39355 +1947 63 8.11 2.11 6.46 0 253.87 311.16 39553 +1947 64 10.44 4.44 8.79 0 292.83 309.75 39753 +1947 65 9.36 3.36 7.71 0 274.18 312.84 39953 +1947 66 9.81 3.81 8.16 0 281.82 313.72 40154 +1947 67 10.19 4.19 8.54 0 288.42 314.81 40355 +1947 68 9.93 3.93 8.28 0.33 283.89 249.47 40556 +1947 69 13.42 7.42 11.77 0.3 350.05 245.83 40758 +1947 70 12.73 6.73 11.08 0.09 336.02 247.3 40960 +1947 71 6.92 0.92 5.27 0 235.74 324.99 41163 +1947 72 8.33 2.33 6.68 0 257.34 325.07 41366 +1947 73 10.82 4.82 9.17 0.05 299.65 252.59 41569 +1947 74 8.31 2.31 6.66 0 257.03 328.24 41772 +1947 75 6.92 0.92 5.27 0.11 235.74 258.74 41976 +1947 76 6.3 0.3 4.65 0.73 226.75 260.48 42179 +1947 77 4.47 -1.53 2.82 0.4 201.91 263.33 42383 +1947 78 0.74 -5.26 -0.91 0 158.43 344.31 42587 +1947 79 -0.73 -6.73 -2.38 0 143.67 348.06 42791 +1947 80 2 -4 0.35 0 172.11 348.06 42996 +1947 81 2.93 -3.07 1.28 0 182.85 349.37 43200 +1947 82 8.44 2.44 6.79 0 259.1 344.72 43404 +1947 83 8.74 2.74 7.09 0.1 263.94 268.08 43608 +1947 84 12.41 6.41 10.76 0.04 329.68 264.29 43812 +1947 85 12.44 6.44 10.79 0.48 330.27 264.81 44016 +1947 86 12.18 6.18 10.53 0 325.18 343.91 44220 +1947 87 15.84 9.84 14.19 0 403.31 308.1 44424 +1947 88 11.66 5.66 10.01 0 315.21 318.66 44627 +1947 89 9.95 3.95 8.3 0.1 284.24 242.82 44831 +1947 90 11.77 5.77 10.12 0.44 317.3 242.31 45034 +1947 91 17.33 11.33 15.68 0.26 439.42 235.17 45237 +1947 92 15.95 9.95 14.3 0.55 405.89 239.27 45439 +1947 93 12.06 6.06 10.41 0.5 322.85 246.92 45642 +1947 94 11.85 5.85 10.2 0.05 318.82 248.81 45843 +1947 95 9.46 3.46 7.81 0.07 275.86 253.45 46045 +1947 96 11.66 5.66 10.01 0.68 315.21 252.25 46246 +1947 97 14.81 8.81 13.16 0 379.85 332.05 46446 +1947 98 16.56 10.56 14.91 0.07 420.43 247.42 46647 +1947 99 12.35 6.35 10.7 0 328.5 341.05 46846 +1947 100 10.47 4.47 8.82 0.06 293.37 259.8 47045 +1947 101 13.57 7.57 11.92 0 353.17 342.46 47243 +1947 102 10.97 4.97 9.32 0.08 302.38 262.03 47441 +1947 103 14.04 8.04 12.39 0.01 363.09 258.88 47638 +1947 104 16.67 10.67 15.02 0 423.1 340.8 47834 +1947 105 18.47 12.47 16.82 0 468.88 337.73 48030 +1947 106 19.81 13.81 18.16 0 505.63 335.37 48225 +1947 107 16.37 10.37 14.72 0.24 415.85 259.92 48419 +1947 108 19.28 13.28 17.63 0 490.81 340.26 48612 +1947 109 20.38 14.38 18.73 0 522 338.4 48804 +1947 110 21.94 15.94 20.29 0 569.1 334.51 48995 +1947 111 19.23 13.23 17.58 0 489.43 344.82 49185 +1947 112 19 13 17.35 0 483.13 346.98 49374 +1947 113 18.19 12.19 16.54 0.16 461.49 262.98 49561 +1947 114 15.11 9.11 13.46 0.03 386.56 270.13 49748 +1947 115 19.67 13.67 18.02 0.1 501.68 261.79 49933 +1947 116 19.53 13.53 17.88 0.44 497.76 263 50117 +1947 117 15.42 9.42 13.77 0 393.6 363.35 50300 +1947 118 13.03 7.03 11.38 0 342.06 370.14 50481 +1947 119 11.25 5.25 9.6 0 307.53 374.95 50661 +1947 120 10.94 4.94 9.29 0 301.83 376.73 50840 +1947 121 17.7 11.7 16.05 0 448.8 362.07 51016 +1947 122 19.2 13.2 17.55 0 488.61 358.79 51191 +1947 123 21.67 15.67 20.02 0 560.7 351.55 51365 +1947 124 23.2 17.2 21.55 0 609.73 346.86 51536 +1947 125 20.81 14.81 19.16 0 534.64 356.54 51706 +1947 126 19.44 13.44 17.79 0 495.25 362.02 51874 +1947 127 20.2 14.2 18.55 0 516.78 360.42 52039 +1947 128 18.9 12.9 17.25 0 480.41 365.55 52203 +1947 129 22.26 16.26 20.61 0.25 579.19 266.21 52365 +1947 130 19.72 13.72 18.07 0 503.09 364.56 52524 +1947 131 20.42 14.42 18.77 0 523.16 363.02 52681 +1947 132 20.3 14.3 18.65 0.06 519.67 273.17 52836 +1947 133 17.82 11.82 16.17 0.66 451.88 279.52 52989 +1947 134 14.63 8.63 12.98 0.18 375.88 286.44 53138 +1947 135 14.33 8.33 12.68 0 369.33 383.34 53286 +1947 136 16.16 10.16 14.51 0.14 410.84 284.52 53430 +1947 137 16.55 10.55 14.9 0 420.19 379.02 53572 +1947 138 14.91 8.91 13.26 0 382.08 383.89 53711 +1947 139 11.35 5.35 9.7 0 309.39 392.54 53848 +1947 140 14.12 8.12 12.47 0.49 364.8 290.24 53981 +1947 141 18.13 12.13 16.48 0 459.92 376.7 54111 +1947 142 16 10 14.35 0 407.06 383.22 54238 +1947 143 17.65 11.65 16 0 447.52 379.15 54362 +1947 144 22.46 16.46 20.81 0.72 585.58 272.55 54483 +1947 145 26.01 20.01 24.36 0 709.28 348.73 54600 +1947 146 21.27 15.27 19.62 0.27 548.44 276.5 54714 +1947 147 19.01 13.01 17.36 0.03 483.41 282.6 54824 +1947 148 20.6 14.6 18.95 0 528.43 371.88 54931 +1947 149 19.14 13.14 17.49 1.96 486.96 282.8 55034 +1947 150 16.13 10.13 14.48 0.95 410.13 289.7 55134 +1947 151 17.27 11.27 15.62 0.42 437.91 287.61 55229 +1947 152 19.85 13.85 18.2 1.45 506.77 281.68 55321 +1947 153 17.85 11.85 16.2 0.57 452.65 286.6 55409 +1947 154 21.75 15.75 20.1 0.66 563.17 277.06 55492 +1947 155 23.37 17.37 21.72 0 615.39 363.27 55572 +1947 156 20.08 14.08 18.43 0 513.33 375.86 55648 +1947 157 22.03 16.03 20.38 0 571.92 369.03 55719 +1947 158 23.14 17.14 21.49 0 607.74 364.86 55786 +1947 159 22.05 16.05 20.4 0 572.55 369.36 55849 +1947 160 21.31 15.31 19.66 0.08 549.66 279.22 55908 +1947 161 18.22 12.22 16.57 0.16 462.28 287.02 55962 +1947 162 19.75 13.75 18.1 0 503.94 377.86 56011 +1947 163 18.57 12.57 16.92 0 471.54 381.88 56056 +1947 164 21.23 15.23 19.58 0 547.23 372.96 56097 +1947 165 22.92 16.92 21.27 0 600.49 366.62 56133 +1947 166 20.7 14.7 19.05 0.01 531.38 281.28 56165 +1947 167 23.88 17.88 22.23 0.53 632.66 272.03 56192 +1947 168 22.08 16.08 20.43 0.76 573.49 277.5 56214 +1947 169 26.25 20.25 24.6 0.44 718.38 264.1 56231 +1947 170 26.11 20.11 24.46 0.28 713.06 264.6 56244 +1947 171 27.79 21.79 26.14 0.84 779.19 258.37 56252 +1947 172 26.73 20.73 25.08 0.6 736.89 262.39 56256 +1947 173 25.31 19.31 23.66 0.3 683.28 267.42 56255 +1947 174 26.06 20.06 24.41 0.4 711.17 264.74 56249 +1947 175 23.47 17.47 21.82 0 618.75 364.42 56238 +1947 176 24.17 18.17 22.52 0 642.66 361.45 56223 +1947 177 24.02 18.02 22.37 0.24 637.47 271.49 56203 +1947 178 20.99 14.99 19.34 0 540 373.85 56179 +1947 179 22.5 16.5 20.85 0 586.86 368.1 56150 +1947 180 19.91 13.91 18.26 0.51 508.47 283.03 56116 +1947 181 20.26 14.26 18.61 0.39 518.51 282.08 56078 +1947 182 23.89 17.89 22.24 0 633 362.14 56035 +1947 183 28.84 22.84 27.19 0 823.1 338.07 55987 +1947 184 27.63 21.63 25.98 0.05 772.68 258.28 55935 +1947 185 24.13 18.13 22.48 0 641.27 360.72 55879 +1947 186 22.73 16.73 21.08 0 594.29 366.21 55818 +1947 187 24.77 18.77 23.12 0 663.78 357.52 55753 +1947 188 27.39 21.39 25.74 0.21 763 258.64 55684 +1947 189 28.21 22.21 26.56 0.01 796.51 255.32 55611 +1947 190 31.6 25.6 29.95 0 948.58 320.4 55533 +1947 191 31.56 25.56 29.91 0.22 946.66 240.31 55451 +1947 192 30.31 24.31 28.66 0.19 888.07 245.84 55366 +1947 193 30.04 24.04 28.39 0.13 875.82 246.85 55276 +1947 194 28.77 22.77 27.12 0 820.11 336.09 55182 +1947 195 28.13 22.13 26.48 0.69 793.19 254.45 55085 +1947 196 23.54 17.54 21.89 0 621.1 360.26 54984 +1947 197 21.58 15.58 19.93 0 557.92 367.42 54879 +1947 198 23.01 17.01 21.36 0.01 603.45 271.15 54770 +1947 199 24.4 18.4 22.75 0.13 650.69 266.59 54658 +1947 200 19.76 13.76 18.11 0.03 504.22 279.44 54542 +1947 201 18.24 12.24 16.59 1.3 462.8 282.69 54423 +1947 202 17.56 11.56 15.91 1.88 445.23 283.77 54301 +1947 203 19.29 13.29 17.64 0 491.09 372.57 54176 +1947 204 15.68 9.68 14.03 0.21 399.59 286.86 54047 +1947 205 18.69 12.69 17.04 0.46 474.75 280.06 53915 +1947 206 22.48 16.48 20.83 0 586.22 359.79 53780 +1947 207 20.59 14.59 18.94 0 528.14 366 53643 +1947 208 22.82 16.82 21.17 0.01 597.22 267.89 53502 +1947 209 22.51 16.51 20.86 0 587.18 357.74 53359 +1947 210 22.6 16.6 20.95 0 590.08 356.79 53213 +1947 211 23.33 17.33 21.68 0.14 614.06 264.88 53064 +1947 212 14.79 8.79 13.14 1.87 379.41 284.5 52913 +1947 213 13.57 7.57 11.92 0.25 353.17 286.05 52760 +1947 214 16.34 10.34 14.69 0 415.13 373.83 52604 +1947 215 16.79 10.79 15.14 0.56 426.03 278.94 52445 +1947 216 17.82 11.82 16.17 0 451.88 368 52285 +1947 217 23.27 17.27 21.62 0 612.06 348.64 52122 +1947 218 23.23 17.23 21.58 0 610.73 348 51958 +1947 219 25.49 19.49 23.84 0 689.89 337.57 51791 +1947 220 24.91 18.91 23.26 0 668.79 339.2 51622 +1947 221 22.99 16.99 21.34 0 602.79 346.01 51451 +1947 222 22.12 16.12 20.47 0 574.76 348.24 51279 +1947 223 22.75 16.75 21.1 0.04 594.94 258.59 51105 +1947 224 22.54 16.54 20.89 0 588.15 344.53 50929 +1947 225 22.61 16.61 20.96 0 590.41 343.15 50751 +1947 226 20.8 14.8 19.15 0 534.34 348.43 50572 +1947 227 22.45 16.45 20.8 0 585.26 341.37 50392 +1947 228 22.67 16.67 21.02 0 592.35 339.37 50210 +1947 229 25.67 19.67 24.02 0 696.55 326.09 50026 +1947 230 24.22 18.22 22.57 0 644.4 330.95 49842 +1947 231 24.89 18.89 23.24 0 668.07 326.79 49656 +1947 232 28.08 22.08 26.43 0 791.12 311.07 49469 +1947 233 28.74 22.74 27.09 0 818.83 306.46 49280 +1947 234 24.04 18.04 22.39 0 638.16 326.2 49091 +1947 235 29.22 23.22 27.57 0 839.5 301.34 48900 +1947 236 27.71 21.71 26.06 0 775.93 307.54 48709 +1947 237 26.52 20.52 24.87 0 728.75 311.48 48516 +1947 238 27.68 21.68 26.03 0 774.71 304.6 48323 +1947 239 27.73 21.73 26.08 0 776.75 302.97 48128 +1947 240 24.96 18.96 23.31 0.78 670.58 235.07 47933 +1947 241 22.66 16.66 21.01 0 592.02 320.49 47737 +1947 242 19.13 13.13 17.48 0 486.69 330.12 47541 +1947 243 21.38 15.38 19.73 0 551.79 321.34 47343 +1947 244 18.96 12.96 17.31 0 482.04 326.93 47145 +1947 245 16.93 10.93 15.28 0 429.47 330.52 46947 +1947 246 17.22 11.22 15.57 0 436.66 327.8 46747 +1947 247 19.89 13.89 18.24 0 507.9 318.61 46547 +1947 248 20.32 14.32 18.67 0.83 520.25 236.56 46347 +1947 249 22.53 16.53 20.88 0 587.83 306.31 46146 +1947 250 23.14 17.14 21.49 0 607.74 302.33 45945 +1947 251 19.41 13.41 17.76 0 494.41 312.03 45743 +1947 252 22.32 16.32 20.67 0 581.1 301 45541 +1947 253 26.17 20.17 24.52 0 715.34 284.81 45339 +1947 254 24.11 18.11 22.46 0 640.58 290.72 45136 +1947 255 21.54 15.54 19.89 0 556.69 297.2 44933 +1947 256 18.81 12.81 17.16 0 477.98 302.85 44730 +1947 257 24.58 18.58 22.93 0 657.03 282.68 44527 +1947 258 24.94 18.94 23.29 0 669.86 279.15 44323 +1947 259 25.96 19.96 24.31 0 707.39 273 44119 +1947 260 23.2 17.2 21.55 0 609.73 280.7 43915 +1947 261 20.49 14.49 18.84 0 525.2 286.68 43711 +1947 262 20.45 14.45 18.8 0 524.04 284.48 43507 +1947 263 19.82 13.82 18.17 0 505.92 283.82 43303 +1947 264 21.85 15.85 20.2 0 566.28 275.53 43099 +1947 265 25.65 19.65 24 0 695.8 260.6 42894 +1947 266 23.35 17.35 21.7 0 614.73 266.23 42690 +1947 267 21.12 15.12 19.47 0 543.91 270.42 42486 +1947 268 23.69 17.69 22.04 0 626.18 260.17 42282 +1947 269 26.37 20.37 24.72 0 722.97 248.49 42078 +1947 270 24.89 18.89 23.24 0 668.07 251.34 41875 +1947 271 26.72 20.72 25.07 0.04 736.5 181.77 41671 +1947 272 24.04 18.04 22.39 0 638.16 249.16 41468 +1947 273 25.16 19.16 23.51 0 677.81 243.11 41265 +1947 274 15.22 9.22 13.57 0 389.05 266.34 41062 +1947 275 13.32 7.32 11.67 0 347.99 267 40860 +1947 276 15.28 9.28 13.63 0 390.41 260.79 40658 +1947 277 15.78 9.78 14.13 0 401.91 257.19 40456 +1947 278 20.25 14.25 18.6 0 518.22 244.54 40255 +1947 279 19.14 13.14 17.49 0.05 486.96 183.37 40054 +1947 280 13.35 7.35 11.7 0 348.61 253.23 39854 +1947 281 18.63 12.63 16.98 0 473.14 240.45 39654 +1947 282 17.58 11.58 15.93 0 445.74 240.03 39455 +1947 283 13.14 7.14 11.49 0.01 344.3 183.96 39256 +1947 284 8.92 2.92 7.27 0 266.88 248.07 39058 +1947 285 10.58 4.58 8.93 0 295.33 243.3 38861 +1947 286 9.8 3.8 8.15 0 281.65 241.51 38664 +1947 287 5.11 -0.89 3.46 0 210.31 243.58 38468 +1947 288 7.64 1.64 5.99 0 246.57 238.21 38273 +1947 289 7.05 1.05 5.4 0 237.67 236.15 38079 +1947 290 5.38 -0.62 3.73 0.11 213.95 176.13 37885 +1947 291 7.05 1.05 5.4 0 237.67 230.48 37693 +1947 292 8.2 2.2 6.55 0 255.28 226.55 37501 +1947 293 11.56 5.56 9.91 0.33 313.32 164.84 37311 +1947 294 7.62 1.62 5.97 0.24 246.26 166.09 37121 +1947 295 11.97 5.97 10.32 0 321.12 213.54 36933 +1947 296 13.55 7.55 11.9 0 352.75 208.78 36745 +1947 297 14.55 8.55 12.9 0.01 374.12 153.46 36560 +1947 298 15.68 9.68 14.03 0.01 399.59 150.22 36375 +1947 299 14.95 8.95 13.3 0 382.97 198.71 36191 +1947 300 11.74 5.74 10.09 0.08 316.72 150.39 36009 +1947 301 9.6 3.6 7.95 0 278.23 200.48 35829 +1947 302 8.42 2.42 6.77 0.71 258.78 149.31 35650 +1947 303 8.77 2.77 7.12 0.17 264.42 147.1 35472 +1947 304 12.39 6.39 10.74 0 329.28 189.61 35296 +1947 305 9.82 3.82 8.17 0.74 282 142.38 35122 +1947 306 10.05 4.05 8.4 0 285.98 187.35 34950 +1947 307 7.06 1.06 5.41 0 237.82 187.71 34779 +1947 308 8.18 2.18 6.53 0.01 254.97 138.07 34610 +1947 309 8.13 2.13 6.48 0 254.18 181.81 34444 +1947 310 6.46 0.46 4.81 0 229.04 180.8 34279 +1947 311 7.03 1.03 5.38 0.36 237.37 133.6 34116 +1947 312 6.97 0.97 5.32 0.23 236.48 131.65 33956 +1947 313 8.28 2.28 6.63 0 256.55 172.28 33797 +1947 314 8.43 2.43 6.78 0 258.94 170.2 33641 +1947 315 8.34 2.34 6.69 0 257.5 167.75 33488 +1947 316 6.79 0.79 5.14 0 233.83 166.86 33337 +1947 317 9.13 3.13 7.48 0 270.34 162.68 33188 +1947 318 6.25 0.25 4.6 0 226.04 162.73 33042 +1947 319 4.18 -1.82 2.53 0 198.19 162.47 32899 +1947 320 6.89 0.89 5.24 0 235.3 158.67 32758 +1947 321 8.49 2.49 6.84 0 259.9 155.27 32620 +1947 322 9.39 3.39 7.74 0 274.68 152.69 32486 +1947 323 9.47 3.47 7.82 0 276.03 151.02 32354 +1947 324 9.54 3.54 7.89 0 277.21 148.92 32225 +1947 325 11.12 5.12 9.47 0 305.13 145.77 32100 +1947 326 14.85 8.85 13.2 0 380.74 140.34 31977 +1947 327 16.92 10.92 15.27 0 429.22 135.93 31858 +1947 328 14.99 8.99 13.34 0 383.87 136.47 31743 +1947 329 13.56 7.56 11.91 0 352.96 136.66 31631 +1947 330 17.19 11.19 15.54 0 435.91 130.89 31522 +1947 331 15.21 9.21 13.56 0.61 388.82 99.09 31417 +1947 332 12.38 6.38 10.73 0.62 329.09 100.2 31316 +1947 333 7.93 1.93 6.28 0 251.05 136.38 31218 +1947 334 6.18 0.18 4.53 0.01 225.05 102.39 31125 +1947 335 2.55 -3.45 0.9 0 178.39 137.49 31035 +1947 336 2.08 -3.92 0.43 0.06 173.01 102.48 30949 +1947 337 3.48 -2.52 1.83 0 189.47 134.24 30867 +1947 338 2.62 -3.38 0.97 0 179.21 133.75 30790 +1947 339 2.05 -3.95 0.4 0 172.67 133.24 30716 +1947 340 1.89 -4.11 0.24 0 170.88 132.58 30647 +1947 341 0.81 -5.19 -0.84 0 159.17 132.16 30582 +1947 342 1.35 -4.65 -0.3 0 164.93 131.15 30521 +1947 343 0.75 -5.25 -0.9 0.09 158.54 97.94 30465 +1947 344 5.57 -0.43 3.92 0.38 216.54 95.2 30413 +1947 345 6.3 0.3 4.65 0.3 226.75 94.54 30366 +1947 346 3.7 -2.3 2.05 0.52 192.17 95.27 30323 +1947 347 1.4 -4.6 -0.25 0.01 165.48 95.68 30284 +1947 348 5.59 -0.41 3.94 0 216.82 125 30251 +1947 349 5.92 -0.08 4.27 0.6 221.39 93.32 30221 +1947 350 2.74 -3.26 1.09 0.58 180.61 94.39 30197 +1947 351 4.51 -1.49 2.86 0.02 202.42 93.52 30177 +1947 352 5.83 -0.17 4.18 0.17 220.13 92.88 30162 +1947 353 7.21 1.21 5.56 0.18 240.06 92.17 30151 +1947 354 7.59 1.59 5.94 0.06 245.81 91.95 30145 +1947 355 6.82 0.82 5.17 0.71 234.27 92.33 30144 +1947 356 0.8 -5.2 -0.85 0.45 159.06 94.78 30147 +1947 357 6.65 0.65 5 0 231.79 123.31 30156 +1947 358 6.81 0.81 5.16 0.15 234.13 92.47 30169 +1947 359 2.6 -3.4 0.95 0 178.98 125.8 30186 +1947 360 3.64 -2.36 1.99 0.02 191.43 94.23 30208 +1947 361 7.03 1.03 5.38 0 237.37 123.95 30235 +1947 362 9.33 3.33 7.68 0 273.67 122.74 30267 +1947 363 9.77 3.77 8.12 0.98 281.14 92.23 30303 +1947 364 6.66 0.66 5.01 1.23 231.94 94.2 30343 +1947 365 8.94 2.94 7.29 0.22 267.2 93.42 30388 +1948 1 9.51 3.51 7.86 0.23 276.71 93.75 30438 +1948 2 12.8 6.8 11.15 1.95 337.42 92.13 30492 +1948 3 13.57 7.57 11.92 0.08 353.17 92.25 30551 +1948 4 11.16 5.16 9.51 1.47 305.87 94.62 30614 +1948 5 10.36 4.36 8.71 0.23 291.42 95.61 30681 +1948 6 13.42 7.42 11.77 0.18 350.05 94.13 30752 +1948 7 11.82 5.82 10.17 0.04 318.25 95.86 30828 +1948 8 12.51 6.51 10.86 0 331.65 128.62 30907 +1948 9 13.91 7.91 12.26 0.05 360.32 96.3 30991 +1948 10 11.95 5.95 10.3 1.76 320.74 98.73 31079 +1948 11 7.3 1.3 5.65 0.57 241.41 102.35 31171 +1948 12 2.48 -3.52 0.83 0.34 177.58 105.34 31266 +1948 13 -1.29 -7.29 -2.94 0 138.37 143.84 31366 +1948 14 -0.58 -6.58 -2.23 0 145.12 145.03 31469 +1948 15 0.23 -5.77 -1.42 0.51 153.17 109.6 31575 +1948 16 3.33 -2.67 1.68 0 187.64 145.82 31686 +1948 17 1.17 -4.83 -0.48 0 162.99 148.67 31800 +1948 18 6.81 0.81 5.16 0 234.13 147.13 31917 +1948 19 5.08 -0.92 3.43 0 209.91 150.25 32038 +1948 20 2.95 -3.05 1.3 0 183.09 153.15 32161 +1948 21 1.98 -4.02 0.33 0.11 171.89 116.78 32289 +1948 22 4.82 -1.18 3.17 0.04 206.47 116.81 32419 +1948 23 0.27 -5.73 -1.38 0 153.58 160.14 32552 +1948 24 3.82 -2.18 2.17 0 193.66 160.23 32688 +1948 25 2.57 -3.43 0.92 0.01 178.63 122.16 32827 +1948 26 3.28 -2.72 1.63 0 187.04 164.38 32969 +1948 27 2.22 -3.78 0.57 0.05 174.6 125.29 33114 +1948 28 2.35 -3.65 0.7 0 176.09 169.19 33261 +1948 29 9.6 3.6 7.95 0 278.23 166.06 33411 +1948 30 7.86 1.86 6.21 0.03 249.96 127.38 33564 +1948 31 8.26 2.26 6.61 0.04 256.23 128.88 33718 +1948 32 3.89 -2.11 2.24 0 194.54 177.34 33875 +1948 33 8.25 2.25 6.6 0 256.08 176.53 34035 +1948 34 7.27 1.27 5.62 0.01 240.96 134.68 34196 +1948 35 6.25 0.25 4.6 0.87 226.04 136.92 34360 +1948 36 10.85 4.85 9.2 0.76 300.2 135.51 34526 +1948 37 11.44 5.44 9.79 0.04 311.07 136.79 34694 +1948 38 8.41 2.41 6.76 0.18 258.62 141.2 34863 +1948 39 5.81 -0.19 4.16 0.1 219.85 144.87 35035 +1948 40 4.14 -1.86 2.49 0.13 197.68 147.8 35208 +1948 41 1.74 -4.26 0.09 0.04 169.21 151.02 35383 +1948 42 2.38 -3.62 0.73 0 176.43 203.51 35560 +1948 43 1.75 -4.25 0.1 0.01 169.32 154.99 35738 +1948 44 1.44 -4.56 -0.21 0.12 165.91 157.08 35918 +1948 45 -1.88 -7.88 -3.53 0.19 132.96 197.58 36099 +1948 46 0.47 -5.53 -1.18 0.02 155.63 198.39 36282 +1948 47 1.89 -4.11 0.24 0.16 170.88 199.44 36466 +1948 48 4.6 -1.4 2.95 0 203.59 218.13 36652 +1948 49 1.57 -4.43 -0.08 0 167.33 223.19 36838 +1948 50 3.3 -2.7 1.65 0 187.28 224.62 37026 +1948 51 2.16 -3.84 0.51 0 173.92 228.46 37215 +1948 52 3.34 -2.66 1.69 0 187.77 230.42 37405 +1948 53 5.43 -0.57 3.78 0 214.63 231.62 37596 +1948 54 7.86 1.86 6.21 0.43 249.96 173.98 37788 +1948 55 2.9 -3.1 1.25 0.52 182.5 179.65 37981 +1948 56 2.63 -3.37 0.98 0 179.33 242.45 38175 +1948 57 1.94 -4.06 0.29 0 171.44 245.89 38370 +1948 58 2.19 -3.81 0.54 0.82 174.26 186.5 38565 +1948 59 -2.08 -8.08 -3.73 0.03 131.17 224.83 38761 +1948 60 5.53 -0.47 3.88 0 215.99 251.4 38958 +1948 61 7.54 1.54 5.89 0 245.04 252.24 39156 +1948 62 10.63 4.63 8.98 0 296.23 251.19 39355 +1948 63 10.9 4.9 9.25 0.04 301.11 190.34 39553 +1948 64 8.67 2.67 7.02 0 262.8 259.58 39753 +1948 65 7.6 1.6 5.95 0 245.96 263.73 39953 +1948 66 4.35 -1.65 2.7 0 200.36 269.88 40154 +1948 67 7.17 1.17 5.52 0 239.46 269.86 40355 +1948 68 7.75 1.75 6.1 0 248.26 272.05 40556 +1948 69 7.72 1.72 6.07 0.08 247.8 206.03 40758 +1948 70 8.52 2.52 6.87 0.01 260.38 207.42 40960 +1948 71 12.3 6.3 10.65 0 327.52 273.99 41163 +1948 72 8.57 2.57 6.92 0 261.19 282.21 41366 +1948 73 5.97 -0.03 4.32 0 222.09 288 41569 +1948 74 10.89 4.89 9.24 0 300.92 284.33 41772 +1948 75 12.01 6.01 10.36 0.04 321.89 213.94 41976 +1948 76 11.4 5.4 9.75 0 310.32 288.84 42179 +1948 77 10.98 4.98 9.33 0 302.56 292.07 42383 +1948 78 7.77 1.77 6.12 0 248.57 299.28 42587 +1948 79 12.7 6.7 11.05 0 335.42 294.54 42791 +1948 80 14.19 8.19 12.54 0 366.3 294.28 42996 +1948 81 7.99 1.99 6.34 0 251.99 306.85 43200 +1948 82 5 -1 3.35 0 208.85 313.15 43404 +1948 83 6.9 0.9 5.25 0 235.45 313.42 43608 +1948 84 5.53 -0.47 3.88 0 215.99 317.63 43812 +1948 85 9.78 3.78 8.13 0 281.31 314.48 44016 +1948 86 13.11 7.11 11.46 0.06 343.69 233.41 44220 +1948 87 12.32 6.32 10.67 0 327.91 315.17 44424 +1948 88 10.56 4.56 8.91 0 294.97 320.52 44627 +1948 89 9.46 3.46 7.81 0 275.86 324.53 44831 +1948 90 11.31 5.31 9.66 0 308.64 323.88 45034 +1948 91 15.45 9.45 13.8 0 394.29 317.98 45237 +1948 92 15.22 9.22 13.57 0.14 389.05 240.51 45439 +1948 93 14.65 8.65 13 0.51 376.32 243.06 45642 +1948 94 11.25 5.25 9.6 0.54 307.53 249.61 45843 +1948 95 11.01 5.01 9.36 0.01 303.11 251.53 46045 +1948 96 16.28 10.28 14.63 0.41 413.7 245 46246 +1948 97 13.22 7.22 11.57 0.6 345.94 251.54 46446 +1948 98 11.45 5.45 9.8 0.27 311.26 255.54 46647 +1948 99 9.5 3.5 7.85 0.17 276.54 259.55 46846 +1948 100 10.51 4.51 8.86 0.42 294.08 259.75 47045 +1948 101 10.06 4.06 8.41 0 286.15 349.04 47243 +1948 102 14.14 8.14 12.49 0 365.23 343.13 47441 +1948 103 16.03 10.03 14.38 0 407.77 340.61 47638 +1948 104 18.06 12.06 16.41 0 458.09 337.13 47834 +1948 105 16.19 10.19 14.54 0.01 411.56 257.82 48030 +1948 106 15.24 9.24 13.59 0 389.5 347.67 48225 +1948 107 17.57 11.57 15.92 0 445.49 343.43 48419 +1948 108 19.33 13.33 17.68 0.1 492.19 255.08 48612 +1948 109 17.38 11.38 15.73 0.08 440.68 260.41 48804 +1948 110 16.82 10.82 15.17 1.42 426.76 262.56 48995 +1948 111 16.56 10.56 14.91 0.13 420.43 264.21 49185 +1948 112 17.88 11.88 16.23 0 453.43 350.21 49374 +1948 113 14.19 8.19 12.54 0.07 366.3 270.62 49561 +1948 114 14.5 8.5 12.85 0.18 373.03 271.21 49748 +1948 115 11.31 5.31 9.66 0 308.64 369.74 49933 +1948 116 12.11 6.11 10.46 0 323.82 369.41 50117 +1948 117 9.81 3.81 8.16 0.21 281.82 281.28 50300 +1948 118 15.64 9.64 13.99 0.02 398.66 273.08 50481 +1948 119 18.19 12.19 16.54 0 461.49 358.41 50661 +1948 120 18.74 12.74 17.09 0 476.09 357.93 50840 +1948 121 23.26 17.26 21.61 0 611.72 343.5 51016 +1948 122 23.36 17.36 21.71 0 615.06 344.24 51191 +1948 123 20.86 14.86 19.21 0.01 536.12 265.78 51365 +1948 124 17.1 11.1 15.45 0.28 433.67 275.25 51536 +1948 125 15.73 9.73 14.08 0 400.75 371.61 51706 +1948 126 21.01 15.01 19.36 0 540.6 356.81 51874 +1948 127 24.92 18.92 23.27 0 669.14 342.49 52039 +1948 128 21.88 15.88 20.23 0.12 567.22 266.65 52203 +1948 129 20.31 14.31 18.66 0.54 519.96 271.38 52365 +1948 130 24.09 18.09 22.44 0.06 639.89 261.36 52524 +1948 131 19.44 13.44 17.79 0.12 495.25 274.68 52681 +1948 132 18.23 12.23 16.58 0 462.54 370.79 52836 +1948 133 18.55 12.55 16.9 0.29 471 277.89 52989 +1948 134 17.8 11.8 16.15 0 451.37 373.46 53138 +1948 135 17.07 11.07 15.42 0 432.93 376.24 53286 +1948 136 17.25 11.25 15.6 0 437.41 376.37 53430 +1948 137 16.55 10.55 14.9 0 420.19 379.02 53572 +1948 138 16.91 10.91 15.26 0 428.97 378.63 53711 +1948 139 15.61 9.61 13.96 0 397.97 382.81 53848 +1948 140 16.93 10.93 15.28 0 429.47 379.75 53981 +1948 141 18.22 12.22 16.57 0 462.28 376.43 54111 +1948 142 14.86 8.86 13.21 0 380.96 386.15 54238 +1948 143 15.79 9.79 14.14 0.19 402.14 288.23 54362 +1948 144 18.52 12.52 16.87 0 470.21 377.01 54483 +1948 145 19.8 13.8 18.15 0 505.35 373.39 54600 +1948 146 20.3 14.3 18.65 0.02 519.67 279.05 54714 +1948 147 23.37 17.37 21.72 0 615.39 361.08 54824 +1948 148 23.6 17.6 21.95 0.16 623.13 270.38 54931 +1948 149 21.65 15.65 20 0 560.08 368.42 55034 +1948 150 20.02 14.02 18.37 0.26 511.61 280.88 55134 +1948 151 18.51 12.51 16.86 1.92 469.94 284.83 55229 +1948 152 16.43 10.43 14.78 0.61 417.29 289.46 55321 +1948 153 19.62 13.62 17.97 0.58 500.28 282.43 55409 +1948 154 17.58 11.58 15.93 0 445.74 383.25 55492 +1948 155 16.38 10.38 14.73 0 416.09 386.85 55572 +1948 156 20.3 14.3 18.65 0.27 519.67 281.33 55648 +1948 157 21.63 15.63 19.98 0.27 559.46 277.89 55719 +1948 158 23.14 17.14 21.49 0 607.74 364.86 55786 +1948 159 24.56 18.56 22.91 0.01 656.32 269.35 55849 +1948 160 23.39 17.39 21.74 0.04 616.06 273.19 55908 +1948 161 21 15 19.35 0 540.3 373.48 55962 +1948 162 22.75 16.75 21.1 0.29 594.94 275.21 56011 +1948 163 20.2 14.2 18.55 1.01 516.78 282.41 56056 +1948 164 23.16 17.16 21.51 0.08 608.4 274.17 56097 +1948 165 25.91 19.91 24.26 0.01 705.51 265.23 56133 +1948 166 20.48 14.48 18.83 0.18 524.91 281.85 56165 +1948 167 23.21 17.21 21.56 0 610.06 365.48 56192 +1948 168 20.53 14.53 18.88 0 526.38 375.65 56214 +1948 169 18.89 12.89 17.24 0 480.14 381.13 56231 +1948 170 20.57 14.57 18.92 0 527.55 375.53 56244 +1948 171 20.56 14.56 18.91 0.65 527.26 281.71 56252 +1948 172 18.3 12.3 16.65 1.28 464.38 287.27 56256 +1948 173 18.43 12.43 16.78 0.05 467.81 286.96 56255 +1948 174 21.72 15.72 20.07 0.11 562.24 278.49 56249 +1948 175 19.76 13.76 18.11 0.13 504.22 283.66 56238 +1948 176 20.84 14.84 19.19 0.82 535.53 280.84 56223 +1948 177 18.09 12.09 16.44 1.01 458.88 287.55 56203 +1948 178 20.91 14.91 19.26 2.54 537.61 280.6 56179 +1948 179 17.27 11.27 15.62 1.55 437.91 289.31 56150 +1948 180 13.5 7.5 11.85 1.57 351.71 296.55 56116 +1948 181 12.35 6.35 10.7 0.07 328.5 298.42 56078 +1948 182 14.12 8.12 12.47 0.06 364.8 295.28 56035 +1948 183 13.45 7.45 11.8 1.45 350.68 296.33 55987 +1948 184 16.54 10.54 14.89 1.31 419.95 290.35 55935 +1948 185 14.07 8.07 12.42 1.32 363.73 295.05 55879 +1948 186 19.53 13.53 17.88 0 497.76 377.74 55818 +1948 187 21.52 15.52 19.87 0 556.07 370.63 55753 +1948 188 25.02 19.02 23.37 0 672.74 356.15 55684 +1948 189 24.72 18.72 23.07 0.06 661.99 267.98 55611 +1948 190 24.98 18.98 23.33 0.77 671.3 266.85 55533 +1948 191 26.08 20.08 24.43 0 711.92 350.49 55451 +1948 192 26.24 20.24 24.59 0.04 718 262.08 55366 +1948 193 24.57 18.57 22.92 0 656.67 356.79 55276 +1948 194 21.54 15.54 19.89 0.31 556.69 276.52 55182 +1948 195 22.64 16.64 20.99 0.25 591.38 273.19 55085 +1948 196 21.62 15.62 19.97 0.5 559.15 275.79 54984 +1948 197 21.21 15.21 19.56 0 546.63 368.76 54879 +1948 198 19.36 13.36 17.71 0.67 493.03 280.99 54770 +1948 199 20.43 14.43 18.78 0.28 523.45 278.05 54658 +1948 200 22.73 16.73 21.08 0.62 594.29 271.42 54542 +1948 201 18.43 12.43 16.78 0.24 467.81 282.25 54423 +1948 202 17.34 11.34 15.69 0.06 439.67 284.25 54301 +1948 203 16.26 10.26 14.61 0.2 413.22 286.11 54176 +1948 204 13.98 7.98 12.33 0.11 361.81 290.01 54047 +1948 205 15.89 9.89 14.24 1.26 404.48 286.05 53915 +1948 206 16.06 10.06 14.41 0.48 408.48 285.28 53780 +1948 207 17.34 11.34 15.69 0.65 439.67 282.14 53643 +1948 208 20.62 14.62 18.97 0.13 529.02 273.93 53502 +1948 209 23.08 17.08 21.43 0.05 605.76 266.65 53359 +1948 210 27.12 21.12 25.47 0 752.22 337.12 53213 +1948 211 27.29 21.29 25.64 0.92 758.99 251.66 53064 +1948 212 26.25 20.25 24.6 0.31 718.38 254.84 52913 +1948 213 31 25 29.35 0 920.02 313.87 52760 +1948 214 30.7 24.7 29.05 0 906.01 314.98 52604 +1948 215 29.71 23.71 28.06 0 861.05 320.06 52445 +1948 216 29.78 23.78 28.13 0 864.16 318.73 52285 +1948 217 27.23 21.23 25.58 0.74 756.6 248.44 52122 +1948 218 21.44 15.44 19.79 0 553.62 354.67 51958 +1948 219 22.53 16.53 20.88 0 587.83 349.66 51791 +1948 220 21.2 15.2 19.55 0.01 546.32 265.16 51622 +1948 221 17.14 11.14 15.49 0 434.67 365.14 51451 +1948 222 16.92 10.92 15.27 0.25 429.22 273.51 51279 +1948 223 16.27 10.27 14.62 0 413.46 365.24 51105 +1948 224 16.96 10.96 15.31 0 430.2 362.33 50929 +1948 225 17.81 11.81 16.16 0 451.62 358.81 50751 +1948 226 22.37 16.37 20.72 0 582.7 342.92 50572 +1948 227 23.58 17.58 21.93 0.12 622.45 252.81 50392 +1948 228 18.61 12.61 16.96 0.06 472.61 264.62 50210 +1948 229 23.19 17.19 21.54 0.2 609.4 252.15 50026 +1948 230 22.32 16.32 20.67 0.08 581.1 253.64 49842 +1948 231 22.54 16.54 20.89 0 588.15 335.95 49656 +1948 232 23.27 17.27 21.62 0.97 612.06 248.94 49469 +1948 233 24.18 18.18 22.53 0.24 643.01 245.26 49280 +1948 234 21.87 15.87 20.22 0.46 566.91 250.68 49091 +1948 235 20.87 14.87 19.22 0 536.42 336.15 48900 +1948 236 26.6 20.6 24.95 0.98 731.84 234.5 48709 +1948 237 26.57 20.57 24.92 0.11 730.68 233.44 48516 +1948 238 27.78 21.78 26.13 2.24 778.79 228.09 48323 +1948 239 22.58 16.58 20.93 0.72 589.44 243.12 48128 +1948 240 19.18 13.18 17.53 0 488.06 333.43 47933 +1948 241 16.7 10.7 15.05 0 423.83 338.44 47737 +1948 242 20.97 14.97 19.32 0 539.4 324.5 47541 +1948 243 22.47 16.47 20.82 0 585.9 317.66 47343 +1948 244 17.49 11.49 15.84 0 443.46 330.94 47145 +1948 245 16.27 10.27 14.62 0.27 413.46 249.11 46947 +1948 246 18.23 12.23 16.58 0.59 462.54 243.87 46747 +1948 247 16.8 10.8 15.15 0 426.27 326.99 46547 +1948 248 16.92 10.92 15.27 0.26 429.22 243.55 46347 +1948 249 16.03 10.03 14.38 0 407.77 324.8 46146 +1948 250 18.85 12.85 17.2 0 479.06 315.68 45945 +1948 251 23.14 17.14 21.49 0 607.74 300.3 45743 +1948 252 24.19 18.19 22.54 0 643.35 294.47 45541 +1948 253 21.53 15.53 19.88 0 556.38 301.5 45339 +1948 254 23.53 17.53 21.88 0 620.77 292.79 45136 +1948 255 22.33 16.33 20.68 0 581.42 294.68 44933 +1948 256 26.86 20.86 25.21 0 741.97 275.8 44730 +1948 257 26.83 20.83 25.18 0 740.8 273.94 44527 +1948 258 28.37 22.37 26.72 0.17 803.2 198.89 44323 +1948 259 22.88 16.88 21.23 0.45 599.18 213.03 44119 +1948 260 20.29 14.29 18.64 0.02 519.38 217.23 43915 +1948 261 20.46 14.46 18.81 0 524.33 286.77 43711 +1948 262 20.51 14.51 18.86 0 525.79 284.32 43507 +1948 263 19.22 13.22 17.57 0.59 489.16 214.06 43303 +1948 264 22.32 16.32 20.67 0 581.1 274.1 43099 +1948 265 19.31 13.31 17.66 0 491.64 280.34 42894 +1948 266 14.78 8.78 13.13 0.13 379.19 216.12 42690 +1948 267 14.43 8.43 12.78 0.18 371.5 214.61 42486 +1948 268 16.01 10.01 14.36 0.17 407.3 210.31 42282 +1948 269 15.94 9.94 14.29 1.43 405.65 208.54 42078 +1948 270 14.05 8.05 12.4 0.13 363.3 209.33 41875 +1948 271 16.42 10.42 14.77 0 417.05 271.82 41671 +1948 272 13.29 7.29 11.64 0.05 347.37 206.31 41468 +1948 273 16.15 10.15 14.5 0 410.61 267.16 41265 +1948 274 10.53 4.53 8.88 0.16 294.44 205.63 41062 +1948 275 12.21 6.21 10.56 0 325.76 268.83 40860 +1948 276 11.03 5.03 9.38 1.15 303.48 200.92 40658 +1948 277 12.59 6.59 10.94 0 333.23 262.82 40456 +1948 278 13.07 7.07 11.42 0 342.87 259.16 40255 +1948 279 9.99 3.99 8.34 0 284.93 260.89 40054 +1948 280 13.11 7.11 11.46 0.07 343.69 190.21 39854 +1948 281 11.77 5.77 10.12 0.08 317.3 189.71 39654 +1948 282 14.51 8.51 12.86 0 373.25 245.83 39455 +1948 283 8.56 2.56 6.91 0 261.02 251.57 39256 +1948 284 11.15 5.15 9.5 0 305.68 245.19 39058 +1948 285 8.25 2.25 6.6 0 256.08 246.17 38861 +1948 286 8.24 2.24 6.59 0.5 255.92 182.53 38664 +1948 287 11.56 5.56 9.91 0.02 313.32 177.17 38468 +1948 288 13.93 7.93 12.28 0 360.75 229.94 38273 +1948 289 14.72 8.72 13.07 0.26 377.86 169.54 38079 +1948 290 15.86 9.86 14.21 1.2 403.78 165.98 37885 +1948 291 15.84 9.84 14.19 0.37 403.31 164.02 37693 +1948 292 16.69 10.69 15.04 0.04 423.59 160.92 37501 +1948 293 18.34 12.34 16.69 0 465.43 208.81 37311 +1948 294 18.26 12.26 16.61 0 463.33 206.17 37121 +1948 295 19.5 13.5 17.85 0 496.92 200.96 36933 +1948 296 17.58 11.58 15.93 0.06 445.74 151.66 36745 +1948 297 17.9 11.9 16.25 0.58 453.94 149.24 36560 +1948 298 18.49 12.49 16.84 0 469.41 195.38 36375 +1948 299 18.17 12.17 16.52 0.09 460.97 144.98 36191 +1948 300 14.75 8.75 13.1 0.58 378.52 147.3 36009 +1948 301 16.94 10.94 15.29 0.06 429.71 142.85 35829 +1948 302 13.44 7.44 11.79 0.15 350.47 144.92 35650 +1948 303 13.1 7.1 11.45 0 343.48 191.13 35472 +1948 304 16.29 10.29 14.64 0.61 413.94 138.09 35296 +1948 305 8.63 2.63 6.98 0 262.15 191.05 35122 +1948 306 8.72 2.72 7.07 0 263.61 188.7 34950 +1948 307 8.15 2.15 6.5 0.33 254.5 140.05 34779 +1948 308 7.22 1.22 5.57 0 240.2 184.95 34610 +1948 309 8.52 2.52 6.87 0 260.38 181.45 34444 +1948 310 9.17 3.17 7.52 0 271 178.39 34279 +1948 311 11.91 5.91 10.26 0.62 319.97 130.01 34116 +1948 312 6.75 0.75 5.1 0 233.25 175.72 33956 +1948 313 8.61 2.61 6.96 0 261.83 171.99 33797 +1948 314 10.37 4.37 8.72 0 291.59 168.36 33641 +1948 315 11.49 5.49 9.84 0 312.01 164.69 33488 +1948 316 9.1 3.1 7.45 0 269.84 164.89 33337 +1948 317 7.53 1.53 5.88 0 244.89 164.06 33188 +1948 318 7.18 1.18 5.53 0 239.61 162.01 33042 +1948 319 10.62 4.62 8.97 0 296.05 157.28 32899 +1948 320 10.34 4.34 8.69 0 291.06 155.7 32758 +1948 321 10.89 4.89 9.24 0 300.92 153.09 32620 +1948 322 6.78 0.78 5.13 0 233.69 154.82 32486 +1948 323 6.47 0.47 4.82 0.24 229.19 115.07 32354 +1948 324 4.68 -1.32 3.03 0 204.63 152.61 32225 +1948 325 4.12 -1.88 2.47 0 197.43 151.23 32100 +1948 326 3.55 -2.45 1.9 0 190.33 150.1 31977 +1948 327 2.93 -3.07 1.28 0.26 182.85 111.45 31858 +1948 328 0.11 -5.89 -1.54 0 151.95 148.05 31743 +1948 329 0.14 -5.86 -1.51 0 152.26 146.52 31631 +1948 330 -0.19 -6.19 -1.84 0.01 148.95 150.81 31522 +1948 331 5.01 -0.99 3.36 1.02 208.98 105.83 31417 +1948 332 5.23 -0.77 3.58 0 211.92 139.32 31316 +1948 333 9.86 3.86 8.21 0.02 282.68 101.13 31218 +1948 334 7.49 1.49 5.84 0 244.28 135.61 31125 +1948 335 0.15 -5.85 -1.5 0 152.36 138.64 31035 +1948 336 1.76 -4.24 0.11 0 169.43 136.8 30949 +1948 337 -2.25 -8.25 -3.9 0 129.67 136.85 30867 +1948 338 0.36 -5.64 -1.29 0 154.5 134.83 30790 +1948 339 -1.02 -7.02 -2.67 0.02 140.9 144 30716 +1948 340 -0.26 -6.26 -1.91 0.32 148.25 144.3 30647 +1948 341 2.54 -3.46 0.89 0 178.28 175.23 30582 +1948 342 4.72 -1.28 3.07 0 205.16 172.75 30521 +1948 343 4.89 -1.11 3.24 0 207.39 128.47 30465 +1948 344 5.91 -0.09 4.26 0 221.25 126.72 30413 +1948 345 5.49 -0.51 3.84 0 215.45 126.55 30366 +1948 346 3.48 -2.52 1.83 0 189.47 127.14 30323 +1948 347 3.16 -2.84 1.51 0 185.59 126.71 30284 +1948 348 5.55 -0.45 3.9 0 216.27 125.03 30251 +1948 349 6.05 0.05 4.4 0 223.21 124.34 30221 +1948 350 4.92 -1.08 3.27 0.03 207.79 93.51 30197 +1948 351 -0.78 -6.78 -2.43 0 143.19 127.2 30177 +1948 352 1.32 -4.68 -0.33 0 164.61 126.22 30162 +1948 353 2.1 -3.9 0.45 0 173.24 125.79 30151 +1948 354 5.18 -0.82 3.53 0 211.25 124.13 30145 +1948 355 -0.06 -6.06 -1.71 0 150.24 126.71 30144 +1948 356 -5.7 -11.7 -7.35 0 102.2 128.67 30147 +1948 357 -3.26 -9.26 -4.91 0 121.03 127.99 30156 +1948 358 -2.28 -8.28 -3.93 0.18 129.41 140.13 30169 +1948 359 -4.62 -10.62 -6.27 0.33 110.2 141.82 30186 +1948 360 -3.16 -9.16 -4.81 0.07 121.87 141.94 30208 +1948 361 -4.76 -10.76 -6.41 0 109.13 174.88 30235 +1948 362 -2.3 -8.3 -3.95 0.11 129.23 142.57 30267 +1948 363 1.29 -4.71 -0.36 0.21 164.28 141.69 30303 +1948 364 0.47 -5.53 -1.18 0.05 155.63 142.14 30343 +1948 365 0.48 -5.52 -1.17 0 155.73 174.81 30388 +1949 1 6.84 0.84 5.19 0 234.57 171.27 30438 +1949 2 8.79 2.79 7.14 0 264.75 126.28 30492 +1949 3 5.65 -0.35 4 0 217.64 129.36 30551 +1949 4 4.58 -1.42 2.93 0 203.33 130.91 30614 +1949 5 6.23 0.23 4.58 0 225.75 130.54 30681 +1949 6 10.82 4.82 9.17 0 299.65 127.95 30752 +1949 7 10.11 4.11 8.46 0.08 287.02 97 30828 +1949 8 8.05 2.05 6.4 0.31 252.93 99.31 30907 +1949 9 4.17 -1.83 2.52 0 198.07 136.21 30991 +1949 10 -0.32 -6.32 -1.97 0 147.66 139.77 31079 +1949 11 5.55 -0.45 3.9 0 216.27 137.65 31171 +1949 12 4.23 -1.77 2.58 0 198.83 139.47 31266 +1949 13 6.19 0.19 4.54 0 225.19 139.84 31366 +1949 14 4.28 -1.72 2.63 0 199.47 142.53 31469 +1949 15 5 -1 3.35 0 208.85 143.53 31575 +1949 16 2.66 -3.34 1.01 0 179.67 146.2 31686 +1949 17 -2.11 -8.11 -3.76 0.09 130.91 154.38 31800 +1949 18 -4.11 -10.11 -5.76 0.27 114.16 157.05 31917 +1949 19 -3.15 -9.15 -4.8 0 121.95 196.7 32038 +1949 20 -2.13 -8.13 -3.78 0 130.73 197.75 32161 +1949 21 0.1 -5.9 -1.55 0 151.85 198.6 32289 +1949 22 1.8 -4.2 0.15 0 169.87 199.11 32419 +1949 23 2.8 -3.2 1.15 0.01 181.32 160.11 32552 +1949 24 2.46 -3.54 0.81 0 177.35 201.6 32688 +1949 25 3.83 -2.17 2.18 0 193.79 162.11 32827 +1949 26 2.85 -3.15 1.2 0.48 181.9 123.48 32969 +1949 27 4.17 -1.83 2.52 0.21 198.07 124.38 33114 +1949 28 6.66 0.66 5.01 0.05 231.94 124.68 33261 +1949 29 8.67 2.67 7.02 0 262.8 166.91 33411 +1949 30 8.62 2.62 6.97 0 261.99 169.17 33564 +1949 31 5.32 -0.68 3.67 0.01 213.14 130.67 33718 +1949 32 3.25 -2.75 1.6 0 186.68 177.77 33875 +1949 33 3.76 -2.24 2.11 0 192.92 180.06 34035 +1949 34 0.72 -5.28 -0.93 0 158.22 184.16 34196 +1949 35 3.4 -2.6 1.75 0 188.49 184.67 34360 +1949 36 10.87 4.87 9.22 0 300.56 180.66 34526 +1949 37 13.06 7.06 11.41 0 342.67 180.44 34694 +1949 38 11.21 5.21 9.56 0 306.79 185.33 34863 +1949 39 6.7 0.7 5.05 0 232.52 192.41 35035 +1949 40 8.88 2.88 7.23 0 266.22 192.96 35208 +1949 41 10.89 4.89 9.24 0 300.92 193.38 35383 +1949 42 6.63 0.63 4.98 0 231.5 200.21 35560 +1949 43 7.2 1.2 5.55 0 239.91 202.38 35738 +1949 44 8.06 2.06 6.41 0 253.08 204.1 35918 +1949 45 4.01 -1.99 2.36 0 196.04 210.26 36099 +1949 46 3.55 -2.45 1.9 0 190.33 213.31 36282 +1949 47 2.69 -3.31 1.04 0 180.03 216.78 36466 +1949 48 3.53 -2.47 1.88 0 190.08 218.98 36652 +1949 49 6.47 0.47 4.82 0 229.19 219.26 36838 +1949 50 5.44 -0.56 3.79 0 214.77 222.86 37026 +1949 51 3.94 -2.06 2.29 0 195.16 227.1 37215 +1949 52 -0.59 -6.59 -2.24 0 145.02 233.13 37405 +1949 53 2.95 -3.05 1.3 0 183.09 233.7 37596 +1949 54 8.48 2.48 6.83 0 259.74 231.29 37788 +1949 55 7.42 1.42 5.77 0 243.22 235.41 37981 +1949 56 5.85 -0.15 4.2 0 220.41 239.67 38175 +1949 57 4.32 -1.68 2.67 0 199.98 243.96 38370 +1949 58 2.29 -3.71 0.64 0 175.4 248.59 38565 +1949 59 -0.1 -6.1 -1.75 0 149.84 253.04 38761 +1949 60 2.22 -3.78 0.57 0 174.6 254.29 38958 +1949 61 6.36 0.36 4.71 0 227.61 253.5 39156 +1949 62 6.26 0.26 4.61 0 226.18 256.4 39355 +1949 63 3.81 -2.19 2.16 0 193.54 261.78 39553 +1949 64 2.29 -3.71 0.64 0 175.4 266 39753 +1949 65 3.17 -2.83 1.52 0 185.71 268.19 39953 +1949 66 5.44 -0.56 3.79 0 214.77 268.81 40154 +1949 67 9.36 3.36 7.71 0 274.18 267.18 40355 +1949 68 8.54 2.54 6.89 0 260.7 271.08 40556 +1949 69 10.91 4.91 9.26 0 301.29 270.47 40758 +1949 70 14.76 8.76 13.11 0 378.75 266.87 40960 +1949 71 15.98 9.98 14.33 0 406.59 267.32 41163 +1949 72 11.5 5.5 9.85 0 312.19 278.04 41366 +1949 73 10.75 4.75 9.1 0 298.39 281.82 41569 +1949 74 1.84 -4.16 0.19 0 170.32 294.79 41772 +1949 75 4.45 -1.55 2.8 0 201.65 295.13 41976 +1949 76 9.82 3.82 8.17 0 282 291.23 42179 +1949 77 11.02 5.02 9.37 0.14 303.3 219 42383 +1949 78 8.67 2.67 7.02 0.04 262.8 223.56 42587 +1949 79 6.49 0.49 4.84 0 229.48 303.6 42791 +1949 80 5.57 -0.43 3.92 0 216.54 307.22 42996 +1949 81 1.9 -4.1 0.25 0 170.99 313.54 43200 +1949 82 1.15 -4.85 -0.5 0 162.78 316.9 43404 +1949 83 2.56 -3.44 0.91 0.01 178.51 238.63 43608 +1949 84 5.17 -0.83 3.52 0 211.12 318.04 43812 +1949 85 5.83 -0.17 4.18 0 220.13 319.81 44016 +1949 86 6.47 0.47 4.82 0.01 229.19 241.09 44220 +1949 87 5.69 -0.31 4.04 0 218.19 324.97 44424 +1949 88 2.38 -3.62 0.73 0 176.43 330.91 44627 +1949 89 -0.96 -6.96 -2.61 0 141.47 336.13 44831 +1949 90 0.08 -5.92 -1.57 0.01 151.65 253.3 45034 +1949 91 8.26 2.26 6.61 0.11 256.23 248.21 45237 +1949 92 8.68 2.68 7.03 0 262.96 332.59 45439 +1949 93 11.52 5.52 9.87 0 312.57 330.19 45642 +1949 94 16.54 10.54 14.89 0.09 419.95 241.42 45843 +1949 95 17.59 11.59 15.94 0.17 446 241.02 46045 +1949 96 21.07 15.07 19.42 0.3 542.4 235.08 46246 +1949 97 18.1 12.1 16.45 0 459.14 324.04 46446 +1949 98 18.85 12.85 17.2 0 479.06 323.88 46647 +1949 99 18.78 12.78 17.13 0.01 477.17 244.51 46846 +1949 100 18.72 12.72 17.07 0.13 475.56 246.04 47045 +1949 101 19.08 13.08 17.43 1.33 485.32 246.66 47243 +1949 102 18 12 16.35 0.08 456.53 250.31 47441 +1949 103 17.81 11.81 16.16 0.56 451.62 252.03 47638 +1949 104 14.14 8.14 12.49 0.24 365.23 260.07 47834 +1949 105 13.72 7.72 12.07 0 356.31 349.45 48030 +1949 106 16.73 10.73 15.08 0 424.56 344.01 48225 +1949 107 16.44 10.44 14.79 0 417.53 346.39 48419 +1949 108 15.16 9.16 13.51 0 387.69 351.23 48612 +1949 109 13.16 7.16 11.51 0 344.71 357.27 48804 +1949 110 14.4 8.4 12.75 0 370.85 355.97 48995 +1949 111 12.16 6.16 10.51 0.01 324.79 271.7 49185 +1949 112 15.25 9.25 13.6 0 389.73 357.03 49374 +1949 113 13.43 7.43 11.78 0 350.26 362.51 49561 +1949 114 12.17 6.17 10.52 0 324.99 366.62 49748 +1949 115 16.23 10.23 14.58 0 412.51 358.82 49933 +1949 116 12.7 6.7 11.05 0 335.42 368.2 50117 +1949 117 13.17 7.17 11.52 0.03 344.91 276.39 50300 +1949 118 12.04 6.04 10.39 0.04 322.47 279.14 50481 +1949 119 12.53 6.53 10.88 0 332.04 372.39 50661 +1949 120 16.27 10.27 14.62 0.24 413.46 273.63 50840 +1949 121 19.82 13.82 18.17 1.15 505.92 266.75 51016 +1949 122 23.88 17.88 22.23 1.25 632.66 256.63 51191 +1949 123 24.61 18.61 22.96 0.98 658.09 255.09 51365 +1949 124 21.83 15.83 20.18 3.26 565.66 264.01 51536 +1949 125 17.93 11.93 16.28 0.85 454.72 274.22 51706 +1949 126 12.2 6.2 10.55 0.77 325.57 285.55 51874 +1949 127 13.13 7.13 11.48 0.36 344.1 284.74 52039 +1949 128 16.05 10.05 14.4 0.03 408.24 280.24 52203 +1949 129 15.02 9.02 13.37 0 384.54 377.12 52365 +1949 130 16.43 10.43 14.78 0 417.29 374.29 52524 +1949 131 15.71 9.71 14.06 0.24 400.28 282.73 52681 +1949 132 12.73 6.73 11.08 0.9 336.02 288.62 52836 +1949 133 13.27 7.27 11.62 1.29 346.96 288.27 52989 +1949 134 15.49 9.49 13.84 0.31 395.2 284.83 53138 +1949 135 16.5 10.5 14.85 1.37 418.98 283.36 53286 +1949 136 15.91 9.91 14.26 0.24 404.95 285.02 53430 +1949 137 15.36 9.36 13.71 0.12 392.23 286.62 53572 +1949 138 17.74 11.74 16.09 0.24 449.83 282.19 53711 +1949 139 17.59 11.59 15.94 0 446 377.38 53848 +1949 140 19.51 13.51 17.86 0 497.2 371.96 53981 +1949 141 18.38 12.38 16.73 0 466.49 375.94 54111 +1949 142 18.58 12.58 16.93 0 471.8 375.83 54238 +1949 143 20.13 14.13 18.48 0.01 514.76 278.51 54362 +1949 144 15.48 9.48 13.83 0.01 394.97 289.2 54483 +1949 145 16.95 10.95 15.3 0 429.96 382.11 54600 +1949 146 16.87 10.87 15.22 0 427.99 382.71 54714 +1949 147 21 15 19.35 0 540.3 370.1 54824 +1949 148 20.68 14.68 19.03 0.18 530.79 278.7 54931 +1949 149 18.89 12.89 17.24 0 480.14 377.87 55034 +1949 150 19.81 13.81 18.16 0 505.63 375.21 55134 +1949 151 16.88 10.88 15.23 0 428.23 384.59 55229 +1949 152 18.18 12.18 16.53 0 461.23 380.9 55321 +1949 153 15.94 9.94 14.29 0 405.65 387.53 55409 +1949 154 18.19 12.19 16.54 0.1 461.49 286.07 55492 +1949 155 18.25 12.25 16.6 0 463.06 381.44 55572 +1949 156 17.09 11.09 15.44 0.67 433.42 288.89 55648 +1949 157 15.22 9.22 13.57 0.02 389.05 292.81 55719 +1949 158 12.98 6.98 11.33 0.04 341.05 296.97 55786 +1949 159 13.93 7.93 12.28 0.04 360.75 295.52 55849 +1949 160 16.81 10.81 15.16 0.11 426.52 290.07 55908 +1949 161 15.84 9.84 14.19 0 403.31 389.48 55962 +1949 162 16.74 10.74 15.09 0 424.8 387.08 56011 +1949 163 18.96 12.96 17.31 0 482.04 380.65 56056 +1949 164 23.08 17.08 21.43 0 605.76 365.89 56097 +1949 165 26.02 20.02 24.37 0 709.66 353.12 56133 +1949 166 24.31 18.31 22.66 0.02 647.54 270.7 56165 +1949 167 19.11 13.11 17.46 0.52 486.14 285.25 56192 +1949 168 20.8 14.8 19.15 0.06 534.34 281.03 56214 +1949 169 21.96 15.96 20.31 0.92 569.72 277.85 56231 +1949 170 20.82 14.82 19.17 0 534.93 374.65 56244 +1949 171 22.04 16.04 20.39 2.28 572.24 277.67 56252 +1949 172 22.65 16.65 21 0.02 591.7 275.89 56256 +1949 173 19.47 13.47 17.82 0.51 496.08 284.47 56255 +1949 174 21.64 15.64 19.99 0.37 559.77 278.71 56249 +1949 175 22.09 16.09 20.44 0.81 573.81 277.42 56238 +1949 176 21.97 15.97 20.32 0.39 570.04 277.73 56223 +1949 177 19.62 13.62 17.97 0 500.28 378.54 56203 +1949 178 18.36 12.36 16.71 0.08 465.96 286.95 56179 +1949 179 17.77 11.77 16.12 0 450.6 384.28 56150 +1949 180 17.94 11.94 16.29 0 454.98 383.65 56116 +1949 181 12.77 6.77 11.12 0.02 336.82 297.73 56078 +1949 182 19.63 13.63 17.98 0.14 500.56 283.57 56035 +1949 183 25.11 19.11 23.46 0.81 676 267.49 55987 +1949 184 26.23 20.23 24.58 0.05 717.62 263.49 55935 +1949 185 20.88 14.88 19.23 0 536.72 373.39 55879 +1949 186 21.79 15.79 20.14 0 564.42 369.81 55818 +1949 187 21.02 15.02 19.37 0.07 540.9 279.34 55753 +1949 188 21.04 15.04 19.39 0 541.5 372.11 55684 +1949 189 20.51 14.51 18.86 0.03 525.79 280.35 55611 +1949 190 20.3 14.3 18.65 0.42 519.67 280.61 55533 +1949 191 20.6 14.6 18.95 0 528.43 372.85 55451 +1949 192 20.56 14.56 18.91 0 527.26 372.69 55366 +1949 193 22.39 16.39 20.74 0 583.34 365.72 55276 +1949 194 21.71 15.71 20.06 0 561.93 368.06 55182 +1949 195 20.01 14.01 18.36 0.19 511.32 280.35 55085 +1949 196 20.62 14.62 18.97 0 529.02 371.3 54984 +1949 197 20.07 14.07 18.42 0 513.04 372.73 54879 +1949 198 21.26 15.26 19.61 0 548.14 368.16 54770 +1949 199 23.69 17.69 22.04 0 626.18 358.44 54658 +1949 200 23.49 17.49 21.84 0.26 619.42 269.15 54542 +1949 201 21.05 15.05 19.4 0.16 541.8 275.77 54423 +1949 202 20.48 14.48 18.83 0 524.91 369.12 54301 +1949 203 20.5 14.5 18.85 0 525.5 368.55 54176 +1949 204 22.65 16.65 21 0 591.7 360.2 54047 +1949 205 22.9 16.9 21.25 0 599.84 358.71 53915 +1949 206 22.69 16.69 21.04 0.26 593 269.24 53780 +1949 207 24.15 18.15 22.5 0.25 641.97 264.34 53643 +1949 208 25.39 19.39 23.74 0.24 686.21 259.83 53502 +1949 209 25.45 19.45 23.8 0 688.41 345.55 53359 +1949 210 28.24 22.24 26.59 0.23 797.76 248.59 53213 +1949 211 30.29 24.29 28.64 0 887.15 319.46 53064 +1949 212 24.58 18.58 22.93 0.04 657.03 260.43 52913 +1949 213 23.23 17.23 21.58 0.05 610.73 264.04 52760 +1949 214 22.34 16.34 20.69 0.22 581.74 266.06 52604 +1949 215 23.85 17.85 22.2 0 631.63 348.18 52445 +1949 216 22.34 16.34 20.69 0 581.74 353.08 52285 +1949 217 22.88 16.88 21.23 0.01 599.18 262.62 52122 +1949 218 22.74 16.74 21.09 0 594.62 349.89 51958 +1949 219 26.9 20.9 25.25 0.02 743.54 248.32 51791 +1949 220 26.92 20.92 25.27 0.09 744.33 247.58 51622 +1949 221 23.5 17.5 21.85 0.57 619.76 258.02 51451 +1949 222 22.59 16.59 20.94 0.72 589.76 259.88 51279 +1949 223 25.19 19.19 23.54 0.19 678.9 251.2 51105 +1949 224 20.18 14.18 18.53 0 516.2 352.75 50929 +1949 225 17.4 11.4 15.75 0.01 441.18 269.97 50751 +1949 226 20 14 18.35 0.37 511.04 263.29 50572 +1949 227 17.99 11.99 16.34 0 456.27 355.85 50392 +1949 228 20.18 14.18 18.53 0.31 516.2 260.99 50210 +1949 229 17.96 11.96 16.31 0.78 455.5 265.09 50026 +1949 230 20.27 14.27 18.62 1.21 518.8 258.89 49842 +1949 231 18.63 12.63 16.98 1.55 473.14 261.57 49656 +1949 232 18.82 12.82 17.17 1.25 478.25 260.13 49469 +1949 233 16.21 10.21 14.56 0.03 412.03 264.4 49280 +1949 234 17.81 11.81 16.16 0 451.62 346.86 49091 +1949 235 18.35 12.35 16.7 0 465.7 343.85 48900 +1949 236 22.68 16.68 21.03 0.28 592.67 246.38 48709 +1949 237 20.07 14.07 18.42 0.03 513.04 251.74 48516 +1949 238 23.57 17.57 21.92 0.02 622.12 241.5 48323 +1949 239 25.07 19.07 23.42 0.1 674.55 235.99 48128 +1949 240 25.55 19.55 23.9 1.34 692.1 233.25 47933 +1949 241 23.68 17.68 22.03 0.3 625.84 237.58 47737 +1949 242 22.75 16.75 21.1 0.01 594.94 238.86 47541 +1949 243 23.99 17.99 22.34 0.16 636.44 234.1 47343 +1949 244 20.61 14.61 18.96 0 528.72 322.01 47145 +1949 245 24 18 22.35 0 636.78 308.58 46947 +1949 246 23.17 17.17 21.52 0 608.73 309.74 46747 +1949 247 24.13 18.13 22.48 0 641.27 304.44 46547 +1949 248 25.35 19.35 23.7 0.07 684.74 223.41 46347 +1949 249 25.77 19.77 24.12 0 700.27 294.24 46146 +1949 250 24.44 18.44 22.79 0 652.09 297.61 45945 +1949 251 20.58 14.58 18.93 0 527.84 308.61 45743 +1949 252 21.9 15.9 20.25 0 567.85 302.37 45541 +1949 253 17.82 11.82 16.17 0 451.88 312.05 45339 +1949 254 16.54 10.54 14.89 0 419.95 313.05 45136 +1949 255 18.56 12.56 16.91 0.02 471.27 229.32 44933 +1949 256 18.01 12.01 16.36 0 456.79 304.93 44730 +1949 257 12.42 6.42 10.77 0.59 329.87 236.1 44527 +1949 258 11.61 5.61 9.96 0 314.26 313.83 44323 +1949 259 12.29 6.29 10.64 0 327.32 310.16 44119 +1949 260 15.32 9.32 13.67 0 391.32 301.85 43915 +1949 261 15.14 9.14 13.49 0 387.24 299.76 43711 +1949 262 21.1 15.1 19.45 0 543.31 282.62 43507 +1949 263 28.45 22.45 26.8 0 806.56 253.89 43303 +1949 264 26.78 20.78 25.13 0 738.84 258.47 43099 +1949 265 24.45 18.45 22.8 0.04 652.44 198.67 42894 +1949 266 25.73 19.73 24.08 0.58 698.78 193.51 42690 +1949 267 21.75 15.75 20.1 0.02 563.17 201.45 42486 +1949 268 20.48 14.48 18.83 0 524.91 269.72 42282 +1949 269 21.46 15.46 19.81 0 554.23 264.57 42078 +1949 270 20.87 14.87 19.22 0 536.42 263.68 41875 +1949 271 21.55 15.55 19.9 0 557 259.27 41671 +1949 272 17.59 11.59 15.94 0 446 266.59 41468 +1949 273 18.07 12.07 16.42 0 458.35 263.02 41265 +1949 274 9.84 3.84 8.19 0 282.34 275.15 41062 +1949 275 11.71 5.71 10.06 0 316.16 269.61 40860 +1949 276 12.27 6.27 10.62 0 326.93 266.01 40658 +1949 277 14.28 8.28 12.63 0 368.25 259.97 40456 +1949 278 16.83 10.83 15.18 0 427.01 252.27 40255 +1949 279 15.53 9.53 13.88 0 396.12 252.04 40054 +1949 280 12.02 6.02 10.37 0 322.08 255.32 39854 +1949 281 14.47 8.47 12.82 0 372.37 248.63 39654 +1949 282 12.02 6.02 10.37 0 322.08 249.82 39455 +1949 283 17.48 11.48 15.83 0 443.2 237.47 39256 +1949 284 18.35 12.35 16.7 0 465.7 232.72 39058 +1949 285 17.17 11.17 15.52 0 435.41 232.56 38861 +1949 286 17.31 11.31 15.66 0 438.92 229.59 38664 +1949 287 16.71 10.71 15.06 0 424.07 227.87 38468 +1949 288 13.08 7.08 11.43 0.01 343.08 173.44 38273 +1949 289 15.8 9.8 14.15 0 402.38 224.22 38079 +1949 290 15.39 9.39 13.74 0.06 392.91 166.59 37885 +1949 291 12.93 6.93 11.28 0 340.04 223.31 37693 +1949 292 10.36 4.36 8.71 0.09 291.42 168.04 37501 +1949 293 10.05 4.05 8.4 0.76 285.98 166.26 37311 +1949 294 11.89 5.89 10.24 0 319.59 216.47 37121 +1949 295 10.31 4.31 8.66 0 290.53 215.62 36933 +1949 296 14.88 8.88 13.23 0 381.41 206.79 36745 +1949 297 17.65 11.65 16 0 447.52 199.45 36560 +1949 298 19.71 13.71 18.06 0 502.81 192.99 36375 +1949 299 20.91 14.91 19.26 0 537.61 187.83 36191 +1949 300 20.79 14.79 19.14 0.07 534.04 139.18 36009 +1949 301 18.47 12.47 16.82 0.5 468.88 140.83 35829 +1949 302 13 7 11.35 0.19 341.45 145.36 35650 +1949 303 10.79 4.79 9.14 0.06 299.11 145.48 35472 +1949 304 8.95 2.95 7.3 0.04 267.37 145.11 35296 +1949 305 5.89 -0.11 4.24 0.04 220.97 145.14 35122 +1949 306 8.31 2.31 6.66 0 257.03 189.1 34950 +1949 307 11.03 5.03 9.38 0.73 303.48 137.84 34779 +1949 308 9.99 3.99 8.34 0 284.93 182.31 34610 +1949 309 10.96 4.96 9.31 0 302.2 178.97 34444 +1949 310 7.34 1.34 5.69 0.11 242.01 135.05 34279 +1949 311 6.29 0.29 4.64 0.01 226.61 134.06 34116 +1949 312 6.31 0.31 4.66 0.05 226.89 132.05 33956 +1949 313 7.82 1.82 6.17 0 249.34 172.69 33797 +1949 314 6.48 0.48 4.83 0 229.33 171.84 33641 +1949 315 7.57 1.57 5.92 0 245.5 168.41 33488 +1949 316 6.37 0.37 4.72 0.25 227.75 125.39 33337 +1949 317 6.11 0.11 4.46 0.56 224.06 123.89 33188 +1949 318 9.15 3.15 7.5 0.84 270.67 120.25 33042 +1949 319 9.6 3.6 7.95 0.22 278.23 118.68 32899 +1949 320 13.14 7.14 11.49 0 344.3 152.78 32758 +1949 321 12.47 6.47 10.82 0 330.86 151.46 32620 +1949 322 16.95 10.95 15.3 0.55 429.96 108.13 32486 +1949 323 12.98 6.98 11.33 2.88 341.05 110.67 32354 +1949 324 9.75 3.75 8.1 0.35 280.79 111.55 32225 +1949 325 10.08 4.08 8.43 0 286.5 146.74 32100 +1949 326 9.43 3.43 7.78 0.97 275.36 109.41 31977 +1949 327 9.07 3.07 7.42 1.18 269.35 108.27 31858 +1949 328 9.7 3.7 8.05 0.76 279.94 106.4 31743 +1949 329 8.71 2.71 7.06 0.73 263.45 105.91 31631 +1949 330 9.76 3.76 8.11 1.21 280.97 104.19 31522 +1949 331 6.77 0.77 5.12 0.26 233.54 104.95 31417 +1949 332 6.93 0.93 5.28 0.29 235.89 103.64 31316 +1949 333 8.26 2.26 6.61 0.02 256.23 102.1 31218 +1949 334 7.53 1.53 5.88 0 244.89 135.58 31125 +1949 335 5.78 -0.22 4.13 0.12 219.44 101.71 31035 +1949 336 1.86 -4.14 0.21 0 170.54 136.75 30949 +1949 337 1.44 -4.56 -0.21 0.23 165.91 101.47 30867 +1949 338 4.12 -1.88 2.47 0.01 197.43 99.7 30790 +1949 339 6.52 0.52 4.87 0 229.91 130.68 30716 +1949 340 3.8 -2.2 2.15 2.4 193.42 98.69 30647 +1949 341 1.96 -4.04 0.31 0.35 171.66 98.72 30582 +1949 342 3.07 -2.93 1.42 0 184.52 130.3 30521 +1949 343 8.38 2.38 6.73 0 258.14 126.17 30465 +1949 344 9.57 3.57 7.92 0 277.72 124.15 30413 +1949 345 10.03 4.03 8.38 0 285.63 123.37 30366 +1949 346 8.54 2.54 6.89 0.17 260.7 92.98 30323 +1949 347 8.04 2.04 6.39 0 252.77 123.74 30284 +1949 348 9.02 3.02 7.37 0 268.52 122.68 30251 +1949 349 9.49 3.49 7.84 0 276.37 121.95 30221 +1949 350 11.43 5.43 9.78 0 310.88 120.03 30197 +1949 351 6.57 0.57 4.92 0 230.63 123.46 30177 +1949 352 1.64 -4.36 -0.01 0 168.1 126.07 30162 +1949 353 2.71 -3.29 1.06 0 180.26 125.49 30151 +1949 354 -2.79 -8.79 -4.44 0.08 124.99 139.85 30145 +1949 355 -2.89 -8.89 -4.54 0 124.14 171.82 30144 +1949 356 0.47 -5.53 -1.18 0 155.63 170.49 30147 +1949 357 0.19 -5.81 -1.46 0 152.76 170.63 30156 +1949 358 4.66 -1.34 3.01 0 204.37 124.59 30169 +1949 359 2.62 -3.38 0.97 0 179.21 125.79 30186 +1949 360 3.15 -2.85 1.5 0 185.47 125.89 30208 +1949 361 4.93 -1.07 3.28 0 207.92 125.25 30235 +1949 362 10.26 4.26 8.61 0 289.65 122.01 30267 +1949 363 13.28 7.28 11.63 0 347.17 119.88 30303 +1949 364 11.41 5.41 9.76 0 310.51 121.99 30343 +1949 365 12.31 6.31 10.66 0 327.71 121.73 30388 +1950 1 6.04 0.04 4.39 0.24 223.07 95.59 30438 +1950 2 5.16 -0.84 3.51 0.01 210.98 96.54 30492 +1950 3 2.23 -3.77 0.58 0 174.72 131.26 30551 +1950 4 1.57 -4.43 -0.08 0 167.33 132.49 30614 +1950 5 1.54 -4.46 -0.11 0 167 133.16 30681 +1950 6 -0.33 -6.33 -1.98 0 147.56 134.9 30752 +1950 7 0.91 -5.09 -0.74 0.01 160.22 101.36 30828 +1950 8 -3.57 -9.57 -5.22 0 118.49 138.44 30907 +1950 9 -1.59 -7.59 -3.24 0 135.6 138.98 30991 +1950 10 1.01 -4.99 -0.64 0.38 161.28 104.38 31079 +1950 11 -2.92 -8.92 -4.57 0.18 123.88 149.26 31171 +1950 12 -0.42 -6.42 -2.07 0.06 146.68 149.33 31266 +1950 13 -3.75 -9.75 -5.4 0.21 117.03 152.04 31366 +1950 14 -3.77 -9.77 -5.42 0 116.87 189.6 31469 +1950 15 -3.8 -9.8 -5.45 0.67 116.63 156.03 31575 +1950 16 -3.05 -9.05 -4.7 0.44 122.79 157.98 31686 +1950 17 -2.53 -8.53 -4.18 0.38 127.22 160.09 31800 +1950 18 -2.91 -8.91 -4.56 1.85 123.97 167.03 31917 +1950 19 -4.87 -10.87 -6.52 0 108.3 207.59 32038 +1950 20 -1.4 -7.4 -3.05 0 137.34 207.68 32161 +1950 21 1.93 -4.07 0.28 0 171.33 207.64 32289 +1950 22 -1.05 -7.05 -2.7 0 140.62 210.67 32419 +1950 23 0.09 -5.91 -1.56 0.46 151.75 171.65 32552 +1950 24 -0.25 -6.25 -1.9 0.3 148.35 174 32688 +1950 25 -1.16 -7.16 -2.81 1.26 139.58 179.21 32827 +1950 26 -1.31 -7.31 -2.96 0.1 138.18 180.78 32969 +1950 27 0.49 -5.51 -1.16 0 155.83 223.35 33114 +1950 28 2.9 -3.1 1.25 0 182.5 223.62 33261 +1950 29 3.84 -2.16 2.19 0 193.91 224.69 33411 +1950 30 5.19 -0.81 3.54 0 211.39 225.13 33564 +1950 31 1.23 -4.77 -0.42 0 163.64 229.66 33718 +1950 32 4.66 -1.34 3.01 0 204.37 228.8 33875 +1950 33 4.66 -1.34 3.01 0.41 204.37 185.77 34035 +1950 34 2.82 -3.18 1.17 0.02 181.55 187.79 34196 +1950 35 6.67 0.67 5.02 0.81 232.08 186.25 34360 +1950 36 4.41 -1.59 2.76 0 201.13 235.32 34526 +1950 37 1.87 -4.13 0.22 0 170.65 239.01 34694 +1950 38 2.3 -3.7 0.65 0.36 175.51 192.72 34863 +1950 39 5.44 -0.56 3.79 0 214.77 240.49 35035 +1950 40 5.1 -0.9 3.45 0 210.18 242.55 35208 +1950 41 6.49 0.49 4.84 0 229.48 243.04 35383 +1950 42 4.74 -1.26 3.09 0 205.42 246.28 35560 +1950 43 5.16 -0.84 3.51 0 210.98 247.84 35738 +1950 44 6.42 0.42 4.77 0 228.47 248.39 35918 +1950 45 9.91 3.91 8.26 0 283.55 246.16 36099 +1950 46 8.81 2.81 7.16 0.02 265.08 196.67 36282 +1950 47 10.8 4.8 9.15 0.13 299.29 195.67 36466 +1950 48 11.23 5.23 9.58 0 307.16 248.74 36652 +1950 49 10.03 4.03 8.38 0 285.63 251.63 36838 +1950 50 9.06 3.06 7.41 0.4 269.18 164.44 37026 +1950 51 7.89 1.89 6.24 0 250.43 223.45 37215 +1950 52 5.1 -0.9 3.45 0 210.18 228.95 37405 +1950 53 3.96 -2.04 2.31 0.22 195.41 174.67 37596 +1950 54 4.08 -1.92 2.43 0 196.93 235.56 37788 +1950 55 2.66 -3.34 1.01 0.04 179.67 179.79 37981 +1950 56 0.67 -5.33 -0.98 0 157.7 243.88 38175 +1950 57 0.11 -5.89 -1.54 0.08 151.95 185.38 38370 +1950 58 -2.77 -8.77 -4.42 0 125.16 251.89 38565 +1950 59 0.4 -5.6 -1.25 0 154.91 252.7 38761 +1950 60 12.43 6.43 10.78 0 330.07 243 38958 +1950 61 11.49 5.49 9.84 0.1 312.01 185.43 39156 +1950 62 7.68 1.68 6.03 0 247.19 254.86 39355 +1950 63 10.87 4.87 9.22 0.39 300.56 190.37 39553 +1950 64 10.87 4.87 9.22 0.02 300.56 192.52 39753 +1950 65 10.51 4.51 8.86 0.01 294.08 195.03 39953 +1950 66 11.85 5.85 10.2 0 318.82 260.79 40154 +1950 67 11.77 5.77 10.12 0 317.3 263.77 40355 +1950 68 10.97 4.97 9.32 0.05 302.38 200.84 40556 +1950 69 9.2 3.2 7.55 0.42 271.5 204.63 40758 +1950 70 9.32 3.32 7.67 0 273.51 275.51 40960 +1950 71 11.15 5.15 9.5 0 305.68 275.79 41163 +1950 72 9.56 3.56 7.91 0 277.55 280.89 41366 +1950 73 11.86 5.86 10.21 0 319.01 280.1 41569 +1950 74 8.23 2.23 6.58 0 255.76 288.05 41772 +1950 75 12.66 6.66 11.01 0 334.62 284.16 41976 +1950 76 12 6 10.35 0 321.7 287.86 42179 +1950 77 10.1 4.1 8.45 0 286.85 293.4 42383 +1950 78 4.5 -1.5 2.85 0 202.29 303.07 42587 +1950 79 4.05 -1.95 2.4 0.08 196.55 229.72 42791 +1950 80 4.73 -1.27 3.08 0.07 205.29 231.11 42996 +1950 81 9.07 3.07 7.42 0.06 269.35 229.02 43200 +1950 82 4.18 -1.82 2.53 0 198.19 314.03 43404 +1950 83 6.45 0.45 4.8 0 228.9 313.98 43608 +1950 84 11.02 5.02 9.37 0 303.3 310.03 43812 +1950 85 11.69 5.69 10.04 0 315.78 311.39 44016 +1950 86 13.45 7.45 11.8 0 350.68 310.57 44220 +1950 87 12.99 6.99 11.34 0 341.25 313.94 44424 +1950 88 12.66 6.66 11.01 0 334.62 316.87 44627 +1950 89 12.29 6.29 10.64 0 327.32 319.8 44831 +1950 90 11.23 5.23 9.58 0 307.16 324.02 45034 +1950 91 12.16 6.16 10.51 0 324.79 324.62 45237 +1950 92 15.97 9.97 14.32 0.06 406.36 239.24 45439 +1950 93 12.35 6.35 10.7 0 328.5 328.68 45642 +1950 94 8.98 2.98 7.33 0 267.86 336.53 45843 +1950 95 5.96 -0.04 4.31 0 221.95 342.89 46045 +1950 96 8.95 2.95 7.3 1.53 267.37 255.64 46246 +1950 97 7.07 1.07 5.42 0 237.97 345.66 46446 +1950 98 6.91 0.91 5.26 0 235.6 347.87 46647 +1950 99 10.58 4.58 8.93 0 295.33 344.26 46846 +1950 100 15.07 9.07 13.42 0 385.66 337.29 47045 +1950 101 16.35 10.35 14.7 0 415.37 336.16 47243 +1950 102 12.29 6.29 10.64 0 327.32 346.92 47441 +1950 103 11.57 5.57 9.92 0 313.51 350.13 47638 +1950 104 11.99 5.99 10.34 0.33 321.51 263.37 47834 +1950 105 11 5 9.35 0.06 302.93 266.1 48030 +1950 106 10.49 4.49 8.84 0 293.72 357.37 48225 +1950 107 8.58 2.58 6.93 0.98 261.35 271.68 48419 +1950 108 14.87 8.87 13.22 0.56 381.19 263.93 48612 +1950 109 16.94 10.94 15.29 0.1 429.71 261.29 48804 +1950 110 16.37 10.37 14.72 1.74 415.85 263.43 48995 +1950 111 13.33 7.33 11.68 0 348.2 359.87 49185 +1950 112 11.77 5.77 10.12 0.02 317.3 273.42 49374 +1950 113 13.57 7.57 11.92 0.57 353.17 271.65 49561 +1950 114 17.71 11.71 16.06 1.09 449.06 265.09 49748 +1950 115 17.35 11.35 15.7 0.02 439.92 266.89 49933 +1950 116 16.09 10.09 14.44 0.04 409.18 270.28 50117 +1950 117 18.9 12.9 17.25 0.36 480.41 265.4 50300 +1950 118 20.44 14.44 18.79 0.01 523.74 262.71 50481 +1950 119 18.23 12.23 16.58 0 462.54 358.29 50661 +1950 120 18.41 12.41 16.76 0 467.28 358.91 50840 +1950 121 24.46 18.46 22.81 0.37 652.79 254.01 51016 +1950 122 20.86 14.86 19.21 0 536.12 353.39 51191 +1950 123 17.44 11.44 15.79 0 442.19 364.99 51365 +1950 124 19.61 13.61 17.96 0 500 359.55 51536 +1950 125 15.54 9.54 13.89 0 396.35 372.09 51706 +1950 126 15.83 9.83 14.18 0 403.08 372.35 51874 +1950 127 18.81 12.81 17.16 0.23 477.98 273.64 52039 +1950 128 17.3 11.3 15.65 0.01 438.67 277.7 52203 +1950 129 17.01 11.01 15.36 0 431.44 371.92 52365 +1950 130 17.25 11.25 15.6 0.19 437.41 279.02 52524 +1950 131 17.93 11.93 16.28 0.76 454.72 278.15 52681 +1950 132 20.12 14.12 18.47 0 514.48 364.83 52836 +1950 133 14.04 8.04 12.39 0.32 363.09 286.95 52989 +1950 134 19.02 13.02 17.37 0.09 483.68 277.32 53138 +1950 135 16.9 10.9 15.25 0.15 428.73 282.54 53286 +1950 136 17.74 11.74 16.09 0.61 449.83 281.22 53430 +1950 137 19.24 13.24 17.59 0 489.71 371.08 53572 +1950 138 18.15 12.15 16.5 0.38 460.44 281.28 53711 +1950 139 18.61 12.61 16.96 0.7 472.61 280.75 53848 +1950 140 19.22 13.22 17.57 0 489.16 372.89 53981 +1950 141 17.88 11.88 16.23 0 453.43 377.45 54111 +1950 142 22.48 16.48 20.83 0 586.22 362.34 54238 +1950 143 22.35 16.35 20.7 0 582.06 363.36 54362 +1950 144 20.48 14.48 18.83 0 524.91 370.62 54483 +1950 145 21.28 15.28 19.63 0.56 548.75 276.2 54600 +1950 146 22.15 16.15 20.5 0 575.7 365.41 54714 +1950 147 23.44 17.44 21.79 0.48 617.74 270.6 54824 +1950 148 25.94 19.94 24.29 0.17 706.64 262.67 54931 +1950 149 25.78 19.78 24.13 0.02 700.65 263.45 55034 +1950 150 24.68 18.68 23.03 0 660.57 356.54 55134 +1950 151 22.46 16.46 20.81 0 585.58 366.06 55229 +1950 152 22.22 16.22 20.57 0 577.92 367.09 55321 +1950 153 21.94 15.94 20.29 0 569.1 368.39 55409 +1950 154 23.17 17.17 21.52 0.53 608.73 272.93 55492 +1950 155 27.27 21.27 25.62 0.01 758.19 259.14 55572 +1950 156 27.16 21.16 25.51 0.07 753.81 259.79 55648 +1950 157 25.18 19.18 23.53 0 678.54 355.98 55719 +1950 158 24.89 18.89 23.24 0 668.07 357.44 55786 +1950 159 27.97 21.97 26.32 0 786.58 342.78 55849 +1950 160 23.29 17.29 21.64 0.41 612.72 273.5 55908 +1950 161 23.04 17.04 21.39 0 604.44 365.74 55962 +1950 162 21.09 15.09 19.44 0 543 373.21 56011 +1950 163 22.95 16.95 21.3 0 601.48 366.36 56056 +1950 164 21.87 15.87 20.22 0.13 566.91 277.95 56097 +1950 165 21.09 15.09 19.44 0.08 543 280.17 56133 +1950 166 22.49 16.49 20.84 0 586.54 368.39 56165 +1950 167 24.88 18.88 23.23 0 667.71 358.38 56192 +1950 168 21.59 15.59 19.94 0 558.23 371.84 56214 +1950 169 18.02 12.02 16.37 0.01 457.05 287.87 56231 +1950 170 20.69 14.69 19.04 0 531.08 375.11 56244 +1950 171 21.27 15.27 19.62 0 548.44 373.09 56252 +1950 172 25.41 19.41 23.76 0 686.94 356.12 56256 +1950 173 25.27 19.27 23.62 0.04 681.82 267.56 56255 +1950 174 23.28 17.28 21.63 0.47 612.39 273.92 56249 +1950 175 21.01 15.01 19.36 0 540.6 373.89 56238 +1950 176 19.41 13.41 17.76 0 494.41 379.34 56223 +1950 177 22.34 16.34 20.69 0 581.74 368.79 56203 +1950 178 20.65 14.65 19 0.17 529.9 281.29 56179 +1950 179 25.77 19.77 24.12 0 700.27 354.13 56150 +1950 180 26.47 20.47 24.82 0 726.82 350.68 56116 +1950 181 24.41 18.41 22.76 0.02 651.04 270.05 56078 +1950 182 22.55 16.55 20.9 0 588.47 367.57 56035 +1950 183 24.94 18.94 23.29 0 669.86 357.42 55987 +1950 184 24.55 18.55 22.9 0.05 655.97 269.24 55935 +1950 185 24.84 18.84 23.19 0 666.28 357.64 55879 +1950 186 24.5 18.5 22.85 0.25 654.2 269.16 55818 +1950 187 23 17 21.35 0 603.12 364.95 55753 +1950 188 25.33 19.33 23.68 0 684.01 354.75 55684 +1950 189 30.55 24.55 28.9 0 899.07 327.22 55611 +1950 190 29.8 23.8 28.15 0.39 865.05 248.46 55533 +1950 191 25.71 19.71 24.06 3.5 698.04 264.17 55451 +1950 192 26.57 20.57 24.92 0 730.68 347.86 55366 +1950 193 23.29 17.29 21.64 0.2 612.72 271.62 55276 +1950 194 21.8 15.8 20.15 0.02 564.73 275.8 55182 +1950 195 20.69 14.69 19.04 0 531.08 371.46 55085 +1950 196 21.36 15.36 19.71 0 551.18 368.67 54984 +1950 197 25.18 19.18 23.53 0 678.54 352.78 54879 +1950 198 27.41 21.41 25.76 0 763.8 341.76 54770 +1950 199 28.43 22.43 26.78 0 805.71 336.14 54658 +1950 200 27.12 21.12 25.47 0.09 752.22 256.88 54542 +1950 201 25.34 19.34 23.69 0 684.38 350.48 54423 +1950 202 23.98 17.98 22.33 0.52 636.09 266.88 54301 +1950 203 21.6 15.6 19.95 0 558.54 364.65 54176 +1950 204 24.75 18.75 23.1 0.17 663.06 263.68 54047 +1950 205 28.11 22.11 26.46 0.05 792.36 251.3 53915 +1950 206 28.1 22.1 26.45 0 791.95 334.59 53780 +1950 207 27.75 21.75 26.1 0 777.56 335.78 53643 +1950 208 27.87 21.87 26.22 0.17 782.47 250.91 53502 +1950 209 25.95 19.95 24.3 0.23 707.02 257.46 53359 +1950 210 24.93 18.93 23.28 0.29 669.5 260.44 53213 +1950 211 21.27 15.27 19.62 0.25 548.44 270.7 53064 +1950 212 20.01 14.01 18.36 0 511.32 364.45 52913 +1950 213 22.15 16.15 20.5 0.24 575.7 267.14 52760 +1950 214 20.52 14.52 18.87 0.05 526.08 270.93 52604 +1950 215 18.66 12.66 17.01 0.25 473.94 274.9 52445 +1950 216 17.64 11.64 15.99 0 447.27 368.51 52285 +1950 217 20.36 14.36 18.71 0 521.41 359.2 52122 +1950 218 24.59 18.59 22.94 0.29 657.38 256.85 51958 +1950 219 21.03 15.03 19.38 0 541.2 355.07 51791 +1950 220 23.7 17.7 22.05 0 626.52 344.21 51622 +1950 221 27.04 21.04 25.39 0 749.06 328.59 51451 +1950 222 29.14 23.14 27.49 0 836.02 316.98 51279 +1950 223 29.33 23.33 27.68 0.02 844.3 236.18 51105 +1950 224 26.78 20.78 25.13 0.15 738.84 245.08 50929 +1950 225 26.96 20.96 25.31 0 745.9 324.84 50751 +1950 226 24.32 18.32 22.67 0 647.88 335.37 50572 +1950 227 27.49 21.49 25.84 0 767.02 320.04 50392 +1950 228 26.09 20.09 24.44 0 712.3 325.41 50210 +1950 229 24.4 18.4 22.75 0 650.69 331.44 50026 +1950 230 25.28 19.28 23.63 0 682.18 326.56 49842 +1950 231 26.18 20.18 24.53 0 715.72 321.24 49656 +1950 232 24.73 18.73 23.08 0.71 662.35 244.62 49469 +1950 233 25.73 19.73 24.08 0.01 698.78 240.44 49280 +1950 234 26.05 20.05 24.4 0 710.79 317.85 49091 +1950 235 25.22 19.22 23.57 0 679.99 319.99 48900 +1950 236 25.44 19.44 23.79 0 688.04 317.72 48709 +1950 237 26.57 20.57 24.92 0.28 730.68 233.44 48516 +1950 238 25.36 19.36 23.71 0.75 685.11 236.17 48323 +1950 239 18.99 12.99 17.34 0.11 482.86 251.8 48128 +1950 240 21.6 15.6 19.95 0.16 558.54 244.37 47933 +1950 241 18.98 12.98 17.33 1.51 482.59 249.22 47737 +1950 242 21.17 15.17 19.52 0.76 545.42 242.89 47541 +1950 243 21.57 15.57 19.92 0.51 557.61 240.54 47343 +1950 244 15 9 13.35 0.66 384.09 252.74 47145 +1950 245 18.87 12.87 17.22 3.03 479.6 244.01 46947 +1950 246 19.61 13.61 17.96 2.81 500 240.95 46747 +1950 247 17.42 11.42 15.77 0.69 441.69 244.07 46547 +1950 248 11.9 5.9 10.25 0 319.78 335.51 46347 +1950 249 11.99 5.99 10.34 0 321.51 333.22 46146 +1950 250 8.6 2.6 6.95 0 261.67 336.8 45945 +1950 251 10.28 4.28 8.63 0.03 290 248.99 45743 +1950 252 15.49 9.49 13.84 0 395.2 319.74 45541 +1950 253 20.11 14.11 18.46 0.66 514.19 229.35 45339 +1950 254 22.68 16.68 21.03 0.02 592.67 221.78 45136 +1950 255 20.93 14.93 19.28 0 538.21 299.08 44933 +1950 256 20.9 14.9 19.25 0.2 537.31 222.72 44730 +1950 257 20.46 14.46 18.81 0.18 524.33 222.11 44527 +1950 258 17.02 11.02 15.37 1.35 431.69 227.15 44323 +1950 259 18.89 12.89 17.24 0.01 480.14 221.84 44119 +1950 260 19.91 13.91 18.26 0 508.47 290.7 43915 +1950 261 23.92 17.92 22.27 0 634.03 275.93 43711 +1950 262 18.27 12.27 16.62 0 463.59 290.26 43507 +1950 263 20.69 14.69 19.04 0 531.08 281.41 43303 +1950 264 21.96 15.96 20.31 0.01 569.72 206.4 43099 +1950 265 20.69 14.69 19.04 0 531.08 276.62 42894 +1950 266 21.92 15.92 20.27 0.26 568.47 203 42690 +1950 267 21.29 15.29 19.64 0.16 549.05 202.45 42486 +1950 268 19.99 13.99 18.34 0.11 510.75 203.27 42282 +1950 269 20.48 14.48 18.83 0 524.91 267.28 42078 +1950 270 20.91 14.91 19.26 0 537.61 263.57 41875 +1950 271 23.95 17.95 22.3 0 635.06 252.01 41671 +1950 272 24.18 18.18 22.53 0.98 643.01 186.53 41468 +1950 273 27.93 21.93 26.28 0.35 784.93 174.71 41265 +1950 274 18.93 12.93 17.28 0 481.23 258.4 41062 +1950 275 16.28 10.28 14.63 0.62 413.7 196.13 40860 +1950 276 14.3 8.3 12.65 0.81 368.68 196.94 40658 +1950 277 9.3 3.3 7.65 0.25 273.17 200.69 40456 +1950 278 11.81 5.81 10.16 0.21 318.06 195.86 40255 +1950 279 8.05 2.05 6.4 0.03 252.93 197.51 40054 +1950 280 11.66 5.66 10.01 0.32 315.21 191.89 39854 +1950 281 10 4 8.35 0 285.11 255.42 39654 +1950 282 8.54 2.54 6.89 0.1 260.7 190.85 39455 +1950 283 4.78 -1.22 3.13 0.45 205.94 191.67 39256 +1950 284 5 -1 3.35 0.5 208.85 189.19 39058 +1950 285 4.2 -1.8 2.55 1.34 198.45 187.69 38861 +1950 286 2.1 -3.9 0.45 0.65 173.24 186.85 38664 +1950 287 4.7 -1.3 3.05 0.13 204.89 182.96 38468 +1950 288 9.02 3.02 7.37 1.47 268.52 177.5 38273 +1950 289 11.06 5.06 9.41 0.03 304.03 173.6 38079 +1950 290 8.5 2.5 6.85 0.15 260.06 173.76 37885 +1950 291 9.33 3.33 7.68 0.1 273.67 171 37693 +1950 292 10.95 4.95 9.3 0 302.02 223.32 37501 +1950 293 10.03 4.03 8.38 0 285.63 221.71 37311 +1950 294 11.14 5.14 9.49 0.03 305.5 163.08 37121 +1950 295 10.71 4.71 9.06 0 297.67 215.14 36933 +1950 296 15.88 9.88 14.23 0 404.24 205.18 36745 +1950 297 15.13 9.13 13.48 0.07 387.01 152.79 36560 +1950 298 15.22 9.22 13.57 0 389.05 201.02 36375 +1950 299 17.26 11.26 15.61 0 437.66 194.93 36191 +1950 300 17.32 11.32 15.67 0.26 439.17 144.19 36009 +1950 301 19.11 13.11 17.46 0 486.14 186.57 35829 +1950 302 23.05 17.05 21.4 1.8 604.77 131.79 35650 +1950 303 15.86 9.86 14.21 0.52 403.78 140.38 35472 +1950 304 14.01 8.01 12.36 0.2 362.45 140.61 35296 +1950 305 10.07 4.07 8.42 0 286.32 189.57 35122 +1950 306 12.56 6.56 10.91 0.01 332.64 138.35 34950 +1950 307 7.17 1.17 5.52 0 239.46 187.62 34779 +1950 308 7.88 1.88 6.23 0 250.27 184.36 34610 +1950 309 8.8 2.8 7.15 0 264.91 181.18 34444 +1950 310 9.36 3.36 7.71 0.07 274.18 133.65 34279 +1950 311 10.46 4.46 8.81 0 293.19 174.92 34116 +1950 312 11.14 5.14 9.49 0 305.5 171.58 33956 +1950 313 12.3 6.3 10.65 0.68 327.52 126.16 33797 +1950 314 14.23 8.23 12.58 0.02 367.17 122.98 33641 +1950 315 15.04 9.04 13.39 0.02 384.99 120.33 33488 +1950 316 13.66 7.66 12.01 0.91 355.05 120.05 33337 +1950 317 10.54 4.54 8.89 2 294.62 121.01 33188 +1950 318 8.08 2.08 6.43 0 253.4 161.27 33042 +1950 319 6.44 0.44 4.79 0.41 228.76 120.66 32899 +1950 320 5.64 -0.36 3.99 1.13 217.5 119.69 32758 +1950 321 2.79 -3.21 1.14 2.32 181.2 119.48 32620 +1950 322 1.55 -4.45 -0.1 0.28 167.11 118.62 32486 +1950 323 1.26 -4.74 -0.39 0.28 163.96 117.5 32354 +1950 324 4.89 -1.11 3.24 0.18 207.39 114.35 32225 +1950 325 4.7 -1.3 3.05 0.01 204.89 113.15 32100 +1950 326 9.31 3.31 7.66 0 273.34 145.98 31977 +1950 327 8.67 2.67 7.02 0.4 262.8 108.51 31858 +1950 328 7.65 1.65 6 0.7 246.72 107.65 31743 +1950 329 7.96 1.96 6.31 0.39 251.52 106.35 31631 +1950 330 7.99 1.99 6.34 0.16 251.99 105.26 31522 +1950 331 6.08 0.08 4.43 0.38 223.63 105.3 31417 +1950 332 5.22 -0.78 3.57 0 211.79 139.33 31316 +1950 333 7.56 1.56 5.91 0 245.35 136.65 31218 +1950 334 11.08 5.08 9.43 0.1 304.4 99.53 31125 +1950 335 5.39 -0.61 3.74 0 214.09 135.86 31035 +1950 336 7.6 1.6 5.95 0.02 245.96 99.98 30949 +1950 337 5.72 -0.28 4.07 0.12 218.61 99.69 30867 +1950 338 5.13 -0.87 3.48 0.13 210.58 99.26 30790 +1950 339 4.18 -1.82 2.53 0 198.19 132.11 30716 +1950 340 0.15 -5.85 -1.5 0.01 152.36 100.04 30647 +1950 341 4.92 -1.08 3.27 0 207.79 130.03 30582 +1950 342 5.17 -0.83 3.52 0 211.12 129.12 30521 +1950 343 7.13 1.13 5.48 0 238.86 127.05 30465 +1950 344 7.46 1.46 5.81 0 243.83 125.7 30413 +1950 345 5.27 -0.73 3.62 0 212.46 126.68 30366 +1950 346 5.94 -0.06 4.29 0.05 221.67 94.3 30323 +1950 347 6.56 0.56 4.91 2.74 230.49 93.56 30284 +1950 348 7.67 1.67 6.02 0.43 247.03 92.74 30251 +1950 349 4.71 -1.29 3.06 0 205.02 125.14 30221 +1950 350 2.33 -3.67 0.68 0 175.86 126.06 30197 +1950 351 0.91 -5.09 -0.74 0.08 160.22 94.87 30177 +1950 352 -0.15 -6.15 -1.8 0.27 149.35 139.76 30162 +1950 353 1.17 -4.83 -0.48 0.54 162.99 139.15 30151 +1950 354 2.68 -3.32 1.03 0.67 179.91 138.24 30145 +1950 355 -1.58 -7.58 -3.23 0.68 135.69 141.78 30144 +1950 356 -1.55 -7.55 -3.2 0.07 135.96 142.01 30147 +1950 357 1.52 -4.48 -0.13 0 166.78 172.41 30156 +1950 358 4.44 -1.56 2.79 0 201.52 170.41 30169 +1950 359 5.3 -0.7 3.65 0 212.87 169.3 30186 +1950 360 7.4 1.4 5.75 2.01 242.92 136.47 30208 +1950 361 4.1 -1.9 2.45 0.11 197.18 94.29 30235 +1950 362 2.46 -3.54 0.81 0 177.35 127.01 30267 +1950 363 -0.38 -6.38 -2.03 0.38 147.07 141.42 30303 +1950 364 1 -5 -0.65 0.14 161.18 141.09 30343 +1950 365 1.14 -4.86 -0.51 0.95 162.67 141.25 30388 +1951 1 2.08 -3.92 0.43 1.6 173.01 141.24 30438 +1951 2 -2.95 -8.95 -4.6 0.56 123.63 145.04 30492 +1951 3 -0.1 -6.1 -1.75 0 149.84 177.93 30551 +1951 4 -0.02 -6.02 -1.67 0 150.64 178.72 30614 +1951 5 -0.16 -6.16 -1.81 0 149.25 179.34 30681 +1951 6 4.75 -1.25 3.1 0.08 205.55 143.94 30752 +1951 7 5.14 -0.86 3.49 0.29 210.72 143.57 30828 +1951 8 7.28 1.28 5.63 0.19 241.11 142.57 30907 +1951 9 9.04 3.04 7.39 0.75 268.85 99.67 30991 +1951 10 6.06 0.06 4.41 0.09 223.35 102.25 31079 +1951 11 3.47 -2.53 1.82 0 189.35 138.9 31171 +1951 12 -0.57 -6.57 -2.22 0 145.22 141.9 31266 +1951 13 -0.68 -6.68 -2.33 0.01 144.15 149.8 31366 +1951 14 -1.42 -7.42 -3.07 0 137.16 187.37 31469 +1951 15 2.01 -3.99 0.36 0 172.22 145.25 31575 +1951 16 4.09 -1.91 2.44 0.69 197.05 109.03 31686 +1951 17 5.92 -0.08 4.27 0 221.39 145.88 31800 +1951 18 5.19 -0.81 3.54 0 211.39 148.26 31917 +1951 19 2.51 -3.49 0.86 0 177.93 151.81 32038 +1951 20 8.5 2.5 6.85 0 260.06 149.3 32161 +1951 21 8.71 2.71 7.06 0 263.45 151.11 32289 +1951 22 12.36 6.36 10.71 0.04 328.69 112.02 32419 +1951 23 6.73 0.73 5.08 0.19 232.96 117.12 32552 +1951 24 7.05 1.05 5.4 0.01 237.67 118.48 32688 +1951 25 2.02 -3.98 0.37 0 172.34 163.19 32827 +1951 26 5.98 -0.02 4.33 0.07 222.23 121.92 32969 +1951 27 4.94 -1.06 3.29 0 208.05 165.32 33114 +1951 28 5.62 -0.38 3.97 0 217.23 167.03 33261 +1951 29 7.38 1.38 5.73 0.7 242.61 126.02 33411 +1951 30 8.87 2.87 7.22 0.17 266.06 126.71 33564 +1951 31 7.72 1.72 6.07 0 247.8 172.31 33718 +1951 32 6.27 0.27 4.62 0 226.32 175.6 33875 +1951 33 8.66 2.66 7.01 0 262.64 176.15 34035 +1951 34 9.38 3.38 7.73 0 274.51 177.64 34196 +1951 35 8.38 2.38 6.73 0 258.14 180.7 34360 +1951 36 9.01 3.01 7.36 0 268.36 182.58 34526 +1951 37 5.63 -0.37 3.98 0.17 217.37 140.98 34694 +1951 38 2.61 -3.39 0.96 0.75 179.09 144.68 34863 +1951 39 5.4 -0.6 3.75 0.01 214.22 145.12 35035 +1951 40 6.95 0.95 5.3 0 236.19 194.79 35208 +1951 41 5.89 -0.11 4.24 0.13 220.97 148.73 35383 +1951 42 5.81 -0.19 4.16 0 219.85 200.92 35560 +1951 43 7.24 1.24 5.59 0 240.5 202.35 35738 +1951 44 8 2 6.35 0 252.14 204.16 35918 +1951 45 6.45 0.45 4.8 0.1 228.9 156.17 36099 +1951 46 5.24 -0.76 3.59 0.02 212.06 158.97 36282 +1951 47 7.15 1.15 5.5 0.03 239.16 159.79 36466 +1951 48 10.12 4.12 8.47 0.25 287.2 159.51 36652 +1951 49 11.49 5.49 9.84 0 312.01 213.73 36838 +1951 50 13.32 7.32 11.67 0.08 347.99 160.37 37026 +1951 51 10.6 4.6 8.95 0.6 295.69 165.28 37215 +1951 52 9.68 3.68 8.03 0.25 279.6 168.2 37405 +1951 53 5.31 -0.69 3.66 0.04 213 173.8 37596 +1951 54 8.84 2.84 7.19 1.18 265.57 173.16 37788 +1951 55 7.44 1.44 5.79 0 243.52 235.39 37981 +1951 56 6.26 0.26 4.61 0 226.18 239.27 38175 +1951 57 5.83 -0.17 4.18 0.14 220.13 181.93 38370 +1951 58 3.99 -2.01 2.34 0.88 195.79 185.4 38565 +1951 59 2.21 -3.79 0.56 0.15 174.49 188.54 38761 +1951 60 2.45 -3.55 0.8 0.8 177.24 190.58 38958 +1951 61 6.81 0.81 5.16 2.01 234.13 189.77 39156 +1951 62 5.64 -0.36 3.99 0.17 217.5 192.77 39355 +1951 63 1.49 -4.51 -0.16 0 166.46 263.69 39553 +1951 64 0.17 -5.83 -1.48 0.03 152.56 200.71 39753 +1951 65 1.09 -4.91 -0.56 0 162.13 269.87 39953 +1951 66 5.53 -0.47 3.88 0 215.99 268.72 40154 +1951 67 5.92 -0.08 4.27 0.29 221.39 203.42 40355 +1951 68 5 -1 3.35 0 208.85 275.06 40556 +1951 69 8.82 2.82 7.17 0 265.24 273.34 40758 +1951 70 6.96 0.96 5.31 0.15 236.34 208.83 40960 +1951 71 5.83 -0.17 4.18 0.25 220.13 211.97 41163 +1951 72 5.76 -0.24 4.11 0.08 219.16 214.16 41366 +1951 73 6.44 0.44 4.79 0 228.76 287.47 41569 +1951 74 8.68 2.68 7.03 0 262.96 287.46 41772 +1951 75 12.33 6.33 10.68 0 328.11 284.72 41976 +1951 76 16.38 10.38 14.73 0 416.09 279.6 42179 +1951 77 12.86 6.86 11.21 0.72 338.63 216.72 42383 +1951 78 9.23 3.23 7.58 0.6 272 222.98 42587 +1951 79 7.5 1.5 5.85 0 244.43 302.35 42791 +1951 80 6.63 0.63 4.98 0 231.5 305.98 42996 +1951 81 7.93 1.93 6.28 0.06 251.05 230.19 43200 +1951 82 9.79 3.79 8.14 0.06 281.48 230.22 43404 +1951 83 12.31 6.31 10.66 0.28 327.71 229 43608 +1951 84 13.02 7.02 11.37 0.28 341.86 229.92 43812 +1951 85 8.48 2.48 6.83 0.19 259.74 237.28 44016 +1951 86 9.27 3.27 7.62 0.04 272.67 238.24 44220 +1951 87 13.43 7.43 11.78 0.48 350.26 234.82 44424 +1951 88 7.85 1.85 6.2 0.81 249.81 243.43 44627 +1951 89 5.4 -0.6 3.75 0.04 214.22 247.5 44831 +1951 90 9.7 3.7 8.05 0.23 279.94 244.89 45034 +1951 91 9.35 3.35 7.7 0 274.01 329.32 45237 +1951 92 8.99 2.99 7.34 0 268.03 332.12 45439 +1951 93 9.67 3.67 8.02 0 279.43 333.29 45642 +1951 94 8.97 2.97 7.32 0 267.7 336.54 45843 +1951 95 11.11 5.11 9.46 0 304.95 335.2 46045 +1951 96 16.27 10.27 14.62 0.06 413.46 245.01 46246 +1951 97 12.89 6.89 11.24 0 339.23 336.05 46446 +1951 98 14.07 8.07 12.42 0.45 363.73 251.69 46647 +1951 99 12.38 6.38 10.73 1.59 329.09 255.74 46846 +1951 100 10.67 4.67 9.02 0.11 296.95 259.55 47045 +1951 101 13.57 7.57 11.92 0 353.17 342.46 47243 +1951 102 14.9 8.9 13.25 0 381.86 341.45 47441 +1951 103 15.64 9.64 13.99 0 398.66 341.54 47638 +1951 104 17.03 11.03 15.38 0.07 431.94 254.91 47834 +1951 105 19.5 13.5 17.85 0 496.92 334.73 48030 +1951 106 17.26 11.26 15.61 0 437.66 342.63 48225 +1951 107 14.95 8.95 13.3 0 382.97 350 48419 +1951 108 11.68 5.68 10.03 0 315.59 358.62 48612 +1951 109 10.82 4.82 9.17 0 299.65 361.84 48804 +1951 110 10.81 4.81 9.16 0.11 299.47 272.46 48995 +1951 111 14.87 8.87 13.22 0 381.19 356.43 49185 +1951 112 11.72 5.72 10.07 0 316.34 364.66 49374 +1951 113 11.03 5.03 9.38 0 303.48 367.33 49561 +1951 114 13.04 7.04 11.39 0 342.26 364.83 49748 +1951 115 13.7 7.7 12.05 0 355.89 364.84 49933 +1951 116 11.63 5.63 9.98 0 314.64 370.36 50117 +1951 117 14.86 8.86 13.21 0 380.96 364.7 50300 +1951 118 15.35 9.35 13.7 0 392 364.82 50481 +1951 119 16.1 10.1 14.45 0 409.42 364.12 50661 +1951 120 14.77 8.77 13.12 0.09 378.97 276.43 50840 +1951 121 17.01 11.01 15.36 0.24 431.44 272.99 51016 +1951 122 16.14 10.14 14.49 0.02 410.37 275.61 51191 +1951 123 19.19 13.19 17.54 0 488.33 359.82 51365 +1951 124 19.59 13.59 17.94 0.11 499.44 269.71 51536 +1951 125 17.12 11.12 15.47 0 434.17 367.92 51706 +1951 126 21.86 15.86 20.21 0 566.6 353.79 51874 +1951 127 16.42 10.42 14.77 0.75 417.05 278.76 52039 +1951 128 19.23 13.23 17.58 0 489.43 364.52 52203 +1951 129 19.3 13.3 17.65 0.25 491.36 273.85 52365 +1951 130 21.02 15.02 19.37 0.01 540.9 270.14 52524 +1951 131 18.73 12.73 17.08 0.01 475.82 276.35 52681 +1951 132 22.18 16.18 20.53 0.24 576.65 268.16 52836 +1951 133 20.39 14.39 18.74 1.05 522.29 273.45 52989 +1951 134 21.29 15.29 19.64 0.52 549.05 271.62 53138 +1951 135 15.73 9.73 14.08 1.75 400.75 284.89 53286 +1951 136 16.34 10.34 14.69 2.16 415.13 284.16 53430 +1951 137 13.73 7.73 12.08 1.83 356.52 289.58 53572 +1951 138 14.73 8.73 13.08 0.19 378.08 288.25 53711 +1951 139 15.07 9.07 13.42 0.21 385.66 288.14 53848 +1951 140 12.57 6.57 10.92 0.46 332.83 292.87 53981 +1951 141 12.64 6.64 10.99 0.09 334.22 293.1 54111 +1951 142 13.5 7.5 11.85 0.62 351.71 292.04 54238 +1951 143 14.06 8.06 12.41 0.3 363.52 291.47 54362 +1951 144 10.81 4.81 9.16 0 299.47 396.1 54483 +1951 145 10.51 4.51 8.86 0 294.08 397.17 54600 +1951 146 11.35 5.35 9.7 0 309.39 395.91 54714 +1951 147 17.53 11.53 15.88 0.02 444.47 285.98 54824 +1951 148 16.71 10.71 15.06 0.47 424.07 288.02 54931 +1951 149 20.1 14.1 18.45 1.2 513.9 280.43 55034 +1951 150 20.71 14.71 19.06 0 531.67 372.13 55134 +1951 151 21.12 15.12 19.47 0 543.91 371.06 55229 +1951 152 24.04 18.04 22.39 0 638.16 359.77 55321 +1951 153 18.51 12.51 16.86 0.08 469.94 285.1 55409 +1951 154 18 12 16.35 0.04 456.53 286.5 55492 +1951 155 19.99 13.99 18.34 0.52 510.75 281.88 55572 +1951 156 22.79 16.79 21.14 0.49 596.25 274.44 55648 +1951 157 25.1 19.1 23.45 1.03 675.64 267.25 55719 +1951 158 24.83 18.83 23.18 0.71 665.92 268.28 55786 +1951 159 21.51 15.51 19.86 3.15 555.77 278.53 55849 +1951 160 22.04 16.04 20.39 1.14 572.24 277.18 55908 +1951 161 17.71 11.71 16.06 2.24 449.06 288.17 55962 +1951 162 15.77 9.77 14.12 0.4 401.68 292.3 56011 +1951 163 17.73 11.73 16.08 0.15 449.57 288.33 56056 +1951 164 17.21 11.21 15.56 0.56 436.41 289.51 56097 +1951 165 14.6 8.6 12.95 0 375.22 393.08 56133 +1951 166 15.81 9.81 14.16 0 402.61 390.06 56165 +1951 167 15.09 9.09 13.44 0 386.11 391.88 56192 +1951 168 17.21 11.21 15.56 0 436.41 386.21 56214 +1951 169 18.55 12.55 16.9 0.74 471 286.65 56231 +1951 170 19.12 13.12 17.47 0 486.41 380.4 56244 +1951 171 21.88 15.88 20.23 0 567.22 370.83 56252 +1951 172 25.47 19.47 23.82 0.04 689.15 266.88 56256 +1951 173 25.15 19.15 23.5 0 677.45 357.29 56255 +1951 174 25.72 19.72 24.07 0.32 698.41 265.94 56249 +1951 175 25.31 19.31 23.66 0 683.28 356.45 56238 +1951 176 25.2 19.2 23.55 0.2 679.27 267.69 56223 +1951 177 26.24 20.24 24.59 0.05 718 263.98 56203 +1951 178 25.19 19.19 23.54 0.92 678.9 267.67 56179 +1951 179 22.67 16.67 21.02 0.24 592.35 275.57 56150 +1951 180 24.19 18.19 22.54 0.12 643.35 270.81 56116 +1951 181 22.39 16.39 20.74 0.26 583.34 276.25 56078 +1951 182 26.93 20.93 25.28 1.13 744.72 261.17 56035 +1951 183 26.91 20.91 25.26 0.1 743.94 261.12 55987 +1951 184 25.65 19.65 24 0 695.8 354.05 55935 +1951 185 24.82 18.82 23.17 0.01 665.56 268.29 55879 +1951 186 25.54 19.54 23.89 0.4 691.73 265.67 55818 +1951 187 24.67 18.67 23.02 0.32 660.22 268.47 55753 +1951 188 26.85 20.85 25.2 0.05 741.58 260.67 55684 +1951 189 26.58 20.58 24.93 0.03 731.07 261.53 55611 +1951 190 27.51 21.51 25.86 0 767.83 343.72 55533 +1951 191 25.89 19.89 24.24 0 704.76 351.39 55451 +1951 192 31.53 25.53 29.88 0 945.21 320.34 55366 +1951 193 29.45 23.45 27.8 0 849.56 332.51 55276 +1951 194 25.31 19.31 23.66 0.17 683.28 264.97 55182 +1951 195 26.52 20.52 24.87 0 728.75 347.38 55085 +1951 196 21.39 15.39 19.74 0 552.1 368.56 54984 +1951 197 22.9 16.9 21.25 0 599.84 362.39 54879 +1951 198 20.59 14.59 18.94 1.08 528.14 277.9 54770 +1951 199 17.88 11.88 16.23 2.34 453.43 284.16 54658 +1951 200 17.41 11.41 15.76 0.59 441.43 284.88 54542 +1951 201 17.75 11.75 16.1 1.23 450.08 283.78 54423 +1951 202 15.79 9.79 14.14 1.42 402.14 287.43 54301 +1951 203 14.49 8.49 12.84 1.23 372.81 289.5 54176 +1951 204 15.42 9.42 13.77 0.73 393.6 287.37 54047 +1951 205 12.06 6.06 10.41 0 322.85 390.39 53915 +1951 206 13.53 7.53 11.88 0.01 352.34 289.95 53780 +1951 207 18.83 12.83 17.18 0 478.52 371.75 53643 +1951 208 18.03 12.03 16.38 0.01 457.31 280.14 53502 +1951 209 19.94 13.94 18.29 0 509.33 366.88 53359 +1951 210 18.73 12.73 17.08 0.35 475.82 277.58 53213 +1951 211 20.6 14.6 18.95 0.05 528.43 272.45 53064 +1951 212 25.84 19.84 24.19 0.23 702.89 256.26 52913 +1951 213 24.78 18.78 23.13 0.04 664.13 259.24 52760 +1951 214 21.07 15.07 19.42 0 542.4 359.35 52604 +1951 215 16.17 10.17 14.52 0 411.08 373.58 52445 +1951 216 16.42 10.42 14.77 0 417.05 371.88 52285 +1951 217 15.65 9.65 14 0 398.89 372.98 52122 +1951 218 22.01 16.01 20.36 0.05 571.29 264.46 51958 +1951 219 22.35 16.35 20.7 0 582.06 350.33 51791 +1951 220 18.98 12.98 17.33 0 482.59 360.81 51622 +1951 221 19.69 13.69 18.04 0.72 502.24 268.19 51451 +1951 222 19.06 13.06 17.41 0.05 484.77 268.88 51279 +1951 223 21.95 15.95 20.3 0.08 569.41 260.8 51105 +1951 224 21.63 15.63 19.98 0 559.46 347.83 50929 +1951 225 21.96 15.96 20.31 0 569.72 345.53 50751 +1951 226 21.84 15.84 20.19 0 565.97 344.83 50572 +1951 227 22.62 16.62 20.97 0 590.73 340.74 50392 +1951 228 24.62 18.62 22.97 0 658.44 331.73 50210 +1951 229 24.43 18.43 22.78 0 651.74 331.32 50026 +1951 230 28.23 22.23 26.58 0 797.35 312.94 49842 +1951 231 25.26 19.26 23.61 0.5 681.45 243.93 49656 +1951 232 25.55 19.55 23.9 0 692.1 322.71 49469 +1951 233 26.91 20.91 25.26 0 743.94 315.32 49280 +1951 234 26.85 20.85 25.2 0 741.58 314.27 49091 +1951 235 26.62 20.62 24.97 1.19 732.62 235.44 48900 +1951 236 27.16 21.16 25.51 0.3 753.81 232.59 48709 +1951 237 23.75 17.75 22.1 0 628.22 322.93 48516 +1951 238 20.71 14.71 19.06 0 531.67 331.98 48323 +1951 239 23.95 17.95 22.3 0.02 635.06 239.32 48128 +1951 240 24.99 18.99 23.34 0.2 671.66 234.98 47933 +1951 241 25.28 19.28 23.63 0.3 682.18 232.86 47737 +1951 242 26.35 20.35 24.7 0 722.21 304.34 47541 +1951 243 25.48 19.48 23.83 0 689.52 306.25 47343 +1951 244 22.25 16.25 20.6 0.02 578.87 237.48 47145 +1951 245 20.95 14.95 19.3 0.05 538.81 239.35 46947 +1951 246 22.53 16.53 20.88 0 587.83 311.98 46747 +1951 247 20.19 14.19 18.54 0.8 516.49 238.29 46547 +1951 248 18.82 12.82 17.17 0 478.25 319.75 46347 +1951 249 20.35 14.35 18.7 0.11 521.12 234.97 46146 +1951 250 21.63 15.63 19.98 0.76 559.46 230.55 45945 +1951 251 20.55 14.55 18.9 1.94 526.96 231.53 45743 +1951 252 17.48 11.48 15.83 0 443.2 315.02 45541 +1951 253 13.63 7.63 11.98 0 354.42 321.52 45339 +1951 254 18.46 12.46 16.81 0 468.61 308.26 45136 +1951 255 18.49 12.49 16.84 0 469.41 305.95 44933 +1951 256 23.06 17.06 21.41 0.21 605.1 217.56 44730 +1951 257 21.67 15.67 20.02 1.53 560.7 219.38 44527 +1951 258 21.35 15.35 19.7 0 550.88 291.22 44323 +1951 259 24.56 18.56 22.91 0 656.32 278.25 44119 +1951 260 21.79 15.79 20.14 0.02 564.42 213.91 43915 +1951 261 24.36 18.36 22.71 0.07 649.28 205.8 43711 +1951 262 26.16 20.16 24.51 0 714.96 265.54 43507 +1951 263 26.9 20.9 25.25 0 743.54 260.36 43303 +1951 264 19.7 13.7 18.05 0 502.53 281.63 43099 +1951 265 16.46 10.46 14.81 0 418.01 287.14 42894 +1951 266 17.44 11.44 15.79 0 442.19 282.47 42690 +1951 267 17.46 11.46 15.81 0 442.7 279.78 42486 +1951 268 16.34 10.34 14.69 0.18 415.13 209.79 42282 +1951 269 18.69 12.69 17.04 1.37 474.75 203.9 42078 +1951 270 18.95 12.95 17.3 0.01 481.77 201.49 41875 +1951 271 20.35 14.35 18.7 1.27 521.12 196.91 41671 +1951 272 19.73 13.73 18.08 0 503.37 261.5 41468 +1951 273 17.55 11.55 15.9 0 444.98 264.19 41265 +1951 274 11.86 5.86 10.21 0 319.01 272.17 41062 +1951 275 14.19 8.19 12.54 0 366.3 265.49 40860 +1951 276 12.98 6.98 11.33 0 341.05 264.86 40658 +1951 277 12.21 6.21 10.56 0 325.76 263.42 40456 +1951 278 12.3 6.3 10.65 0 327.52 260.39 40255 +1951 279 16.25 10.25 14.6 0 412.98 250.66 40054 +1951 280 11.81 5.81 10.16 0 318.06 255.63 39854 +1951 281 10.79 4.79 9.14 0 299.11 254.35 39654 +1951 282 14.91 8.91 13.26 0 382.08 245.13 39455 +1951 283 12.84 6.84 11.19 0 338.22 245.75 39256 +1951 284 10.66 4.66 9.01 0 296.77 245.86 39058 +1951 285 7.34 1.34 5.69 0 242.01 247.18 38861 +1951 286 9.53 3.53 7.88 0 277.05 241.85 38664 +1951 287 8.75 2.75 7.1 0 264.1 239.8 38468 +1951 288 16.43 10.43 14.78 0 417.29 225.67 38273 +1951 289 12.17 6.17 10.52 0 324.99 229.95 38079 +1951 290 7.93 1.93 6.28 0 251.05 232.31 37885 +1951 291 8.16 2.16 6.51 0 254.65 229.32 37693 +1951 292 5.38 -0.62 3.73 0 213.95 229.32 37501 +1951 293 6.6 0.6 4.95 0 231.07 225.4 37311 +1951 294 3.51 -2.49 1.86 0.01 189.84 168.85 37121 +1951 295 2.76 -3.24 1.11 0 180.85 222.79 36933 +1951 296 3.31 -2.69 1.66 0 187.4 219.72 36745 +1951 297 8.51 2.51 6.86 0 260.22 212.29 36560 +1951 298 15.81 9.81 14.16 0.06 402.61 150.06 36375 +1951 299 17.32 11.32 15.67 0 439.17 194.83 36191 +1951 300 15.23 9.23 13.58 0 389.27 195.67 36009 +1951 301 16.75 10.75 15.1 0 425.05 190.79 35829 +1951 302 17.86 11.86 16.21 0.37 452.91 139.77 35650 +1951 303 20.99 14.99 19.34 0.01 540 133.43 35472 +1951 304 22.16 16.16 20.51 0 576.02 173.09 35296 +1951 305 19.71 13.71 18.06 0 502.81 175.54 35122 +1951 306 16.1 10.1 14.45 0 409.42 179.57 34950 +1951 307 18 12 16.35 0 456.53 174.09 34779 +1951 308 18.77 12.77 17.12 0 476.9 170.27 34610 +1951 309 16.93 10.93 15.28 0.26 429.47 128.33 34444 +1951 310 13.05 7.05 11.4 0.06 342.47 130.6 34279 +1951 311 13.14 7.14 11.49 0 344.3 171.89 34116 +1951 312 10.32 4.32 8.67 0.1 290.71 129.33 33956 +1951 313 7.97 1.97 6.32 0.27 251.67 129.42 33797 +1951 314 6.04 0.04 4.39 1.96 223.07 129.13 33641 +1951 315 5.29 -0.71 3.64 0.04 212.73 127.64 33488 +1951 316 3.52 -2.48 1.87 1.17 189.96 126.89 33337 +1951 317 4.59 -1.41 2.94 0 203.46 166.27 33188 +1951 318 9.83 3.83 8.18 0 282.17 159.71 33042 +1951 319 10.87 4.87 9.22 0.88 300.56 117.77 32899 +1951 320 9.78 3.78 8.13 0.23 281.31 117.17 32758 +1951 321 7.38 1.38 5.73 0.34 242.61 117.13 32620 +1951 322 7.9 1.9 6.25 0.06 250.58 115.46 32486 +1951 323 10.34 4.34 8.69 0 291.06 150.23 32354 +1951 324 12.7 6.7 11.05 0.51 335.42 109.39 32225 +1951 325 9.73 3.73 8.08 0.57 280.45 110.29 32100 +1951 326 9.21 3.21 7.56 0 271.67 146.07 31977 +1951 327 9.82 3.82 8.17 0 282 143.71 31858 +1951 328 11.11 5.11 9.46 0 304.95 140.6 31743 +1951 329 14.7 8.7 13.05 0.22 377.42 101.53 31631 +1951 330 9.61 3.61 7.96 0 278.4 139.04 31522 +1951 331 3.81 -2.19 2.16 0.09 193.54 106.37 31417 +1951 332 6.62 0.62 4.97 0.01 231.36 103.8 31316 +1951 333 7.84 1.84 6.19 0.16 249.65 102.33 31218 +1951 334 9.2 3.2 7.55 0 271.5 134.31 31125 +1951 335 5.15 -0.85 3.5 0 210.85 136.01 31035 +1951 336 0.62 -5.38 -1.03 0 157.18 137.34 30949 +1951 337 -0.49 -6.49 -2.14 0 145.99 136.15 30867 +1951 338 1.23 -4.77 -0.42 0 163.64 134.44 30790 +1951 339 4.18 -1.82 2.53 0 198.19 132.11 30716 +1951 340 3.61 -2.39 1.96 0 191.06 131.7 30647 +1951 341 1.5 -4.5 -0.15 0.07 166.57 98.88 30582 +1951 342 -0.34 -6.34 -1.99 0 147.46 131.89 30521 +1951 343 -3.41 -9.41 -5.06 0 119.8 132.2 30465 +1951 344 -0.42 -6.42 -2.07 0 146.68 129.95 30413 +1951 345 3.08 -2.92 1.43 0 184.64 127.9 30366 +1951 346 6.32 0.32 4.67 0 227.04 125.49 30323 +1951 347 7.51 1.51 5.86 0 244.59 124.11 30284 +1951 348 9.98 3.98 8.33 0 284.76 121.94 30251 +1951 349 6.49 0.49 4.84 0.07 229.48 93.05 30221 +1951 350 10.09 4.09 8.44 0.2 286.67 90.86 30197 +1951 351 9.86 3.86 8.21 0.55 282.68 90.84 30177 +1951 352 4.45 -1.55 2.8 0.06 201.65 93.48 30162 +1951 353 5.25 -0.75 3.6 0 212.19 124.12 30151 +1951 354 6.63 0.63 4.98 0.01 231.5 92.43 30145 +1951 355 10.44 4.44 8.79 0 292.83 120.47 30144 +1951 356 7.45 1.45 5.8 0 243.67 122.72 30147 +1951 357 7.83 1.83 6.18 0 249.5 122.52 30156 +1951 358 3.7 -2.3 2.05 0.1 192.17 93.84 30169 +1951 359 7.49 1.49 5.84 0 244.28 122.95 30186 +1951 360 4.97 -1.03 3.32 0 208.45 124.9 30208 +1951 361 6.19 0.19 4.54 0 225.19 124.49 30235 +1951 362 3.48 -2.52 1.83 0 189.47 126.49 30267 +1951 363 2.87 -3.13 1.22 0.99 182.14 95.55 30303 +1951 364 4.9 -1.1 3.25 0.43 207.52 95.01 30343 +1951 365 1.96 -4.04 0.31 1.24 171.66 96.61 30388 +1952 1 -1.12 -7.12 -2.77 0.3 139.96 142.6 30438 +1952 2 1.45 -4.55 -0.2 2.1 166.02 142.06 30492 +1952 3 -1.28 -7.28 -2.93 0 138.46 176.76 30551 +1952 4 4.35 -1.65 2.7 0 200.36 174.34 30614 +1952 5 8.14 2.14 6.49 0 254.34 129.22 30681 +1952 6 7.29 1.29 5.64 0 241.26 130.71 30752 +1952 7 6.31 0.31 4.66 0.02 226.89 99.12 30828 +1952 8 4.67 -1.33 3.02 0 204.5 134.66 30907 +1952 9 1.27 -4.73 -0.38 0 164.07 137.74 30991 +1952 10 1.79 -4.21 0.14 0.09 169.76 104.1 31079 +1952 11 0.71 -5.29 -0.94 0 158.12 140.31 31171 +1952 12 2.57 -3.43 0.92 0.01 178.63 105.3 31266 +1952 13 -0.31 -6.31 -1.96 0.71 147.76 151.83 31366 +1952 14 1.3 -4.7 -0.35 0.21 164.39 152.07 31469 +1952 15 4.79 -1.21 3.14 0 206.07 186.85 31575 +1952 16 5.97 -0.03 4.32 0.05 222.09 150.4 31686 +1952 17 0.79 -5.21 -0.86 0.35 158.96 153.67 31800 +1952 18 -0.15 -6.15 -1.8 0 149.35 193.08 31917 +1952 19 -1.63 -7.63 -3.28 0 135.23 195.52 32038 +1952 20 -1.78 -7.78 -3.43 0 133.87 197.03 32161 +1952 21 -1.1 -7.1 -2.75 0 140.15 198.61 32289 +1952 22 2.91 -3.09 1.26 0 182.61 197.8 32419 +1952 23 5.52 -0.48 3.87 0 215.86 157.04 32552 +1952 24 6.3 0.3 4.65 0.73 226.75 118.9 32688 +1952 25 -1 -7 -2.65 0.88 141.09 166.33 32827 +1952 26 3.29 -2.71 1.64 0.65 187.16 165.48 32969 +1952 27 1.27 -4.73 -0.38 0.31 164.07 167.54 33114 +1952 28 5.6 -0.4 3.95 0.06 216.95 166.28 33261 +1952 29 8.02 2.02 6.37 0.03 252.46 165.46 33411 +1952 30 4.54 -1.46 2.89 0 202.81 172.41 33564 +1952 31 5.72 -0.28 4.07 0 218.61 173.92 33718 +1952 32 10.95 4.95 9.3 0 302.02 171.29 33875 +1952 33 12.38 6.38 10.73 0.07 329.09 129.2 34035 +1952 34 10.65 4.65 9 0.12 296.59 132.26 34196 +1952 35 7.7 1.7 6.05 1.09 247.49 135.99 34360 +1952 36 3.78 -2.22 2.13 0 193.17 186.93 34526 +1952 37 3.93 -2.07 2.28 0 195.04 189.25 34694 +1952 38 3.25 -2.75 1.6 0 186.68 192.47 34863 +1952 39 0.38 -5.62 -1.27 1.09 154.7 147.67 35035 +1952 40 4.27 -1.73 2.62 0 199.34 196.98 35208 +1952 41 2.72 -3.28 1.07 0 180.38 200.71 35383 +1952 42 3.36 -2.64 1.71 0 188.01 202.83 35560 +1952 43 0.84 -5.16 -0.81 0 159.48 207.22 35738 +1952 44 1.91 -4.09 0.26 0 171.1 209.13 35918 +1952 45 5.01 -0.99 3.36 0 208.98 209.47 36099 +1952 46 6.13 0.13 4.48 0 224.34 211.19 36282 +1952 47 6.59 0.59 4.94 0.64 230.92 160.19 36466 +1952 48 5.66 -0.34 4.01 0.75 217.78 162.92 36652 +1952 49 1.29 -4.71 -0.36 2.07 164.28 167.53 36838 +1952 50 4.14 -1.86 2.49 0.03 197.68 167.97 37026 +1952 51 3.03 -2.97 1.38 0.51 184.04 170.86 37215 +1952 52 1.29 -4.71 -0.36 0.22 164.28 173.94 37405 +1952 53 -0.01 -6.01 -1.66 0.17 150.74 212.37 37596 +1952 54 0.9 -5.1 -0.75 0.5 160.12 213.74 37788 +1952 55 0.28 -5.72 -1.37 0 153.68 276.47 37981 +1952 56 1.43 -4.57 -0.22 0 165.8 278.08 38175 +1952 57 2.24 -3.76 0.59 0.02 174.83 184.25 38370 +1952 58 2.95 -3.05 1.3 0.13 183.09 186.05 38565 +1952 59 -0.15 -6.15 -1.8 0 149.35 253.07 38761 +1952 60 0.27 -5.73 -1.38 0 153.58 255.72 38958 +1952 61 0.08 -5.92 -1.57 0 151.65 258.83 39156 +1952 62 2.57 -3.43 0.92 0 178.63 259.8 39355 +1952 63 4.11 -1.89 2.46 0 197.3 261.51 39553 +1952 64 0.41 -5.59 -1.24 0.02 155.01 200.58 39753 +1952 65 4.71 -1.29 3.06 0.46 205.02 200.09 39953 +1952 66 10.22 4.22 8.57 0 288.95 263.15 40154 +1952 67 13.48 7.48 11.83 0 351.3 261.03 40355 +1952 68 17 11 15.35 1.03 431.19 192.87 40556 +1952 69 12.02 6.02 10.37 0.73 322.08 201.59 40758 +1952 70 4.12 -1.88 2.47 0.08 197.43 211.08 40960 +1952 71 3.19 -2.81 1.54 0 185.95 285.25 41163 +1952 72 4.31 -1.69 2.66 0.11 199.85 215.28 41366 +1952 73 3.79 -2.21 2.14 0.23 193.29 217.69 41569 +1952 74 5.15 -0.85 3.5 0 210.85 291.65 41772 +1952 75 3.46 -2.54 1.81 0 189.23 296.1 41976 +1952 76 4.93 -1.07 3.28 0 207.92 297.29 42179 +1952 77 3.64 -2.36 1.99 0 191.43 301.24 42383 +1952 78 7.17 1.17 5.52 0 239.46 300.03 42587 +1952 79 5.78 -0.22 4.13 0 219.44 304.43 42791 +1952 80 4.46 -1.54 2.81 0.15 201.78 231.33 42996 +1952 81 2.37 -3.63 0.72 0 176.32 313.11 43200 +1952 82 5.19 -0.81 3.54 0.02 211.39 234.7 43404 +1952 83 6.74 0.74 5.09 0 233.1 313.62 43608 +1952 84 3.95 -2.05 2.3 0 195.29 319.37 43812 +1952 85 7.42 1.42 5.77 0 243.22 317.82 44016 +1952 86 7.72 1.72 6.07 0 247.8 319.84 44220 +1952 87 7.32 1.32 5.67 0 241.71 322.92 44424 +1952 88 9 3 7.35 0 268.19 322.94 44627 +1952 89 7.81 1.81 6.16 0 249.19 326.92 44831 +1952 90 7.13 1.13 5.48 0 238.86 330.23 45034 +1952 91 20.3 14.3 18.65 0 519.67 305.51 45237 +1952 92 15.64 9.64 13.99 0 398.66 319.74 45439 +1952 93 15.99 9.99 14.34 0 406.83 321.1 45642 +1952 94 15.01 9.01 13.36 0 384.31 325.42 45843 +1952 95 13.74 7.74 12.09 0 356.73 330.22 46045 +1952 96 9.93 3.93 8.28 0 283.89 339.31 46246 +1952 97 12.7 6.7 11.05 0 335.42 336.42 46446 +1952 98 10.63 4.63 8.98 0 296.23 342.16 46647 +1952 99 9.6 3.6 7.95 0 278.23 345.9 46846 +1952 100 12.87 6.87 11.22 0.13 338.83 256.47 47045 +1952 101 15.1 9.1 13.45 0.03 386.34 254.34 47243 +1952 102 13.43 7.43 11.78 0 350.26 344.64 47441 +1952 103 11.46 5.46 9.81 0 311.44 350.33 47638 +1952 104 14.06 8.06 12.41 0 363.52 346.94 47834 +1952 105 12.84 6.84 11.19 0 338.22 351.28 48030 +1952 106 15.61 9.61 13.96 0 397.97 346.79 48225 +1952 107 19.3 13.3 17.65 0 491.36 338.52 48419 +1952 108 22.05 16.05 20.4 0 572.55 331.28 48612 +1952 109 19.07 13.07 17.42 0 485.04 342.44 48804 +1952 110 19.53 13.53 17.88 0 497.76 342.41 48995 +1952 111 17.88 11.88 16.23 0 453.43 348.73 49185 +1952 112 15.99 9.99 14.34 0 406.83 355.22 49374 +1952 113 13.54 7.54 11.89 0 352.55 362.27 49561 +1952 114 15.87 9.87 14.22 0 404.01 358.32 49748 +1952 115 17.64 11.64 15.99 0 447.27 355.05 49933 +1952 116 18.62 12.62 16.97 0 472.87 353.42 50117 +1952 117 19.75 13.75 18.1 0 503.94 351.24 50300 +1952 118 21.66 15.66 20.01 0 560.39 346.12 50481 +1952 119 19.04 13.04 17.39 0 484.22 355.88 50661 +1952 120 20.95 14.95 19.3 0 538.81 350.85 50840 +1952 121 23.22 17.22 21.57 0 610.39 343.65 51016 +1952 122 24.52 18.52 22.87 0.41 654.91 254.66 51191 +1952 123 24.09 18.09 22.44 3.19 639.89 256.71 51365 +1952 124 24.33 18.33 22.68 0.35 648.23 256.73 51536 +1952 125 22.88 16.88 21.23 0.31 599.18 261.77 51706 +1952 126 23.54 17.54 21.89 0.15 621.1 260.54 51874 +1952 127 21.72 15.72 20.07 0 562.24 355.15 52039 +1952 128 19.13 13.13 17.48 0 486.69 364.84 52203 +1952 129 16.31 10.31 14.66 0.34 414.42 280.36 52365 +1952 130 19.75 13.75 18.1 0 503.94 364.46 52524 +1952 131 19.59 13.59 17.94 0 499.44 365.76 52681 +1952 132 19.36 13.36 17.71 0 493.03 367.3 52836 +1952 133 17.93 11.93 16.28 0 454.72 372.38 52989 +1952 134 17.31 11.31 15.66 0 438.92 374.87 53138 +1952 135 10.64 4.64 8.99 0 296.41 391.23 53286 +1952 136 11.72 5.72 10.07 0 316.34 389.75 53430 +1952 137 14.94 8.94 13.29 0.09 382.75 287.41 53572 +1952 138 12.92 6.92 11.27 0 339.83 388.54 53711 +1952 139 16.5 10.5 14.85 0 418.98 380.45 53848 +1952 140 16.65 10.65 15 0.28 422.61 285.39 53981 +1952 141 14.34 8.34 12.69 0 369.54 386.91 54111 +1952 142 13.68 7.68 12.03 0.32 355.47 291.73 54238 +1952 143 15.27 9.27 13.62 0.05 390.18 289.24 54362 +1952 144 13.19 7.19 11.54 1.27 345.32 293.34 54483 +1952 145 12.92 6.92 11.27 0.06 339.83 294.15 54600 +1952 146 11.38 5.38 9.73 0.07 309.95 296.88 54714 +1952 147 11.18 5.18 9.53 0.04 306.24 297.55 54824 +1952 148 13.38 7.38 11.73 0.15 349.23 294.32 54931 +1952 149 12.18 6.18 10.53 0.04 325.18 296.55 55034 +1952 150 14.48 8.48 12.83 0 372.59 390.49 55134 +1952 151 14.21 8.21 12.56 0 366.73 391.54 55229 +1952 152 21.9 15.9 20.25 0 567.85 368.3 55321 +1952 153 18.66 12.66 17.01 0.15 473.94 284.75 55409 +1952 154 19.34 13.34 17.69 0 492.47 377.81 55492 +1952 155 21.41 15.41 19.76 0 552.71 370.85 55572 +1952 156 21.63 15.63 19.98 0 559.46 370.36 55648 +1952 157 22.11 16.11 20.46 0.16 574.44 276.54 55719 +1952 158 23.81 17.81 22.16 0 630.27 362.1 55786 +1952 159 22.55 16.55 20.9 0 588.47 367.43 55849 +1952 160 24.26 18.26 22.61 0.04 645.79 270.45 55908 +1952 161 23.3 17.3 21.65 1.17 613.06 273.51 55962 +1952 162 23.11 17.11 21.46 0 606.75 365.51 56011 +1952 163 19.71 13.71 18.06 0 502.81 378.21 56056 +1952 164 19.08 13.08 17.43 0 485.32 380.31 56097 +1952 165 18.95 12.95 17.3 0 481.77 380.83 56133 +1952 166 22.92 16.92 21.27 0.13 600.49 275.02 56165 +1952 167 18.89 12.89 17.24 0 480.14 381.04 56192 +1952 168 19.89 13.89 18.24 1.25 507.9 283.39 56214 +1952 169 20.85 14.85 19.2 0 535.82 374.54 56231 +1952 170 20.31 14.31 18.66 0.45 519.96 282.32 56244 +1952 171 21.17 15.17 19.52 0.11 545.42 280.09 56252 +1952 172 20.11 14.11 18.46 0.31 514.19 282.87 56256 +1952 173 18.18 12.18 16.53 0.13 461.23 287.53 56255 +1952 174 18.45 12.45 16.8 0 468.34 382.46 56249 +1952 175 21.51 15.51 19.86 0 555.77 372.07 56238 +1952 176 21.13 15.13 19.48 0.36 544.21 280.06 56223 +1952 177 23.28 17.28 21.63 0 612.39 365.06 56203 +1952 178 21.42 15.42 19.77 0 553.01 372.29 56179 +1952 179 25.3 19.3 23.65 0.01 682.91 267.22 56150 +1952 180 24.83 18.83 23.18 1.05 665.92 268.71 56116 +1952 181 25.36 19.36 23.71 0.45 685.11 266.88 56078 +1952 182 25.79 19.79 24.14 0 701.02 353.71 56035 +1952 183 28.6 22.6 26.95 0 812.89 339.38 55987 +1952 184 26.43 20.43 24.78 0 725.28 350.36 55935 +1952 185 25.48 19.48 23.83 0.06 689.52 266.06 55879 +1952 186 28.52 22.52 26.87 0.28 809.5 254.52 55818 +1952 187 26.64 20.64 24.99 0.01 733.39 261.63 55753 +1952 188 24.59 18.59 22.94 0 657.38 358.05 55684 +1952 189 24.69 18.69 23.04 0.04 660.93 268.08 55611 +1952 190 27.99 21.99 26.34 0 787.4 341.24 55533 +1952 191 32.14 26.14 30.49 0 974.93 316.7 55451 +1952 192 30.61 24.61 28.96 0.29 901.84 244.5 55366 +1952 193 30.01 24.01 28.36 0 874.47 329.3 55276 +1952 194 30.28 24.28 28.63 0 886.7 327.53 55182 +1952 195 24.79 18.79 23.14 0 664.49 355.35 55085 +1952 196 24.24 18.24 22.59 0.17 645.09 268 54984 +1952 197 19.36 13.36 17.71 0.03 493.03 281.31 54879 +1952 198 23.7 17.7 22.05 0 626.52 358.74 54770 +1952 199 26.02 20.02 24.37 0 709.66 348.19 54658 +1952 200 22.19 16.19 20.54 1.22 576.97 272.98 54542 +1952 201 24.55 18.55 22.9 0.06 655.97 265.47 54423 +1952 202 22.01 16.01 20.36 0 571.29 363.63 54301 +1952 203 18.87 12.87 17.22 0 479.6 373.9 54176 +1952 204 19.34 13.34 17.69 0 492.47 371.89 54047 +1952 205 21.03 15.03 19.38 0 541.2 365.68 53915 +1952 206 17.02 11.02 15.37 0 431.69 377.76 53780 +1952 207 18.74 12.74 17.09 0 476.09 372.03 53643 +1952 208 19.64 13.64 17.99 0 500.84 368.52 53502 +1952 209 23.72 17.72 22.07 0.22 627.2 264.72 53359 +1952 210 26.57 20.57 24.92 0 730.68 339.78 53213 +1952 211 25.18 19.18 23.53 0.85 678.54 259.06 53064 +1952 212 23.53 17.53 21.88 0.35 620.77 263.7 52913 +1952 213 21.83 15.83 20.18 0.61 565.66 268.03 52760 +1952 214 22.58 16.58 20.93 0 589.44 353.84 52604 +1952 215 21.48 15.48 19.83 0.01 554.85 267.92 52445 +1952 216 24.38 18.38 22.73 0.06 649.98 258.75 52285 +1952 217 20.59 14.59 18.94 1.38 528.14 268.82 52122 +1952 218 21.24 15.24 19.59 0 547.53 355.38 51958 +1952 219 20.2 14.2 18.55 0 516.78 357.87 51791 +1952 220 21.69 15.69 20.04 0 561.31 351.82 51622 +1952 221 20.47 14.47 18.82 0 524.62 355.04 51451 +1952 222 24.45 18.45 22.8 0 652.44 339.16 51279 +1952 223 23.83 17.83 22.18 0 630.95 340.58 51105 +1952 224 27.86 21.86 26.21 0 782.06 321.55 50929 +1952 225 30.34 24.34 28.69 0.8 889.44 230.5 50751 +1952 226 30.12 24.12 28.47 0.38 879.43 230.66 50572 +1952 227 26.39 20.39 24.74 0.06 723.74 243.9 50392 +1952 228 27.8 21.8 26.15 0 779.6 317.39 50210 +1952 229 24.89 18.89 23.24 0 668.07 329.42 50026 +1952 230 26.61 20.61 24.96 0.28 732.23 240.52 49842 +1952 231 26.85 20.85 25.2 0.24 741.58 238.65 49656 +1952 232 22.73 16.73 21.08 0.02 594.29 250.45 49469 +1952 233 24.08 18.08 22.43 0 639.54 327.41 49280 +1952 234 25.13 19.13 23.48 0.03 676.72 241.34 49091 +1952 235 27.15 21.15 25.5 0 753.41 311.49 48900 +1952 236 25.04 19.04 23.39 0.07 673.47 239.54 48709 +1952 237 23.29 17.29 21.64 0 612.72 324.67 48516 +1952 238 26 20 24.35 0.02 708.9 234.14 48323 +1952 239 22.31 16.31 20.66 0 580.78 325.12 48128 +1952 240 23.26 17.26 21.61 0 611.72 319.99 47933 +1952 241 24.82 18.82 23.17 0.05 665.56 234.26 47737 +1952 242 26.05 20.05 24.4 0 710.79 305.62 47541 +1952 243 29.25 23.25 27.6 0.1 840.8 216.8 47343 +1952 244 18.29 12.29 16.64 0.84 464.12 246.6 47145 +1952 245 17.45 11.45 15.8 0.04 442.44 246.89 46947 +1952 246 16.03 10.03 14.38 0 407.77 330.73 46747 +1952 247 14.99 8.99 13.34 0 383.87 331.24 46547 +1952 248 19.19 13.19 17.54 0 488.33 318.72 46347 +1952 249 16.72 10.72 15.07 0.01 424.32 242.36 46146 +1952 250 17.86 11.86 16.21 0.21 452.91 238.74 45945 +1952 251 19.48 13.48 17.83 0.36 496.36 233.87 45743 +1952 252 21.87 15.87 20.22 0.17 566.91 226.85 45541 +1952 253 19.96 13.96 18.31 0.03 509.9 229.68 45339 +1952 254 18.69 12.69 17.04 0.08 474.75 230.74 45136 +1952 255 16.23 10.23 14.58 0.86 412.51 233.63 44933 +1952 256 17.8 11.8 16.15 0.09 451.37 229.1 44730 +1952 257 15.08 9.08 13.43 0.95 385.89 232.18 44527 +1952 258 13.35 7.35 11.7 0.38 348.61 233.01 44323 +1952 259 11.49 5.49 9.84 0.15 312.01 233.66 44119 +1952 260 11.54 5.54 9.89 0.01 312.94 231.76 43915 +1952 261 11.26 5.26 9.61 0 307.72 306.97 43711 +1952 262 13.19 7.19 11.54 0.07 345.32 225.89 43507 +1952 263 17.16 11.16 15.51 0.34 435.17 217.86 43303 +1952 264 13.13 7.13 11.48 0.22 344.1 222.14 43099 +1952 265 12.98 6.98 11.33 0 341.05 294.05 42894 +1952 266 15.04 9.04 13.39 0 384.99 287.64 42690 +1952 267 15.4 9.4 13.75 0 393.14 284.23 42486 +1952 268 16.58 10.58 14.93 0 420.91 279.2 42282 +1952 269 19.52 13.52 17.87 0.02 497.48 202.35 42078 +1952 270 21.65 15.65 20 0 560.08 261.49 41875 +1952 271 21.43 15.43 19.78 1.68 553.32 194.7 41671 +1952 272 18.83 12.83 17.18 0.54 478.52 197.79 41468 +1952 273 15.88 9.88 14.23 0.09 404.24 200.78 41265 +1952 274 8.17 2.17 6.52 0.73 254.81 208 41062 +1952 275 12.35 6.35 10.7 0 328.5 268.6 40860 +1952 276 13.36 7.36 11.71 0.2 348.81 198.17 40658 +1952 277 14.82 8.82 13.17 0.84 380.08 194.25 40456 +1952 278 20.65 14.65 19 0.06 529.9 182.65 40255 +1952 279 19.03 13.03 17.38 0.19 483.95 183.56 40054 +1952 280 18.63 12.63 16.98 0.08 473.14 182.31 39854 +1952 281 17 11 15.35 0 431.19 243.89 39654 +1952 282 18.2 12.2 16.55 0 461.75 238.72 39455 +1952 283 17.55 11.55 15.9 1.99 444.98 178 39256 +1952 284 13.99 7.99 12.34 0.57 362.02 180.67 39058 +1952 285 11.23 5.23 9.58 0 307.16 242.42 38861 +1952 286 9.59 3.59 7.94 0 278.06 241.77 38664 +1952 287 9.1 3.1 7.45 0 269.84 239.39 38468 +1952 288 3.68 -2.32 2.03 0 191.93 241.97 38273 +1952 289 10.03 4.03 8.38 1.07 285.63 174.59 38079 +1952 290 12.14 6.14 10.49 0.75 324.4 170.35 37885 +1952 291 13.41 7.41 11.76 0.07 349.85 166.95 37693 +1952 292 13.11 7.11 11.46 0.45 343.69 165.28 37501 +1952 293 12.39 6.39 10.74 0.88 329.28 164.01 37311 +1952 294 13.16 7.16 11.51 0.51 344.71 161.04 37121 +1952 295 16.34 10.34 14.69 0.24 415.13 155.19 36933 +1952 296 10.85 4.85 9.2 0.21 300.2 159.28 36745 +1952 297 9.72 3.72 8.07 0.08 280.28 158.23 36560 +1952 298 11.78 5.78 10.13 0.23 317.49 154.42 36375 +1952 299 11.53 5.53 9.88 0.2 312.76 152.57 36191 +1952 300 7.58 1.58 5.93 1.27 245.65 153.81 36009 +1952 301 9.85 3.85 8.2 0 282.51 200.21 35829 +1952 302 11.33 5.33 9.68 0.09 309.02 146.93 35650 +1952 303 13.23 7.23 11.58 0 346.14 190.96 35472 +1952 304 12.37 6.37 10.72 0 328.89 189.63 35296 +1952 305 6.81 0.81 5.16 0 234.13 192.74 35122 +1952 306 9.16 3.16 7.51 0 270.84 188.27 34950 +1952 307 8.27 2.27 6.62 0.72 256.39 139.96 34779 +1952 308 5.43 -0.57 3.78 0 214.63 186.43 34610 +1952 309 5.45 -0.55 3.8 0 214.9 184.07 34444 +1952 310 7.8 1.8 6.15 0 249.03 179.66 34279 +1952 311 1.9 -4.1 0.25 0.15 170.99 136.35 34116 +1952 312 1.83 -4.17 0.18 0.03 170.21 134.37 33956 +1952 313 1.67 -4.33 0.02 0.41 168.43 132.82 33797 +1952 314 5.1 -0.9 3.45 0 210.18 172.88 33641 +1952 315 7.16 1.16 5.51 0 239.31 168.75 33488 +1952 316 6.7 0.7 5.05 0 232.52 166.93 33337 +1952 317 6.45 0.45 4.8 0 228.9 164.92 33188 +1952 318 8.49 2.49 6.84 0 259.9 160.92 33042 +1952 319 10.64 4.64 8.99 0 296.41 157.26 32899 +1952 320 8.95 2.95 7.3 0 267.37 156.97 32758 +1952 321 13.54 7.54 11.89 0.02 352.55 112.7 32620 +1952 322 12.74 6.74 11.09 0.91 336.22 112.04 32486 +1952 323 12.07 6.07 10.42 0.13 323.05 111.39 32354 +1952 324 15.88 9.88 14.23 0.01 404.24 106.58 32225 +1952 325 13.43 7.43 11.78 0 350.26 143.38 32100 +1952 326 6.27 0.27 4.62 0 226.32 148.35 31977 +1952 327 2.95 -3.05 1.3 0 183.09 148.59 31858 +1952 328 1.59 -4.41 -0.06 0 167.55 147.33 31743 +1952 329 1.34 -4.66 -0.31 0 164.82 145.95 31631 +1952 330 1.53 -4.47 -0.12 0 166.89 144.39 31522 +1952 331 3.35 -2.65 1.7 0 187.89 142.09 31417 +1952 332 3.71 -2.29 2.06 0 192.3 140.24 31316 +1952 333 3.61 -2.39 1.96 0.15 191.06 104.4 31218 +1952 334 3.97 -2.03 2.32 0.44 195.54 103.42 31125 +1952 335 0.24 -5.76 -1.41 1.09 153.27 103.95 31035 +1952 336 -2.34 -8.34 -3.99 0 128.88 138.56 30949 +1952 337 -0.02 -6.02 -1.67 0 150.64 135.95 30867 +1952 338 5.46 -0.54 3.81 0.61 215.04 99.11 30790 +1952 339 -0.26 -6.26 -1.91 0.1 148.25 144.01 30716 +1952 340 -2.84 -8.84 -4.49 0.15 124.56 144.77 30647 +1952 341 -2.06 -8.06 -3.71 0 131.35 177.28 30582 +1952 342 0.71 -5.29 -0.94 0 158.12 175.38 30521 +1952 343 1.25 -4.75 -0.4 0 163.85 174.22 30465 +1952 344 6.07 0.07 4.42 0 223.49 126.62 30413 +1952 345 4.33 -1.67 2.68 0 200.11 127.23 30366 +1952 346 5.74 -0.26 4.09 0 218.88 125.85 30323 +1952 347 5.17 -0.83 3.52 0.14 211.12 94.2 30284 +1952 348 5.02 -0.98 3.37 1.22 209.11 94 30251 +1952 349 2.07 -3.93 0.42 0.63 172.9 94.89 30221 +1952 350 2.41 -3.59 0.76 0.39 176.78 94.51 30197 +1952 351 0.37 -5.63 -1.28 0.02 154.6 95.05 30177 +1952 352 -1.18 -7.18 -2.83 0.11 139.39 139.56 30162 +1952 353 1.27 -4.73 -0.38 0.05 164.07 138.59 30151 +1952 354 2.38 -3.62 0.73 0.12 176.43 94.22 30145 +1952 355 1.22 -4.78 -0.43 1.68 163.53 94.62 30144 +1952 356 0.43 -5.57 -1.22 0.27 155.21 94.9 30147 +1952 357 -1.2 -7.2 -2.85 0.02 139.21 139.28 30156 +1952 358 0.59 -5.41 -1.06 0 156.87 126.61 30169 +1952 359 3.09 -2.91 1.44 0 184.76 125.56 30186 +1952 360 2.17 -3.83 0.52 0 174.03 126.38 30208 +1952 361 4.53 -1.47 2.88 0 202.68 125.48 30235 +1952 362 5.39 -0.61 3.74 0 214.09 125.42 30267 +1952 363 10.72 4.72 9.07 0 297.85 122.2 30303 +1952 364 9.07 3.07 7.42 0 269.35 123.91 30343 +1952 365 7.49 1.49 5.84 0.01 244.28 94.21 30388 +1953 1 6.68 0.68 5.03 0 232.23 127.04 30438 +1953 2 1.18 -4.82 -0.47 0.4 163.1 98.11 30492 +1953 3 -1.98 -7.98 -3.63 0 132.07 133.07 30551 +1953 4 -0.94 -6.94 -2.59 0.57 141.66 145.1 30614 +1953 5 -0.83 -6.83 -2.48 0 142.71 179.01 30681 +1953 6 -2.3 -8.3 -3.95 0.04 129.23 146.58 30752 +1953 7 -0.8 -6.8 -2.45 0.01 143 146.67 30828 +1953 8 1.07 -4.93 -0.58 0 161.92 181.07 30907 +1953 9 -1.08 -7.08 -2.73 0 140.33 183.15 30991 +1953 10 1.23 -4.77 -0.42 0 163.64 183.16 31079 +1953 11 -2.24 -8.24 -3.89 0 129.76 185.51 31171 +1953 12 -2.64 -8.64 -4.29 1 126.27 153.94 31266 +1953 13 0.96 -5.04 -0.69 0 160.75 189.46 31366 +1953 14 2.56 -3.44 0.91 0.19 178.51 153.78 31469 +1953 15 6.45 0.45 4.8 0.01 228.9 152.09 31575 +1953 16 1.4 -4.6 -0.25 0 165.48 191.69 31686 +1953 17 0.13 -5.87 -1.52 0 152.15 193.82 31800 +1953 18 -2.42 -8.42 -4.07 0 128.18 196.67 31917 +1953 19 -5.35 -11.35 -7 0 104.73 199.5 32038 +1953 20 -4.12 -10.12 -5.77 0 114.08 200.53 32161 +1953 21 0.81 -5.19 -0.84 0.01 159.17 161.11 32289 +1953 22 0.89 -5.11 -0.76 0 160.01 201.63 32419 +1953 23 2.08 -3.92 0.43 0 173.01 202.34 32552 +1953 24 5.42 -0.58 3.77 0.02 214.49 161.68 32688 +1953 25 9.47 3.47 7.82 0.61 276.03 159.3 32827 +1953 26 6.15 0.15 4.5 0.02 224.62 121.82 32969 +1953 27 7.5 1.5 5.85 0 244.43 163.38 33114 +1953 28 5.23 -0.77 3.58 0 211.92 167.31 33261 +1953 29 9.15 3.15 7.5 0 270.67 166.48 33411 +1953 30 9.69 3.69 8.04 0 279.77 168.17 33564 +1953 31 8.88 2.88 7.23 0.04 266.22 128.46 33718 +1953 32 8.19 2.19 6.54 0 255.13 173.98 33875 +1953 33 6.78 0.78 5.13 0.02 233.69 133.35 34035 +1953 34 4.54 -1.46 2.89 0 202.81 181.72 34196 +1953 35 4.28 -1.72 2.63 0 199.47 184.06 34360 +1953 36 3.52 -2.48 1.87 0 189.96 187.11 34526 +1953 37 4.18 -1.82 2.53 0 198.19 189.07 34694 +1953 38 2.73 -3.27 1.08 0 180.49 192.82 34863 +1953 39 3.57 -2.43 1.92 0 190.57 194.86 35035 +1953 40 2.79 -3.21 1.14 0.2 181.2 148.52 35208 +1953 41 -1.18 -7.18 -2.83 0 139.39 203.05 35383 +1953 42 2.23 -3.77 0.58 0.24 174.72 152.71 35560 +1953 43 -3.34 -9.34 -4.99 0.51 120.37 195.39 35738 +1953 44 -0.82 -6.82 -2.47 0.45 142.8 197.41 35918 +1953 45 -0.53 -6.53 -2.18 0.04 145.6 199.19 36099 +1953 46 -0.12 -6.12 -1.77 0 149.64 254.79 36282 +1953 47 0.87 -5.13 -0.78 0 159.8 256.75 36466 +1953 48 1.6 -4.4 -0.05 0 167.66 258.73 36652 +1953 49 6.36 0.36 4.71 0 227.61 256.83 36838 +1953 50 8.66 2.66 7.01 0.02 262.64 201.11 37026 +1953 51 9.37 3.37 7.72 0 274.35 221.84 37215 +1953 52 10.12 4.12 8.47 0 287.2 223.74 37405 +1953 53 3.14 -2.86 1.49 0 185.35 233.55 37596 +1953 54 6.62 0.62 4.97 0.05 231.36 174.93 37788 +1953 55 6.88 0.88 5.23 0 235.16 235.97 37981 +1953 56 6.17 0.17 4.52 0 224.9 239.36 38175 +1953 57 6.24 0.24 4.59 0 225.9 242.18 38370 +1953 58 5.07 -0.93 3.42 0 209.78 246.23 38565 +1953 59 6.23 0.23 4.58 0 225.75 247.82 38761 +1953 60 14 8 12.35 0 362.24 240.53 38958 +1953 61 17.78 11.78 16.13 0 450.85 236.35 39156 +1953 62 12.8 6.8 11.15 0 337.42 248.03 39355 +1953 63 16.38 10.38 14.73 0 416.09 244.7 39553 +1953 64 11.45 5.45 9.8 0 311.26 255.86 39753 +1953 65 10.25 4.25 8.6 0 289.48 260.4 39953 +1953 66 11.92 5.92 10.27 0 320.16 260.69 40154 +1953 67 12.39 6.39 10.74 0 329.28 262.81 40355 +1953 68 11.09 5.09 9.44 0 304.58 267.61 40556 +1953 69 13.24 7.24 11.59 0.49 346.35 200.1 40758 +1953 70 10.59 4.59 8.94 0.01 295.51 205.31 40960 +1953 71 6.67 0.67 5.02 0.03 232.08 211.27 41163 +1953 72 7.66 1.66 6.01 0 246.88 283.35 41366 +1953 73 7.39 1.39 5.74 0 242.76 286.35 41569 +1953 74 6.45 0.45 4.8 0 228.9 290.22 41772 +1953 75 7.18 1.18 5.53 0 239.61 292.09 41976 +1953 76 5.31 -0.69 3.66 0 213 296.89 42179 +1953 77 7.1 1.1 5.45 0 238.41 297.44 42383 +1953 78 5.06 -0.94 3.41 0 209.65 302.47 42587 +1953 79 5.7 -0.3 4.05 0 218.33 304.52 42791 +1953 80 4.94 -1.06 3.29 0 208.05 307.92 42996 +1953 81 3.83 -2.17 2.18 0 193.79 311.7 43200 +1953 82 2.22 -3.78 0.57 0 174.6 315.95 43404 +1953 83 8.24 2.24 6.59 0 255.92 311.67 43608 +1953 84 10.96 4.96 9.31 0 302.2 310.13 43812 +1953 85 9.55 3.55 7.9 0 277.38 314.82 44016 +1953 86 7.55 1.55 5.9 0.01 245.19 240.05 44220 +1953 87 6.09 0.09 4.44 0 223.77 324.48 44424 +1953 88 5.12 -0.88 3.47 0 210.45 328.01 44627 +1953 89 -0.61 -6.61 -2.26 0 144.83 335.86 44831 +1953 90 0.95 -5.05 -0.7 0.01 160.64 252.73 45034 +1953 91 9.38 3.38 7.73 0.11 274.51 246.96 45237 +1953 92 13.99 7.99 12.34 0 362.02 323.29 45439 +1953 93 18.22 12.22 16.57 0 462.28 315.57 45642 +1953 94 19.23 13.23 17.58 0 489.43 314.88 45843 +1953 95 18.63 12.63 16.98 0 473.14 318.6 46045 +1953 96 19.69 13.69 18.04 0 502.24 317.63 46246 +1953 97 17.99 11.99 16.34 0 456.27 324.34 46446 +1953 98 12.84 6.84 11.19 0 338.22 338.09 46647 +1953 99 12.2 6.2 10.55 0 325.57 341.33 46846 +1953 100 14 8 12.35 0.35 362.24 254.73 47045 +1953 101 16.82 10.82 15.17 0 426.76 334.99 47243 +1953 102 13.88 7.88 12.23 0 359.69 343.69 47441 +1953 103 15.36 9.36 13.71 0 392.23 342.2 47638 +1953 104 13.14 7.14 11.49 0.04 344.3 261.66 47834 +1953 105 13.97 7.97 12.32 0.2 361.6 261.68 48030 +1953 106 10.04 4.04 8.39 0 285.8 358.15 48225 +1953 107 10.27 4.27 8.62 0 289.83 359.44 48419 +1953 108 9.84 3.84 8.19 0 282.34 361.94 48612 +1953 109 11.06 5.06 9.41 0 304.03 361.4 48804 +1953 110 12.08 6.08 10.43 0 323.24 360.88 48995 +1953 111 14.09 8.09 12.44 0 364.16 358.21 49185 +1953 112 16.41 10.41 14.76 0 416.81 354.16 49374 +1953 113 13.54 7.54 11.89 0 352.55 362.27 49561 +1953 114 15.36 9.36 13.71 0 392.23 359.57 49748 +1953 115 11.43 5.43 9.78 0.09 310.88 277.14 49933 +1953 116 18.14 12.14 16.49 0.34 460.18 266.12 50117 +1953 117 14.4 8.4 12.75 1.55 370.85 274.33 50300 +1953 118 14.02 8.02 12.37 0 362.66 367.96 50481 +1953 119 14.27 8.27 12.62 0.23 368.03 276.44 50661 +1953 120 9.08 3.08 7.43 0 269.51 380.04 50840 +1953 121 13.01 7.01 11.36 0.14 341.66 280.27 51016 +1953 122 10.53 4.53 8.88 0.11 294.44 284.89 51191 +1953 123 14.56 8.56 12.91 1.5 374.34 279.32 51365 +1953 124 14.59 8.59 12.94 0.85 375 280.08 51536 +1953 125 15.62 9.62 13.97 0.72 398.2 278.92 51706 +1953 126 15.15 9.15 13.5 0.5 387.46 280.54 51874 +1953 127 17.3 11.3 15.65 0.44 438.67 276.96 52039 +1953 128 19.59 13.59 17.94 1.03 499.44 272.53 52203 +1953 129 16.85 10.85 15.2 0.36 427.5 279.27 52365 +1953 130 13.91 7.91 12.26 0 360.32 380.56 52524 +1953 131 14.54 8.54 12.89 0.32 373.9 284.91 52681 +1953 132 14 8 12.35 0.22 362.24 286.49 52836 +1953 133 15.99 9.99 14.34 0 406.83 377.77 52989 +1953 134 14.42 8.42 12.77 0.17 371.28 286.82 53138 +1953 135 16.48 10.48 14.83 0 418.5 377.87 53286 +1953 136 20.98 14.98 19.33 0 539.7 364.56 53430 +1953 137 24.04 18.04 22.39 0 638.16 353.49 53572 +1953 138 17.17 11.17 15.52 0 435.41 377.9 53711 +1953 139 17.3 11.3 15.65 0 438.67 378.22 53848 +1953 140 15.12 9.12 13.47 0 386.79 384.55 53981 +1953 141 18.89 12.89 17.24 0 480.14 374.37 54111 +1953 142 16.48 10.48 14.83 0 418.5 381.93 54238 +1953 143 16.3 10.3 14.65 0 414.18 382.95 54362 +1953 144 19.86 13.86 18.21 0.68 507.05 279.54 54483 +1953 145 21.99 15.99 20.34 0.88 570.66 274.24 54600 +1953 146 19.69 13.69 18.04 0.23 502.24 280.59 54714 +1953 147 19.58 13.58 17.93 0 499.16 374.95 54824 +1953 148 18.85 12.85 17.2 0 479.06 377.68 54931 +1953 149 18.9 12.9 17.25 0 480.41 377.83 55034 +1953 150 17.11 11.11 15.46 0 433.92 383.54 55134 +1953 151 17.45 11.45 15.8 0 442.44 382.96 55229 +1953 152 19.9 13.9 18.25 0.59 508.19 281.55 55321 +1953 153 18.46 12.46 16.81 0 468.61 380.28 55409 +1953 154 18.18 12.18 16.53 1.1 461.23 286.09 55492 +1953 155 16.77 10.77 15.12 0 425.54 385.77 55572 +1953 156 17.82 11.82 16.17 0 451.88 383.06 55648 +1953 157 22.28 16.28 20.63 0 579.83 368.07 55719 +1953 158 25.54 19.54 23.89 0.04 691.73 265.88 55786 +1953 159 23.7 17.7 22.05 0.63 626.52 272.1 55849 +1953 160 22.8 16.8 21.15 2.38 596.57 274.97 55908 +1953 161 20.5 14.5 18.85 0.67 525.5 281.43 55962 +1953 162 22.23 16.23 20.58 0.23 578.24 276.73 56011 +1953 163 25.44 19.44 23.79 0 688.04 355.69 56056 +1953 164 22.41 16.41 20.76 0.13 583.98 276.4 56097 +1953 165 22.72 16.72 21.07 0.15 593.97 275.56 56133 +1953 166 19.46 13.46 17.81 0.08 495.8 284.44 56165 +1953 167 20.34 14.34 18.69 0.67 520.83 282.18 56192 +1953 168 16.97 10.97 15.32 0.1 430.45 290.17 56214 +1953 169 18.61 12.61 16.96 0.38 472.61 286.51 56231 +1953 170 16.84 10.84 15.19 0.25 427.25 290.46 56244 +1953 171 20.48 14.48 18.83 0 524.91 375.9 56252 +1953 172 21.43 15.43 19.78 0.01 553.32 279.37 56256 +1953 173 15.74 9.74 14.09 0.17 400.98 292.74 56255 +1953 174 21.49 15.49 19.84 0.06 555.15 279.13 56249 +1953 175 20.22 14.22 18.57 1 517.36 282.49 56238 +1953 176 21.96 15.96 20.31 0.74 569.72 277.76 56223 +1953 177 23.4 17.4 21.75 0.96 616.4 273.43 56203 +1953 178 25.66 19.66 24.01 0.77 696.18 266.05 56179 +1953 179 24.14 18.14 22.49 2.98 641.62 271.05 56150 +1953 180 24.82 18.82 23.17 0.21 665.56 268.75 56116 +1953 181 22.06 16.06 20.41 0 572.86 369.61 56078 +1953 182 20.42 14.42 18.77 0.13 523.16 281.56 56035 +1953 183 23.62 17.62 21.97 0 623.81 363.09 55987 +1953 184 26.16 20.16 24.51 0.01 714.96 263.74 55935 +1953 185 24.6 18.6 22.95 0.63 657.73 269.02 55879 +1953 186 20.46 14.46 18.81 0.17 524.33 280.95 55818 +1953 187 26.46 20.46 24.81 1.62 726.43 262.29 55753 +1953 188 28.23 22.23 26.58 0.45 797.35 255.37 55684 +1953 189 29.49 23.49 27.84 0.51 851.31 250.05 55611 +1953 190 27.13 21.13 25.48 0.5 752.62 259.23 55533 +1953 191 29.05 23.05 27.4 0.13 832.13 251.46 55451 +1953 192 21.46 15.46 19.81 0 554.23 369.48 55366 +1953 193 22.74 16.74 21.09 0.99 594.62 273.27 55276 +1953 194 21.86 15.86 20.21 0.49 566.6 275.63 55182 +1953 195 25.29 19.29 23.64 0.59 682.55 264.84 55085 +1953 196 24.08 18.08 22.43 0 639.54 358.01 54984 +1953 197 16.27 10.27 14.62 0.39 413.46 288.18 54879 +1953 198 12.99 6.99 11.34 0 341.25 391.86 54770 +1953 199 15.7 9.7 14.05 0 400.05 384.95 54658 +1953 200 16.66 10.66 15.01 0 422.85 381.96 54542 +1953 201 21.2 15.2 19.55 0 546.32 367.16 54423 +1953 202 22.77 16.77 21.12 0 595.59 360.73 54301 +1953 203 20.28 14.28 18.63 0 519.09 369.3 54176 +1953 204 22.55 16.55 20.9 0 588.47 360.58 54047 +1953 205 27.6 21.6 25.95 0 771.46 337.69 53915 +1953 206 28.45 22.45 26.8 0 806.56 332.76 53780 +1953 207 25.37 19.37 23.72 0 685.47 347.16 53643 +1953 208 25.09 19.09 23.44 0.23 675.27 260.83 53502 +1953 209 25.35 19.35 23.7 0.59 684.74 259.5 53359 +1953 210 21.87 15.87 20.22 0 566.91 359.53 53213 +1953 211 22.95 16.95 21.3 0.01 601.48 266 53064 +1953 212 24.81 18.81 23.16 0.22 665.2 259.69 52913 +1953 213 22.88 16.88 21.23 0 599.18 353.42 52760 +1953 214 19.69 13.69 18.04 0.56 502.24 272.99 52604 +1953 215 23.73 17.73 22.08 0.17 627.54 261.5 52445 +1953 216 23.94 17.94 22.29 1.49 634.72 260.11 52285 +1953 217 21.66 15.66 20.01 0.62 560.39 266.02 52122 +1953 218 20.47 14.47 18.82 0.31 524.62 268.51 51958 +1953 219 21.58 15.58 19.93 0.4 557.92 264.85 51791 +1953 220 21.08 15.08 19.43 0 542.7 353.96 51622 +1953 221 22.39 16.39 20.74 0.01 583.34 261.21 51451 +1953 222 24.29 18.29 22.64 0 646.84 339.82 51279 +1953 223 22.79 16.79 21.14 0.97 596.25 258.47 51105 +1953 224 21.5 15.5 19.85 0.66 555.46 261.22 50929 +1953 225 18.87 12.87 17.22 1.51 479.6 266.79 50751 +1953 226 19.61 13.61 17.96 0 500 352.29 50572 +1953 227 20.24 14.24 18.59 0 517.94 349 50392 +1953 228 27.65 21.65 26 0 773.49 318.13 50210 +1953 229 23.46 17.46 21.81 0.18 618.41 251.38 50026 +1953 230 22.33 16.33 20.68 0 581.42 338.15 49842 +1953 231 19.45 13.45 17.8 0.06 495.53 259.73 49656 +1953 232 19.86 13.86 18.21 0 507.05 343.68 49469 +1953 233 18.38 12.38 16.73 0.11 466.49 260.02 49280 +1953 234 19.11 13.11 17.46 0 486.14 343.13 49091 +1953 235 16.07 10.07 14.42 0 408.71 349.91 48900 +1953 236 15.13 9.13 13.48 0.62 387.01 263.04 48709 +1953 237 16.62 10.62 14.97 0.52 421.88 259.05 48516 +1953 238 16.8 10.8 15.15 0 426.27 343.25 48323 +1953 239 20.13 14.13 18.48 0.03 514.76 249.23 48128 +1953 240 23.82 17.82 22.17 0.12 630.61 238.42 47933 +1953 241 23.96 17.96 22.31 0 635.41 315.71 47737 +1953 242 25.53 19.53 23.88 0 691.36 307.81 47541 +1953 243 21.68 15.68 20.03 0.02 561.01 240.26 47343 +1953 244 19.36 13.36 17.71 0 493.03 325.78 47145 +1953 245 18.65 12.65 17 0 473.68 325.96 46947 +1953 246 22.36 16.36 20.71 0.01 582.38 234.43 46747 +1953 247 22.56 16.56 20.91 0.63 588.79 232.56 46547 +1953 248 21.14 15.14 19.49 0.31 544.51 234.66 46347 +1953 249 22.03 16.03 20.38 0 571.92 307.99 46146 +1953 250 24.85 18.85 23.2 0 666.63 296.05 45945 +1953 251 23.46 17.46 21.81 0.08 618.41 224.38 45743 +1953 252 21.95 15.95 20.3 0 569.41 302.21 45541 +1953 253 22.59 16.59 20.94 0.3 589.76 223.54 45339 +1953 254 22.45 16.45 20.8 0 585.26 296.47 45136 +1953 255 22.61 16.61 20.96 0 590.41 293.76 44933 +1953 256 19.27 13.27 17.62 0.05 490.54 226.21 44730 +1953 257 20.62 14.62 18.97 1.48 529.02 221.76 44527 +1953 258 14.46 8.46 12.81 3.06 372.15 231.37 44323 +1953 259 18.38 12.38 16.73 0.28 466.49 222.83 44119 +1953 260 18.87 12.87 17.22 0.3 479.6 220.12 43915 +1953 261 17.72 11.72 16.07 0.13 449.31 220.47 43711 +1953 262 17.4 11.4 15.75 0.28 441.18 219.28 43507 +1953 263 18.25 12.25 16.6 0 463.06 287.88 43303 +1953 264 18.61 12.61 16.96 0.06 472.61 213.33 43099 +1953 265 21.44 15.44 19.79 0 553.62 274.47 42894 +1953 266 23.25 17.25 21.6 0 611.39 266.55 42690 +1953 267 16.57 10.57 14.92 0 420.67 281.77 42486 +1953 268 13.07 7.07 11.42 0 342.87 286.07 42282 +1953 269 13.05 7.05 11.4 0 342.47 283.56 42078 +1953 270 14.71 8.71 13.06 0 377.64 277.87 41875 +1953 271 17.34 11.34 15.69 0.42 439.67 202.38 41671 +1953 272 17.66 11.66 16.01 1.67 447.78 199.82 41468 +1953 273 14.6 8.6 12.95 0.09 375.22 202.64 41265 +1953 274 8.99 2.99 7.34 0 268.03 276.29 41062 +1953 275 11.31 5.31 9.66 0 308.64 270.21 40860 +1953 276 9.92 3.92 8.27 0 283.72 269.46 40658 +1953 277 11.6 5.6 9.95 0 314.07 264.35 40456 +1953 278 10.74 4.74 9.09 0 298.21 262.71 40255 +1953 279 16.3 10.3 14.65 0 414.18 250.56 40054 +1953 280 14.12 8.12 12.47 0.28 364.8 188.95 39854 +1953 281 16.37 10.37 14.72 0.07 415.85 183.85 39654 +1953 282 17.14 11.14 15.49 0.12 434.67 180.69 39455 +1953 283 18.27 12.27 16.62 0 463.59 235.83 39256 +1953 284 17.57 11.57 15.92 0.07 445.49 175.75 39058 +1953 285 12.57 6.57 10.92 0 332.83 240.49 38861 +1953 286 14.21 8.21 12.56 0.36 366.73 176.38 38664 +1953 287 14.88 8.88 13.23 0.24 381.41 173.36 38468 +1953 288 15.29 9.29 13.64 0.3 390.64 170.77 38273 +1953 289 11.66 5.66 10.01 0.8 315.21 172.99 38079 +1953 290 15.53 9.53 13.88 1.9 396.12 166.41 37885 +1953 291 15.4 9.4 13.75 0.27 393.14 164.58 37693 +1953 292 14.94 8.94 13.29 0.22 382.75 163.17 37501 +1953 293 12.64 6.64 10.99 0 334.22 218.33 37311 +1953 294 11.34 5.34 9.69 0 309.2 217.19 37121 +1953 295 15.13 9.13 13.48 0 387.01 208.93 36933 +1953 296 17.07 11.07 15.42 0 432.93 203.14 36745 +1953 297 17.96 11.96 16.31 0 455.5 198.88 36560 +1953 298 19.9 13.9 18.25 0 508.19 192.6 36375 +1953 299 20.68 14.68 19.03 0 530.79 188.32 36191 +1953 300 14.86 8.86 13.21 0 380.96 196.24 36009 +1953 301 22.04 16.04 20.39 0 572.24 180.48 35829 +1953 302 14.04 8.04 12.39 0.01 363.09 144.29 35650 +1953 303 11.61 5.61 9.96 0 314.26 193.01 35472 +1953 304 9.25 3.25 7.6 0 272.34 193.18 35296 +1953 305 0.64 -5.36 -1.01 0 157.39 197.18 35122 +1953 306 -1.38 -7.38 -3.03 0 137.53 195.95 34950 +1953 307 2.96 -3.04 1.31 0 183.21 190.85 34779 +1953 308 4.05 -1.95 2.4 0 196.55 187.46 34610 +1953 309 3.16 -2.84 1.51 0 185.59 185.71 34444 +1953 310 5.81 -0.19 4.16 0 219.85 181.32 34279 +1953 311 5.82 -0.18 4.17 0 219.99 179.12 34116 +1953 312 4.73 -1.27 3.08 0 205.29 177.26 33956 +1953 313 8.95 2.95 7.3 0 267.37 171.67 33797 +1953 314 5.9 -0.1 4.25 0 221.11 172.29 33641 +1953 315 6.88 0.88 5.23 0 235.16 168.98 33488 +1953 316 5.99 -0.01 4.34 0 222.37 167.47 33337 +1953 317 4.55 -1.45 2.9 0 202.94 166.29 33188 +1953 318 4.91 -1.09 3.26 0.04 207.65 122.77 33042 +1953 319 4.88 -1.12 3.23 0 207.26 162 32899 +1953 320 5.09 -0.91 3.44 0 210.05 159.98 32758 +1953 321 9.69 3.69 8.04 0 279.77 154.22 32620 +1953 322 6.9 0.9 5.25 0 235.45 154.73 32486 +1953 323 9.44 3.44 7.79 0 275.52 151.04 32354 +1953 324 9.81 3.81 8.16 0.03 281.82 111.51 32225 +1953 325 5.66 -0.34 4.01 0 217.78 150.23 32100 +1953 326 8.02 2.02 6.37 0 252.46 147.04 31977 +1953 327 6.59 0.59 4.94 0 230.92 146.27 31858 +1953 328 8.19 2.19 6.54 0 255.13 143.11 31743 +1953 329 8.34 2.34 6.69 0 257.5 141.51 31631 +1953 330 8.86 2.86 7.21 0 265.89 139.66 31522 +1953 331 11.54 5.54 9.89 0 312.94 136.02 31417 +1953 332 6.27 0.27 4.62 0 226.32 138.64 31316 +1953 333 6.05 0.05 4.4 0 223.21 137.7 31218 +1953 334 6.31 0.31 4.66 0.5 226.89 102.32 31125 +1953 335 4.06 -1.94 2.41 0.07 196.67 102.49 31035 +1953 336 0.31 -5.69 -1.34 0 153.98 137.48 30949 +1953 337 1.7 -4.3 0.05 0 168.77 135.16 30867 +1953 338 3.11 -2.89 1.46 0 184.99 133.49 30790 +1953 339 2.79 -3.21 1.14 0 181.2 132.87 30716 +1953 340 1.8 -4.2 0.15 0 169.87 132.63 30647 +1953 341 0.11 -5.89 -1.54 0 151.95 132.47 30582 +1953 342 -1.18 -7.18 -2.83 0.03 139.39 142.51 30521 +1953 343 -0.17 -6.17 -1.82 0 149.15 174.41 30465 +1953 344 -1.31 -7.31 -2.96 0 138.18 173.8 30413 +1953 345 -1.98 -7.98 -3.63 0 132.07 173.68 30366 +1953 346 -5.78 -11.78 -7.43 0 101.63 174.41 30323 +1953 347 1 -5 -0.65 0 161.18 127.75 30284 +1953 348 4.62 -1.38 2.97 0 203.85 125.57 30251 +1953 349 8.36 2.36 6.71 0 257.82 122.8 30221 +1953 350 9.29 3.29 7.64 0 273.01 121.78 30197 +1953 351 5.33 -0.67 3.68 0 213.27 124.23 30177 +1953 352 3.28 -2.72 1.63 0.12 187.04 93.95 30162 +1953 353 3.31 -2.69 1.66 0 187.4 125.19 30151 +1953 354 0.08 -5.92 -1.57 0 151.65 126.66 30145 +1953 355 6.14 0.14 4.49 0 224.48 123.54 30144 +1953 356 10.35 4.35 8.7 0 291.24 120.57 30147 +1953 357 7.69 1.69 6.04 0 247.34 122.61 30156 +1953 358 5.08 -0.92 3.43 0 209.91 124.35 30169 +1953 359 5.54 -0.46 3.89 0 216.13 124.2 30186 +1953 360 5.61 -0.39 3.96 0 217.09 124.52 30208 +1953 361 5.37 -0.63 3.72 0 213.82 125 30235 +1953 362 4.27 -1.73 2.62 0 199.34 126.06 30267 +1953 363 2.93 -3.07 1.28 0 182.85 127.36 30303 +1953 364 2.26 -3.74 0.61 0 175.06 128.1 30343 +1953 365 0.16 -5.84 -1.49 0 152.46 129.63 30388 +1954 1 -2.55 -8.55 -4.2 0.12 127.05 142.43 30438 +1954 2 -3.84 -9.84 -5.49 0.27 116.3 144.09 30492 +1954 3 -5.92 -11.92 -7.57 0.53 100.63 146.86 30551 +1954 4 -6.55 -12.55 -8.2 0.15 96.27 148.06 30614 +1954 5 -2.95 -8.95 -4.6 0 123.63 181.38 30681 +1954 6 -5.19 -11.19 -6.84 0 105.91 182.9 30752 +1954 7 1.26 -4.74 -0.39 0 163.96 180.97 30828 +1954 8 -2.6 -8.6 -4.25 0.01 126.62 149.47 30907 +1954 9 -4.58 -10.58 -6.23 0 110.5 185.82 30991 +1954 10 -5.63 -11.63 -7.28 0 102.7 187.33 31079 +1954 11 -4.42 -10.42 -6.07 0 111.74 187.83 31171 +1954 12 -3.13 -9.13 -4.78 0.05 122.12 152.71 31266 +1954 13 -4.13 -10.13 -5.78 0.09 114 154.33 31366 +1954 14 -5.58 -11.58 -7.23 0.1 103.06 155.96 31469 +1954 15 0.66 -5.34 -0.99 0 157.6 191.5 31575 +1954 16 -1.29 -7.29 -2.94 0.17 138.37 157 31686 +1954 17 -1.36 -7.36 -3.01 2.16 137.72 164.66 31800 +1954 18 -4.18 -10.18 -5.83 0.45 113.61 168.07 31917 +1954 19 -6.42 -12.42 -8.07 0 97.15 208.76 32038 +1954 20 -6.92 -12.92 -8.57 0 93.78 210.33 32161 +1954 21 -6.62 -12.62 -8.27 0 95.79 212.07 32289 +1954 22 -2.12 -8.12 -3.77 0 130.82 212.05 32419 +1954 23 -0.53 -6.53 -2.18 0 145.6 212.92 32552 +1954 24 3.7 -2.3 2.05 0 192.17 212.03 32688 +1954 25 6.03 0.03 4.38 0.06 222.93 171.23 32827 +1954 26 7.47 1.47 5.82 0 243.98 211.04 32969 +1954 27 2.24 -3.76 0.59 0 174.83 216.18 33114 +1954 28 1.95 -4.05 0.3 0 171.55 218.12 33261 +1954 29 0 -6 -1.65 0 150.84 221.35 33411 +1954 30 -0.63 -6.63 -2.28 0 144.63 223.71 33564 +1954 31 -1.88 -7.88 -3.53 0 132.96 226.48 33718 +1954 32 0.38 -5.62 -1.27 0.74 154.7 182.37 33875 +1954 33 -1.59 -7.59 -3.24 0 135.6 230.66 34035 +1954 34 0.36 -5.64 -1.29 0 154.5 231.63 34196 +1954 35 -3.35 -9.35 -5 0.03 120.29 188.38 34360 +1954 36 -2.07 -8.07 -3.72 0 131.26 237.21 34526 +1954 37 -0.55 -6.55 -2.2 0 145.41 238.69 34694 +1954 38 1.82 -4.18 0.17 0 170.1 239.65 34863 +1954 39 0.96 -5.04 -0.69 0.07 160.75 193.33 35035 +1954 40 1.67 -4.33 0.02 0 168.43 244.25 35208 +1954 41 2 -4 0.35 0 172.11 246.22 35383 +1954 42 0.16 -5.84 -1.49 0 152.46 249.69 35560 +1954 43 -3.14 -9.14 -4.79 0 122.03 253.93 35738 +1954 44 -9.75 -15.75 -11.4 0 76.52 258.8 35918 +1954 45 -6.77 -12.77 -8.42 0 94.78 260.28 36099 +1954 46 -8.6 -14.6 -10.25 0.31 83.17 209.38 36282 +1954 47 -6.46 -12.46 -8.11 0 96.88 266.17 36466 +1954 48 -5.47 -11.47 -7.12 0 103.86 268.42 36652 +1954 49 -9.36 -15.36 -11.01 0 78.72 272.45 36838 +1954 50 -11.08 -17.08 -12.73 0.01 69.42 217.59 37026 +1954 51 -10.14 -16.14 -11.79 0 74.38 278.05 37215 +1954 52 -6.52 -12.52 -8.17 0 96.47 279.47 37405 +1954 53 -5.38 -11.38 -7.03 0 104.52 281.8 37596 +1954 54 -1.19 -7.19 -2.84 0 139.3 282.26 37788 +1954 55 1.62 -4.38 -0.03 0 167.88 283.07 37981 +1954 56 2.34 -3.66 0.69 0 175.97 284.79 38175 +1954 57 5.19 -0.81 3.54 0 211.39 284.53 38370 +1954 58 3.89 -2.11 2.24 0 194.54 288.02 38565 +1954 59 5 -1 3.35 0 208.85 289.02 38761 +1954 60 15.04 9.04 13.39 0.13 384.99 217.33 38958 +1954 61 11.4 5.4 9.75 0.58 310.32 222.41 39156 +1954 62 10.36 4.36 8.71 0.9 291.42 224.3 39355 +1954 63 7.76 1.76 6.11 0.54 248.42 227.99 39553 +1954 64 9.55 3.55 7.9 0.01 277.38 227.38 39753 +1954 65 8.68 2.68 7.03 0.12 262.96 196.83 39953 +1954 66 5.75 -0.25 4.1 0.88 219.02 201.37 40154 +1954 67 7.7 1.7 6.05 0 247.49 269.24 40355 +1954 68 7.14 1.14 5.49 0.43 239.01 204.57 40556 +1954 69 6.56 0.56 4.91 0 230.49 276.05 40758 +1954 70 5.65 -0.35 4 0 217.64 279.89 40960 +1954 71 1.65 -4.35 0 0.03 168.21 214.94 41163 +1954 72 4.85 -1.15 3.2 0 206.86 286.5 41366 +1954 73 3.39 -2.61 1.74 0 188.37 290.63 41569 +1954 74 7.76 1.76 6.11 0 248.42 288.65 41772 +1954 75 8.83 2.83 7.18 0 265.4 289.98 41976 +1954 76 8.55 2.55 6.9 0 260.86 292.99 42179 +1954 77 14.37 8.37 12.72 0 370.19 286.19 42383 +1954 78 17.31 11.31 15.66 0 438.92 282.6 42587 +1954 79 15.92 9.92 14.27 0 405.18 288.3 42791 +1954 80 12.03 6.03 10.38 0 322.28 298.19 42996 +1954 81 13.18 7.18 11.53 0 345.12 298.71 43200 +1954 82 10.57 4.57 8.92 0.08 295.15 229.32 43404 +1954 83 11.27 5.27 9.62 0 307.9 307.11 43608 +1954 84 10.88 4.88 9.23 0 300.74 310.26 43812 +1954 85 9.63 3.63 7.98 0 278.74 314.7 44016 +1954 86 9.51 3.51 7.86 0.01 276.71 237.97 44220 +1954 87 8.98 2.98 7.33 0 267.86 320.61 44424 +1954 88 3.94 -2.06 2.29 0 195.16 329.32 44627 +1954 89 5.01 -0.99 3.36 0.24 208.98 247.84 44831 +1954 90 0.13 -5.87 -1.52 0.35 152.15 253.26 45034 +1954 91 2.58 -3.42 0.93 0 178.74 337.76 45237 +1954 92 3.36 -2.64 1.71 0.01 188.01 254.44 45439 +1954 93 6.62 0.62 4.97 0.3 231.36 253.26 45642 +1954 94 9.86 3.86 8.21 0.14 282.68 251.36 45843 +1954 95 15.07 9.07 13.42 0 385.66 327.38 46045 +1954 96 12.15 6.15 10.5 0.34 324.6 251.57 46246 +1954 97 13 7 11.35 0.03 341.45 251.87 46446 +1954 98 13.18 7.18 11.53 0 345.12 337.42 46647 +1954 99 9.39 3.39 7.74 0 274.68 346.24 46846 +1954 100 13.53 7.53 11.88 0 352.34 340.63 47045 +1954 101 12.01 6.01 10.36 0 321.89 345.56 47243 +1954 102 10.69 4.69 9.04 0 297.3 349.87 47441 +1954 103 12.43 6.43 10.78 0 330.07 348.49 47638 +1954 104 12.56 6.56 10.91 1.59 332.64 262.54 47834 +1954 105 9.16 3.16 7.51 0.55 270.84 268.46 48030 +1954 106 10.59 4.59 8.94 0.03 295.51 267.89 48225 +1954 107 7.84 1.84 6.19 0 249.65 363.37 48419 +1954 108 7.4 1.4 5.75 0 242.92 365.79 48612 +1954 109 4.32 -1.68 2.67 0 199.98 371.53 48804 +1954 110 7.91 1.91 6.26 0 250.74 368.11 48995 +1954 111 11.1 5.1 9.45 0 304.76 364.31 49185 +1954 112 10.38 4.38 8.73 0 291.77 367.16 49374 +1954 113 9.68 3.68 8.03 0 279.6 369.74 49561 +1954 114 11.03 5.03 9.38 0 303.48 368.83 49748 +1954 115 12.6 6.6 10.95 0 333.43 367.18 49933 +1954 116 13.99 7.99 12.34 0 362.02 365.41 50117 +1954 117 17.69 11.69 16.04 0 448.55 357.38 50300 +1954 118 19.23 13.23 17.58 0 489.43 354.14 50481 +1954 119 16.31 10.31 14.66 0.58 414.42 272.68 50661 +1954 120 13.8 7.8 12.15 2.34 357.99 278.12 50840 +1954 121 19.4 13.4 17.75 0.35 494.14 267.75 51016 +1954 122 17.55 11.55 15.9 0.13 444.98 272.75 51191 +1954 123 13.79 7.79 12.14 0.34 357.78 280.66 51365 +1954 124 15.54 9.54 13.89 0.53 396.35 278.33 51536 +1954 125 16.06 10.06 14.41 0.28 408.48 278.07 51706 +1954 126 12.78 6.78 11.13 2.01 337.02 284.63 51874 +1954 127 11.91 5.91 10.26 0.36 319.97 286.67 52039 +1954 128 15.47 9.47 13.82 0.53 394.74 281.36 52203 +1954 129 19.8 13.8 18.15 0.71 505.35 272.65 52365 +1954 130 19.19 13.19 17.54 0.01 488.33 274.69 52524 +1954 131 15.51 9.51 13.86 0.4 395.66 283.11 52681 +1954 132 16.84 10.84 15.19 1.11 427.25 281.09 52836 +1954 133 16.84 10.84 15.19 0 427.25 375.48 52989 +1954 134 19.03 13.03 17.38 0.68 483.95 277.3 53138 +1954 135 18.32 12.32 16.67 0.41 464.91 279.46 53286 +1954 136 21.3 15.3 19.65 0.42 549.35 272.57 53430 +1954 137 23.4 17.4 21.75 0.61 616.4 267.09 53572 +1954 138 17.39 11.39 15.74 0 440.93 377.27 53711 +1954 139 13.19 7.19 11.54 0.28 345.32 291.48 53848 +1954 140 11.43 5.43 9.78 1.39 310.88 294.66 53981 +1954 141 11.98 5.98 10.33 0.87 321.31 294.15 54111 +1954 142 8.33 2.33 6.68 0.34 257.34 299.65 54238 +1954 143 8.56 2.56 6.91 0 261.02 399.7 54362 +1954 144 14.7 8.7 13.05 0 377.42 387.56 54483 +1954 145 11.95 5.95 10.3 0.11 320.74 295.72 54600 +1954 146 15.8 9.8 14.15 0.15 402.38 289.21 54714 +1954 147 21.16 15.16 19.51 0 545.11 369.53 54824 +1954 148 22.03 16.03 20.38 0 571.92 366.7 54931 +1954 149 21.18 15.18 19.53 0 545.72 370.14 55034 +1954 150 21.49 15.49 19.84 0 555.15 369.34 55134 +1954 151 20.81 14.81 19.16 0 534.64 372.17 55229 +1954 152 28.02 22.02 26.37 0 788.64 340.97 55321 +1954 153 23.82 17.82 22.17 0 630.61 360.93 55409 +1954 154 21.38 15.38 19.73 0 551.79 370.78 55492 +1954 155 18.5 12.5 16.85 0 469.67 380.67 55572 +1954 156 16.22 10.22 14.57 1.44 412.27 290.71 55648 +1954 157 15.91 9.91 14.26 1.2 404.95 291.46 55719 +1954 158 15.74 9.74 14.09 0 400.98 389.24 55786 +1954 159 18.51 12.51 16.86 0.37 469.94 286.16 55849 +1954 160 18.8 12.8 17.15 1.76 477.71 285.61 55908 +1954 161 19.33 13.33 17.68 0.55 492.19 284.39 55962 +1954 162 22.62 16.62 20.97 0.23 590.73 275.6 56011 +1954 163 22.8 16.8 21.15 0.03 596.57 275.22 56056 +1954 164 23.04 17.04 21.39 0.74 604.44 274.53 56097 +1954 165 24.65 18.65 23 0.17 659.51 269.53 56133 +1954 166 26.45 20.45 24.8 0.02 726.05 263.36 56165 +1954 167 22.99 16.99 21.34 0.01 602.79 274.77 56192 +1954 168 22.34 16.34 20.69 0.28 581.74 276.75 56214 +1954 169 22.81 16.81 21.16 0.07 596.9 275.38 56231 +1954 170 24.28 18.28 22.63 0.86 646.49 270.82 56244 +1954 171 23.85 17.85 22.2 0 631.63 362.98 56252 +1954 172 23.28 17.28 21.63 0.16 612.39 274 56256 +1954 173 22.65 16.65 21 0.01 591.7 275.88 56255 +1954 174 21.37 15.37 19.72 0 551.49 372.61 56249 +1954 175 21.5 15.5 19.85 0.24 555.46 279.08 56238 +1954 176 18.63 12.63 16.98 0.03 473.14 286.38 56223 +1954 177 22.95 16.95 21.3 0.31 601.48 274.8 56203 +1954 178 21.25 15.25 19.6 0.01 547.84 279.68 56179 +1954 179 24.95 18.95 23.3 0 670.22 357.87 56150 +1954 180 21.51 15.51 19.86 0 555.77 371.73 56116 +1954 181 24.08 18.08 22.43 0.01 639.54 271.11 56078 +1954 182 23.82 17.82 22.17 0 630.61 362.43 56035 +1954 183 23.69 17.69 22.04 0.78 626.18 272.1 55987 +1954 184 21.21 15.21 19.56 0.69 546.63 279.22 55935 +1954 185 20.56 14.56 18.91 0 527.26 374.51 55879 +1954 186 23.32 17.32 21.67 0.62 613.72 272.88 55818 +1954 187 19.89 13.89 18.24 0 507.9 376.36 55753 +1954 188 18.81 12.81 17.16 0 477.98 379.61 55684 +1954 189 18.13 12.13 16.48 0 459.92 381.53 55611 +1954 190 17.93 11.93 16.28 0 454.72 381.76 55533 +1954 191 21.62 15.62 19.97 0 559.15 369.19 55451 +1954 192 19.07 13.07 17.42 0 485.04 377.66 55366 +1954 193 17.28 11.28 15.63 0 438.16 382.81 55276 +1954 194 21.94 15.94 20.29 0.48 569.1 275.4 55182 +1954 195 23.47 17.47 21.82 0.71 618.75 270.71 55085 +1954 196 21.88 15.88 20.23 0.1 567.22 275.07 54984 +1954 197 17.02 11.02 15.37 0.03 431.69 286.62 54879 +1954 198 19.81 13.81 18.16 0.8 505.63 279.88 54770 +1954 199 20.21 14.21 18.56 1.8 517.07 278.61 54658 +1954 200 20.36 14.36 18.71 1.3 521.41 277.92 54542 +1954 201 20.58 14.58 18.93 0.74 527.84 277.01 54423 +1954 202 23.29 17.29 21.64 0 612.72 358.67 54301 +1954 203 22.16 16.16 20.51 0 576.02 362.57 54176 +1954 204 21.92 15.92 20.27 0.02 568.47 272.23 54047 +1954 205 24.23 18.23 22.58 0.42 644.75 264.98 53915 +1954 206 20.88 14.88 19.23 0 536.72 365.65 53780 +1954 207 20.73 14.73 19.08 0.9 532.26 274.14 53643 +1954 208 16.66 10.66 15.01 0.43 422.85 283.06 53502 +1954 209 22.52 16.52 20.87 0 587.51 357.7 53359 +1954 210 21.88 15.88 20.23 0.4 567.22 269.62 53213 +1954 211 17.05 11.05 15.4 0 432.43 374.25 53064 +1954 212 14.51 8.51 12.86 0 373.25 380.01 52913 +1954 213 18.35 12.35 16.7 0.42 465.7 276.68 52760 +1954 214 20.03 14.03 18.38 0 511.9 362.88 52604 +1954 215 20.09 14.09 18.44 0 513.62 362 52445 +1954 216 19.2 13.2 17.55 0 488.61 363.84 52285 +1954 217 23.01 17.01 21.36 0.36 603.45 262.24 52122 +1954 218 23.62 17.62 21.97 0 623.81 346.46 51958 +1954 219 22.8 16.8 21.15 0 596.57 348.64 51791 +1954 220 24.52 18.52 22.87 0.07 654.91 255.64 51622 +1954 221 28.22 22.22 26.57 0.38 796.93 242.07 51451 +1954 222 25.47 19.47 23.82 0.15 689.15 251.1 51279 +1954 223 22.17 16.17 20.52 0.6 576.34 260.2 51105 +1954 224 23.22 17.22 21.57 0 610.39 341.96 50929 +1954 225 22.67 16.67 21.02 0 592.35 342.93 50751 +1954 226 24.94 18.94 23.29 0 669.86 332.79 50572 +1954 227 23.4 17.4 21.75 0.51 616.4 253.34 50392 +1954 228 27.39 21.39 25.74 0.23 763 239.54 50210 +1954 229 25.25 19.25 23.6 0 681.09 327.9 50026 +1954 230 23.13 17.13 21.48 0.43 607.41 251.4 49842 +1954 231 17.25 11.25 15.6 0.21 437.41 264.48 49656 +1954 232 19.22 13.22 17.57 0.05 489.16 259.24 49469 +1954 233 16.79 10.79 15.14 0.52 426.03 263.28 49280 +1954 234 16.76 10.76 15.11 0 425.29 349.68 49091 +1954 235 17.38 11.38 15.73 0.92 440.68 259.9 48900 +1954 236 17.47 11.47 15.82 0.19 442.95 258.63 48709 +1954 237 18.44 12.44 16.79 0 468.08 340.5 48516 +1954 238 19.97 13.97 18.32 0 510.18 334.31 48323 +1954 239 23.48 17.48 21.83 0 619.08 320.88 48128 +1954 240 20.85 14.85 19.2 1.88 535.82 246.22 47933 +1954 241 21.52 15.52 19.87 0 556.07 324.41 47737 +1954 242 19.96 13.96 18.31 0 509.9 327.66 47541 +1954 243 21.43 15.43 19.78 0 553.32 321.18 47343 +1954 244 18.31 12.31 16.66 0.01 464.64 246.56 47145 +1954 245 15.63 9.63 13.98 0 398.43 333.66 46947 +1954 246 16.5 10.5 14.85 0 418.98 329.6 46747 +1954 247 20.39 14.39 18.74 1.19 522.29 237.84 46547 +1954 248 19.39 13.39 17.74 0.78 493.86 238.61 46347 +1954 249 17.28 11.28 15.63 0 438.16 321.76 46146 +1954 250 17.22 11.22 15.57 1.22 436.66 239.97 45945 +1954 251 19.36 13.36 17.71 0.2 493.03 234.13 45743 +1954 252 16.88 10.88 15.23 0.4 428.23 237.38 45541 +1954 253 19.95 13.95 18.3 0.44 509.61 229.7 45339 +1954 254 20.06 14.06 18.41 1.46 512.76 227.89 45136 +1954 255 20.13 14.13 18.48 1.42 514.76 226.08 44933 +1954 256 20.79 14.79 19.14 0.3 534.04 222.96 44730 +1954 257 16.97 10.97 15.32 0 430.45 305.33 44527 +1954 258 18.31 12.31 16.66 0.33 464.64 224.77 44323 +1954 259 20.05 14.05 18.4 0.63 512.47 219.48 44119 +1954 260 17.3 11.3 15.65 0.25 438.67 223.05 43915 +1954 261 21.39 15.39 19.74 0 552.1 284.06 43711 +1954 262 21.63 15.63 19.98 0.18 559.46 210.79 43507 +1954 263 25.19 19.19 23.54 0 678.9 266.89 43303 +1954 264 23.93 17.93 22.28 0.23 634.38 201.67 43099 +1954 265 22.85 16.85 21.2 0 598.2 270.18 42894 +1954 266 20.62 14.62 18.97 0 529.02 274.41 42690 +1954 267 21.7 15.7 20.05 0.02 561.62 201.56 42486 +1954 268 20.89 14.89 19.24 0 537.02 268.59 42282 +1954 269 21.46 15.46 19.81 1.02 554.23 198.43 42078 +1954 270 19.46 13.46 17.81 0.06 495.8 200.54 41875 +1954 271 19.93 13.93 18.28 0.03 509.04 197.73 41671 +1954 272 20.99 14.99 19.34 0 540 258.19 41468 +1954 273 22.43 16.43 20.78 0 584.62 251.72 41265 +1954 274 16.72 10.72 15.07 0 424.32 263.34 41062 +1954 275 12.09 6.09 10.44 0 323.43 269.02 40860 +1954 276 11.31 5.31 9.66 0 308.64 267.48 40658 +1954 277 9.8 3.8 8.15 1.2 281.65 200.19 40456 +1954 278 10.94 4.94 9.29 0.27 301.83 196.82 40255 +1954 279 13.52 7.52 11.87 0.89 352.13 191.7 40054 +1954 280 14.35 8.35 12.7 0.07 369.76 188.66 39854 +1954 281 14.4 8.4 12.75 0 370.85 248.75 39654 +1954 282 13.44 7.44 11.79 0 350.47 247.62 39455 +1954 283 13.94 7.94 12.29 0 360.96 243.99 39256 +1954 284 15.25 9.25 13.6 0.11 389.73 179.06 39058 +1954 285 14.25 8.25 12.6 0 367.6 237.84 38861 +1954 286 16.29 10.29 14.64 0.05 413.94 173.66 38664 +1954 287 12.36 6.36 10.71 0.02 328.69 176.32 38468 +1954 288 10.36 4.36 8.71 0 291.42 235.03 38273 +1954 289 16.17 10.17 14.52 0 411.08 223.56 38079 +1954 290 11.67 5.67 10.02 0 315.4 227.78 37885 +1954 291 12.1 6.1 10.45 0 323.63 224.49 37693 +1954 292 15.52 9.52 13.87 0 395.89 216.6 37501 +1954 293 10.98 4.98 9.33 0 302.56 220.54 37311 +1954 294 10.22 4.22 8.57 0 288.95 218.58 37121 +1954 295 12.29 6.29 10.64 0 327.32 213.11 36933 +1954 296 12.56 6.56 10.91 0.03 332.64 157.63 36745 +1954 297 10.74 4.74 9.09 0.15 298.21 157.33 36560 +1954 298 16.48 10.48 14.83 0.44 418.5 149.23 36375 +1954 299 13.98 7.98 12.33 0 361.81 200.15 36191 +1954 300 13.56 7.56 11.91 0 352.96 198.12 36009 +1954 301 11.02 5.02 9.37 0.18 303.3 149.16 35829 +1954 302 10.7 4.7 9.05 0 297.48 196.64 35650 +1954 303 7.88 1.88 6.23 0 250.27 197.01 35472 +1954 304 5.28 -0.72 3.63 0.05 212.6 147.59 35296 +1954 305 4.98 -1.02 3.33 0.36 208.58 145.68 35122 +1954 306 7.31 1.31 5.66 0.04 241.56 142.52 34950 +1954 307 9.9 3.9 8.25 0 283.37 185 34779 +1954 308 9.01 3.01 7.36 0.48 268.36 137.47 34610 +1954 309 4.59 -1.41 2.94 0.22 203.46 138.54 34444 +1954 310 4.7 -1.3 3.05 0.02 204.89 136.62 34279 +1954 311 2.05 -3.95 0.4 0.01 172.67 136.28 34116 +1954 312 1.11 -4.89 -0.54 0 162.35 179.58 33956 +1954 313 4.32 -1.68 2.67 0.01 199.98 131.56 33797 +1954 314 4.35 -1.65 2.7 0 200.36 173.41 33641 +1954 315 6.53 0.53 4.88 0.05 230.05 126.94 33488 +1954 316 10.32 4.32 8.67 0.08 290.71 122.8 33337 +1954 317 11.89 5.89 10.24 0 319.59 159.94 33188 +1954 318 11.99 5.99 10.34 0 321.51 157.54 33042 +1954 319 9.5 3.5 7.85 0 276.54 158.34 32899 +1954 320 9.23 3.23 7.58 0 272 156.73 32758 +1954 321 3.67 -2.33 2.02 0.03 191.8 119.08 32620 +1954 322 3.67 -2.33 2.02 0.01 191.8 117.7 32486 +1954 323 8.99 2.99 7.34 0.14 268.03 113.58 32354 +1954 324 6.14 0.14 4.49 0 224.48 151.62 32225 +1954 325 2.44 -3.56 0.79 0 177.12 152.21 32100 +1954 326 4.72 -1.28 3.07 0 205.16 149.39 31977 +1954 327 7.49 1.49 5.84 0.18 244.28 109.21 31858 +1954 328 10.72 4.72 9.07 0 297.85 140.96 31743 +1954 329 7.2 1.2 5.55 2.84 239.91 106.78 31631 +1954 330 9.37 3.37 7.72 0.12 274.35 104.43 31522 +1954 331 8.4 2.4 6.75 0.81 258.46 104.04 31417 +1954 332 9.69 3.69 8.04 0.92 279.77 102.04 31316 +1954 333 8.56 2.56 6.91 0.12 261.02 101.92 31218 +1954 334 6.36 0.36 4.71 0 227.61 136.4 31125 +1954 335 9.75 3.75 8.1 0 280.79 132.7 31035 +1954 336 10.95 4.95 9.3 0.14 302.02 97.97 30949 +1954 337 8.05 2.05 6.4 0 252.93 131.32 30867 +1954 338 10.28 4.28 8.63 0.97 290 96.48 30790 +1954 339 5.53 -0.47 3.88 1.09 215.99 98.48 30716 +1954 340 5.41 -0.59 3.76 0.28 214.36 97.99 30647 +1954 341 11.01 5.01 9.36 0.12 303.11 94.22 30582 +1954 342 12.1 6.1 10.45 0 323.63 123.91 30521 +1954 343 9.61 3.61 7.96 0.29 278.4 93.93 30465 +1954 344 6.32 0.32 4.67 0 227.04 126.46 30413 +1954 345 2.12 -3.88 0.47 0 173.47 128.38 30366 +1954 346 5.99 -0.01 4.34 0.12 222.37 94.27 30323 +1954 347 4.8 -1.2 3.15 0 206.2 125.82 30284 +1954 348 2.48 -3.52 0.83 1.02 177.58 95.03 30251 +1954 349 3.82 -2.18 2.17 0.02 193.66 94.22 30221 +1954 350 4.16 -1.84 2.51 0 197.94 125.11 30197 +1954 351 2.72 -3.28 1.07 0 180.38 125.65 30177 +1954 352 5.18 -0.82 3.53 0.01 211.25 93.17 30162 +1954 353 3.7 -2.3 2.05 0 192.17 124.98 30151 +1954 354 4.6 -1.4 2.95 0 203.59 124.46 30145 +1954 355 8.1 2.1 6.45 0 253.71 122.25 30144 +1954 356 9.6 3.6 7.95 0.05 278.23 90.87 30147 +1954 357 4.97 -1.03 3.32 0.95 208.45 93.25 30156 +1954 358 5.87 -0.13 4.22 0.63 220.69 92.91 30169 +1954 359 3.63 -2.37 1.98 0 191.31 125.28 30186 +1954 360 2.01 -3.99 0.36 0 172.22 126.46 30208 +1954 361 1.71 -4.29 0.06 0 168.88 126.93 30235 +1954 362 5.72 -0.28 4.07 0.09 218.61 93.92 30267 +1954 363 9.18 3.18 7.53 0 271.17 123.44 30303 +1954 364 3.34 -2.66 1.69 0.12 187.77 95.66 30343 +1954 365 4.61 -1.39 2.96 0.01 203.72 95.57 30388 +1955 1 1.32 -4.68 -0.33 0.01 164.61 97.51 30438 +1955 2 0.65 -5.35 -1 0 157.49 131.05 30492 +1955 3 -0.83 -6.83 -2.48 0 142.71 132.63 30551 +1955 4 -2.08 -8.08 -3.73 0 131.17 134.03 30614 +1955 5 -0.01 -6.01 -1.66 0 150.74 133.86 30681 +1955 6 3.25 -2.75 1.6 0.14 186.68 99.89 30752 +1955 7 1.85 -4.15 0.2 0.31 170.43 101.03 30828 +1955 8 1.43 -4.57 -0.22 0 165.8 136.4 30907 +1955 9 -1.42 -7.42 -3.07 0 137.16 138.92 30991 +1955 10 -1.17 -7.17 -2.82 0 139.49 140.13 31079 +1955 11 3 -3 1.35 0 183.68 139.16 31171 +1955 12 6.14 0.14 4.49 0.19 224.48 103.7 31266 +1955 13 1.83 -4.17 0.18 0 170.21 142.41 31366 +1955 14 5.37 -0.63 3.72 0 213.82 141.86 31469 +1955 15 5.2 -0.8 3.55 0 211.52 143.4 31575 +1955 16 4.31 -1.69 2.66 0 199.85 145.24 31686 +1955 17 6.36 0.36 4.71 0 227.61 145.57 31800 +1955 18 9.17 3.17 7.52 0 271 145.28 31917 +1955 19 7.24 1.24 5.59 0 240.5 148.73 32038 +1955 20 4.56 -1.44 2.91 0.07 203.07 114.13 32161 +1955 21 2.91 -3.09 1.26 0 182.61 155.18 32289 +1955 22 0.01 -5.99 -1.64 0 150.94 158.47 32419 +1955 23 0.09 -5.91 -1.56 0.04 151.75 120.17 32552 +1955 24 -1.02 -7.02 -2.67 1.19 140.9 166 32688 +1955 25 -3.2 -9.2 -4.85 0 121.53 209.36 32827 +1955 26 -1.87 -7.87 -3.52 0 133.05 210.58 32969 +1955 27 2.49 -3.51 0.84 0 177.7 209.9 33114 +1955 28 2.7 -3.3 1.05 0 180.14 211.47 33261 +1955 29 3.7 -2.3 2.05 0 192.17 212.59 33411 +1955 30 5.28 -0.72 3.63 0.14 212.6 169.94 33564 +1955 31 1.3 -4.7 -0.35 0 164.39 217.51 33718 +1955 32 2.72 -3.28 1.07 0.29 180.38 173.75 33875 +1955 33 2.27 -3.73 0.62 1.44 175.17 175.49 34035 +1955 34 2.17 -3.83 0.52 0.91 174.03 176.75 34196 +1955 35 2.45 -3.55 0.8 0.06 177.24 177.76 34360 +1955 36 3.06 -2.94 1.41 0.15 184.4 178.82 34526 +1955 37 3.9 -2.1 2.25 0 194.66 189.27 34694 +1955 38 5.35 -0.65 3.7 0 213.54 190.93 34863 +1955 39 6.55 0.55 4.9 0 230.34 192.54 35035 +1955 40 5.54 -0.46 3.89 0 216.13 195.99 35208 +1955 41 7.06 1.06 5.41 0 237.82 197.29 35383 +1955 42 9.61 3.61 7.96 0.45 278.4 147.98 35560 +1955 43 7.26 1.26 5.61 0.98 240.81 151.75 35738 +1955 44 5.95 -0.05 4.3 0.57 221.81 154.54 35918 +1955 45 1.82 -4.18 0.17 0 170.1 211.83 36099 +1955 46 1.03 -4.97 -0.62 0.19 161.49 161.3 36282 +1955 47 -0.34 -6.34 -1.99 0 147.46 218.75 36466 +1955 48 1.66 -4.34 0.01 0 168.32 220.32 36652 +1955 49 1.88 -4.12 0.23 0.31 170.77 167.23 36838 +1955 50 4.08 -1.92 2.43 0.38 196.93 168.01 37026 +1955 51 2.89 -3.11 1.24 0.3 182.38 170.94 37215 +1955 52 4.34 -1.66 2.69 0 200.23 229.61 37405 +1955 53 4.81 -1.19 3.16 0 206.34 232.17 37596 +1955 54 5.62 -0.38 3.97 0 217.23 234.2 37788 +1955 55 7.37 1.37 5.72 0.08 242.46 176.6 37981 +1955 56 4.8 -1.2 3.15 0.76 206.2 180.48 38175 +1955 57 7.4 1.4 5.75 0.03 242.92 180.74 38370 +1955 58 4.01 -1.99 2.36 0.14 196.04 185.38 38565 +1955 59 2.51 -3.49 0.86 0.59 177.93 188.36 38761 +1955 60 1.82 -4.18 0.17 0.26 170.1 190.95 38958 +1955 61 4.06 -1.94 2.41 0.12 196.67 191.78 39156 +1955 62 3.68 -2.32 2.03 0.15 191.93 194.15 39355 +1955 63 6.32 0.32 4.67 0 227.04 259.35 39553 +1955 64 9.18 3.18 7.53 0 271.17 258.95 39753 +1955 65 9.15 3.15 7.5 0 270.67 261.85 39953 +1955 66 6.55 0.55 4.9 0.25 230.34 200.74 40154 +1955 67 3.61 -2.39 1.96 0.21 191.06 205.12 40355 +1955 68 3.18 -2.82 1.53 0 185.83 276.78 40556 +1955 69 6.51 0.51 4.86 0 229.76 276.1 40758 +1955 70 9.63 3.63 7.98 0 278.74 275.09 40960 +1955 71 9.65 3.65 8 0 279.08 277.96 41163 +1955 72 4.17 -1.83 2.52 0 198.07 287.18 41366 +1955 73 6.59 0.59 4.94 0 230.92 287.3 41569 +1955 74 4.88 -1.12 3.23 0.1 207.26 218.95 41772 +1955 75 3.8 -2.2 2.15 0.42 193.42 221.83 41976 +1955 76 6.96 0.96 5.31 0.8 236.34 221.25 42179 +1955 77 3.46 -2.54 1.81 0.95 189.23 226.06 42383 +1955 78 5.2 -0.8 3.55 0.01 211.52 226.74 42587 +1955 79 3.14 -2.86 1.49 0.06 185.35 230.39 42791 +1955 80 7.65 1.65 6 0.12 246.72 228.53 42996 +1955 81 3.71 -2.29 2.06 0.28 192.3 233.86 43200 +1955 82 3.72 -2.28 2.07 0 192.42 314.5 43404 +1955 83 1.4 -4.6 -0.25 0.08 165.48 239.42 43608 +1955 84 2.17 -3.83 0.52 0 174.03 321.12 43812 +1955 85 6.77 0.77 5.12 0 233.54 318.66 44016 +1955 86 6.75 0.75 5.1 0.01 233.25 240.83 44220 +1955 87 5.12 -0.88 3.47 0.01 210.45 244.22 44424 +1955 88 1.38 -4.62 -0.27 0.25 165.26 248.88 44627 +1955 89 1 -5 -0.65 0 161.18 334.51 44831 +1955 90 4.52 -1.48 2.87 0 202.55 333.41 45034 +1955 91 8.91 2.91 7.26 0 266.71 329.99 45237 +1955 92 9.51 3.51 7.86 0.44 276.71 248.49 45439 +1955 93 9.26 3.26 7.61 0 272.5 333.93 45642 +1955 94 9.22 3.22 7.57 0.24 271.84 252.12 45843 +1955 95 10.32 4.32 8.67 0 290.71 336.54 46045 +1955 96 9.52 3.52 7.87 0 276.88 339.97 46246 +1955 97 10.61 4.61 8.96 0 295.87 340.23 46446 +1955 98 9.52 3.52 7.87 0.3 276.88 258 46647 +1955 99 8.39 2.39 6.74 0 258.3 347.79 46846 +1955 100 3.09 -2.91 1.44 0 184.76 356.53 47045 +1955 101 4.09 -1.91 2.44 0 197.05 357.4 47243 +1955 102 8.4 2.4 6.75 0 258.46 353.62 47441 +1955 103 12.45 6.45 10.8 0 330.46 348.45 47638 +1955 104 14.31 8.31 12.66 0.03 368.89 259.79 47834 +1955 105 11.28 5.28 9.63 0.13 308.09 265.72 48030 +1955 106 9.61 3.61 7.96 0.22 278.4 269.16 48225 +1955 107 11.15 5.15 9.5 0 305.68 357.86 48419 +1955 108 9.31 3.31 7.66 0 273.34 362.83 48612 +1955 109 14.62 8.62 12.97 0 375.66 354.07 48804 +1955 110 15.64 9.64 13.99 0 398.66 353.06 48995 +1955 111 12.43 6.43 10.78 0 330.07 361.73 49185 +1955 112 13.62 7.62 11.97 0 354.21 360.76 49374 +1955 113 13.49 7.49 11.84 0 351.51 362.38 49561 +1955 114 13.14 7.14 11.49 0 344.3 364.62 49748 +1955 115 16.45 10.45 14.8 0 417.77 358.25 49933 +1955 116 14.61 8.61 12.96 0.05 375.44 272.99 50117 +1955 117 10.8 4.8 9.15 0 299.29 373.26 50300 +1955 118 9.8 3.8 8.15 1.46 281.65 282.3 50481 +1955 119 11.21 5.21 9.56 0.09 306.79 281.27 50661 +1955 120 14.07 8.07 12.42 0.43 363.73 277.66 50840 +1955 121 20.38 14.38 18.73 0.28 522 265.38 51016 +1955 122 21.2 15.2 19.55 0 546.32 352.22 51191 +1955 123 21.29 15.29 19.64 0.13 549.05 264.67 51365 +1955 124 20.53 14.53 18.88 0.27 526.38 267.4 51536 +1955 125 15.35 9.35 13.7 0 392 372.57 51706 +1955 126 16.02 10.02 14.37 0 407.53 371.85 51874 +1955 127 12.71 6.71 11.06 0 335.62 380.56 52039 +1955 128 13.67 7.67 12.02 0.8 355.26 284.59 52203 +1955 129 10.01 4.01 8.36 0 285.28 387.77 52365 +1955 130 8.65 2.65 7 0 262.48 390.95 52524 +1955 131 11.22 5.22 9.57 0.68 306.98 290.33 52681 +1955 132 7.76 1.76 6.11 0.29 248.42 295.55 52836 +1955 133 13.18 7.18 11.53 0 345.12 384.56 52989 +1955 134 17.53 11.53 15.88 0.02 444.47 280.68 53138 +1955 135 20.52 14.52 18.87 0.25 526.08 274.15 53286 +1955 136 16.72 10.72 15.07 0 424.32 377.85 53430 +1955 137 17.15 11.15 15.5 0 434.92 377.35 53572 +1955 138 19.3 13.3 17.65 0.22 491.36 278.61 53711 +1955 139 19.07 13.07 17.42 0 485.04 372.89 53848 +1955 140 21.36 15.36 19.71 0 551.18 365.62 53981 +1955 141 21.59 15.59 19.94 0.01 558.23 273.9 54111 +1955 142 19.61 13.61 17.96 0 500 372.55 54238 +1955 143 22.99 16.99 21.34 0.12 602.79 270.65 54362 +1955 144 20.7 14.7 19.05 0 531.38 369.86 54483 +1955 145 21.92 15.92 20.27 0 568.47 365.91 54600 +1955 146 17.47 11.47 15.82 1.23 442.95 285.75 54714 +1955 147 15.21 9.21 13.56 1.91 388.82 290.72 54824 +1955 148 15.33 9.33 13.68 1.1 391.55 290.78 54931 +1955 149 11.59 5.59 9.94 0.67 313.89 297.47 55034 +1955 150 7.5 1.5 5.85 0.97 244.43 303.28 55134 +1955 151 10.07 4.07 8.42 0.24 286.32 300.26 55229 +1955 152 13.89 7.89 12.24 0.29 359.9 294.32 55321 +1955 153 15.72 9.72 14.07 0 400.51 388.11 55409 +1955 154 19.48 13.48 17.83 0 496.36 377.35 55492 +1955 155 19.54 13.54 17.89 0 498.04 377.34 55572 +1955 156 19.57 13.57 17.92 0 498.88 377.57 55648 +1955 157 17.76 11.76 16.11 0 450.34 383.4 55719 +1955 158 23.76 17.76 22.11 0 628.56 362.31 55786 +1955 159 23.74 17.74 22.09 0 627.88 362.63 55849 +1955 160 22.35 16.35 20.7 0 582.06 368.39 55908 +1955 161 14.74 8.74 13.09 0 378.3 392.31 55962 +1955 162 17.48 11.48 15.83 0 443.2 384.96 56011 +1955 163 22.07 16.07 20.42 0.01 573.18 277.35 56056 +1955 164 18.69 12.69 17.04 0.11 474.75 286.16 56097 +1955 165 21.87 15.87 20.22 0 566.91 370.69 56133 +1955 166 21.11 15.11 19.46 0.6 543.61 280.18 56165 +1955 167 20.89 14.89 19.24 1.18 537.02 280.73 56192 +1955 168 21.19 15.19 19.54 0 546.02 373.31 56214 +1955 169 24.31 18.31 22.66 0.07 647.54 270.72 56231 +1955 170 22.9 16.9 21.25 0 599.84 366.81 56244 +1955 171 24.33 18.33 22.68 0.06 648.23 270.7 56252 +1955 172 21.41 15.41 19.76 0 552.71 372.56 56256 +1955 173 23.35 17.35 21.7 0 614.73 365.03 56255 +1955 174 18.79 12.79 17.14 0.01 477.44 286.05 56249 +1955 175 16.92 10.92 15.27 0.42 429.22 290.23 56238 +1955 176 17.69 11.69 16.04 0.03 448.55 288.53 56223 +1955 177 15.09 9.09 13.44 0 386.11 391.75 56203 +1955 178 21.05 15.05 19.4 0 541.8 373.63 56179 +1955 179 19.23 13.23 17.58 0.19 489.43 284.81 56150 +1955 180 18.34 12.34 16.69 0.11 465.43 286.82 56116 +1955 181 17.92 11.92 16.27 1.05 454.46 287.73 56078 +1955 182 17.94 11.94 16.29 1.99 454.98 287.57 56035 +1955 183 15.92 9.92 14.27 0.14 405.18 291.73 55987 +1955 184 21.86 15.86 20.21 0.05 566.6 277.42 55935 +1955 185 21.94 15.94 20.29 1.81 569.1 277.13 55879 +1955 186 18.37 12.37 16.72 0.43 466.23 286.08 55818 +1955 187 21.23 15.23 19.58 0 547.23 371.69 55753 +1955 188 25.33 19.33 23.68 0 684.01 354.75 55684 +1955 189 28.65 22.65 27 0.54 815.01 253.55 55611 +1955 190 25.75 19.75 24.1 0.92 699.53 264.22 55533 +1955 191 24.89 18.89 23.24 0 668.07 355.94 55451 +1955 192 27.77 21.77 26.12 0 778.38 341.85 55366 +1955 193 28.84 22.84 27.19 0.04 823.1 251.93 55276 +1955 194 24.8 18.8 23.15 0 664.85 355.57 55182 +1955 195 23.9 17.9 22.25 1.08 633.35 269.37 55085 +1955 196 19.77 13.77 18.12 0.94 504.5 280.64 54984 +1955 197 18.87 12.87 17.22 0.63 479.6 282.48 54879 +1955 198 16.49 10.49 14.84 0.15 418.74 287.4 54770 +1955 199 15.84 9.84 14.19 0 403.31 384.58 54658 +1955 200 23.43 17.43 21.78 0 617.4 359.11 54542 +1955 201 23.27 17.27 21.62 0.47 612.06 269.47 54423 +1955 202 19.94 13.94 18.29 0.19 509.33 278.21 54301 +1955 203 20.38 14.38 18.73 0.92 522 276.72 54176 +1955 204 20.67 14.67 19.02 0.44 530.49 275.59 54047 +1955 205 20.46 14.46 18.81 0 524.33 367.66 53915 +1955 206 21.86 15.86 20.21 0 566.6 362.12 53780 +1955 207 23.77 17.77 22.12 0.07 628.9 265.52 53643 +1955 208 23.34 17.34 21.69 0.59 614.39 266.35 53502 +1955 209 22.16 16.16 20.51 0.02 576.02 269.3 53359 +1955 210 18.83 12.83 17.18 0 478.52 369.8 53213 +1955 211 19.14 13.14 17.49 0 486.96 368.05 53064 +1955 212 21.6 15.6 19.95 0.76 558.54 269.22 52913 +1955 213 17.71 11.71 16.06 0.95 449.06 278.1 52760 +1955 214 19.47 13.47 17.82 0.75 496.08 273.52 52604 +1955 215 19.69 13.69 18.04 0 502.24 363.3 52445 +1955 216 20.74 14.74 19.09 1.05 532.56 269.1 52285 +1955 217 21.1 15.1 19.45 0.65 543.31 267.51 52122 +1955 218 20.99 14.99 19.34 0.96 540 267.18 51958 +1955 219 18.17 12.17 16.52 0.19 460.97 273.14 51791 +1955 220 21.08 15.08 19.43 1.29 542.7 265.47 51622 +1955 221 25.25 19.25 23.6 0.97 681.09 252.58 51451 +1955 222 24.47 18.47 22.82 1.16 653.15 254.31 51279 +1955 223 22.36 16.36 20.71 0.54 582.38 259.68 51105 +1955 224 22.33 16.33 20.68 0.89 581.42 258.98 50929 +1955 225 21.36 15.36 19.71 0.51 551.18 260.74 50751 +1955 226 21.6 15.6 19.95 0 558.54 345.68 50572 +1955 227 23.41 17.41 21.76 0.32 616.73 253.31 50392 +1955 228 26.22 20.22 24.57 0.51 717.24 243.62 50210 +1955 229 23.04 17.04 21.39 0.52 604.44 252.58 50026 +1955 230 23.9 17.9 22.25 1.11 633.35 249.16 49842 +1955 231 22.63 16.63 20.98 0.58 591.05 251.72 49656 +1955 232 24.18 18.18 22.53 0.01 643.01 246.29 49469 +1955 233 22.5 16.5 20.85 0 586.86 333.39 49280 +1955 234 18.85 12.85 17.2 0.37 479.06 257.93 49091 +1955 235 20.31 14.31 18.66 0.16 519.96 253.47 48900 +1955 236 20.18 14.18 18.53 0 516.2 336.95 48709 +1955 237 18.61 12.61 16.96 0.55 472.61 255.01 48516 +1955 238 15.68 9.68 14.03 0.88 399.59 259.52 48323 +1955 239 14.65 8.65 13 0.35 376.32 260.16 48128 +1955 240 14.53 8.53 12.88 0 373.68 345.35 47933 +1955 241 17.61 11.61 15.96 0 446.5 336.08 47737 +1955 242 19.1 13.1 17.45 0 485.86 330.2 47541 +1955 243 21.12 15.12 19.47 0 543.91 322.19 47343 +1955 244 18.65 12.65 17 0.19 473.68 245.85 47145 +1955 245 17.18 11.18 15.53 0 435.66 329.88 46947 +1955 246 15.97 9.97 14.32 0.01 406.36 248.16 46747 +1955 247 18.67 12.67 17.02 0.21 474.21 241.58 46547 +1955 248 17.46 11.46 15.81 0 442.7 323.38 46347 +1955 249 15.17 9.17 13.52 0 387.92 326.77 46146 +1955 250 16.63 10.63 14.98 0 422.13 321.41 45945 +1955 251 20.21 14.21 18.56 0 517.07 309.71 45743 +1955 252 18.73 12.73 17.08 0.04 475.82 233.82 45541 +1955 253 19.46 13.46 17.81 0.57 495.8 230.74 45339 +1955 254 24.75 18.75 23.1 0 663.06 288.37 45136 +1955 255 24.97 18.97 23.32 0 670.94 285.41 44933 +1955 256 23.16 17.16 21.51 0.05 608.4 217.3 44730 +1955 257 14.56 8.56 12.91 0.01 374.34 233 44527 +1955 258 14.06 8.06 12.41 0 363.52 309.3 44323 +1955 259 19.54 13.54 17.89 0 498.04 294.05 44119 +1955 260 21.37 15.37 19.72 0.04 551.49 214.87 43915 +1955 261 18.76 12.76 17.11 0.96 476.63 218.52 43711 +1955 262 18.16 12.16 16.51 0.38 460.7 217.9 43507 +1955 263 20.14 14.14 18.49 0.09 515.05 212.21 43303 +1955 264 17.54 11.54 15.89 0.81 444.72 215.28 43099 +1955 265 18.04 12.04 16.39 0 457.57 283.51 42894 +1955 266 13.36 7.36 11.71 0.19 348.81 218.14 42690 +1955 267 12.63 6.63 10.98 0.12 334.03 217.07 42486 +1955 268 16.45 10.45 14.8 0.39 417.77 209.61 42282 +1955 269 15.99 9.99 14.34 0 406.83 277.95 42078 +1955 270 17.92 11.92 16.27 0 454.46 271.11 41875 +1955 271 21.88 15.88 20.23 0.45 567.22 193.74 41671 +1955 272 20.4 14.4 18.75 0.11 522.58 194.83 41468 +1955 273 18.55 12.55 16.9 0 471 261.91 41265 +1955 274 16.73 10.73 15.08 0.04 424.56 197.49 41062 +1955 275 15.82 9.82 14.17 1.24 402.84 196.82 40860 +1955 276 13.91 7.91 12.26 0.8 360.32 197.46 40658 +1955 277 14.54 8.54 12.89 0.6 373.9 194.63 40456 +1955 278 17.72 11.72 16.07 0.16 449.31 187.8 40255 +1955 279 15.13 9.13 13.48 0.22 387.01 189.59 40054 +1955 280 10.47 4.47 8.82 0.02 293.37 193.16 39854 +1955 281 6.89 0.89 5.24 0.3 235.3 194.37 39654 +1955 282 8.53 2.53 6.88 0.28 260.54 190.86 39455 +1955 283 9.92 3.92 8.27 0.11 283.72 187.41 39256 +1955 284 11.39 5.39 9.74 0.14 310.13 183.64 39058 +1955 285 14.91 8.91 13.26 0.77 382.08 177.55 38861 +1955 286 9.51 3.51 7.86 0.69 276.71 181.4 38664 +1955 287 10.08 4.08 8.43 0.27 286.5 178.64 38468 +1955 288 12.01 6.01 10.36 0.12 321.89 174.61 38273 +1955 289 12.56 6.56 10.91 0.1 332.64 172.04 38079 +1955 290 14.52 8.52 12.87 0.04 373.46 167.67 37885 +1955 291 12.88 6.88 11.23 0 339.03 223.38 37693 +1955 292 14.09 8.09 12.44 0 364.16 218.9 37501 +1955 293 9.98 3.98 8.33 0.06 284.76 166.33 37311 +1955 294 9.79 3.79 8.14 1.54 281.48 164.32 37121 +1955 295 10.12 4.12 8.47 0.11 287.2 161.89 36933 +1955 296 12.54 6.54 10.89 1.45 332.24 157.65 36745 +1955 297 10.38 4.38 8.73 0.46 291.77 157.65 36560 +1955 298 9.69 3.69 8.04 0.16 279.77 156.29 36375 +1955 299 9.26 3.26 7.61 0.28 272.5 154.54 36191 +1955 300 12.37 6.37 10.72 0.66 328.89 149.79 36009 +1955 301 11.85 5.85 10.2 0.16 318.82 148.4 35829 +1955 302 15.25 9.25 13.6 0 389.73 190.63 35650 +1955 303 19.36 13.36 17.71 0 493.03 181.15 35472 +1955 304 21.77 15.77 20.12 0.01 563.79 130.46 35296 +1955 305 13.61 7.61 11.96 0.13 354.01 139 35122 +1955 306 14.35 8.35 12.7 0.1 369.76 136.59 34950 +1955 307 7.59 1.59 5.94 0.3 245.81 140.43 34779 +1955 308 3.74 -2.26 2.09 0 192.67 187.67 34610 +1955 309 2.49 -3.51 0.84 0 177.7 186.15 34444 +1955 310 1.12 -4.88 -0.53 0 162.45 184.49 34279 +1955 311 1.2 -4.8 -0.45 0.07 163.31 136.66 34116 +1955 312 4.13 -1.87 2.48 0 197.56 177.69 33956 +1955 313 3.39 -2.61 1.74 0 188.37 176.03 33797 +1955 314 4.44 -1.56 2.79 0 201.52 173.35 33641 +1955 315 4.49 -1.51 2.84 0 202.16 170.75 33488 +1955 316 7.38 1.38 5.73 0.44 242.61 124.79 33337 +1955 317 8.64 2.64 6.99 0 262.32 163.12 33188 +1955 318 7.19 1.19 5.54 0 239.76 162 33042 +1955 319 9.24 3.24 7.59 0.38 272.17 118.93 32899 +1955 320 9.76 3.76 8.11 0.95 280.97 117.19 32758 +1955 321 13.99 7.99 12.34 0.06 362.02 112.31 32620 +1955 322 12.89 6.89 11.24 0.11 339.23 111.92 32486 +1955 323 14.75 8.75 13.1 0.11 378.52 109.13 32354 +1955 324 10.55 4.55 8.9 0 294.79 148.01 32225 +1955 325 9.73 3.73 8.08 0.12 280.45 110.29 32100 +1955 326 9.33 3.33 7.68 0.02 273.67 109.47 31977 +1955 327 8.63 2.63 6.98 0 262.15 144.72 31858 +1955 328 8.9 2.9 7.25 0 266.55 142.54 31743 +1955 329 6.58 0.58 4.93 0.04 230.78 107.11 31631 +1955 330 1.04 -4.96 -0.61 0.47 161.6 108.47 31522 +1955 331 0.54 -5.46 -1.11 0.19 156.35 107.65 31417 +1955 332 1.92 -4.08 0.27 0.18 171.21 105.9 31316 +1955 333 5.13 -0.87 3.48 0.22 210.58 103.72 31218 +1955 334 4.58 -1.42 2.93 0 203.33 137.53 31125 +1955 335 2.7 -3.3 1.05 0.76 180.14 103.06 31035 +1955 336 -1.79 -7.79 -3.44 0 133.78 138.36 30949 +1955 337 -0.41 -6.41 -2.06 0.04 146.78 144.98 30867 +1955 338 0.42 -5.58 -1.23 0 155.11 177.75 30790 +1955 339 4.44 -1.56 2.79 0 201.52 131.97 30716 +1955 340 4.18 -1.82 2.53 0 198.19 131.38 30647 +1955 341 7.36 1.36 5.71 0 242.31 128.47 30582 +1955 342 10.84 4.84 9.19 0 300.02 125.04 30521 +1955 343 10.1 4.1 8.45 0.01 286.85 93.63 30465 +1955 344 8.86 2.86 7.21 0 265.89 124.7 30413 +1955 345 7.35 1.35 5.7 0.41 242.16 94.02 30366 +1955 346 6.31 0.31 4.66 0.24 226.89 94.12 30323 +1955 347 3.39 -2.61 1.74 0 188.37 126.59 30284 +1955 348 5.28 -0.72 3.63 0 212.6 125.19 30251 +1955 349 3.75 -2.25 2.1 0 192.79 125.67 30221 +1955 350 3.41 -2.59 1.76 0 188.62 125.51 30197 +1955 351 4.93 -1.07 3.28 0 207.92 124.46 30177 +1955 352 5.83 -0.17 4.18 0.3 220.13 92.88 30162 +1955 353 0.35 -5.65 -1.3 0 154.39 126.58 30151 +1955 354 4.05 -1.95 2.4 0 196.55 124.76 30145 +1955 355 6.57 0.57 4.92 0 230.63 123.27 30144 +1955 356 6.6 0.6 4.95 0 231.07 123.28 30147 +1955 357 7.63 1.63 5.98 0 246.42 122.66 30156 +1955 358 6.87 0.87 5.22 0 235.01 123.25 30169 +1955 359 8.5 2.5 6.85 0 260.06 122.24 30186 +1955 360 10.91 4.91 9.26 0 301.29 120.72 30208 +1955 361 9.14 3.14 7.49 0 270.51 122.46 30235 +1955 362 9.81 3.81 8.16 0 281.82 122.37 30267 +1955 363 5.8 -0.2 4.15 0 219.72 125.75 30303 +1955 364 8.34 2.34 6.69 0 257.5 124.45 30343 +1955 365 8.07 2.07 6.42 0 253.24 125.2 30388 +1956 1 3.29 -2.71 1.64 0.12 187.16 96.78 30438 +1956 2 3.8 -2.2 2.15 0 193.42 129.5 30492 +1956 3 4.57 -1.43 2.92 0 203.2 130 30551 +1956 4 7.13 1.13 5.48 0 238.86 129.3 30614 +1956 5 10.11 4.11 8.46 0.05 287.02 95.77 30681 +1956 6 6 0 4.35 0 222.51 131.57 30752 +1956 7 6.04 0.04 4.39 0 223.07 132.33 30828 +1956 8 7.35 1.35 5.7 0 242.16 132.92 30907 +1956 9 1.66 -4.34 0.01 0.2 168.32 103.16 30991 +1956 10 -0.28 -6.28 -1.93 0.39 148.06 148.49 31079 +1956 11 -1.01 -7.01 -2.66 0 141 184.61 31171 +1956 12 -2.35 -8.35 -4 0 128.79 186.04 31266 +1956 13 2.53 -3.47 0.88 0 178.16 185 31366 +1956 14 3.85 -2.15 2.2 0 194.04 185.11 31469 +1956 15 2.84 -3.16 1.19 0 181.79 186.62 31575 +1956 16 3.65 -2.35 2 0 191.56 145.64 31686 +1956 17 -0.14 -6.14 -1.79 0 149.44 149.29 31800 +1956 18 -0.28 -6.28 -1.93 0.01 148.06 154.84 31917 +1956 19 -4.31 -10.31 -5.96 0 112.59 196.07 32038 +1956 20 0.88 -5.12 -0.77 0 159.9 154.26 32161 +1956 21 6.89 0.89 5.24 0 235.3 152.55 32289 +1956 22 7.25 1.25 5.6 0 240.65 154.01 32419 +1956 23 6.77 0.77 5.12 0.02 233.54 117.1 32552 +1956 24 2.04 -3.96 0.39 0.14 172.56 120.96 32688 +1956 25 4.96 -1.04 3.31 0.06 208.32 121.02 32827 +1956 26 6.93 0.93 5.28 0.07 235.89 121.38 32969 +1956 27 5.94 -0.06 4.29 0 221.67 164.6 33114 +1956 28 9.22 3.22 7.57 0 271.84 164.07 33261 +1956 29 7.2 1.2 5.55 0 239.91 168.17 33411 +1956 30 8.17 2.17 6.52 0 254.81 169.57 33564 +1956 31 9.52 3.52 7.87 0 276.88 170.67 33718 +1956 32 -5.4 -11.4 -7.05 0 104.37 182.03 33875 +1956 33 -5.4 -11.4 -7.05 0.43 104.37 178.52 34035 +1956 34 -5.4 -11.4 -7.05 0.19 104.37 180.55 34196 +1956 35 -5.4 -11.4 -7.05 0.07 104.37 182.2 34360 +1956 36 -5.4 -11.4 -7.05 0 104.37 231.85 34526 +1956 37 -5.4 -11.4 -7.05 0 104.37 234.13 34694 +1956 38 -5.4 -11.4 -7.05 0 104.37 236.73 34863 +1956 39 -5.4 -11.4 -7.05 0.38 104.37 190.33 35035 +1956 40 -5.4 -11.4 -7.05 0 104.37 242.7 35208 +1956 41 -5.4 -11.4 -7.05 0.07 104.37 194.12 35383 +1956 42 -5.4 -11.4 -7.05 0 104.37 247.77 35560 +1956 43 -5.4 -11.4 -7.05 0 104.37 250.33 35738 +1956 44 -5.4 -11.4 -7.05 0.05 104.37 199.65 35918 +1956 45 -5.4 -11.4 -7.05 0 104.37 255.36 36099 +1956 46 -5.4 -11.4 -7.05 0 104.37 257.91 36282 +1956 47 -5.4 -11.4 -7.05 0.02 104.37 205.32 36466 +1956 48 -5.4 -11.4 -7.05 0 104.37 263.3 36652 +1956 49 -5.4 -11.4 -7.05 0.15 104.37 209.59 36838 +1956 50 -5.4 -11.4 -7.05 0 104.37 268.86 37026 +1956 51 -5.4 -11.4 -7.05 0 104.37 271.69 37215 +1956 52 -5.4 -11.4 -7.05 0.32 104.37 216.3 37405 +1956 53 -5.4 -11.4 -7.05 0.18 104.37 218.83 37596 +1956 54 -5.4 -11.4 -7.05 0 104.37 281.1 37788 +1956 55 -5.4 -11.4 -7.05 0 104.37 283.96 37981 +1956 56 -5.4 -11.4 -7.05 0.49 104.37 225.93 38175 +1956 57 -5.4 -11.4 -7.05 0.66 104.37 229.59 38370 +1956 58 -5.4 -11.4 -7.05 0.76 104.37 233.52 38565 +1956 59 -5.4 -11.4 -7.05 0 104.37 299.38 38761 +1956 60 3.97 -2.03 2.32 0 195.54 295.6 38958 +1956 61 4.74 -1.26 3.09 0 205.42 297.15 39156 +1956 62 6.46 0.46 4.81 0 229.04 297.38 39355 +1956 63 5.16 -0.84 3.51 0 210.98 300.97 39553 +1956 64 4.07 -1.93 2.42 0.03 196.8 238.19 39753 +1956 65 0.95 -5.05 -0.7 0.83 160.64 242.02 39953 +1956 66 -1.76 -7.76 -3.41 0 134.05 313.96 40154 +1956 67 4.1 -1.9 2.45 0.07 197.18 243.52 40355 +1956 68 4.99 -1.01 3.34 0.02 208.72 244.35 40556 +1956 69 0.99 -5.01 -0.66 0 161.07 319.02 40758 +1956 70 2.27 -3.73 0.62 0 175.17 320.46 40960 +1956 71 2.98 -3.02 1.33 0 183.44 322.32 41163 +1956 72 2.25 -3.75 0.6 0 174.94 325.42 41366 +1956 73 4.96 -1.04 3.31 0 208.32 324.9 41569 +1956 74 6.28 0.28 4.63 0 226.47 325.45 41772 +1956 75 8.59 2.59 6.94 0 261.51 324.34 41976 +1956 76 10.92 4.92 9.27 0 301.47 322.42 42179 +1956 77 8.93 2.93 7.28 0.25 267.04 253.13 42383 +1956 78 9.64 3.64 7.99 0.13 278.91 222.54 42587 +1956 79 6.73 0.73 5.08 0.04 232.96 227.48 42791 +1956 80 5.71 -0.29 4.06 0 218.47 307.06 42996 +1956 81 3.62 -2.38 1.97 0.31 191.19 233.93 43200 +1956 82 4.34 -1.66 2.69 0 200.23 313.86 43404 +1956 83 6.57 0.57 4.92 0 230.63 313.83 43608 +1956 84 6.47 0.47 4.82 0 229.19 316.51 43812 +1956 85 2.11 -3.89 0.46 0.08 173.35 242.79 44016 +1956 86 0.16 -5.84 -1.49 0 152.46 327.89 44220 +1956 87 4.83 -1.17 3.18 0 206.6 325.96 44424 +1956 88 3.28 -2.72 1.63 0.31 187.04 247.51 44627 +1956 89 2.58 -3.42 0.93 0.08 178.74 249.78 44831 +1956 90 5.37 -0.63 3.72 0 213.82 332.43 45034 +1956 91 14.32 8.32 12.67 0.03 369.11 240.3 45237 +1956 92 12.53 6.53 10.88 0 332.04 326.15 45439 +1956 93 14.89 8.89 13.24 0.27 381.63 242.67 45642 +1956 94 16.1 10.1 14.45 0.01 409.42 242.2 45843 +1956 95 16.62 10.62 14.97 0.41 421.88 242.84 46045 +1956 96 16.48 10.48 14.83 0.21 418.5 244.63 46246 +1956 97 18.04 12.04 16.39 0.27 457.57 243.15 46446 +1956 98 16.12 10.12 14.47 0 409.89 330.96 46647 +1956 99 15.61 9.61 13.96 0 397.97 334.13 46846 +1956 100 11.57 5.57 9.92 0 313.51 344.45 47045 +1956 101 15.2 9.2 13.55 0 388.59 338.89 47243 +1956 102 14.8 8.8 13.15 0.35 379.63 256.26 47441 +1956 103 12.33 6.33 10.68 0.18 328.11 261.51 47638 +1956 104 11.15 5.15 9.5 0.26 305.68 264.55 47834 +1956 105 10.79 4.79 9.14 1.5 299.11 266.39 48030 +1956 106 9.56 3.56 7.91 0.67 277.55 269.22 48225 +1956 107 8.01 2.01 6.36 1.13 252.3 272.34 48419 +1956 108 9.19 3.19 7.54 0 271.34 363.02 48612 +1956 109 8.28 2.28 6.63 0.11 256.55 274.58 48804 +1956 110 6.61 0.61 4.96 0.01 231.21 277.51 48995 +1956 111 6.47 0.47 4.82 0 229.19 371.79 49185 +1956 112 4.84 -1.16 3.19 0 206.73 375.5 49374 +1956 113 3.98 -2.02 2.33 0.12 195.67 283.46 49561 +1956 114 7.15 1.15 5.5 0 239.16 375.27 49748 +1956 115 12.13 6.13 10.48 0 324.21 368.14 49933 +1956 116 11.9 5.9 10.25 0 319.78 369.83 50117 +1956 117 13.65 7.65 12 0 354.84 367.47 50300 +1956 118 13.92 7.92 12.27 0 360.53 368.19 50481 +1956 119 15.26 9.26 13.61 0.14 389.95 274.67 50661 +1956 120 17.5 11.5 15.85 0 443.71 361.52 50840 +1956 121 23.29 17.29 21.64 1 612.72 257.54 51016 +1956 122 21.6 15.6 19.95 1.76 558.54 263.11 51191 +1956 123 20.95 14.95 19.3 0.65 538.81 265.55 51365 +1956 124 18.11 12.11 16.46 0.03 459.4 273.1 51536 +1956 125 18.3 12.3 16.65 0.44 464.38 273.4 51706 +1956 126 13.79 7.79 12.14 0 357.78 377.28 51874 +1956 127 16.43 10.43 14.78 0 417.29 371.66 52039 +1956 128 17.62 11.62 15.97 0 446.76 369.36 52203 +1956 129 17.64 11.64 15.99 0 447.27 370.14 52365 +1956 130 12.34 6.34 10.69 0 328.3 384.02 52524 +1956 131 16.07 10.07 14.42 0 408.71 376.03 52681 +1956 132 14.14 8.14 12.49 0.25 365.23 286.24 52836 +1956 133 16.02 10.02 14.37 0.04 407.53 283.27 52989 +1956 134 16.15 10.15 14.5 0 410.61 378.06 53138 +1956 135 19.51 13.51 17.86 0 497.2 368.89 53286 +1956 136 17.2 11.2 15.55 0.01 436.16 282.38 53430 +1956 137 16.31 10.31 14.66 0.05 414.42 284.75 53572 +1956 138 17.59 11.59 15.94 0 446 376.7 53711 +1956 139 19.62 13.62 17.97 0 500.28 371.12 53848 +1956 140 19.94 13.94 18.29 0.09 509.33 277.91 53981 +1956 141 16.43 10.43 14.78 0.38 417.29 286.17 54111 +1956 142 17.25 11.25 15.6 0 437.41 379.78 54238 +1956 143 18.18 12.18 16.53 0 461.23 377.58 54362 +1956 144 19.16 13.16 17.51 0.14 487.51 281.25 54483 +1956 145 19.19 13.19 17.54 0.48 488.33 281.53 54600 +1956 146 19.26 13.26 17.61 0 490.26 375.52 54714 +1956 147 15.31 9.31 13.66 0.07 391.09 290.53 54824 +1956 148 15.41 9.41 13.76 1.58 393.37 290.63 54931 +1956 149 18.48 12.48 16.83 0.35 469.14 284.36 55034 +1956 150 15.15 9.15 13.5 0.06 387.46 291.62 55134 +1956 151 12.27 6.27 10.62 0 326.93 395.94 55229 +1956 152 10.53 4.53 8.88 0.04 294.44 299.7 55321 +1956 153 13.59 7.59 11.94 0.57 353.59 295.03 55409 +1956 154 15.69 9.69 14.04 0.34 399.82 291.38 55492 +1956 155 18.1 12.1 16.45 0 459.14 381.89 55572 +1956 156 19.07 13.07 17.42 0 485.04 379.19 55648 +1956 157 18.43 12.43 16.78 0.23 467.81 286.03 55719 +1956 158 16.17 10.17 14.52 1.5 411.08 291.07 55786 +1956 159 18.62 12.62 16.97 0.02 472.87 285.9 55849 +1956 160 17.26 11.26 15.61 1.42 437.66 289.1 55908 +1956 161 17.94 11.94 16.29 0.09 454.98 287.65 55962 +1956 162 17.5 11.5 15.85 0.08 443.71 288.68 56011 +1956 163 17.39 11.39 15.74 0 440.93 385.44 56056 +1956 164 19.88 13.88 18.23 0 507.62 377.68 56097 +1956 165 23.41 17.41 21.76 0.03 616.73 273.48 56133 +1956 166 26.7 20.7 25.05 0.1 735.72 262.44 56165 +1956 167 25.3 19.3 23.65 1.91 682.91 267.37 56192 +1956 168 24.56 18.56 22.91 0.63 656.32 269.9 56214 +1956 169 23.64 17.64 21.99 0.84 624.48 272.85 56231 +1956 170 22.99 16.99 21.34 1.11 602.79 274.84 56244 +1956 171 23.32 17.32 21.67 0.49 613.72 273.88 56252 +1956 172 21.77 15.77 20.12 1.05 563.79 278.42 56256 +1956 173 18.41 12.41 16.76 0.05 467.28 287 56255 +1956 174 16.17 10.17 14.52 0.43 411.08 291.81 56249 +1956 175 17.94 11.94 16.29 0.98 454.98 287.99 56238 +1956 176 16.53 10.53 14.88 0.06 419.7 291.02 56223 +1956 177 20.78 14.78 19.13 0.15 533.75 280.93 56203 +1956 178 20.09 14.09 18.44 1.11 513.62 282.74 56179 +1956 179 20 14 18.35 0.54 511.04 282.89 56150 +1956 180 20.53 14.53 18.88 0.02 526.38 281.44 56116 +1956 181 21.23 15.23 19.58 1.06 547.23 279.52 56078 +1956 182 24.11 18.11 22.46 0.12 640.58 270.91 56035 +1956 183 21.21 15.21 19.56 0 546.63 372.44 55987 +1956 184 25.14 19.14 23.49 0.33 677.09 267.28 55935 +1956 185 24.3 18.3 22.65 0.02 647.19 269.99 55879 +1956 186 22.1 16.1 20.45 0.94 574.13 276.48 55818 +1956 187 25.8 19.8 24.15 0.05 701.39 264.64 55753 +1956 188 23.73 17.73 22.08 0 627.54 361.71 55684 +1956 189 23.22 17.22 21.57 0 610.39 363.63 55611 +1956 190 26.11 20.11 24.46 0 713.06 350.6 55533 +1956 191 27.1 21.1 25.45 0.04 751.43 259.15 55451 +1956 192 21.46 15.46 19.81 0 554.23 369.48 55366 +1956 193 24.53 18.53 22.88 0 655.26 356.96 55276 +1956 194 22.44 16.44 20.79 0 584.94 365.3 55182 +1956 195 19.76 13.76 18.11 0 504.22 374.63 55085 +1956 196 19.9 13.9 18.25 0.02 508.19 280.32 54984 +1956 197 22.54 16.54 20.89 0 588.15 363.8 54879 +1956 198 24.61 18.61 22.96 0 658.09 354.89 54770 +1956 199 21.95 15.95 20.3 0.97 569.41 273.96 54658 +1956 200 22.89 16.89 21.24 0.54 599.51 270.95 54542 +1956 201 26.55 20.55 24.9 0.03 729.9 258.64 54423 +1956 202 26.83 20.83 25.18 0 740.8 342.95 54301 +1956 203 25.76 19.76 24.11 1.4 699.9 260.66 54176 +1956 204 22.27 16.27 20.62 0 579.51 361.65 54047 +1956 205 22.38 16.38 20.73 0 583.02 360.73 53915 +1956 206 23.68 17.68 22.03 0.29 625.84 266.28 53780 +1956 207 22.8 16.8 21.15 1.32 596.57 268.43 53643 +1956 208 18.91 12.91 17.26 0 480.69 370.84 53502 +1956 209 19.07 13.07 17.42 0 485.04 369.68 53359 +1956 210 21.27 15.27 19.62 0 548.44 361.7 53213 +1956 211 19.19 13.19 17.54 0 488.33 367.9 53064 +1956 212 21.63 15.63 19.98 0 559.46 358.85 52913 +1956 213 20.49 14.49 18.84 0 525.2 362.09 52760 +1956 214 20.57 14.57 18.92 0 527.55 361.07 52604 +1956 215 21.67 15.67 20.02 0 560.7 356.54 52445 +1956 216 28.35 22.35 26.7 0 802.36 326.44 52285 +1956 217 27.01 21.01 25.36 0 747.87 332.32 52122 +1956 218 26.64 20.64 24.99 0.67 733.39 249.99 51958 +1956 219 24.01 18.01 22.36 0.37 637.13 257.9 51791 +1956 220 22.08 16.08 20.43 0 573.49 350.41 51622 +1956 221 18.74 12.74 17.09 1.4 476.09 270.4 51451 +1956 222 17.26 11.26 15.61 1.75 437.66 272.81 51279 +1956 223 15.98 9.98 14.33 0.02 406.59 274.49 51105 +1956 224 17.69 11.69 16.04 1.3 448.55 270.23 50929 +1956 225 20.21 14.21 18.56 0.18 517.07 263.64 50751 +1956 226 19.83 13.83 18.18 0.01 506.2 263.7 50572 +1956 227 19.24 13.24 17.59 0 489.71 352.15 50392 +1956 228 17.65 11.65 16 0.45 447.52 266.68 50210 +1956 229 18.74 12.74 17.09 0.06 476.09 263.39 50026 +1956 230 21.11 15.11 19.46 0 543.61 342.42 49842 +1956 231 23.72 17.72 22.07 0.01 627.2 248.63 49656 +1956 232 26.69 20.69 25.04 0 735.33 317.66 49469 +1956 233 24.68 18.68 23.03 0.12 660.57 243.75 49280 +1956 234 24.29 18.29 22.64 0 646.84 325.21 49091 +1956 235 27.22 21.22 25.57 0.52 756.2 233.38 48900 +1956 236 21.46 15.46 19.81 0.31 554.23 249.58 48709 +1956 237 17.15 11.15 15.5 0.09 434.92 258.02 48516 +1956 238 22.26 16.26 20.61 0.26 579.19 245.07 48323 +1956 239 24.45 18.45 22.8 0.02 652.44 237.86 48128 +1956 240 21.37 15.37 19.72 0.3 551.49 244.95 47933 +1956 241 20.45 14.45 18.8 0.15 524.04 245.9 47737 +1956 242 20.32 14.32 18.67 0.72 520.25 244.91 47541 +1956 243 22 16 20.35 0.12 570.98 239.46 47343 +1956 244 15.93 9.93 14.28 0 405.42 334.83 47145 +1956 245 11.62 5.62 9.97 0.08 314.45 256.48 46947 +1956 246 13.41 7.41 11.76 0 349.85 336.5 46747 +1956 247 12.34 6.34 10.69 0 328.3 336.69 46547 +1956 248 10.53 4.53 8.88 0 294.44 337.92 46347 +1956 249 11.69 5.69 10.04 0 315.78 333.76 46146 +1956 250 13.66 7.66 12.01 0 355.05 327.99 45945 +1956 251 19.01 13.01 17.36 0 483.41 313.14 45743 +1956 252 19.84 13.84 18.19 0 506.48 308.67 45541 +1956 253 21.52 15.52 19.87 0.04 556.07 226.15 45339 +1956 254 21.92 15.92 20.27 0 568.47 298.19 45136 +1956 255 22.38 16.38 20.73 0 583.02 294.52 44933 +1956 256 24.92 18.92 23.27 0 669.14 283.46 44730 +1956 257 19.09 13.09 17.44 0 485.59 299.97 44527 +1956 258 20.98 14.98 19.33 0.13 539.7 219.25 44323 +1956 259 17.48 11.48 15.83 0 443.2 299.34 44119 +1956 260 21.99 15.99 20.34 0 570.66 284.59 43915 +1956 261 20.89 14.89 19.24 0 537.02 285.53 43711 +1956 262 18.79 12.79 17.14 0 477.44 288.95 43507 +1956 263 21.55 15.55 19.9 0 557 278.91 43303 +1956 264 27.33 21.33 25.68 0 760.59 256.26 43099 +1956 265 23.99 17.99 22.34 0 636.44 266.46 42894 +1956 266 25.02 19.02 23.37 0 672.74 260.58 42690 +1956 267 23.81 17.81 22.16 0.91 630.27 196.64 42486 +1956 268 21.27 15.27 19.62 0 548.44 267.52 42282 +1956 269 19.84 13.84 18.19 0 506.48 268.98 42078 +1956 270 19.55 13.55 17.9 0 498.32 267.16 41875 +1956 271 18.12 12.12 16.47 0 459.66 268.06 41671 +1956 272 23.82 17.82 22.17 0 630.61 249.87 41468 +1956 273 19.46 13.46 17.81 0 495.8 259.72 41265 +1956 274 12.15 6.15 10.5 0.88 324.6 203.79 41062 +1956 275 11.83 5.83 10.18 0.86 318.44 202.07 40860 +1956 276 12.32 6.32 10.67 0 327.91 265.93 40658 +1956 277 13.22 7.22 11.57 0.24 345.94 196.34 40456 +1956 278 13.18 7.18 11.53 0.33 345.12 194.23 40255 +1956 279 13.69 7.69 12.04 0 355.68 255.31 40054 +1956 280 12.98 6.98 11.33 0.03 341.05 190.37 39854 +1956 281 11.66 5.66 10.01 0.33 315.21 189.83 39654 +1956 282 14.03 8.03 12.38 0 362.88 246.65 39455 +1956 283 14.99 8.99 13.34 0 383.87 242.2 39256 +1956 284 15.8 9.8 14.15 0 402.38 237.76 39058 +1956 285 11.52 5.52 9.87 0 312.57 242.01 38861 +1956 286 13.23 7.23 11.58 1.03 346.14 177.55 38664 +1956 287 12.57 6.57 10.92 0 332.83 234.79 38468 +1956 288 10.64 4.64 8.99 0.02 296.41 176 38273 +1956 289 11.93 5.93 10.28 0.23 320.35 172.71 38079 +1956 290 10.33 4.33 8.68 0 290.89 229.52 37885 +1956 291 14.62 8.62 12.97 0 375.66 220.72 37693 +1956 292 20.23 14.23 18.58 0 517.65 207.48 37501 +1956 293 18.74 12.74 17.09 0 476.09 208.01 37311 +1956 294 11.85 5.85 10.2 0 318.82 216.53 37121 +1956 295 8.76 2.76 7.11 0 264.26 217.39 36933 +1956 296 9.67 3.67 8.02 0 279.43 213.77 36745 +1956 297 12.6 6.6 10.95 0 333.43 207.41 36560 +1956 298 9.06 3.06 7.41 0 269.18 209.07 36375 +1956 299 12.84 6.84 11.19 0 338.22 201.74 36191 +1956 300 13.17 7.17 11.52 0 344.91 198.65 36009 +1956 301 11.29 5.29 9.64 0 308.27 198.56 35829 +1956 302 12.3 6.3 10.65 1.94 327.52 146.04 35650 +1956 303 11.27 5.27 9.62 0 307.9 193.41 35472 +1956 304 13.24 7.24 11.59 0.11 346.35 141.39 35296 +1956 305 5.4 -0.6 3.75 0.03 214.22 145.44 35122 +1956 306 9.22 3.22 7.57 0.01 271.84 141.15 34950 +1956 307 4.87 -1.13 3.22 0.04 207.13 142.12 34779 +1956 308 1.25 -4.75 -0.4 0.47 163.85 141.96 34610 +1956 309 3.94 -2.06 2.29 0.02 195.16 138.89 34444 +1956 310 4.92 -1.08 3.27 0 207.79 182 34279 +1956 311 4.03 -1.97 2.38 0 196.29 180.43 34116 +1956 312 5.8 -0.2 4.15 0 219.72 176.47 33956 +1956 313 5.75 -0.25 4.1 0.08 219.02 130.78 33797 +1956 314 4.19 -1.81 2.54 0.05 198.32 130.14 33641 +1956 315 1.17 -4.83 -0.48 0.74 162.99 129.6 33488 +1956 316 -0.92 -6.92 -2.57 0 141.85 171.65 33337 +1956 317 0.34 -5.66 -1.31 0 154.29 168.79 33188 +1956 318 3.4 -2.6 1.75 0.01 188.49 123.51 33042 +1956 319 5.57 -0.43 3.92 1 216.54 121.14 32899 +1956 320 3.72 -2.28 2.07 0.34 192.42 120.65 32758 +1956 321 1.72 -4.28 0.07 0 168.99 159.91 32620 +1956 322 3.97 -2.03 2.32 0.01 195.54 117.56 32486 +1956 323 2.73 -3.27 1.08 0 180.49 155.86 32354 +1956 324 2.8 -3.2 1.15 0.24 181.32 115.31 32225 +1956 325 7.26 1.26 5.61 0 240.81 149.08 32100 +1956 326 10.55 4.55 8.9 0.39 294.79 108.66 31977 +1956 327 7.49 1.49 5.84 0.43 244.28 109.21 31858 +1956 328 2.36 -3.64 0.71 0.86 176.2 110.2 31743 +1956 329 3.79 -2.21 2.14 0.07 193.29 108.46 31631 +1956 330 4.98 -1.02 3.33 0.65 208.58 106.83 31522 +1956 331 3.81 -2.19 2.16 0.65 193.54 106.37 31417 +1956 332 6.49 0.49 4.84 0.55 229.48 103.87 31316 +1956 333 11.95 5.95 10.3 0 320.74 132.96 31218 +1956 334 6.28 0.28 4.63 0 226.47 136.45 31125 +1956 335 6 0 4.35 0 222.51 135.47 31035 +1956 336 3.71 -2.29 2.06 0.35 192.3 101.84 30949 +1956 337 6.6 0.6 4.95 0.16 231.07 99.26 30867 +1956 338 3.44 -2.56 1.79 0 188.98 133.32 30790 +1956 339 -1.93 -7.93 -3.58 0 132.51 134.97 30716 +1956 340 3.63 -2.37 1.98 0 191.31 131.69 30647 +1956 341 4.52 -1.48 2.87 0 202.55 130.27 30582 +1956 342 5.03 -0.97 3.38 0 209.25 129.21 30521 +1956 343 2.87 -3.13 1.22 0 182.14 129.57 30465 +1956 344 -1.59 -7.59 -3.24 0 135.6 130.41 30413 +1956 345 -1.33 -7.33 -2.98 0 137.99 129.87 30366 +1956 346 0.99 -5.01 -0.66 0 161.07 128.35 30323 +1956 347 1.06 -4.94 -0.59 0 161.81 127.72 30284 +1956 348 4.87 -1.13 3.22 0 207.13 125.43 30251 +1956 349 7.36 1.36 5.71 0 242.31 123.49 30221 +1956 350 3.32 -2.68 1.67 0 187.52 125.56 30197 +1956 351 6.22 0.22 4.57 0.03 225.61 92.76 30177 +1956 352 7 1 5.35 0 236.93 123.09 30162 +1956 353 5.28 -0.72 3.63 0 212.6 124.1 30151 +1956 354 8.87 2.87 7.22 0 266.06 121.69 30145 +1956 355 12.66 6.66 11.01 0 334.62 118.53 30144 +1956 356 10.09 4.09 8.44 0 286.67 120.78 30147 +1956 357 7.38 1.38 5.73 0.13 242.61 92.12 30156 +1956 358 6.1 0.1 4.45 0.37 223.91 92.81 30169 +1956 359 1.23 -4.77 -0.42 0.15 163.64 94.84 30186 +1956 360 0.73 -5.27 -0.92 0.06 158.33 95.28 30208 +1956 361 -0.96 -6.96 -2.61 0 141.47 128.08 30235 +1956 362 -3.32 -9.32 -4.97 0.94 120.54 143.62 30267 +1956 363 -8.27 -14.27 -9.92 0.02 85.17 145.12 30303 +1956 364 -5.93 -11.93 -7.58 0 100.56 177.71 30343 +1956 365 -4.98 -10.98 -6.63 0.28 107.47 145.96 30388 +1957 1 -8.6 -14.6 -10.25 0 83.17 180.61 30438 +1957 2 -6.19 -12.19 -7.84 0 98.74 180.66 30492 +1957 3 -6.74 -12.74 -8.39 0.02 94.98 148.1 30551 +1957 4 -5.01 -11.01 -6.66 0 107.25 182.08 30614 +1957 5 -1.85 -7.85 -3.5 0 133.23 181.57 30681 +1957 6 0.75 -5.25 -0.9 0.06 158.54 147.58 30752 +1957 7 0.85 -5.15 -0.8 0 159.59 181.71 30828 +1957 8 0.83 -5.17 -0.82 0 159.38 182.99 30907 +1957 9 -0.94 -6.94 -2.59 0 141.66 184.9 30991 +1957 10 1 -5 -0.65 0.19 161.18 150.3 31079 +1957 11 -0.37 -6.37 -2.02 0 147.17 186.58 31171 +1957 12 1.5 -4.5 -0.15 0 166.57 186.4 31266 +1957 13 6.81 0.81 5.16 0 234.13 183.85 31366 +1957 14 2.36 -3.64 0.71 0 176.2 187.6 31469 +1957 15 2.63 -3.37 0.98 0 179.33 188.42 31575 +1957 16 1.99 -4.01 0.34 0.04 172 153.01 31686 +1957 17 2.85 -3.15 1.2 0 181.9 190.36 31800 +1957 18 0.04 -5.96 -1.61 0.07 151.25 155.76 31917 +1957 19 1.54 -4.46 -0.11 0 167 194.39 32038 +1957 20 0.02 -5.98 -1.63 0.13 151.05 157.91 32161 +1957 21 2.26 -3.74 0.61 0.02 175.06 158.12 32289 +1957 22 2.14 -3.86 0.49 0.01 173.69 159.05 32419 +1957 23 2.61 -3.39 0.96 0 179.09 158.89 32552 +1957 24 2.39 -3.61 0.74 1.54 176.55 120.82 32688 +1957 25 -0.71 -6.71 -2.36 0 143.86 164.6 32827 +1957 26 3.15 -2.85 1.5 0 185.47 164.46 32969 +1957 27 0.64 -5.36 -1.01 0 157.39 167.92 33114 +1957 28 0.74 -5.26 -0.91 0 158.43 170.09 33261 +1957 29 -1.19 -7.19 -2.84 0.08 139.3 169.83 33411 +1957 30 2.72 -3.28 1.07 0 180.38 173.61 33564 +1957 31 -1.15 -7.15 -2.8 0 139.68 178.11 33718 +1957 32 10.48 4.48 8.83 0 293.55 171.78 33875 +1957 33 10.31 4.31 8.66 0 290.53 174.54 34035 +1957 34 14.22 8.22 12.57 0.85 366.95 129.08 34196 +1957 35 12.22 6.22 10.57 0 325.96 176.67 34360 +1957 36 11.93 5.93 10.28 0.22 320.35 134.59 34526 +1957 37 6.47 0.47 4.82 0 229.19 187.29 34694 +1957 38 8.8 2.8 7.15 0.03 264.91 140.91 34863 +1957 39 5.22 -0.78 3.57 0 211.79 193.63 35035 +1957 40 2.62 -3.38 0.97 0 179.21 198.15 35208 +1957 41 2.62 -3.38 0.97 0 179.21 200.78 35383 +1957 42 3.91 -2.09 2.26 0 194.79 202.43 35560 +1957 43 5.13 -0.87 3.48 0 210.58 204.18 35738 +1957 44 6.89 0.89 5.24 0 235.3 205.22 35918 +1957 45 8.92 2.92 7.27 0.03 266.88 154.36 36099 +1957 46 7.15 1.15 5.5 2.44 239.16 157.69 36282 +1957 47 5.51 -0.49 3.86 0.69 215.72 160.91 36466 +1957 48 6.86 0.86 5.21 0 234.86 216.12 36652 +1957 49 7.52 1.52 5.87 0 244.74 218.24 36838 +1957 50 8.55 2.55 6.9 0.05 260.86 164.86 37026 +1957 51 9.33 3.33 7.68 0 273.67 221.88 37215 +1957 52 9.05 3.05 7.4 0 269.02 224.99 37405 +1957 53 7.94 1.94 6.29 0 251.21 229.15 37596 +1957 54 8.6 2.6 6.95 0.15 261.67 173.37 37788 +1957 55 8.14 2.14 6.49 0.11 254.34 175.98 37981 +1957 56 9.03 3.03 7.38 0.45 268.69 177.22 38175 +1957 57 2.79 -3.21 1.14 0.77 181.2 183.93 38370 +1957 58 4.08 -1.92 2.43 0.88 196.93 185.34 38565 +1957 59 4.51 -1.49 2.86 0.08 202.42 187.09 38761 +1957 60 6.49 0.49 4.84 0 229.48 250.44 38958 +1957 61 9.36 3.36 7.71 0.07 274.18 187.57 39156 +1957 62 5.24 -0.76 3.59 0.01 212.06 193.07 39355 +1957 63 3.66 -2.34 2.01 0.21 191.68 196.43 39553 +1957 64 1.72 -4.28 0.07 0 168.99 266.46 39753 +1957 65 0.76 -5.24 -0.89 1.04 158.64 202.59 39953 +1957 66 0.57 -5.43 -1.08 0 156.66 273.04 40154 +1957 67 5.98 -0.02 4.33 0 222.23 271.17 40355 +1957 68 8.22 2.22 6.57 0 255.6 271.48 40556 +1957 69 8.71 2.71 7.06 0 263.45 273.48 40758 +1957 70 16.26 10.26 14.61 0 413.22 263.94 40960 +1957 71 15.43 9.43 13.78 0 393.83 268.41 41163 +1957 72 14.69 8.69 13.04 0 377.2 272.57 41366 +1957 73 15.16 9.16 13.51 0 387.69 274.26 41569 +1957 74 15.37 9.37 13.72 0 392.46 276.5 41772 +1957 75 14.23 8.23 12.58 0 367.17 281.36 41976 +1957 76 13.84 7.84 12.19 0 358.84 284.65 42179 +1957 77 14.55 8.55 12.9 0 374.12 285.85 42383 +1957 78 9.27 3.27 7.62 0 272.67 297.25 42587 +1957 79 9.84 3.84 8.19 0.16 282.34 224.36 42791 +1957 80 10.54 4.54 8.89 0 294.62 300.61 42996 +1957 81 14.01 8.01 12.36 0 362.45 297.15 43200 +1957 82 14.92 8.92 13.27 0 382.3 297.93 43404 +1957 83 11.11 5.11 9.46 0 304.95 307.37 43608 +1957 84 11.93 5.93 10.28 0 320.35 308.5 43812 +1957 85 10.28 4.28 8.63 0 290 313.7 44016 +1957 86 11.8 5.8 10.15 0 317.87 313.58 44220 +1957 87 9.06 3.06 7.41 0 269.18 320.49 44424 +1957 88 10.65 4.65 9 0 296.59 320.37 44627 +1957 89 10.67 4.67 9.02 0 296.95 322.61 44831 +1957 90 11.32 5.32 9.67 0 308.83 323.87 45034 +1957 91 16.15 10.15 14.5 0 410.61 316.39 45237 +1957 92 15.8 9.8 14.15 0 402.38 319.37 45439 +1957 93 15.78 9.78 14.13 0.21 401.91 241.18 45642 +1957 94 14.17 8.17 12.52 0 365.87 327.22 45843 +1957 95 14.23 8.23 12.58 0.08 367.17 246.9 46045 +1957 96 15.24 9.24 13.59 0.25 389.5 246.81 46246 +1957 97 11.21 5.21 9.56 1.08 306.79 254.39 46446 +1957 98 6.99 0.99 5.34 0.57 236.78 260.82 46647 +1957 99 8.27 2.27 6.62 0.14 256.39 260.97 46846 +1957 100 6.3 0.3 4.65 0 226.75 352.71 47045 +1957 101 8.21 2.21 6.56 0 255.44 351.98 47243 +1957 102 10.37 4.37 8.72 0 291.59 350.43 47441 +1957 103 11.96 5.96 10.31 0 320.93 349.39 47638 +1957 104 13.96 7.96 12.31 0.01 361.38 260.36 47834 +1957 105 12.99 6.99 11.34 0.02 341.25 263.23 48030 +1957 106 13.38 7.38 11.73 0 349.23 351.8 48225 +1957 107 13.95 7.95 12.3 0 361.17 352.25 48419 +1957 108 16.67 10.67 15.02 0.03 423.1 260.63 48612 +1957 109 14.79 8.79 13.14 0.64 379.41 265.26 48804 +1957 110 16.83 10.83 15.18 0.99 427.01 262.54 48995 +1957 111 11.73 5.73 10.08 0.77 316.53 272.34 49185 +1957 112 10.01 4.01 8.36 0.12 285.28 275.86 49374 +1957 113 8.87 2.87 7.22 0 266.06 371.09 49561 +1957 114 11.48 5.48 9.83 0.05 311.82 275.98 49748 +1957 115 12.17 6.17 10.52 0.34 324.99 276.04 49933 +1957 116 14.47 8.47 12.82 0.08 372.37 273.23 50117 +1957 117 15.82 9.82 14.17 0 402.84 362.35 50300 +1957 118 16.03 10.03 14.38 0 407.77 363.12 50481 +1957 119 14.47 8.47 12.82 0.05 372.37 276.09 50661 +1957 120 13.36 7.36 11.71 0 348.81 371.8 50840 +1957 121 11.83 5.83 10.18 0 318.44 376.14 51016 +1957 122 12.87 6.87 11.22 0 338.83 375.19 51191 +1957 123 14.5 8.5 12.85 2.42 373.03 279.43 51365 +1957 124 14.41 8.41 12.76 0.34 371.06 280.39 51536 +1957 125 13.66 7.66 12.01 0.84 355.05 282.43 51706 +1957 126 11.28 5.28 9.63 0.29 308.09 286.94 51874 +1957 127 15.78 9.78 14.13 0.24 401.91 280.02 52039 +1957 128 16.91 10.91 15.26 0 428.97 371.35 52203 +1957 129 15.77 9.77 14.12 0 401.68 375.23 52365 +1957 130 14.39 8.39 12.74 0.23 370.63 284.58 52524 +1957 131 12.52 6.52 10.87 0.72 331.84 288.34 52681 +1957 132 15.71 9.71 14.06 0.1 400.28 283.35 52836 +1957 133 14.94 8.94 13.29 0.04 382.75 285.33 52989 +1957 134 15.31 9.31 13.66 0 391.09 380.23 53138 +1957 135 16.98 10.98 15.33 0 430.7 376.5 53286 +1957 136 16.76 10.76 15.11 0 425.29 377.74 53430 +1957 137 14.77 8.77 13.12 0 378.97 383.63 53572 +1957 138 9.64 3.64 7.99 0 278.91 395.08 53711 +1957 139 13.72 7.72 12.07 0 356.31 387.44 53848 +1957 140 11.59 5.59 9.94 0.65 313.89 294.41 53981 +1957 141 10.26 4.26 8.61 0.16 289.65 296.7 54111 +1957 142 12.66 6.66 11.01 0.43 334.62 293.45 54238 +1957 143 14.69 8.69 13.04 0 377.2 387.11 54362 +1957 144 17.32 11.32 15.67 0.02 439.17 285.44 54483 +1957 145 17.56 11.56 15.91 0.66 445.23 285.27 54600 +1957 146 19.03 13.03 17.38 0.02 483.95 282.19 54714 +1957 147 17.29 11.29 15.64 0 438.42 382 54824 +1957 148 16.12 10.12 14.47 0 409.89 385.63 54931 +1957 149 15.72 9.72 14.07 0.28 400.51 290.26 55034 +1957 150 17.19 11.19 15.54 0 435.91 383.32 55134 +1957 151 16.28 10.28 14.63 0.4 413.7 289.69 55229 +1957 152 23.55 17.55 21.9 0.05 621.44 271.36 55321 +1957 153 25.77 19.77 24.12 0 700.27 352.32 55409 +1957 154 22.38 16.38 20.73 0 583.02 367.02 55492 +1957 155 21.71 15.71 20.06 0 561.93 369.75 55572 +1957 156 23.4 17.4 21.75 0.14 616.4 272.6 55648 +1957 157 23.02 17.02 21.37 0 603.78 365.17 55719 +1957 158 22.12 16.12 20.47 0 574.76 368.86 55786 +1957 159 19.42 13.42 17.77 0 494.69 378.64 55849 +1957 160 19.87 13.87 18.22 0.15 507.33 283 55908 +1957 161 20.62 14.62 18.97 0.17 529.02 281.12 55962 +1957 162 22.35 16.35 20.7 0.4 582.06 276.38 56011 +1957 163 22.62 16.62 20.97 0.08 590.73 275.75 56056 +1957 164 19.65 13.65 18 0 501.12 378.45 56097 +1957 165 20.41 14.41 18.76 0 522.87 375.97 56133 +1957 166 19.92 13.92 18.27 0.05 508.76 283.29 56165 +1957 167 20.6 14.6 18.95 0.04 528.43 281.5 56192 +1957 168 24.38 18.38 22.73 0.01 649.98 270.49 56214 +1957 169 25.11 19.11 23.46 0 676 357.43 56231 +1957 170 25.4 19.4 23.75 0 686.58 356.12 56244 +1957 171 25.99 19.99 24.34 0.67 708.52 265.07 56252 +1957 172 21.32 15.32 19.67 0.17 549.96 279.67 56256 +1957 173 21.31 15.31 19.66 0.83 549.66 279.69 56255 +1957 174 23.33 17.33 21.68 0.02 614.06 273.77 56249 +1957 175 25.96 19.96 24.31 0.06 707.39 265.08 56238 +1957 176 29.36 23.36 27.71 0 845.61 335.81 56223 +1957 177 25.06 19.06 23.41 0 674.19 357.45 56203 +1957 178 23.49 17.49 21.84 0.65 619.42 273.17 56179 +1957 179 26.74 20.74 25.09 0.49 737.28 262.11 56150 +1957 180 23.72 17.72 22.07 0.09 627.2 272.29 56116 +1957 181 23.01 17.01 21.36 0.18 603.45 274.42 56078 +1957 182 21.04 15.04 19.39 2.4 541.5 279.92 56035 +1957 183 17.09 11.09 15.44 0.29 433.42 289.3 55987 +1957 184 19.3 13.3 17.65 1.39 491.36 284.13 55935 +1957 185 22.99 16.99 21.34 0.14 602.79 274.07 55879 +1957 186 20.89 14.89 19.24 1.3 537.02 279.82 55818 +1957 187 21.08 15.08 19.43 2.85 542.7 279.17 55753 +1957 188 23.58 17.58 21.93 1.2 622.45 271.75 55684 +1957 189 26.31 20.31 24.66 0.05 720.68 262.51 55611 +1957 190 27.73 21.73 26.08 0.79 776.75 256.94 55533 +1957 191 28.11 22.11 26.46 0 792.36 340.36 55451 +1957 192 24.15 18.15 22.5 0.3 641.97 269.14 55366 +1957 193 21.92 15.92 20.27 0.31 568.47 275.63 55276 +1957 194 24.11 18.11 22.46 1.36 640.58 268.91 55182 +1957 195 23.15 17.15 21.5 0.27 608.07 271.68 55085 +1957 196 22.71 16.71 21.06 0.8 593.64 272.69 54984 +1957 197 24.67 18.67 23.02 0.81 660.22 266.28 54879 +1957 198 24.14 18.14 22.49 0.6 641.62 267.68 54770 +1957 199 24.18 18.18 22.53 0.51 643.01 267.29 54658 +1957 200 22.97 16.97 21.32 0.91 602.13 270.72 54542 +1957 201 18.83 12.83 17.18 0.12 478.52 281.32 54423 +1957 202 18.99 12.99 17.34 0.63 482.86 280.52 54301 +1957 203 20.34 14.34 18.69 0.09 520.83 276.82 54176 +1957 204 25.24 19.24 23.59 0.02 680.72 262.06 54047 +1957 205 23.95 17.95 22.3 0 635.06 354.47 53915 +1957 206 29.79 23.79 28.14 0 864.61 325.4 53780 +1957 207 31.3 25.3 29.65 0.06 934.21 236.9 53643 +1957 208 27.59 21.59 25.94 0.01 771.06 251.98 53502 +1957 209 23.82 17.82 22.17 0 630.61 352.55 53359 +1957 210 25.52 19.52 23.87 0.17 690.99 258.48 53213 +1957 211 22.48 16.48 20.83 0.25 586.22 267.36 53064 +1957 212 23.14 17.14 21.49 0 607.74 353.15 52913 +1957 213 20.04 14.04 18.39 0.38 512.18 272.69 52760 +1957 214 21.7 15.7 20.05 0 561.62 357.1 52604 +1957 215 23.97 17.97 22.32 0 635.75 347.69 52445 +1957 216 21.26 15.26 19.61 0.22 548.14 267.75 52285 +1957 217 20.02 14.02 18.37 0 511.61 360.32 52122 +1957 218 20.31 14.31 18.66 0.01 519.96 268.91 51958 +1957 219 22.89 16.89 21.24 0 599.51 348.29 51791 +1957 220 19.78 13.78 18.13 0 504.78 358.3 51622 +1957 221 24.18 18.18 22.53 1.03 643.01 255.97 51451 +1957 222 22.95 16.95 21.3 0.09 601.48 258.86 51279 +1957 223 22.51 16.51 20.86 0.16 587.18 259.26 51105 +1957 224 22.02 16.02 20.37 0.05 571.61 259.83 50929 +1957 225 19.75 13.75 18.1 1.05 503.94 264.74 50751 +1957 226 18.79 12.79 17.14 0.49 477.44 266.1 50572 +1957 227 21.31 15.31 19.66 0 549.66 345.43 50392 +1957 228 24.43 18.43 22.78 0 651.74 332.51 50210 +1957 229 17.45 11.45 15.8 0 442.44 354.87 50026 +1957 230 17.97 11.97 16.32 0 455.76 352.13 49842 +1957 231 22.88 16.88 21.23 0.01 599.18 251.02 49656 +1957 232 20.26 14.26 18.61 0 518.51 342.42 49469 +1957 233 16.97 10.97 15.32 0.66 430.45 262.93 49280 +1957 234 15.71 9.71 14.06 0 400.28 352.32 49091 +1957 235 14.33 8.33 12.68 0 369.33 354.03 48900 +1957 236 15.3 9.3 13.65 0 390.86 350.32 48709 +1957 237 19.86 13.86 18.21 0 507.05 336.31 48516 +1957 238 20.87 14.87 19.22 0 536.42 331.46 48323 +1957 239 21.28 15.28 19.63 0.2 548.75 246.47 48128 +1957 240 23.53 17.53 21.88 0.81 620.77 239.24 47933 +1957 241 22.95 16.95 21.3 0 601.48 319.45 47737 +1957 242 23.65 17.65 22 0.12 624.82 236.4 47541 +1957 243 23.33 17.33 21.68 0 614.06 314.59 47343 +1957 244 21.05 15.05 19.4 0.11 541.8 240.46 47145 +1957 245 19.73 13.73 18.08 0.32 503.37 242.15 46947 +1957 246 16.57 10.57 14.92 0.12 420.67 247.07 46747 +1957 247 16.72 10.72 15.07 0.19 424.32 245.39 46547 +1957 248 14.6 8.6 12.95 0 375.22 330.12 46347 +1957 249 11.72 5.72 10.07 0 316.34 333.71 46146 +1957 250 14.25 8.25 12.6 0 367.6 326.77 45945 +1957 251 19.71 13.71 18.06 0.02 502.81 233.38 45743 +1957 252 20.11 14.11 18.46 0.05 514.19 230.91 45541 +1957 253 20.18 14.18 18.53 1.57 516.2 229.2 45339 +1957 254 17.67 11.67 16.02 0.44 448.04 232.72 45136 +1957 255 19.35 13.35 17.7 0 492.75 303.63 44933 +1957 256 19.37 13.37 17.72 0 493.3 301.34 44730 +1957 257 22.15 16.15 20.5 0 575.7 290.99 44527 +1957 258 15.58 9.58 13.93 0 397.27 306.14 44323 +1957 259 13.6 7.6 11.95 0 353.8 307.73 44119 +1957 260 16.4 10.4 14.75 0 416.57 299.49 43915 +1957 261 20.04 14.04 18.39 0.07 512.18 215.96 43711 +1957 262 20.7 14.7 19.05 0 531.38 283.78 43507 +1957 263 19.6 13.6 17.95 0.21 499.72 213.31 43303 +1957 264 21.62 15.62 19.97 0.76 559.15 207.17 43099 +1957 265 15.85 9.85 14.2 0.48 403.54 216.34 42894 +1957 266 14.54 8.54 12.89 0.28 373.9 216.47 42690 +1957 267 18.31 12.31 16.66 0.03 464.64 208.33 42486 +1957 268 18.98 12.98 17.33 0.05 482.59 205.21 42282 +1957 269 18.95 12.95 17.3 0.41 481.77 203.42 42078 +1957 270 15.12 9.12 13.47 0 386.79 277.07 41875 +1957 271 17.26 11.26 15.61 0 437.66 270.01 41671 +1957 272 16.66 10.66 15.01 0 422.85 268.61 41468 +1957 273 16.26 10.26 14.61 0 413.22 266.94 41265 +1957 274 14.04 8.04 12.39 0 363.09 268.53 41062 +1957 275 13.11 7.11 11.46 0 343.69 267.36 40860 +1957 276 15.56 9.56 13.91 0 396.81 260.25 40658 +1957 277 12.83 6.83 11.18 0 338.02 262.43 40456 +1957 278 14.45 8.45 12.8 0 371.94 256.81 40255 +1957 279 14.83 8.83 13.18 0.07 380.3 190 40054 +1957 280 12.32 6.32 10.67 0.3 327.91 191.14 39854 +1957 281 9.43 3.43 7.78 0.15 275.36 192.12 39654 +1957 282 13.2 7.2 11.55 0 345.53 248.01 39455 +1957 283 15.26 9.26 13.61 0 389.95 241.72 39256 +1957 284 15.33 9.33 13.68 0 391.55 238.6 39058 +1957 285 13.87 7.87 12.22 0 359.47 238.47 38861 +1957 286 19.27 13.27 17.62 0 490.54 225.51 38664 +1957 287 14.56 8.56 12.91 0 374.34 231.68 38468 +1957 288 7.26 1.26 5.61 0.03 240.81 178.96 38273 +1957 289 10.54 4.54 8.89 0 294.62 232.14 38079 +1957 290 11.82 5.82 10.17 0 318.25 227.57 37885 +1957 291 11.63 5.63 9.98 0 314.64 225.13 37693 +1957 292 12.53 6.53 10.88 0 332.04 221.2 37501 +1957 293 13.3 7.3 11.65 0 347.58 217.38 37311 +1957 294 13.36 7.36 11.71 0.01 348.81 160.82 37121 +1957 295 12.32 6.32 10.67 0.22 327.91 159.8 36933 +1957 296 11.95 5.95 10.3 1.21 320.74 158.24 36745 +1957 297 10.18 4.18 8.53 0.07 288.25 157.83 36560 +1957 298 6.36 0.36 4.71 0 227.61 211.74 36375 +1957 299 7.38 1.38 5.73 0.02 242.61 155.98 36191 +1957 300 9.39 3.39 7.74 0 274.68 203.24 36009 +1957 301 10.43 4.43 8.78 0 292.66 199.56 35829 +1957 302 13.27 7.27 11.62 0 346.96 193.45 35650 +1957 303 13.92 7.92 12.27 0 360.53 190.02 35472 +1957 304 14.78 8.78 13.13 0.27 379.19 139.8 35296 +1957 305 11.34 5.34 9.69 0.42 309.2 141.12 35122 +1957 306 11.34 5.34 9.69 0 309.2 185.92 34950 +1957 307 11.01 5.01 9.36 0 303.11 183.8 34779 +1957 308 6.61 0.61 4.96 0 231.21 185.47 34610 +1957 309 7.54 1.54 5.89 0.57 245.04 136.76 34444 +1957 310 6 0 4.35 0 222.51 181.17 34279 +1957 311 6.76 0.76 5.11 0 233.39 178.36 34116 +1957 312 4.76 -1.24 3.11 0 205.68 177.24 33956 +1957 313 6.04 0.04 4.39 0.25 223.07 130.61 33797 +1957 314 5.64 -0.36 3.99 0 217.5 172.48 33641 +1957 315 4.44 -1.56 2.79 0.13 201.52 128.09 33488 +1957 316 2.46 -3.54 0.81 0.19 177.35 127.38 33337 +1957 317 4.81 -1.19 3.16 0.03 206.34 124.59 33188 +1957 318 3.35 -2.65 1.7 0 187.89 164.71 33042 +1957 319 6.08 0.08 4.43 0 223.63 161.15 32899 +1957 320 9.34 3.34 7.69 0 273.84 156.63 32758 +1957 321 10.96 4.96 9.31 0 302.2 153.02 32620 +1957 322 10.71 4.71 9.06 0 297.67 151.47 32486 +1957 323 15.09 9.09 13.44 0.01 386.11 108.82 32354 +1957 324 10.19 4.19 8.54 0.01 288.42 111.25 32225 +1957 325 14 8 12.35 0 362.24 142.74 32100 +1957 326 14.67 8.67 13.02 0.02 376.76 105.42 31977 +1957 327 14.29 8.29 12.64 1.04 368.46 104.41 31858 +1957 328 13.12 7.12 11.47 0 343.89 138.58 31743 +1957 329 11.53 5.53 9.88 0.09 312.76 104.05 31631 +1957 330 7.25 1.25 5.6 0 240.65 140.9 31522 +1957 331 6.31 0.31 4.66 0 226.89 140.25 31417 +1957 332 6.63 0.63 4.98 0 231.5 138.39 31316 +1957 333 9.07 3.07 7.42 0 269.35 135.5 31218 +1957 334 8.24 2.24 6.59 0 255.92 135.06 31125 +1957 335 5.95 -0.05 4.3 0 221.81 135.5 31035 +1957 336 3.06 -2.94 1.41 0 184.4 136.14 30949 +1957 337 2.18 -3.82 0.53 0 174.15 134.92 30867 +1957 338 1.92 -4.08 0.27 0 171.21 134.1 30790 +1957 339 5.56 -0.44 3.91 0 216.41 131.29 30716 +1957 340 5.43 -0.57 3.78 0 214.63 130.64 30647 +1957 341 5.03 -0.97 3.38 0 209.25 129.97 30582 +1957 342 8.09 2.09 6.44 0 253.55 127.2 30521 +1957 343 6.6 0.6 4.95 0 231.07 127.41 30465 +1957 344 3.37 -2.63 1.72 0 188.13 128.18 30413 +1957 345 3.68 -2.32 2.03 0 191.93 127.58 30366 +1957 346 1.48 -4.52 -0.17 0 166.35 128.13 30323 +1957 347 -0.31 -6.31 -1.96 0 147.76 128.31 30284 +1957 348 0.11 -5.89 -1.54 0 151.95 127.78 30251 +1957 349 -0.6 -6.6 -2.25 0 144.92 127.69 30221 +1957 350 -0.43 -6.43 -2.08 0 146.58 127.28 30197 +1957 351 -0.06 -6.06 -1.71 0 150.24 126.91 30177 +1957 352 2.43 -3.57 0.78 1.88 177.01 94.27 30162 +1957 353 3 -3 1.35 0 183.68 125.35 30151 +1957 354 2.15 -3.85 0.5 0.04 173.81 94.3 30145 +1957 355 7.15 1.15 5.5 0 239.16 122.9 30144 +1957 356 6.81 0.81 5.16 0 234.13 123.15 30147 +1957 357 7.63 1.63 5.98 0 246.42 122.66 30156 +1957 358 4.74 -1.26 3.09 0 205.42 124.55 30169 +1957 359 4.67 -1.33 3.02 0 204.5 124.71 30186 +1957 360 2.42 -3.58 0.77 0 176.89 126.26 30208 +1957 361 3.52 -2.48 1.87 0 189.96 126.03 30235 +1957 362 4.46 -1.54 2.81 0.12 201.78 94.47 30267 +1957 363 5.6 -0.4 3.95 0.2 216.95 94.41 30303 +1957 364 2.86 -3.14 1.21 0 182.02 127.8 30343 +1957 365 2.94 -3.06 1.29 0.01 182.97 96.24 30388 +1958 1 0.5 -5.5 -1.15 0 155.94 130.38 30438 +1958 2 0.49 -5.51 -1.16 0 155.83 131.12 30492 +1958 3 0.62 -5.38 -1.03 0 157.18 132.01 30551 +1958 4 -1.35 -7.35 -3 0 137.81 133.75 30614 +1958 5 -0.48 -6.48 -2.13 0 146.09 134.06 30681 +1958 6 0.92 -5.08 -0.73 0 160.33 134.35 30752 +1958 7 -0.23 -6.23 -1.88 0 148.55 135.66 30828 +1958 8 0.51 -5.49 -1.14 0.06 156.04 102.62 30907 +1958 9 2.73 -3.27 1.08 0.05 180.49 102.76 30991 +1958 10 1.99 -4.01 0.34 0 172 138.69 31079 +1958 11 7.18 1.18 5.53 0 239.61 136.55 31171 +1958 12 9.76 3.76 8.11 0 280.97 135.54 31266 +1958 13 12.65 6.65 11 0 334.42 134.45 31366 +1958 14 8.35 2.35 6.7 0 257.66 139.73 31469 +1958 15 5.75 -0.25 4.1 0 219.02 143.04 31575 +1958 16 4.46 -1.54 2.81 0.22 201.78 108.86 31686 +1958 17 6.17 0.17 4.52 0 224.9 145.71 31800 +1958 18 6.77 0.77 5.12 0 233.54 147.16 31917 +1958 19 2.9 -3.1 1.25 0.15 182.5 113.69 32038 +1958 20 -2.08 -8.08 -3.73 0 131.17 155.61 32161 +1958 21 -2.8 -8.8 -4.45 0 124.9 157.93 32289 +1958 22 -2.42 -8.42 -4.07 0.07 128.18 160.59 32419 +1958 23 -3.08 -9.08 -4.73 0.52 122.54 163.5 32552 +1958 24 -2.68 -8.68 -4.33 0.44 125.93 166.07 32688 +1958 25 0.2 -5.8 -1.45 0 152.86 207.36 32827 +1958 26 2.62 -3.38 0.97 0 179.21 207.47 32969 +1958 27 0.5 -5.5 -1.15 1.04 155.94 168.44 33114 +1958 28 -4.18 -10.18 -5.83 0.45 113.61 172.78 33261 +1958 29 -0.23 -6.23 -1.88 1.15 148.55 176.41 33411 +1958 30 0.24 -5.76 -1.41 0.34 153.27 177.68 33564 +1958 31 0.74 -5.26 -0.91 0 158.43 223.26 33718 +1958 32 8.11 2.11 6.46 0 253.87 219 33875 +1958 33 8.86 2.86 7.21 0.04 265.89 175.66 34035 +1958 34 7.39 1.39 5.74 0 242.76 222.08 34196 +1958 35 5.75 -0.25 4.1 0.51 219.02 178.94 34360 +1958 36 2.26 -3.74 0.61 0 175.06 229.2 34526 +1958 37 4.25 -1.75 2.6 0.01 199.08 182.33 34694 +1958 38 7.29 1.29 5.64 0 241.26 228.83 34863 +1958 39 9.26 3.26 7.61 0.13 272.5 180.77 35035 +1958 40 10.58 4.58 8.93 0.22 295.33 143.37 35208 +1958 41 9 3 7.35 0 268.19 195.43 35383 +1958 42 11.5 5.5 9.85 0 312.19 195.16 35560 +1958 43 7 1 5.35 0 236.93 202.57 35738 +1958 44 4.31 -1.69 2.66 0 199.85 207.4 35918 +1958 45 8.78 2.78 7.13 0 264.59 205.96 36099 +1958 46 6.71 0.71 5.06 0.44 232.66 158 36282 +1958 47 9.14 3.14 7.49 0.11 270.51 158.27 36466 +1958 48 3.55 -2.45 1.9 0.28 190.33 164.22 36652 +1958 49 5.18 -0.82 3.53 0.73 211.25 165.31 36838 +1958 50 3.5 -2.5 1.85 0.3 189.71 168.35 37026 +1958 51 3.7 -2.3 2.05 1.34 192.17 170.47 37215 +1958 52 1.26 -4.74 -0.39 0.45 163.96 173.96 37405 +1958 53 4.96 -1.04 3.31 0.01 208.32 174.03 37596 +1958 54 3.18 -2.82 1.53 0 185.83 236.29 37788 +1958 55 5.17 -0.83 3.52 0 211.12 237.61 37981 +1958 56 8.35 2.35 6.7 0 257.66 237.07 38175 +1958 57 10.78 4.78 9.13 0.02 298.93 177.72 38370 +1958 58 12.56 6.56 10.91 0 332.64 237.35 38565 +1958 59 9.78 3.78 8.13 0.06 281.31 182.86 38761 +1958 60 5.47 -0.53 3.82 0 215.17 251.46 38958 +1958 61 1.99 -4.01 0.34 0 172 257.43 39156 +1958 62 1.44 -4.56 -0.21 0 165.91 260.68 39355 +1958 63 -1.75 -7.75 -3.4 0 134.14 265.91 39553 +1958 64 0.38 -5.62 -1.27 0 154.7 267.46 39753 +1958 65 2.28 -3.72 0.63 0 175.29 268.94 39953 +1958 66 -0.69 -6.69 -2.34 0.21 144.05 238.82 40154 +1958 67 -0.44 -6.44 -2.09 0 146.48 309.92 40355 +1958 68 2.29 -3.71 0.64 0 175.4 310.36 40556 +1958 69 3.76 -2.24 2.11 0.24 192.92 209.18 40758 +1958 70 4.91 -1.09 3.26 0.67 207.65 210.5 40960 +1958 71 5.97 -0.03 4.32 0.16 222.09 211.86 41163 +1958 72 7.57 1.57 5.92 0.37 245.5 212.6 41366 +1958 73 9.07 3.07 7.42 0 269.35 284.21 41569 +1958 74 9.81 3.81 8.16 0 281.82 285.91 41772 +1958 75 5.27 -0.73 3.62 0 212.46 294.27 41976 +1958 76 4.65 -1.35 3 0 204.24 297.59 42179 +1958 77 3.55 -2.45 1.9 0 190.33 301.33 42383 +1958 78 4.27 -1.73 2.62 0 199.34 303.31 42587 +1958 79 6.01 0.01 4.36 0 222.65 304.16 42791 +1958 80 7.42 1.42 5.77 0 243.22 305 42996 +1958 81 2.91 -3.09 1.26 0 182.61 312.61 43200 +1958 82 6.42 0.42 4.77 0 228.47 311.5 43404 +1958 83 4.17 -1.83 2.52 0 198.07 316.57 43608 +1958 84 3.18 -2.82 1.53 0 185.83 320.15 43812 +1958 85 4.38 -1.62 2.73 0.52 200.75 241.09 44016 +1958 86 3.59 -2.41 1.94 0 190.82 324.73 44220 +1958 87 3.4 -2.6 1.75 0 188.49 327.5 44424 +1958 88 4.79 -1.21 3.14 0.06 206.07 246.29 44627 +1958 89 6.81 0.81 5.16 1.1 234.13 246.19 44831 +1958 90 2.62 -3.38 0.97 0.79 179.21 251.56 45034 +1958 91 16.3 10.3 14.65 0 414.18 316.04 45237 +1958 92 9.41 3.41 7.76 0.71 275.02 248.61 45439 +1958 93 8 2 6.35 0 252.14 335.8 45642 +1958 94 11.17 5.17 9.52 0 306.05 332.96 45843 +1958 95 14.42 8.42 12.77 0 371.28 328.8 46045 +1958 96 12.8 6.8 11.15 0 337.42 334.19 46246 +1958 97 10.07 4.07 8.42 0 286.32 341.14 46446 +1958 98 9.61 3.61 7.96 0 278.4 343.86 46647 +1958 99 8.3 2.3 6.65 0.02 256.87 260.94 46846 +1958 100 5.43 -0.57 3.78 0 214.63 353.82 47045 +1958 101 8.45 2.45 6.8 0.05 259.26 263.71 47243 +1958 102 9.36 3.36 7.71 0.68 274.18 264.09 47441 +1958 103 8.88 2.88 7.23 0.27 266.22 266.05 47638 +1958 104 13.27 7.27 11.62 0 346.96 348.61 47834 +1958 105 13.53 7.53 11.88 0 352.34 349.85 48030 +1958 106 12.59 6.59 10.94 0 333.23 353.42 48225 +1958 107 8.62 2.62 6.97 0 261.99 362.17 48419 +1958 108 7.91 1.91 6.26 0 250.74 365.04 48612 +1958 109 9.48 3.48 7.83 0 276.2 364.18 48804 +1958 110 10.66 4.66 9.01 0.54 296.77 272.67 48995 +1958 111 9.58 3.58 7.93 0.38 277.89 275.26 49185 +1958 112 10.75 4.75 9.1 0 298.39 366.49 49374 +1958 113 4.59 -1.41 2.94 0 203.46 377.2 49561 +1958 114 12.3 6.3 10.65 0 327.52 366.36 49748 +1958 115 11.34 5.34 9.69 0 309.2 369.69 49933 +1958 116 12.09 6.09 10.44 0 323.43 369.45 50117 +1958 117 13.49 7.49 11.84 0 351.51 367.83 50300 +1958 118 15.24 9.24 13.59 0 389.5 365.09 50481 +1958 119 11.81 5.81 10.16 0.45 318.06 280.39 50661 +1958 120 9.72 3.72 8.07 0 280.28 378.94 50840 +1958 121 19.45 13.45 17.8 0.15 495.53 267.63 51016 +1958 122 20.49 14.49 18.84 0.27 525.2 265.98 51191 +1958 123 18.27 12.27 16.62 0.18 463.59 271.95 51365 +1958 124 18.76 12.76 17.11 0 476.63 362.19 51536 +1958 125 22.46 16.46 20.81 0 585.58 350.63 51706 +1958 126 21.59 15.59 19.94 0 558.23 354.77 51874 +1958 127 20.07 14.07 18.42 0 513.04 360.85 52039 +1958 128 22.42 16.42 20.77 0 584.3 353.53 52203 +1958 129 24.05 18.05 22.4 0 638.51 347.9 52365 +1958 130 23.35 17.35 21.7 0.48 614.73 263.62 52524 +1958 131 17.78 11.78 16.13 0 450.85 371.31 52681 +1958 132 17.46 11.46 15.81 0 442.7 373.04 52836 +1958 133 16.52 10.52 14.87 0 419.46 376.36 52989 +1958 134 19.42 13.42 17.77 0 494.69 368.5 53138 +1958 135 17.89 11.89 16.24 0.02 453.69 280.42 53286 +1958 136 18.44 12.44 16.79 0 468.08 372.87 53430 +1958 137 21.66 15.66 20.01 0.17 560.39 272.1 53572 +1958 138 24.49 18.49 22.84 0.27 653.85 264.12 53711 +1958 139 25.02 19.02 23.37 0.02 672.74 262.89 53848 +1958 140 22.67 16.67 21.02 0 592.35 360.71 53981 +1958 141 20.22 14.22 18.57 0 517.36 370.03 54111 +1958 142 17.44 11.44 15.79 0.03 442.19 284.42 54238 +1958 143 18.45 12.45 16.8 0 468.34 376.76 54362 +1958 144 19.92 13.92 18.27 0 508.76 372.52 54483 +1958 145 19.76 13.76 18.11 0 504.22 373.52 54600 +1958 146 19.84 13.84 18.19 0 506.48 373.62 54714 +1958 147 21.25 15.25 19.6 0.05 547.84 276.9 54824 +1958 148 23.43 17.43 21.78 0 617.4 361.2 54931 +1958 149 22.77 16.77 21.12 0 595.59 364.15 55034 +1958 150 26.53 20.53 24.88 0 729.13 348.02 55134 +1958 151 27.26 21.26 25.61 0.05 757.79 258.59 55229 +1958 152 22.3 16.3 20.65 0.6 580.46 275.09 55321 +1958 153 15.24 9.24 13.59 0.77 389.5 292.02 55409 +1958 154 17.33 11.33 15.68 1.35 439.42 287.99 55492 +1958 155 17.5 11.5 15.85 2.21 443.71 287.76 55572 +1958 156 20.25 14.25 18.6 0.21 518.22 281.46 55648 +1958 157 20.25 14.25 18.6 0.71 518.22 281.59 55719 +1958 158 21.21 15.21 19.56 2.49 546.63 279.18 55786 +1958 159 20.28 14.28 18.63 0.82 519.09 281.82 55849 +1958 160 19.27 13.27 17.62 0.13 490.54 284.48 55908 +1958 161 21.99 15.99 20.34 0.38 570.66 277.37 55962 +1958 162 23.38 17.38 21.73 0.31 615.73 273.31 56011 +1958 163 20.15 14.15 18.5 1.75 515.34 282.54 56056 +1958 164 23.22 17.22 21.57 0.34 610.39 273.99 56097 +1958 165 18.63 12.63 16.98 0.19 473.14 286.38 56133 +1958 166 18.33 12.33 16.68 0.3 465.17 287.14 56165 +1958 167 19.26 13.26 17.61 0 490.26 379.85 56192 +1958 168 19.97 13.97 18.32 0.14 510.18 283.18 56214 +1958 169 18.39 12.39 16.74 0.84 466.76 287.02 56231 +1958 170 20.86 14.86 19.21 0.32 536.12 280.88 56244 +1958 171 23.68 17.68 22.03 0 625.84 363.69 56252 +1958 172 21.27 15.27 19.62 0.05 548.44 279.81 56256 +1958 173 26.91 20.91 25.26 0.34 743.94 261.71 56255 +1958 174 24.87 18.87 23.22 0.02 667.35 268.84 56249 +1958 175 23.09 17.09 21.44 0.33 606.09 274.48 56238 +1958 176 20.14 14.14 18.49 0.73 515.05 282.67 56223 +1958 177 18.5 12.5 16.85 0.09 469.67 286.6 56203 +1958 178 16.68 10.68 15.03 0.03 423.34 290.65 56179 +1958 179 17.77 11.77 16.12 1 450.6 288.21 56150 +1958 180 19.69 13.69 18.04 0 502.24 378.11 56116 +1958 181 13.5 7.5 11.85 0 351.71 395.32 56078 +1958 182 21.75 15.75 20.1 0 563.17 370.63 56035 +1958 183 23.21 17.21 21.56 0.24 610.06 273.58 55987 +1958 184 24.27 18.27 22.62 0.07 646.14 270.15 55935 +1958 185 23.91 17.91 22.26 0.58 633.69 271.24 55879 +1958 186 24.88 18.88 23.23 0.33 667.71 267.91 55818 +1958 187 26 20 24.35 0.02 708.9 263.93 55753 +1958 188 26.74 20.74 25.09 0.75 737.28 261.07 55684 +1958 189 27.03 21.03 25.38 0.2 748.66 259.87 55611 +1958 190 25.62 19.62 23.97 0.1 694.69 264.67 55533 +1958 191 24.02 18.02 22.37 0.11 637.47 269.78 55451 +1958 192 22.89 16.89 21.24 1.1 599.51 273.02 55366 +1958 193 26.13 20.13 24.48 0.95 713.82 262.28 55276 +1958 194 27.41 21.41 25.76 0.36 763.8 257.43 55182 +1958 195 26.89 20.89 25.24 0.17 743.15 259.18 55085 +1958 196 21.06 15.06 19.41 0 542.1 369.75 54984 +1958 197 14.04 8.04 12.39 0.01 363.09 292.41 54879 +1958 198 15.48 9.48 13.83 0 394.97 385.89 54770 +1958 199 15.02 9.02 13.37 0 384.54 386.69 54658 +1958 200 16.62 10.62 14.97 0 421.88 382.07 54542 +1958 201 16.96 10.96 15.31 0 430.2 380.64 54423 +1958 202 19.99 13.99 18.34 0 510.75 370.78 54301 +1958 203 22.04 16.04 20.39 0 572.24 363.02 54176 +1958 204 23.69 17.69 22.04 0 626.18 356.05 54047 +1958 205 25.12 19.12 23.47 0.31 676.36 262.09 53915 +1958 206 23.68 17.68 22.03 0.64 625.84 266.28 53780 +1958 207 22.82 16.82 21.17 0 597.22 357.83 53643 +1958 208 24.01 18.01 22.36 0.08 637.13 264.3 53502 +1958 209 26.24 20.24 24.59 0 718 341.93 53359 +1958 210 25.93 19.93 24.28 0 706.27 342.78 53213 +1958 211 30.18 24.18 28.53 0.02 882.15 240.07 53064 +1958 212 34.17 28.17 32.52 0.12 1079.54 220.4 52913 +1958 213 33 27 31.35 0 1018.16 301.23 52760 +1958 214 29.59 23.59 27.94 0 855.73 321.34 52604 +1958 215 27.86 21.86 26.21 0 782.06 329.91 52445 +1958 216 21.92 15.92 20.27 0.09 568.47 265.97 52285 +1958 217 20.05 14.05 18.4 0 512.47 360.23 52122 +1958 218 20.86 14.86 19.21 0 536.12 356.69 51958 +1958 219 23.34 17.34 21.69 0 614.39 346.55 51791 +1958 220 23.22 17.22 21.57 0.32 610.39 259.58 51622 +1958 221 22.7 16.7 21.05 0 593.32 347.12 51451 +1958 222 24.71 18.71 23.06 0 661.64 338.08 51279 +1958 223 20.82 14.82 19.17 0.3 534.93 263.76 51105 +1958 224 20.93 14.93 19.28 1.16 538.21 262.69 50929 +1958 225 18.81 12.81 17.16 0.01 477.98 266.92 50751 +1958 226 17.42 11.42 15.77 1.83 441.69 269.06 50572 +1958 227 19.15 13.15 17.5 0.22 487.23 264.32 50392 +1958 228 20.44 14.44 18.79 0 523.74 347.14 50210 +1958 229 21.37 15.37 19.72 0.14 551.49 257.09 50026 +1958 230 24.58 18.58 22.93 0 657.03 329.48 49842 +1958 231 24.87 18.87 23.22 0.06 667.35 245.16 49656 +1958 232 27.09 21.09 25.44 0.82 751.04 236.86 49469 +1958 233 23.8 17.8 22.15 0 629.93 328.51 49280 +1958 234 23.7 17.7 22.05 0.3 626.52 245.64 49091 +1958 235 23.24 17.24 21.59 0 611.06 327.83 48900 +1958 236 21.56 15.56 19.91 0.35 557.3 249.33 48709 +1958 237 21.21 15.21 19.56 0 546.63 331.99 48516 +1958 238 23.29 17.29 21.64 0.02 612.72 242.28 48323 +1958 239 24.13 18.13 22.48 0 641.27 318.4 48128 +1958 240 23.22 17.22 21.57 0 610.39 320.14 47933 +1958 241 20.59 14.59 18.94 0 528.14 327.43 47737 +1958 242 21.81 15.81 20.16 0.55 565.04 241.3 47541 +1958 243 23.16 17.16 21.51 0.02 608.4 236.41 47343 +1958 244 17.13 11.13 15.48 0.1 434.42 248.9 47145 +1958 245 18.56 12.56 16.91 0 471.27 326.21 46947 +1958 246 18.94 12.94 17.29 0 481.5 323.2 46747 +1958 247 16.21 10.21 14.56 0.4 412.03 246.32 46547 +1958 248 15.83 9.83 14.18 0.05 403.08 245.52 46347 +1958 249 23.75 17.75 22.1 0 628.22 302.02 46146 +1958 250 26.66 20.66 25.01 0 734.17 288.73 45945 +1958 251 30.17 24.17 28.52 0 881.7 270.45 45743 +1958 252 26.56 20.56 24.91 0.01 730.29 213.88 45541 +1958 253 26.01 20.01 24.36 0.39 709.28 214.1 45339 +1958 254 21.61 15.61 19.96 0.31 558.84 224.38 45136 +1958 255 18.12 12.12 16.47 0.07 459.66 230.18 44933 +1958 256 16.57 10.57 14.92 0.14 420.67 231.33 44730 +1958 257 17.17 11.17 15.52 0.6 435.41 228.64 44527 +1958 258 15.97 9.97 14.32 1.24 406.36 228.96 44323 +1958 259 13.62 7.62 11.97 0.01 354.21 230.77 44119 +1958 260 15.03 9.03 13.38 0 384.76 302.46 43915 +1958 261 19.42 13.42 17.77 0 494.69 289.63 43711 +1958 262 19.62 13.62 17.97 0.33 500.28 215.08 43507 +1958 263 21.04 15.04 19.39 0 541.5 280.41 43303 +1958 264 19.11 13.11 17.46 0.73 486.14 212.38 43099 +1958 265 18.14 12.14 16.49 0.09 460.18 212.45 42894 +1958 266 17.19 11.19 15.54 0.1 435.91 212.29 42690 +1958 267 18.07 12.07 16.42 0 458.35 278.35 42486 +1958 268 16.84 10.84 15.19 0 427.25 278.63 42282 +1958 269 17.53 11.53 15.88 0 444.47 274.6 42078 +1958 270 15.77 9.77 14.12 0 401.68 275.77 41875 +1958 271 18.26 12.26 16.61 0 463.33 267.74 41671 +1958 272 17.48 11.48 15.83 0 443.2 266.83 41468 +1958 273 15.64 9.64 13.99 0.35 398.66 201.14 41265 +1958 274 8.86 2.86 7.21 0 265.89 276.46 41062 +1958 275 14.09 8.09 12.44 0.32 364.16 199.25 40860 +1958 276 14.05 8.05 12.4 0.69 363.3 197.28 40658 +1958 277 11.82 5.82 10.17 0 318.25 264.02 40456 +1958 278 15.21 9.21 13.56 0 388.82 255.43 40255 +1958 279 16.64 10.64 14.99 0.03 422.37 187.42 40054 +1958 280 18.61 12.61 16.96 0.03 472.61 182.35 39854 +1958 281 15.11 9.11 13.46 0 386.56 247.49 39654 +1958 282 18.97 12.97 17.32 0 482.32 237.03 39455 +1958 283 19.23 13.23 17.58 0 489.43 233.72 39256 +1958 284 14.62 8.62 12.97 0.16 375.66 179.88 39058 +1958 285 14.03 8.03 12.38 0.02 362.88 178.65 38861 +1958 286 9.75 3.75 8.1 0 280.79 241.57 38664 +1958 287 10.99 4.99 9.34 1.56 302.75 177.76 38468 +1958 288 12.39 6.39 10.74 0.39 329.28 174.2 38273 +1958 289 10.86 4.86 9.21 0.02 300.38 173.8 38079 +1958 290 11.85 5.85 10.2 0 318.82 227.53 37885 +1958 291 15.93 9.93 14.28 0 405.42 218.53 37693 +1958 292 15.33 9.33 13.68 0 391.55 216.92 37501 +1958 293 15.59 9.59 13.94 0.89 397.51 160.35 37311 +1958 294 15.04 9.04 13.39 0.42 384.99 158.9 37121 +1958 295 16.58 10.58 14.93 0.32 420.91 154.88 36933 +1958 296 13.82 7.82 12.17 1.08 358.42 156.29 36745 +1958 297 14.05 8.05 12.4 0.27 363.3 154.02 36560 +1958 298 11.75 5.75 10.1 0.1 316.91 154.45 36375 +1958 299 11.49 5.49 9.84 0.19 312.01 152.61 36191 +1958 300 12.19 6.19 10.54 0.31 325.37 149.96 36009 +1958 301 13.62 7.62 11.97 0 354.21 195.55 35829 +1958 302 14.17 8.17 12.52 0.72 365.87 144.16 35650 +1958 303 12.33 6.33 10.68 0 328.11 192.12 35472 +1958 304 16.46 10.46 14.81 0 418.01 183.85 35296 +1958 305 10.93 4.93 9.28 0 301.65 188.62 35122 +1958 306 9.73 3.73 8.08 0.04 280.45 140.76 34950 +1958 307 10.57 4.57 8.92 0 295.15 184.29 34779 +1958 308 10.44 4.44 8.79 0.5 292.83 136.38 34610 +1958 309 8.41 2.41 6.76 0.34 258.62 136.16 34444 +1958 310 8.3 2.3 6.65 0.24 256.87 134.41 34279 +1958 311 8.57 2.57 6.92 0.62 261.19 132.59 34116 +1958 312 6.95 0.95 5.3 0.32 236.19 131.66 33956 +1958 313 9.73 3.73 8.08 1.01 280.45 128.2 33797 +1958 314 8.33 2.33 6.68 0.99 257.34 127.72 33641 +1958 315 7.46 1.46 5.81 0.46 243.83 126.38 33488 +1958 316 8.19 2.19 6.54 0 255.13 165.7 33337 +1958 317 5.93 -0.07 4.28 0 221.53 165.31 33188 +1958 318 11.03 5.03 9.38 0 303.48 158.54 33042 +1958 319 12.09 6.09 10.44 0 323.43 155.77 32899 +1958 320 7.25 1.25 5.6 0.04 240.65 118.79 32758 +1958 321 7.55 1.55 5.9 0.47 245.19 117.03 32620 +1958 322 3.56 -2.44 1.91 0.33 190.45 117.75 32486 +1958 323 4.21 -1.79 2.56 0.28 198.57 116.23 32354 +1958 324 2.18 -3.82 0.53 0.11 174.15 115.57 32225 +1958 325 5.64 -0.36 3.99 0 217.5 150.24 32100 +1958 326 6.95 0.95 5.3 0 236.19 147.86 31977 +1958 327 8.91 2.91 7.26 0.88 266.71 108.37 31858 +1958 328 7.62 1.62 5.97 0.24 246.26 107.66 31743 +1958 329 11 5 9.35 0.01 302.93 104.42 31631 +1958 330 12.29 6.29 10.64 0 327.32 136.57 31522 +1958 331 10.79 4.79 9.14 0 299.11 136.71 31417 +1958 332 10.78 4.78 9.13 0 298.93 135.11 31316 +1958 333 9.47 3.47 7.82 0.04 276.03 101.38 31218 +1958 334 9.97 3.97 8.32 0 284.59 133.67 31125 +1958 335 6.05 0.05 4.4 0 223.21 135.43 31035 +1958 336 4.78 -1.22 3.13 0.3 205.94 101.37 30949 +1958 337 7.04 1.04 5.39 0 237.52 132.04 30867 +1958 338 9.65 3.65 8 0 279.08 129.16 30790 +1958 339 8.74 2.74 7.09 0 263.94 129.1 30716 +1958 340 4.23 -1.77 2.58 0 198.83 131.35 30647 +1958 341 6.2 0.2 4.55 0.15 225.33 96.93 30582 +1958 342 0.2 -5.8 -1.45 0.47 152.86 98.75 30521 +1958 343 1.56 -4.44 -0.09 0 167.22 130.22 30465 +1958 344 2.62 -3.38 0.97 0 179.21 128.57 30413 +1958 345 5.22 -0.78 3.57 0 211.79 126.71 30366 +1958 346 10.57 4.57 8.92 0 295.15 122.39 30323 +1958 347 9.52 3.52 7.87 0 276.88 122.64 30284 +1958 348 10.24 4.24 8.59 0 289.3 121.73 30251 +1958 349 7.64 1.64 5.99 0.28 246.57 92.48 30221 +1958 350 4.25 -1.75 2.6 0 199.08 125.06 30197 +1958 351 2.69 -3.31 1.04 0 180.03 125.66 30177 +1958 352 0.48 -5.52 -1.17 0 155.73 126.59 30162 +1958 353 1.31 -4.69 -0.34 0 164.5 126.16 30151 +1958 354 3.56 -2.44 1.91 0.39 190.45 93.77 30145 +1958 355 5.66 -0.34 4.01 2.15 217.78 92.88 30144 +1958 356 4.46 -1.54 2.81 0.1 201.78 93.42 30147 +1958 357 4.7 -1.3 3.05 0.2 204.89 93.36 30156 +1958 358 7.73 1.73 6.08 0 247.95 122.67 30169 +1958 359 11.08 5.08 9.43 0 304.4 120.22 30186 +1958 360 9.39 3.39 7.74 0 274.68 121.94 30208 +1958 361 3.2 -2.8 1.55 0.13 186.07 94.65 30235 +1958 362 3.25 -2.75 1.6 0 186.68 126.61 30267 +1958 363 5.75 -0.25 4.1 0 219.02 125.79 30303 +1958 364 8.49 2.49 6.84 0.05 259.9 93.25 30343 +1958 365 8.55 2.55 6.9 0 260.86 124.85 30388 +1959 1 10.11 4.11 8.46 0 287.02 124.52 30438 +1959 2 8.82 2.82 7.17 0 265.24 126.25 30492 +1959 3 6.07 0.07 4.42 0.02 223.49 96.82 30551 +1959 4 1.72 -4.28 0.07 0 168.99 132.42 30614 +1959 5 -2.57 -8.57 -4.22 0 126.88 134.87 30681 +1959 6 -1.89 -7.89 -3.54 0 132.87 135.52 30752 +1959 7 -1.05 -7.05 -2.7 0 140.62 136 30828 +1959 8 1.67 -4.33 0.02 0 168.43 136.28 30907 +1959 9 5.34 -0.66 3.69 0 213.41 135.51 30991 +1959 10 4.78 -1.22 3.13 0 205.94 137.15 31079 +1959 11 6.45 0.45 4.8 0 228.9 137.06 31171 +1959 12 3.07 -2.93 1.42 0.08 184.52 105.1 31266 +1959 13 2.88 -3.12 1.23 0.46 182.26 106.39 31366 +1959 14 4.56 -1.44 2.91 0.21 203.07 106.77 31469 +1959 15 2.56 -3.44 0.91 0 178.51 144.96 31575 +1959 16 1.3 -4.7 -0.35 0 164.39 146.91 31686 +1959 17 0.03 -5.97 -1.62 0 151.15 149.22 31800 +1959 18 0.31 -5.69 -1.34 0 153.98 151 31917 +1959 19 2.13 -3.87 0.48 0 173.58 152.02 32038 +1959 20 2.55 -3.45 0.9 0 178.39 153.38 32161 +1959 21 0.13 -5.87 -1.52 0 152.15 156.65 32289 +1959 22 0.79 -5.21 -0.86 0 158.96 158.09 32419 +1959 23 3.33 -2.67 1.68 0 187.64 158.46 32552 +1959 24 2.23 -3.77 0.58 0 174.72 161.18 32688 +1959 25 7.69 1.69 6.04 0 247.34 159.32 32827 +1959 26 7.25 1.25 5.6 0 240.65 161.58 32969 +1959 27 8.97 2.97 7.32 0 267.7 162.12 33114 +1959 28 5.18 -0.82 3.53 0 211.25 167.35 33261 +1959 29 3.37 -2.63 1.72 0 188.13 170.95 33411 +1959 30 0.53 -5.47 -1.12 0 156.25 174.86 33564 +1959 31 1.92 -4.08 0.27 0 171.21 176.47 33718 +1959 32 3.24 -2.76 1.59 0 186.56 177.78 33875 +1959 33 0.98 -5.02 -0.67 0 160.96 181.79 34035 +1959 34 2.97 -3.03 1.32 0 183.33 182.8 34196 +1959 35 7.64 1.64 5.99 0 246.57 181.37 34360 +1959 36 6.74 0.74 5.09 0 233.1 184.65 34526 +1959 37 4.96 -1.04 3.31 0 208.32 188.49 34694 +1959 38 4.49 -1.51 2.84 0 202.16 191.58 34863 +1959 39 3.05 -2.95 1.4 0 184.28 195.23 35035 +1959 40 6.59 0.59 4.94 0 230.92 195.1 35208 +1959 41 4.76 -1.24 3.11 0 205.68 199.22 35383 +1959 42 1.02 -4.98 -0.63 0 161.39 204.38 35560 +1959 43 2.36 -3.64 0.71 0 176.2 206.24 35738 +1959 44 -1.12 -7.12 -2.77 0 139.96 210.95 35918 +1959 45 -0.88 -6.88 -2.53 0 142.23 213.48 36099 +1959 46 4.26 -1.74 2.61 0 199.21 212.76 36282 +1959 47 3.84 -2.16 2.19 0 193.91 215.92 36466 +1959 48 1.75 -4.25 0.1 0 169.32 220.26 36652 +1959 49 4.21 -1.79 2.56 0 198.57 221.23 36838 +1959 50 1.73 -4.27 0.08 0 169.1 225.77 37026 +1959 51 0.2 -5.8 -1.45 0.03 152.86 172.33 37215 +1959 52 -1.6 -7.6 -3.25 0 135.5 233.72 37405 +1959 53 -5 -11 -6.65 0 107.32 238.45 37596 +1959 54 0.98 -5.02 -0.67 0 160.96 237.91 37788 +1959 55 2.92 -3.08 1.27 0 182.73 239.51 37981 +1959 56 3.53 -2.47 1.88 0 190.08 241.73 38175 +1959 57 6.11 0.11 4.46 0.1 224.06 181.73 38370 +1959 58 3.37 -2.63 1.72 0 188.13 247.72 38565 +1959 59 8.25 2.25 6.6 0 256.08 245.65 38761 +1959 60 13.58 7.58 11.93 0 353.38 241.22 38958 +1959 61 15.15 9.15 13.5 0 387.46 241.41 39156 +1959 62 14.86 8.86 13.21 0 380.96 244.61 39355 +1959 63 10.53 4.53 8.88 0 294.44 254.3 39553 +1959 64 8.11 2.11 6.46 0.26 253.87 195.19 39753 +1959 65 7.98 1.98 6.33 0.14 251.83 197.47 39953 +1959 66 8.27 2.27 6.62 0 256.39 265.67 40154 +1959 67 8.28 2.28 6.63 0 256.55 268.55 40355 +1959 68 10.38 4.38 8.73 0 291.77 268.64 40556 +1959 69 15.6 9.6 13.95 0 397.74 262.51 40758 +1959 70 16.34 10.34 14.69 0.3 415.13 197.83 40960 +1959 71 18.36 12.36 16.71 0.37 465.96 196.62 41163 +1959 72 16.28 10.28 14.63 0.3 413.7 202.07 41366 +1959 73 17.53 11.53 15.88 0 444.47 269.29 41569 +1959 74 14.52 8.52 12.87 0 373.46 278.15 41772 +1959 75 15.86 9.86 14.21 0 403.78 278.15 41976 +1959 76 14.66 8.66 13.01 0 376.54 283.1 42179 +1959 77 11.55 5.55 9.9 0.02 313.13 218.37 42383 +1959 78 8.82 2.82 7.17 0.26 265.24 223.41 42587 +1959 79 7.91 1.91 6.26 0.29 250.74 226.37 42791 +1959 80 10.14 4.14 8.49 0 287.55 301.22 42996 +1959 81 9.6 3.6 7.95 0.03 278.23 228.45 43200 +1959 82 6.22 0.22 4.57 0.34 225.61 233.81 43404 +1959 83 4.25 -1.75 2.6 0 199.08 316.48 43608 +1959 84 2.36 -3.64 0.71 0.15 176.2 240.71 43812 +1959 85 4.87 -1.13 3.22 0 207.13 320.91 44016 +1959 86 5.97 -0.03 4.32 0 222.09 322.07 44220 +1959 87 7.47 1.47 5.82 0 243.98 322.72 44424 +1959 88 11.52 5.52 9.87 0 312.57 318.91 44627 +1959 89 9.85 3.85 8.2 0 282.51 323.92 44831 +1959 90 8.85 2.85 7.2 0.07 265.73 245.86 45034 +1959 91 13.72 7.72 12.07 0.67 356.31 241.22 45237 +1959 92 11.82 5.82 10.17 0 318.25 327.46 45439 +1959 93 9.77 3.77 8.12 0.09 281.14 249.85 45642 +1959 94 11.55 5.55 9.9 0.65 313.13 249.21 45843 +1959 95 7.74 1.74 6.09 1.48 248.11 255.38 46045 +1959 96 5.36 -0.64 3.71 0.36 213.68 259.34 46246 +1959 97 5.26 -0.74 3.61 0.27 212.33 261 46446 +1959 98 9.77 3.77 8.12 0 281.14 343.6 46647 +1959 99 8.44 2.44 6.79 0.84 259.1 260.78 46846 +1959 100 7.61 1.61 5.96 0.2 246.11 263.18 47045 +1959 101 10.49 4.49 8.84 0 293.72 348.31 47243 +1959 102 16.27 10.27 14.62 0 413.46 338.22 47441 +1959 103 16.41 10.41 14.76 0.04 416.81 254.75 47638 +1959 104 11.55 5.55 9.9 0.17 313.13 264 47834 +1959 105 16.73 10.73 15.08 0 424.56 342.4 48030 +1959 106 19.27 13.27 17.62 0 490.54 337 48225 +1959 107 19.63 13.63 17.98 0 500.56 337.52 48419 +1959 108 14.79 8.79 13.14 0 379.41 352.09 48612 +1959 109 16.98 10.98 15.33 0.03 430.7 261.21 48804 +1959 110 15.75 9.75 14.1 1.88 401.21 264.59 48995 +1959 111 17.32 11.32 15.67 0.04 439.17 262.7 49185 +1959 112 19.59 13.59 17.94 0.39 499.44 258.89 49374 +1959 113 15.77 9.77 14.12 0 401.68 357.09 49561 +1959 114 20.25 14.25 18.6 0 518.22 345.83 49748 +1959 115 20.43 14.43 18.78 0 523.45 346.62 49933 +1959 116 18.28 12.28 16.63 0 463.85 354.42 50117 +1959 117 16.96 10.96 15.31 0 430.2 359.39 50300 +1959 118 13.78 7.78 12.13 0 357.57 368.5 50481 +1959 119 13.79 7.79 12.14 0 357.78 369.67 50661 +1959 120 13.78 7.78 12.13 0 357.57 370.87 50840 +1959 121 19.43 13.43 17.78 0 494.97 356.91 51016 +1959 122 16.28 10.28 14.63 0.09 413.7 275.34 51191 +1959 123 15.24 9.24 13.59 0.02 389.5 278.09 51365 +1959 124 15.08 9.08 13.43 0.19 385.89 279.19 51536 +1959 125 17.64 11.64 15.99 0 447.27 366.46 51706 +1959 126 16.25 10.25 14.6 0 412.98 371.25 51874 +1959 127 20.68 14.68 19.03 0 530.79 358.8 52039 +1959 128 18.17 12.17 16.52 0.17 460.97 275.82 52203 +1959 129 12.27 6.27 10.62 0.02 326.93 287.52 52365 +1959 130 15.49 9.49 13.84 0 395.2 376.74 52524 +1959 131 15.17 9.17 13.52 0.23 387.92 283.75 52681 +1959 132 17.54 11.54 15.89 0.16 444.72 279.61 52836 +1959 133 17.06 11.06 15.41 0 432.68 374.87 52989 +1959 134 20.1 14.1 18.45 0 513.9 366.27 53138 +1959 135 20.99 14.99 19.34 0 540 363.91 53286 +1959 136 20.23 14.23 18.58 0 517.65 367.14 53430 +1959 137 21.23 15.23 19.58 0 547.23 364.36 53572 +1959 138 17.04 11.04 15.39 0 432.18 378.27 53711 +1959 139 15.91 9.91 14.26 0 404.95 382.03 53848 +1959 140 14.68 8.68 13.03 1.12 376.98 289.23 53981 +1959 141 12.33 6.33 10.68 2.33 328.11 293.6 54111 +1959 142 10.86 4.86 9.21 0.72 300.38 296.23 54238 +1959 143 14.43 8.43 12.78 0.72 371.5 290.81 54362 +1959 144 11.25 5.25 9.6 1.39 307.53 296.43 54483 +1959 145 17.83 11.83 16.18 0.28 452.14 284.68 54600 +1959 146 20.66 14.66 19.01 1.41 530.2 278.12 54714 +1959 147 20.61 14.61 18.96 0 528.72 371.47 54824 +1959 148 22.6 16.6 20.95 0 590.08 364.51 54931 +1959 149 18.95 12.95 17.3 0 481.77 377.68 55034 +1959 150 19.65 13.65 18 0.03 501.12 281.81 55134 +1959 151 22.37 16.37 20.72 0.29 582.7 274.81 55229 +1959 152 26 20 24.35 1.45 708.9 263.26 55321 +1959 153 25.9 19.9 24.25 1.05 705.14 263.79 55409 +1959 154 23.71 17.71 22.06 0.48 626.86 271.27 55492 +1959 155 22.61 16.61 20.96 0.76 590.41 274.73 55572 +1959 156 23.14 17.14 21.49 0.56 607.74 273.39 55648 +1959 157 19.25 13.25 17.6 0.48 489.98 284.08 55719 +1959 158 17.63 11.63 15.98 0 447.01 383.97 55786 +1959 159 20.54 14.54 18.89 0.67 526.67 281.14 55849 +1959 160 21.43 15.43 19.78 0.92 553.32 278.89 55908 +1959 161 22.94 16.94 21.29 0.96 601.15 274.6 55962 +1959 162 18.24 12.24 16.59 0.17 462.8 287.02 56011 +1959 163 11.79 5.79 10.14 0.51 317.68 299.5 56056 +1959 164 13.74 7.74 12.09 0.29 356.73 296.29 56097 +1959 165 17.59 11.59 15.94 0 446 385 56133 +1959 166 13.49 7.49 11.84 0.29 351.51 296.86 56165 +1959 167 13.92 7.92 12.27 0 360.53 394.76 56192 +1959 168 15.69 9.69 14.04 0 399.82 390.41 56214 +1959 169 17.84 11.84 16.19 0.03 452.4 288.28 56231 +1959 170 19.99 13.99 18.34 0 510.75 377.52 56244 +1959 171 23.12 17.12 21.47 0.4 607.08 274.49 56252 +1959 172 17.56 11.56 15.91 0.03 445.23 288.94 56256 +1959 173 21.04 15.04 19.39 1.4 541.5 280.42 56255 +1959 174 23.92 17.92 22.27 1.71 634.03 271.93 56249 +1959 175 25.42 19.42 23.77 0.68 687.31 266.96 56238 +1959 176 24.92 18.92 23.27 0.57 669.14 268.63 56223 +1959 177 22 16 20.35 0.52 570.98 277.57 56203 +1959 178 20.23 14.23 18.58 0.2 517.65 282.38 56179 +1959 179 20.29 14.29 18.64 0.43 519.38 282.15 56150 +1959 180 22.46 16.46 20.81 0.05 585.58 276.1 56116 +1959 181 22.02 16.02 20.37 1.08 571.61 277.32 56078 +1959 182 28.92 22.92 27.27 0.7 826.53 253.35 56035 +1959 183 28.29 22.29 26.64 2.4 799.85 255.79 55987 +1959 184 24.36 18.36 22.71 0.01 649.28 269.86 55935 +1959 185 23.97 17.97 22.32 0 635.75 361.4 55879 +1959 186 22.22 16.22 20.57 0.06 577.92 276.14 55818 +1959 187 18.92 12.92 17.27 0 480.96 379.53 55753 +1959 188 20.07 14.07 18.42 0 513.04 375.49 55684 +1959 189 17.55 11.55 15.9 0.05 444.98 287.44 55611 +1959 190 20.73 14.73 19.08 0 532.26 372.66 55533 +1959 191 16.05 10.05 14.4 0.46 408.24 290.11 55451 +1959 192 21.63 15.63 19.98 0.38 559.46 276.64 55366 +1959 193 20.54 14.54 18.89 2.08 526.67 279.36 55276 +1959 194 22.03 16.03 20.38 0.14 571.92 275.15 55182 +1959 195 22.62 16.62 20.97 0.04 590.73 273.25 55085 +1959 196 26.07 20.07 24.42 0.02 711.55 261.85 54984 +1959 197 25.48 19.48 23.83 1.25 689.52 263.57 54879 +1959 198 27.71 21.71 26.06 0.08 775.93 255.17 54770 +1959 199 29.52 23.52 27.87 0.13 852.64 247.62 54658 +1959 200 32.12 26.12 30.47 0 973.94 314.09 54542 +1959 201 32.09 26.09 30.44 0.01 972.46 235.4 54423 +1959 202 29.51 23.51 27.86 0.03 852.2 246.67 54301 +1959 203 21.97 15.97 20.32 0 570.04 363.28 54176 +1959 204 21.27 15.27 19.62 0.7 548.44 274.01 54047 +1959 205 23 17 21.35 0.09 603.12 268.74 53915 +1959 206 21.9 15.9 20.25 0 567.85 361.97 53780 +1959 207 19.07 13.07 17.42 1.08 485.04 278.25 53643 +1959 208 16.95 10.95 15.3 0.74 429.96 282.46 53502 +1959 209 22.96 16.96 21.31 0 601.8 356 53359 +1959 210 23.44 17.44 21.79 0.28 617.74 265.12 53213 +1959 211 21.31 15.31 19.66 0.43 549.66 270.59 53064 +1959 212 17.25 11.25 15.6 0.28 437.41 279.66 52913 +1959 213 18.26 12.26 16.61 0.24 463.33 276.88 52760 +1959 214 16.36 10.36 14.71 0 415.61 373.78 52604 +1959 215 19.19 13.19 17.54 0 488.33 364.9 52445 +1959 216 23.72 17.72 22.07 0 627.2 347.71 52285 +1959 217 18.52 12.52 16.87 0.14 470.21 273.77 52122 +1959 218 20.63 14.63 18.98 0 529.31 357.48 51958 +1959 219 19.83 13.83 18.18 0 506.2 359.08 51791 +1959 220 20.15 14.15 18.5 0 515.34 357.1 51622 +1959 221 18.01 12.01 16.36 0.27 456.79 272.02 51451 +1959 222 16.84 10.84 15.19 0.1 427.25 273.67 51279 +1959 223 19.12 13.12 17.47 0.63 486.41 267.88 51105 +1959 224 17.98 11.98 16.33 0 456.02 359.49 50929 +1959 225 22.56 16.56 20.91 0.02 588.79 257.5 50751 +1959 226 20.87 14.87 19.22 0.33 536.42 261.14 50572 +1959 227 22.64 16.64 20.99 0 591.38 340.67 50392 +1959 228 23.75 17.75 22.1 0 628.22 335.24 50210 +1959 229 22.84 16.84 21.19 0.41 597.88 253.14 50026 +1959 230 21.52 15.52 19.87 0.73 556.07 255.76 49842 +1959 231 22.76 16.76 21.11 0.03 595.27 251.36 49656 +1959 232 21.95 15.95 20.3 0 569.41 336.74 49469 +1959 233 23.43 17.43 21.78 0 617.4 329.93 49280 +1959 234 24.12 18.12 22.47 0 640.93 325.89 49091 +1959 235 24.92 18.92 23.27 0 669.14 321.24 48900 +1959 236 22.66 16.66 21.01 1.05 592.02 246.44 48709 +1959 237 22.08 16.08 20.43 0 573.49 329.03 48516 +1959 238 24.84 18.84 23.19 0 666.28 317.03 48323 +1959 239 24.49 18.49 22.84 0 653.85 316.99 48128 +1959 240 21.26 15.26 19.61 0 548.14 326.96 47933 +1959 241 23.33 17.33 21.68 0.24 614.06 238.55 47737 +1959 242 21.2 15.2 19.55 0.46 546.32 242.82 47541 +1959 243 23.96 17.96 22.31 0 635.41 312.25 47343 +1959 244 19.27 13.27 17.62 0 490.54 326.04 47145 +1959 245 18.37 12.37 16.72 0 466.23 326.74 46947 +1959 246 18.51 12.51 16.86 0 469.94 324.39 46747 +1959 247 20.21 14.21 18.56 0 517.07 317.66 46547 +1959 248 19.97 13.97 18.32 0 510.18 316.46 46347 +1959 249 20.24 14.24 18.59 0 517.94 313.62 46146 +1959 250 16.01 10.01 14.36 0.17 407.3 242.16 45945 +1959 251 13.09 7.09 11.44 0.27 343.28 245.22 45743 +1959 252 11.86 5.86 10.21 0 319.01 327.04 45541 +1959 253 11.54 5.54 9.89 0 312.94 325.43 45339 +1959 254 12.27 6.27 10.62 0 326.93 321.93 45136 +1959 255 12.39 6.39 10.74 0.01 329.28 239.55 44933 +1959 256 17.56 11.56 15.91 0 445.23 306.06 44730 +1959 257 19.82 13.82 18.17 0 505.92 297.97 44527 +1959 258 19.35 13.35 17.7 0 492.75 296.96 44323 +1959 259 20.01 14.01 18.36 0 511.32 292.75 44119 +1959 260 21.42 15.42 19.77 0.34 553.01 214.75 43915 +1959 261 19.78 13.78 18.13 0.4 504.78 216.49 43711 +1959 262 23.22 17.22 21.57 0.01 610.39 207.03 43507 +1959 263 20.91 14.91 19.26 0.09 537.61 210.59 43303 +1959 264 18.02 12.02 16.37 0.14 457.05 214.42 43099 +1959 265 15.28 9.28 13.63 0.01 390.41 217.23 42894 +1959 266 14.42 8.42 12.77 0.4 371.28 216.65 42690 +1959 267 14.55 8.55 12.9 0 374.12 285.92 42486 +1959 268 13.42 7.42 11.77 0 350.05 285.44 42282 +1959 269 15.92 9.92 14.27 0 405.18 278.09 42078 +1959 270 15.61 9.61 13.96 0 397.97 276.1 41875 +1959 271 14.76 8.76 13.11 0 378.75 275.15 41671 +1959 272 16.26 10.26 14.61 0 413.22 269.45 41468 +1959 273 18.22 12.22 16.57 0 462.28 262.67 41265 +1959 274 15.75 9.75 14.1 0 401.21 265.31 41062 +1959 275 16.21 10.21 14.56 0 412.03 261.65 40860 +1959 276 13.99 7.99 12.34 0 362.02 263.14 40658 +1959 277 12.44 6.44 10.79 0 330.27 263.06 40456 +1959 278 17.66 11.66 16.01 0.1 447.78 187.9 40255 +1959 279 17.86 11.86 16.21 0 452.91 247.35 40054 +1959 280 19.6 13.6 17.95 0 499.72 240.86 39854 +1959 281 18.49 12.49 16.84 0 469.41 240.75 39654 +1959 282 18.63 12.63 16.98 0 473.14 237.79 39455 +1959 283 12.03 6.03 10.38 0 322.28 246.97 39256 +1959 284 9.12 3.12 7.47 0 270.17 247.83 39058 +1959 285 11.82 5.82 10.17 0.28 318.25 181.19 38861 +1959 286 10.69 4.69 9.04 0.03 297.3 180.27 38664 +1959 287 9.46 3.46 7.81 0 275.86 238.96 38468 +1959 288 10.17 4.17 8.52 0.17 288.07 176.45 38273 +1959 289 7.09 1.09 5.44 0 238.26 236.1 38079 +1959 290 7.15 1.15 5.5 0 239.16 233.13 37885 +1959 291 7.13 1.13 5.48 0 238.86 230.4 37693 +1959 292 7.65 1.65 6 0 246.72 227.13 37501 +1959 293 11.23 5.23 9.58 0 307.16 220.22 37311 +1959 294 14.42 8.42 12.77 0 371.28 212.84 37121 +1959 295 13.8 7.8 12.15 0 357.99 210.98 36933 +1959 296 11.71 5.71 10.06 0 316.16 211.29 36745 +1959 297 11.43 5.43 9.78 0 310.88 208.93 36560 +1959 298 10.61 4.61 8.96 0 295.87 207.32 36375 +1959 299 11.28 5.28 9.63 0 308.09 203.74 36191 +1959 300 10.92 4.92 9.27 0 301.47 201.51 36009 +1959 301 5.34 -0.66 3.69 0.35 213.41 153.39 35829 +1959 302 9.03 3.03 7.38 0 268.69 198.46 35650 +1959 303 9.77 3.77 8.12 0 281.14 195.1 35472 +1959 304 13.85 7.85 12.2 0.02 359.05 140.78 35296 +1959 305 8.24 2.24 6.59 0.03 255.92 143.57 35122 +1959 306 13.87 7.87 12.22 0 359.47 182.77 34950 +1959 307 10.92 4.92 9.27 0 301.47 183.9 34779 +1959 308 9.97 3.97 8.32 0.25 284.59 136.75 34610 +1959 309 9.79 3.79 8.14 0.67 281.48 135.16 34444 +1959 310 11.13 5.13 9.48 0 305.31 176.37 34279 +1959 311 12.38 6.38 10.73 0 329.09 172.8 34116 +1959 312 14.35 8.35 12.7 0.01 369.76 125.83 33956 +1959 313 13.81 7.81 12.16 0.35 358.21 124.8 33797 +1959 314 13.37 7.37 11.72 0.02 349.02 123.78 33641 +1959 315 14.04 8.04 12.39 0.1 363.09 121.3 33488 +1959 316 9.64 3.64 7.99 0.17 278.91 123.29 33337 +1959 317 4.99 -1.01 3.34 0.32 208.72 124.49 33188 +1959 318 3.5 -2.5 1.85 0 189.71 164.62 33042 +1959 319 5.1 -0.9 3.45 0 210.18 161.85 32899 +1959 320 1.96 -4.04 0.31 0.15 171.66 121.44 32758 +1959 321 -2.78 -8.78 -4.43 0 125.07 162.02 32620 +1959 322 1.55 -4.45 -0.1 0 167.11 158.15 32486 +1959 323 4.45 -1.55 2.8 0 201.65 154.82 32354 +1959 324 4.71 -1.29 3.06 0 205.02 152.59 32225 +1959 325 3.27 -2.73 1.62 0 186.92 151.74 32100 +1959 326 7.07 1.07 5.42 0 237.97 147.77 31977 +1959 327 11.05 5.05 9.4 0 303.84 142.59 31858 +1959 328 7.15 1.15 5.5 0 239.16 143.9 31743 +1959 329 5.37 -0.63 3.72 0.53 213.82 107.73 31631 +1959 330 6.96 0.96 5.31 0.03 236.34 105.83 31522 +1959 331 7.73 1.73 6.08 0 247.95 139.24 31417 +1959 332 7.93 1.93 6.28 0.45 251.05 103.09 31316 +1959 333 7.17 1.17 5.52 0 239.46 136.93 31218 +1959 334 11.23 5.23 9.58 0 307.16 132.57 31125 +1959 335 11.5 5.5 9.85 0.32 312.19 98.38 31035 +1959 336 9.48 3.48 7.83 0.13 276.2 98.9 30949 +1959 337 10.06 4.06 8.41 0 286.15 129.75 30867 +1959 338 9.06 3.06 7.41 0 269.18 129.63 30790 +1959 339 10.94 4.94 9.29 0 301.83 127.31 30716 +1959 340 8.27 2.27 6.62 0 256.39 128.73 30647 +1959 341 10.67 4.67 9.02 0.08 296.95 94.44 30582 +1959 342 6 0 4.35 1.81 222.51 96.46 30521 +1959 343 7.26 1.26 5.61 1.65 240.81 95.22 30465 +1959 344 5.77 -0.23 4.12 0.25 219.3 95.11 30413 +1959 345 6.63 0.63 4.98 0 231.5 125.84 30366 +1959 346 6.52 0.52 4.87 0.08 229.91 94.02 30323 +1959 347 6.63 0.63 4.98 0.36 231.5 93.52 30284 +1959 348 1.27 -4.73 -0.38 0 164.07 127.28 30251 +1959 349 0.02 -5.98 -1.63 0.34 151.05 95.58 30221 +1959 350 -1.09 -7.09 -2.74 0 140.24 127.54 30197 +1959 351 1.5 -4.5 -0.15 0 166.57 126.23 30177 +1959 352 5.07 -0.93 3.42 0 209.78 124.29 30162 +1959 353 4.87 -1.13 3.22 0 207.13 124.34 30151 +1959 354 6.47 0.47 4.82 0.06 229.19 92.5 30145 +1959 355 2.31 -3.69 0.66 3.83 175.63 94.24 30144 +1959 356 3 -3 1.35 1.24 183.68 94 30147 +1959 357 7.38 1.38 5.73 0.08 242.61 92.12 30156 +1959 358 2.73 -3.27 1.08 0 180.49 125.62 30169 +1959 359 6.82 0.82 5.17 0 234.27 123.4 30186 +1959 360 8.68 2.68 7.03 0.01 262.96 91.85 30208 +1959 361 7.14 1.14 5.49 0 239.01 123.88 30235 +1959 362 9.76 3.76 8.11 0.03 280.97 91.81 30267 +1959 363 4.56 -1.44 2.91 0.16 203.07 94.87 30303 +1959 364 6.49 0.49 4.84 0.04 229.48 94.28 30343 +1959 365 4.26 -1.74 2.61 0.42 199.21 95.71 30388 +1960 1 0.56 -5.44 -1.09 0.02 156.56 97.76 30438 +1960 2 -1.14 -7.14 -2.79 0.14 139.77 142.58 30492 +1960 3 -3.07 -9.07 -4.72 0 122.62 177.11 30551 +1960 4 -4.9 -10.9 -6.55 0 108.07 178.54 30614 +1960 5 -3.14 -9.14 -4.79 0 122.03 178.53 30681 +1960 6 -1.9 -7.9 -3.55 0.2 132.78 145.63 30752 +1960 7 1.89 -4.11 0.24 0 170.88 178.31 30828 +1960 8 4.28 -1.72 2.63 0 199.47 177.85 30907 +1960 9 3 -3 1.35 0 183.68 136.86 30991 +1960 10 0.17 -5.83 -1.48 0 152.56 139.56 31079 +1960 11 -0.53 -6.53 -2.18 0 145.6 140.86 31171 +1960 12 1.97 -4.03 0.32 0.32 171.77 105.53 31266 +1960 13 3.18 -2.82 1.53 0.09 185.83 106.27 31366 +1960 14 -0.63 -6.63 -2.28 0 144.63 145.06 31469 +1960 15 3.48 -2.52 1.83 0 189.47 144.45 31575 +1960 16 4.29 -1.71 2.64 0 199.59 145.25 31686 +1960 17 2.61 -3.39 0.96 0 179.09 147.91 31800 +1960 18 5.16 -0.84 3.51 0 210.98 148.28 31917 +1960 19 -1.08 -7.08 -2.73 0.05 140.33 156.53 32038 +1960 20 -1.35 -7.35 -3 0.05 137.81 157.82 32161 +1960 21 -0.68 -6.68 -2.33 0 144.15 198.21 32289 +1960 22 -0.9 -6.9 -2.55 1.9 142.04 165.81 32419 +1960 23 3.42 -2.58 1.77 0 188.74 204.43 32552 +1960 24 0.21 -5.79 -1.44 0 152.96 208.06 32688 +1960 25 1.47 -4.53 -0.18 0 166.24 208.93 32827 +1960 26 6.31 0.31 4.66 0 226.89 206.78 32969 +1960 27 5.05 -0.95 3.4 0 209.51 208.9 33114 +1960 28 2.9 -3.1 1.25 0.15 182.5 169.75 33261 +1960 29 2.84 -3.16 1.19 0.41 181.79 171.04 33411 +1960 30 8.32 2.32 6.67 0.03 257.19 168.46 33564 +1960 31 9.55 3.55 7.9 0 277.38 210.69 33718 +1960 32 8.46 2.46 6.81 0.36 259.42 130.31 33875 +1960 33 4.95 -1.05 3.3 0 208.18 179.22 34035 +1960 34 4.08 -1.92 2.43 0 196.93 182.05 34196 +1960 35 2.84 -3.16 1.19 0.35 181.79 138.78 34360 +1960 36 -1.67 -7.67 -3.32 0 134.87 190.12 34526 +1960 37 -0.21 -6.21 -1.86 0 148.75 191.82 34694 +1960 38 1.73 -4.27 0.08 0 169.1 193.46 34863 +1960 39 0.06 -5.94 -1.59 0 151.45 197.08 35035 +1960 40 1.27 -4.73 -0.38 0 164.07 199.01 35208 +1960 41 4.06 -1.94 2.41 1.15 196.67 149.82 35383 +1960 42 0.82 -5.18 -0.83 0 159.27 204.51 35560 +1960 43 6.28 0.28 4.63 0 226.47 203.21 35738 +1960 44 0.09 -5.91 -1.56 0 151.75 210.27 35918 +1960 45 -4.83 -10.83 -6.48 0 108.6 215.4 36099 +1960 46 0.26 -5.74 -1.39 0.42 153.47 161.65 36282 +1960 47 4.36 -1.64 2.71 0 200.49 215.51 36466 +1960 48 6.72 0.72 5.07 0.67 232.81 162.19 36652 +1960 49 9.64 3.64 7.99 0 278.91 215.97 36838 +1960 50 7.05 1.05 5.4 0 237.67 221.36 37026 +1960 51 4.72 -1.28 3.07 0 205.16 226.45 37215 +1960 52 0.3 -5.7 -1.35 0 153.88 232.58 37405 +1960 53 3.37 -2.63 1.72 0 188.13 233.37 37596 +1960 54 5 -1 3.35 0 208.85 234.77 37788 +1960 55 10.94 4.94 9.29 0 301.83 231.27 37981 +1960 56 11.15 5.15 9.5 0 305.68 233.64 38175 +1960 57 8.05 2.05 6.4 0 252.93 240.27 38370 +1960 58 6.59 0.59 4.94 0 230.92 244.75 38565 +1960 59 5.1 -0.9 3.45 0 210.18 248.92 38761 +1960 60 11.62 5.62 9.97 0.02 314.45 183.14 38958 +1960 61 7.81 1.81 6.16 0.24 249.19 188.95 39156 +1960 62 8.85 2.85 7.2 0 265.73 253.49 39355 +1960 63 7.4 1.4 5.75 0 242.92 258.18 39553 +1960 64 8.29 2.29 6.64 0.01 256.71 195.03 39753 +1960 65 10.28 4.28 8.63 0 290 260.36 39953 +1960 66 11.63 5.63 9.98 1.55 314.64 195.84 40154 +1960 67 7.45 1.45 5.8 1.42 243.67 202.15 40355 +1960 68 4.23 -1.77 2.58 0.78 198.83 206.86 40556 +1960 69 1.3 -4.7 -0.35 0.63 164.39 210.76 40758 +1960 70 -0.47 -6.47 -2.12 0.22 146.19 246.67 40960 +1960 71 5.54 -0.46 3.89 0 216.13 282.94 41163 +1960 72 9.54 3.54 7.89 0.21 277.21 210.68 41366 +1960 73 12.69 6.69 11.04 0 335.22 278.74 41569 +1960 74 9.5 3.5 7.85 0 276.54 286.35 41772 +1960 75 10.7 4.7 9.05 0 297.48 287.31 41976 +1960 76 9.3 3.3 7.65 0 273.17 291.97 42179 +1960 77 8.38 2.38 6.73 0.01 258.14 221.86 42383 +1960 78 7.28 1.28 5.63 0 241.11 299.9 42587 +1960 79 7.11 1.11 5.46 0 238.56 302.84 42791 +1960 80 8.34 2.34 6.69 0.01 257.5 227.85 42996 +1960 81 12.55 6.55 10.9 0 332.44 299.84 43200 +1960 82 9.5 3.5 7.85 0 276.54 307.39 43404 +1960 83 12.82 6.82 11.17 0 337.82 304.42 43608 +1960 84 11.92 5.92 10.27 0.07 320.16 231.39 43812 +1960 85 10.2 4.2 8.55 0 288.6 313.83 44016 +1960 86 8.76 2.76 7.11 0.03 264.26 238.8 44220 +1960 87 7.77 1.77 6.12 0.23 248.57 241.74 44424 +1960 88 8.17 2.17 6.52 0 254.81 324.13 44627 +1960 89 6.05 0.05 4.4 0 223.21 329.21 44831 +1960 90 8.6 2.6 6.95 0 261.67 328.18 45034 +1960 91 10.25 4.25 8.6 0 289.48 327.9 45237 +1960 92 9.11 3.11 7.46 0.56 270.01 248.96 45439 +1960 93 10.67 4.67 9.02 0.21 296.95 248.75 45642 +1960 94 12.2 6.2 10.55 0 325.57 331.1 45843 +1960 95 11.4 5.4 9.75 0.01 310.32 251.02 46045 +1960 96 10.73 4.73 9.08 0 298.03 337.97 46246 +1960 97 13.15 7.15 11.5 0.01 344.5 251.65 46446 +1960 98 14.91 8.91 13.26 0 382.08 333.76 46647 +1960 99 14.97 8.97 13.32 0 383.42 335.6 46846 +1960 100 11.87 5.87 10.22 0 319.2 343.9 47045 +1960 101 6.07 0.07 4.42 1.01 223.49 266.23 47243 +1960 102 9.11 3.11 7.46 0 270.01 352.52 47441 +1960 103 5.62 -0.38 3.97 0 217.23 359.38 47638 +1960 104 6.66 0.66 5.01 0 231.94 359.86 47834 +1960 105 13.42 7.42 11.77 0 350.05 350.08 48030 +1960 106 13.88 7.88 12.23 0 359.69 350.74 48225 +1960 107 17.95 11.95 16.3 0 455.24 342.4 48419 +1960 108 18.13 12.13 16.48 0 459.92 343.59 48612 +1960 109 15.56 9.56 13.91 0 396.81 351.86 48804 +1960 110 14.95 8.95 13.3 0 382.97 354.71 48995 +1960 111 17.45 11.45 15.8 0 442.44 349.92 49185 +1960 112 15.62 9.62 13.97 0 398.2 356.14 49374 +1960 113 19.08 13.08 17.43 0 485.32 348.03 49561 +1960 114 13.24 7.24 11.59 0 346.35 364.41 49748 +1960 115 13.12 7.12 11.47 0 343.89 366.09 49933 +1960 116 15.49 9.49 13.84 0.07 395.2 271.41 50117 +1960 117 12.75 6.75 11.1 0 336.42 369.41 50300 +1960 118 11.45 5.45 9.8 0 311.26 373.36 50481 +1960 119 11.55 5.55 9.9 0 313.13 374.37 50661 +1960 120 13.14 7.14 11.49 0 344.3 372.28 50840 +1960 121 19.78 13.78 18.13 0.16 504.78 266.85 51016 +1960 122 17.47 11.47 15.82 0 442.95 363.89 51191 +1960 123 21.22 15.22 19.57 0 546.93 353.13 51365 +1960 124 21.87 15.87 20.22 0.01 566.91 263.9 51536 +1960 125 18.93 12.93 17.28 0.09 481.23 271.98 51706 +1960 126 17.05 11.05 15.4 0 432.43 369.09 51874 +1960 127 18.23 12.23 16.58 0.07 462.54 274.95 52039 +1960 128 18.7 12.7 17.05 0.15 475.02 274.62 52203 +1960 129 18.37 12.37 16.72 0 466.23 368 52365 +1960 130 18.15 12.15 16.5 0.04 460.44 277.07 52524 +1960 131 18.64 12.64 16.99 0 473.41 368.74 52681 +1960 132 19.68 13.68 18.03 0 501.96 366.27 52836 +1960 133 17.31 11.31 15.66 0.3 438.92 280.63 52989 +1960 134 15.2 9.2 13.55 0 388.59 380.51 53138 +1960 135 12.55 6.55 10.9 0 332.44 387.37 53286 +1960 136 13.34 7.34 11.69 0.65 348.4 289.71 53430 +1960 137 12.39 6.39 10.74 0.06 329.28 291.8 53572 +1960 138 14.01 8.01 12.36 0 362.45 386.06 53711 +1960 139 11.49 5.49 9.84 0.12 312.01 294.19 53848 +1960 140 10.42 4.42 8.77 0 292.48 394.85 53981 +1960 141 9.88 3.88 8.23 0.01 283.03 297.23 54111 +1960 142 14.11 8.11 12.46 0.05 364.59 290.98 54238 +1960 143 16.14 10.14 14.49 0.05 410.37 287.54 54362 +1960 144 14.87 8.87 13.22 0.83 381.19 290.36 54483 +1960 145 15.07 9.07 13.42 0.19 385.66 290.34 54600 +1960 146 16.59 10.59 14.94 0.03 421.16 287.62 54714 +1960 147 15.54 9.54 13.89 0.83 396.35 290.09 54824 +1960 148 17.06 11.06 15.41 0 432.68 383.04 54931 +1960 149 20.8 14.8 19.15 0 534.34 371.49 55034 +1960 150 18.05 12.05 16.4 0 457.83 380.79 55134 +1960 151 20.97 14.97 19.32 0 539.4 371.6 55229 +1960 152 24.36 18.36 22.71 1.48 649.28 268.8 55321 +1960 153 24.53 18.53 22.88 0 655.26 357.9 55409 +1960 154 24.49 18.49 22.84 0.43 653.85 268.78 55492 +1960 155 20.12 14.12 18.47 0.38 514.48 281.55 55572 +1960 156 20.79 14.79 19.14 0.16 534.04 280.05 55648 +1960 157 22.13 16.13 20.48 0 575.07 368.65 55719 +1960 158 24.84 18.84 23.19 0 666.28 357.66 55786 +1960 159 27.52 21.52 25.87 0 768.23 345.11 55849 +1960 160 28.02 22.02 26.37 0 788.64 342.69 55908 +1960 161 25.43 19.43 23.78 0.66 687.68 266.61 55962 +1960 162 24.07 18.07 22.42 0.08 639.2 271.15 56011 +1960 163 21.63 15.63 19.98 0 559.46 371.45 56056 +1960 164 22.1 16.1 20.45 0 574.13 369.73 56097 +1960 165 25.65 19.65 24 0 695.8 354.86 56133 +1960 166 21.52 15.52 19.87 0 556.07 372.07 56165 +1960 167 17.41 11.41 15.76 0 441.43 385.55 56192 +1960 168 17.27 11.27 15.62 0.16 437.91 289.53 56214 +1960 169 15.19 9.19 13.54 0.37 388.37 293.79 56231 +1960 170 17.77 11.77 16.12 0.28 450.6 288.44 56244 +1960 171 19.01 13.01 17.36 0.76 483.41 285.61 56252 +1960 172 23.39 17.39 21.74 0.24 616.06 273.66 56256 +1960 173 21.85 15.85 20.2 1.11 566.28 278.18 56255 +1960 174 21.02 15.02 19.37 0.41 540.9 280.41 56249 +1960 175 20.32 14.32 18.67 0.08 520.25 282.24 56238 +1960 176 16.56 10.56 14.91 0 420.43 387.94 56223 +1960 177 19.19 13.19 17.54 0 488.33 379.95 56203 +1960 178 21.23 15.23 19.58 0.17 547.23 279.74 56179 +1960 179 21.67 15.67 20.02 0.24 560.7 278.45 56150 +1960 180 18.29 12.29 16.64 0.34 464.12 286.94 56116 +1960 181 16.41 10.41 14.76 0.01 416.81 290.98 56078 +1960 182 15.64 9.64 13.99 0 398.66 389.9 56035 +1960 183 19.6 13.6 17.95 0 499.72 378.01 55987 +1960 184 22.87 16.87 21.22 0.47 598.86 274.49 55935 +1960 185 22.09 16.09 20.44 0 573.81 368.94 55879 +1960 186 24.52 18.52 22.87 0.28 654.91 269.09 55818 +1960 187 21.9 15.9 20.25 0.13 567.85 276.91 55753 +1960 188 21.24 15.24 19.59 0.51 547.53 278.54 55684 +1960 189 18.69 12.69 17.04 0.83 474.75 284.85 55611 +1960 190 17.42 11.42 15.77 1.11 441.69 287.45 55533 +1960 191 18.81 12.81 17.16 2.15 477.98 284.09 55451 +1960 192 19.2 13.2 17.55 1.66 488.61 282.93 55366 +1960 193 15.88 9.88 14.23 0.26 404.24 290.01 55276 +1960 194 20.75 14.75 19.1 0.62 532.86 278.65 55182 +1960 195 24.08 18.08 22.43 0.26 639.54 268.81 55085 +1960 196 25.73 19.73 24.08 0.2 698.78 263.04 54984 +1960 197 27.48 21.48 25.83 0.39 766.62 256.35 54879 +1960 198 24.93 18.93 23.28 0.02 669.5 265.11 54770 +1960 199 27.32 21.32 25.67 0.05 760.19 256.41 54658 +1960 200 22.53 16.53 20.88 0 587.83 362.68 54542 +1960 201 21.81 15.81 20.16 0.09 565.04 273.7 54423 +1960 202 22.34 16.34 20.69 0.32 581.74 271.79 54301 +1960 203 20.41 14.41 18.76 0.45 522.87 276.64 54176 +1960 204 19.29 13.29 17.64 0.4 491.09 279.04 54047 +1960 205 18.46 12.46 16.81 0.18 468.61 280.59 53915 +1960 206 18.2 12.2 16.55 0.56 461.75 280.76 53780 +1960 207 17.78 11.78 16.13 0.03 450.85 281.19 53643 +1960 208 19.47 13.47 17.82 0 496.08 369.07 53502 +1960 209 18.64 12.64 16.99 0 473.41 371.02 53359 +1960 210 19.27 13.27 17.62 0 490.54 368.42 53213 +1960 211 21.49 15.49 19.84 0.11 555.15 270.11 53064 +1960 212 21.12 15.12 19.47 1.31 543.91 270.5 52913 +1960 213 22.75 16.75 21.1 0.46 594.94 265.44 52760 +1960 214 19.91 13.91 18.26 0 508.47 363.27 52604 +1960 215 21.06 15.06 19.41 0 542.1 358.71 52445 +1960 216 19.6 13.6 17.95 0.08 499.72 271.93 52285 +1960 217 17.59 11.59 15.94 0.05 446 275.81 52122 +1960 218 17.51 11.51 15.86 0.01 443.96 275.36 51958 +1960 219 15.97 9.97 14.32 0 406.36 370.25 51791 +1960 220 17.71 11.71 16.06 0 449.06 364.56 51622 +1960 221 20.67 14.67 19.02 0.08 530.49 265.78 51451 +1960 222 21.9 15.9 20.25 1.18 567.85 261.78 51279 +1960 223 20.5 14.5 18.85 0 525.5 352.76 51105 +1960 224 20.6 14.6 18.95 0 528.43 351.37 50929 +1960 225 24.48 18.48 22.83 0.1 653.5 251.86 50751 +1960 226 27.82 21.82 26.17 1.69 780.42 239.71 50572 +1960 227 27.09 21.09 25.44 0.58 751.04 241.46 50392 +1960 228 23.9 17.9 22.25 0.02 633.35 250.99 50210 +1960 229 24.8 18.8 23.15 0 664.85 329.8 50026 +1960 230 26.47 20.47 24.82 0.22 726.82 241 49842 +1960 231 26.04 20.04 24.39 0 710.41 321.86 49656 +1960 232 24.02 18.02 22.37 0.18 637.47 246.76 49469 +1960 233 27.02 21.02 25.37 0.35 748.27 236.11 49280 +1960 234 25.72 19.72 24.07 0.9 698.41 239.47 49091 +1960 235 24.9 18.9 23.25 0.73 668.43 240.99 48900 +1960 236 21.32 15.32 19.67 0.82 549.96 249.94 48709 +1960 237 18.06 12.06 16.41 0 458.09 341.57 48516 +1960 238 19.11 13.11 17.46 0 486.14 336.9 48323 +1960 239 22.05 16.05 20.4 0 572.55 326.02 48128 +1960 240 18.49 12.49 16.84 0 469.41 335.4 47933 +1960 241 19.61 13.61 17.96 0.01 500 247.83 47737 +1960 242 20.47 14.47 18.82 0.06 524.62 244.56 47541 +1960 243 24.67 18.67 23.02 0.09 660.22 232.13 47343 +1960 244 20.14 14.14 18.49 1.11 515.05 242.59 47145 +1960 245 15.33 9.33 13.68 0.85 391.55 250.77 46947 +1960 246 14.97 8.97 13.32 0.18 383.42 249.88 46747 +1960 247 13.65 7.65 12 0.69 354.84 250.58 46547 +1960 248 14.99 8.99 13.34 1.28 383.87 246.95 46347 +1960 249 17.04 11.04 15.39 0.32 432.18 241.77 46146 +1960 250 17.44 11.44 15.79 0.04 442.19 239.55 45945 +1960 251 18.06 12.06 16.41 0 458.09 315.69 45743 +1960 252 20.52 14.52 18.87 0.66 526.08 230 45541 +1960 253 21.25 15.25 19.6 1.71 547.84 226.78 45339 +1960 254 15.82 9.82 14.17 0.19 402.84 236.03 45136 +1960 255 20.16 14.16 18.51 0 515.63 301.35 44933 +1960 256 18.39 12.39 16.74 0 466.76 303.96 44730 +1960 257 14.71 8.71 13.06 0 377.64 310.35 44527 +1960 258 15.38 9.38 13.73 0.25 392.69 229.93 44323 +1960 259 13.5 7.5 11.85 0.51 351.71 230.94 44119 +1960 260 10.46 4.46 8.81 0 293.19 310.78 43915 +1960 261 13.03 7.03 11.38 0 342.06 303.89 43711 +1960 262 14.89 8.89 13.24 0 381.63 297.89 43507 +1960 263 15.85 9.85 14.2 0.21 403.54 220.05 43303 +1960 264 17.52 11.52 15.87 0.64 444.22 215.32 43099 +1960 265 14.1 8.1 12.45 0 364.37 291.98 42894 +1960 266 10.76 4.76 9.11 0.04 298.57 221.41 42690 +1960 267 14.96 8.96 13.31 0 383.2 285.12 42486 +1960 268 17.7 11.7 16.05 0 448.8 276.69 42282 +1960 269 22.6 16.6 20.95 0 590.08 261.21 42078 +1960 270 26.09 20.09 24.44 0 712.3 247.1 41875 +1960 271 25.48 19.48 23.83 0 689.52 246.86 41671 +1960 272 22.76 16.76 21.11 0 595.27 253.14 41468 +1960 273 26.43 20.43 24.78 1 725.28 178.98 41265 +1960 274 21.6 15.6 19.95 0.41 558.54 188.65 41062 +1960 275 20.06 14.06 18.41 0.01 512.76 189.71 40860 +1960 276 17.36 11.36 15.71 0 440.17 256.6 40658 +1960 277 13.92 7.92 12.27 0 360.53 260.6 40456 +1960 278 16.19 10.19 14.54 0 411.56 253.55 40255 +1960 279 18.12 12.12 16.47 0 459.66 246.79 40054 +1960 280 19.64 13.64 17.99 0.09 500.84 180.57 39854 +1960 281 19.66 13.66 18.01 1.6 501.4 178.57 39654 +1960 282 18.01 12.01 16.36 0.94 456.79 179.34 39455 +1960 283 14.02 8.02 12.37 0.04 362.66 182.89 39256 +1960 284 14.25 8.25 12.6 0.32 367.6 180.35 39058 +1960 285 12.26 6.26 10.61 0.85 326.74 180.71 38861 +1960 286 9.76 3.76 8.11 0.21 280.97 181.17 38664 +1960 287 3.48 -2.52 1.83 0 189.47 245 38468 +1960 288 5.06 -0.94 3.41 0 209.65 240.77 38273 +1960 289 7.99 1.99 6.34 0 251.99 235.15 38079 +1960 290 7.48 1.48 5.83 0.06 244.13 174.59 37885 +1960 291 9.97 3.97 8.32 1.03 284.59 170.43 37693 +1960 292 10.44 4.44 8.79 0.15 292.83 167.97 37501 +1960 293 12.14 6.14 10.49 0.25 324.4 164.26 37311 +1960 294 15.04 9.04 13.39 0.19 384.99 158.9 37121 +1960 295 16.22 10.22 14.57 0 412.27 207.13 36933 +1960 296 19.87 13.87 18.22 0.1 507.33 148.3 36745 +1960 297 16.85 10.85 15.2 0 427.5 200.87 36560 +1960 298 18.25 12.25 16.6 0 463.06 195.83 36375 +1960 299 19.25 13.25 17.6 0 489.98 191.25 36191 +1960 300 20.05 14.05 18.4 0 512.47 187.11 36009 +1960 301 17.91 11.91 16.26 0.25 454.2 141.59 35829 +1960 302 14.43 8.43 12.78 1.17 371.5 143.88 35650 +1960 303 10.46 4.46 8.81 0 293.19 194.34 35472 +1960 304 11.77 5.77 10.12 0 317.3 190.37 35296 +1960 305 7.89 1.89 6.24 0 250.43 191.76 35122 +1960 306 11.46 5.46 9.81 0.58 311.44 139.34 34950 +1960 307 9.72 3.72 8.07 0.43 280.28 138.89 34779 +1960 308 7.81 1.81 6.16 0.05 249.19 138.32 34610 +1960 309 10.21 4.21 8.56 0 288.77 179.78 34444 +1960 310 12.08 6.08 10.43 0 323.24 175.3 34279 +1960 311 15.59 9.59 13.94 0 397.51 168.66 34116 +1960 312 18.3 12.3 16.65 0 464.38 161.95 33956 +1960 313 21.78 15.78 20.13 0.11 564.11 115.24 33797 +1960 314 21.08 15.08 19.43 0 542.7 153.22 33641 +1960 315 19.11 13.11 17.46 0 486.14 154.35 33488 +1960 316 16.21 10.21 14.56 0.64 412.03 117.55 33337 +1960 317 14.56 8.56 12.91 0.19 374.34 117.62 33188 +1960 318 10.98 4.98 9.33 0.73 302.56 118.94 33042 +1960 319 9.31 3.31 7.66 1.03 273.34 118.88 32899 +1960 320 5.52 -0.48 3.87 0 215.86 159.68 32758 +1960 321 6.48 0.48 4.83 0 229.33 156.87 32620 +1960 322 0.2 -5.8 -1.45 0 152.86 158.84 32486 +1960 323 3.69 -2.31 2.04 0.02 192.05 116.47 32354 +1960 324 5.61 -0.39 3.96 1.83 217.09 113.99 32225 +1960 325 0.35 -5.65 -1.3 1.12 154.39 114.97 32100 +1960 326 2.96 -3.04 1.31 0.57 183.21 112.83 31977 +1960 327 3.91 -2.09 2.26 0.04 194.79 111.02 31858 +1960 328 6.15 0.15 4.5 0.3 224.62 108.46 31743 +1960 329 6.35 0.35 4.7 0.02 227.47 107.24 31631 +1960 330 9.91 3.91 8.26 0.02 283.55 104.09 31522 +1960 331 10.24 4.24 8.59 0 289.3 137.2 31417 +1960 332 9.59 3.59 7.94 0.48 278.06 102.1 31316 +1960 333 8.67 2.67 7.02 0 262.8 135.81 31218 +1960 334 7.67 1.67 6.02 0 247.03 135.48 31125 +1960 335 6.87 0.87 5.22 0 235.01 134.88 31035 +1960 336 5.99 -0.01 4.34 0 222.37 134.4 30949 +1960 337 0.54 -5.46 -1.11 0.97 156.35 101.78 30867 +1960 338 2.14 -3.86 0.49 1.31 173.69 100.5 30790 +1960 339 1.41 -4.59 -0.24 0.46 165.58 100.17 30716 +1960 340 4.39 -1.61 2.74 0.21 200.88 98.45 30647 +1960 341 7.7 1.7 6.05 0.09 247.49 96.17 30582 +1960 342 5.26 -0.74 3.61 0 212.33 129.07 30521 +1960 343 5.78 -0.22 4.13 0.03 219.44 95.95 30465 +1960 344 5.35 -0.65 3.7 0.03 213.54 95.3 30413 +1960 345 3.08 -2.92 1.43 0 184.64 127.9 30366 +1960 346 0.94 -5.06 -0.71 0 160.54 128.38 30323 +1960 347 6.1 0.1 4.45 0 223.91 125.04 30284 +1960 348 6.87 0.87 5.22 0.11 235.01 93.15 30251 +1960 349 7.48 1.48 5.83 0 244.13 123.41 30221 +1960 350 11.09 5.09 9.44 0 304.58 120.33 30197 +1960 351 9.71 3.71 8.06 0 280.11 121.24 30177 +1960 352 5.13 -0.87 3.48 0.03 210.58 93.19 30162 +1960 353 6.9 0.9 5.25 0 235.45 123.1 30151 +1960 354 4.81 -1.19 3.16 0.2 206.34 93.25 30145 +1960 355 5.99 -0.01 4.34 0 222.37 123.64 30144 +1960 356 6.87 0.87 5.22 0.07 235.01 92.33 30147 +1960 357 8.68 2.68 7.03 0 262.96 121.91 30156 +1960 358 5.7 -0.3 4.05 0.83 218.33 92.99 30169 +1960 359 6.61 0.61 4.96 0 231.21 123.53 30186 +1960 360 6.32 0.32 4.67 0 227.04 124.08 30208 +1960 361 8.65 2.65 7 0 262.48 122.82 30235 +1960 362 7.89 1.89 6.24 0 250.43 123.8 30267 +1960 363 6.09 0.09 4.44 0.21 223.77 94.18 30303 +1960 364 8.08 2.08 6.43 0.25 253.4 93.48 30343 +1960 365 8.2 2.2 6.55 0 255.28 125.11 30388 +1961 1 -1.98 -7.98 -3.63 0 132.07 131.38 30438 +1961 2 1.23 -4.77 -0.42 0 163.64 130.79 30492 +1961 3 -0.8 -6.8 -2.45 0.01 143 142.7 30551 +1961 4 0.47 -5.53 -1.18 0.06 155.63 99.75 30614 +1961 5 0.99 -5.01 -0.66 0 161.07 133.42 30681 +1961 6 2.85 -3.15 1.2 0 181.9 133.4 30752 +1961 7 6.12 0.12 4.47 0 224.2 132.28 30828 +1961 8 5.28 -0.72 3.63 0 212.6 134.29 30907 +1961 9 3.76 -2.24 2.11 0 192.92 136.45 30991 +1961 10 3.71 -2.29 2.06 0 192.3 137.77 31079 +1961 11 5.17 -0.83 3.52 0 211.12 137.89 31171 +1961 12 4.25 -1.75 2.6 0 199.08 139.46 31266 +1961 13 2.75 -3.25 1.1 0 180.73 141.93 31366 +1961 14 -1.77 -7.77 -3.42 0 133.96 145.53 31469 +1961 15 -3.29 -9.29 -4.94 1.58 120.79 157.29 31575 +1961 16 -3.32 -9.32 -4.97 0 120.54 195.34 31686 +1961 17 -1.37 -7.37 -3.02 0 137.62 196.11 31800 +1961 18 1.63 -4.37 -0.02 0.05 167.99 158.66 31917 +1961 19 2.64 -3.36 0.99 0 179.44 197.13 32038 +1961 20 2.04 -3.96 0.39 0 172.56 198.63 32161 +1961 21 0.16 -5.84 -1.49 0 152.46 201.41 32289 +1961 22 0.58 -5.42 -1.07 0 156.76 202.71 32419 +1961 23 1.55 -4.45 -0.1 0 167.11 203.62 32552 +1961 24 -1.88 -7.88 -3.53 0.01 132.96 166.4 32688 +1961 25 -2.96 -8.96 -4.61 0.19 123.55 168.54 32827 +1961 26 1.15 -4.85 -0.5 0.28 162.78 168.23 32969 +1961 27 -3.42 -9.42 -5.07 0.2 119.71 171.74 33114 +1961 28 -2.31 -8.31 -3.96 0.55 129.14 174.47 33261 +1961 29 -4.67 -10.67 -6.32 0 109.82 220.51 33411 +1961 30 -0.57 -6.57 -2.22 0 145.22 220.82 33564 +1961 31 5.33 -0.67 3.68 0 213.27 218.76 33718 +1961 32 9.18 3.18 7.53 0 271.17 216.32 33875 +1961 33 8.84 2.84 7.19 0 265.57 217.98 34035 +1961 34 7.55 1.55 5.9 0 245.19 220.24 34196 +1961 35 5.96 -0.04 4.31 0 221.95 222.8 34360 +1961 36 9.12 3.12 7.47 0.37 270.17 175.62 34526 +1961 37 6.47 0.47 4.82 0.77 229.19 140.46 34694 +1961 38 1.06 -4.94 -0.59 0.51 161.81 145.4 34863 +1961 39 3.95 -2.05 2.3 0 195.29 194.59 35035 +1961 40 0.7 -5.3 -0.95 0 158.01 199.35 35208 +1961 41 1.24 -4.76 -0.41 0 163.74 201.67 35383 +1961 42 0.77 -5.23 -0.88 0.72 158.75 153.4 35560 +1961 43 2.47 -3.53 0.82 0.64 177.47 154.63 35738 +1961 44 0.11 -5.89 -1.54 0 151.95 210.26 35918 +1961 45 5.33 -0.67 3.68 0 213.27 209.2 36099 +1961 46 7.44 1.44 5.79 0 243.52 209.97 36282 +1961 47 4.12 -1.88 2.47 0 197.43 215.7 36466 +1961 48 4.29 -1.71 2.64 0.02 199.59 163.78 36652 +1961 49 8.09 2.09 6.44 0 253.55 217.66 36838 +1961 50 10.01 4.01 8.36 0 285.28 218.16 37026 +1961 51 11.59 5.59 9.94 0.03 313.89 164.33 37215 +1961 52 11.93 5.93 10.28 0 320.35 221.42 37405 +1961 53 13.09 7.09 11.44 0.02 343.28 167.01 37596 +1961 54 7.18 1.18 5.53 0 239.61 232.68 37788 +1961 55 7.9 1.9 6.25 0 250.58 234.9 37981 +1961 56 11.96 5.96 10.31 0 320.93 232.53 38175 +1961 57 8.67 2.67 7.02 0 262.8 239.57 38370 +1961 58 5.28 -0.72 3.63 0.05 212.6 184.53 38565 +1961 59 7.61 1.61 5.96 0 246.11 246.37 38761 +1961 60 10.91 4.91 9.26 0 301.29 245.17 38958 +1961 61 9.86 3.86 8.21 0.19 282.68 187.09 39156 +1961 62 8.4 2.4 6.75 0.26 258.46 190.52 39355 +1961 63 6.92 0.92 5.27 0.13 235.74 194.03 39553 +1961 64 10.64 4.64 8.99 0.23 296.41 192.76 39753 +1961 65 8.45 2.45 6.8 0 259.26 262.72 39953 +1961 66 7.37 1.37 5.72 0 242.46 266.73 40154 +1961 67 12.29 6.29 10.64 0.01 327.32 197.22 40355 +1961 68 8.82 2.82 7.17 0.65 265.24 203.05 40556 +1961 69 8.42 2.42 6.77 0.05 258.78 205.39 40758 +1961 70 11.47 5.47 9.82 0.3 311.63 204.32 40960 +1961 71 8.87 2.87 7.22 0 266.06 279.01 41163 +1961 72 6.99 0.99 5.34 0 236.78 284.16 41366 +1961 73 6.12 0.12 4.47 0.05 224.2 215.87 41569 +1961 74 7.07 1.07 5.42 0 237.97 289.49 41772 +1961 75 10.59 4.59 8.94 0.06 295.51 215.61 41976 +1961 76 8.18 2.18 6.53 0 254.97 293.48 42179 +1961 77 10.21 4.21 8.56 0 288.77 293.24 42383 +1961 78 11.35 5.35 9.7 0 309.39 294.12 42587 +1961 79 13.98 7.98 12.33 0 361.81 292.2 42791 +1961 80 12.9 6.9 11.25 0.08 339.43 222.51 42996 +1961 81 10.45 4.45 8.8 0 293.01 303.31 43200 +1961 82 11.75 5.75 10.1 0 316.91 303.84 43404 +1961 83 15.34 9.34 13.69 0 391.77 299.49 43608 +1961 84 14.94 8.94 13.29 0 382.75 302.79 43812 +1961 85 16.04 10.04 14.39 0 408 302.86 44016 +1961 86 17.2 11.2 15.55 0 436.16 302.5 44220 +1961 87 19.84 13.84 18.19 0 506.48 298.07 44424 +1961 88 18.32 12.32 16.67 0 464.91 304.41 44627 +1961 89 15.12 9.12 13.47 0 386.79 314.18 44831 +1961 90 15.85 9.85 14.2 0 403.54 314.88 45034 +1961 91 16.7 10.7 15.05 0.1 423.83 236.32 45237 +1961 92 19.76 13.76 18.11 1.49 504.22 231.91 45439 +1961 93 17.97 11.97 16.32 0 455.76 316.23 45642 +1961 94 17.51 11.51 15.86 0.04 443.96 239.62 45843 +1961 95 15.85 9.85 14.2 0 403.54 325.61 46045 +1961 96 15.11 9.11 13.46 0 386.56 329.37 46246 +1961 97 17.58 11.58 15.93 0 445.74 325.41 46446 +1961 98 17.23 11.23 15.58 0 436.91 328.22 46647 +1961 99 19.68 13.68 18.03 1.04 501.96 242.56 46846 +1961 100 18.56 12.56 16.91 0.02 471.27 246.37 47045 +1961 101 19.02 13.02 17.37 0 483.68 329.06 47243 +1961 102 19.1 13.1 17.45 0 485.86 330.66 47441 +1961 103 18.58 12.58 16.93 0 471.8 333.92 47638 +1961 104 17.81 11.81 16.16 0.06 451.62 253.36 47834 +1961 105 16.17 10.17 14.52 0.16 411.08 257.86 48030 +1961 106 13.61 7.61 11.96 0 354.01 351.32 48225 +1961 107 14.48 8.48 12.83 0 372.59 351.07 48419 +1961 108 14.29 8.29 12.64 0 368.46 353.22 48612 +1961 109 15.22 9.22 13.57 0 389.05 352.68 48804 +1961 110 17.17 11.17 15.52 0 435.41 349.16 48995 +1961 111 12.29 6.29 10.64 0 327.32 362.01 49185 +1961 112 12.25 6.25 10.6 0 326.54 363.62 49374 +1961 113 11.91 5.91 10.26 0 319.97 365.64 49561 +1961 114 10.37 4.37 8.72 0 291.59 370.04 49748 +1961 115 13.5 7.5 11.85 1.69 351.71 273.96 49933 +1961 116 16.13 10.13 14.48 0 410.13 360.27 50117 +1961 117 13.81 7.81 12.16 0 358.21 367.12 50300 +1961 118 13.27 7.27 11.62 0.02 346.96 277.22 50481 +1961 119 13.81 7.81 12.16 0.01 358.21 277.22 50661 +1961 120 17.6 11.6 15.95 0.15 446.25 270.93 50840 +1961 121 19.03 13.03 17.38 0.17 483.95 268.61 51016 +1961 122 16.62 10.62 14.97 0 421.88 366.22 51191 +1961 123 14.78 8.78 13.13 0.07 379.19 278.93 51365 +1961 124 17 11 15.35 1.34 431.19 275.46 51536 +1961 125 19.68 13.68 18.03 0 501.96 360.28 51706 +1961 126 25.5 19.5 23.85 0 690.25 339.13 51874 +1961 127 22.6 16.6 20.95 0 590.08 351.89 52039 +1961 128 25.86 19.86 24.21 0.52 703.64 254.45 52203 +1961 129 19.43 13.43 17.78 0 494.97 364.72 52365 +1961 130 17.58 11.58 15.93 0.59 445.74 278.32 52524 +1961 131 17.39 11.39 15.74 0.94 440.93 279.32 52681 +1961 132 19.68 13.68 18.03 0.18 501.96 274.71 52836 +1961 133 20.88 14.88 19.23 0.33 536.72 272.19 52989 +1961 134 17.92 11.92 16.27 0.69 454.46 279.83 53138 +1961 135 17.45 11.45 15.8 0.35 442.44 281.37 53286 +1961 136 18.04 12.04 16.39 0.69 457.57 280.56 53430 +1961 137 14.93 8.93 13.28 0.01 382.52 287.42 53572 +1961 138 12.3 6.3 10.65 0.02 327.52 292.41 53711 +1961 139 11.75 5.75 10.1 0.29 316.91 293.8 53848 +1961 140 12.22 6.22 10.57 0 325.96 391.25 53981 +1961 141 10.26 4.26 8.61 0 289.65 395.6 54111 +1961 142 9.48 3.48 7.83 0.03 276.2 298.16 54238 +1961 143 10.15 4.15 8.5 0.12 287.72 297.65 54362 +1961 144 11.84 5.84 10.19 0 318.63 394.04 54483 +1961 145 13.3 7.3 11.65 0 347.58 391.35 54600 +1961 146 12.44 6.44 10.79 0.16 330.27 295.23 54714 +1961 147 14.83 8.83 13.18 0.36 380.3 291.44 54824 +1961 148 12.27 6.27 10.62 0.06 326.93 296.16 54931 +1961 149 7.77 1.77 6.12 0.57 248.57 302.7 55034 +1961 150 15.62 9.62 13.97 0 398.2 387.61 55134 +1961 151 20.09 14.09 18.44 0 513.62 374.66 55229 +1961 152 25.25 19.25 23.6 0 681.09 354.48 55321 +1961 153 25.6 19.6 23.95 0.12 693.95 264.83 55409 +1961 154 24.77 18.77 23.12 0.25 663.78 267.87 55492 +1961 155 25.75 19.75 24.1 0 699.53 352.89 55572 +1961 156 26.65 20.65 25 0 733.78 348.91 55648 +1961 157 29.78 23.78 28.13 0.12 864.16 249.32 55719 +1961 158 28.44 22.44 26.79 0 806.14 340.05 55786 +1961 159 23.41 17.41 21.76 0 616.73 363.99 55849 +1961 160 23.41 17.41 21.76 0.06 616.73 273.13 55908 +1961 161 23.45 17.45 21.8 0.07 618.08 273.05 55962 +1961 162 22.91 16.91 21.26 0.71 600.17 274.73 56011 +1961 163 21.46 15.46 19.81 0.96 554.23 279.06 56056 +1961 164 13.32 7.32 11.67 0.09 347.99 297.02 56097 +1961 165 15.63 9.63 13.98 0 398.43 390.46 56133 +1961 166 18.14 12.14 16.49 0 460.18 383.43 56165 +1961 167 16.23 10.23 14.58 0.08 412.51 291.66 56192 +1961 168 16.61 10.61 14.96 0.58 421.64 290.93 56214 +1961 169 15.28 9.28 13.63 0.92 390.41 293.62 56231 +1961 170 15.66 9.66 14.01 0.3 399.12 292.87 56244 +1961 171 18.9 12.9 17.25 0.23 480.41 285.87 56252 +1961 172 18.91 12.91 17.26 0 480.69 381.12 56256 +1961 173 25.42 19.42 23.77 0.7 687.31 267.04 56255 +1961 174 23.8 17.8 22.15 0 629.93 363.08 56249 +1961 175 26.7 20.7 25.05 0.37 735.72 262.41 56238 +1961 176 25.03 19.03 23.38 0 673.11 357.68 56223 +1961 177 26.12 20.12 24.47 1.92 713.44 264.41 56203 +1961 178 25.25 19.25 23.6 0.25 681.09 267.46 56179 +1961 179 18.77 12.77 17.12 0 476.9 381.21 56150 +1961 180 19.38 13.38 17.73 0 493.58 379.13 56116 +1961 181 20.41 14.41 18.76 0 522.87 375.6 56078 +1961 182 20.01 14.01 18.36 0 511.32 376.82 56035 +1961 183 20.43 14.43 18.78 0.01 523.45 281.4 55987 +1961 184 26.73 20.73 25.08 0.22 736.89 261.67 55935 +1961 185 24.81 18.81 23.16 0 665.2 357.77 55879 +1961 186 26.36 20.36 24.71 0 722.59 350.37 55818 +1961 187 24.55 18.55 22.9 0.03 655.97 268.86 55753 +1961 188 22.72 16.72 21.07 0.01 593.97 274.35 55684 +1961 189 19.79 13.79 18.14 0 505.07 376.25 55611 +1961 190 19.97 13.97 18.32 0 510.18 375.27 55533 +1961 191 24.19 18.19 22.54 0 643.35 358.98 55451 +1961 192 22.15 16.15 20.5 0.25 575.7 275.18 55366 +1961 193 23.94 17.94 22.29 0.65 634.72 269.61 55276 +1961 194 25.7 19.7 24.05 0 697.66 351.51 55182 +1961 195 24.24 18.24 22.59 0.14 645.09 268.3 55085 +1961 196 25.1 19.1 23.45 0.09 675.64 265.19 54984 +1961 197 26.34 20.34 24.69 0.09 721.82 260.56 54879 +1961 198 25.8 19.8 24.15 0.22 701.39 262.16 54770 +1961 199 19.79 13.79 18.14 0.01 505.07 279.66 54658 +1961 200 18.64 12.64 16.99 0.58 473.41 282.12 54542 +1961 201 18.67 12.67 17.02 0 474.21 375.6 54423 +1961 202 17.55 11.55 15.9 0.05 444.98 283.79 54301 +1961 203 18.73 12.73 17.08 0 475.82 374.33 54176 +1961 204 19.33 13.33 17.68 0.07 492.19 278.94 54047 +1961 205 21.16 15.16 19.51 0 545.11 365.22 53915 +1961 206 18.74 12.74 17.09 0 476.09 372.7 53780 +1961 207 17.78 11.78 16.13 1.57 450.85 281.19 53643 +1961 208 21.58 15.58 19.93 2.28 557.92 271.39 53502 +1961 209 17.8 11.8 16.15 0.17 451.37 280.15 53359 +1961 210 20.5 14.5 18.85 0.7 525.5 273.28 53213 +1961 211 16.49 10.49 14.84 0.78 418.74 281.84 53064 +1961 212 15.4 9.4 13.75 0.08 393.14 283.36 52913 +1961 213 21.19 15.19 19.54 0 546.02 359.67 52760 +1961 214 24.01 18.01 22.36 0 637.13 348.18 52604 +1961 215 22.84 16.84 21.19 0 597.88 352.18 52445 +1961 216 25.95 19.95 24.3 0.02 707.02 253.6 52285 +1961 217 23.01 17.01 21.36 0 603.45 349.65 52122 +1961 218 24.73 18.73 23.08 0 662.35 341.88 51958 +1961 219 21.6 15.6 19.95 0 558.54 353.07 51791 +1961 220 22.57 16.57 20.92 0.02 589.12 261.44 51622 +1961 221 19.4 13.4 17.75 0 494.14 358.5 51451 +1961 222 18.68 12.68 17.03 0.59 474.48 269.74 51279 +1961 223 17.96 11.96 16.31 0.71 455.5 270.46 51105 +1961 224 14.58 8.58 12.93 0 374.78 368.33 50929 +1961 225 18.48 12.48 16.83 0 469.14 356.88 50751 +1961 226 20.57 14.57 18.92 0 527.55 349.19 50572 +1961 227 18.79 12.79 17.14 0 477.44 353.51 50392 +1961 228 21.4 15.4 19.75 0 552.4 343.91 50210 +1961 229 17.02 11.02 15.37 0.12 431.69 267.03 50026 +1961 230 15.03 9.03 13.38 0.3 384.76 269.82 49842 +1961 231 18.73 12.73 17.08 0.31 475.82 261.35 49656 +1961 232 22.16 16.16 20.51 0.39 576.02 252 49469 +1961 233 24.17 18.17 22.52 0 642.66 327.05 49280 +1961 234 27.59 21.59 25.94 0 771.06 310.81 49091 +1961 235 25.48 19.48 23.83 0.14 689.52 239.17 48900 +1961 236 25.35 19.35 23.7 0 684.74 318.09 48709 +1961 237 25.26 19.26 23.61 0.25 681.45 237.68 48516 +1961 238 27.14 21.14 25.49 0 753.02 307.11 48323 +1961 239 25.57 19.57 23.92 0.39 692.84 234.44 48128 +1961 240 22.44 16.44 20.79 0 584.94 322.94 47933 +1961 241 24.14 18.14 22.49 0.64 641.62 236.26 47737 +1961 242 28.68 22.68 27.03 0.21 816.28 220.2 47541 +1961 243 28.6 22.6 26.95 0 812.89 292.28 47343 +1961 244 27.63 21.63 25.98 0 772.68 295.19 47145 +1961 245 28.14 22.14 26.49 0 793.6 291.13 46947 +1961 246 25.86 19.86 24.21 0 703.64 299.37 46747 +1961 247 21.8 15.8 20.15 0 564.73 312.65 46547 +1961 248 25.36 19.36 23.71 0 685.11 297.84 46347 +1961 249 21.96 15.96 20.31 0 569.72 308.22 46146 +1961 250 26.47 20.47 24.82 0 726.82 289.53 45945 +1961 251 26.67 20.67 25.02 0 734.56 286.72 45743 +1961 252 23.73 17.73 22.08 0.3 627.54 222.11 45541 +1961 253 23.54 17.54 21.89 0 621.1 294.79 45339 +1961 254 23.63 17.63 21.98 0 624.15 292.44 45136 +1961 255 20.15 14.15 18.5 0.08 515.34 226.03 44933 +1961 256 23.12 17.12 21.47 0 607.08 289.87 44730 +1961 257 18.5 12.5 16.85 0 469.67 301.53 44527 +1961 258 19.46 13.46 17.81 0 495.8 296.66 44323 +1961 259 18.69 12.69 17.04 0 474.75 296.31 44119 +1961 260 19.83 13.83 18.18 0 506.2 290.92 43915 +1961 261 18.12 12.12 16.47 0.05 459.66 219.74 43711 +1961 262 19.77 13.77 18.12 0 504.5 286.36 43507 +1961 263 20.17 14.17 18.52 0 515.92 282.87 43303 +1961 264 14.42 8.42 12.77 0 371.28 293.75 43099 +1961 265 10.67 4.67 9.02 0 296.95 297.89 42894 +1961 266 14.36 8.36 12.71 0 369.98 288.98 42690 +1961 267 17.23 11.23 15.58 0 436.91 280.3 42486 +1961 268 20 14 18.35 0 511.04 271 42282 +1961 269 19.9 13.9 18.25 0 508.19 268.82 42078 +1961 270 20.47 14.47 18.82 0 524.62 264.76 41875 +1961 271 18.8 12.8 17.15 0.57 477.71 199.84 41671 +1961 272 17.44 11.44 15.79 0.66 442.19 200.19 41468 +1961 273 12.91 6.91 11.26 0 339.63 273.17 41265 +1961 274 8.31 2.31 6.66 0.03 257.03 207.87 41062 +1961 275 10.32 4.32 8.67 0.04 290.71 203.74 40860 +1961 276 9.42 3.42 7.77 0.58 275.19 202.6 40658 +1961 277 7.79 1.79 6.14 0.03 248.88 202.1 40456 +1961 278 13.23 7.23 11.58 0.34 346.14 194.17 40255 +1961 279 9.42 3.42 7.77 0.93 275.19 196.23 40054 +1961 280 11.45 5.45 9.8 0 311.26 256.16 39854 +1961 281 14.84 8.84 13.19 0.25 380.52 185.98 39654 +1961 282 12.42 6.42 10.77 0.01 329.87 186.92 39455 +1961 283 10.77 4.77 9.12 0 298.75 248.76 39256 +1961 284 13.28 7.28 11.63 0 347.17 242.04 39058 +1961 285 12.28 6.28 10.63 0.07 327.13 180.69 38861 +1961 286 10.71 4.71 9.06 0.04 297.67 180.25 38664 +1961 287 15.58 9.58 13.93 0 397.27 229.93 38468 +1961 288 14.92 8.92 13.27 0.04 382.3 171.24 38273 +1961 289 13.95 7.95 12.3 0.09 361.17 170.47 38079 +1961 290 19.12 13.12 17.47 0 486.41 215.03 37885 +1961 291 17.16 11.16 15.51 0.09 435.17 162.24 37693 +1961 292 20.14 14.14 18.49 0.02 515.05 155.76 37501 +1961 293 15.77 9.77 14.12 0.4 401.68 160.12 37311 +1961 294 18.57 12.57 16.92 0.97 471.54 154.18 37121 +1961 295 18.08 12.08 16.43 1.25 458.62 152.83 36933 +1961 296 18.89 12.89 17.24 0.01 480.14 149.79 36745 +1961 297 18.98 12.98 17.33 1.46 482.59 147.7 36560 +1961 298 18 12 16.35 0.83 456.53 147.22 36375 +1961 299 15.58 9.58 13.93 0.05 397.27 148.3 36191 +1961 300 18.26 12.26 16.61 0 463.33 190.58 36009 +1961 301 20.6 14.6 18.95 0.01 528.43 137.7 35829 +1961 302 18.76 12.76 17.11 0.18 476.63 138.55 35650 +1961 303 18.49 12.49 16.84 0.95 469.41 137.07 35472 +1961 304 17.98 11.98 16.33 0 456.02 181.32 35296 +1961 305 12.76 6.76 11.11 1.03 336.62 139.82 35122 +1961 306 9.86 3.86 8.21 0 282.68 187.55 34950 +1961 307 12.17 6.17 10.52 0.18 324.99 136.84 34779 +1961 308 10.77 4.77 9.12 0.73 298.75 136.11 34610 +1961 309 3.83 -2.17 2.18 0.28 193.79 138.94 34444 +1961 310 0.71 -5.29 -0.94 0.22 158.12 138.54 34279 +1961 311 4.07 -1.93 2.42 0.05 196.8 135.3 34116 +1961 312 5.77 -0.23 4.12 0.33 219.3 132.37 33956 +1961 313 5.53 -0.47 3.88 0.13 215.99 130.9 33797 +1961 314 8.84 2.84 7.19 0.03 265.57 127.37 33641 +1961 315 7.37 1.37 5.72 0 242.46 168.58 33488 +1961 316 10.01 4.01 8.36 0 285.28 164.03 33337 +1961 317 6.22 0.22 4.57 1.01 225.61 123.82 33188 +1961 318 5.56 -0.44 3.91 0.38 216.41 122.43 33042 +1961 319 8.01 2.01 6.36 0.15 252.3 119.73 32899 +1961 320 10.44 4.44 8.79 0.37 292.83 116.71 32758 +1961 321 11.84 5.84 10.19 0.1 318.63 114.1 32620 +1961 322 11.98 5.98 10.33 0.42 321.31 112.65 32486 +1961 323 12.58 6.58 10.93 0.07 333.03 110.99 32354 +1961 324 6.42 0.42 4.77 0.02 228.47 113.56 32225 +1961 325 4.24 -1.76 2.59 0 198.96 151.15 32100 +1961 326 2.69 -3.31 1.04 0.32 180.03 112.95 31977 +1961 327 5.97 -0.03 4.32 0 222.09 146.71 31858 +1961 328 6.95 0.95 5.3 0 236.19 144.05 31743 +1961 329 7.7 1.7 6.05 0.7 247.49 106.5 31631 +1961 330 6.55 0.55 4.9 0.52 230.34 106.05 31522 +1961 331 8.17 2.17 6.52 0.71 254.81 104.18 31417 +1961 332 10.47 4.47 8.82 0.85 293.37 101.54 31316 +1961 333 7.59 1.59 5.94 0.04 245.81 102.47 31218 +1961 334 8.24 2.24 6.59 0 255.92 135.06 31125 +1961 335 -1.43 -7.43 -3.08 0 137.07 139.31 31035 +1961 336 1.2 -4.8 -0.45 0 163.31 137.07 30949 +1961 337 7.55 1.55 5.9 0.02 245.19 98.76 30867 +1961 338 6.04 0.04 4.39 0.25 223.07 98.83 30790 +1961 339 9.06 3.06 7.41 0 269.18 128.86 30716 +1961 340 8.71 2.71 7.06 0.31 263.45 96.3 30647 +1961 341 6.07 0.07 4.42 0.11 223.49 97 30582 +1961 342 2.23 -3.77 0.58 0.06 174.72 98.04 30521 +1961 343 3.83 -2.17 2.18 0 193.79 129.07 30465 +1961 344 5.88 -0.12 4.23 0 220.83 126.74 30413 +1961 345 6.16 0.16 4.51 0 224.76 126.14 30366 +1961 346 6.19 0.19 4.54 0.02 225.19 94.18 30323 +1961 347 7.03 1.03 5.38 0 237.37 124.44 30284 +1961 348 2.04 -3.96 0.39 0.04 172.56 95.19 30251 +1961 349 1.22 -4.78 -0.43 0 163.53 126.92 30221 +1961 350 -1.34 -7.34 -2.99 0 137.9 127.64 30197 +1961 351 0.92 -5.08 -0.73 0.56 160.33 94.87 30177 +1961 352 1.37 -4.63 -0.28 0.14 165.15 94.65 30162 +1961 353 1.69 -4.31 0.04 0.14 168.65 94.49 30151 +1961 354 2.83 -3.17 1.18 0.1 181.67 94.05 30145 +1961 355 -1.76 -7.76 -3.41 0 134.05 127.37 30144 +1961 356 -0.86 -6.86 -2.51 0 142.42 127.06 30147 +1961 357 -3.81 -9.81 -5.46 0 116.55 128.16 30156 +1961 358 -7.64 -13.64 -9.29 0.58 89.1 142.59 30169 +1961 359 -9.37 -15.37 -11.02 0 78.67 175.42 30186 +1961 360 -5.25 -11.25 -6.9 0 105.47 174.73 30208 +1961 361 -1.47 -7.47 -3.12 0 136.7 173.77 30235 +1961 362 4.73 -1.27 3.08 0 205.29 170.63 30267 +1961 363 2.17 -3.83 0.52 0 174.03 172.22 30303 +1961 364 0.86 -5.14 -0.79 1.15 159.69 140.87 30343 +1961 365 -2.89 -8.89 -4.54 0.91 124.14 145.22 30388 +1962 1 -1.18 -7.18 -2.83 0.53 139.39 147.01 30438 +1962 2 2.85 -3.15 1.2 0.13 181.9 145.75 30492 +1962 3 3.74 -2.26 2.09 1.41 192.67 145.51 30551 +1962 4 -0.11 -6.11 -1.76 0.08 149.74 147.75 30614 +1962 5 -0.35 -6.35 -2 0 147.37 181.71 30681 +1962 6 2.44 -3.56 0.79 0.13 177.12 147.49 30752 +1962 7 6.46 0.46 4.81 0 229.04 178.37 30828 +1962 8 5.74 -0.26 4.09 0 218.88 179.45 30907 +1962 9 2.25 -3.75 0.6 0 174.94 182.29 30991 +1962 10 0.88 -5.12 -0.77 0 159.9 184.03 31079 +1962 11 0.23 -5.77 -1.42 1.46 153.17 150.03 31171 +1962 12 2.5 -3.5 0.85 0.36 177.82 149.5 31266 +1962 13 3.98 -2.02 2.33 0 195.67 184.76 31366 +1962 14 3.49 -2.51 1.84 0.14 189.59 150.18 31469 +1962 15 1.67 -4.33 0.02 0 168.43 188 31575 +1962 16 2.32 -3.68 0.67 0 175.74 188.51 31686 +1962 17 7.94 1.94 6.29 0 251.21 144.41 31800 +1962 18 6.06 0.06 4.41 0 223.35 147.67 31917 +1962 19 5.03 -0.97 3.38 0 209.25 150.29 32038 +1962 20 3.64 -2.36 1.99 0 191.43 152.74 32161 +1962 21 2.34 -3.66 0.69 0.03 175.97 116.63 32289 +1962 22 3.56 -2.44 1.91 0 190.45 156.55 32419 +1962 23 1.77 -4.23 0.12 0.02 169.54 119.52 32552 +1962 24 2.47 -3.53 0.82 0 177.47 161.04 32688 +1962 25 2.88 -3.12 1.23 0 182.26 162.7 32827 +1962 26 3.28 -2.72 1.63 0 187.04 164.38 32969 +1962 27 3.52 -2.48 1.87 0 189.96 166.26 33114 +1962 28 2.2 -3.8 0.55 0 174.37 169.28 33261 +1962 29 2.52 -3.48 0.87 0.02 178.05 128.61 33411 +1962 30 4.11 -1.89 2.46 0 197.3 172.71 33564 +1962 31 2.93 -3.07 1.28 0 182.85 175.85 33718 +1962 32 0.64 -5.36 -1.01 0 157.39 179.33 33875 +1962 33 -0.18 -6.18 -1.83 0 149.05 182.41 34035 +1962 34 2.46 -3.54 0.81 0 177.35 183.12 34196 +1962 35 0.99 -5.01 -0.66 0 161.07 186.17 34360 +1962 36 -1.39 -7.39 -3.04 0.16 137.44 181.16 34526 +1962 37 0.76 -5.24 -0.89 0 158.64 229.69 34694 +1962 38 4.72 -1.28 3.07 0 205.16 191.41 34863 +1962 39 3.94 -2.06 2.29 0 195.16 194.6 35035 +1962 40 4.43 -1.57 2.78 0 201.39 196.86 35208 +1962 41 6.93 0.93 5.28 0 235.89 197.41 35383 +1962 42 5.49 -0.51 3.84 0 215.45 201.19 35560 +1962 43 3.5 -2.5 1.85 0 189.71 205.44 35738 +1962 44 4.29 -1.71 2.64 0 199.59 207.42 35918 +1962 45 3.72 -2.28 2.07 0 192.42 210.49 36099 +1962 46 7.17 1.17 5.52 0 239.46 210.23 36282 +1962 47 2.66 -3.34 1.01 0.53 179.67 162.6 36466 +1962 48 3.15 -2.85 1.5 0.5 185.47 164.45 36652 +1962 49 2.2 -3.8 0.55 0 174.37 222.75 36838 +1962 50 3.77 -2.23 2.12 0 193.04 224.26 37026 +1962 51 7.9 1.9 6.25 0 250.58 223.44 37215 +1962 52 9.91 3.91 8.26 0.22 283.55 167.99 37405 +1962 53 9.83 3.83 8.18 0.01 282.17 170.26 37596 +1962 54 9.86 3.86 8.21 0.5 282.68 172.27 37788 +1962 55 5.49 -0.51 3.84 0.24 215.45 177.99 37981 +1962 56 -1.99 -7.99 -3.64 0 131.98 245.54 38175 +1962 57 -3.94 -9.94 -5.59 0 115.51 249.52 38370 +1962 58 -1.28 -7.28 -2.93 0 138.46 251.04 38565 +1962 59 -0.89 -6.89 -2.54 0 142.14 253.55 38761 +1962 60 2.76 -3.24 1.11 0 180.85 253.86 38958 +1962 61 3.77 -2.23 2.12 0 193.04 255.97 39156 +1962 62 0 -6 -1.65 0 150.84 261.72 39355 +1962 63 1.31 -4.69 -0.34 0 164.5 263.83 39553 +1962 64 5.07 -0.93 3.42 0 209.78 263.53 39753 +1962 65 4.03 -1.97 2.38 0 196.29 267.42 39953 +1962 66 2.77 -3.23 1.12 0 180.96 271.3 40154 +1962 67 4.51 -1.49 2.86 0 202.42 272.65 40355 +1962 68 4.49 -1.51 2.84 0 202.16 275.56 40556 +1962 69 4.55 -1.45 2.9 0 202.94 278.15 40758 +1962 70 5.33 -0.67 3.68 0 213.27 280.23 40960 +1962 71 4.86 -1.14 3.21 0.4 206.99 212.73 41163 +1962 72 3.66 -2.34 2.01 0.06 191.68 215.75 41366 +1962 73 5.87 -0.13 4.22 0 220.69 288.11 41569 +1962 74 7.09 1.09 5.44 0 238.26 289.47 41772 +1962 75 9.3 3.3 7.65 0.33 273.17 217.01 41976 +1962 76 8.82 2.82 7.17 0.21 265.24 219.47 42179 +1962 77 4.04 -1.96 2.39 0.08 196.42 225.63 42383 +1962 78 4.89 -1.11 3.24 1.18 207.39 226.99 42587 +1962 79 3.87 -2.13 2.22 1.87 194.29 229.85 42791 +1962 80 2.93 -3.07 1.28 0.05 182.85 232.47 42996 +1962 81 1.31 -4.69 -0.34 0.3 164.5 235.54 43200 +1962 82 0.1 -5.9 -1.55 0.11 151.85 238.33 43404 +1962 83 1.4 -4.6 -0.25 0 165.48 319.23 43608 +1962 84 4.47 -1.53 2.82 0.76 201.91 239.11 43812 +1962 85 3.59 -2.41 1.94 0 190.82 322.28 44016 +1962 86 3.78 -2.22 2.13 0 193.17 324.53 44220 +1962 87 6.1 0.1 4.45 0 223.91 324.47 44424 +1962 88 5.47 -0.53 3.82 0.12 215.17 245.7 44627 +1962 89 9.33 3.33 7.68 0 273.67 324.72 44831 +1962 90 10.23 4.23 8.58 0 289.12 325.68 45034 +1962 91 19.24 13.24 17.59 0 489.71 308.54 45237 +1962 92 15.99 9.99 14.34 0 406.83 318.94 45439 +1962 93 15.15 9.15 13.5 0 387.46 323 45642 +1962 94 16.15 10.15 14.5 0 410.61 322.82 45843 +1962 95 18.42 12.42 16.77 0 467.55 319.17 46045 +1962 96 20.72 14.72 19.07 0 531.97 314.54 46246 +1962 97 26.74 20.74 25.09 0 737.28 294.25 46446 +1962 98 22.51 16.51 20.86 0 587.18 312.46 46647 +1962 99 20.57 14.57 18.92 0.42 527.55 240.54 46846 +1962 100 16.56 10.56 14.91 2.18 420.43 250.32 47045 +1962 101 14.7 8.7 13.05 0.26 377.42 255.02 47243 +1962 102 13.06 7.06 11.41 0 342.67 345.4 47441 +1962 103 10.77 4.77 9.12 0.02 298.75 263.69 47638 +1962 104 10 4 8.35 0.39 285.11 266.06 47834 +1962 105 8.75 2.75 7.1 0.03 264.1 268.95 48030 +1962 106 7.68 1.68 6.03 0.22 247.19 271.43 48225 +1962 107 4.8 -1.2 3.15 0 206.2 367.51 48419 +1962 108 0.59 -5.41 -1.06 0 156.87 373.84 48612 +1962 109 3.96 -2.04 2.31 0.12 195.41 278.97 48804 +1962 110 6.74 0.74 5.09 0.32 233.1 277.37 48995 +1962 111 8.45 2.45 6.8 0 259.26 368.85 49185 +1962 112 11.76 5.76 10.11 0 317.1 364.58 49374 +1962 113 9.72 3.72 8.07 0 280.28 369.67 49561 +1962 114 13.27 7.27 11.62 0 346.96 364.34 49748 +1962 115 13.12 7.12 11.47 0 343.89 366.09 49933 +1962 116 16.79 10.79 15.14 0.02 426.03 268.91 50117 +1962 117 18.46 12.46 16.81 0.18 468.61 266.38 50300 +1962 118 19.25 13.25 17.6 0.06 489.98 265.56 50481 +1962 119 14.66 8.66 13.01 0 376.54 367.67 50661 +1962 120 15.8 9.8 14.15 0 402.38 366.05 50840 +1962 121 19.15 13.15 17.5 0 487.23 357.78 51016 +1962 122 17.96 11.96 16.31 0.45 455.5 271.87 51191 +1962 123 16.08 10.08 14.43 0.21 408.95 276.49 51365 +1962 124 17.55 11.55 15.9 0.13 444.98 274.31 51536 +1962 125 17.39 11.39 15.74 0 440.93 367.17 51706 +1962 126 19.16 13.16 17.51 0.11 487.51 272.17 51874 +1962 127 21.25 15.25 19.6 0.01 547.84 267.62 52039 +1962 128 19.02 13.02 17.37 0.15 483.68 273.88 52203 +1962 129 17.42 11.42 15.77 0 441.69 370.77 52365 +1962 130 18.03 12.03 16.38 1.85 457.31 277.34 52524 +1962 131 14.27 8.27 12.62 0.91 368.03 285.39 52681 +1962 132 12.64 6.64 10.99 0 334.22 385.03 52836 +1962 133 15.35 9.35 13.7 0 392 379.42 52989 +1962 134 16.06 10.06 14.41 0 408.48 378.3 53138 +1962 135 16.85 10.85 15.2 0.27 427.5 282.64 53286 +1962 136 13.63 7.63 11.98 0.29 354.42 289.22 53430 +1962 137 16.24 10.24 14.59 1 412.74 284.89 53572 +1962 138 12.01 6.01 10.36 0.74 321.89 292.87 53711 +1962 139 13.81 7.81 12.16 0.01 358.21 290.42 53848 +1962 140 15.25 9.25 13.6 0.72 389.73 288.17 53981 +1962 141 11.58 5.58 9.93 0.08 313.7 294.77 54111 +1962 142 16.32 10.32 14.67 0.19 414.65 286.77 54238 +1962 143 15.12 9.12 13.47 0.25 386.79 289.53 54362 +1962 144 15.01 9.01 13.36 0.18 384.31 290.1 54483 +1962 145 14.59 8.59 12.94 0 375 388.31 54600 +1962 146 12.64 6.64 10.99 0 334.22 393.2 54714 +1962 147 15.15 9.15 13.5 0 387.46 387.78 54824 +1962 148 18.38 12.38 16.73 0 466.49 379.14 54931 +1962 149 19.41 13.41 17.76 0 494.41 376.2 55034 +1962 150 19.67 13.67 18.02 0.01 501.68 281.76 55134 +1962 151 20.73 14.73 19.08 0.19 532.26 279.34 55229 +1962 152 20.27 14.27 18.62 0.49 518.8 280.61 55321 +1962 153 17.88 11.88 16.23 0 453.43 382.05 55409 +1962 154 17.49 11.49 15.84 1 443.46 287.64 55492 +1962 155 21.66 15.66 20.01 0.5 560.39 277.45 55572 +1962 156 23.38 17.38 21.73 0.1 615.73 272.66 55648 +1962 157 18.38 12.38 16.73 0 466.49 381.53 55719 +1962 158 18.12 12.12 16.47 0 459.66 382.5 55786 +1962 159 15.9 9.9 14.25 0 404.71 389.06 55849 +1962 160 15.11 9.11 13.46 0 386.56 391.31 55908 +1962 161 18.59 12.59 16.94 0 472.07 381.55 55962 +1962 162 20.53 14.53 18.88 0.04 526.38 281.4 56011 +1962 163 16.11 10.11 14.46 0.72 409.66 291.78 56056 +1962 164 17.23 11.23 15.58 0.04 436.91 289.46 56097 +1962 165 17.18 11.18 15.53 0 435.66 386.19 56133 +1962 166 15.14 9.14 13.49 0 387.24 391.81 56165 +1962 167 18.13 12.13 16.48 0 459.92 383.41 56192 +1962 168 22.56 16.56 20.91 0 588.79 368.14 56214 +1962 169 23.66 17.66 22.01 0 625.16 363.71 56231 +1962 170 26.23 20.23 24.58 0 717.62 352.23 56244 +1962 171 25.76 19.76 24.11 0 699.9 354.51 56252 +1962 172 24.66 18.66 23.01 0.35 659.86 269.61 56256 +1962 173 24.71 18.71 23.06 0 661.64 359.25 56255 +1962 174 19.09 13.09 17.44 0 485.59 380.44 56249 +1962 175 21.5 15.5 19.85 0.76 555.46 279.08 56238 +1962 176 18.73 12.73 17.08 0.05 475.82 286.14 56223 +1962 177 18.61 12.61 16.96 0.78 472.61 286.34 56203 +1962 178 17.63 11.63 15.98 0.3 447.01 288.6 56179 +1962 179 16.72 10.72 15.07 0.02 424.32 290.48 56150 +1962 180 12.17 6.17 10.52 0 324.99 398.35 56116 +1962 181 12.41 6.41 10.76 0 329.68 397.76 56078 +1962 182 17.44 11.44 15.79 0 442.19 384.91 56035 +1962 183 19.2 13.2 17.55 0 488.61 379.32 55987 +1962 184 20.95 14.95 19.3 0 538.81 373.22 55935 +1962 185 21.63 15.63 19.98 0.23 559.46 278 55879 +1962 186 23.78 17.78 22.13 0 629.24 361.95 55818 +1962 187 23.02 17.02 21.37 0 603.78 364.87 55753 +1962 188 22.52 16.52 20.87 0.03 587.51 274.94 55684 +1962 189 22.51 16.51 20.86 0.19 587.18 274.83 55611 +1962 190 20.95 14.95 19.3 0.45 538.81 278.91 55533 +1962 191 21.14 15.14 19.49 0.16 544.51 278.2 55451 +1962 192 21.03 15.03 19.38 0 541.2 371.03 55366 +1962 193 20.91 14.91 19.26 0 537.61 371.19 55276 +1962 194 21.78 15.78 20.13 0 564.11 367.8 55182 +1962 195 20.21 14.21 18.56 0 517.07 373.12 55085 +1962 196 18.11 12.11 16.46 0.02 459.4 284.58 54984 +1962 197 19.21 13.21 17.56 0 488.88 375.56 54879 +1962 198 24.03 18.03 22.38 0.03 637.82 268.02 54770 +1962 199 23.03 17.03 21.38 0.12 604.11 270.83 54658 +1962 200 22 16 20.35 0.05 570.98 273.52 54542 +1962 201 23.1 17.1 21.45 1.43 606.42 269.98 54423 +1962 202 19.42 13.42 17.77 0.38 494.69 279.49 54301 +1962 203 18.66 12.66 17.01 2.64 473.94 280.91 54176 +1962 204 22.06 16.06 20.41 0.25 572.86 271.83 54047 +1962 205 24.29 18.29 22.64 0 646.84 353.05 53915 +1962 206 24.04 18.04 22.39 0 638.16 353.55 53780 +1962 207 26.54 20.54 24.89 0 729.52 341.75 53643 +1962 208 19.94 13.94 18.29 0.15 509.33 275.65 53502 +1962 209 21.44 15.44 19.79 1.13 553.62 271.28 53359 +1962 210 16.19 10.19 14.54 0.89 411.56 283.04 53213 +1962 211 18.75 12.75 17.1 1.58 476.36 276.95 53064 +1962 212 15.99 9.99 14.34 2.86 406.83 282.23 52913 +1962 213 16.22 10.22 14.57 0.82 412.27 281.19 52760 +1962 214 19.62 13.62 17.97 0.22 500.28 273.16 52604 +1962 215 18.82 12.82 17.17 0.89 478.25 274.53 52445 +1962 216 19.05 13.05 17.4 0.41 484.5 273.23 52285 +1962 217 20.03 14.03 18.38 0.16 511.9 270.22 52122 +1962 218 20.35 14.35 18.7 0.2 521.12 268.81 51958 +1962 219 21.36 15.36 19.71 0 551.18 353.92 51791 +1962 220 27.13 21.13 25.48 0 752.62 329.1 51622 +1962 221 25.51 19.51 23.86 0 690.62 335.63 51451 +1962 222 23.42 17.42 21.77 0.17 617.07 257.49 51279 +1962 223 22.25 16.25 20.6 0 578.87 346.64 51105 +1962 224 23.68 17.68 22.03 0 625.84 340.16 50929 +1962 225 23.37 17.37 21.72 0 615.39 340.26 50751 +1962 226 26.27 20.27 24.62 0 719.15 326.96 50572 +1962 227 23.36 17.36 21.71 0 615.06 337.94 50392 +1962 228 24.94 18.94 23.29 0 669.86 330.4 50210 +1962 229 23.18 17.18 21.53 0 609.06 336.24 50026 +1962 230 26.29 20.29 24.64 0 719.91 322.14 49842 +1962 231 23.89 17.89 22.24 0 633 330.83 49656 +1962 232 24.18 18.18 22.53 0 643.01 328.38 49469 +1962 233 27 21 25.35 0 747.48 314.9 49280 +1962 234 26.89 20.89 25.24 0.1 743.15 235.56 49091 +1962 235 28.14 22.14 26.49 0.01 793.6 230.08 48900 +1962 236 24.26 18.26 22.61 0 645.79 322.53 48709 +1962 237 23.87 17.87 22.22 0 632.32 322.47 48516 +1962 238 26.1 20.1 24.45 0 712.68 311.75 48323 +1962 239 25.17 19.17 23.52 0.37 678.18 235.69 48128 +1962 240 25.46 19.46 23.81 0.52 688.78 233.53 47933 +1962 241 22.27 16.27 20.62 0 579.51 321.86 47737 +1962 242 26.84 20.84 25.19 0 741.19 302.19 47541 +1962 243 27.15 21.15 25.5 0.01 753.41 224.3 47343 +1962 244 16.91 10.91 15.26 0 428.97 332.42 47145 +1962 245 17.46 11.46 15.81 0 442.7 329.16 46947 +1962 246 19.67 13.67 18.02 0 501.68 321.1 46747 +1962 247 18.4 12.4 16.75 0.04 467.02 242.13 46547 +1962 248 18.58 12.58 16.93 0.71 471.8 240.31 46347 +1962 249 20.31 14.31 18.66 0.1 519.96 235.06 46146 +1962 250 18.96 12.96 17.31 0 482.04 315.38 45945 +1962 251 21.75 15.75 20.1 0 563.17 304.96 45743 +1962 252 17.81 11.81 16.16 0.12 451.62 235.64 45541 +1962 253 20.28 14.28 18.63 0 519.09 305.31 45339 +1962 254 18 12 16.35 0.05 456.53 232.09 45136 +1962 255 19.46 13.46 17.81 2.98 495.8 227.5 44933 +1962 256 16.38 10.38 14.73 1.51 416.09 231.66 44730 +1962 257 14.53 8.53 12.88 0.5 373.68 233.05 44527 +1962 258 12.72 6.72 11.07 0.16 335.82 233.89 44323 +1962 259 11.01 5.01 9.36 0.05 303.11 234.26 44119 +1962 260 16.65 10.65 15 0 422.61 298.92 43915 +1962 261 18.14 12.14 16.49 0.02 460.18 219.7 43711 +1962 262 18.21 12.21 16.56 0 462.01 290.41 43507 +1962 263 18.67 12.67 17.02 0 474.21 286.83 43303 +1962 264 18.32 12.32 16.67 0.86 464.91 213.87 43099 +1962 265 17.82 11.82 16.17 0.01 451.88 213.03 42894 +1962 266 18.46 12.46 16.81 0.3 468.61 210.04 42690 +1962 267 19.5 13.5 17.85 0.13 496.92 206.1 42486 +1962 268 19.02 13.02 17.37 0.14 483.68 205.14 42282 +1962 269 19.35 13.35 17.7 0.51 492.75 202.67 42078 +1962 270 19.4 13.4 17.75 0.21 494.14 200.65 41875 +1962 271 17.92 11.92 16.27 0 454.46 268.53 41671 +1962 272 15.41 9.41 13.76 0 393.37 271.16 41468 +1962 273 15.25 9.25 13.6 0.01 389.73 201.71 41265 +1962 274 6.91 0.91 5.26 0 235.6 278.84 41062 +1962 275 9.21 3.21 7.56 0 271.67 273.17 40860 +1962 276 10.01 4.01 8.36 0 285.28 269.34 40658 +1962 277 11.29 5.29 9.64 0.48 308.27 198.61 40456 +1962 278 15.43 9.43 13.78 0 393.83 255.02 40255 +1962 279 13.85 7.85 12.2 0 359.05 255.04 40054 +1962 280 11.32 5.32 9.67 0 308.83 256.35 39854 +1962 281 9.61 3.61 7.96 0.08 278.4 191.95 39654 +1962 282 9.2 3.2 7.55 0 271.5 253.66 39455 +1962 283 11.05 5.05 9.4 0 303.84 248.37 39256 +1962 284 11.92 5.92 10.27 0 320.16 244.1 39058 +1962 285 15.08 9.08 13.43 0 385.89 236.43 38861 +1962 286 14.78 8.78 13.13 0.24 379.19 175.66 38664 +1962 287 15.01 9.01 13.36 0.04 384.31 173.19 38468 +1962 288 13.91 7.91 12.26 0.07 360.32 172.48 38273 +1962 289 11.46 5.46 9.81 1.03 311.44 173.2 38079 +1962 290 10.25 4.25 8.6 0.43 289.48 172.22 37885 +1962 291 7.76 1.76 6.11 0 248.42 229.74 37693 +1962 292 8.78 2.78 7.13 0 264.59 225.91 37501 +1962 293 13.67 7.67 12.02 0.01 355.26 162.63 37311 +1962 294 14.06 8.06 12.41 0 363.52 213.39 37121 +1962 295 15.45 9.45 13.8 0.04 394.29 156.31 36933 +1962 296 19.59 13.59 17.94 0 499.44 198.31 36745 +1962 297 14.33 8.33 12.68 0 369.33 204.95 36560 +1962 298 17.69 11.69 16.04 0 448.55 196.86 36375 +1962 299 20.41 14.41 18.76 0 522.87 188.89 36191 +1962 300 18.92 12.92 17.27 0.21 480.96 142.01 36009 +1962 301 18.23 12.23 16.58 0.58 462.54 141.16 35829 +1962 302 16.99 10.99 15.34 0 430.95 187.86 35650 +1962 303 17.49 11.49 15.84 0.15 443.46 138.39 35472 +1962 304 13.72 7.72 12.07 0 356.31 187.88 35296 +1962 305 9.79 3.79 8.14 0 281.48 189.87 35122 +1962 306 8.17 2.17 6.52 0.36 254.81 141.92 34950 +1962 307 9.33 3.33 7.68 0.68 273.67 139.19 34779 +1962 308 9.44 3.44 7.79 0 275.52 182.87 34610 +1962 309 7.39 1.39 5.74 0 242.76 182.47 34444 +1962 310 8.78 2.78 7.13 0 264.59 178.76 34279 +1962 311 8.73 2.73 7.08 0 263.77 176.63 34116 +1962 312 9.73 3.73 8.08 0.75 280.45 129.78 33956 +1962 313 8.09 2.09 6.44 0.05 253.55 129.34 33797 +1962 314 5.34 -0.66 3.69 0 213.41 172.7 33641 +1962 315 6.27 0.27 4.62 0 226.32 169.46 33488 +1962 316 3.86 -2.14 2.21 0.13 194.16 126.73 33337 +1962 317 1.21 -4.79 -0.44 0 163.42 168.33 33188 +1962 318 4.44 -1.56 2.79 0.31 201.52 123.01 33042 +1962 319 3.39 -2.61 1.74 0.08 188.37 122.23 32899 +1962 320 2.72 -3.28 1.07 0.54 180.38 121.11 32758 +1962 321 5.48 -0.52 3.83 2.44 215.31 118.19 32620 +1962 322 1.76 -4.24 0.11 2.23 169.43 118.53 32486 +1962 323 2.39 -3.61 0.74 0.19 176.55 117.04 32354 +1962 324 5.39 -0.61 3.74 0.21 214.09 114.1 32225 +1962 325 6.86 0.86 5.21 0 234.86 149.37 32100 +1962 326 9.87 3.87 8.22 0 282.86 145.49 31977 +1962 327 10.53 4.53 8.88 0.31 294.44 107.31 31858 +1962 328 7.52 1.52 5.87 0.35 244.74 107.72 31743 +1962 329 10.36 4.36 8.71 0.06 291.42 104.86 31631 +1962 330 12.15 6.15 10.5 0.79 324.6 102.54 31522 +1962 331 5.88 -0.12 4.23 3.6 220.83 105.4 31417 +1962 332 4.86 -1.14 3.21 1.47 206.99 104.66 31316 +1962 333 3.83 -2.17 2.18 1.84 193.79 104.3 31218 +1962 334 3.13 -2.87 1.48 0.49 185.23 103.77 31125 +1962 335 -3.58 -9.58 -5.23 0 118.4 140.1 31035 +1962 336 -2.55 -8.55 -4.2 0 127.05 138.64 30949 +1962 337 -2.27 -8.27 -3.92 0 129.49 136.86 30867 +1962 338 -2.63 -8.63 -4.28 0 126.36 136.03 30790 +1962 339 -0.27 -6.27 -1.92 0 148.15 134.3 30716 +1962 340 -2.76 -8.76 -4.41 0 125.24 134.52 30647 +1962 341 -2.53 -8.53 -4.18 0.2 127.22 143.92 30582 +1962 342 -3.53 -9.53 -5.18 0.06 118.81 143.87 30521 +1962 343 -4.27 -10.27 -5.92 0 112.9 176.63 30465 +1962 344 -7.43 -13.43 -9.08 0 90.44 176.45 30413 +1962 345 -3.2 -9.2 -4.85 0 121.53 174.84 30366 +1962 346 2.56 -3.44 0.91 0 178.51 171.63 30323 +1962 347 1.34 -4.66 -0.31 0.01 164.82 139.59 30284 +1962 348 1.15 -4.85 -0.5 0 162.78 171.12 30251 +1962 349 4.64 -1.36 2.99 0 204.11 125.18 30221 +1962 350 2.8 -3.2 1.15 0 181.32 125.83 30197 +1962 351 0.49 -5.51 -1.16 0 155.83 126.68 30177 +1962 352 -0.46 -6.46 -2.11 0 146.29 126.98 30162 +1962 353 -1.4 -7.4 -3.05 0 137.34 127.28 30151 +1962 354 2.07 -3.93 0.42 0 172.9 125.77 30145 +1962 355 2.22 -3.78 0.57 0 174.6 125.69 30144 +1962 356 1.5 -4.5 -0.15 0 166.57 126.06 30147 +1962 357 2.99 -3.01 1.34 0 183.56 125.4 30156 +1962 358 -1.34 -7.34 -2.99 0 137.9 127.4 30169 +1962 359 -2.81 -8.81 -4.46 0 124.82 128.05 30186 +1962 360 -3.79 -9.79 -5.44 0.96 116.71 143.3 30208 +1962 361 -0.7 -6.7 -2.35 0.41 143.96 143.99 30235 +1962 362 -3.69 -9.69 -5.34 0 117.51 177.45 30267 +1962 363 -0.49 -6.49 -2.14 0.65 145.99 146.65 30303 +1962 364 -0.19 -6.19 -1.84 0 148.95 179.09 30343 +1962 365 0.78 -5.22 -0.87 0 158.85 179.07 30388 +1963 1 -3.8 -9.8 -5.45 0 116.63 181.64 30438 +1963 2 -3.8 -9.8 -5.45 0.61 116.63 151.03 30492 +1963 3 -3.8 -9.8 -5.45 0 116.63 185.07 30551 +1963 4 -3.8 -9.8 -5.45 0.06 116.63 152.43 30614 +1963 5 -3.8 -9.8 -5.45 0.9 116.63 155.62 30681 +1963 6 -3.8 -9.8 -5.45 0.18 116.63 156.74 30752 +1963 7 -3.8 -9.8 -5.45 0 116.63 191.47 30828 +1963 8 -3.8 -9.8 -5.45 0.01 116.63 158.23 30907 +1963 9 -3.8 -9.8 -5.45 0.02 116.63 159.1 30991 +1963 10 -3.8 -9.8 -5.45 0.09 116.63 160.22 31079 +1963 11 -3.8 -9.8 -5.45 0 116.63 196.34 31171 +1963 12 -3.8 -9.8 -5.45 0 116.63 197.21 31266 +1963 13 -3.8 -9.8 -5.45 0 116.63 198.68 31366 +1963 14 -3.8 -9.8 -5.45 0 116.63 200 31469 +1963 15 -3.8 -9.8 -5.45 1.14 116.63 167.81 31575 +1963 16 -3.8 -9.8 -5.45 0.89 116.63 171.3 31686 +1963 17 -3.8 -9.8 -5.45 0.82 116.63 174.84 31800 +1963 18 -3.8 -9.8 -5.45 0.26 116.63 176.84 31917 +1963 19 -3.8 -9.8 -5.45 0.55 116.63 179.72 32038 +1963 20 -3.8 -9.8 -5.45 0 116.63 219.75 32161 +1963 21 -3.8 -9.8 -5.45 0 116.63 221.54 32289 +1963 22 -3.8 -9.8 -5.45 0 116.63 223.06 32419 +1963 23 -3.8 -9.8 -5.45 0 116.63 224.61 32552 +1963 24 -3.8 -9.8 -5.45 0.45 116.63 186.77 32688 +1963 25 -3.8 -9.8 -5.45 0.57 116.63 189.6 32827 +1963 26 -3.8 -9.8 -5.45 0 116.63 232.76 32969 +1963 27 -3.8 -9.8 -5.45 0 116.63 234.53 33114 +1963 28 -3.8 -9.8 -5.45 0 116.63 236.49 33261 +1963 29 -3.8 -9.8 -5.45 0 116.63 238.61 33411 +1963 30 -3.8 -9.8 -5.45 0.11 116.63 196.7 33564 +1963 31 -3.8 -9.8 -5.45 0.29 116.63 199.04 33718 +1963 32 -2.86 -8.86 -4.51 0 124.39 245.32 33875 +1963 33 -2.53 -8.53 -4.18 0 127.22 247.54 34035 +1963 34 -3.23 -9.23 -4.88 0.08 121.28 203.48 34196 +1963 35 -3 -9 -4.65 0.15 123.21 205.16 34360 +1963 36 -5.41 -11.41 -7.06 0.81 104.3 209.75 34526 +1963 37 -8.99 -14.99 -10.64 0 80.86 261.02 34694 +1963 38 -6.29 -12.29 -7.94 0 98.05 262.63 34863 +1963 39 -3.75 -9.75 -5.4 0 117.03 263.97 35035 +1963 40 -1.48 -7.48 -3.13 0 136.61 265.24 35208 +1963 41 3.39 -2.61 1.74 0 188.37 264.23 35383 +1963 42 4.04 -1.96 2.39 0.03 196.42 214.96 35560 +1963 43 4.39 -1.61 2.74 0.04 200.88 215.98 35738 +1963 44 4.82 -1.18 3.17 0 206.47 268.55 35918 +1963 45 1.04 -4.96 -0.61 0.7 161.6 220.38 36099 +1963 46 2.08 -3.92 0.43 0 173.01 274.95 36282 +1963 47 6.56 0.56 4.91 0.17 230.49 219.76 36466 +1963 48 5.69 -0.31 4.04 1.43 218.19 221.52 36652 +1963 49 0.67 -5.33 -0.98 0 157.7 282.04 36838 +1963 50 -1.41 -7.41 -3.06 0 137.25 285.69 37026 +1963 51 -4 -10 -5.65 0 115.03 289.75 37215 +1963 52 -3.32 -9.32 -4.97 0 120.54 292.01 37405 +1963 53 3.42 -2.58 1.77 0.39 188.74 231.71 37596 +1963 54 -3.03 -9.03 -4.68 0 122.96 296.74 37788 +1963 55 -7.25 -13.25 -8.9 0.38 91.61 241.05 37981 +1963 56 -6.38 -12.38 -8.03 0 97.43 304.49 38175 +1963 57 -5.99 -11.99 -7.64 0 100.14 306.99 38370 +1963 58 -5.91 -11.91 -7.56 0.11 100.71 246.59 38565 +1963 59 -4.96 -10.96 -6.61 0.19 107.62 248.53 38761 +1963 60 6.06 0.06 4.41 0.33 223.35 243.94 38958 +1963 61 4.57 -1.43 2.92 0.03 203.2 246.47 39156 +1963 62 5.14 -0.86 3.49 0 210.72 311.75 39355 +1963 63 5.57 -0.43 3.92 0 216.54 313.5 39553 +1963 64 7.54 1.54 5.89 0 245.04 313.27 39753 +1963 65 8.42 2.42 6.77 0.03 258.78 248.31 39953 +1963 66 8.13 2.13 6.48 1.25 254.18 249.54 40154 +1963 67 6.59 0.59 4.94 0 230.92 319.77 40355 +1963 68 5.99 -0.01 4.34 0 222.37 322.46 40556 +1963 69 5.35 -0.65 3.7 0 213.54 325 40758 +1963 70 6.59 0.59 4.94 0.55 230.92 255.92 40960 +1963 71 5.52 -0.48 3.87 0.04 215.86 258.22 41163 +1963 72 6.05 0.05 4.4 0 223.21 330.41 41366 +1963 73 7.42 1.42 5.77 0.01 243.22 258.98 41569 +1963 74 10.86 4.86 9.21 0 300.38 327.35 41772 +1963 75 6.68 0.68 5.03 0 232.23 334.81 41976 +1963 76 9.76 3.76 8.11 0.38 280.97 259.47 42179 +1963 77 4.61 -1.39 2.96 0 203.72 340.61 42383 +1963 78 6.72 0.72 5.07 0 232.81 340.1 42587 +1963 79 7.91 1.91 6.26 0 250.74 340.42 42791 +1963 80 7.77 1.77 6.12 0 248.57 342.23 42996 +1963 81 8.56 2.56 6.91 0 261.02 342.77 43200 +1963 82 4.37 -1.63 2.72 0.03 200.62 271.49 43404 +1963 83 4.94 -1.06 3.29 0 208.05 351.23 43608 +1963 84 0.62 -5.38 -1.03 0 157.18 357.76 43812 +1963 85 0.43 -5.57 -1.22 0 155.21 360.27 44016 +1963 86 4.88 -1.12 3.23 0 207.26 357.8 44220 +1963 87 3.47 -2.53 1.82 0 189.35 361.42 44424 +1963 88 4.13 -1.87 2.48 0 197.56 362.58 44627 +1963 89 9.47 3.47 7.82 0 276.03 356.97 44831 +1963 90 5.79 -0.21 4.14 0 219.58 363.72 45034 +1963 91 12.37 6.37 10.72 0 328.89 354.78 45237 +1963 92 18.35 12.35 16.7 0 465.7 313.1 45439 +1963 93 20.67 14.67 19.02 0.02 530.49 231.47 45642 +1963 94 21.13 15.13 19.48 0.11 544.21 231.93 45843 +1963 95 15.07 9.07 13.42 0 385.66 327.38 46045 +1963 96 10.26 4.26 8.61 0.18 289.65 254.07 46246 +1963 97 13.74 7.74 12.09 0.18 356.73 250.75 46446 +1963 98 17.48 11.48 15.83 0 443.2 327.57 46647 +1963 99 15.79 9.79 14.14 0.02 402.14 250.28 46846 +1963 100 11.14 5.14 9.49 0.07 305.5 258.92 47045 +1963 101 10.21 4.21 8.56 0 288.77 348.79 47243 +1963 102 16.49 10.49 14.84 0 418.74 337.67 47441 +1963 103 16.38 10.38 14.73 0 416.09 339.75 47638 +1963 104 16.25 10.25 14.6 0 412.98 341.86 47834 +1963 105 15.49 9.49 13.84 0 395.2 345.46 48030 +1963 106 14.85 8.85 13.2 0.16 380.74 261.43 48225 +1963 107 11.19 5.19 9.54 0.02 306.42 268.34 48419 +1963 108 12.42 6.42 10.77 0 329.87 357.18 48612 +1963 109 14.19 8.19 12.54 0.86 366.3 266.28 48804 +1963 110 17.17 11.17 15.52 0 435.41 349.16 48995 +1963 111 14.18 8.18 12.53 0 366.09 358.01 49185 +1963 112 10.54 4.54 8.89 0.49 294.62 275.15 49374 +1963 113 11.01 5.01 9.36 1.43 303.11 275.52 49561 +1963 114 10.78 4.78 9.13 0.08 298.93 276.97 49748 +1963 115 8.2 2.2 6.55 0 255.28 375.14 49933 +1963 116 9.84 3.84 8.19 0.31 282.34 280.25 50117 +1963 117 9.65 3.65 8 0.06 279.08 281.49 50300 +1963 118 10.69 4.69 9.04 0.11 297.3 281.1 50481 +1963 119 14.18 8.18 12.53 0.03 366.09 276.59 50661 +1963 120 17.27 11.27 15.62 0 437.91 362.16 50840 +1963 121 16.49 10.49 14.84 0.02 418.74 274.04 51016 +1963 122 15.87 9.87 14.22 0.04 404.01 276.13 51191 +1963 123 13.37 7.37 11.72 0 349.02 375.15 51365 +1963 124 10.16 4.16 8.51 0 287.9 382.67 51536 +1963 125 12.76 6.76 11.11 0 336.62 378.55 51706 +1963 126 10.12 4.12 8.47 0.01 287.2 288.58 51874 +1963 127 10.2 4.2 8.55 0 288.6 385.53 52039 +1963 128 14.17 8.17 12.52 0 365.87 378.3 52203 +1963 129 16.34 10.34 14.69 0.18 415.13 280.3 52365 +1963 130 15.41 9.41 13.76 0 393.37 376.94 52524 +1963 131 17.37 11.37 15.72 0 440.43 372.48 52681 +1963 132 25.77 19.77 24.12 0 700.27 342.7 52836 +1963 133 27.41 21.41 25.76 0.16 763.8 251.64 52989 +1963 134 26.33 20.33 24.68 1.39 721.44 256.06 53138 +1963 135 21.16 15.16 19.51 0.33 545.11 272.48 53286 +1963 136 23.77 17.77 22.12 1.18 628.9 265.46 53430 +1963 137 25.61 19.61 23.96 1.34 694.32 259.98 53572 +1963 138 21.66 15.66 20.01 0 560.39 363.39 53711 +1963 139 20.88 14.88 19.23 0 536.72 366.86 53848 +1963 140 18.15 12.15 16.5 0 460.44 376.21 53981 +1963 141 14.19 8.19 12.54 0 366.3 387.27 54111 +1963 142 16.4 10.4 14.75 0 416.57 382.15 54238 +1963 143 15.66 9.66 14.01 0 399.12 384.65 54362 +1963 144 16.09 10.09 14.44 0 409.18 384 54483 +1963 145 15.38 9.38 13.73 0 392.69 386.33 54600 +1963 146 15.95 9.95 14.3 0 405.89 385.22 54714 +1963 147 14.23 8.23 12.58 0 367.17 390.05 54824 +1963 148 16.34 10.34 14.69 0 415.13 385.04 54931 +1963 149 18.17 12.17 16.52 0.26 460.97 285.07 55034 +1963 150 16.69 10.69 15.04 0.01 423.59 288.55 55134 +1963 151 17.01 11.01 15.36 0 431.44 384.22 55229 +1963 152 23.25 17.25 21.6 0.11 611.39 272.28 55321 +1963 153 17.89 11.89 16.24 0.46 453.69 286.51 55409 +1963 154 21.43 15.43 19.78 0.25 553.32 277.95 55492 +1963 155 22.37 16.37 20.72 1.09 582.7 275.43 55572 +1963 156 25.04 19.04 23.39 0.17 673.47 267.33 55648 +1963 157 26.17 20.17 24.52 0 715.34 351.39 55719 +1963 158 26.37 20.37 24.72 0.03 722.97 262.95 55786 +1963 159 26.42 20.42 24.77 2.19 724.89 262.94 55849 +1963 160 25.25 19.25 23.6 0 681.09 356.24 55908 +1963 161 18.74 12.74 17.09 0 476.09 381.08 55962 +1963 162 17.87 11.87 16.22 0 453.17 383.81 56011 +1963 163 17.32 11.32 15.67 0.28 439.17 289.23 56056 +1963 164 19.32 13.32 17.67 0 491.92 379.54 56097 +1963 165 21.87 15.87 20.22 0 566.91 370.69 56133 +1963 166 22.39 16.39 20.74 0 583.34 368.78 56165 +1963 167 23.04 17.04 21.39 0 604.44 366.16 56192 +1963 168 23.24 17.24 21.59 0 611.06 365.43 56214 +1963 169 23.72 17.72 22.07 0 627.2 363.46 56231 +1963 170 24.19 18.19 22.54 0.49 643.35 271.11 56244 +1963 171 25.52 19.52 23.87 1.37 690.99 266.72 56252 +1963 172 25.19 19.19 23.54 0.04 678.9 267.84 56256 +1963 173 25.6 19.6 23.95 0.09 693.95 266.42 56255 +1963 174 24.17 18.17 22.52 0.04 642.66 271.13 56249 +1963 175 25.44 19.44 23.79 0 688.04 355.86 56238 +1963 176 17.78 11.78 16.13 0.78 450.85 288.32 56223 +1963 177 18.15 12.15 16.5 0.29 460.44 287.41 56203 +1963 178 16.13 10.13 14.48 0.04 410.13 291.78 56179 +1963 179 12.43 6.43 10.78 0 330.07 397.92 56150 +1963 180 15.21 9.21 13.56 0.02 388.82 293.43 56116 +1963 181 16.75 10.75 15.1 0.55 425.05 290.27 56078 +1963 182 18.55 12.55 16.9 0.4 471 286.17 56035 +1963 183 18.15 12.15 16.5 0 460.44 382.61 55987 +1963 184 23.1 17.1 21.45 0 606.42 365.07 55935 +1963 185 23.51 17.51 21.86 0 620.09 363.32 55879 +1963 186 19.19 13.19 17.54 0 488.33 378.85 55818 +1963 187 20.57 14.57 18.92 0 527.55 374.04 55753 +1963 188 24.99 18.99 23.34 0 671.66 356.28 55684 +1963 189 27.3 21.3 25.65 0 759.39 345.14 55611 +1963 190 25.89 19.89 24.24 0 704.76 351.64 55533 +1963 191 29.25 23.25 27.6 0 840.8 334.16 55451 +1963 192 27.06 21.06 25.41 0 749.85 345.45 55366 +1963 193 29.56 23.56 27.91 0 854.4 331.89 55276 +1963 194 25.47 19.47 23.82 0.03 689.15 264.42 55182 +1963 195 23.72 17.72 22.07 0.37 627.2 269.94 55085 +1963 196 21.49 15.49 19.84 0.33 555.15 276.15 54984 +1963 197 22.61 16.61 20.96 0 590.41 363.52 54879 +1963 198 24.94 18.94 23.29 0 669.86 353.44 54770 +1963 199 26.76 20.76 25.11 0 738.06 344.66 54658 +1963 200 29.25 23.25 27.6 0 840.8 331.31 54542 +1963 201 27.91 21.91 26.26 0 784.11 338.06 54423 +1963 202 27.15 21.15 25.5 0 753.41 341.38 54301 +1963 203 22.69 16.69 21.04 0 593 360.54 54176 +1963 204 18.87 12.87 17.22 0 479.6 373.38 54047 +1963 205 21.72 15.72 20.07 1.34 562.24 272.4 53915 +1963 206 25.56 19.56 23.91 0.2 692.47 260.2 53780 +1963 207 22.83 16.83 21.18 1.22 597.55 268.34 53643 +1963 208 23.53 17.53 21.88 0.54 620.77 265.78 53502 +1963 209 23.81 17.81 22.16 0.02 630.27 264.45 53359 +1963 210 23.19 17.19 21.54 0.1 609.4 265.87 53213 +1963 211 26.55 20.55 24.9 0 729.9 339.13 53064 +1963 212 24.4 18.4 22.75 0.07 650.69 261.01 52913 +1963 213 23.31 17.31 21.66 0 613.39 351.73 52760 +1963 214 23.54 17.54 21.89 0 621.1 350.09 52604 +1963 215 23.67 17.67 22.02 0.21 625.5 261.68 52445 +1963 216 23.94 17.94 22.29 0 634.72 346.82 52285 +1963 217 26.69 20.69 25.04 0.23 735.33 250.38 52122 +1963 218 24.06 18.06 22.41 0.14 638.85 258.51 51958 +1963 219 23.53 17.53 21.88 1.18 620.77 259.35 51791 +1963 220 24.36 18.36 22.71 0 649.28 341.51 51622 +1963 221 28.05 22.05 26.4 0.24 789.88 242.71 51451 +1963 222 29.83 23.83 28.18 0.07 866.39 234.92 51279 +1963 223 30.03 24.03 28.38 1.67 875.37 233.3 51105 +1963 224 32.27 26.27 30.62 0.27 981.36 222.65 50929 +1963 225 26.95 20.95 25.3 0.45 745.51 243.67 50751 +1963 226 24.24 18.24 22.59 2.27 645.09 251.77 50572 +1963 227 21.97 15.97 20.32 0.52 570.04 257.33 50392 +1963 228 21.76 15.76 20.11 0 563.48 342.66 50210 +1963 229 22.63 16.63 20.98 0 591.05 338.3 50026 +1963 230 20.75 14.75 19.1 0.44 532.86 257.72 49842 +1963 231 21.95 15.95 20.3 0.42 569.41 253.55 49656 +1963 232 21.67 15.67 20.02 0 560.7 337.72 49469 +1963 233 22.66 16.66 21.01 0.46 592.02 249.6 49280 +1963 234 19.3 13.3 17.65 0.49 491.36 256.92 49091 +1963 235 16.76 10.76 15.11 4.49 425.29 261.12 48900 +1963 236 14.99 8.99 13.34 0.82 383.87 263.29 48709 +1963 237 17.37 11.37 15.72 0.2 440.43 257.58 48516 +1963 238 19.23 13.23 17.58 0 489.43 336.54 48323 +1963 239 19.16 13.16 17.51 0.07 487.51 251.43 48128 +1963 240 20.77 14.77 19.12 0.07 533.45 246.42 47933 +1963 241 18.93 12.93 17.28 0.54 481.23 249.32 47737 +1963 242 17.53 11.53 15.88 0.27 444.47 250.91 47541 +1963 243 16.98 10.98 15.33 0.03 430.7 250.57 47343 +1963 244 13.33 7.33 11.68 0 348.2 340.57 47145 +1963 245 19.14 13.14 17.49 0.01 486.96 243.44 46947 +1963 246 17.41 11.41 15.76 0.04 441.43 245.49 46747 +1963 247 14.93 8.93 13.28 0 382.52 331.37 46547 +1963 248 12.21 6.21 10.56 0.02 325.76 251.2 46347 +1963 249 14.46 8.46 12.81 0.27 372.15 246.24 46146 +1963 250 18.95 12.95 17.3 0.01 481.77 236.55 45945 +1963 251 17.91 11.91 16.26 0.01 454.2 237.06 45743 +1963 252 18.56 12.56 16.91 0.01 471.27 234.17 45541 +1963 253 19.49 13.49 17.84 0.05 496.64 230.68 45339 +1963 254 18.02 12.02 16.37 0.61 457.05 232.06 45136 +1963 255 18.37 12.37 16.72 0.17 466.23 229.69 44933 +1963 256 21.93 15.93 20.28 0.1 568.78 220.33 44730 +1963 257 23.07 17.07 21.42 2.12 605.43 215.98 44527 +1963 258 18.26 12.26 16.61 2.58 463.33 224.87 44323 +1963 259 16.58 10.58 14.93 0 420.91 301.46 44119 +1963 260 19.98 13.98 18.33 0.6 510.47 217.88 43915 +1963 261 20.98 14.98 19.33 0.06 539.7 213.95 43711 +1963 262 18.07 12.07 16.42 0 458.35 290.75 43507 +1963 263 23.43 17.43 21.78 0 617.4 273 43303 +1963 264 23.29 17.29 21.64 0 612.72 271.02 43099 +1963 265 19.34 13.34 17.69 0 492.47 280.26 42894 +1963 266 18.79 12.79 17.14 0 477.44 279.23 42690 +1963 267 18.42 12.42 16.77 0 467.55 277.51 42486 +1963 268 20.96 14.96 19.31 0.01 539.11 201.3 42282 +1963 269 23.31 17.31 21.66 0.26 613.39 194.26 42078 +1963 270 23.43 17.43 21.78 0.2 617.4 192.11 41875 +1963 271 22.88 16.88 21.23 0.49 599.18 191.53 41671 +1963 272 17.8 11.8 16.15 0.11 451.37 199.59 41468 +1963 273 23.7 17.7 22.05 0 626.52 247.88 41265 +1963 274 15.82 9.82 14.17 0 402.84 265.17 41062 +1963 275 13.6 7.6 11.95 0 353.8 266.52 40860 +1963 276 10.66 4.66 9.01 0 296.77 268.43 40658 +1963 277 10.06 4.06 8.41 0 286.15 266.56 40456 +1963 278 12.36 6.36 10.71 0 328.69 260.29 40255 +1963 279 9.8 3.8 8.15 0 281.65 261.14 40054 +1963 280 12.79 6.79 11.14 0 337.22 254.13 39854 +1963 281 11.95 5.95 10.3 0.12 320.74 189.51 39654 +1963 282 16.14 10.14 14.49 0 410.37 242.88 39455 +1963 283 13 7 11.35 0.47 341.45 184.12 39256 +1963 284 12.86 6.86 11.21 0.02 338.63 182.02 39058 +1963 285 11.26 5.26 9.61 0 307.72 242.38 38861 +1963 286 10.85 4.85 9.2 0.89 300.2 180.11 38664 +1963 287 13.06 7.06 11.41 0.42 342.67 175.54 38468 +1963 288 12.8 6.8 11.15 0.08 337.42 173.75 38273 +1963 289 16.09 10.09 14.44 0.28 409.18 167.78 38079 +1963 290 15.41 9.41 13.76 1.17 393.37 166.56 37885 +1963 291 9.89 3.89 8.24 0.18 283.2 170.5 37693 +1963 292 9.6 3.6 7.95 0.03 278.23 168.73 37501 +1963 293 12.16 6.16 10.51 0 324.79 218.99 37311 +1963 294 11.41 5.41 9.76 0 310.51 217.1 37121 +1963 295 11.37 5.37 9.72 0.01 309.76 160.74 36933 +1963 296 14.7 8.7 13.05 0.03 377.42 155.3 36745 +1963 297 15.35 9.35 13.7 0.1 392 152.53 36560 +1963 298 18.2 12.2 16.55 0.04 461.75 146.95 36375 +1963 299 18.89 12.89 17.24 0 480.14 191.95 36191 +1963 300 14.69 8.69 13.04 0 377.2 196.49 36009 +1963 301 15.5 9.5 13.85 0.16 395.43 144.6 35829 +1963 302 13.08 7.08 11.43 0.76 343.08 145.28 35650 +1963 303 11.6 5.6 9.95 0.16 314.07 144.76 35472 +1963 304 10.92 4.92 9.27 0.01 301.47 143.52 35296 +1963 305 10.46 4.46 8.81 0 293.19 189.15 35122 +1963 306 6.61 0.61 4.96 1 231.21 142.97 34950 +1963 307 7.83 1.83 6.18 0.13 249.5 140.27 34779 +1963 308 11.57 5.57 9.92 0 313.51 180.58 34610 +1963 309 13.23 7.23 11.58 0.03 346.14 132.23 34444 +1963 310 11.4 5.4 9.75 0 310.32 176.07 34279 +1963 311 11.73 5.73 10.08 0.31 316.53 130.16 34116 +1963 312 8.52 2.52 6.87 0.5 260.38 130.64 33956 +1963 313 8.08 2.08 6.43 0.2 253.4 129.35 33797 +1963 314 10.64 4.64 8.99 0 296.41 168.08 33641 +1963 315 9.28 3.28 7.63 0.02 272.84 125.17 33488 +1963 316 11.62 5.62 9.97 0 314.45 162.39 33337 +1963 317 13.68 7.68 12.03 0 355.47 157.91 33188 +1963 318 15.69 9.69 14.04 0 399.82 153.08 33042 +1963 319 17.23 11.23 15.58 0.12 436.91 111.98 32899 +1963 320 15.2 9.2 13.55 0 388.59 150.3 32758 +1963 321 15.92 9.92 14.27 0.11 405.18 110.49 32620 +1963 322 12.97 6.97 11.32 0.5 340.85 111.85 32486 +1963 323 11.39 5.39 9.74 0 310.13 149.22 32354 +1963 324 11.15 5.15 9.5 0.2 305.68 110.57 32225 +1963 325 12.66 6.66 11.01 0.64 334.62 108.16 32100 +1963 326 11.4 5.4 9.75 0.1 310.32 108.06 31977 +1963 327 8.22 2.22 6.57 0.15 255.6 108.78 31858 +1963 328 7.02 1.02 5.37 0.54 237.22 108 31743 +1963 329 7.39 1.39 5.74 1.14 242.76 106.68 31631 +1963 330 10.26 4.26 8.61 0.37 289.65 103.86 31522 +1963 331 11.62 5.62 9.97 0 314.45 135.94 31417 +1963 332 12.48 6.48 10.83 0.01 331.05 100.12 31316 +1963 333 13.78 7.78 12.13 0 357.57 131.11 31218 +1963 334 16.9 10.9 15.25 0.19 428.73 94.8 31125 +1963 335 1.43 -4.57 -0.22 0 165.8 138.05 31035 +1963 336 -1.66 -7.66 -3.31 0.37 134.96 147.53 30949 +1963 337 -2.64 -8.64 -4.29 0.22 126.27 147.34 30867 +1963 338 -0.91 -6.91 -2.56 0.57 141.95 148.02 30790 +1963 339 1.21 -4.79 -0.44 0.15 163.42 146.68 30716 +1963 340 -0.52 -6.52 -2.17 0.04 145.7 146.92 30647 +1963 341 -2.73 -8.73 -4.38 0 125.5 180.35 30582 +1963 342 0.6 -5.4 -1.05 0 156.97 178.27 30521 +1963 343 1.05 -4.95 -0.6 0 161.71 177.18 30465 +1963 344 -2.4 -8.4 -4.05 0 128.35 177.52 30413 +1963 345 -3.74 -9.74 -5.39 0 117.11 177.61 30366 +1963 346 -4.55 -10.55 -6.2 0 110.73 177.37 30323 +1963 347 -7.19 -13.19 -8.84 0.82 92 147.52 30284 +1963 348 -3.67 -9.67 -5.32 0.14 117.67 147 30251 +1963 349 -1.91 -7.91 -3.56 0 132.69 178.35 30221 +1963 350 2.83 -3.17 1.18 0 181.67 175.63 30197 +1963 351 3 -3 1.35 0 183.68 174.96 30177 +1963 352 3.97 -2.03 2.32 0.13 195.54 142.62 30162 +1963 353 1.61 -4.39 -0.04 0.21 167.77 143.26 30151 +1963 354 -1.98 -7.98 -3.63 0 132.07 176.22 30145 +1963 355 -1.19 -7.19 -2.84 0.48 139.3 145.66 30144 +1963 356 -2.23 -8.23 -3.88 0 129.85 177.86 30147 +1963 357 1.73 -4.27 0.08 0 169.1 176.05 30156 +1963 358 0.25 -5.75 -1.4 0 153.37 176.74 30169 +1963 359 -0.97 -6.97 -2.62 0 141.38 177.33 30186 +1963 360 -1.75 -7.75 -3.4 0.03 134.14 146.04 30208 +1963 361 -1.37 -7.37 -3.02 1.06 137.62 149.51 30235 +1963 362 -6.99 -12.99 -8.64 0.01 93.31 151.14 30267 +1963 363 -11.31 -17.31 -12.96 0 68.25 185.24 30303 +1963 364 -8.91 -14.91 -10.56 0 81.33 185.09 30343 +1963 365 -5.39 -11.39 -7.04 0 104.44 184.69 30388 +1964 1 -3.4 -9.4 -5.05 0 119.88 184.88 30438 +1964 2 -3.4 -9.4 -5.05 0 119.88 185.53 30492 +1964 3 -3.4 -9.4 -5.05 0 119.88 186.39 30551 +1964 4 -3.4 -9.4 -5.05 0 119.88 187.21 30614 +1964 5 -3.4 -9.4 -5.05 0 119.88 187.75 30681 +1964 6 -3.4 -9.4 -5.05 0 119.88 188.53 30752 +1964 7 -3.4 -9.4 -5.05 0 119.88 189.21 30828 +1964 8 -3.4 -9.4 -5.05 0 119.88 190.58 30907 +1964 9 -3.4 -9.4 -5.05 0 119.88 191.72 30991 +1964 10 -3.4 -9.4 -5.05 0 119.88 192.89 31079 +1964 11 -3.4 -9.4 -5.05 0 119.88 193.74 31171 +1964 12 -3.4 -9.4 -5.05 0 119.88 194.61 31266 +1964 13 -3.4 -9.4 -5.05 0 119.88 196.09 31366 +1964 14 -3.4 -9.4 -5.05 0 119.88 197.42 31469 +1964 15 -3.4 -9.4 -5.05 0 119.88 198.71 31575 +1964 16 -3.4 -9.4 -5.05 0 119.88 199.85 31686 +1964 17 -3.4 -9.4 -5.05 0 119.88 201.37 31800 +1964 18 -3.4 -9.4 -5.05 0 119.88 203.11 31917 +1964 19 -3.4 -9.4 -5.05 0 119.88 204.87 32038 +1964 20 -3.4 -9.4 -5.05 0 119.88 206.29 32161 +1964 21 -3.4 -9.4 -5.05 0 119.88 208.13 32289 +1964 22 -3.4 -9.4 -5.05 0 119.88 209.71 32419 +1964 23 -3.4 -9.4 -5.05 0 119.88 211.3 32552 +1964 24 -3.4 -9.4 -5.05 0 119.88 213.19 32688 +1964 25 -3.4 -9.4 -5.05 0 119.88 214.9 32827 +1964 26 -3.4 -9.4 -5.05 0 119.88 216.65 32969 +1964 27 -3.4 -9.4 -5.05 0 119.88 218.49 33114 +1964 28 -3.4 -9.4 -5.05 0 119.88 220.51 33261 +1964 29 -3.4 -9.4 -5.05 0 119.88 222.71 33411 +1964 30 -3.4 -9.4 -5.05 0 119.88 224.77 33564 +1964 31 -3.4 -9.4 -5.05 0 119.88 226.96 33718 +1964 32 5.95 -0.05 4.3 0.5 221.81 178.81 33875 +1964 33 7.63 1.63 5.98 0 246.42 222.88 34035 +1964 34 4.43 -1.57 2.78 0 201.39 226.86 34196 +1964 35 5.62 -0.38 3.97 0 217.23 227.24 34360 +1964 36 7.43 1.43 5.78 0 243.37 227.16 34526 +1964 37 6.71 0.71 5.06 0 232.66 229.2 34694 +1964 38 2.01 -3.99 0.36 0 172.22 234.97 34863 +1964 39 0.98 -5.02 -0.67 0 160.96 237.91 35035 +1964 40 2.4 -3.6 0.75 0 176.66 239.18 35208 +1964 41 3.82 -2.18 2.17 0 193.66 240.18 35383 +1964 42 8.64 2.64 6.99 0 262.32 237.38 35560 +1964 43 4.52 -1.48 2.87 0 202.55 243.03 35738 +1964 44 4.22 -1.78 2.57 0 198.7 245.17 35918 +1964 45 1.91 -4.09 0.26 0.11 171.1 196.13 36099 +1964 46 0.81 -5.19 -0.84 0.39 159.17 198.42 36282 +1964 47 1.81 -4.19 0.16 0 169.99 254.02 36466 +1964 48 2.91 -3.09 1.26 0.1 182.61 200.71 36652 +1964 49 0.28 -5.72 -1.37 0 153.68 259.94 36838 +1964 50 2.34 -3.66 0.69 0 175.97 225.34 37026 +1964 51 -1.49 -7.49 -3.14 0 136.51 230.79 37215 +1964 52 -2.68 -8.68 -4.33 0 125.93 234.31 37405 +1964 53 -2.72 -8.72 -4.37 0 125.59 237.34 37596 +1964 54 0.52 -5.48 -1.13 0 156.14 238.22 37788 +1964 55 0.55 -5.45 -1.1 0 156.45 241.23 37981 +1964 56 4.22 -1.78 2.57 0 198.7 241.15 38175 +1964 57 5.98 -0.02 4.33 0 222.23 242.43 38370 +1964 58 4.68 -1.32 3.03 0 204.63 246.59 38565 +1964 59 5.02 -0.98 3.37 0 209.11 248.99 38761 +1964 60 8.04 2.04 6.39 0 252.77 248.76 38958 +1964 61 3.56 -2.44 1.91 0 190.45 256.15 39156 +1964 62 6.26 0.26 4.61 0 226.18 256.4 39355 +1964 63 8.19 2.19 6.54 0 255.13 257.27 39553 +1964 64 8.36 2.36 6.71 0 257.82 259.96 39753 +1964 65 9.87 3.87 8.22 0 282.86 260.91 39953 +1964 66 11.33 5.33 9.68 0 309.02 261.57 40154 +1964 67 7.77 1.77 6.12 2.59 248.57 201.87 40355 +1964 68 6.48 0.48 4.83 1 229.33 205.13 40556 +1964 69 7.14 1.14 5.49 0.18 239.01 206.54 40758 +1964 70 5.74 -0.26 4.09 0.32 218.88 209.85 40960 +1964 71 4.08 -1.92 2.43 0.03 196.93 213.31 41163 +1964 72 -0.68 -6.68 -2.33 0.43 144.15 251.33 41366 +1964 73 4.16 -1.84 2.51 0.62 197.94 249.76 41569 +1964 74 7 1 5.35 0.09 236.93 217.18 41772 +1964 75 2.9 -3.1 1.25 0 182.5 296.63 41976 +1964 76 -1.35 -7.35 -3 0 137.81 302.72 42179 +1964 77 0.24 -5.76 -1.41 0 153.27 304.21 42383 +1964 78 3.14 -2.86 1.49 0 185.35 304.42 42587 +1964 79 4.28 -1.72 2.63 0 199.47 306.05 42791 +1964 80 7.12 1.12 5.47 0.09 238.71 229.03 42996 +1964 81 5.82 -0.18 4.17 0 219.99 309.54 43200 +1964 82 6.86 0.86 5.21 0 234.86 310.96 43404 +1964 83 9.39 3.39 7.74 0.11 274.68 232.53 43608 +1964 84 6.81 0.81 5.16 0.3 234.13 237.07 43812 +1964 85 2.13 -3.87 0.48 0.57 173.58 242.78 44016 +1964 86 1.5 -4.5 -0.15 0 166.57 326.74 44220 +1964 87 2.27 -3.73 0.62 0 175.17 328.61 44424 +1964 88 0.25 -5.75 -1.4 0.09 153.37 249.61 44627 +1964 89 1.63 -4.37 -0.02 0 167.99 333.94 44831 +1964 90 0.15 -5.85 -1.5 0 152.36 337.67 45034 +1964 91 12.59 6.59 10.94 0.09 333.23 242.87 45237 +1964 92 12.73 6.73 11.08 0.33 336.02 244.33 45439 +1964 93 11.14 5.14 9.49 0 305.5 330.86 45642 +1964 94 11.45 5.45 9.8 0 311.26 332.46 45843 +1964 95 11.54 5.54 9.89 0.54 312.94 250.83 46045 +1964 96 16.7 10.7 15.05 1.58 423.83 244.23 46246 +1964 97 14.64 8.64 12.99 0.38 376.1 249.32 46446 +1964 98 14.23 8.23 12.58 0 367.17 335.24 46647 +1964 99 13.53 7.53 11.88 0.04 352.34 254.02 46846 +1964 100 12.35 6.35 10.7 0.14 328.5 257.24 47045 +1964 101 10 4 8.35 0 285.11 349.14 47243 +1964 102 13.85 7.85 12.2 0.3 359.05 257.82 47441 +1964 103 14.5 8.5 12.85 0.01 373.03 258.12 47638 +1964 104 16.22 10.22 14.57 0 412.27 341.93 47834 +1964 105 15.47 9.47 13.82 1.06 394.74 259.13 48030 +1964 106 13.05 7.05 11.4 0.01 342.47 264.37 48225 +1964 107 13.5 7.5 11.85 0.73 351.71 264.91 48419 +1964 108 12.51 6.51 10.86 0 331.65 357 48612 +1964 109 11.92 5.92 10.27 0.29 320.16 269.83 48804 +1964 110 19.18 13.18 17.53 0 488.06 343.47 48995 +1964 111 18.57 12.57 16.92 0.38 471.54 260.08 49185 +1964 112 18.76 12.76 17.11 0.68 476.63 260.77 49374 +1964 113 17.44 11.44 15.79 0.42 442.19 264.55 49561 +1964 114 16.04 10.04 14.39 0.05 408 268.42 49748 +1964 115 16.99 10.99 15.34 0.18 430.95 267.62 49933 +1964 116 18.04 12.04 16.39 0.56 457.57 266.33 50117 +1964 117 12.96 6.96 11.31 0 340.64 368.97 50300 +1964 118 7.47 1.47 5.82 0.15 243.98 285.15 50481 +1964 119 9.9 3.9 8.25 0 283.37 377.43 50661 +1964 120 9.11 3.11 7.46 0 270.01 379.99 50840 +1964 121 13.09 7.09 11.44 0 343.28 373.52 51016 +1964 122 13.75 7.75 12.1 0.27 356.94 279.95 51191 +1964 123 14.63 8.63 12.98 1.07 375.88 279.19 51365 +1964 124 12.65 6.65 11 0.43 334.42 283.34 51536 +1964 125 17.82 11.82 16.17 0.9 451.88 274.46 51706 +1964 126 19.44 13.44 17.79 0 495.25 362.02 51874 +1964 127 16.07 10.07 14.42 0 408.71 372.61 52039 +1964 128 19.36 13.36 17.71 0 493.03 364.11 52203 +1964 129 18.09 12.09 16.44 0 458.88 368.83 52365 +1964 130 21.76 15.76 20.11 0 563.48 357.55 52524 +1964 131 17.11 11.11 15.46 0 433.92 373.21 52681 +1964 132 19.31 13.31 17.66 0.21 491.64 275.6 52836 +1964 133 19.11 13.11 17.46 0.65 486.14 276.59 52989 +1964 134 15.51 9.51 13.86 0 395.66 379.72 53138 +1964 135 13.56 7.56 11.91 0 352.96 385.14 53286 +1964 136 14.45 8.45 12.8 0.72 371.94 287.77 53430 +1964 137 12.45 6.45 10.8 0 330.46 388.94 53572 +1964 138 17.04 11.04 15.39 1.54 432.18 283.7 53711 +1964 139 16.09 10.09 14.44 0.57 409.18 286.17 53848 +1964 140 19.93 13.93 18.28 0.27 509.04 277.93 53981 +1964 141 21.34 15.34 19.69 0.21 550.57 274.58 54111 +1964 142 21 15 19.35 0.11 540.3 275.86 54238 +1964 143 19.37 13.37 17.72 0.75 493.3 280.39 54362 +1964 144 16.31 10.31 14.66 0 414.42 383.4 54483 +1964 145 18.47 12.47 16.82 0 468.88 377.64 54600 +1964 146 18.81 12.81 17.16 0.04 477.98 282.71 54714 +1964 147 20.2 14.2 18.55 0 516.78 372.88 54824 +1964 148 21.53 15.53 19.88 0 556.38 368.56 54931 +1964 149 19.44 13.44 17.79 0.57 495.25 282.08 55034 +1964 150 17.77 11.77 16.12 0 450.6 381.63 55134 +1964 151 13.44 7.44 11.79 0.36 350.47 295.01 55229 +1964 152 20.15 14.15 18.5 0 515.34 374.56 55321 +1964 153 18.63 12.63 16.98 0.07 473.14 284.82 55409 +1964 154 15.99 9.99 14.34 0.07 406.83 290.78 55492 +1964 155 17.62 11.62 15.97 0.16 446.76 287.49 55572 +1964 156 19.66 13.66 18.01 0.16 501.4 282.95 55648 +1964 157 20.73 14.73 19.08 0.05 532.26 280.33 55719 +1964 158 23.78 17.78 22.13 3.08 629.24 271.67 55786 +1964 159 20.51 14.51 18.86 0.05 525.79 281.22 55849 +1964 160 22.5 16.5 20.85 0 586.86 367.81 55908 +1964 161 24.86 18.86 23.21 0.26 666.99 268.54 55962 +1964 162 24.63 18.63 22.98 0 658.8 359.12 56011 +1964 163 24.44 18.44 22.79 0.02 652.09 270.12 56056 +1964 164 26.62 20.62 24.97 0.01 732.62 262.61 56097 +1964 165 26.09 20.09 24.44 0.15 712.3 264.59 56133 +1964 166 26.67 20.67 25.02 1.22 734.56 262.55 56165 +1964 167 24.22 18.22 22.57 0 644.4 361.26 56192 +1964 168 19.84 13.84 18.19 0.17 506.48 283.51 56214 +1964 169 22.99 16.99 21.34 1.32 602.79 274.84 56231 +1964 170 22.86 16.86 21.21 0.01 598.53 275.23 56244 +1964 171 22.86 16.86 21.21 0 598.53 367.03 56252 +1964 172 26.68 20.68 25.03 0 734.95 350.1 56256 +1964 173 28.8 22.8 27.15 0 821.39 339.07 56255 +1964 174 26.81 20.81 25.16 0.19 740.02 262.02 56249 +1964 175 27.68 21.68 26.03 0.12 774.71 258.7 56238 +1964 176 22.18 16.18 20.53 0 576.65 369.51 56223 +1964 177 22.96 16.96 21.31 0 601.8 366.36 56203 +1964 178 24.21 18.21 22.56 0.23 644.05 270.91 56179 +1964 179 23.55 17.55 21.9 0.21 621.44 272.91 56150 +1964 180 21.43 15.43 19.78 1.23 553.32 279.02 56116 +1964 181 19.46 13.46 17.81 0.29 495.8 284.1 56078 +1964 182 18.17 12.17 16.52 0.07 460.97 287.05 56035 +1964 183 18.24 12.24 16.59 0 462.8 382.34 55987 +1964 184 17.46 11.46 15.81 0 442.7 384.51 55935 +1964 185 20.64 14.64 18.99 0 529.61 374.23 55879 +1964 186 17.72 11.72 16.07 0.03 449.31 287.55 55818 +1964 187 20.83 14.83 19.18 0.27 535.23 279.84 55753 +1964 188 18.49 12.49 16.84 0 469.41 380.61 55684 +1964 189 18.77 12.77 17.12 0 476.9 379.55 55611 +1964 190 17.11 11.11 15.46 0 433.92 384.15 55533 +1964 191 20.86 14.86 19.21 0.06 536.12 278.95 55451 +1964 192 21.41 15.41 19.76 0 552.71 369.66 55366 +1964 193 26.81 20.81 25.16 0 740.02 346.43 55276 +1964 194 24.13 18.13 22.48 0 641.27 358.46 55182 +1964 195 25.24 19.24 23.59 0.01 680.72 265.01 55085 +1964 196 22.71 16.71 21.06 0 593.64 363.58 54984 +1964 197 26.53 20.53 24.88 0 729.13 346.51 54879 +1964 198 29.34 23.34 27.69 0 844.73 331.49 54770 +1964 199 24.13 18.13 22.48 0 641.27 356.6 54658 +1964 200 26.28 20.28 24.63 0 719.53 346.59 54542 +1964 201 26.17 20.17 24.52 0 715.34 346.66 54423 +1964 202 23.54 17.54 21.89 0.91 621.1 268.24 54301 +1964 203 25.17 19.17 23.52 1.8 678.18 262.66 54176 +1964 204 24.02 18.02 22.37 0.82 637.47 266.01 54047 +1964 205 23.34 17.34 21.69 0.42 614.39 267.73 53915 +1964 206 23.95 17.95 22.3 0.09 635.06 265.45 53780 +1964 207 22.61 16.61 20.96 0.23 590.41 268.98 53643 +1964 208 25.39 19.39 23.74 0.48 686.21 259.83 53502 +1964 209 26.91 20.91 25.26 0.06 743.94 254.05 53359 +1964 210 23.28 17.28 21.63 0 612.39 354.13 53213 +1964 211 25.7 19.7 24.05 0.6 697.66 257.31 53064 +1964 212 26.73 20.73 25.08 0.07 736.89 253.14 52913 +1964 213 26.34 20.34 24.69 0.01 721.82 253.99 52760 +1964 214 25.67 19.67 24.02 0.09 696.55 255.76 52604 +1964 215 21.21 15.21 19.56 0 546.63 358.18 52445 +1964 216 22.3 16.3 20.65 0 580.46 353.23 52285 +1964 217 22.62 16.62 20.97 0 590.73 351.15 52122 +1964 218 26.83 20.83 25.18 0 740.8 332.41 51958 +1964 219 25.61 19.61 23.96 0.47 694.32 252.78 51791 +1964 220 22.55 16.55 20.9 0.08 588.47 261.5 51622 +1964 221 22.93 16.93 21.28 0.51 600.82 259.68 51451 +1964 222 20.32 14.32 18.67 0.2 520.25 265.87 51279 +1964 223 18.03 12.03 16.38 0 457.31 360.41 51105 +1964 224 15.65 9.65 14 0.63 398.89 274.3 50929 +1964 225 14.26 8.26 12.61 0.27 367.81 275.92 50751 +1964 226 16.22 10.22 14.57 0 412.27 361.95 50572 +1964 227 17.72 11.72 16.07 0.27 449.31 267.46 50392 +1964 228 14.96 8.96 13.31 0 383.2 362.51 50210 +1964 229 20.82 14.82 19.17 0 534.93 344.65 50026 +1964 230 22.28 16.28 20.63 0 579.83 338.34 49842 +1964 231 23.8 17.8 22.15 1.42 629.93 248.39 49656 +1964 232 24.67 18.67 23.02 0 660.22 326.4 49469 +1964 233 25.25 19.25 23.6 0 681.09 322.64 49280 +1964 234 23.55 17.55 21.9 1.07 621.44 246.08 49091 +1964 235 22.29 16.29 20.64 0 580.15 331.3 48900 +1964 236 17.38 11.38 15.73 0.29 440.68 258.81 48709 +1964 237 22.36 16.36 20.71 0 582.38 328.05 48516 +1964 238 16.8 10.8 15.15 0.08 426.27 257.44 48323 +1964 239 20.98 14.98 19.33 0.1 539.7 247.21 48128 +1964 240 20.85 14.85 19.2 0.19 535.82 246.22 47933 +1964 241 20.99 14.99 19.34 1.12 540 244.61 47737 +1964 242 19.68 13.68 18.03 0 501.96 328.5 47541 +1964 243 24.6 18.6 22.95 0 657.73 309.78 47343 +1964 244 22.74 16.74 21.09 0.22 594.62 236.21 47145 +1964 245 21.83 15.83 20.18 0 565.66 316.27 46947 +1964 246 17.4 11.4 15.75 0 441.18 327.34 46747 +1964 247 18.22 12.22 16.57 0.35 462.28 242.5 46547 +1964 248 15.28 9.28 13.63 0.02 390.41 246.46 46347 +1964 249 15.93 9.93 14.28 1.25 405.42 243.78 46146 +1964 250 12.36 6.36 10.71 0.79 328.69 247.89 45945 +1964 251 15.97 9.97 14.32 1.11 406.36 240.63 45743 +1964 252 17.82 11.82 16.17 0.05 451.88 235.62 45541 +1964 253 18.03 12.03 16.38 0.27 457.31 233.63 45339 +1964 254 20.54 14.54 18.89 0.06 526.67 226.84 45136 +1964 255 19.21 13.21 17.56 0 488.88 304.02 44933 +1964 256 19.72 13.72 18.07 0 503.09 300.37 44730 +1964 257 21.42 15.42 19.77 0.48 553.01 219.96 44527 +1964 258 20.29 14.29 18.64 0.98 519.38 220.76 44323 +1964 259 19.16 13.16 17.51 0 487.51 295.08 44119 +1964 260 20.18 14.18 18.53 0.4 516.2 217.46 43915 +1964 261 22.13 16.13 20.48 0.07 575.07 211.35 43711 +1964 262 17.04 11.04 15.39 0 432.18 293.21 43507 +1964 263 13.6 7.6 11.95 0 353.8 297.92 43303 +1964 264 14.84 8.84 13.19 0 380.52 292.92 43099 +1964 265 17.88 11.88 16.23 0 453.43 283.89 42894 +1964 266 21.24 15.24 19.59 0 547.53 272.66 42690 +1964 267 20.17 14.17 18.52 0 515.92 273.04 42486 +1964 268 19.68 13.68 18.03 0 501.96 271.84 42282 +1964 269 17.43 11.43 15.78 0.22 441.94 206.12 42078 +1964 270 17.37 11.37 15.72 0.02 440.43 204.27 41875 +1964 271 18.13 12.13 16.48 0.01 459.92 201.03 41671 +1964 272 16.74 10.74 15.09 0.44 424.8 201.33 41468 +1964 273 16.18 10.18 14.53 0 411.32 267.1 41265 +1964 274 5.81 -0.19 4.16 0 219.85 280.06 41062 +1964 275 7.27 1.27 5.62 0.09 240.96 206.69 40860 +1964 276 6.21 0.21 4.56 0 225.47 273.99 40658 +1964 277 13.09 7.09 11.44 0 343.28 262 40456 +1964 278 12.36 6.36 10.71 0.4 328.69 195.22 40255 +1964 279 14.99 8.99 13.34 0.02 383.87 189.78 40054 +1964 280 8.91 2.91 7.26 1.23 266.71 194.69 39854 +1964 281 9.28 3.28 7.63 1.7 272.84 192.26 39654 +1964 282 11.55 5.55 9.9 3.01 313.13 187.88 39455 +1964 283 10.24 4.24 8.59 0.75 289.3 187.1 39256 +1964 284 7.76 1.76 6.11 0.73 248.42 187.07 39058 +1964 285 12.81 6.81 11.16 0.13 337.62 180.1 38861 +1964 286 11.23 5.23 9.58 0.06 307.16 179.73 38664 +1964 287 7.9 1.9 6.25 0 250.58 240.76 38468 +1964 288 9.68 3.68 8.03 0.25 279.6 176.91 38273 +1964 289 10.18 4.18 8.53 0 288.25 232.6 38079 +1964 290 11.44 5.44 9.79 0 311.07 228.09 37885 +1964 291 10.81 4.81 9.16 0 299.47 226.2 37693 +1964 292 10.88 4.88 9.23 0 300.74 223.41 37501 +1964 293 12.63 6.63 10.98 0 334.03 218.34 37311 +1964 294 13.59 7.59 11.94 0 353.59 214.09 37121 +1964 295 16.24 10.24 14.59 0 412.74 207.1 36933 +1964 296 19.75 13.75 18.1 0 503.94 197.98 36745 +1964 297 18.95 12.95 17.3 0 481.77 196.99 36560 +1964 298 18.34 12.34 16.69 0.05 465.43 146.75 36375 +1964 299 16.08 10.08 14.43 0.3 408.95 147.7 36191 +1964 300 11.73 5.73 10.08 0.04 316.53 150.4 36009 +1964 301 14.31 8.31 12.66 0.53 368.89 145.93 35829 +1964 302 15.89 9.89 14.24 1.74 404.48 142.23 35650 +1964 303 15.9 9.9 14.25 0.68 404.71 140.34 35472 +1964 304 16.12 10.12 14.47 2.82 409.89 138.29 35296 +1964 305 8.21 2.21 6.56 0.08 255.44 143.59 35122 +1964 306 6.46 0.46 4.81 0.53 229.04 143.07 34950 +1964 307 5.82 -0.18 4.17 0 219.99 188.75 34779 +1964 308 5.07 -0.93 3.42 0 209.78 186.71 34610 +1964 309 2.23 -3.77 0.58 0.22 174.72 139.73 34444 +1964 310 5.33 -0.67 3.68 0 213.27 181.69 34279 +1964 311 7.64 1.64 5.99 0 246.57 177.62 34116 +1964 312 7.1 1.1 5.45 0 238.41 175.43 33956 +1964 313 6.52 0.52 4.87 0 229.91 173.77 33797 +1964 314 6.85 0.85 5.2 0 234.71 171.54 33641 +1964 315 9.55 3.55 7.9 0.01 277.38 124.98 33488 +1964 316 12.45 6.45 10.8 0.69 330.46 121.11 33337 +1964 317 13.87 7.87 12.22 0.01 359.47 118.26 33188 +1964 318 14.83 8.83 13.18 0 380.3 154.2 33042 +1964 319 11.62 5.62 9.97 0 314.45 156.26 32899 +1964 320 13.12 7.12 11.47 0.02 343.89 114.6 32758 +1964 321 13.26 7.26 11.61 0.01 346.76 112.94 32620 +1964 322 8.01 2.01 6.36 0.12 252.3 115.4 32486 +1964 323 8.49 2.49 6.84 0.08 259.9 113.89 32354 +1964 324 8.19 2.19 6.54 0 255.13 150.06 32225 +1964 325 9.51 3.51 7.86 0 276.71 147.25 32100 +1964 326 10.92 4.92 9.27 0.13 301.47 108.4 31977 +1964 327 13.5 7.5 11.85 0 351.71 140.1 31858 +1964 328 13.7 7.7 12.05 0.51 355.89 103.46 31743 +1964 329 8.23 2.23 6.58 0.03 255.76 106.2 31631 +1964 330 8.56 2.56 6.91 0 261.02 139.9 31522 +1964 331 6.94 0.94 5.29 0 236.04 139.81 31417 +1964 332 6.12 0.12 4.47 0.17 224.2 104.06 31316 +1964 333 10.67 4.67 9.02 0 296.95 134.15 31218 +1964 334 10.88 4.88 9.23 0.2 300.74 99.66 31125 +1964 335 3.34 -2.66 1.69 0.36 187.77 102.8 31035 +1964 336 -0.29 -6.29 -1.94 0.14 147.96 146.39 30949 +1964 337 0.73 -5.27 -0.92 0.06 158.33 144.82 30867 +1964 338 1.53 -4.47 -0.12 0.36 166.89 143.73 30790 +1964 339 -3.64 -9.64 -5.29 0.87 117.92 147.52 30716 +1964 340 -4.28 -10.28 -5.93 0.01 112.82 147.24 30647 +1964 341 -1.2 -7.2 -2.85 0 139.21 179.07 30582 +1964 342 5.08 -0.92 3.43 0.04 209.91 142.37 30521 +1964 343 6.46 0.46 4.81 0.02 229.04 140.34 30465 +1964 344 8.11 2.11 6.46 0 253.87 168.97 30413 +1964 345 6.44 0.44 4.79 0.07 228.76 94.47 30366 +1964 346 7.91 1.91 6.26 0.27 250.74 93.32 30323 +1964 347 4.14 -1.86 2.49 0.11 197.68 94.64 30284 +1964 348 3.9 -2.1 2.25 0.04 194.66 94.48 30251 +1964 349 6.37 0.37 4.72 0.45 227.75 93.11 30221 +1964 350 4.75 -1.25 3.1 0.21 205.55 93.59 30197 +1964 351 0.33 -5.67 -1.32 0 154.19 126.75 30177 +1964 352 0.09 -5.91 -1.56 0 151.75 126.75 30162 +1964 353 4.04 -1.96 2.39 0 196.42 124.8 30151 +1964 354 -0.82 -6.82 -2.47 0 142.8 127.02 30145 +1964 355 1.51 -4.49 -0.14 0 166.68 126.03 30144 +1964 356 -0.86 -6.86 -2.51 0 142.42 127.06 30147 +1964 357 0.7 -5.3 -0.95 0.15 158.01 94.86 30156 +1964 358 -0.15 -6.15 -1.8 0.09 149.35 139.24 30169 +1964 359 -2.12 -8.12 -3.77 0.25 130.82 140.66 30186 +1964 360 -0.57 -6.57 -2.22 0.24 145.22 141.23 30208 +1964 361 1.93 -4.07 0.28 0 171.33 172.07 30235 +1964 362 -0.22 -6.22 -1.87 0.09 148.65 141.65 30267 +1964 363 2.75 -3.25 1.1 0.17 180.73 140.65 30303 +1964 364 2.48 -3.52 0.83 0 177.58 172.66 30343 +1964 365 1.42 -4.58 -0.23 0.74 165.69 141.22 30388 +1965 1 1.73 -4.27 0.08 0 169.1 173.93 30438 +1965 2 0.57 -5.43 -1.08 0 156.66 175.05 30492 +1965 3 0.9 -5.1 -0.75 0 160.12 175.64 30551 +1965 4 0.82 -5.18 -0.83 0.02 159.27 143.19 30614 +1965 5 0.88 -5.12 -0.77 0 159.9 176.82 30681 +1965 6 0.23 -5.77 -1.42 0 153.17 177.87 30752 +1965 7 0.16 -5.84 -1.49 0 152.46 178.58 30828 +1965 8 3.03 -2.97 1.38 0.4 184.04 101.69 30907 +1965 9 2.75 -3.25 1.1 0.5 180.73 102.75 30991 +1965 10 3.72 -2.28 2.07 0 192.42 137.77 31079 +1965 11 1.54 -4.46 -0.11 0.59 167 104.93 31171 +1965 12 1.38 -4.62 -0.27 0 165.26 141.01 31266 +1965 13 -1.07 -7.07 -2.72 0.06 140.43 150.08 31366 +1965 14 0.6 -5.4 -1.05 0.7 156.97 150.43 31469 +1965 15 4.97 -1.03 3.32 0.27 208.45 107.66 31575 +1965 16 4.45 -1.55 2.8 0.02 201.65 108.87 31686 +1965 17 1.91 -4.09 0.26 0 171.1 148.29 31800 +1965 18 4.81 -1.19 3.16 0 206.34 148.5 31917 +1965 19 6.61 0.61 4.96 0 231.21 149.2 32038 +1965 20 6.12 0.12 4.47 0 224.2 151.12 32161 +1965 21 5.34 -0.66 3.69 0.05 213.41 115.24 32289 +1965 22 5.75 -0.25 4.1 0.03 219.02 116.34 32419 +1965 23 8.5 2.5 6.85 0.86 260.06 116.06 32552 +1965 24 7.77 1.77 6.12 0.21 248.57 118.05 32688 +1965 25 7.47 1.47 5.82 0.03 243.98 119.63 32827 +1965 26 7.04 1.04 5.39 0.26 237.52 121.31 32969 +1965 27 4.78 -1.22 3.13 0 205.94 165.43 33114 +1965 28 2.59 -3.41 0.94 0.45 178.86 126.78 33261 +1965 29 1.97 -4.03 0.32 0 171.77 171.8 33411 +1965 30 -0.48 -6.48 -2.13 0 146.09 175.38 33564 +1965 31 -1.28 -7.28 -2.93 0.21 138.46 173.37 33718 +1965 32 -2.26 -8.26 -3.91 0.11 129.58 175.45 33875 +1965 33 1.85 -4.15 0.2 0.23 170.43 175.43 34035 +1965 34 2.09 -3.91 0.44 0.57 173.13 176.55 34196 +1965 35 3.21 -2.79 1.56 0 186.2 223.27 34360 +1965 36 4.74 -1.26 3.09 0 205.42 186.24 34526 +1965 37 1.74 -4.26 0.09 0 169.21 190.7 34694 +1965 38 1.7 -4.3 0.05 0.64 168.77 145.11 34863 +1965 39 3.71 -2.29 2.06 0.02 192.3 146.07 35035 +1965 40 1.59 -4.41 -0.06 0.06 167.55 149.11 35208 +1965 41 3.22 -2.78 1.57 0 186.32 200.36 35383 +1965 42 0.32 -5.68 -1.33 0 154.09 204.8 35560 +1965 43 1.85 -4.15 0.2 0 170.43 206.58 35738 +1965 44 2.96 -3.04 1.31 0 183.21 208.41 35918 +1965 45 -1.07 -7.07 -2.72 0 140.43 213.58 36099 +1965 46 -7.28 -13.28 -8.93 0 91.41 219.09 36282 +1965 47 -6.33 -12.33 -7.98 0 97.77 221.62 36466 +1965 48 -1.46 -7.46 -3.11 0 136.79 222.23 36652 +1965 49 2.02 -3.98 0.37 0 172.34 222.88 36838 +1965 50 -0.09 -6.09 -1.74 0 149.94 226.96 37026 +1965 51 0.45 -5.55 -1.2 0 155.42 229.62 37215 +1965 52 1.89 -4.11 0.24 0 170.88 231.5 37405 +1965 53 -0.01 -6.01 -1.66 0.05 150.74 212.07 37596 +1965 54 -0.73 -6.73 -2.38 0 143.67 274.07 37788 +1965 55 1.81 -4.19 0.16 0 169.99 240.35 37981 +1965 56 2.69 -3.31 1.04 0 180.03 242.41 38175 +1965 57 1.99 -4.01 0.34 0 172 245.85 38370 +1965 58 1.81 -4.19 0.16 0 169.99 248.95 38565 +1965 59 5.23 -0.77 3.58 0 211.92 248.8 38761 +1965 60 9.79 3.79 8.14 0 281.48 246.65 38958 +1965 61 8.87 2.87 7.22 0 266.06 250.69 39156 +1965 62 11.7 5.7 10.05 0 315.97 249.68 39355 +1965 63 8.56 2.56 6.91 0 261.02 256.83 39553 +1965 64 13.11 7.11 11.46 0 343.69 253.32 39753 +1965 65 12.2 6.2 10.55 0 325.57 257.57 39953 +1965 66 9.61 3.61 7.96 0.23 278.4 197.98 40154 +1965 67 8.33 2.33 6.68 0.06 257.34 201.36 40355 +1965 68 9.78 3.78 8.13 0 281.31 269.46 40556 +1965 69 9.23 3.23 7.58 0.11 272 204.6 40758 +1965 70 7.76 1.76 6.11 0.18 248.42 208.12 40960 +1965 71 7.03 1.03 5.38 0.5 237.37 210.96 41163 +1965 72 9.87 3.87 8.22 1.6 282.86 210.34 41366 +1965 73 10.22 4.22 8.57 0.85 288.95 211.95 41569 +1965 74 5.76 -0.24 4.11 0.05 219.16 218.24 41772 +1965 75 3.7 -2.3 2.05 0 192.17 295.87 41976 +1965 76 6.75 0.75 5.1 0 233.25 295.25 42179 +1965 77 5.19 -0.81 3.54 0.02 211.39 224.73 42383 +1965 78 4.75 -1.25 3.1 0 205.55 302.81 42587 +1965 79 3.91 -2.09 2.26 0 194.79 306.43 42791 +1965 80 3.27 -2.73 1.62 0.07 186.92 232.23 42996 +1965 81 3.91 -2.09 2.26 0 194.79 311.62 43200 +1965 82 5.17 -0.83 3.52 0 211.12 312.96 43404 +1965 83 10.4 4.4 8.75 0 292.12 308.5 43608 +1965 84 10.44 4.44 8.79 0 292.83 310.96 43812 +1965 85 9 3 7.35 0 268.19 315.64 44016 +1965 86 6.23 0.23 4.58 0 225.75 321.76 44220 +1965 87 7.19 1.19 5.54 0 239.76 323.09 44424 +1965 88 9.14 3.14 7.49 0.33 270.51 242.05 44627 +1965 89 9.28 3.28 7.63 1.11 272.84 243.6 44831 +1965 90 7.02 1.02 5.37 0.36 237.22 247.78 45034 +1965 91 12.9 6.9 11.25 0 339.43 323.24 45237 +1965 92 15.05 9.05 13.4 0.49 385.21 240.79 45439 +1965 93 6.99 0.99 5.34 0.96 236.78 252.89 45642 +1965 94 4.78 -1.22 3.13 0.27 205.94 256.61 45843 +1965 95 9.28 3.28 7.63 0 272.84 338.22 46045 +1965 96 9.86 3.86 8.21 0 282.68 339.42 46246 +1965 97 15.96 9.96 14.31 0.46 406.12 247.07 46446 +1965 98 10.52 4.52 8.87 1.61 294.26 256.76 46647 +1965 99 8.09 2.09 6.44 0.02 253.55 261.17 46846 +1965 100 6.94 0.94 5.29 0.12 236.04 263.88 47045 +1965 101 6.82 0.82 5.17 0 234.27 353.97 47243 +1965 102 9.2 3.2 7.55 0 271.5 352.37 47441 +1965 103 9.71 3.71 8.06 0 280.11 353.4 47638 +1965 104 9.54 3.54 7.89 0.14 277.21 266.64 47834 +1965 105 11.45 5.45 9.8 0.2 311.26 265.48 48030 +1965 106 16.57 10.57 14.92 1.86 420.67 258.32 48225 +1965 107 16.77 10.77 15.12 1.39 425.54 259.16 48419 +1965 108 16.92 10.92 15.27 0.34 429.22 260.15 48612 +1965 109 12.95 6.95 11.3 0.02 340.44 268.28 48804 +1965 110 12.96 6.96 11.31 0 340.64 359.1 48995 +1965 111 12.5 6.5 10.85 0 331.45 361.59 49185 +1965 112 11.73 5.73 10.08 0 316.53 364.64 49374 +1965 113 9.99 3.99 8.34 0.29 284.93 276.9 49561 +1965 114 12.02 6.02 10.37 0.52 322.08 275.19 49748 +1965 115 14.73 8.73 13.08 1.05 378.08 271.87 49933 +1965 116 12.85 6.85 11.2 1.94 338.42 275.92 50117 +1965 117 14.5 8.5 12.85 0.19 373.03 274.16 50300 +1965 118 13.66 7.66 12.01 0 355.05 368.77 50481 +1965 119 14.2 8.2 12.55 0.03 366.52 276.56 50661 +1965 120 15.53 9.53 13.88 0.06 396.12 275.05 50840 +1965 121 15.59 9.59 13.94 1.81 397.51 275.77 51016 +1965 122 13.54 7.54 11.89 0.63 352.55 280.3 51191 +1965 123 13.63 7.63 11.98 1.17 354.42 280.93 51365 +1965 124 15.45 9.45 13.8 0.08 394.29 278.5 51536 +1965 125 17.74 11.74 16.09 0.37 449.83 274.63 51706 +1965 126 17.16 11.16 15.51 0.42 435.17 276.59 51874 +1965 127 15.93 9.93 14.28 0.36 405.42 279.73 52039 +1965 128 14.24 8.24 12.59 0.24 367.38 283.6 52203 +1965 129 15.58 9.58 13.93 0 397.27 375.71 52365 +1965 130 11.57 5.57 9.92 0.07 313.51 289.2 52524 +1965 131 14.63 8.63 12.98 0 375.88 379.66 52681 +1965 132 16.67 10.67 15.02 0 423.1 375.25 52836 +1965 133 17.71 11.71 16.06 0 449.06 373.02 52989 +1965 134 17.82 11.82 16.17 0 451.88 373.4 53138 +1965 135 18.79 12.79 17.14 0.16 477.44 278.38 53286 +1965 136 16.78 10.78 15.13 0.26 425.78 283.26 53430 +1965 137 15.45 9.45 13.8 0.88 394.29 286.44 53572 +1965 138 16.19 10.19 14.54 0.02 411.56 285.45 53711 +1965 139 16.8 10.8 15.15 0.07 426.27 284.72 53848 +1965 140 14.02 8.02 12.37 0.27 362.66 290.42 53981 +1965 141 11.56 5.56 9.91 0 313.32 393.06 54111 +1965 142 15.26 9.26 13.61 0 389.95 385.14 54238 +1965 143 17.41 11.41 15.76 1.76 441.43 284.89 54362 +1965 144 16.27 10.27 14.62 0.03 413.46 287.63 54483 +1965 145 21.45 15.45 19.8 0 553.93 367.65 54600 +1965 146 18.47 12.47 16.82 0.12 468.88 283.51 54714 +1965 147 18.06 12.06 16.41 0.28 458.09 284.8 54824 +1965 148 15.86 9.86 14.21 0.15 403.78 289.75 54931 +1965 149 14.27 8.27 12.62 0.73 368.03 293 55034 +1965 150 12.79 6.79 11.14 3.34 337.22 295.81 55134 +1965 151 15.04 9.04 13.39 1.58 384.99 292.12 55229 +1965 152 21.38 15.38 19.73 0.09 551.79 277.67 55321 +1965 153 19.95 13.95 18.3 0 509.61 375.48 55409 +1965 154 18.03 12.03 16.38 0 457.31 381.91 55492 +1965 155 21.22 15.22 19.57 0.02 546.93 278.66 55572 +1965 156 21.03 15.03 19.38 0 541.2 372.55 55648 +1965 157 21.4 15.4 19.75 0.18 552.4 278.53 55719 +1965 158 23.06 17.06 21.41 0.04 605.1 273.88 55786 +1965 159 23.61 17.61 21.96 0 623.47 363.17 55849 +1965 160 24.62 18.62 22.97 0 658.44 359.04 55908 +1965 161 24.22 18.22 22.57 0.1 644.4 270.63 55962 +1965 162 21.51 15.51 19.86 0.07 555.77 278.76 56011 +1965 163 19.77 13.77 18.12 0.17 504.5 283.51 56056 +1965 164 21.92 15.92 20.27 0.31 568.47 277.81 56097 +1965 165 23.33 17.33 21.68 0.34 614.06 273.72 56133 +1965 166 22.27 16.27 20.62 0.14 579.51 276.94 56165 +1965 167 20.59 14.59 18.94 0.02 528.14 281.53 56192 +1965 168 22.9 16.9 21.25 0.28 599.84 275.1 56214 +1965 169 24.51 18.51 22.86 1.9 654.55 270.07 56231 +1965 170 25.01 19.01 23.36 2.03 672.38 268.41 56244 +1965 171 25.51 19.51 23.86 1.78 690.62 266.75 56252 +1965 172 21.33 15.33 19.68 0.74 550.27 279.64 56256 +1965 173 19.98 13.98 18.33 0.8 510.47 283.19 56255 +1965 174 20.08 14.08 18.43 0.02 513.33 282.87 56249 +1965 175 17.94 11.94 16.29 1.57 454.98 287.99 56238 +1965 176 16.33 10.33 14.68 0.21 414.89 291.43 56223 +1965 177 15.93 9.93 14.28 1.35 405.42 292.17 56203 +1965 178 13.65 7.65 12 0.08 354.84 296.46 56179 +1965 179 17.49 11.49 15.84 1.32 443.46 288.83 56150 +1965 180 20.17 14.17 18.52 0 515.92 376.49 56116 +1965 181 19.43 13.43 17.78 0.24 494.97 284.17 56078 +1965 182 16.94 10.94 15.29 0.2 429.71 289.76 56035 +1965 183 20.25 14.25 18.6 0.02 518.22 281.87 55987 +1965 184 20.61 14.61 18.96 0.93 528.72 280.82 55935 +1965 185 20.3 14.3 18.65 0.57 519.67 281.56 55879 +1965 186 21.01 15.01 19.36 1.18 540.6 279.5 55818 +1965 187 26.48 20.48 24.83 0.64 727.2 262.21 55753 +1965 188 22.29 16.29 20.64 0.8 580.15 275.6 55684 +1965 189 21.15 15.15 19.5 2.56 544.81 278.65 55611 +1965 190 15.93 9.93 14.28 0.63 405.42 290.56 55533 +1965 191 17.37 11.37 15.72 0.01 440.43 287.35 55451 +1965 192 17.03 11.03 15.38 0 431.94 383.8 55366 +1965 193 23.38 17.38 21.73 0 615.73 361.79 55276 +1965 194 22.74 16.74 21.09 0.01 594.62 273.1 55182 +1965 195 21.42 15.42 19.77 0.47 553.01 276.64 55085 +1965 196 23.74 17.74 22.09 1.58 627.88 269.58 54984 +1965 197 22.31 16.31 20.66 2.14 580.78 273.51 54879 +1965 198 24.55 18.55 22.9 0 655.97 355.15 54770 +1965 199 25.24 19.24 23.59 0 680.72 351.77 54658 +1965 200 21.82 15.82 20.17 0.01 565.35 274.02 54542 +1965 201 18.84 12.84 17.19 0.62 478.79 281.3 54423 +1965 202 22.5 16.5 20.85 0.37 586.86 271.33 54301 +1965 203 24 18 22.35 0.03 636.78 266.45 54176 +1965 204 24.98 18.98 23.33 0.96 671.3 262.93 54047 +1965 205 25.88 19.88 24.23 0 704.39 346.01 53915 +1965 206 23.42 17.42 21.77 0.83 617.07 267.07 53780 +1965 207 24.53 18.53 22.88 0 655.26 350.84 53643 +1965 208 25.05 19.05 23.4 0 673.83 347.95 53502 +1965 209 23.46 17.46 21.81 0.08 618.41 265.51 53359 +1965 210 21.91 15.91 20.26 0.56 568.16 269.54 53213 +1965 211 18.32 12.32 16.67 0.16 464.91 277.93 53064 +1965 212 16.82 10.82 15.17 0.34 426.76 280.56 52913 +1965 213 17.77 11.77 16.12 0.19 450.6 277.97 52760 +1965 214 18.64 12.64 16.99 0.05 473.41 275.46 52604 +1965 215 18.94 12.94 17.29 0.61 481.5 274.25 52445 +1965 216 20.58 14.58 18.93 0.23 527.84 269.51 52285 +1965 217 20.68 14.68 19.03 0.66 530.79 268.59 52122 +1965 218 19.16 13.16 17.51 0.27 487.51 271.69 51958 +1965 219 19.4 13.4 17.75 0.41 494.14 270.34 51791 +1965 220 17.92 11.92 16.27 0 454.46 363.96 51622 +1965 221 16.86 10.86 15.21 0 427.74 365.91 51451 +1965 222 17.75 11.75 16.1 0 450.08 362.37 51279 +1965 223 19.03 13.03 17.38 0.92 483.95 268.08 51105 +1965 224 21.01 15.01 19.36 0 540.6 349.99 50929 +1965 225 19.49 13.49 17.84 0 496.64 353.81 50751 +1965 226 17.6 11.6 15.95 0.53 446.25 268.68 50572 +1965 227 16.24 10.24 14.59 0.1 412.74 270.44 50392 +1965 228 17.15 11.15 15.5 0 434.92 356.95 50210 +1965 229 20.96 14.96 19.31 0.01 539.11 258.14 50026 +1965 230 20.46 14.46 18.81 0.08 524.33 258.43 49842 +1965 231 19.38 13.38 17.73 0 493.58 346.52 49656 +1965 232 18.44 12.44 16.79 0 468.08 347.95 49469 +1965 233 26.05 20.05 24.4 0.25 710.79 239.39 49280 +1965 234 24.87 18.87 23.22 0 667.35 322.87 49091 +1965 235 23.87 17.87 22.22 0 632.32 325.43 48900 +1965 236 23.42 17.42 21.77 0 617.07 325.77 48709 +1965 237 23.41 17.41 21.76 0 616.73 324.22 48516 +1965 238 24.87 18.87 23.22 0.01 667.35 237.68 48323 +1965 239 21.2 15.2 19.55 0.1 546.32 246.67 48128 +1965 240 18.72 12.72 17.07 2.87 475.56 251.07 47933 +1965 241 19.42 13.42 17.77 0.8 494.69 248.25 47737 +1965 242 17.67 11.67 16.02 0.13 448.04 250.63 47541 +1965 243 18.01 12.01 16.36 0 456.79 331.39 47343 +1965 244 14.88 8.88 13.23 0.11 381.41 252.94 47145 +1965 245 15.53 9.53 13.88 0 396.12 333.9 46947 +1965 246 18.05 12.05 16.4 0.14 457.83 244.23 46747 +1965 247 14.27 8.27 12.62 0 368.03 332.81 46547 +1965 248 16.32 10.32 14.67 0 414.65 326.2 46347 +1965 249 17.6 11.6 15.95 0 446.25 320.95 46146 +1965 250 19.14 13.14 17.49 0 486.96 314.88 45945 +1965 251 20.96 14.96 19.31 0.27 539.11 230.59 45743 +1965 252 21.92 15.92 20.27 0 568.47 302.31 45541 +1965 253 25.07 19.07 23.42 0 674.55 289.16 45339 +1965 254 24.76 18.76 23.11 0 663.42 288.33 45136 +1965 255 28.23 22.23 26.58 0.02 797.35 203.96 44933 +1965 256 28.73 22.73 27.08 0.3 818.41 200.71 44730 +1965 257 27.39 21.39 25.74 1.65 763 203.69 44527 +1965 258 24.03 18.03 22.38 0.48 637.82 211.83 44323 +1965 259 20.2 14.2 18.55 0.13 516.78 219.16 44119 +1965 260 21.55 15.55 19.9 0.16 557 214.46 43915 +1965 261 21.01 15.01 19.36 0.88 540.6 213.89 43711 +1965 262 20.67 14.67 19.02 0 530.49 283.86 43507 +1965 263 20.09 14.09 18.44 0 513.62 283.09 43303 +1965 264 18.12 12.12 16.47 0 459.66 285.66 43099 +1965 265 11.25 5.25 9.6 0 307.53 296.98 42894 +1965 266 10.97 4.97 9.32 0 302.38 294.88 42690 +1965 267 12.47 6.47 10.82 0.01 330.86 217.28 42486 +1965 268 11.08 5.08 9.43 0.04 304.4 217.02 42282 +1965 269 13.08 7.08 11.43 0 343.08 283.5 42078 +1965 270 12.86 6.86 11.21 0 338.63 281.22 41875 +1965 271 12.48 6.48 10.83 0 331.05 279.21 41671 +1965 272 14.53 8.53 12.88 0.75 373.68 204.63 41468 +1965 273 18.6 12.6 16.95 0.34 472.34 196.34 41265 +1965 274 12.14 6.14 10.49 0 324.4 271.73 41062 +1965 275 12.85 6.85 11.2 0 338.42 267.79 40860 +1965 276 11.96 5.96 10.31 0 320.93 266.49 40658 +1965 277 10.71 4.71 9.06 0 297.67 265.66 40456 +1965 278 13.5 7.5 11.85 0 351.71 258.45 40255 +1965 279 14.48 8.48 12.83 0 372.59 253.95 40054 +1965 280 12.75 6.75 11.1 0 336.42 254.19 39854 +1965 281 15.61 9.61 13.96 0 397.97 246.58 39654 +1965 282 9.48 3.48 7.83 0 276.2 253.31 39455 +1965 283 9.81 3.81 8.16 0 281.82 250.03 39256 +1965 284 12.49 6.49 10.84 0 331.25 243.26 39058 +1965 285 12.06 6.06 10.41 0 322.85 241.24 38861 +1965 286 11.79 5.79 10.14 0 317.68 238.86 38664 +1965 287 9.18 3.18 7.53 0 271.17 239.3 38468 +1965 288 7.29 1.29 5.64 0 241.26 238.58 38273 +1965 289 9.49 3.49 7.84 0 276.37 233.44 38079 +1965 290 11.93 5.93 10.28 0 320.35 227.42 37885 +1965 291 13.32 7.32 11.67 0 347.99 222.74 37693 +1965 292 15.84 9.84 14.19 0 403.31 216.06 37501 +1965 293 14.62 8.62 12.97 0 375.66 215.38 37311 +1965 294 12.76 6.76 11.11 0 336.62 215.29 37121 +1965 295 9.06 3.06 7.41 0 269.18 217.06 36933 +1965 296 11 5 9.35 0 302.93 212.19 36745 +1965 297 12.4 6.4 10.75 0 329.48 207.67 36560 +1965 298 9.37 3.37 7.72 0 274.35 208.74 36375 +1965 299 11.88 5.88 10.23 0 319.39 202.99 36191 +1965 300 10.15 4.15 8.5 0 287.72 202.4 36009 +1965 301 11.41 5.41 9.76 0 310.51 198.41 35829 +1965 302 12.04 6.04 10.39 0 322.47 195.04 35650 +1965 303 11.96 5.96 10.31 0 320.93 192.58 35472 +1965 304 12.3 6.3 10.65 0 327.52 189.72 35296 +1965 305 5.75 -0.25 4.1 0.25 219.02 145.22 35122 +1965 306 3.82 -2.18 2.17 0.02 193.66 144.61 34950 +1965 307 3.45 -2.55 1.8 2.36 189.1 142.89 34779 +1965 308 5.95 -0.05 4.3 0.31 221.81 139.51 34610 +1965 309 7.31 1.31 5.66 0.68 241.56 136.91 34444 +1965 310 5.35 -0.65 3.7 0.17 213.54 136.26 34279 +1965 311 4.46 -1.54 2.81 0 201.78 180.13 34116 +1965 312 6.54 0.54 4.89 0.15 230.2 131.92 33956 +1965 313 7.4 1.4 5.75 0.1 242.92 129.79 33797 +1965 314 6.24 0.24 4.59 0 225.9 172.03 33641 +1965 315 5.86 -0.14 4.21 0 220.55 169.77 33488 +1965 316 1.93 -4.07 0.28 0 171.33 170.15 33337 +1965 317 3.83 -2.17 2.18 0.42 193.79 125.08 33188 +1965 318 2.75 -3.25 1.1 2.03 180.73 123.81 33042 +1965 319 6.75 0.75 5.1 0.34 233.25 120.48 32899 +1965 320 7.15 1.15 5.5 0.79 239.16 118.85 32758 +1965 321 5.6 -0.4 3.95 0 216.95 157.5 32620 +1965 322 4.93 -1.07 3.28 0 207.92 156.13 32486 +1965 323 6.48 0.48 4.83 0 229.33 153.43 32354 +1965 324 1.82 -4.18 0.17 0 170.1 154.29 32225 +1965 325 1.76 -4.24 0.11 0 169.43 152.58 32100 +1965 326 2.44 -3.56 0.79 0 177.12 150.74 31977 +1965 327 6.84 0.84 5.19 0.14 234.57 109.57 31858 +1965 328 7.8 1.8 6.15 0.34 249.03 107.56 31743 +1965 329 6.08 0.08 4.43 0.44 223.63 107.37 31631 +1965 330 4.81 -1.19 3.16 0 206.34 142.55 31522 +1965 331 4.83 -1.17 3.18 0.19 206.6 105.91 31417 +1965 332 5.88 -0.12 4.23 0.72 220.83 104.17 31316 +1965 333 5.6 -0.4 3.95 0.39 216.95 103.5 31218 +1965 334 11.22 5.22 9.57 0.01 306.98 99.43 31125 +1965 335 9.27 3.27 7.62 1.52 272.67 99.82 31035 +1965 336 8.32 2.32 6.67 0.01 257.19 99.58 30949 +1965 337 7.19 1.19 5.54 0 239.76 131.94 30867 +1965 338 7.41 1.41 5.76 0 243.07 130.85 30790 +1965 339 6.96 0.96 5.31 0 236.34 130.38 30716 +1965 340 5.77 -0.23 4.12 0 219.3 130.43 30647 +1965 341 8.09 2.09 6.44 0 253.55 127.95 30582 +1965 342 6.73 0.73 5.08 0.05 232.96 96.11 30521 +1965 343 8.04 2.04 6.39 0.53 252.77 94.82 30465 +1965 344 6.88 0.88 5.23 0 235.16 126.1 30413 +1965 345 8.84 2.84 7.19 0 265.57 124.29 30366 +1965 346 7.08 1.08 5.43 0 238.11 124.99 30323 +1965 347 4.21 -1.79 2.56 0.14 198.57 94.61 30284 +1965 348 2.18 -3.82 0.53 0 174.15 126.85 30251 +1965 349 -1.3 -7.3 -2.95 0 138.27 127.96 30221 +1965 350 -0.3 -6.3 -1.95 0.39 147.86 140.38 30197 +1965 351 -6.59 -12.59 -8.24 0.42 95.99 143.13 30177 +1965 352 -4.22 -10.22 -5.87 0 113.29 174.65 30162 +1965 353 -4.55 -10.55 -6.2 0.01 110.73 142.65 30151 +1965 354 -1.41 -7.41 -3.06 0 137.25 173.65 30145 +1965 355 1.83 -4.17 0.18 0 170.21 172.04 30144 +1965 356 3.88 -2.12 2.23 0 194.41 170.51 30147 +1965 357 3.86 -2.14 2.21 0 194.16 170.05 30156 +1965 358 9.15 3.15 7.5 0 270.67 165.51 30169 +1965 359 9.02 3.02 7.37 0.1 268.52 91.4 30186 +1965 360 7.09 1.09 5.44 1.19 238.26 92.69 30208 +1965 361 10.48 4.48 8.83 0 293.55 121.4 30235 +1965 362 10.57 4.57 8.92 0.73 295.15 91.31 30267 +1965 363 5.61 -0.39 3.96 0 217.09 125.87 30303 +1965 364 7.8 1.8 6.15 0.28 249.03 93.62 30343 +1965 365 5.84 -0.16 4.19 0.02 220.27 95.02 30388 +1966 1 2.3 -3.7 0.65 0 175.51 129.54 30438 +1966 2 -0.19 -6.19 -1.84 0 148.95 131.41 30492 +1966 3 0.98 -5.02 -0.67 0 160.96 131.85 30551 +1966 4 0 -6 -1.65 0 150.84 133.2 30614 +1966 5 4.8 -1.2 3.15 0.23 206.2 98.57 30681 +1966 6 2.63 -3.37 0.98 1.09 179.33 100.13 30752 +1966 7 1.08 -4.92 -0.57 0.17 162.03 101.3 30828 +1966 8 2.79 -3.21 1.14 1.02 181.2 101.79 30907 +1966 9 -0.26 -6.26 -1.91 0.21 148.25 147.07 30991 +1966 10 -4.38 -10.38 -6.03 0 112.05 184.42 31079 +1966 11 -2.7 -8.7 -4.35 0.01 125.76 149.32 31171 +1966 12 -5.13 -11.13 -6.78 0 106.36 186.47 31266 +1966 13 -3.81 -9.81 -5.46 0.45 116.55 152.73 31366 +1966 14 -7.41 -13.41 -9.06 0 90.57 191.39 31469 +1966 15 -7.69 -13.69 -9.34 0.01 88.78 155.58 31575 +1966 16 -3.62 -9.62 -5.27 0 118.08 192.72 31686 +1966 17 -4.4 -10.4 -6.05 0 111.89 194.54 31800 +1966 18 -0.4 -6.4 -2.05 0 146.88 194.73 31917 +1966 19 -2.31 -8.31 -3.96 0 129.14 197.33 32038 +1966 20 -2.59 -8.59 -4.24 0 126.7 198.89 32161 +1966 21 -1.21 -7.21 -2.86 0 139.11 200.17 32289 +1966 22 -0.52 -6.52 -2.17 0 145.7 201.46 32419 +1966 23 0.17 -5.83 -1.48 0.03 152.56 162.67 32552 +1966 24 -0.3 -6.3 -1.95 0.01 147.86 164.26 32688 +1966 25 -1.62 -7.62 -3.27 0 135.32 207.22 32827 +1966 26 -0.75 -6.75 -2.4 0.32 143.48 167.88 32969 +1966 27 0.48 -5.52 -1.17 0 155.73 210.71 33114 +1966 28 1.35 -4.65 -0.3 0.28 164.93 169.68 33261 +1966 29 0.41 -5.59 -1.24 0 155.01 214.78 33411 +1966 30 -0.16 -6.16 -1.81 0 149.25 217.15 33564 +1966 31 -0.56 -6.56 -2.21 0 145.31 219.55 33718 +1966 32 8.88 2.88 7.23 0 266.22 213.84 33875 +1966 33 9.25 3.25 7.6 0 272.34 214.79 34035 +1966 34 12.43 6.43 10.78 0.19 330.07 130.76 34196 +1966 35 11.96 5.96 10.31 0 320.93 176.97 34360 +1966 36 11.67 5.67 10.02 0.01 315.4 134.82 34526 +1966 37 11.87 5.87 10.22 0 319.2 181.89 34694 +1966 38 9.24 3.24 7.59 0.29 272.17 140.59 34863 +1966 39 9.72 3.72 8.07 0.03 280.28 142.14 35035 +1966 40 12.28 6.28 10.63 0.04 327.13 141.87 35208 +1966 41 13.64 7.64 11.99 0 354.63 189.94 35383 +1966 42 10.2 4.2 8.55 0.42 288.6 147.5 35560 +1966 43 7.75 1.75 6.1 1.26 248.26 151.4 35738 +1966 44 5.97 -0.03 4.32 0.7 222.09 154.53 35918 +1966 45 11.02 5.02 9.37 0 303.3 203.45 36099 +1966 46 14.07 8.07 12.42 0 363.73 202.02 36282 +1966 47 14.07 8.07 12.42 0 363.73 204.75 36466 +1966 48 11.86 5.86 10.21 0 319.01 210.53 36652 +1966 49 11.81 5.81 10.16 0 318.06 213.31 36838 +1966 50 7.88 1.88 6.23 0 250.27 220.52 37026 +1966 51 6.45 0.45 4.8 0 228.9 224.89 37215 +1966 52 5.87 -0.13 4.22 0 220.69 228.26 37405 +1966 53 4.17 -1.83 2.52 0.16 198.07 174.54 37596 +1966 54 4.81 -1.19 3.16 1.14 206.34 176.2 37788 +1966 55 6.33 0.33 4.68 0 227.18 236.52 37981 +1966 56 8.9 2.9 7.25 0 266.55 236.45 38175 +1966 57 10.39 4.39 8.74 0.57 291.95 178.1 38370 +1966 58 11.81 5.81 10.16 0.16 318.06 178.82 38565 +1966 59 10.78 4.78 9.13 0.43 298.93 181.88 38761 +1966 60 10.38 4.38 8.73 0 291.77 245.88 38958 +1966 61 10.94 4.94 9.29 0 301.83 248.02 39156 +1966 62 11.28 5.28 9.63 0 308.09 250.29 39355 +1966 63 11.56 5.56 9.91 0.38 313.32 189.63 39553 +1966 64 11.03 5.03 9.38 0.54 303.48 192.35 39753 +1966 65 10.42 4.42 8.77 0 292.48 260.17 39953 +1966 66 10.85 4.85 9.2 0 300.2 262.27 40154 +1966 67 10.41 4.41 8.76 0 292.3 265.75 40355 +1966 68 6.27 0.27 4.62 0.41 226.32 205.3 40556 +1966 69 6.67 0.67 5.02 0.01 232.08 206.94 40758 +1966 70 4.75 -1.25 3.1 0 205.55 280.82 40960 +1966 71 8.02 2.02 6.37 0 252.46 280.09 41163 +1966 72 3.25 -2.75 1.6 0 186.68 288.05 41366 +1966 73 6.84 0.84 5.19 0 234.57 287.01 41569 +1966 74 4.56 -1.44 2.91 0 203.07 292.26 41772 +1966 75 5.91 -0.09 4.26 0 221.25 293.57 41976 +1966 76 0.39 -5.61 -1.26 0 154.8 301.44 42179 +1966 77 1.05 -4.95 -0.6 0 161.71 303.57 42383 +1966 78 4 -2 2.35 0 195.92 303.58 42587 +1966 79 4.06 -1.94 2.41 0 196.67 306.28 42791 +1966 80 5.89 -0.11 4.24 0 220.97 306.86 42996 +1966 81 5.49 -0.51 3.84 0.66 215.45 232.44 43200 +1966 82 8.96 2.96 7.31 0.07 267.53 231.13 43404 +1966 83 13.59 7.59 11.94 0 353.59 302.99 43608 +1966 84 12.13 6.13 10.48 0 324.21 308.15 43812 +1966 85 11.86 5.86 10.21 0.01 319.01 233.32 44016 +1966 86 11.21 5.21 9.56 0.01 306.79 235.94 44220 +1966 87 11.33 5.33 9.68 0.02 309.02 237.68 44424 +1966 88 8.02 2.02 6.37 0.19 252.46 243.25 44627 +1966 89 8.6 2.6 6.95 0.46 261.67 244.35 44831 +1966 90 8.43 2.43 6.78 0 258.94 328.43 45034 +1966 91 9.93 3.93 8.28 0.61 283.89 246.31 45237 +1966 92 17.38 11.38 15.73 0 440.68 315.6 45439 +1966 93 14.69 8.69 13.04 0 377.2 324 45642 +1966 94 17.79 11.79 16.14 0.18 451.11 239.08 45843 +1966 95 14.54 8.54 12.89 0.14 373.9 246.4 46045 +1966 96 18.36 12.36 16.71 0 465.96 321.37 46246 +1966 97 17.71 11.71 16.06 1.73 449.06 243.8 46446 +1966 98 10.58 4.58 8.93 0.29 295.33 256.69 46647 +1966 99 12.09 6.09 10.44 0 323.43 341.54 46846 +1966 100 11.27 5.27 9.62 0 307.9 345 47045 +1966 101 13.98 7.98 12.33 0 361.81 341.59 47243 +1966 102 13.98 7.98 12.33 0.23 361.81 257.61 47441 +1966 103 18.7 12.7 17.05 1.75 475.02 250.18 47638 +1966 104 18.84 12.84 17.19 0.01 478.79 251.2 47834 +1966 105 16.02 10.02 14.37 0 407.53 344.18 48030 +1966 106 12.62 6.62 10.97 0.22 333.83 265.02 48225 +1966 107 12.05 6.05 10.4 0.63 322.66 267.12 48419 +1966 108 11.37 5.37 9.72 0.37 309.76 269.4 48612 +1966 109 13.79 7.79 12.14 0.12 357.78 266.94 48804 +1966 110 17.29 11.29 15.64 0.15 438.42 261.63 48995 +1966 111 14.59 8.59 12.94 0.64 375 267.81 49185 +1966 112 15.99 9.99 14.34 0.17 406.83 266.42 49374 +1966 113 7.93 1.93 6.28 0.24 251.05 279.44 49561 +1966 114 10.4 4.4 8.75 0 292.12 369.98 49748 +1966 115 17.73 11.73 16.08 0 449.57 354.8 49933 +1966 116 17.06 11.06 15.41 0 432.68 357.83 50117 +1966 117 14.92 8.92 13.27 0 382.3 364.56 50300 +1966 118 18.24 12.24 16.59 0 462.8 357.1 50481 +1966 119 15.81 9.81 14.16 0 402.61 364.86 50661 +1966 120 18.67 12.67 17.02 0 474.21 358.14 50840 +1966 121 16.17 10.17 14.52 0 411.08 366.22 51016 +1966 122 15.92 9.92 14.27 0.02 405.18 276.04 51191 +1966 123 12.48 6.48 10.83 0 331.05 377.06 51365 +1966 124 13.46 7.46 11.81 0 350.88 376.03 51536 +1966 125 15.72 9.72 14.07 0.52 400.51 278.73 51706 +1966 126 16.77 10.77 15.12 0.11 425.54 277.4 51874 +1966 127 16.55 10.55 14.9 0 420.19 371.34 52039 +1966 128 18.02 12.02 16.37 0.05 457.05 276.15 52203 +1966 129 19.2 13.2 17.55 0.14 488.61 274.09 52365 +1966 130 16.96 10.96 15.31 0.08 430.2 279.63 52524 +1966 131 19.7 13.7 18.05 0 502.53 365.4 52681 +1966 132 20.15 14.15 18.5 0 515.34 364.73 52836 +1966 133 19.89 13.89 18.24 0.04 507.9 274.71 52989 +1966 134 16.75 10.75 15.1 0.08 425.05 282.33 53138 +1966 135 16.31 10.31 14.66 0.01 414.42 283.75 53286 +1966 136 13.02 7.02 11.37 0.04 341.86 290.24 53430 +1966 137 15.53 9.53 13.88 0.07 396.12 286.29 53572 +1966 138 17.15 11.15 15.5 0 434.92 377.96 53711 +1966 139 18.68 12.68 17.03 0 474.48 374.11 53848 +1966 140 17.17 11.17 15.52 0.01 435.41 284.3 53981 +1966 141 15.26 9.26 13.61 0 389.95 384.64 54111 +1966 142 14.92 8.92 13.27 0 382.3 386 54238 +1966 143 16.73 10.73 15.08 0 424.56 381.78 54362 +1966 144 18.33 12.33 16.68 0.52 465.17 283.2 54483 +1966 145 21.61 15.61 19.96 0.04 558.84 275.3 54600 +1966 146 22.73 16.73 21.08 0 594.29 363.17 54714 +1966 147 17.58 11.58 15.93 3.49 445.74 285.87 54824 +1966 148 17 11 15.35 0.67 431.19 287.41 54931 +1966 149 17.8 11.8 16.15 0.17 451.37 285.9 55034 +1966 150 20.64 14.64 18.99 0.88 529.61 279.28 55134 +1966 151 23.25 17.25 21.6 1.55 611.39 272.2 55229 +1966 152 26.19 20.19 24.54 0 716.1 350.12 55321 +1966 153 25.56 19.56 23.91 0.57 692.47 264.97 55409 +1966 154 22.82 16.82 21.17 0.05 597.22 273.98 55492 +1966 155 25.33 19.33 23.68 0.81 684.01 266.12 55572 +1966 156 25.73 19.73 24.08 0.15 698.78 264.97 55648 +1966 157 21.91 15.91 20.26 0.15 568.16 277.11 55719 +1966 158 22.64 16.64 20.99 0.2 591.38 275.13 55786 +1966 159 19.09 13.09 17.44 0.26 485.59 284.78 55849 +1966 160 15.24 9.24 13.59 0.21 389.5 293.23 55908 +1966 161 18.9 12.9 17.25 0.38 480.41 285.43 55962 +1966 162 19 13 17.35 1.59 483.13 285.23 56011 +1966 163 16.95 10.95 15.3 0 429.96 386.71 56056 +1966 164 20.76 14.76 19.11 0.54 533.15 280.99 56097 +1966 165 25.76 19.76 24.11 0 699.9 354.35 56133 +1966 166 24.01 18.01 22.36 2.09 637.13 271.66 56165 +1966 167 24.27 18.27 22.62 0.01 646.14 270.79 56192 +1966 168 24.66 18.66 23.01 0 659.86 359.43 56214 +1966 169 18.07 12.07 16.42 0 458.35 383.68 56231 +1966 170 20.21 14.21 18.56 0.2 517.07 282.58 56244 +1966 171 15.39 9.39 13.74 0 392.91 391.26 56252 +1966 172 16.6 10.6 14.95 0.07 421.4 291 56256 +1966 173 14.3 8.3 12.65 0.46 368.68 295.48 56255 +1966 174 19.65 13.65 18 0.07 501.12 283.96 56249 +1966 175 21.73 15.73 20.08 0.4 562.55 278.44 56238 +1966 176 20.53 14.53 18.88 0 526.38 375.55 56223 +1966 177 21.4 15.4 19.75 0 552.4 372.33 56203 +1966 178 20.77 14.77 19.12 0 533.45 374.63 56179 +1966 179 22.43 16.43 20.78 0.05 584.62 276.28 56150 +1966 180 23 17 21.35 0.4 603.12 274.5 56116 +1966 181 26.88 20.88 25.23 0.64 742.76 261.46 56078 +1966 182 23.59 17.59 21.94 1.36 622.79 272.54 56035 +1966 183 23.94 17.94 22.29 2.74 634.72 271.32 55987 +1966 184 21.11 15.11 19.46 0.2 543.61 279.49 55935 +1966 185 24.12 18.12 22.47 0.44 640.93 270.57 55879 +1966 186 20.32 14.32 18.67 0.42 520.25 281.32 55818 +1966 187 20.14 14.14 18.49 0.04 515.05 281.64 55753 +1966 188 18.4 12.4 16.75 0.65 467.02 285.67 55684 +1966 189 21.91 15.91 20.26 0 568.16 368.74 55611 +1966 190 22.43 16.43 20.78 0.47 584.62 274.79 55533 +1966 191 23.42 17.42 21.77 0 617.07 362.19 55451 +1966 192 22.02 16.02 20.37 0 571.61 367.4 55366 +1966 193 18.36 12.36 16.71 0 465.96 379.6 55276 +1966 194 17.01 11.01 15.36 0 431.44 383.35 55182 +1966 195 15.58 9.58 13.93 1.39 397.27 290.21 55085 +1966 196 15.66 9.66 14.01 1.13 399.12 289.74 54984 +1966 197 18.87 12.87 17.22 0 479.6 376.64 54879 +1966 198 22.21 16.21 20.56 0.76 577.6 273.48 54770 +1966 199 25.6 19.6 23.95 0.11 693.95 262.6 54658 +1966 200 26.08 20.08 24.43 0.75 711.92 260.65 54542 +1966 201 24.47 18.47 22.82 2.6 653.15 265.73 54423 +1966 202 20.82 14.82 19.17 0.37 534.93 275.96 54301 +1966 203 17.81 11.81 16.16 0.15 451.62 282.84 54176 +1966 204 21.59 15.59 19.94 0 558.23 364.18 54047 +1966 205 21.11 15.11 19.46 0.24 543.61 274.05 53915 +1966 206 23.72 17.72 22.07 0.05 627.2 266.16 53780 +1966 207 24.76 18.76 23.11 0.17 663.42 262.39 53643 +1966 208 24.46 18.46 22.81 0 652.79 350.51 53502 +1966 209 24.58 18.58 22.93 0.64 657.03 262.03 53359 +1966 210 21.83 15.83 20.18 0.14 565.66 269.76 53213 +1966 211 19.7 13.7 18.05 0 502.53 366.26 53064 +1966 212 18.39 12.39 16.74 0.72 466.76 277.17 52913 +1966 213 22.16 16.16 20.51 0.18 576.02 267.11 52760 +1966 214 20.04 14.04 18.39 0 512.18 362.84 52604 +1966 215 12.98 6.98 11.33 0 341.05 381.23 52445 +1966 216 15.15 9.15 13.5 0.2 387.46 281.36 52285 +1966 217 18.12 12.12 16.47 0.16 459.66 274.67 52122 +1966 218 17.06 11.06 15.41 0.67 432.68 276.3 51958 +1966 219 15.46 9.46 13.81 0.45 394.52 278.66 51791 +1966 220 14.53 8.53 12.88 1.16 373.68 279.63 51622 +1966 221 15.77 9.77 14.12 0.09 401.68 276.57 51451 +1966 222 19.78 13.78 18.13 0 504.78 356.25 51279 +1966 223 17.69 11.69 16.04 0 448.55 361.39 51105 +1966 224 19.89 13.89 18.24 0.01 507.9 265.27 50929 +1966 225 21.04 15.04 19.39 0 541.5 348.75 50751 +1966 226 26.84 20.84 25.19 0.47 741.19 243.25 50572 +1966 227 22.46 16.46 20.81 0.57 585.58 256 50392 +1966 228 22.03 16.03 20.38 0.06 571.92 256.27 50210 +1966 229 22.01 16.01 20.36 0 571.29 340.55 50026 +1966 230 21.78 15.78 20.13 0.58 564.11 255.09 49842 +1966 231 20.58 14.58 18.93 0.7 527.84 257.04 49656 +1966 232 19.34 13.34 17.69 0 492.47 345.29 49469 +1966 233 22.43 16.43 20.78 0 584.62 333.64 49280 +1966 234 28.18 22.18 26.53 0 795.27 307.96 49091 +1966 235 26.56 20.56 24.91 0 730.29 314.19 48900 +1966 236 24.41 18.41 22.76 0.23 651.04 241.45 48709 +1966 237 22.77 16.77 21.12 0.08 595.59 244.93 48516 +1966 238 21.24 15.24 19.59 0 547.53 330.25 48323 +1966 239 22.94 16.94 21.29 3.7 601.15 242.15 48128 +1966 240 25.03 19.03 23.38 0 673.11 313.14 47933 +1966 241 20.05 14.05 18.4 0 512.47 329.11 47737 +1966 242 20.9 14.9 19.25 0.19 537.31 243.54 47541 +1966 243 24.74 18.74 23.09 0.2 662.71 231.93 47343 +1966 244 23.09 17.09 21.44 0 606.09 313.7 47145 +1966 245 24.23 18.23 22.58 0 644.75 307.71 46947 +1966 246 23.94 17.94 22.29 0 634.72 306.93 46747 +1966 247 21.2 15.2 19.55 0.03 546.32 235.94 46547 +1966 248 24.25 18.25 22.6 0 645.44 302.14 46347 +1966 249 21.55 15.55 19.9 0.01 557 232.17 46146 +1966 250 19.72 13.72 18.07 0 503.09 313.23 45945 +1966 251 18.68 12.68 17.03 0 474.48 314.05 45743 +1966 252 21.26 15.26 19.61 0 548.14 304.41 45541 +1966 253 17.38 11.38 15.73 0 440.68 313.15 45339 +1966 254 17.84 11.84 16.19 0 452.4 309.87 45136 +1966 255 16.25 10.25 14.6 0.01 412.98 233.59 44933 +1966 256 12.49 6.49 10.84 2.2 331.25 237.67 44730 +1966 257 11.88 5.88 10.23 0 319.39 315.76 44527 +1966 258 15.47 9.47 13.82 0 394.74 306.38 44323 +1966 259 14.11 8.11 12.46 1.17 364.59 230.05 44119 +1966 260 14.74 8.74 13.09 0.01 378.3 227.29 43915 +1966 261 16.48 10.48 14.83 0 418.5 296.86 43711 +1966 262 20.21 14.21 18.56 0.02 517.07 213.87 43507 +1966 263 19.45 13.45 17.8 0 495.53 284.81 43303 +1966 264 21.99 15.99 20.34 0 570.66 275.11 43099 +1966 265 19.15 13.15 17.5 0 487.23 280.75 42894 +1966 266 15.68 9.68 14.03 0.24 399.59 214.75 42690 +1966 267 14.67 8.67 13.02 0 376.76 285.69 42486 +1966 268 15.84 9.84 14.19 0 403.31 280.77 42282 +1966 269 16.21 10.21 14.56 0 412.03 277.49 42078 +1966 270 16.37 10.37 14.72 0.15 415.85 205.9 41875 +1966 271 20.01 14.01 18.36 0 511.32 263.43 41671 +1966 272 23.26 17.26 21.61 0 611.72 251.62 41468 +1966 273 18.86 12.86 17.21 0.44 479.33 195.88 41265 +1966 274 15.38 9.38 13.73 0.32 392.69 199.53 41062 +1966 275 15.28 9.28 13.63 0.14 390.41 197.61 40860 +1966 276 12.99 6.99 11.34 1.62 341.25 198.63 40658 +1966 277 12.41 6.41 10.76 0.04 329.68 197.33 40456 +1966 278 14.75 8.75 13.1 0.03 378.52 192.2 40255 +1966 279 11.01 5.01 9.36 2.08 303.11 194.61 40054 +1966 280 15.1 9.1 13.45 0.01 386.34 187.66 39854 +1966 281 16.54 10.54 14.89 0 419.95 244.8 39654 +1966 282 13.52 7.52 11.87 0 352.13 247.49 39455 +1966 283 14.26 8.26 12.61 0 367.81 243.45 39256 +1966 284 15.02 9.02 13.37 0 384.54 239.15 39058 +1966 285 13.08 7.08 11.43 0 343.08 239.72 38861 +1966 286 11.04 5.04 9.39 0 303.66 239.9 38664 +1966 287 13.53 7.53 11.88 0 352.34 233.34 38468 +1966 288 12.29 6.29 10.64 0 327.32 232.41 38273 +1966 289 14.13 8.13 12.48 0 365.02 227.01 38079 +1966 290 14.7 8.7 13.05 0.08 377.42 167.45 37885 +1966 291 22.87 16.87 21.22 0.24 598.86 152.77 37693 +1966 292 23.14 17.14 21.49 0 607.74 200.49 37501 +1966 293 21.78 15.78 20.13 0 564.11 201.33 37311 +1966 294 20.26 14.26 18.61 0.37 518.51 151.55 37121 +1966 295 19.28 13.28 17.63 0.03 490.81 151.06 36933 +1966 296 21.49 15.49 19.84 0 555.15 194.19 36745 +1966 297 20.23 14.23 18.58 0 517.65 194.38 36560 +1966 298 18.01 12.01 16.36 0 456.79 196.28 36375 +1966 299 16.9 10.9 15.25 0 428.73 195.56 36191 +1966 300 17.15 11.15 15.5 0.76 434.92 144.41 36009 +1966 301 18.27 12.27 16.62 0.08 463.59 141.11 35829 +1966 302 18.8 12.8 17.15 0.16 477.71 138.5 35650 +1966 303 15.52 9.52 13.87 0.22 395.89 140.78 35472 +1966 304 18.39 12.39 16.74 0 466.76 180.59 35296 +1966 305 6.09 0.09 4.44 0 223.77 193.35 35122 +1966 306 7.98 1.98 6.33 0.13 251.83 142.06 34950 +1966 307 8.27 2.27 6.62 0 256.39 186.62 34779 +1966 308 6.4 0.4 4.75 0 228.18 185.65 34610 +1966 309 9.98 3.98 8.33 0.03 284.76 135.01 34444 +1966 310 8.66 2.66 7.01 0 262.64 178.87 34279 +1966 311 10.58 4.58 8.93 0 295.33 174.8 34116 +1966 312 11.48 5.48 9.83 0.73 311.82 128.41 33956 +1966 313 8.77 2.77 7.12 0.63 264.42 128.88 33797 +1966 314 4.59 -1.41 2.94 0.86 203.46 129.93 33641 +1966 315 6.39 0.39 4.74 0.58 228.04 127.02 33488 +1966 316 12.55 6.55 10.9 0.67 332.44 121.03 33337 +1966 317 12.24 6.24 10.59 0 326.35 159.56 33188 +1966 318 10.54 4.54 8.89 0 294.62 159.03 33042 +1966 319 6.66 0.66 5.01 0.45 231.94 120.54 32899 +1966 320 6.23 0.23 4.58 0.83 225.75 119.37 32758 +1966 321 3.46 -2.54 1.81 1.06 189.23 119.18 32620 +1966 322 2.53 -3.47 0.88 1.59 178.16 118.21 32486 +1966 323 -0.65 -6.65 -2.3 0.45 144.44 160.33 32354 +1966 324 3.97 -2.03 2.32 0 195.54 194.86 32225 +1966 325 6.62 0.62 4.97 0.51 231.36 153.3 32100 +1966 326 6.55 0.55 4.9 0.15 230.34 111.11 31977 +1966 327 6.06 0.06 4.41 0.97 223.35 109.98 31858 +1966 328 7.12 1.12 5.47 0.41 238.71 107.94 31743 +1966 329 4.3 -1.7 2.65 0.47 199.72 108.23 31631 +1966 330 2.87 -3.13 1.22 0.1 182.14 107.76 31522 +1966 331 0.89 -5.11 -0.76 0 160.01 143.37 31417 +1966 332 2.81 -3.19 1.16 0.27 181.43 105.55 31316 +1966 333 0.21 -5.79 -1.44 0.03 152.96 105.69 31218 +1966 334 -0.1 -6.1 -1.75 0.06 149.84 147.55 31125 +1966 335 -1.52 -7.52 -3.17 0.07 136.24 147.44 31035 +1966 336 2.61 -3.39 0.96 0 179.09 179.09 30949 +1966 337 4.71 -1.29 3.06 0 205.02 133.54 30867 +1966 338 0.7 -5.3 -0.95 0 158.01 134.68 30790 +1966 339 2.69 -3.31 1.04 0 180.03 132.92 30716 +1966 340 4.87 -1.13 3.22 0 207.13 130.98 30647 +1966 341 8.15 2.15 6.5 0 254.5 127.91 30582 +1966 342 8.91 2.91 7.26 0 266.71 126.59 30521 +1966 343 4.08 -1.92 2.43 0 196.93 128.93 30465 +1966 344 7.02 1.02 5.37 0 237.22 126 30413 +1966 345 1.76 -4.24 0.11 0 169.43 128.55 30366 +1966 346 5.53 -0.47 3.88 0.04 215.99 94.48 30323 +1966 347 2.79 -3.21 1.14 0.41 181.2 95.17 30284 +1966 348 4.63 -1.37 2.98 0 203.98 125.56 30251 +1966 349 8.98 2.98 7.33 1.07 267.86 91.76 30221 +1966 350 5.78 -0.22 4.13 0 219.44 124.17 30197 +1966 351 4.51 -1.49 2.86 0.04 202.42 93.52 30177 +1966 352 4.15 -1.85 2.5 0.06 197.81 93.6 30162 +1966 353 2.68 -3.32 1.03 0.06 179.91 94.13 30151 +1966 354 2.64 -3.36 0.99 0.58 179.44 94.12 30145 +1966 355 2.25 -3.75 0.6 0 174.94 125.68 30144 +1966 356 1.18 -4.82 -0.47 0.22 163.1 94.65 30147 +1966 357 -1.85 -7.85 -3.5 0 133.23 127.5 30156 +1966 358 -0.45 -6.45 -2.1 0.75 146.39 141.43 30169 +1966 359 0.99 -5.01 -0.66 0.61 161.07 140.9 30186 +1966 360 3.23 -2.77 1.58 0.15 186.44 139.91 30208 +1966 361 3.51 -2.49 1.86 0.04 189.84 139.54 30235 +1966 362 7.21 1.21 5.56 0 240.06 168.27 30267 +1966 363 8.86 2.86 7.21 0 265.89 123.68 30303 +1966 364 5.48 -0.52 3.83 0 215.31 126.34 30343 +1966 365 5.75 -0.25 4.1 0 219.02 126.74 30388 +1967 1 4.38 -1.62 2.73 0 200.75 128.44 30438 +1967 2 1.07 -4.93 -0.58 0 161.92 130.86 30492 +1967 3 2.92 -3.08 1.27 0 182.73 130.91 30551 +1967 4 1.76 -4.24 0.11 0 169.43 132.4 30614 +1967 5 4.04 -1.96 2.39 0.04 196.42 98.9 30681 +1967 6 1.09 -4.91 -0.56 0 162.13 134.27 30752 +1967 7 0.68 -5.32 -0.97 0.14 157.8 101.44 30828 +1967 8 -2.77 -8.77 -4.42 0 125.16 138.16 30907 +1967 9 -0.72 -6.72 -2.37 0.01 143.77 146.6 30991 +1967 10 1.66 -4.34 0.01 0.64 168.32 104.14 31079 +1967 11 1.98 -4.02 0.33 0.53 171.89 104.77 31171 +1967 12 1.34 -4.66 -0.31 0.06 164.82 105.77 31266 +1967 13 0.34 -5.66 -1.31 0.1 154.29 107.35 31366 +1967 14 1.08 -4.92 -0.57 0.15 162.03 108.2 31469 +1967 15 3.25 -2.75 1.6 0.04 186.68 108.43 31575 +1967 16 2.29 -3.71 0.64 0 175.4 146.4 31686 +1967 17 3.73 -2.27 2.08 0 192.55 147.27 31800 +1967 18 -5.26 -11.26 -6.91 0 105.4 153.19 31917 +1967 19 -0.35 -6.35 -2 0 147.37 153.25 32038 +1967 20 -0.56 -6.56 -2.21 0 145.31 154.95 32161 +1967 21 0.76 -5.24 -0.89 0.5 158.64 117.26 32289 +1967 22 -0.42 -6.42 -2.07 0 146.68 158.68 32419 +1967 23 -1.52 -7.52 -3.17 0 136.24 160.97 32552 +1967 24 1.93 -4.07 0.28 0 171.33 161.35 32688 +1967 25 1.81 -4.19 0.16 0 169.99 163.31 32827 +1967 26 3.66 -2.34 2.01 0 191.68 164.14 32969 +1967 27 3.31 -2.69 1.66 0 187.4 166.39 33114 +1967 28 3.28 -2.72 1.63 0.09 187.04 126.47 33261 +1967 29 -0.58 -6.58 -2.23 0 145.12 173.16 33411 +1967 30 2.88 -3.12 1.23 0.14 182.26 130.13 33564 +1967 31 3.08 -2.92 1.43 0.33 184.64 131.82 33718 +1967 32 4.03 -1.97 2.38 0 196.29 177.25 33875 +1967 33 0.9 -5.1 -0.75 0.01 160.12 136.37 34035 +1967 34 4.73 -1.27 3.08 0 205.29 181.59 34196 +1967 35 3.74 -2.26 2.09 0 192.67 184.44 34360 +1967 36 6.83 0.83 5.18 0 234.42 184.57 34526 +1967 37 8.65 2.65 7 0.91 262.48 138.99 34694 +1967 38 7.7 1.7 6.05 0.01 247.49 141.7 34863 +1967 39 6.57 0.57 4.92 0 230.63 192.52 35035 +1967 40 7.99 1.99 6.34 0.04 251.99 145.37 35208 +1967 41 3.32 -2.68 1.67 0 187.52 200.29 35383 +1967 42 6.97 0.97 5.32 0.55 236.48 149.93 35560 +1967 43 6.66 0.66 5.01 0.35 231.94 152.16 35738 +1967 44 6.27 0.27 4.62 0.17 226.32 154.33 35918 +1967 45 5.32 -0.68 3.67 0.23 213.14 156.91 36099 +1967 46 3.5 -2.5 1.85 0 189.71 213.35 36282 +1967 47 1.37 -4.63 -0.28 0 165.15 217.69 36466 +1967 48 -0.38 -6.38 -2.03 0 147.07 221.61 36652 +1967 49 -1.46 -7.46 -3.11 0.1 136.79 204.88 36838 +1967 50 2.21 -3.79 0.56 0 174.49 261.1 37026 +1967 51 3.49 -2.51 1.84 0 189.59 227.46 37215 +1967 52 2.58 -3.42 0.93 0 178.74 231 37405 +1967 53 4.73 -1.27 3.08 0 205.29 232.24 37596 +1967 54 9.22 3.22 7.57 0.07 271.84 172.84 37788 +1967 55 7.74 1.74 6.09 0.16 248.11 176.3 37981 +1967 56 10.42 4.42 8.77 0 292.48 234.59 38175 +1967 57 8.51 2.51 6.86 0 260.22 239.76 38370 +1967 58 10.58 4.58 8.93 0 295.33 240.11 38565 +1967 59 8.6 2.6 6.95 0.11 261.67 183.93 38761 +1967 60 9.43 3.43 7.78 0.38 275.36 185.33 38958 +1967 61 10.72 4.72 9.07 0 297.85 248.32 39156 +1967 62 9.82 3.82 8.17 0 282 252.27 39355 +1967 63 10.63 4.63 8.98 0.26 296.23 190.62 39553 +1967 64 5.44 -0.56 3.79 0.01 214.77 197.37 39753 +1967 65 3.51 -2.49 1.86 1.21 189.84 200.92 39953 +1967 66 6.67 0.67 5.02 0 232.08 267.52 40154 +1967 67 6.88 0.88 5.23 0 235.16 270.19 40355 +1967 68 10.77 4.77 9.12 0.04 298.75 201.06 40556 +1967 69 10.49 4.49 8.84 0 293.72 271.07 40758 +1967 70 6.46 0.46 4.81 0 229.04 279.01 40960 +1967 71 5.37 -0.63 3.72 0.97 213.82 212.34 41163 +1967 72 5.84 -0.16 4.19 0.07 220.27 214.09 41366 +1967 73 2.12 -3.88 0.47 0 173.47 291.77 41569 +1967 74 5.95 -0.05 4.3 0 221.81 290.78 41772 +1967 75 7.12 1.12 5.47 0 238.71 292.16 41976 +1967 76 9.71 3.71 8.06 0 280.11 291.39 42179 +1967 77 12.61 6.61 10.96 0.04 333.63 217.05 42383 +1967 78 10.95 4.95 9.3 0.95 302.02 221.07 42587 +1967 79 9.3 3.3 7.65 0 273.17 299.93 42791 +1967 80 14.26 8.26 12.61 0 367.81 294.14 42996 +1967 81 12.86 6.86 11.21 0 338.63 299.29 43200 +1967 82 12.6 6.6 10.95 0 333.43 302.36 43404 +1967 83 11.11 5.11 9.46 0 304.95 307.37 43608 +1967 84 12.96 6.96 11.31 0.11 340.64 230 43812 +1967 85 17.43 11.43 15.78 0.32 441.94 224.73 44016 +1967 86 16.3 10.3 14.65 0 414.18 304.61 44220 +1967 87 14.04 8.04 12.39 0 363.09 311.9 44424 +1967 88 14.39 8.39 12.74 0 370.63 313.49 44627 +1967 89 8.94 2.94 7.29 0.01 267.2 243.98 44831 +1967 90 9.43 3.43 7.78 0.01 275.36 245.21 45034 +1967 91 12.31 6.31 10.66 0 327.71 324.34 45237 +1967 92 14.73 8.73 13.08 0 378.08 321.74 45439 +1967 93 11.93 5.93 10.28 0 320.35 329.46 45642 +1967 94 12.41 6.41 10.76 0 329.68 330.71 45843 +1967 95 10.5 4.5 8.85 0 293.9 336.24 46045 +1967 96 10.18 4.18 8.53 0 288.25 338.89 46246 +1967 97 9.41 3.41 7.76 0 275.02 342.2 46446 +1967 98 10.32 4.32 8.67 0.05 290.71 257.02 46647 +1967 99 12.75 6.75 11.1 0.52 336.42 255.2 46846 +1967 100 11.49 5.49 9.84 0.07 312.01 258.45 47045 +1967 101 11.75 5.75 10.1 0.24 316.91 259.54 47243 +1967 102 9.61 3.61 7.96 0 278.4 351.71 47441 +1967 103 13.4 7.4 11.75 0 349.64 346.53 47638 +1967 104 12.98 6.98 11.33 0 341.05 349.21 47834 +1967 105 9.22 3.22 7.57 0 271.84 357.85 48030 +1967 106 11.59 5.59 9.94 0.01 313.89 266.52 48225 +1967 107 13.78 7.78 12.13 0.53 357.57 264.46 48419 +1967 108 13.44 7.44 11.79 0.41 350.47 266.31 48612 +1967 109 10.55 4.55 8.9 0 294.79 362.33 48804 +1967 110 15.67 9.67 14.02 0.02 399.35 264.74 48995 +1967 111 11.6 5.6 9.95 0.45 314.07 272.52 49185 +1967 112 6.73 0.73 5.08 0 232.96 372.98 49374 +1967 113 9.67 3.67 8.02 0.28 279.43 277.32 49561 +1967 114 11.8 5.8 10.15 0 317.87 367.36 49748 +1967 115 14.34 8.34 12.69 0 369.54 363.4 49933 +1967 116 16.28 10.28 14.63 0.02 413.7 269.92 50117 +1967 117 16.72 10.72 15.07 0 424.32 360.03 50300 +1967 118 16.52 10.52 14.87 0 419.46 361.85 50481 +1967 119 16.89 10.89 15.24 0.44 428.48 271.53 50661 +1967 120 18.33 12.33 16.68 1.16 465.17 269.36 50840 +1967 121 19.66 13.66 18.01 1.91 501.4 267.13 51016 +1967 122 18.62 12.62 16.97 1.52 472.87 270.42 51191 +1967 123 15.73 9.73 14.08 0.04 400.75 277.17 51365 +1967 124 15.19 9.19 13.54 0.01 388.37 278.99 51536 +1967 125 16.34 10.34 14.69 0.49 415.13 277.52 51706 +1967 126 17.35 11.35 15.7 0.43 439.92 276.19 51874 +1967 127 18.6 12.6 16.95 1.27 472.34 274.12 52039 +1967 128 14.85 8.85 13.2 0.64 380.74 282.51 52203 +1967 129 17.43 11.43 15.78 0.67 441.94 278.05 52365 +1967 130 18.16 12.16 16.51 0.09 460.7 277.05 52524 +1967 131 18.79 12.79 17.14 0 477.44 368.28 52681 +1967 132 12.72 6.72 11.07 0.04 335.82 288.64 52836 +1967 133 15.57 9.57 13.92 0 397.04 378.86 52989 +1967 134 13.95 7.95 12.3 0 361.17 383.53 53138 +1967 135 16.66 10.66 15.01 0 422.85 377.38 53286 +1967 136 16.85 10.85 15.2 0 427.5 377.49 53430 +1967 137 18.74 12.74 17.09 0 476.09 372.65 53572 +1967 138 20.11 14.11 18.46 0 514.19 368.82 53711 +1967 139 21.76 15.76 20.11 0 563.48 363.69 53848 +1967 140 20.6 14.6 18.95 0.14 528.43 276.23 53981 +1967 141 19.22 13.22 17.57 0.01 489.16 279.99 54111 +1967 142 15.11 9.11 13.46 0.87 386.56 289.14 54238 +1967 143 17.3 11.3 15.65 1.35 438.67 285.13 54362 +1967 144 16.25 10.25 14.6 0.07 412.98 287.68 54483 +1967 145 17.53 11.53 15.88 0.09 444.47 285.34 54600 +1967 146 19.86 13.86 18.21 0.02 507.05 280.17 54714 +1967 147 22.05 16.05 20.4 0.04 572.55 274.69 54824 +1967 148 21.36 15.36 19.71 0.24 551.18 276.88 54931 +1967 149 21.79 15.79 20.14 0.22 564.42 275.93 55034 +1967 150 19.13 13.13 17.48 0.26 486.69 283.07 55134 +1967 151 16.3 10.3 14.65 0.91 414.18 289.65 55229 +1967 152 19.86 13.86 18.21 0.95 507.05 281.65 55321 +1967 153 12.02 6.02 10.37 0.05 322.08 297.64 55409 +1967 154 16.25 10.25 14.6 0 412.98 387.01 55492 +1967 155 14.81 8.81 13.16 0 379.85 390.96 55572 +1967 156 14.47 8.47 12.82 0 372.37 392.12 55648 +1967 157 17.47 11.47 15.82 0 442.95 384.26 55719 +1967 158 16.71 10.71 15.06 0 424.07 386.61 55786 +1967 159 17.01 11.01 15.36 0 431.44 386 55849 +1967 160 16.68 10.68 15.03 0 423.34 387.12 55908 +1967 161 16.08 10.08 14.43 0 408.95 388.84 55962 +1967 162 18.36 12.36 16.71 0 465.96 382.32 56011 +1967 163 20.55 14.55 18.9 0.1 526.96 281.51 56056 +1967 164 19.87 13.87 18.22 0 507.33 377.72 56097 +1967 165 21.67 15.67 20.02 0 560.7 371.44 56133 +1967 166 20.54 14.54 18.89 0 526.67 375.59 56165 +1967 167 22.12 16.12 20.47 0 574.76 369.77 56192 +1967 168 22.42 16.42 20.77 0.4 584.3 276.52 56214 +1967 169 21.25 15.25 19.6 0.76 547.84 279.82 56231 +1967 170 21.13 15.13 19.48 0.65 544.21 280.15 56244 +1967 171 20.52 14.52 18.87 0.47 526.08 281.82 56252 +1967 172 20.87 14.87 19.22 0.08 536.42 280.89 56256 +1967 173 21.03 15.03 19.38 0 541.2 373.93 56255 +1967 174 24.25 18.25 22.6 0 645.44 361.17 56249 +1967 175 22.97 16.97 21.32 0 602.13 366.45 56238 +1967 176 21.69 15.69 20.04 0 561.31 371.36 56223 +1967 177 23.32 17.32 21.67 0 613.72 364.9 56203 +1967 178 24.99 18.99 23.34 0 671.66 357.79 56179 +1967 179 26.98 20.98 25.33 0 746.69 348.29 56150 +1967 180 26.51 20.51 24.86 0.13 728.36 262.87 56116 +1967 181 26.54 20.54 24.89 0 729.52 350.28 56078 +1967 182 27.02 21.02 25.37 0 748.27 347.78 56035 +1967 183 28.2 22.2 26.55 0.3 796.1 256.15 55987 +1967 184 26.03 20.03 24.38 1.04 710.03 264.2 55935 +1967 185 24.67 18.67 23.02 2.07 660.22 268.79 55879 +1967 186 23.18 17.18 21.53 0 609.06 364.41 55818 +1967 187 25.54 19.54 23.89 0 691.73 354.05 55753 +1967 188 22.99 16.99 21.34 0 602.79 364.73 55684 +1967 189 23.28 17.28 21.63 0 612.39 363.39 55611 +1967 190 21.88 15.88 20.23 0.18 567.22 276.36 55533 +1967 191 21.16 15.16 19.51 0 545.11 370.87 55451 +1967 192 21.84 15.84 20.19 0 565.97 368.07 55366 +1967 193 23.82 17.82 22.17 0 630.61 359.98 55276 +1967 194 25.16 19.16 23.51 0.01 677.81 265.48 55182 +1967 195 24.51 18.51 22.86 0 654.55 356.57 55085 +1967 196 27.5 21.5 25.85 0 767.42 342.14 54984 +1967 197 32.19 26.19 30.54 0 977.4 314.67 54879 +1967 198 30.77 24.77 29.12 0 909.26 323.18 54770 +1967 199 30.34 24.34 28.69 0.69 889.44 244.07 54658 +1967 200 23.54 17.54 21.89 0.43 621.1 269 54542 +1967 201 19.16 13.16 17.51 0.52 487.51 280.54 54423 +1967 202 20.47 14.47 18.82 0.66 524.62 276.87 54301 +1967 203 26.32 20.32 24.67 0 721.06 344.93 54176 +1967 204 23.89 17.89 22.24 0 633 355.23 54047 +1967 205 25.19 19.19 23.54 0 678.9 349.14 53915 +1967 206 24.55 18.55 22.9 0.12 655.97 263.55 53780 +1967 207 22.67 16.67 21.02 0.18 592.35 268.81 53643 +1967 208 19.49 13.49 17.84 0.01 496.64 276.75 53502 +1967 209 20.32 14.32 18.67 0 520.25 365.61 53359 +1967 210 19.73 13.73 18.08 0 503.37 366.94 53213 +1967 211 21.18 15.18 19.53 0 545.72 361.25 53064 +1967 212 21.01 15.01 19.36 0 540.6 361.06 52913 +1967 213 17.15 11.15 15.5 0 434.92 372.39 52760 +1967 214 21.46 15.46 19.81 0 554.23 357.97 52604 +1967 215 22.01 16.01 20.36 0 571.29 355.3 52445 +1967 216 26.25 20.25 24.6 0 718.38 336.75 52285 +1967 217 25.16 19.16 23.51 0.04 677.81 255.6 52122 +1967 218 22.11 16.11 20.46 0 574.44 352.25 51958 +1967 219 21.1 15.1 19.45 0.88 543.31 266.12 51791 +1967 220 20.54 14.54 18.89 0.49 526.67 266.85 51622 +1967 221 19.63 13.63 17.98 0 500.56 357.77 51451 +1967 222 19.29 13.29 17.64 0.24 491.09 268.34 51279 +1967 223 17.53 11.53 15.88 0.12 444.47 271.38 51105 +1967 224 15.15 9.15 13.5 0.04 387.46 275.23 50929 +1967 225 16.84 10.84 15.19 0 427.25 361.49 50751 +1967 226 20.31 14.31 18.66 0.22 519.96 262.54 50572 +1967 227 24.45 18.45 22.8 0 652.44 333.6 50392 +1967 228 21.96 15.96 20.31 0.31 569.72 256.46 50210 +1967 229 22.3 16.3 20.65 0 580.46 339.51 50026 +1967 230 21.82 15.82 20.17 0 565.35 339.97 49842 +1967 231 22.75 16.75 21.1 0.3 594.94 251.39 49656 +1967 232 23.86 17.86 22.21 0 631.98 329.65 49469 +1967 233 20.97 14.97 19.32 0 539.4 338.69 49280 +1967 234 21.11 15.11 19.46 0 543.61 336.83 49091 +1967 235 23.33 17.33 21.68 0 614.06 327.49 48900 +1967 236 23.46 17.46 21.81 0 618.41 325.62 48709 +1967 237 26.26 20.26 24.61 0 718.77 312.63 48516 +1967 238 27.57 21.57 25.92 0 770.25 305.11 48323 +1967 239 25.65 19.65 24 0 695.8 312.25 48128 +1967 240 30.46 24.46 28.81 0 894.93 287.54 47933 +1967 241 25.18 19.18 23.53 0.29 678.54 233.17 47737 +1967 242 26.21 20.21 24.56 0.97 716.86 228.71 47541 +1967 243 22.79 16.79 21.14 0.52 596.25 237.4 47343 +1967 244 15.27 9.27 13.62 0.62 390.18 252.28 47145 +1967 245 11.75 5.75 10.1 2.7 316.91 256.3 46947 +1967 246 10.23 4.23 8.58 1.81 289.12 256.78 46747 +1967 247 11.28 5.28 9.63 0 308.09 338.64 46547 +1967 248 15.88 9.88 14.23 0 404.24 327.24 46347 +1967 249 16.89 10.89 15.24 0 428.48 322.74 46146 +1967 250 15.68 9.68 14.03 0.04 399.59 242.73 45945 +1967 251 17.73 11.73 16.08 0.27 449.57 237.41 45743 +1967 252 15.52 9.52 13.87 0.02 395.89 239.76 45541 +1967 253 18.04 12.04 16.39 1.47 457.57 233.61 45339 +1967 254 22.26 16.26 20.61 0 579.19 297.09 45136 +1967 255 21.02 15.02 19.37 0 540.9 298.8 44933 +1967 256 21.13 15.13 19.48 0 544.21 296.26 44730 +1967 257 23.05 17.05 21.4 0 604.77 288.05 44527 +1967 258 22.87 16.87 21.22 0 598.86 286.4 44323 +1967 259 21.28 15.28 19.63 0 548.75 289.07 44119 +1967 260 22.13 16.13 20.48 0.29 575.07 213.12 43915 +1967 261 22.9 16.9 21.25 0 599.84 279.35 43711 +1967 262 21.53 15.53 19.88 0 556.38 281.35 43507 +1967 263 22.23 16.23 20.58 1.18 578.24 207.63 43303 +1967 264 19.32 13.32 17.67 0 491.92 282.63 43099 +1967 265 19.36 13.36 17.71 0 493.03 280.21 42894 +1967 266 18.09 12.09 16.44 0.03 458.88 210.71 42690 +1967 267 19.05 13.05 17.4 0 484.5 275.95 42486 +1967 268 19.1 13.1 17.45 0.03 485.86 204.99 42282 +1967 269 22.97 16.97 21.32 0.64 602.13 195.06 42078 +1967 270 23.8 17.8 22.15 0.49 629.93 191.22 41875 +1967 271 25.45 19.45 23.8 0 688.41 246.97 41671 +1967 272 21.23 15.23 19.58 0 547.23 257.54 41468 +1967 273 20.29 14.29 18.64 0.16 519.38 193.21 41265 +1967 274 17.59 11.59 15.94 0 446 261.47 41062 +1967 275 13.34 7.34 11.69 0 348.4 266.97 40860 +1967 276 15.3 9.3 13.65 0 390.86 260.75 40658 +1967 277 13.85 7.85 12.2 0 359.05 260.72 40456 +1967 278 16.02 10.02 14.37 0 407.53 253.89 40255 +1967 279 14.46 8.46 12.81 0.16 372.15 190.49 40054 +1967 280 16.4 10.4 14.75 0.11 416.57 185.82 39854 +1967 281 16.98 10.98 15.33 0 430.7 243.93 39654 +1967 282 16.16 10.16 14.51 0 410.84 242.84 39455 +1967 283 12.63 6.63 10.98 0 334.03 246.07 39256 +1967 284 15.14 9.14 13.49 0 387.24 238.94 39058 +1967 285 13.33 7.33 11.68 0 348.2 239.33 38861 +1967 286 13.89 7.89 12.24 0.03 359.9 176.77 38664 +1967 287 12.99 6.99 11.34 0 341.25 234.16 38468 +1967 288 12.64 6.64 10.99 0.06 334.22 173.93 38273 +1967 289 9.27 3.27 7.62 0.02 272.67 175.28 38079 +1967 290 12.63 6.63 10.98 0.22 334.03 169.83 37885 +1967 291 13.57 7.57 11.92 0.58 353.17 166.77 37693 +1967 292 12.78 6.78 11.13 0 337.02 220.85 37501 +1967 293 15.56 9.56 13.91 0 396.81 213.85 37311 +1967 294 13.37 7.37 11.72 0 349.02 214.42 37121 +1967 295 16.33 10.33 14.68 0.22 414.89 155.21 36933 +1967 296 21.28 15.28 19.63 0.72 548.75 146 36745 +1967 297 18.63 12.63 16.98 0.06 473.14 148.21 36560 +1967 298 16.83 10.83 15.18 0.43 427.01 148.79 36375 +1967 299 19.06 13.06 17.41 0.88 484.77 143.71 36191 +1967 300 13 7 11.35 0 341.45 198.88 36009 +1967 301 12.33 6.33 10.68 0.16 328.11 147.95 35829 +1967 302 12.49 6.49 10.84 0 331.25 194.47 35650 +1967 303 13.88 7.88 12.23 0 359.69 190.08 35472 +1967 304 15.09 9.09 13.44 0 386.11 185.94 35296 +1967 305 7.28 1.28 5.63 0 241.11 192.32 35122 +1967 306 5.77 -0.23 4.12 0 219.3 191.33 34950 +1967 307 6.22 0.22 4.57 0 225.61 188.43 34779 +1967 308 7.84 1.84 6.19 0.12 249.65 138.3 34610 +1967 309 11.78 5.78 10.13 1.75 317.49 133.54 34444 +1967 310 13.11 7.11 11.46 0 343.69 174.06 34279 +1967 311 13.95 7.95 12.3 0 361.17 170.87 34116 +1967 312 10.51 4.51 8.86 1.09 294.08 129.19 33956 +1967 313 4.01 -1.99 2.36 0 196.04 175.62 33797 +1967 314 1.23 -4.77 -0.42 0 163.64 175.35 33641 +1967 315 2.22 -3.78 0.57 0 174.6 172.2 33488 +1967 316 5.39 -0.61 3.74 0.19 214.09 125.94 33337 +1967 317 9.28 3.28 7.63 0 272.84 162.54 33188 +1967 318 8.15 2.15 6.5 0.01 254.5 120.91 33042 +1967 319 11.88 5.88 10.23 0.02 319.39 116.99 32899 +1967 320 11.77 5.77 10.12 0 317.3 154.27 32758 +1967 321 5.44 -0.56 3.79 0.05 214.77 118.21 32620 +1967 322 7.4 1.4 5.75 0 242.92 154.35 32486 +1967 323 7.92 1.92 6.27 0.03 250.9 114.24 32354 +1967 324 5.9 -0.1 4.25 0 221.11 151.79 32225 +1967 325 11.35 5.35 9.7 0.3 309.39 109.16 32100 +1967 326 10.73 4.73 9.08 0.04 298.03 108.53 31977 +1967 327 13.38 7.38 11.73 0.03 349.23 105.17 31858 +1967 328 7.97 1.97 6.32 0 251.67 143.28 31743 +1967 329 6.18 0.18 4.53 0 225.05 143.1 31631 +1967 330 6.65 0.65 5 0 231.79 141.33 31522 +1967 331 9.37 3.37 7.72 0 274.35 137.94 31417 +1967 332 3.54 -2.46 1.89 0 190.2 140.33 31316 +1967 333 1.02 -4.98 -0.63 0 161.39 140.54 31218 +1967 334 4.39 -1.61 2.74 0 200.88 137.64 31125 +1967 335 5.26 -0.74 3.61 0 212.33 135.94 31035 +1967 336 2.22 -3.78 0.57 0 174.6 136.57 30949 +1967 337 1.23 -4.77 -0.42 0 163.64 135.39 30867 +1967 338 2.3 -3.7 0.65 0.1 175.51 100.44 30790 +1967 339 1.37 -4.63 -0.28 0 165.15 133.57 30716 +1967 340 -1.05 -7.05 -2.7 0 140.62 133.88 30647 +1967 341 -0.41 -6.41 -2.06 0 146.78 132.69 30582 +1967 342 -0.63 -6.63 -2.28 0.35 144.63 143.36 30521 +1967 343 -1.06 -7.06 -2.71 0.43 140.52 144.3 30465 +1967 344 2.44 -3.56 0.79 0 177.12 174.2 30413 +1967 345 1.12 -4.88 -0.53 0 162.45 174.31 30366 +1967 346 3.26 -2.74 1.61 0 186.8 172.35 30323 +1967 347 1.76 -4.24 0.11 0 169.43 172.32 30284 +1967 348 6.18 0.18 4.53 0 225.05 168.78 30251 +1967 349 8.05 2.05 6.4 0 252.93 123.02 30221 +1967 350 5.85 -0.15 4.2 0 220.41 124.13 30197 +1967 351 5.47 -0.53 3.82 0.41 215.17 93.11 30177 +1967 352 2.75 -3.25 1.1 0.01 180.73 94.15 30162 +1967 353 -2.33 -8.33 -3.98 0.15 128.97 139.97 30151 +1967 354 -1.7 -7.7 -3.35 0 134.59 171.62 30145 +1967 355 1.25 -4.75 -0.4 0 163.85 170.25 30144 +1967 356 4.42 -1.58 2.77 0 201.26 124.58 30147 +1967 357 2.59 -3.41 0.94 0 178.86 125.6 30156 +1967 358 2.59 -3.41 0.94 0 178.86 125.69 30169 +1967 359 5.63 -0.37 3.98 0 217.37 124.15 30186 +1967 360 5.69 -0.31 4.04 1.12 218.19 93.35 30208 +1967 361 6.51 0.51 4.86 0 229.76 124.29 30235 +1967 362 4.05 -1.95 2.4 0 196.55 126.19 30267 +1967 363 2.07 -3.93 0.42 0.14 172.9 95.84 30303 +1967 364 2.7 -3.3 1.05 0.62 180.14 95.91 30343 +1967 365 1.28 -4.72 -0.37 0.42 164.17 96.85 30388 +1968 1 -4.24 -10.24 -5.89 0 113.14 132.15 30438 +1968 2 -0.18 -6.18 -1.83 0.06 149.05 142.03 30492 +1968 3 -3.25 -9.25 -4.9 0 121.12 176.92 30551 +1968 4 2.03 -3.97 0.38 0 172.45 132.27 30614 +1968 5 1.02 -4.98 -0.63 0 161.39 133.4 30681 +1968 6 -1.72 -7.72 -3.37 0.33 134.41 145.55 30752 +1968 7 -3.53 -9.53 -5.18 0.26 118.81 147.34 30828 +1968 8 -5.88 -11.88 -7.53 0.06 100.92 149.1 30907 +1968 9 -4.08 -10.08 -5.73 0.34 114.39 150.57 30991 +1968 10 -4.45 -10.45 -6.1 0.12 111.5 151.89 31079 +1968 11 -3.11 -9.11 -4.76 0 122.28 187.64 31171 +1968 12 -2.15 -8.15 -3.8 0 130.55 188.17 31266 +1968 13 -0.39 -6.39 -2.04 0 146.97 188.94 31366 +1968 14 6.27 0.27 4.62 0.01 226.32 150.47 31469 +1968 15 3 -3 1.35 0 183.68 188.71 31575 +1968 16 3.79 -2.21 2.14 0.08 193.29 152.53 31686 +1968 17 0.65 -5.35 -1 0 157.49 192.05 31800 +1968 18 0.48 -5.52 -1.17 0 155.73 193.82 31917 +1968 19 2.79 -3.21 1.14 0 181.2 194.04 32038 +1968 20 4.69 -1.31 3.04 0.36 204.76 155.71 32161 +1968 21 0.64 -5.36 -1.01 0.89 157.39 158.7 32289 +1968 22 -2.98 -8.98 -4.63 0.05 123.38 161.21 32419 +1968 23 0.03 -5.97 -1.62 0 151.15 201.46 32552 +1968 24 2.73 -3.27 1.08 0 180.49 201.59 32688 +1968 25 4.84 -1.16 3.19 0 206.73 161.45 32827 +1968 26 5.04 -0.96 3.39 0 209.38 163.23 32969 +1968 27 8.46 2.46 6.81 0 259.42 162.57 33114 +1968 28 9.44 3.44 7.79 0 275.52 163.86 33261 +1968 29 6.01 0.01 4.36 0 222.65 169.11 33411 +1968 30 3.89 -2.11 2.24 0 194.54 172.86 33564 +1968 31 5.94 -0.06 4.29 0 221.67 173.76 33718 +1968 32 7.97 1.97 6.32 0 251.67 174.18 33875 +1968 33 9.32 3.32 7.67 0 273.51 175.53 34035 +1968 34 8.34 2.34 6.69 0 257.5 178.62 34196 +1968 35 8.96 2.96 7.31 0 267.53 180.15 34360 +1968 36 7.69 1.69 6.04 0 247.34 183.82 34526 +1968 37 6.88 0.88 5.23 0 235.16 186.94 34694 +1968 38 5.97 -0.03 4.32 0 222.09 190.43 34863 +1968 39 10.19 4.19 8.54 0 288.42 189.02 35035 +1968 40 6.79 0.79 5.14 0.01 233.83 146.2 35208 +1968 41 6.12 0.12 4.47 0 224.2 198.11 35383 +1968 42 2.44 -3.56 0.79 0 177.12 203.47 35560 +1968 43 0.41 -5.59 -1.24 0 155.01 207.48 35738 +1968 44 1.76 -4.24 0.11 0 169.43 209.23 35918 +1968 45 3.84 -2.16 2.19 0.24 193.91 157.8 36099 +1968 46 5.1 -0.9 3.45 0 210.18 212.08 36282 +1968 47 1.64 -4.36 -0.01 0 168.1 217.51 36466 +1968 48 1.39 -4.61 -0.26 0.09 165.37 165.38 36652 +1968 49 -0.5 -6.5 -2.15 0 145.9 224.5 36838 +1968 50 -2.64 -8.64 -4.29 0.05 126.27 207.07 37026 +1968 51 1.2 -4.8 -0.45 0 163.31 229.13 37215 +1968 52 1.84 -4.16 0.19 0 170.32 231.54 37405 +1968 53 3.78 -2.22 2.13 0 193.17 233.04 37596 +1968 54 8.29 2.29 6.64 0 256.71 231.5 37788 +1968 55 9.01 3.01 7.36 0 268.36 233.66 37981 +1968 56 9.82 3.82 8.17 0 282 235.34 38175 +1968 57 9.69 3.69 8.04 0 279.77 238.35 38370 +1968 58 5.07 -0.93 3.42 0.33 209.78 184.67 38565 +1968 59 7.99 1.99 6.34 0 251.99 245.94 38761 +1968 60 16.79 10.79 15.14 0 426.03 235.54 38958 +1968 61 14.57 8.57 12.92 0 374.56 242.42 39156 +1968 62 11.57 5.57 9.92 0 313.51 249.87 39355 +1968 63 10.62 4.62 8.97 0 296.05 254.17 39553 +1968 64 8.51 2.51 6.86 0 260.22 259.78 39753 +1968 65 8.79 2.79 7.14 0 264.75 262.3 39953 +1968 66 6.48 0.48 4.83 0 229.33 267.72 40154 +1968 67 7.68 1.68 6.03 0.14 247.19 201.95 40355 +1968 68 8.93 2.93 7.28 0 267.04 270.59 40556 +1968 69 6.66 0.66 5.01 0 231.94 275.94 40758 +1968 70 4.45 -1.55 2.8 0 201.65 281.12 40960 +1968 71 7.41 1.41 5.76 0.01 243.07 210.63 41163 +1968 72 10.06 4.06 8.41 0.37 286.15 210.14 41366 +1968 73 8.61 2.61 6.96 0 261.83 284.82 41569 +1968 74 1.67 -4.33 0.02 0 168.43 294.94 41772 +1968 75 4.7 -1.3 3.05 0 204.89 294.87 41976 +1968 76 7.85 1.85 6.2 0.08 249.81 220.43 42179 +1968 77 6.83 0.83 5.18 0 234.42 297.77 42383 +1968 78 9.03 3.03 7.38 0 268.69 297.59 42587 +1968 79 9.59 3.59 7.94 0 278.06 299.51 42791 +1968 80 9.75 3.75 8.1 0 280.79 301.8 42996 +1968 81 8.91 2.91 7.26 0 266.71 305.59 43200 +1968 82 5.47 -0.53 3.82 0.01 215.17 234.46 43404 +1968 83 5.86 -0.14 4.21 0 220.55 314.69 43608 +1968 84 13.33 7.33 11.68 0 348.2 305.98 43812 +1968 85 13.46 7.46 11.81 0 350.88 308.18 44016 +1968 86 11.01 5.01 9.36 0 303.11 314.92 44220 +1968 87 13.07 7.07 11.42 0.02 342.87 235.34 44424 +1968 88 9.33 3.33 7.68 0 273.67 322.44 44627 +1968 89 8.99 2.99 7.34 0.14 268.03 243.93 44831 +1968 90 8.41 2.41 6.76 0 258.62 328.46 45034 +1968 91 15.88 9.88 14.23 0 404.24 317.01 45237 +1968 92 19.84 13.84 18.19 0 506.48 308.98 45439 +1968 93 17.98 11.98 16.33 0 456.02 316.2 45642 +1968 94 16.03 10.03 14.38 0.3 407.77 242.33 45843 +1968 95 14.28 8.28 12.63 0 368.25 329.09 46045 +1968 96 17.12 11.12 15.47 0 434.17 324.6 46246 +1968 97 17.02 11.02 15.37 0 431.69 326.84 46446 +1968 98 13.67 7.67 12.02 0 355.26 336.42 46647 +1968 99 11.39 5.39 9.74 0 310.13 342.83 46846 +1968 100 9.7 3.7 8.05 0.03 279.94 260.77 47045 +1968 101 12.48 6.48 10.83 0 331.05 344.66 47243 +1968 102 14.1 8.1 12.45 0 364.37 343.22 47441 +1968 103 13.97 7.97 12.32 0 361.6 345.32 47638 +1968 104 13.59 7.59 11.94 0 353.59 347.94 47834 +1968 105 11.74 5.74 10.09 0 316.72 353.43 48030 +1968 106 13.35 7.35 11.7 0 348.61 351.87 48225 +1968 107 17.68 11.68 16.03 0 448.29 343.14 48419 +1968 108 13.97 7.97 12.32 0.14 361.6 265.45 48612 +1968 109 14.11 8.11 12.46 0 364.59 355.22 48804 +1968 110 15.81 9.81 14.16 0.24 402.61 264.48 48995 +1968 111 13.58 7.58 11.93 0.02 353.38 269.5 49185 +1968 112 11.24 5.24 9.59 0 307.35 365.58 49374 +1968 113 11.86 5.86 10.21 0 319.01 365.74 49561 +1968 114 14.46 8.46 12.81 0 372.15 361.7 49748 +1968 115 17.04 11.04 15.39 0.01 432.18 267.52 49933 +1968 116 12.5 6.5 10.85 0 331.45 368.61 50117 +1968 117 17.7 11.7 16.05 0 448.8 357.35 50300 +1968 118 15.09 9.09 13.44 0 386.11 365.46 50481 +1968 119 16.13 10.13 14.48 0 410.13 364.04 50661 +1968 120 19.56 13.56 17.91 0 498.6 355.4 50840 +1968 121 18.87 12.87 17.22 0 479.6 358.63 51016 +1968 122 19.95 13.95 18.3 0 509.61 356.41 51191 +1968 123 18.85 12.85 17.2 0 479.06 360.86 51365 +1968 124 18.09 12.09 16.44 0 458.88 364.19 51536 +1968 125 17.57 11.57 15.92 0.28 445.49 274.99 51706 +1968 126 17.33 11.33 15.68 0 439.42 368.32 51874 +1968 127 21.05 15.05 19.4 0 541.8 357.53 52039 +1968 128 22.53 16.53 20.88 0 587.83 353.11 52203 +1968 129 24.43 18.43 22.78 0 651.74 346.32 52365 +1968 130 27.29 21.29 25.64 0 758.99 333.99 52524 +1968 131 25.46 19.46 23.81 0.35 688.78 257.5 52681 +1968 132 21.9 15.9 20.25 0 567.85 358.59 52836 +1968 133 21.49 15.49 19.84 0 555.15 360.76 52989 +1968 134 21.41 15.41 19.76 0.01 552.71 271.3 53138 +1968 135 17.38 11.38 15.73 0.82 440.68 281.52 53286 +1968 136 14.51 8.51 12.86 0 373.25 383.55 53430 +1968 137 14.55 8.55 12.9 1.35 374.12 288.12 53572 +1968 138 14.3 8.3 12.65 0.04 368.68 289.03 53711 +1968 139 17.73 11.73 16.08 0.78 449.57 282.73 53848 +1968 140 13.77 7.77 12.12 0.68 357.36 290.86 53981 +1968 141 16.77 10.77 15.12 1.15 425.54 285.47 54111 +1968 142 14.12 8.12 12.47 0.02 364.8 290.96 54238 +1968 143 12.72 6.72 11.07 0 335.82 391.68 54362 +1968 144 11.11 5.11 9.46 0 304.95 395.52 54483 +1968 145 15.89 9.89 14.24 0 404.48 385 54600 +1968 146 19.12 13.12 17.47 0.03 486.41 281.98 54714 +1968 147 18.42 12.42 16.77 0 467.55 378.64 54824 +1968 148 15.34 9.34 13.69 0.17 391.77 290.76 54931 +1968 149 14.78 8.78 13.13 0.27 379.19 292.06 55034 +1968 150 15.77 9.77 14.12 0.12 401.68 290.41 55134 +1968 151 14.88 8.88 13.23 0.72 381.41 292.43 55229 +1968 152 17.02 11.02 15.37 0.04 431.69 288.23 55321 +1968 153 18.21 12.21 16.56 0 462.01 381.05 55409 +1968 154 19.1 13.1 17.45 0.26 485.86 283.94 55492 +1968 155 18.91 12.91 17.26 0 480.69 379.38 55572 +1968 156 24.18 18.18 22.53 0 643.01 360.21 55648 +1968 157 25.32 19.32 23.67 0.08 683.64 266.51 55719 +1968 158 25 19 23.35 0.39 672.02 267.71 55786 +1968 159 22.98 16.98 21.33 0 602.46 365.73 55849 +1968 160 25.54 19.54 23.89 0 691.73 354.91 55908 +1968 161 27.75 21.75 26.1 0.6 777.56 258.12 55962 +1968 162 21.95 15.95 20.3 0.13 569.41 277.53 56011 +1968 163 24.82 18.82 23.17 0.1 665.56 268.87 56056 +1968 164 26.62 20.62 24.97 1.06 732.62 262.61 56097 +1968 165 24.25 18.25 22.6 0.04 645.44 270.83 56133 +1968 166 24.67 18.67 23.02 0.05 660.22 269.52 56165 +1968 167 26.06 20.06 24.41 0.15 711.17 264.72 56192 +1968 168 23.83 17.83 22.18 0.77 630.95 272.25 56214 +1968 169 21.53 15.53 19.88 0.85 556.38 279.05 56231 +1968 170 23.81 17.81 22.16 0.61 630.27 272.32 56244 +1968 171 19.1 13.1 17.45 0 485.86 380.52 56252 +1968 172 21.86 15.86 20.21 0 566.6 370.89 56256 +1968 173 17.69 11.69 16.04 0 448.55 384.85 56255 +1968 174 15.81 9.81 14.16 0.02 402.61 292.54 56249 +1968 175 13.04 7.04 11.39 0 342.26 396.8 56238 +1968 176 11.81 5.81 10.16 0.07 318.06 299.57 56223 +1968 177 17.07 11.07 15.42 0.13 432.93 289.8 56203 +1968 178 15.02 9.02 13.37 0 384.54 391.95 56179 +1968 179 20.98 14.98 19.33 0 539.7 373.78 56150 +1968 180 19.3 13.3 17.65 0 491.36 379.39 56116 +1968 181 21.81 15.81 20.16 0 565.04 370.55 56078 +1968 182 19.79 13.79 18.14 0.27 505.07 283.17 56035 +1968 183 20.77 14.77 19.12 0.24 533.45 280.51 55987 +1968 184 18.11 12.11 16.46 0.59 459.4 286.93 55935 +1968 185 16.94 10.94 15.29 1.82 429.71 289.44 55879 +1968 186 16.34 10.34 14.69 0.27 415.13 290.5 55818 +1968 187 15.14 9.14 13.49 0.65 387.24 292.73 55753 +1968 188 11.97 5.97 10.32 0 321.12 397.38 55684 +1968 189 17.23 11.23 15.58 0.14 436.91 288.14 55611 +1968 190 20.42 14.42 18.77 0.11 523.16 280.3 55533 +1968 191 20.09 14.09 18.44 0 513.62 374.6 55451 +1968 192 22.04 16.04 20.39 0.58 572.24 275.49 55366 +1968 193 23.88 17.88 22.23 0 632.66 359.73 55276 +1968 194 24.98 18.98 23.33 0.1 671.3 266.08 55182 +1968 195 25.67 19.67 24.02 0.01 696.55 263.54 55085 +1968 196 24.44 18.44 22.79 0 652.09 356.48 54984 +1968 197 22.68 16.68 21.03 0.12 592.67 272.44 54879 +1968 198 20.55 14.55 18.9 0.44 526.96 278 54770 +1968 199 23.96 17.96 22.31 0 635.41 357.32 54658 +1968 200 23.55 17.55 21.9 0 621.44 358.62 54542 +1968 201 22.82 16.82 21.17 0 597.22 361.09 54423 +1968 202 25.2 19.2 23.55 0 679.27 350.57 54301 +1968 203 26.05 20.05 24.4 0 710.79 346.2 54176 +1968 204 26.41 20.41 24.76 0.57 724.51 258.01 54047 +1968 205 23.45 17.45 21.8 0.08 618.08 267.39 53915 +1968 206 20.89 14.89 19.24 0.19 537.02 274.21 53780 +1968 207 26.08 20.08 24.43 0.03 711.92 257.94 53643 +1968 208 26.11 20.11 24.46 0 713.06 343.15 53502 +1968 209 25.6 19.6 23.95 0.01 693.95 258.66 53359 +1968 210 27.77 21.77 26.12 1.16 778.38 250.4 53213 +1968 211 28.06 22.06 26.41 0 790.29 331.66 53064 +1968 212 26.07 20.07 24.42 0.02 711.55 255.47 52913 +1968 213 24.25 18.25 22.6 0.37 645.44 260.93 52760 +1968 214 25.15 19.15 23.5 0.18 677.45 257.5 52604 +1968 215 20.91 14.91 19.26 0.3 537.61 269.42 52445 +1968 216 16.9 10.9 15.25 0.48 428.73 277.94 52285 +1968 217 19.31 13.31 17.66 0.48 491.64 271.95 52122 +1968 218 19.03 13.03 17.38 0.57 483.95 271.99 51958 +1968 219 19.9 13.9 18.25 1.62 508.19 269.14 51791 +1968 220 15.92 9.92 14.27 0 405.18 369.41 51622 +1968 221 21.94 15.94 20.29 1.64 569.1 262.45 51451 +1968 222 23.09 17.09 21.44 0.91 606.09 258.45 51279 +1968 223 23.46 17.46 21.81 2.25 618.41 256.54 51105 +1968 224 20.32 14.32 18.67 0.68 520.25 264.22 50929 +1968 225 22 16 20.35 0 570.98 345.39 50751 +1968 226 23.68 17.68 22.03 1.68 625.84 253.45 50572 +1968 227 21.24 15.24 19.59 0.05 547.53 259.25 50392 +1968 228 16.73 10.73 15.08 0.09 424.56 268.55 50210 +1968 229 15.3 9.3 13.65 0.01 390.86 270.31 50026 +1968 230 18.96 12.96 17.31 0.12 482.04 261.94 49842 +1968 231 16.69 10.69 15.04 0.35 423.59 265.59 49656 +1968 232 16.6 10.6 14.95 0 421.4 352.98 49469 +1968 233 13.55 7.55 11.9 0 352.75 358.74 49280 +1968 234 17.27 11.27 15.62 0 437.91 348.33 49091 +1968 235 19.47 13.47 17.82 0 496.08 340.56 48900 +1968 236 23.99 17.99 22.34 0 636.44 323.59 48709 +1968 237 23.74 17.74 22.09 0.65 627.88 242.22 48516 +1968 238 26.82 20.82 25.17 0.79 740.41 231.42 48323 +1968 239 28.02 22.02 26.37 0.03 788.64 226.19 48128 +1968 240 22.55 16.55 20.9 0.18 588.47 241.92 47933 +1968 241 23.53 17.53 21.88 0.08 620.77 238 47737 +1968 242 22.75 16.75 21.1 0.76 594.94 238.86 47541 +1968 243 22 16 20.35 0.11 570.98 239.46 47343 +1968 244 16.85 10.85 15.2 0 427.5 332.58 47145 +1968 245 12.89 6.89 11.24 0 339.23 339.56 46947 +1968 246 13.63 7.63 11.98 0.67 354.42 252.04 46747 +1968 247 16.52 10.52 14.87 0.31 419.46 245.76 46547 +1968 248 20.78 14.78 19.13 0.37 533.75 235.51 46347 +1968 249 21.09 15.09 19.44 0.08 543 233.26 46146 +1968 250 21.92 15.92 20.27 0.61 568.47 229.84 45945 +1968 251 19.63 13.63 17.98 0 500.56 311.4 45743 +1968 252 18.52 12.52 16.87 0 470.21 312.33 45541 +1968 253 18.02 12.02 16.37 0 457.05 311.53 45339 +1968 254 18.76 12.76 17.11 0 476.63 307.47 45136 +1968 255 21.53 15.53 19.88 0 556.38 297.24 44933 +1968 256 23.53 17.53 21.88 0.48 620.77 216.35 44730 +1968 257 22.19 16.19 20.54 0 576.97 290.87 44527 +1968 258 19.34 13.34 17.69 0 492.47 296.99 44323 +1968 259 20.49 14.49 18.84 0.72 525.2 218.54 44119 +1968 260 19.13 13.13 17.48 0.43 486.69 219.61 43915 +1968 261 12.7 6.7 11.05 0.91 335.42 228.37 43711 +1968 262 14.23 8.23 12.58 0.77 367.17 224.41 43507 +1968 263 17.45 11.45 15.8 0.06 442.44 217.35 43303 +1968 264 16.47 10.47 14.82 0.13 418.26 217.11 43099 +1968 265 12.62 6.62 10.97 0.38 333.83 221.01 42894 +1968 266 15.53 9.53 13.88 0.73 396.12 214.99 42690 +1968 267 17.42 11.42 15.77 0.81 441.69 209.9 42486 +1968 268 14.5 8.5 12.85 0 373.03 283.44 42282 +1968 269 15.14 9.14 13.49 0 387.24 279.67 42078 +1968 270 16.47 10.47 14.82 0 418.26 274.32 41875 +1968 271 21.1 15.1 19.45 0.04 543.31 195.39 41671 +1968 272 19.46 13.46 17.81 0.1 495.8 196.63 41468 +1968 273 14.02 8.02 12.37 0.04 362.66 203.43 41265 +1968 274 13.88 7.88 12.23 0 359.69 268.81 41062 +1968 275 8.32 2.32 6.67 0 257.19 274.31 40860 +1968 276 9.19 3.19 7.54 0 271.34 270.44 40658 +1968 277 10.36 4.36 8.71 0.01 291.42 199.61 40456 +1968 278 8.53 2.53 6.88 0 260.54 265.63 40255 +1968 279 9.64 3.64 7.99 0 278.91 261.35 40054 +1968 280 16.28 10.28 14.63 0 413.7 247.99 39854 +1968 281 14.78 8.78 13.13 0.42 379.19 186.06 39654 +1968 282 16.79 10.79 15.14 0 426.03 241.62 39455 +1968 283 18.72 12.72 17.07 0 475.56 234.85 39256 +1968 284 16.5 10.5 14.85 0.12 418.98 177.33 39058 +1968 285 16.31 10.31 14.66 0.16 414.42 175.66 38861 +1968 286 20.12 14.12 18.47 0.09 514.48 167.69 38664 +1968 287 18.41 12.41 16.76 0.22 467.28 168.38 38468 +1968 288 16.82 10.82 15.17 0.01 426.76 168.71 38273 +1968 289 16.43 10.43 14.78 0.38 417.29 167.32 38079 +1968 290 13.14 7.14 11.49 0 344.3 225.69 37885 +1968 291 16.45 10.45 14.8 0 417.77 217.62 37693 +1968 292 14.5 8.5 12.85 0 373.03 218.26 37501 +1968 293 13.34 7.34 11.69 0 348.4 217.32 37311 +1968 294 11.5 5.5 9.85 0 312.19 216.98 37121 +1968 295 12.92 6.92 11.27 0 339.83 212.24 36933 +1968 296 12.52 6.52 10.87 0 331.84 210.22 36745 +1968 297 11.24 5.24 9.59 0 307.35 209.17 36560 +1968 298 12.81 6.81 11.16 0 337.62 204.54 36375 +1968 299 13.39 7.39 11.74 0 349.43 200.98 36191 +1968 300 14.03 8.03 12.38 0.1 362.88 148.09 36009 +1968 301 10.61 4.61 8.96 0 295.87 199.36 35829 +1968 302 10.79 4.79 9.14 0 299.11 196.54 35650 +1968 303 10.86 4.86 9.21 0 300.38 193.89 35472 +1968 304 8.17 2.17 6.52 0 254.81 194.25 35296 +1968 305 6.31 0.31 4.66 0 226.89 193.17 35122 +1968 306 6.51 0.51 4.86 0 229.76 190.72 34950 +1968 307 5.01 -0.99 3.36 0.01 208.98 142.04 34779 +1968 308 7.03 1.03 5.38 0.54 237.37 138.84 34610 +1968 309 6.36 0.36 4.71 0 227.61 183.35 34444 +1968 310 10.25 4.25 8.6 0.75 289.48 132.98 34279 +1968 311 9.7 3.7 8.05 0.32 279.94 131.77 34116 +1968 312 8.25 2.25 6.6 0 256.08 174.43 33956 +1968 313 10.01 4.01 8.36 0.05 285.28 127.99 33797 +1968 314 10.36 4.36 8.71 0 291.42 168.37 33641 +1968 315 9.04 3.04 7.39 0 268.85 167.12 33488 +1968 316 8.54 2.54 6.89 0.36 260.7 124.05 33337 +1968 317 7.1 1.1 5.45 0.01 238.41 123.31 33188 +1968 318 5.75 -0.25 4.1 0.69 219.02 122.32 33042 +1968 319 4.83 -1.17 3.18 0 206.6 162.03 32899 +1968 320 4.09 -1.91 2.44 0 197.05 160.64 32758 +1968 321 5.5 -0.5 3.85 0 215.58 157.57 32620 +1968 322 8.66 2.66 7.01 0 262.64 153.32 32486 +1968 323 7.82 1.82 6.17 0 249.34 152.4 32354 +1968 324 11.15 5.15 9.5 0 305.68 147.43 32225 +1968 325 12.94 6.94 11.29 0 340.24 143.91 32100 +1968 326 12.64 6.64 10.99 0 334.22 142.82 31977 +1968 327 9.51 3.51 7.86 0.66 276.71 107.99 31858 +1968 328 7.19 1.19 5.54 0.27 239.76 107.9 31743 +1968 329 8.31 2.31 6.66 0.14 257.03 106.15 31631 +1968 330 8.44 2.44 6.79 0.72 259.1 105 31522 +1968 331 6.92 0.92 5.27 0.27 235.74 104.87 31417 +1968 332 6.67 0.67 5.02 1.54 232.08 103.77 31316 +1968 333 5.38 -0.62 3.73 0.46 213.95 103.6 31218 +1968 334 8.34 2.34 6.69 0 257.5 134.98 31125 +1968 335 6.14 0.14 4.49 0 224.48 135.38 31035 +1968 336 1.54 -4.46 -0.11 0 167 136.91 30949 +1968 337 0.69 -5.31 -0.96 0.08 157.91 101.73 30867 +1968 338 0.09 -5.91 -1.56 0 151.75 134.95 30790 +1968 339 -0.71 -6.71 -2.36 0 143.86 134.49 30716 +1968 340 -0.06 -6.06 -1.71 0.22 150.24 143.86 30647 +1968 341 1.16 -4.84 -0.49 0.81 162.88 142.7 30582 +1968 342 0.29 -5.71 -1.36 0 153.78 175.37 30521 +1968 343 2.4 -3.6 0.75 0 176.66 173.32 30465 +1968 344 3.5 -2.5 1.85 0 189.71 128.11 30413 +1968 345 0.99 -5.01 -0.66 0 161.07 128.91 30366 +1968 346 6.44 0.44 4.79 0 228.76 125.41 30323 +1968 347 4.52 -1.48 2.87 0 202.55 125.98 30284 +1968 348 -1.1 -7.1 -2.75 0 140.15 128.27 30251 +1968 349 -2.55 -8.55 -4.2 0 127.05 128.42 30221 +1968 350 -3.06 -9.06 -4.71 0 122.7 128.25 30197 +1968 351 -3.21 -9.21 -4.86 0.29 121.45 140.73 30177 +1968 352 -1.77 -7.77 -3.42 0 133.96 172.17 30162 +1968 353 1.44 -4.56 -0.21 0 165.91 170.61 30151 +1968 354 -1.81 -7.81 -3.46 0 133.59 171.91 30145 +1968 355 1.91 -4.09 0.26 0 171.1 170.11 30144 +1968 356 3.48 -2.52 1.83 1.2 189.47 137.61 30147 +1968 357 1.07 -4.93 -0.58 0.14 161.92 94.74 30156 +1968 358 -0.34 -6.34 -1.99 0 147.46 127 30169 +1968 359 0.57 -5.43 -1.08 0.01 156.66 95.06 30186 +1968 360 1.2 -4.8 -0.45 0 163.31 126.83 30208 +1968 361 -0.79 -6.79 -2.44 0 143.09 128.01 30235 +1968 362 -1.43 -7.43 -3.08 0 137.07 128.7 30267 +1968 363 -2.05 -8.05 -3.7 0 131.44 129.52 30303 +1968 364 -5.91 -11.91 -7.56 0.77 100.71 144.31 30343 +1968 365 -2.2 -8.2 -3.85 0 130.11 176.43 30388 +1969 1 -0.58 -6.58 -2.23 1.19 145.12 147.67 30438 +1969 2 1.6 -4.4 -0.05 0 167.66 179.86 30492 +1969 3 0.32 -5.68 -1.33 0 154.09 181.26 30551 +1969 4 0.18 -5.82 -1.47 0.31 152.66 148.83 30614 +1969 5 -3.88 -9.88 -5.53 0.02 115.98 150.43 30681 +1969 6 -1.92 -7.92 -3.57 0.26 132.6 151.29 30752 +1969 7 -1.84 -7.84 -3.49 0.08 133.32 152 30828 +1969 8 -6.21 -12.21 -7.86 0.04 98.6 154.21 30907 +1969 9 -5.4 -11.4 -7.05 1.22 104.37 158.63 30991 +1969 10 -4.6 -10.6 -6.25 0.01 110.35 159.32 31079 +1969 11 -2.35 -8.35 -4 0 128.79 194.73 31171 +1969 12 -2.78 -8.78 -4.43 0 125.07 195.75 31266 +1969 13 0.54 -5.46 -1.11 0 156.35 195.77 31366 +1969 14 0.8 -5.2 -0.85 0 159.06 196.86 31469 +1969 15 3.65 -2.35 2 0 191.56 196.16 31575 +1969 16 2.87 -3.13 1.22 0.21 182.14 160.83 31686 +1969 17 4.09 -1.91 2.44 0.39 197.05 160.86 31800 +1969 18 1.91 -4.09 0.26 0.19 171.1 162.78 31917 +1969 19 -2.28 -8.28 -3.93 0 129.41 204.03 32038 +1969 20 1.11 -4.89 -0.54 0 162.35 203.77 32161 +1969 21 -2.17 -8.17 -3.82 0.57 130.38 169.37 32289 +1969 22 1.63 -4.37 -0.02 0 167.99 208.36 32419 +1969 23 1.74 -4.26 0.09 0 169.21 209.66 32552 +1969 24 3.3 -2.7 1.65 0 187.28 210.22 32688 +1969 25 3.76 -2.24 2.11 0 192.92 211.15 32827 +1969 26 2.94 -3.06 1.29 0 182.97 213.02 32969 +1969 27 2.91 -3.09 1.26 0 182.61 214.5 33114 +1969 28 2.31 -3.69 0.66 0.28 175.63 174.28 33261 +1969 29 2.89 -3.11 1.24 0.25 182.38 175.25 33411 +1969 30 1.07 -4.93 -0.58 0.93 161.92 177.39 33564 +1969 31 0.03 -5.97 -1.62 0 151.15 223.77 33718 +1969 32 4.57 -1.43 2.92 0 203.2 222.37 33875 +1969 33 5.01 -0.99 3.36 0 208.98 223.87 34035 +1969 34 7.18 1.18 5.53 1.54 239.61 178.37 34196 +1969 35 5.63 -0.37 3.98 0.06 217.37 180.05 34360 +1969 36 2.51 -3.49 0.86 0.03 177.93 183.09 34526 +1969 37 6.56 0.56 4.91 0 230.49 228.5 34694 +1969 38 5.25 -0.75 3.6 0 212.19 231.49 34863 +1969 39 6.11 0.11 4.46 0 224.06 232.49 35035 +1969 40 5.21 -0.79 3.56 0 211.65 235.04 35208 +1969 41 3.51 -2.49 1.86 0.06 189.84 188.32 35383 +1969 42 3.67 -2.33 2.02 0.57 191.8 189.55 35560 +1969 43 2.65 -3.35 1 0 179.56 243.15 35738 +1969 44 1.86 -4.14 0.21 0 170.54 209.17 35918 +1969 45 -1.34 -7.34 -2.99 0 137.9 213.73 36099 +1969 46 -0.55 -6.55 -2.2 0.47 145.41 199.64 36282 +1969 47 -3.61 -9.61 -5.26 0.79 118.16 204.87 36466 +1969 48 -5.3 -11.3 -6.95 0.7 105.1 209.21 36652 +1969 49 2.15 -3.85 0.5 0.25 173.81 207.79 36838 +1969 50 2.02 -3.98 0.37 1.23 172.34 209.45 37026 +1969 51 0.6 -5.4 -1.05 0.53 156.97 212.15 37215 +1969 52 0.8 -5.2 -0.85 0.52 159.06 213.91 37405 +1969 53 0.43 -5.57 -1.22 0 155.21 274.96 37596 +1969 54 0.39 -5.61 -1.26 0 154.8 277.54 37788 +1969 55 1.66 -4.34 0.01 0.11 168.32 219.2 37981 +1969 56 0.29 -5.71 -1.36 0 153.78 282.76 38175 +1969 57 0.92 -5.08 -0.73 1.93 160.33 223.3 38370 +1969 58 -0.92 -6.92 -2.57 0.38 141.85 227.2 38565 +1969 59 4.13 -1.87 2.48 0.1 197.56 225.81 38761 +1969 60 2.31 -3.69 0.66 1.29 175.63 228.69 38958 +1969 61 4 -2 2.35 0.58 195.92 229.24 39156 +1969 62 1.68 -4.32 0.03 1.42 168.54 232.44 39355 +1969 63 -3.22 -9.22 -4.87 0.03 121.37 237.02 39553 +1969 64 -2.77 -8.77 -4.42 0 125.16 306.24 39753 +1969 65 1.5 -4.5 -0.15 0.66 166.57 238.59 39953 +1969 66 5.08 -0.92 3.43 0.32 209.91 237.61 40154 +1969 67 7 1 5.35 0.1 236.93 237.39 40355 +1969 68 3.82 -2.18 2.17 0 193.66 310.5 40556 +1969 69 4.28 -1.72 2.63 0 199.47 312.12 40758 +1969 70 4.1 -1.9 2.45 0.03 197.18 244.23 40960 +1969 71 3.97 -2.03 2.32 0 195.54 317.11 41163 +1969 72 4.7 -1.3 3.05 0 204.89 318.62 41366 +1969 73 1.55 -4.45 -0.1 0 167.11 292.25 41569 +1969 74 1.76 -4.24 0.11 0 169.43 294.86 41772 +1969 75 0.98 -5.02 -0.67 0 160.96 298.28 41976 +1969 76 9.94 3.94 8.29 0 284.07 291.05 42179 +1969 77 7.27 1.27 5.62 0 240.96 297.24 42383 +1969 78 6.85 0.85 5.2 0 234.71 300.42 42587 +1969 79 9.65 3.65 8 0 279.08 299.43 42791 +1969 80 14.07 8.07 12.42 0 363.73 294.51 42996 +1969 81 11.37 5.37 9.72 0 309.76 301.84 43200 +1969 82 11.76 5.76 10.11 0 317.1 303.82 43404 +1969 83 14.27 8.27 12.62 0 368.03 301.67 43608 +1969 84 11.71 5.71 10.06 0 316.16 308.88 43812 +1969 85 9.33 3.33 7.68 0 273.67 315.15 44016 +1969 86 10.55 4.55 8.9 0 294.79 315.67 44220 +1969 87 10.15 4.15 8.5 0 287.72 318.83 44424 +1969 88 8.49 2.49 6.84 0 259.9 323.68 44627 +1969 89 4.54 -1.46 2.89 0 202.81 330.99 44831 +1969 90 5.7 -0.3 4.05 0 218.33 332.04 45034 +1969 91 7.82 1.82 6.17 0 249.34 331.56 45237 +1969 92 8.98 2.98 7.33 0 267.86 332.14 45439 +1969 93 12.23 6.23 10.58 0 326.15 328.91 45642 +1969 94 17.13 11.13 15.48 0.03 434.42 240.34 45843 +1969 95 16.13 10.13 14.48 0.64 410.13 243.72 46045 +1969 96 17.32 11.32 15.67 0.7 439.17 243.07 46246 +1969 97 15.26 9.26 13.61 0.21 389.95 248.28 46446 +1969 98 14.11 8.11 12.46 0.54 364.59 251.62 46647 +1969 99 14.37 8.37 12.72 0 370.19 336.92 46846 +1969 100 14.7 8.7 13.05 0.02 377.42 253.59 47045 +1969 101 15.54 9.54 13.89 0 396.35 338.1 47243 +1969 102 11.21 5.21 9.56 0 306.79 348.95 47441 +1969 103 11.43 5.43 9.78 0 310.88 350.39 47638 +1969 104 10.82 4.82 9.17 0 299.65 353.32 47834 +1969 105 15.09 9.09 13.44 0.01 386.11 259.8 48030 +1969 106 13.25 7.25 11.6 0 346.55 352.07 48225 +1969 107 11.39 5.39 9.74 0 310.13 357.42 48419 +1969 108 14.79 8.79 13.14 0 379.41 352.09 48612 +1969 109 15.41 9.41 13.76 0 393.37 352.22 48804 +1969 110 13.29 7.29 11.64 0.24 347.37 268.8 48995 +1969 111 12.81 6.81 11.16 0.04 337.62 270.72 49185 +1969 112 11.85 5.85 10.2 0.02 318.82 273.31 49374 +1969 113 13.11 7.11 11.46 0 343.69 363.19 49561 +1969 114 11 5 9.35 0 302.93 368.89 49748 +1969 115 8.78 2.78 7.13 0 264.59 374.21 49933 +1969 116 11.36 5.36 9.71 0.02 309.57 278.16 50117 +1969 117 11.53 5.53 9.88 0 312.76 371.87 50300 +1969 118 11.41 5.41 9.76 0 310.51 373.43 50481 +1969 119 7.04 1.04 5.39 0.11 237.52 286.54 50661 +1969 120 17.39 11.39 15.74 0 440.93 361.83 50840 +1969 121 23.99 17.99 22.34 1.01 636.44 255.45 51016 +1969 122 19.87 13.87 18.22 0.01 507.33 267.5 51191 +1969 123 21 15 19.35 0 540.3 353.9 51365 +1969 124 24.27 18.27 22.62 0.02 646.14 256.92 51536 +1969 125 24.23 18.23 22.58 0 644.75 343.65 51706 +1969 126 24.41 18.41 22.76 0.38 651.04 257.87 51874 +1969 127 26.52 20.52 24.87 0 728.75 335.28 52039 +1969 128 24.18 18.18 22.53 0 643.01 346.57 52203 +1969 129 21.31 15.31 19.66 0 549.66 358.4 52365 +1969 130 17.74 11.74 16.09 0 449.83 370.63 52524 +1969 131 16.82 10.82 15.17 0 426.76 374.02 52681 +1969 132 15.62 9.62 13.97 0.01 398.2 283.52 52836 +1969 133 17.3 11.3 15.65 0 438.67 374.2 52989 +1969 134 21.37 15.37 19.72 0 551.49 361.88 53138 +1969 135 22.18 16.18 20.53 0 576.65 359.58 53286 +1969 136 21.77 15.77 20.12 0.51 563.79 271.29 53430 +1969 137 21.03 15.03 19.38 0.02 541.2 273.8 53572 +1969 138 21.42 15.42 19.77 0.46 553.01 273.2 53711 +1969 139 21.87 15.87 20.22 1.09 566.91 272.46 53848 +1969 140 23.22 17.22 21.57 0.03 610.39 268.91 53981 +1969 141 23.84 17.84 22.19 0.89 631.29 267.32 54111 +1969 142 23.62 17.62 21.97 0.26 623.81 268.36 54238 +1969 143 20.39 14.39 18.74 0 522.29 370.46 54362 +1969 144 18.64 12.64 16.99 0.21 473.41 282.48 54483 +1969 145 16.54 10.54 14.89 0.01 419.95 287.44 54600 +1969 146 14.12 8.12 12.47 0 364.8 389.83 54714 +1969 147 13.25 7.25 11.6 0 346.55 392.34 54824 +1969 148 14.54 8.54 12.89 0 373.9 389.69 54931 +1969 149 15.56 9.56 13.91 0 396.81 387.43 55034 +1969 150 16.78 10.78 15.13 1.03 425.78 288.36 55134 +1969 151 16.77 10.77 15.12 1.14 425.54 288.67 55229 +1969 152 17.45 11.45 15.8 0.53 442.44 287.3 55321 +1969 153 16.61 10.61 14.96 0.62 421.64 289.28 55409 +1969 154 17.74 11.74 16.09 1.18 449.83 287.09 55492 +1969 155 13.63 7.63 11.98 0.36 354.42 295.35 55572 +1969 156 20.41 14.41 18.76 1.43 522.87 281.05 55648 +1969 157 18.74 12.74 17.09 2.41 476.09 285.31 55719 +1969 158 14.26 8.26 12.61 0 367.81 392.99 55786 +1969 159 16.78 10.78 15.13 0 425.78 386.65 55849 +1969 160 14.63 8.63 12.98 0.01 375.88 294.38 55908 +1969 161 16.24 10.24 14.59 0.57 412.74 291.3 55962 +1969 162 20.43 14.43 18.78 1.1 523.45 281.66 56011 +1969 163 21.25 15.25 19.6 1.16 547.84 279.64 56056 +1969 164 21.46 15.46 19.81 0.67 554.23 279.09 56097 +1969 165 21.28 15.28 19.63 0.1 548.75 279.66 56133 +1969 166 22.13 16.13 20.48 0.97 575.07 277.34 56165 +1969 167 23.36 17.36 21.71 0.04 615.06 273.65 56192 +1969 168 20.42 14.42 18.77 0 523.16 376.04 56214 +1969 169 19.63 13.63 17.98 0.36 500.56 284.05 56231 +1969 170 21.79 15.79 20.14 0.03 564.42 278.33 56244 +1969 171 21.96 15.96 20.31 0.67 569.72 277.89 56252 +1969 172 23.36 17.36 21.71 0.26 615.06 273.75 56256 +1969 173 24.36 18.36 22.71 0 649.28 360.78 56255 +1969 174 26.31 20.31 24.66 0.37 720.68 263.85 56249 +1969 175 29.32 23.32 27.67 0 843.86 336.07 56238 +1969 176 23.16 17.16 21.51 0 608.4 365.65 56223 +1969 177 22.38 16.38 20.73 0 583.02 368.64 56203 +1969 178 19.04 13.04 17.39 0.08 484.22 285.34 56179 +1969 179 18.24 12.24 16.59 0 462.8 382.86 56150 +1969 180 17.01 11.01 15.36 0.01 431.44 289.78 56116 +1969 181 19.28 13.28 17.63 0.05 490.81 284.54 56078 +1969 182 21.56 15.56 19.91 0 557.3 371.34 56035 +1969 183 24.57 18.57 22.92 0 656.67 359.05 55987 +1969 184 22.3 16.3 20.65 0 580.46 368.22 55935 +1969 185 24.86 18.86 23.21 0.08 666.99 268.16 55879 +1969 186 21.5 15.5 19.85 0.11 555.46 278.17 55818 +1969 187 18.91 12.91 17.26 0.1 480.69 284.67 55753 +1969 188 24.5 18.5 22.85 0.27 654.2 268.83 55684 +1969 189 25.62 19.62 23.97 0.08 694.69 264.94 55611 +1969 190 21.42 15.42 19.77 0.17 553.01 277.64 55533 +1969 191 23.28 17.28 21.63 0.02 612.39 272.07 55451 +1969 192 20.64 14.64 18.99 0 529.61 372.41 55366 +1969 193 20.79 14.79 19.14 0 534.04 371.61 55276 +1969 194 23.26 17.26 21.61 0 611.72 362.06 55182 +1969 195 19.93 13.93 18.28 0.33 509.04 280.55 55085 +1969 196 20.96 14.96 19.31 0 539.11 370.11 54984 +1969 197 17.51 11.51 15.86 0 443.96 380.76 54879 +1969 198 16.84 10.84 15.19 0.47 427.25 286.68 54770 +1969 199 18.37 12.37 16.72 0.13 466.23 283.05 54658 +1969 200 21.55 15.55 19.9 0.32 557 274.77 54542 +1969 201 22.31 16.31 20.66 0.66 580.78 272.29 54423 +1969 202 21.01 15.01 19.36 0.17 540.6 275.46 54301 +1969 203 22.77 16.77 21.12 0.13 595.59 270.17 54176 +1969 204 22.63 16.63 20.98 0 591.05 360.28 54047 +1969 205 23.82 17.82 22.17 0 630.61 355.01 53915 +1969 206 23.36 17.36 21.71 0 615.06 356.34 53780 +1969 207 24.74 18.74 23.09 0.36 662.71 262.45 53643 +1969 208 27.64 21.64 25.99 0 773.09 335.72 53502 +1969 209 23.17 17.17 21.52 0 608.73 355.18 53359 +1969 210 25.21 19.21 23.56 0.01 679.63 259.52 53213 +1969 211 27 21 25.35 0.41 747.48 252.73 53064 +1969 212 26.85 20.85 25.2 1.04 741.58 252.71 52913 +1969 213 21.18 15.18 19.53 0.35 545.72 269.78 52760 +1969 214 25.13 19.13 23.48 0.11 676.72 257.56 52604 +1969 215 24.49 18.49 22.84 0 653.85 345.52 52445 +1969 216 23.42 17.42 21.77 0 617.07 348.91 52285 +1969 217 22.76 16.76 21.11 0 595.27 350.62 52122 +1969 218 21.31 15.31 19.66 0.24 549.66 266.35 51958 +1969 219 21.88 15.88 20.23 0.36 567.22 264.05 51791 +1969 220 20.68 14.68 19.03 2.13 530.79 266.5 51622 +1969 221 19.21 13.21 17.56 0.41 488.88 269.32 51451 +1969 222 19.9 13.9 18.25 0 508.19 355.86 51279 +1969 223 17.07 11.07 15.42 0.82 432.93 272.33 51105 +1969 224 16.71 10.71 15.06 0 424.07 363 50929 +1969 225 16.24 10.24 14.59 0.77 412.74 272.3 50751 +1969 226 16.58 10.58 14.93 0.25 420.91 270.76 50572 +1969 227 19.46 13.46 17.81 0.38 495.8 263.61 50392 +1969 228 22.56 16.56 20.91 1.79 588.79 254.83 50210 +1969 229 24.12 18.12 22.47 0.46 640.93 249.43 50026 +1969 230 26.45 20.45 24.8 0.15 726.05 241.06 49842 +1969 231 23.69 17.69 22.04 0.73 626.18 248.71 49656 +1969 232 24.29 18.29 22.64 0.9 646.84 245.96 49469 +1969 233 23.03 17.03 21.38 0.94 604.11 248.58 49280 +1969 234 22.08 16.08 20.43 0 573.49 333.5 49091 +1969 235 17.81 11.81 16.16 0.33 451.62 259.02 48900 +1969 236 18.51 12.51 16.86 0 469.94 341.96 48709 +1969 237 19.14 13.14 17.49 0.2 486.96 253.86 48516 +1969 238 20.5 14.5 18.85 0 525.5 332.65 48323 +1969 239 21.46 15.46 19.81 0.14 554.23 246.02 48128 +1969 240 17.92 11.92 16.27 0.16 454.46 252.74 47933 +1969 241 15.72 9.72 14.07 0.67 400.51 255.63 47737 +1969 242 16.08 10.08 14.43 0.62 408.95 253.66 47541 +1969 243 15.64 9.64 13.99 0.56 398.66 253.03 47343 +1969 244 16.93 10.93 15.28 0 429.47 332.37 47145 +1969 245 19.5 13.5 17.85 0 496.92 323.54 46947 +1969 246 19.45 13.45 17.8 0.13 495.53 241.3 46747 +1969 247 23.12 17.12 21.47 0 607.08 308.13 46547 +1969 248 25.36 19.36 23.71 0 685.11 297.84 46347 +1969 249 27.18 21.18 25.53 0 754.61 288.29 46146 +1969 250 25.58 19.58 23.93 0 693.21 293.18 45945 +1969 251 24.17 18.17 22.52 0 642.66 296.6 45743 +1969 252 26.43 20.43 24.78 0 725.28 285.72 45541 +1969 253 21.63 15.63 19.98 0.02 559.46 225.89 45339 +1969 254 21.06 15.06 19.41 0 542.1 300.88 45136 +1969 255 17.42 11.42 15.77 0 441.69 308.67 44933 +1969 256 12.93 6.93 11.28 0 340.04 316.07 44730 +1969 257 10.99 4.99 9.34 0 302.75 317.28 44527 +1969 258 12.62 6.62 10.97 0 333.83 312.04 44323 +1969 259 15 9 13.35 0.4 384.09 228.69 44119 +1969 260 14.11 8.11 12.46 0.42 364.59 228.24 43915 +1969 261 16.78 10.78 15.13 1.08 425.78 222.13 43711 +1969 262 15.51 9.51 13.86 0 395.66 296.6 43507 +1969 263 16.32 10.32 14.67 0 414.65 292.38 43303 +1969 264 17.01 11.01 15.36 0 431.44 288.27 43099 +1969 265 14.18 8.18 12.53 0 366.09 291.83 42894 +1969 266 12.68 6.68 11.03 0 335.02 292.06 42690 +1969 267 15.65 9.65 14 0 398.89 283.72 42486 +1969 268 14.62 8.62 12.97 0.14 375.66 212.41 42282 +1969 269 15.65 9.65 14 0 398.89 278.65 42078 +1969 270 25.07 19.07 23.42 0.64 674.55 188.04 41875 +1969 271 22.83 16.83 21.18 0.29 597.55 191.64 41671 +1969 272 23.95 17.95 22.3 0.96 635.06 187.09 41468 +1969 273 18.77 12.77 17.12 0 476.9 261.39 41265 +1969 274 10.89 4.89 9.24 0 300.92 273.65 41062 +1969 275 11.21 5.21 9.56 0 306.79 270.36 40860 +1969 276 11.27 5.27 9.62 0 307.9 267.54 40658 +1969 277 13.8 7.8 12.15 0.69 357.99 195.61 40456 +1969 278 12.35 6.35 10.7 0.06 328.5 195.23 40255 +1969 279 12.67 6.67 11.02 0 334.82 256.98 40054 +1969 280 9.12 3.12 7.47 0 270.17 259.32 39854 +1969 281 6.98 0.98 5.33 0.52 236.63 194.29 39654 +1969 282 10 4 8.35 0 285.11 252.64 39455 +1969 283 12.29 6.29 10.64 0.59 327.32 184.94 39256 +1969 284 12.58 6.58 10.93 0.59 333.03 182.34 39058 +1969 285 14.18 8.18 12.53 0.01 366.09 178.47 38861 +1969 286 16.31 10.31 14.66 0 414.42 231.5 38664 +1969 287 15.86 9.86 14.21 0 403.78 229.44 38468 +1969 288 15.66 9.66 14.01 0 399.12 227.05 38273 +1969 289 14.63 8.63 12.98 0 375.88 226.21 38079 +1969 290 14.23 8.23 12.58 0 367.17 224.02 37885 +1969 291 14.93 8.93 13.28 0.02 382.52 165.17 37693 +1969 292 13.16 7.16 11.51 0 344.71 220.3 37501 +1969 293 12.27 6.27 10.62 0 326.93 218.84 37311 +1969 294 13.46 7.46 11.81 0 350.88 214.28 37121 +1969 295 14.24 8.24 12.59 0 367.38 210.32 36933 +1969 296 15.66 9.66 14.01 0 399.12 205.54 36745 +1969 297 17.05 11.05 15.4 0.01 432.43 150.39 36560 +1969 298 13.86 7.86 12.21 0 359.26 203.07 36375 +1969 299 15.07 9.07 13.42 0 385.66 198.53 36191 +1969 300 15.63 9.63 13.98 0 398.43 195.05 36009 +1969 301 17.1 11.1 15.45 0 433.67 190.2 35829 +1969 302 18.3 12.3 16.65 0 464.38 185.58 35650 +1969 303 17.11 11.11 15.46 0.38 433.92 138.87 35472 +1969 304 15.7 9.7 14.05 0.23 400.05 138.77 35296 +1969 305 11.79 5.79 10.14 0.57 317.68 140.72 35122 +1969 306 9.66 3.66 8.01 0.3 279.26 140.82 34950 +1969 307 13.21 7.21 11.56 0 345.73 181.17 34779 +1969 308 12.85 6.85 11.2 0 338.42 179.06 34610 +1969 309 13.98 7.98 12.33 0.58 361.81 131.51 34444 +1969 310 11.42 5.42 9.77 0.04 310.69 132.04 34279 +1969 311 10.15 4.15 8.5 0.44 287.72 131.43 34116 +1969 312 6.92 0.92 5.27 0 235.74 175.58 33956 +1969 313 7.91 1.91 6.26 0 250.74 172.61 33797 +1969 314 8.24 2.24 6.59 0.25 255.92 127.78 33641 +1969 315 7.35 1.35 5.7 0 242.16 168.59 33488 +1969 316 10.54 4.54 8.89 0 294.62 163.51 33337 +1969 317 10.51 4.51 8.86 0 294.08 161.37 33188 +1969 318 13.82 7.82 12.17 2.07 358.42 116.59 33042 +1969 319 13 7 11.35 0 341.45 154.76 32899 +1969 320 14.37 8.37 12.72 0 370.19 151.34 32758 +1969 321 8.88 2.88 7.23 0 266.22 154.94 32620 +1969 322 5.48 -0.52 3.83 0.08 215.31 116.82 32486 +1969 323 6.08 0.08 4.43 0 223.63 153.71 32354 +1969 324 7.51 1.51 5.86 0 244.59 150.6 32225 +1969 325 8.66 2.66 7.01 0 262.64 147.97 32100 +1969 326 11.48 5.48 9.83 0.01 311.82 108 31977 +1969 327 11.32 5.32 9.67 0 308.83 142.34 31858 +1969 328 12.19 6.19 10.54 0 325.37 139.54 31743 +1969 329 9.41 3.41 7.76 0.01 275.02 105.48 31631 +1969 330 15.41 9.41 13.76 0 393.37 133.15 31522 +1969 331 13.83 7.83 12.18 0.18 358.63 100.27 31417 +1969 332 7.85 1.85 6.2 0.08 249.81 103.14 31316 +1969 333 7.84 1.84 6.19 0.38 249.65 102.33 31218 +1969 334 6.89 0.89 5.24 0.17 235.3 102.03 31125 +1969 335 -4.45 -10.45 -6.1 1.41 111.5 152.19 31035 +1969 336 -0.91 -6.91 -2.56 0.11 141.95 150.87 30949 +1969 337 1.06 -4.94 -0.59 0 161.81 182.82 30867 +1969 338 2.98 -3.02 1.33 0 183.44 180.64 30790 +1969 339 2.95 -3.05 1.3 0.32 183.09 146.4 30716 +1969 340 2.25 -3.75 0.6 0.19 174.94 145.92 30647 +1969 341 0.69 -5.31 -0.96 0.28 157.91 145.79 30582 +1969 342 -1.72 -7.72 -3.37 1.29 134.41 150.1 30521 +1969 343 -4.07 -10.07 -5.72 0.84 114.47 152.83 30465 +1969 344 -8.33 -14.33 -9.98 0.21 84.8 153.6 30413 +1969 345 -4.78 -10.78 -6.43 0 108.98 185.41 30366 +1969 346 -2.18 -8.18 -3.83 0 130.29 184.06 30323 +1969 347 -1.25 -7.25 -2.9 0.4 138.74 152.28 30284 +1969 348 -2.16 -8.16 -3.81 0.07 130.46 152.55 30251 +1969 349 -1.88 -7.88 -3.53 0.31 132.96 153.23 30221 +1969 350 -0.38 -6.38 -2.03 0 147.07 184.4 30197 +1969 351 1.38 -4.62 -0.27 0.01 165.26 151.71 30177 +1969 352 -0.9 -6.9 -2.55 0 142.04 184.17 30162 +1969 353 1.65 -4.35 0 0 168.21 182.82 30151 +1969 354 0.14 -5.86 -1.51 0 152.26 183.44 30145 +1969 355 -1.87 -7.87 -3.52 0 133.05 184.23 30144 +1969 356 -1.24 -7.24 -2.89 0 138.83 184.02 30147 +1969 357 -4.02 -10.02 -5.67 0 114.87 185.02 30156 +1969 358 -3.39 -9.39 -5.04 0.96 119.96 155.91 30169 +1969 359 -1.69 -7.69 -3.34 0.01 134.68 155.56 30186 +1969 360 -1.11 -7.11 -2.76 0 140.05 187.57 30208 +1969 361 0.13 -5.87 -1.52 0 152.15 187.34 30235 +1969 362 0.28 -5.72 -1.37 0 153.68 187.62 30267 +1969 363 2.23 -3.77 0.58 0 174.72 186.95 30303 +1969 364 4.14 -1.86 2.49 0 197.68 185.73 30343 +1969 365 0.31 -5.69 -1.34 0 153.98 188.05 30388 +1970 1 3.44 -2.56 1.79 0 188.98 186.89 30438 +1970 2 3.48 -2.52 1.83 0 189.47 187.04 30492 +1970 3 -0.99 -6.99 -2.64 0 141.19 189.95 30551 +1970 4 0.03 -5.97 -1.62 0 151.15 190.33 30614 +1970 5 -0.37 -6.37 -2.02 0 147.17 191.03 30681 +1970 6 -2.88 -8.88 -4.53 0 124.22 192.76 30752 +1970 7 -3.5 -9.5 -5.15 0 119.06 193.65 30828 +1970 8 -1.42 -7.42 -3.07 0.04 137.16 159.95 30907 +1970 9 2.47 -3.53 0.82 0 177.47 193.39 30991 +1970 10 -0.73 -6.73 -2.38 0.41 143.67 162.31 31079 +1970 11 0.12 -5.88 -1.53 0.21 152.05 162.6 31171 +1970 12 4.87 -1.13 3.22 0 207.13 195.45 31266 +1970 13 5.46 -0.54 3.81 0.28 215.04 160.73 31366 +1970 14 2.51 -3.49 0.86 0 177.93 198.52 31469 +1970 15 5.29 -0.71 3.64 0.07 212.73 161.63 31575 +1970 16 2.06 -3.94 0.41 0.12 172.79 163.56 31686 +1970 17 0.51 -5.49 -1.14 0.35 156.04 165.15 31800 +1970 18 -1.14 -7.14 -2.79 0.42 139.77 168.22 31917 +1970 19 -1.47 -7.47 -3.12 0 136.7 208.02 32038 +1970 20 1.13 -4.87 -0.52 0 162.56 208.06 32161 +1970 21 -0.96 -6.96 -2.61 0.04 141.47 171.69 32289 +1970 22 -2.74 -8.74 -4.39 0.02 125.42 173.43 32419 +1970 23 -6.18 -12.18 -7.83 0.01 98.81 175.51 32552 +1970 24 -0.09 -6.09 -1.74 0 149.94 215.66 32688 +1970 25 -1.18 -7.18 -2.83 0 139.39 217.85 32827 +1970 26 0.35 -5.65 -1.3 0 154.39 218.79 32969 +1970 27 3.79 -2.21 2.14 0 193.29 218.15 33114 +1970 28 6.84 0.84 5.19 0 234.57 217.11 33261 +1970 29 3.89 -2.11 2.24 0 194.54 220.92 33411 +1970 30 1.31 -4.69 -0.34 0 164.5 224.36 33564 +1970 31 6.01 0.01 4.36 0 222.65 222.68 33718 +1970 32 11.04 5.04 9.39 0.06 303.66 175.83 33875 +1970 33 9.4 3.4 7.75 1.48 274.85 177.69 34035 +1970 34 8.52 2.52 6.87 0.89 260.38 178.72 34196 +1970 35 3.14 -2.86 1.49 0 185.35 229.14 34360 +1970 36 2.92 -3.08 1.27 0.1 182.73 184.37 34526 +1970 37 1.01 -4.99 -0.64 0 161.28 234.55 34694 +1970 38 -0.71 -6.71 -2.36 0 143.86 238.06 34863 +1970 39 -2.34 -8.34 -3.99 0 128.88 241.31 35035 +1970 40 0.39 -5.61 -1.26 0 154.8 242.27 35208 +1970 41 3.01 -2.99 1.36 0 183.8 242.69 35383 +1970 42 4.4 -1.6 2.75 0 201 243.53 35560 +1970 43 4.33 -1.67 2.68 0.2 200.11 194.39 35738 +1970 44 6.56 0.56 4.91 0.19 230.49 193.98 35918 +1970 45 7.98 1.98 6.33 0.72 251.83 193.83 36099 +1970 46 5.73 -0.27 4.08 0.01 218.75 196.57 36282 +1970 47 5.36 -0.64 3.71 0 213.68 251.81 36466 +1970 48 5.2 -0.8 3.55 0.06 211.52 199.58 36652 +1970 49 4.22 -1.78 2.57 0.24 198.7 165.91 36838 +1970 50 -0.27 -6.27 -1.92 0.09 148.15 206.18 37026 +1970 51 -0.72 -6.72 -2.37 0 143.77 266.04 37215 +1970 52 -1.55 -7.55 -3.2 0 135.96 269.21 37405 +1970 53 0.96 -5.04 -0.69 0 160.75 270.38 37596 +1970 54 -2.46 -8.46 -4.11 0 127.83 275.07 37788 +1970 55 -2.28 -8.28 -3.93 0 129.41 277.84 37981 +1970 56 3.53 -2.47 1.88 0 190.08 241.73 38175 +1970 57 3.14 -2.86 1.49 0.01 185.35 183.72 38370 +1970 58 3.49 -2.51 1.84 0 189.59 247.62 38565 +1970 59 3.56 -2.44 1.91 0.25 190.45 187.72 38761 +1970 60 1.95 -4.05 0.3 0.09 171.55 190.88 38958 +1970 61 4.03 -1.97 2.38 1.62 196.29 191.8 39156 +1970 62 5.09 -0.91 3.44 0 210.05 257.57 39355 +1970 63 7.37 1.37 5.72 1.35 242.46 193.66 39553 +1970 64 5.17 -0.83 3.52 0.1 211.12 197.57 39753 +1970 65 8.72 2.72 7.07 0 263.61 262.39 39953 +1970 66 11.84 5.84 10.19 0.01 318.63 195.61 40154 +1970 67 8.88 2.88 7.23 0.02 266.22 200.85 40355 +1970 68 6.79 0.79 5.14 0 233.83 273.16 40556 +1970 69 7.82 1.82 6.17 0.11 249.34 205.94 40758 +1970 70 9.98 3.98 8.33 0 284.76 274.61 40960 +1970 71 9.01 3.01 7.36 0 268.36 278.82 41163 +1970 72 8.76 2.76 7.11 0 264.26 281.96 41366 +1970 73 11.08 5.08 9.43 0.69 304.4 210.99 41569 +1970 74 11.36 5.36 9.71 0.5 309.57 212.7 41772 +1970 75 4.29 -1.71 2.64 0.48 199.59 221.47 41976 +1970 76 7.79 1.79 6.14 0 248.88 293.98 42179 +1970 77 9.01 3.01 7.36 0 268.36 294.96 42383 +1970 78 8.99 2.99 7.34 0.03 268.03 223.24 42587 +1970 79 7.25 1.25 5.6 0.8 240.65 227 42791 +1970 80 7.71 1.71 6.06 0.31 247.65 228.47 42996 +1970 81 1.18 -4.82 -0.47 0.3 163.1 235.63 43200 +1970 82 6.87 0.87 5.22 0.63 235.01 233.21 43404 +1970 83 4.3 -1.7 2.65 0.24 199.72 237.32 43608 +1970 84 3.69 -2.31 2.04 0 192.05 319.64 43812 +1970 85 5.5 -0.5 3.85 0.22 215.58 240.14 44016 +1970 86 4.71 -1.29 3.06 0.15 205.02 242.65 44220 +1970 87 2.96 -3.04 1.31 0 183.21 327.94 44424 +1970 88 1.21 -4.79 -0.44 1.9 163.42 248.99 44627 +1970 89 2.48 -3.52 0.83 0.04 177.58 249.85 44831 +1970 90 6.53 0.53 4.88 0.03 230.05 248.26 45034 +1970 91 9.69 3.69 8.04 0 279.77 328.8 45237 +1970 92 8.55 2.55 6.9 0 260.86 332.78 45439 +1970 93 14.23 8.23 12.58 0.35 367.17 243.73 45642 +1970 94 12.3 6.3 10.65 0.05 327.52 248.19 45843 +1970 95 10.73 4.73 9.08 0 298.03 335.85 46045 +1970 96 10.92 4.92 9.27 0.93 301.47 253.23 46246 +1970 97 11.49 5.49 9.84 0.16 312.01 254.01 46446 +1970 98 11.47 5.47 9.82 0.05 311.63 255.51 46647 +1970 99 9.55 3.55 7.9 0 277.38 345.98 46846 +1970 100 11.72 5.72 10.07 0.11 316.34 258.13 47045 +1970 101 13.97 7.97 12.32 1.14 361.6 256.21 47243 +1970 102 15.97 9.97 14.32 1 406.36 254.21 47441 +1970 103 16.68 10.68 15.03 0.1 423.34 254.25 47638 +1970 104 15.3 9.3 13.65 0.13 390.86 258.11 47834 +1970 105 15.37 9.37 13.72 1.22 392.46 259.31 48030 +1970 106 15.51 9.51 13.86 0.03 395.66 260.27 48225 +1970 107 14.27 8.27 12.62 0.53 368.03 263.66 48419 +1970 108 7.53 1.53 5.88 0.09 244.89 274.2 48612 +1970 109 4.47 -1.53 2.82 0 201.91 371.35 48804 +1970 110 4.02 -1.98 2.37 0.42 196.17 280.01 48995 +1970 111 8.17 2.17 6.52 0.48 254.81 276.97 49185 +1970 112 10 4 8.35 0 285.11 367.83 49374 +1970 113 12.18 6.18 10.53 0 325.18 365.11 49561 +1970 114 10.31 4.31 8.66 0.21 290.53 277.61 49748 +1970 115 9.27 3.27 7.62 0.1 272.67 280.05 49933 +1970 116 13.25 7.25 11.6 0 346.55 367.04 50117 +1970 117 16.58 10.58 14.93 0 420.91 360.4 50300 +1970 118 16.54 10.54 14.89 0.74 419.95 271.35 50481 +1970 119 17.05 11.05 15.4 0 432.43 361.61 50661 +1970 120 12.61 6.61 10.96 0 333.63 373.4 50840 +1970 121 13.2 7.2 11.55 0 345.53 373.28 51016 +1970 122 14.65 8.65 13 0 376.32 371.18 51191 +1970 123 12.7 6.7 11.05 0 335.42 376.59 51365 +1970 124 13.08 7.08 11.43 0.17 343.08 282.65 51536 +1970 125 14.19 8.19 12.54 0 366.3 375.36 51706 +1970 126 12.33 6.33 10.68 0 328.11 380.46 51874 +1970 127 11.57 5.57 9.92 0.69 313.51 287.19 52039 +1970 128 11.1 5.1 9.45 0.46 304.76 288.64 52203 +1970 129 9.22 3.22 7.57 0.18 271.84 291.87 52365 +1970 130 8.12 2.12 6.47 0.01 254.02 293.87 52524 +1970 131 13.25 7.25 11.6 0 346.55 382.86 52681 +1970 132 9.79 3.79 8.14 0 281.48 390.64 52836 +1970 133 16.2 10.2 14.55 0.06 411.79 282.91 52989 +1970 134 14.91 8.91 13.26 0 382.08 381.23 53138 +1970 135 14.68 8.68 13.03 0.01 376.98 286.87 53286 +1970 136 13.03 7.03 11.38 0.04 342.06 290.23 53430 +1970 137 16.28 10.28 14.63 0 413.7 379.75 53572 +1970 138 21.93 15.93 20.28 0.01 568.78 271.79 53711 +1970 139 22.78 16.78 21.13 0.82 595.92 269.87 53848 +1970 140 21.99 15.99 20.34 0 570.66 363.3 53981 +1970 141 20.75 14.75 19.1 0 532.86 368.21 54111 +1970 142 19.38 13.38 17.73 0 493.58 373.3 54238 +1970 143 23.06 17.06 21.41 0.4 605.1 270.44 54362 +1970 144 18.88 12.88 17.23 0 479.87 375.89 54483 +1970 145 19.39 13.39 17.74 0 493.86 374.73 54600 +1970 146 19.36 13.36 17.71 0 493.03 375.2 54714 +1970 147 17.28 11.28 15.63 0.34 438.16 286.52 54824 +1970 148 16.07 10.07 14.42 0 408.71 385.77 54931 +1970 149 19.06 13.06 17.41 0.79 484.77 283 55034 +1970 150 18.24 12.24 16.59 0.06 462.8 285.16 55134 +1970 151 15.49 9.49 13.84 0.04 395.2 291.26 55229 +1970 152 23.85 17.85 22.2 0.67 631.63 270.42 55321 +1970 153 24.76 18.76 23.11 0.01 663.42 267.67 55409 +1970 154 24.76 18.76 23.11 1.28 663.42 267.9 55492 +1970 155 21.95 15.95 20.3 0.03 569.41 276.64 55572 +1970 156 26.3 20.3 24.65 0 720.29 350.61 55648 +1970 157 27.93 21.93 26.28 0.04 784.93 256.95 55719 +1970 158 25.7 19.7 24.05 0 697.66 353.76 55786 +1970 159 25.37 19.37 23.72 0 685.47 355.51 55849 +1970 160 27.66 21.66 26.01 0 773.9 344.56 55908 +1970 161 31.32 25.32 29.67 0 935.16 323.76 55962 +1970 162 32.14 26.14 30.49 0 974.93 318.56 56011 +1970 163 30.19 24.19 28.54 0 882.61 330.89 56056 +1970 164 30.57 24.57 28.92 0.79 899.99 246.49 56097 +1970 165 29.07 23.07 27.42 0 832.99 337.44 56133 +1970 166 24.37 18.37 22.72 0.11 649.63 270.5 56165 +1970 167 22.26 16.26 20.61 0 579.19 369.23 56192 +1970 168 22.27 16.27 20.62 1.93 579.51 276.95 56214 +1970 169 15.13 9.13 13.48 0 387.01 391.87 56231 +1970 170 15.59 9.59 13.94 0 397.51 390.68 56244 +1970 171 14.57 8.57 12.92 0.46 374.56 295 56252 +1970 172 11.46 5.46 9.81 0.01 311.44 300.25 56256 +1970 173 15.18 9.18 13.53 0 388.14 391.78 56255 +1970 174 13.46 7.46 11.81 0 350.88 395.88 56249 +1970 175 13.42 7.42 11.77 0.18 350.05 296.95 56238 +1970 176 17.12 11.12 15.47 0 434.17 386.36 56223 +1970 177 17.85 11.85 16.2 0 452.65 384.12 56203 +1970 178 15.03 9.03 13.38 0.05 384.76 293.94 56179 +1970 179 20.09 14.09 18.44 0 513.62 376.88 56150 +1970 180 21.22 15.22 19.57 0.04 546.93 279.6 56116 +1970 181 21.5 15.5 19.85 0 555.46 371.7 56078 +1970 182 24.54 18.54 22.89 0 655.61 359.35 56035 +1970 183 25.65 19.65 24 0 695.8 354.19 55987 +1970 184 21.58 15.58 19.93 0.68 557.92 278.2 55935 +1970 185 18.34 12.34 16.69 0 465.43 381.79 55879 +1970 186 18.09 12.09 16.44 0.1 458.88 286.72 55818 +1970 187 16.39 10.39 14.74 0 416.33 387 55753 +1970 188 18.19 12.19 16.54 0.28 461.49 286.15 55684 +1970 189 23.37 17.37 21.72 0 615.39 363.02 55611 +1970 190 21.85 15.85 20.2 0 566.28 368.6 55533 +1970 191 26.09 20.09 24.44 0.01 712.3 262.83 55451 +1970 192 25.38 19.38 23.73 0.16 685.84 265.09 55366 +1970 193 21.84 15.84 20.19 0.11 565.97 275.85 55276 +1970 194 18.34 12.34 16.69 0 465.43 379.43 55182 +1970 195 20.49 14.49 18.84 0 525.2 372.16 55085 +1970 196 23.93 17.93 22.28 0.08 634.38 268.98 54984 +1970 197 25.49 19.49 23.84 0.01 689.89 263.54 54879 +1970 198 24.32 18.32 22.67 0.73 647.88 267.1 54770 +1970 199 23.43 17.43 21.78 0 617.4 359.5 54658 +1970 200 26.71 20.71 25.06 0.73 736.11 258.39 54542 +1970 201 23.36 17.36 21.71 0.65 615.06 269.2 54423 +1970 202 21.87 15.87 20.22 0.5 566.91 273.12 54301 +1970 203 20.04 14.04 18.39 1.81 512.18 277.58 54176 +1970 204 18.6 12.6 16.95 0.45 472.34 280.67 54047 +1970 205 17.95 11.95 16.3 0.05 455.24 281.74 53915 +1970 206 16.53 10.53 14.88 0.01 419.7 284.34 53780 +1970 207 18.28 12.28 16.63 0 463.85 373.44 53643 +1970 208 20.54 14.54 18.89 0.14 526.67 274.14 53502 +1970 209 20.98 14.98 19.33 0 539.7 363.34 53359 +1970 210 25 19 23.35 0.13 672.02 260.21 53213 +1970 211 28.21 22.21 26.56 0.99 796.51 248.16 53064 +1970 212 30.5 24.5 28.85 0.22 896.77 238.14 52913 +1970 213 26.56 20.56 24.91 1.38 730.29 253.21 52760 +1970 214 27.06 21.06 25.41 0.67 749.85 250.88 52604 +1970 215 23.81 17.81 22.16 1.4 630.27 261.25 52445 +1970 216 23.79 17.79 22.14 0.04 629.58 260.57 52285 +1970 217 24.22 18.22 22.57 0.15 644.4 258.6 52122 +1970 218 22.87 16.87 21.22 0.07 598.86 262.05 51958 +1970 219 23.72 17.72 22.07 1.12 627.2 258.78 51791 +1970 220 22.59 16.59 20.94 0 589.76 348.51 51622 +1970 221 18.89 12.89 17.24 0 480.14 360.07 51451 +1970 222 16.36 10.36 14.71 0.23 415.61 274.63 51279 +1970 223 18.29 12.29 16.64 0.24 464.12 269.74 51105 +1970 224 19.49 13.49 17.84 0.57 496.64 266.22 50929 +1970 225 20.97 14.97 19.32 1.31 539.4 261.74 50751 +1970 226 17.14 11.14 15.49 0.08 434.67 269.63 50572 +1970 227 18.11 12.11 16.46 0.3 459.4 266.63 50392 +1970 228 20.38 14.38 18.73 0.31 522 260.5 50210 +1970 229 24.5 18.5 22.85 0.11 654.2 248.28 50026 +1970 230 23.5 17.5 21.85 1.09 619.76 250.34 49842 +1970 231 28.13 22.13 26.48 0.76 793.19 234.05 49656 +1970 232 24.86 18.86 23.21 0.05 666.99 244.22 49469 +1970 233 26.91 20.91 25.26 0 743.94 315.32 49280 +1970 234 24.95 18.95 23.3 0.55 670.22 241.9 49091 +1970 235 23.27 17.27 21.62 0.1 612.06 245.79 48900 +1970 236 22.57 16.57 20.92 0 589.12 328.9 48709 +1970 237 20 14 18.35 0 511.04 335.88 48516 +1970 238 21.28 15.28 19.63 0 548.75 330.11 48323 +1970 239 18.35 12.35 16.7 0 465.7 337.56 48128 +1970 240 18.85 12.85 17.2 0.05 479.06 250.79 47933 +1970 241 19.15 13.15 17.5 0.38 487.23 248.85 47737 +1970 242 19.9 13.9 18.25 0.74 508.19 245.88 47541 +1970 243 24.15 18.15 22.5 0.38 641.97 233.64 47343 +1970 244 19.85 13.85 18.2 0.05 506.77 243.25 47145 +1970 245 17.34 11.34 15.69 0 439.67 329.47 46947 +1970 246 15.31 9.31 13.66 0 391.09 332.41 46747 +1970 247 15.41 9.41 13.76 0 393.37 330.29 46547 +1970 248 16.96 10.96 15.31 0.26 430.2 243.48 46347 +1970 249 16.98 10.98 15.33 0.15 430.7 241.88 46146 +1970 250 17.39 11.39 15.74 0 440.93 319.53 45945 +1970 251 20.79 14.79 19.14 0.18 534.04 230.98 45743 +1970 252 16.89 10.89 15.24 0.17 428.48 237.36 45541 +1970 253 12.16 6.16 10.51 0 324.79 324.32 45339 +1970 254 12.78 6.78 11.13 0 337.02 320.98 45136 +1970 255 11.74 5.74 10.09 0 316.72 320.56 44933 +1970 256 11.19 5.19 9.54 0 306.42 319.18 44730 +1970 257 13.2 7.2 11.55 0 345.53 313.36 44527 +1970 258 15.33 9.33 13.68 0 391.55 306.68 44323 +1970 259 18.97 12.97 17.32 1.04 482.32 221.68 44119 +1970 260 21.99 15.99 20.34 0 570.66 284.59 43915 +1970 261 20.81 14.81 19.16 0.33 534.64 214.32 43711 +1970 262 22.93 16.93 21.28 0.08 600.82 207.74 43507 +1970 263 21.19 15.19 19.54 0 546.02 279.97 43303 +1970 264 18.27 12.27 16.62 0 463.59 285.29 43099 +1970 265 19.49 13.49 17.84 0 496.64 279.87 42894 +1970 266 22.65 16.65 21 0 591.7 268.45 42690 +1970 267 23.41 17.41 21.76 0 616.73 263.5 42486 +1970 268 20.94 14.94 19.29 0 538.51 268.45 42282 +1970 269 23.71 17.71 22.06 0 626.86 257.74 42078 +1970 270 21.45 15.45 19.8 0 553.93 262.06 41875 +1970 271 21.79 15.79 20.14 0 564.42 258.58 41671 +1970 272 17.72 11.72 16.07 0 449.31 266.3 41468 +1970 273 21.71 15.71 20.06 0 561.93 253.79 41265 +1970 274 19.44 13.44 17.79 0.03 495.25 192.88 41062 +1970 275 15.15 9.15 13.5 0 387.46 263.72 40860 +1970 276 16.41 10.41 14.76 0.27 416.81 193.93 40658 +1970 277 13.46 7.46 11.81 0.57 350.88 196.04 40456 +1970 278 12.71 6.71 11.06 0 335.62 259.74 40255 +1970 279 12.09 6.09 10.44 0 323.43 257.88 40054 +1970 280 12.03 6.03 10.38 0 322.28 255.3 39854 +1970 281 9.14 3.14 7.49 0.03 270.51 192.4 39654 +1970 282 8.84 2.84 7.19 0 265.57 254.11 39455 +1970 283 8.02 2.02 6.37 0 252.46 252.2 39256 +1970 284 6.91 0.91 5.26 0 235.6 250.35 39058 +1970 285 8.69 2.69 7.04 0.12 263.12 184.24 38861 +1970 286 10.02 4.02 8.37 0.02 285.45 180.93 38664 +1970 287 15.18 9.18 13.53 0.14 388.14 172.97 38468 +1970 288 14.12 8.12 12.47 0 364.8 229.64 38273 +1970 289 15.42 9.42 13.77 0.18 393.6 168.66 38079 +1970 290 18.77 12.77 17.12 0.35 476.9 161.82 37885 +1970 291 16.58 10.58 14.93 0 420.91 217.38 37693 +1970 292 17.69 11.69 16.04 0 448.55 212.71 37501 +1970 293 16.83 10.83 15.18 0 427.01 211.65 37311 +1970 294 17.11 11.11 15.46 0 433.92 208.33 37121 +1970 295 17.53 11.53 15.88 0 444.47 204.81 36933 +1970 296 16.09 10.09 14.44 0 409.18 204.83 36745 +1970 297 13.5 7.5 11.85 0 351.71 206.16 36560 +1970 298 11.57 5.57 9.92 0.36 313.51 154.62 36375 +1970 299 9.41 3.41 7.76 0.38 275.02 154.42 36191 +1970 300 4.15 -1.85 2.5 1.05 197.81 156.03 36009 +1970 301 5.64 -0.36 3.99 0.45 217.5 153.2 35829 +1970 302 8.95 2.95 7.3 0 267.37 198.55 35650 +1970 303 12.25 6.25 10.6 0 326.54 192.22 35472 +1970 304 7.68 1.68 6.03 0 247.19 194.72 35296 +1970 305 3.37 -2.63 1.72 0.17 188.13 146.58 35122 +1970 306 5.04 -0.96 3.39 0.01 209.38 143.93 34950 +1970 307 8.66 2.66 7.01 0 262.64 186.24 34779 +1970 308 8.47 2.47 6.82 0 259.58 183.82 34610 +1970 309 6.1 0.1 4.45 0 223.91 183.56 34444 +1970 310 7.66 1.66 6.01 0.03 246.88 134.84 34279 +1970 311 9.31 3.31 7.66 0.06 273.34 132.06 34116 +1970 312 10.59 4.59 8.94 0 295.51 172.17 33956 +1970 313 15.2 9.2 13.55 0.67 388.59 123.43 33797 +1970 314 12.59 6.59 10.94 0.41 333.23 124.47 33641 +1970 315 16.74 10.74 15.09 0.82 424.8 118.56 33488 +1970 316 15.78 9.78 14.13 1.44 401.91 118 33337 +1970 317 9.16 3.16 7.51 0.14 270.84 121.99 33188 +1970 318 12.61 6.61 10.96 0.76 333.63 117.64 33042 +1970 319 9.09 3.09 7.44 0.48 269.68 119.03 32899 +1970 320 10.36 4.36 8.71 0.01 291.42 116.76 32758 +1970 321 10.61 4.61 8.96 0 295.87 153.36 32620 +1970 322 8.03 2.03 6.38 0 252.61 153.84 32486 +1970 323 9.85 3.85 8.2 0 282.51 150.68 32354 +1970 324 10.63 4.63 8.98 0.62 296.23 110.95 32225 +1970 325 7.66 1.66 6.01 0 246.88 148.77 32100 +1970 326 7.63 1.63 5.98 0 246.42 147.34 31977 +1970 327 8.25 2.25 6.6 0 256.08 145.02 31858 +1970 328 8.45 2.45 6.8 0 259.26 142.9 31743 +1970 329 8.23 2.23 6.58 0.13 255.76 106.2 31631 +1970 330 11.42 5.42 9.77 0 310.69 137.42 31522 +1970 331 9.91 3.91 8.26 0 283.55 137.49 31417 +1970 332 13.3 7.3 11.65 0 347.58 132.66 31316 +1970 333 12.96 6.96 11.31 0 340.64 131.97 31218 +1970 334 13.52 7.52 11.87 0.07 352.13 97.74 31125 +1970 335 3.04 -2.96 1.39 0.42 184.16 102.92 31035 +1970 336 5.59 -0.41 3.94 0 216.82 134.66 30949 +1970 337 2.74 -3.26 1.09 0 180.61 134.64 30867 +1970 338 -2.94 -8.94 -4.59 0 123.71 136.14 30790 +1970 339 0.48 -5.52 -1.17 0.03 155.73 100.48 30716 +1970 340 -1.2 -7.2 -2.85 0 139.21 133.94 30647 +1970 341 2.81 -3.19 1.16 0 181.43 131.2 30582 +1970 342 4.19 -1.81 2.54 0.23 198.32 97.27 30521 +1970 343 5.52 -0.48 3.87 0.02 215.86 96.07 30465 +1970 344 3.39 -2.61 1.74 0 188.37 128.17 30413 +1970 345 2.88 -3.12 1.23 0.01 182.26 96 30366 +1970 346 1.23 -4.77 -0.42 0.47 163.64 96.18 30323 +1970 347 -2.54 -8.54 -4.19 0.83 127.14 143.09 30284 +1970 348 2.45 -3.55 0.8 0 177.24 172.66 30251 +1970 349 2.28 -3.72 0.63 0 175.29 172.1 30221 +1970 350 1.33 -4.67 -0.32 0 164.72 172.07 30197 +1970 351 4.71 -1.29 3.06 0 205.02 169.53 30177 +1970 352 7.08 1.08 5.43 0 238.11 167.06 30162 +1970 353 8.68 2.68 7.03 0 262.96 121.86 30151 +1970 354 9.54 3.54 7.89 0 277.21 121.19 30145 +1970 355 8.84 2.84 7.19 0 265.57 121.71 30144 +1970 356 6.96 0.96 5.31 0 236.34 123.05 30147 +1970 357 6.52 0.52 4.87 0 229.91 123.39 30156 +1970 358 0.55 -5.45 -1.1 0 156.45 126.63 30169 +1970 359 1.3 -4.7 -0.35 0 164.39 126.42 30186 +1970 360 2.18 -3.82 0.53 0.11 174.15 94.78 30208 +1970 361 -0.84 -6.84 -2.49 0 142.61 128.03 30235 +1970 362 0.81 -5.19 -0.84 0 159.17 127.78 30267 +1970 363 0.3 -5.7 -1.35 0 153.88 128.59 30303 +1970 364 0.96 -5.04 -0.69 0.01 160.75 96.53 30343 +1970 365 0.38 -5.62 -1.27 0.09 154.7 97.15 30388 +1971 1 0.32 -5.68 -1.33 0 154.09 130.46 30438 +1971 2 -1.02 -7.02 -2.67 0 140.9 131.75 30492 +1971 3 1.26 -4.74 -0.39 0 163.96 131.72 30551 +1971 4 -2.09 -8.09 -3.74 0 131.09 134.04 30614 +1971 5 1.51 -4.49 -0.14 0 166.68 133.17 30681 +1971 6 -1.73 -7.73 -3.38 0 134.32 135.46 30752 +1971 7 -4.5 -10.5 -6.15 0.03 111.12 145.84 30828 +1971 8 -4.63 -10.63 -6.28 0 110.12 181.59 30907 +1971 9 -4.01 -10.01 -5.66 0 114.95 182.54 30991 +1971 10 -5.33 -11.33 -6.98 0.01 104.88 148.8 31079 +1971 11 -1.24 -7.24 -2.89 0.12 138.83 148.71 31171 +1971 12 -2.04 -8.04 -3.69 0 131.53 185.21 31266 +1971 13 1.78 -4.22 0.13 0 169.65 184.78 31366 +1971 14 1.45 -4.55 -0.2 0.69 166.02 150.09 31469 +1971 15 -2.73 -8.73 -4.38 0 125.5 189.24 31575 +1971 16 0.39 -5.61 -1.26 0 154.8 189.04 31686 +1971 17 2.08 -3.92 0.43 0 173.01 148.2 31800 +1971 18 -0.39 -6.39 -2.04 0 146.97 151.32 31917 +1971 19 0.24 -5.76 -1.41 0 153.27 152.98 32038 +1971 20 3.21 -2.79 1.56 0 186.2 153 32161 +1971 21 0.28 -5.72 -1.37 0 153.68 156.58 32289 +1971 22 3.93 -2.07 2.28 0 195.04 156.32 32419 +1971 23 5.23 -0.77 3.58 0.01 211.92 117.93 32552 +1971 24 6.66 0.66 5.01 0.22 231.94 118.7 32688 +1971 25 6.15 0.15 4.5 0 224.62 160.52 32827 +1971 26 6.26 0.26 4.61 0 226.18 162.35 32969 +1971 27 4.76 -1.24 3.11 0 205.68 165.44 33114 +1971 28 5.94 -0.06 4.29 1.28 221.67 125.1 33261 +1971 29 4.2 -1.8 2.55 0.03 198.45 127.8 33411 +1971 30 1.87 -4.13 0.22 0.22 170.65 130.59 33564 +1971 31 2.23 -3.77 0.58 0 174.72 176.29 33718 +1971 32 5.93 -0.07 4.28 0 221.53 175.87 33875 +1971 33 8.51 2.51 6.86 0.08 260.22 132.22 34035 +1971 34 6.48 0.48 4.83 0 229.33 180.24 34196 +1971 35 1.37 -4.63 -0.28 0.01 165.15 139.46 34360 +1971 36 0.89 -5.11 -0.76 0 160.01 188.76 34526 +1971 37 1.84 -4.16 0.19 0 170.32 190.64 34694 +1971 38 5.38 -0.62 3.73 0 213.95 190.9 34863 +1971 39 7.97 1.97 6.32 0.26 251.67 143.45 35035 +1971 40 9.64 3.64 7.99 0 278.91 192.18 35208 +1971 41 11.28 5.28 9.63 0.11 308.09 144.69 35383 +1971 42 11 5 9.35 0.07 302.93 146.81 35560 +1971 43 10.93 4.93 9.28 0.02 301.65 148.86 35738 +1971 44 5.23 -0.77 3.58 0 211.92 206.67 35918 +1971 45 5.61 -0.39 3.96 0 217.09 208.97 36099 +1971 46 3.73 -2.27 2.08 0.19 192.55 159.88 36282 +1971 47 7.57 1.57 5.92 0 245.5 212.65 36466 +1971 48 9.39 3.39 7.74 0 274.68 213.51 36652 +1971 49 8.06 2.06 6.41 0.12 253.08 163.27 36838 +1971 50 6.13 0.13 4.48 0.1 224.34 166.67 37026 +1971 51 5.08 -0.92 3.43 0 209.91 226.14 37215 +1971 52 2.64 -3.36 0.99 0 179.44 230.96 37405 +1971 53 1.95 -4.05 0.3 0 171.55 234.45 37596 +1971 54 3.78 -2.22 2.13 0 193.17 235.81 37788 +1971 55 5.39 -0.61 3.74 0.01 214.09 178.06 37981 +1971 56 5.45 -0.55 3.8 0 214.9 240.05 38175 +1971 57 2.7 -3.3 1.05 0.34 180.14 183.98 38370 +1971 58 2.23 -3.77 0.58 0 174.72 248.63 38565 +1971 59 1.98 -4.02 0.33 0 171.89 251.56 38761 +1971 60 1 -5 -0.65 0 161.18 255.21 38958 +1971 61 -1.68 -7.68 -3.33 0 134.77 259.96 39156 +1971 62 1.31 -4.69 -0.34 0 164.5 260.78 39355 +1971 63 2.45 -3.55 0.8 0.04 177.24 197.2 39553 +1971 64 1.73 -4.27 0.08 0 169.1 266.45 39753 +1971 65 -1.26 -7.26 -2.91 0.03 138.65 236.74 39953 +1971 66 -0.87 -6.87 -2.52 0.14 142.33 238.82 40154 +1971 67 0.42 -5.58 -1.23 0 155.11 309.17 40355 +1971 68 3.81 -2.19 2.16 0 193.54 276.21 40556 +1971 69 4.59 -1.41 2.94 0 203.46 278.11 40758 +1971 70 8.07 2.07 6.42 0 253.24 277.12 40960 +1971 71 9.53 3.53 7.88 0 277.05 278.12 41163 +1971 72 8.66 2.66 7.01 0 262.64 282.09 41366 +1971 73 8.01 2.01 6.36 0 252.3 285.59 41569 +1971 74 6.67 0.67 5.02 0.38 232.08 217.47 41772 +1971 75 5.75 -0.25 4.1 1.89 219.02 220.31 41976 +1971 76 4.19 -1.81 2.54 0 198.32 298.06 42179 +1971 77 9.15 3.15 7.5 0.56 270.67 221.07 42383 +1971 78 3.94 -2.06 2.29 0 195.16 303.64 42587 +1971 79 4.96 -1.04 3.31 0.53 208.32 229 42791 +1971 80 5.92 -0.08 4.27 0.16 221.39 230.12 42996 +1971 81 8.46 2.46 6.81 0 259.42 306.21 43200 +1971 82 9.07 3.07 7.42 0.16 269.35 231.01 43404 +1971 83 1.06 -4.94 -0.59 0 161.81 319.53 43608 +1971 84 6.6 0.6 4.95 0 231.07 316.35 43812 +1971 85 7.27 1.27 5.62 0 240.96 318.02 44016 +1971 86 8.2 2.2 6.55 0 255.28 319.19 44220 +1971 87 7.74 1.74 6.09 0 248.11 322.36 44424 +1971 88 10.28 4.28 8.63 0 290 320.97 44627 +1971 89 7.58 1.58 5.93 0.02 245.65 245.43 44831 +1971 90 6.58 0.58 4.93 0 230.78 330.94 45034 +1971 91 14.57 8.57 12.92 0 374.56 319.88 45237 +1971 92 11.59 5.59 9.94 0 313.89 327.87 45439 +1971 93 15.16 9.16 13.51 0 387.69 322.97 45642 +1971 94 15.24 9.24 13.59 0.14 389.5 243.68 45843 +1971 95 18.45 12.45 16.8 0 468.34 319.09 46045 +1971 96 22.33 16.33 20.68 0.01 581.42 231.99 46246 +1971 97 16.91 10.91 15.26 0 428.97 327.12 46446 +1971 98 19.58 13.58 17.93 0.11 499.16 241.34 46647 +1971 99 14.88 8.88 13.23 0 381.41 335.8 46846 +1971 100 12.18 6.18 10.53 0 325.18 343.31 47045 +1971 101 11.36 5.36 9.71 0 309.57 346.77 47243 +1971 102 10.05 4.05 8.4 0 285.98 350.98 47441 +1971 103 12.36 6.36 10.71 0 328.69 348.62 47638 +1971 104 13.2 7.2 11.55 0 345.53 348.76 47834 +1971 105 16.43 10.43 14.78 0.53 417.29 257.37 48030 +1971 106 17.44 11.44 15.79 0.04 442.19 256.62 48225 +1971 107 14.39 8.39 12.74 0 370.63 351.27 48419 +1971 108 15.54 9.54 13.89 0.04 396.35 262.74 48612 +1971 109 16.35 10.35 14.7 0 415.37 349.91 48804 +1971 110 17.47 11.47 15.82 0 442.95 348.35 48995 +1971 111 16.14 10.14 14.49 0 410.37 353.35 49185 +1971 112 15.06 9.06 13.41 0 385.44 357.49 49374 +1971 113 8.52 2.52 6.87 0.95 260.38 278.74 49561 +1971 114 11.32 5.32 9.67 0.55 308.83 276.21 49748 +1971 115 9.12 3.12 7.47 0.52 270.17 280.24 49933 +1971 116 10.22 4.22 8.57 0.81 288.95 279.74 50117 +1971 117 9.83 3.83 8.18 0.03 282.17 281.26 50300 +1971 118 10.32 4.32 8.67 0 290.71 375.47 50481 +1971 119 12.03 6.03 10.38 0 322.28 373.41 50661 +1971 120 7.26 1.26 5.61 0 240.81 382.94 50840 +1971 121 16.82 10.82 15.17 0 426.76 364.5 51016 +1971 122 14.7 8.7 13.05 0 377.42 371.06 51191 +1971 123 13.58 7.58 11.93 0 353.38 374.68 51365 +1971 124 14.45 8.45 12.8 0 371.94 373.77 51536 +1971 125 16.37 10.37 14.72 0 415.85 369.95 51706 +1971 126 13.21 7.21 11.56 0 345.73 378.58 51874 +1971 127 19.45 13.45 17.8 0 495.53 362.85 52039 +1971 128 19.81 13.81 18.16 0 505.63 362.67 52203 +1971 129 19.45 13.45 17.8 0.13 495.53 273.49 52365 +1971 130 21.28 15.28 19.63 0 548.75 359.27 52524 +1971 131 23.94 17.94 22.29 0.41 634.72 262.39 52681 +1971 132 23.75 17.75 22.1 0.08 628.22 263.56 52836 +1971 133 22.64 16.64 20.99 0 591.38 356.48 52989 +1971 134 21 15 19.35 0 540.3 363.19 53138 +1971 135 22.21 16.21 20.56 0 577.6 359.47 53286 +1971 136 23.55 17.55 21.9 0.03 621.44 266.13 53430 +1971 137 20.91 14.91 19.26 0.44 537.61 274.12 53572 +1971 138 15.65 9.65 14 0 398.89 382.02 53711 +1971 139 17.31 11.31 15.66 0 438.92 378.19 53848 +1971 140 18.54 12.54 16.89 0 470.74 375.02 53981 +1971 141 21.57 15.57 19.92 0 557.61 365.28 54111 +1971 142 20.17 14.17 18.52 0 515.92 370.69 54238 +1971 143 18.09 12.09 16.44 0 458.88 377.85 54362 +1971 144 19.27 13.27 17.62 0.72 490.54 280.99 54483 +1971 145 20.35 14.35 18.7 0.45 521.12 278.65 54600 +1971 146 21.68 15.68 20.03 0.74 561.01 275.37 54714 +1971 147 21.05 15.05 19.4 0 541.8 369.92 54824 +1971 148 18.53 12.53 16.88 0 470.47 378.68 54931 +1971 149 18.75 12.75 17.1 0.04 476.36 283.73 55034 +1971 150 17.58 11.58 15.93 0.02 445.74 286.64 55134 +1971 151 18.69 12.69 17.04 0 474.75 379.22 55229 +1971 152 20.72 14.72 19.07 0.37 531.97 279.44 55321 +1971 153 21.78 15.78 20.13 0.59 564.11 276.74 55409 +1971 154 23.48 17.48 21.83 0.93 619.08 271.98 55492 +1971 155 19.32 13.32 17.67 0 491.92 378.06 55572 +1971 156 16.58 10.58 14.93 0.14 420.91 289.97 55648 +1971 157 19.39 13.39 17.74 1.59 493.86 283.74 55719 +1971 158 19.14 13.14 17.49 2.31 486.96 284.48 55786 +1971 159 19.14 13.14 17.49 0.42 486.96 284.66 55849 +1971 160 19.32 13.32 17.67 0.3 491.92 284.36 55908 +1971 161 18.16 12.16 16.51 0.02 460.7 287.15 55962 +1971 162 17.17 11.17 15.52 0 435.41 385.86 56011 +1971 163 22.03 16.03 20.38 0 571.92 369.95 56056 +1971 164 20.93 14.93 19.28 0 538.21 374.04 56097 +1971 165 21.5 15.5 19.85 0 555.46 372.07 56133 +1971 166 21.32 15.32 19.67 0 549.96 372.81 56165 +1971 167 21.36 15.36 19.71 0 551.18 372.61 56192 +1971 168 20.98 14.98 19.33 0.04 539.7 280.55 56214 +1971 169 17.43 11.43 15.78 0 441.94 385.58 56231 +1971 170 19.21 13.21 17.56 0.41 488.88 285.08 56244 +1971 171 19.68 13.68 18.03 0.01 501.96 283.97 56252 +1971 172 19.2 13.2 17.55 0.18 488.61 285.14 56256 +1971 173 14.38 8.38 12.73 0 370.41 393.78 56255 +1971 174 19.87 13.87 18.22 0 507.33 377.88 56249 +1971 175 19.54 13.54 17.89 0 498.04 378.95 56238 +1971 176 21.76 15.76 20.11 0.24 563.48 278.33 56223 +1971 177 21.79 15.79 20.14 0 564.42 370.89 56203 +1971 178 19.69 13.69 18.04 0.57 502.24 283.75 56179 +1971 179 19.23 13.23 17.58 0 489.43 379.74 56150 +1971 180 20.18 14.18 18.53 0 516.2 376.46 56116 +1971 181 21.9 15.9 20.25 0 567.85 370.21 56078 +1971 182 23.93 17.93 22.28 0.18 634.38 271.48 56035 +1971 183 26.69 20.69 25.04 0 735.33 349.24 55987 +1971 184 21.88 15.88 20.23 0 567.22 369.81 55935 +1971 185 21.68 15.68 20.03 0.09 561.01 277.86 55879 +1971 186 21.04 15.04 19.39 0 541.5 372.56 55818 +1971 187 19.65 13.65 18 0 501.12 377.16 55753 +1971 188 21.95 15.95 20.3 0 569.41 368.77 55684 +1971 189 23.02 17.02 21.37 0 603.78 364.43 55611 +1971 190 23.6 17.6 21.95 0.14 623.13 271.28 55533 +1971 191 24.53 18.53 22.88 0 655.26 357.52 55451 +1971 192 20.8 14.8 19.15 0 534.34 371.85 55366 +1971 193 20.36 14.36 18.71 0.12 521.41 279.83 55276 +1971 194 17.18 11.18 15.53 0 435.66 382.86 55182 +1971 195 18.53 12.53 16.88 0.05 470.47 283.93 55085 +1971 196 18.39 12.39 16.74 0.07 466.76 283.94 54984 +1971 197 22.27 16.27 20.62 0 579.51 364.83 54879 +1971 198 25.79 19.79 24.14 2.01 701.02 262.2 54770 +1971 199 27.89 21.89 26.24 0.96 783.29 254.23 54658 +1971 200 24.88 18.88 23.23 0.14 667.71 264.74 54542 +1971 201 24.72 18.72 23.07 0.21 661.99 264.92 54423 +1971 202 25.79 19.79 24.14 0 701.02 347.89 54301 +1971 203 21.97 15.97 20.32 0.29 570.04 272.46 54176 +1971 204 24.66 18.66 23.01 0.73 659.86 263.97 54047 +1971 205 25.37 19.37 23.72 0.19 685.47 261.25 53915 +1971 206 24.94 18.94 23.29 0.9 669.86 262.28 53780 +1971 207 26.02 20.02 24.37 0.16 709.66 258.15 53643 +1971 208 27.39 21.39 25.74 0.14 763 252.73 53502 +1971 209 27 21 25.35 0.17 747.48 253.72 53359 +1971 210 25.2 19.2 23.55 0.97 679.27 259.55 53213 +1971 211 24.5 18.5 22.85 0 654.2 348.35 53064 +1971 212 24.55 18.55 22.9 0.11 655.97 260.53 52913 +1971 213 24.44 18.44 22.79 0 652.09 347.11 52760 +1971 214 26.98 20.98 25.33 0 746.69 334.9 52604 +1971 215 26.24 20.24 24.59 0.01 718 253.33 52445 +1971 216 20.9 14.9 19.25 0.27 537.31 268.69 52285 +1971 217 24.52 18.52 22.87 0.73 654.91 257.66 52122 +1971 218 20.37 14.37 18.72 0.7 521.7 268.76 51958 +1971 219 18.67 12.67 17.02 0.21 474.21 272.02 51791 +1971 220 19.94 13.94 18.29 0 509.33 357.78 51622 +1971 221 22.09 16.09 20.44 0.07 573.81 262.04 51451 +1971 222 24.32 18.32 22.67 0 647.88 339.7 51279 +1971 223 23.39 17.39 21.74 0 616.06 342.33 51105 +1971 224 24.71 18.71 23.06 0 661.64 335.96 50929 +1971 225 24.5 18.5 22.85 0.11 654.2 251.8 50751 +1971 226 26.45 20.45 24.8 0.04 726.05 244.61 50572 +1971 227 24.71 18.71 23.06 0.08 661.64 249.4 50392 +1971 228 26.3 20.3 24.65 0.13 720.29 243.35 50210 +1971 229 21.99 15.99 20.34 0.57 570.66 255.47 50026 +1971 230 23.53 17.53 21.88 0 620.77 333.67 49842 +1971 231 24.05 18.05 22.4 0 638.51 330.2 49656 +1971 232 26.62 20.62 24.97 0 732.62 317.98 49469 +1971 233 29.83 23.83 28.18 0 866.39 300.76 49280 +1971 234 27.73 21.73 26.08 0 776.75 310.14 49091 +1971 235 23.69 17.69 22.04 0.44 626.18 244.59 48900 +1971 236 22.85 16.85 21.2 0 598.2 327.89 48709 +1971 237 25.72 19.72 24.07 0 698.41 314.96 48516 +1971 238 25.29 19.29 23.64 0 682.55 315.18 48323 +1971 239 24.66 18.66 23.01 0 659.86 316.31 48128 +1971 240 21.11 15.11 19.46 0.56 543.61 245.59 47933 +1971 241 21.87 15.87 20.22 0.27 566.91 242.43 47737 +1971 242 19.24 13.24 17.59 0 489.71 329.8 47541 +1971 243 21.17 15.17 19.52 0 545.42 322.03 47343 +1971 244 13.69 7.69 12.04 0 355.68 339.83 47145 +1971 245 14.49 8.49 12.84 0 372.81 336.23 46947 +1971 246 19.18 13.18 17.53 0 488.06 322.52 46747 +1971 247 24.26 18.26 22.61 0.3 645.79 227.97 46547 +1971 248 21.05 15.05 19.4 0 541.8 313.17 46347 +1971 249 16.39 10.39 14.74 0 416.33 323.95 46146 +1971 250 14.93 8.93 13.28 0 382.52 325.31 45945 +1971 251 17.01 11.01 15.36 0.2 431.44 238.77 45743 +1971 252 20.7 14.7 19.05 0 531.38 306.13 45541 +1971 253 21.9 15.9 20.25 0.08 567.85 225.24 45339 +1971 254 19.84 13.84 18.19 0.36 506.48 228.36 45136 +1971 255 20.86 14.86 19.21 0.29 536.12 224.46 44933 +1971 256 21.43 15.43 19.78 0 553.32 295.34 44730 +1971 257 16.13 10.13 14.48 0.67 410.13 230.46 44527 +1971 258 13.25 7.25 11.6 0 346.55 310.87 44323 +1971 259 14.56 8.56 12.91 0 374.34 305.83 44119 +1971 260 16.94 10.94 15.29 0.22 429.71 223.69 43915 +1971 261 16.71 10.71 15.06 0 424.07 296.34 43711 +1971 262 13.85 7.85 12.2 0 359.05 299.94 43507 +1971 263 10.12 4.12 8.47 0 287.2 303.81 43303 +1971 264 12.69 6.69 11.04 0 335.22 296.97 43099 +1971 265 15.77 9.77 14.12 0 401.68 288.63 42894 +1971 266 17.09 11.09 15.44 1.01 433.42 212.46 42690 +1971 267 15.71 9.71 14.06 0.04 400.28 212.7 42486 +1971 268 11.62 5.62 9.97 0.83 314.45 216.38 42282 +1971 269 11.88 5.88 10.23 0 319.39 285.52 42078 +1971 270 14.01 8.01 12.36 0.49 362.45 209.38 41875 +1971 271 15.08 9.08 13.43 0.27 385.89 205.9 41671 +1971 272 16.5 10.5 14.85 0 418.98 268.95 41468 +1971 273 17.87 11.87 16.22 0 453.17 263.47 41265 +1971 274 16.17 10.17 14.52 0 411.08 264.47 41062 +1971 275 14.63 8.63 12.98 0 375.88 264.69 40860 +1971 276 16.81 10.81 15.16 0 426.52 257.76 40658 +1971 277 14.3 8.3 12.65 0.02 368.68 194.95 40456 +1971 278 15.05 9.05 13.4 0.01 385.21 191.79 40255 +1971 279 13.93 7.93 12.28 0 360.75 254.91 40054 +1971 280 12.06 6.06 10.41 0.1 322.85 191.44 39854 +1971 281 11.87 5.87 10.22 0.71 319.2 189.6 39654 +1971 282 8.69 2.69 7.04 0 263.12 254.29 39455 +1971 283 6.66 0.66 5.01 0 231.94 253.7 39256 +1971 284 9.26 3.26 7.61 0 272.5 247.66 39058 +1971 285 9.65 3.65 8 0 279.08 244.49 38861 +1971 286 10.89 4.89 9.24 0 300.92 240.1 38664 +1971 287 14.69 8.69 13.04 0 377.2 231.46 38468 +1971 288 11.77 5.77 10.12 0 317.3 233.15 38273 +1971 289 14.22 8.22 12.57 0 366.95 226.87 38079 +1971 290 13.48 7.48 11.83 0 351.3 225.18 37885 +1971 291 12.76 6.76 11.11 0 336.62 223.56 37693 +1971 292 14.01 8.01 12.36 0 362.45 219.03 37501 +1971 293 11 5 9.35 0 302.93 220.52 37311 +1971 294 11.83 5.83 10.18 0.08 318.44 162.41 37121 +1971 295 12.63 6.63 10.98 0 334.03 212.65 36933 +1971 296 12.23 6.23 10.58 0 326.15 210.61 36745 +1971 297 12.85 6.85 11.2 0 338.42 207.07 36560 +1971 298 10.87 4.87 9.22 0 300.56 207.01 36375 +1971 299 16.45 10.45 14.8 0.21 417.77 147.24 36191 +1971 300 17 11 15.35 0.72 431.19 144.6 36009 +1971 301 14.13 8.13 12.48 0 365.02 194.83 35829 +1971 302 14.22 8.22 12.57 0.09 366.95 144.1 35650 +1971 303 14.89 8.89 13.24 0 381.63 188.64 35472 +1971 304 10.03 4.03 8.38 0 285.63 192.35 35296 +1971 305 3.29 -2.71 1.64 0 187.16 195.49 35122 +1971 306 3.93 -2.07 2.28 0.68 195.04 144.55 34950 +1971 307 7.26 1.26 5.61 0 240.81 187.54 34779 +1971 308 6.46 0.46 4.81 0.03 229.04 139.2 34610 +1971 309 1.2 -4.8 -0.45 0.04 163.31 140.2 34444 +1971 310 6.19 0.19 4.54 0 225.19 181.02 34279 +1971 311 9.57 3.57 7.92 0 277.72 175.83 34116 +1971 312 9.15 3.15 7.5 0 270.67 173.6 33956 +1971 313 13.08 7.08 11.43 0.36 343.08 125.47 33797 +1971 314 10.15 4.15 8.5 0 287.72 168.58 33641 +1971 315 8.17 2.17 6.52 0.03 254.81 125.92 33488 +1971 316 8.39 2.39 6.74 0 258.3 165.53 33337 +1971 317 5.19 -0.81 3.54 0.13 211.39 124.39 33188 +1971 318 5.32 -0.68 3.67 0 213.14 163.41 33042 +1971 319 7.1 1.1 5.45 0.32 238.41 120.28 32899 +1971 320 10.31 4.31 8.66 0.43 290.53 116.8 32758 +1971 321 7.14 1.14 5.49 0 239.01 156.37 32620 +1971 322 6.26 0.26 4.61 0.19 226.18 116.4 32486 +1971 323 5.23 -0.77 3.58 0 211.92 154.3 32354 +1971 324 7.14 1.14 5.49 0.08 239.01 113.16 32225 +1971 325 10.7 4.7 9.05 0.05 297.48 109.63 32100 +1971 326 10.01 4.01 8.36 0 285.28 145.37 31977 +1971 327 9.27 3.27 7.62 0.02 272.67 108.14 31858 +1971 328 8.87 2.87 7.22 1.77 266.06 106.92 31743 +1971 329 9.36 3.36 7.71 0.36 274.18 105.51 31631 +1971 330 4.59 -1.41 2.94 0 203.46 142.68 31522 +1971 331 2.13 -3.87 0.48 0 173.58 142.75 31417 +1971 332 7.01 1.01 5.36 0 237.08 138.13 31316 +1971 333 9.04 3.04 7.39 0 268.85 135.52 31218 +1971 334 10.06 4.06 8.41 0 286.15 133.6 31125 +1971 335 7.52 1.52 5.87 0 244.74 134.43 31035 +1971 336 7.53 1.53 5.88 0.01 244.89 100.02 30949 +1971 337 9.93 3.93 8.28 0 283.89 129.86 30867 +1971 338 11.82 5.82 10.17 0 318.25 127.28 30790 +1971 339 13.8 7.8 12.15 0 357.99 124.58 30716 +1971 340 7.95 1.95 6.3 0 251.36 128.96 30647 +1971 341 5.82 -0.18 4.17 0 219.99 129.48 30582 +1971 342 4.8 -1.2 3.15 0.41 206.2 97.01 30521 +1971 343 7.06 1.06 5.41 0.09 237.82 95.33 30465 +1971 344 7.09 1.09 5.44 0 238.26 125.96 30413 +1971 345 3.8 -2.2 2.15 0.71 193.42 95.64 30366 +1971 346 10.53 4.53 8.88 0 294.44 122.42 30323 +1971 347 9.34 3.34 7.69 0 273.84 122.78 30284 +1971 348 4.52 -1.48 2.87 0 202.55 125.63 30251 +1971 349 6.23 0.23 4.58 0 225.75 124.23 30221 +1971 350 1.59 -4.41 -0.06 0.61 167.55 94.81 30197 +1971 351 3.42 -2.58 1.77 0.07 188.74 93.97 30177 +1971 352 2.85 -3.15 1.2 0.14 181.9 94.11 30162 +1971 353 -3.68 -9.68 -5.33 0 117.59 128.07 30151 +1971 354 -2.27 -8.27 -3.92 0 129.49 127.56 30145 +1971 355 -1.16 -7.16 -2.81 0 139.58 127.15 30144 +1971 356 -1.85 -7.85 -3.5 0.52 133.23 141.02 30147 +1971 357 -1.36 -7.36 -3.01 0 137.72 172.74 30156 +1971 358 1.68 -4.32 0.03 0 168.54 171.31 30169 +1971 359 5.43 -0.57 3.78 0 214.63 168.7 30186 +1971 360 7.19 1.19 5.54 0.25 239.76 92.64 30208 +1971 361 5.89 -0.11 4.24 0.3 220.97 93.51 30235 +1971 362 2.01 -3.99 0.36 0.49 172.22 95.42 30267 +1971 363 4 -2 2.35 0.03 195.92 95.1 30303 +1971 364 2.27 -3.73 0.62 0.31 175.17 96.07 30343 +1971 365 1.65 -4.35 0 0 168.21 128.96 30388 +1972 1 -2.3 -8.3 -3.95 0.02 129.23 142.05 30438 +1972 2 -1.85 -7.85 -3.5 0.06 133.23 142.59 30492 +1972 3 -3.55 -9.55 -5.2 0 118.65 177.08 30551 +1972 4 -3.35 -9.35 -5 0 120.29 177.85 30614 +1972 5 -4.69 -10.69 -6.34 0 109.66 178.85 30681 +1972 6 -4.57 -10.57 -6.22 0 110.58 179.62 30752 +1972 7 -5.47 -11.47 -7.12 0.02 103.86 146.28 30828 +1972 8 -3.35 -9.35 -5 0 120.29 181.38 30907 +1972 9 -2.6 -8.6 -4.25 0.4 126.62 148.67 30991 +1972 10 -2.24 -8.24 -3.89 0.31 129.76 150.39 31079 +1972 11 -3.03 -9.03 -4.68 0.47 122.96 152.67 31171 +1972 12 0.65 -5.35 -1 0 157.49 187.42 31266 +1972 13 -0.6 -6.6 -2.25 0 144.92 189.47 31366 +1972 14 -2.71 -8.71 -4.36 0 125.67 191.66 31469 +1972 15 -1.15 -7.15 -2.8 0.31 139.68 156.61 31575 +1972 16 0.39 -5.61 -1.26 0.01 154.8 156.86 31686 +1972 17 2.46 -3.54 0.81 0 177.35 193.86 31800 +1972 18 -0.42 -6.42 -2.07 0 146.68 197.03 31917 +1972 19 -0.73 -6.73 -2.38 0.23 143.67 161.28 32038 +1972 20 0.83 -5.17 -0.82 0.18 159.38 161.65 32161 +1972 21 3.11 -2.89 1.46 0.1 184.99 161.66 32289 +1972 22 4.34 -1.66 2.69 0 200.23 200.7 32419 +1972 23 6.26 0.26 4.61 0 226.18 200.19 32552 +1972 24 7.34 1.34 5.69 0 242.01 200.34 32688 +1972 25 7.97 1.97 6.32 0 251.67 200.53 32827 +1972 26 1.59 -4.41 -0.06 1.98 167.55 165.09 32969 +1972 27 0.47 -5.53 -1.18 0.54 155.63 166.83 33114 +1972 28 1.82 -4.18 0.17 0 170.1 209.92 33261 +1972 29 4.39 -1.61 2.74 0.04 200.88 167.42 33411 +1972 30 7.05 1.05 5.4 0.03 237.67 127.89 33564 +1972 31 5.97 -0.03 4.32 0 222.09 173.73 33718 +1972 32 10.91 4.91 9.26 0 301.29 171.33 33875 +1972 33 11.94 5.94 10.29 0 320.54 172.77 34035 +1972 34 10.65 4.65 9 0 296.59 176.34 34196 +1972 35 6.55 0.55 4.9 0.1 230.34 136.73 34360 +1972 36 6.4 0.4 4.75 0 228.18 184.93 34526 +1972 37 4.83 -1.17 3.18 0.16 206.6 141.44 34694 +1972 38 2.96 -3.04 1.31 0 183.21 192.67 34863 +1972 39 3.98 -2.02 2.33 0.24 195.67 145.93 35035 +1972 40 1.2 -4.8 -0.45 0.77 163.31 149.29 35208 +1972 41 2.67 -3.33 1.02 0.14 179.79 150.56 35383 +1972 42 7.04 1.04 5.39 0.98 237.52 149.88 35560 +1972 43 4.28 -1.72 2.63 0.49 199.47 153.64 35738 +1972 44 4.29 -1.71 2.64 0.39 199.59 155.57 35918 +1972 45 6.83 0.83 5.18 0.04 234.42 155.91 36099 +1972 46 4.19 -1.81 2.54 0 198.32 212.82 36282 +1972 47 4.15 -1.85 2.5 0.01 197.81 161.76 36466 +1972 48 5.69 -0.31 4.04 0.9 218.19 162.9 36652 +1972 49 2.27 -3.73 0.62 0 175.17 222.7 36838 +1972 50 3.37 -2.63 1.72 0 188.13 224.57 37026 +1972 51 7.79 1.79 6.14 0.14 248.88 167.67 37215 +1972 52 7.36 1.36 5.71 0.88 242.31 170.11 37405 +1972 53 4.72 -1.28 3.07 0 205.16 232.25 37596 +1972 54 4.77 -1.23 3.12 0.02 205.81 176.23 37788 +1972 55 5.23 -0.77 3.58 0.1 211.92 178.17 37981 +1972 56 7.76 1.76 6.11 0 248.42 237.73 38175 +1972 57 6.92 0.92 5.27 0.08 235.74 181.12 38370 +1972 58 5.45 -0.55 3.8 0.62 214.9 184.41 38565 +1972 59 4.47 -1.53 2.82 0.02 201.91 187.12 38761 +1972 60 8.78 2.78 7.13 0 264.59 247.89 38958 +1972 61 8.69 2.69 7.04 0 263.12 250.91 39156 +1972 62 12.51 6.51 10.86 0.19 331.65 186.36 39355 +1972 63 6.97 0.97 5.32 0.07 236.48 193.99 39553 +1972 64 6.43 0.43 4.78 0 228.61 262.14 39753 +1972 65 11.01 5.01 9.36 0.2 303.11 194.5 39953 +1972 66 13.27 7.27 11.62 1.32 346.96 193.91 40154 +1972 67 7.61 1.61 5.96 0 246.11 269.35 40355 +1972 68 9.94 3.94 8.29 0.44 284.07 201.94 40556 +1972 69 14.09 8.09 12.44 0 364.16 265.32 40758 +1972 70 16.16 10.16 14.51 0 410.84 264.14 40960 +1972 71 13.82 7.82 12.17 0 358.42 271.41 41163 +1972 72 12.94 6.94 11.29 0 340.24 275.7 41366 +1972 73 13.55 7.55 11.9 0 352.75 277.25 41569 +1972 74 13.68 7.68 12.03 0 355.47 279.7 41772 +1972 75 14.93 8.93 13.28 0 382.52 280.02 41976 +1972 76 12.61 6.61 10.96 0.01 333.63 215.13 42179 +1972 77 12.64 6.64 10.99 0 334.22 289.34 42383 +1972 78 10.42 4.42 8.77 0 292.48 295.57 42587 +1972 79 6.78 0.78 5.13 0 233.69 303.25 42791 +1972 80 4.72 -1.28 3.07 0 205.16 308.16 42996 +1972 81 8.58 2.58 6.93 0.44 261.35 229.54 43200 +1972 82 8.82 2.82 7.17 0.1 265.24 231.28 43404 +1972 83 6.62 0.62 4.97 0 231.36 313.77 43608 +1972 84 9 3 7.35 0 268.19 313.14 43812 +1972 85 9.58 3.58 7.93 0.01 277.89 236.08 44016 +1972 86 13.46 7.46 11.81 0.23 350.88 232.91 44220 +1972 87 8.76 2.76 7.11 0 264.26 320.93 44424 +1972 88 8.46 2.46 6.81 0 259.42 323.72 44627 +1972 89 11.77 5.77 10.12 0 317.3 320.73 44831 +1972 90 12.64 6.64 10.99 0 334.22 321.5 45034 +1972 91 18.51 12.51 16.86 0 469.94 310.52 45237 +1972 92 17.18 11.18 15.53 0 435.66 316.09 45439 +1972 93 16.77 10.77 15.12 0 425.54 319.24 45642 +1972 94 14.05 8.05 12.4 0 363.3 327.47 45843 +1972 95 17.57 11.57 15.92 0 445.49 321.41 46045 +1972 96 17.46 11.46 15.81 0 442.7 323.74 46246 +1972 97 13.16 7.16 11.51 0.01 344.71 251.63 46446 +1972 98 14.39 8.39 12.74 0.03 370.63 251.17 46647 +1972 99 13.26 7.26 11.61 0.34 346.76 254.44 46846 +1972 100 8.64 2.64 6.99 0.2 262.32 262.03 47045 +1972 101 11.15 5.15 9.5 0.05 305.68 260.36 47243 +1972 102 11.29 5.29 9.64 0.22 308.27 261.6 47441 +1972 103 10.77 4.77 9.12 0.4 298.75 263.69 47638 +1972 104 11.14 5.14 9.49 0 305.5 352.75 47834 +1972 105 13.07 7.07 11.42 0 342.87 350.81 48030 +1972 106 11.29 5.29 9.64 0.7 308.27 266.94 48225 +1972 107 8.67 2.67 7.02 0 262.8 362.1 48419 +1972 108 9.42 3.42 7.77 0.53 275.19 271.98 48612 +1972 109 12.64 6.64 10.99 0.83 334.22 268.76 48804 +1972 110 10.42 4.42 8.77 3.13 292.48 272.99 48995 +1972 111 8.39 2.39 6.74 0.06 258.3 276.71 49185 +1972 112 11.81 5.81 10.16 0 318.06 364.49 49374 +1972 113 6.84 0.84 5.19 0.14 234.57 280.65 49561 +1972 114 9.68 3.68 8.03 0 279.6 371.25 49748 +1972 115 11.12 5.12 9.47 0.01 305.13 277.58 49933 +1972 116 14.58 8.58 12.93 0.13 374.78 273.04 50117 +1972 117 15.01 9.01 13.36 0 384.31 364.34 50300 +1972 118 14.96 8.96 13.31 0.04 383.2 274.33 50481 +1972 119 18.35 12.35 16.7 0.07 465.7 268.45 50661 +1972 120 15.05 9.05 13.4 0.04 385.21 275.93 50840 +1972 121 21.15 15.15 19.5 1.27 544.81 263.43 51016 +1972 122 18.73 12.73 17.08 0.55 475.82 270.17 51191 +1972 123 15.33 9.33 13.68 0.27 391.55 277.92 51365 +1972 124 17.88 11.88 16.23 0.48 453.43 273.6 51536 +1972 125 20.1 14.1 18.45 0 513.9 358.92 51706 +1972 126 18.69 12.69 17.04 0.03 474.75 273.26 51874 +1972 127 18.63 12.63 16.98 0 473.14 365.4 52039 +1972 128 19.03 13.03 17.38 0 483.95 365.15 52203 +1972 129 15.89 9.89 14.24 0.47 404.48 281.19 52365 +1972 130 14.38 8.38 12.73 0.41 370.41 284.6 52524 +1972 131 17.44 11.44 15.79 0.59 442.19 279.21 52681 +1972 132 20.77 14.77 19.12 0 533.45 362.62 52836 +1972 133 18.37 12.37 16.72 0.01 466.23 278.3 52989 +1972 134 17.76 11.76 16.11 0.16 450.34 280.18 53138 +1972 135 14.26 8.26 12.61 0.07 367.81 287.63 53286 +1972 136 17.76 11.76 16.11 0.03 450.34 281.18 53430 +1972 137 19.66 13.66 18.01 0.09 501.4 277.29 53572 +1972 138 19.89 13.89 18.24 0.03 507.9 277.17 53711 +1972 139 20.63 14.63 18.98 1.11 529.31 275.8 53848 +1972 140 18.04 12.04 16.39 1.65 457.57 282.4 53981 +1972 141 16.51 10.51 14.86 0.67 419.22 286.01 54111 +1972 142 12.59 6.59 10.94 0.77 333.23 293.56 54238 +1972 143 10.86 4.86 9.21 1 300.38 296.64 54362 +1972 144 16.48 10.48 14.83 0.21 418.5 287.21 54483 +1972 145 12.64 6.64 10.99 1.15 334.22 294.61 54600 +1972 146 13.88 7.88 12.23 0.62 359.69 292.8 54714 +1972 147 14.96 8.96 13.31 0 383.2 388.26 54824 +1972 148 17.68 11.68 16.03 0 448.29 381.25 54931 +1972 149 17.46 11.46 15.81 0.12 442.7 286.65 55034 +1972 150 16.03 10.03 14.38 0.02 407.77 289.9 55134 +1972 151 15.17 9.17 13.52 0.28 387.92 291.88 55229 +1972 152 20.19 14.19 18.54 0.35 516.49 280.82 55321 +1972 153 21.76 15.76 20.11 0.02 563.48 276.8 55409 +1972 154 22.99 16.99 21.34 0.01 602.79 273.47 55492 +1972 155 20.46 14.46 18.81 0 524.33 374.24 55572 +1972 156 18.02 12.02 16.37 0 457.05 382.46 55648 +1972 157 18.83 12.83 17.18 0 478.52 380.12 55719 +1972 158 19.24 13.24 17.59 0.35 489.71 284.24 55786 +1972 159 23.12 17.12 21.47 0 607.08 365.17 55849 +1972 160 21.24 15.24 19.59 0 547.53 372.55 55908 +1972 161 24.39 18.39 22.74 0.2 650.34 270.08 55962 +1972 162 24.81 18.81 23.16 1.68 665.2 268.74 56011 +1972 163 22.66 16.66 21.01 1.05 592.02 275.64 56056 +1972 164 20.78 14.78 19.13 1.32 533.75 280.93 56097 +1972 165 19.59 13.59 17.94 0 499.44 378.75 56133 +1972 166 23.79 17.79 22.14 0 629.58 363.14 56165 +1972 167 22.27 16.27 20.62 0.9 579.51 276.9 56192 +1972 168 22.16 16.16 20.51 0 576.02 369.69 56214 +1972 169 26.39 20.39 24.74 0 723.74 351.46 56231 +1972 170 21.87 15.87 20.22 0.03 566.91 278.1 56244 +1972 171 20.5 14.5 18.85 0 525.5 375.83 56252 +1972 172 24.75 18.75 23.1 0 663.06 359.09 56256 +1972 173 23.42 17.42 21.77 0 617.07 364.74 56255 +1972 174 24.22 18.22 22.57 0 644.4 361.3 56249 +1972 175 23.51 17.51 21.86 0.01 620.09 273.19 56238 +1972 176 22.48 16.48 20.83 0.37 586.22 276.27 56223 +1972 177 20.62 14.62 18.97 0 529.02 375.13 56203 +1972 178 16.89 10.89 15.24 0.84 428.48 290.2 56179 +1972 179 17.23 11.23 15.58 0 436.91 385.86 56150 +1972 180 19.11 13.11 17.46 0.03 486.14 285 56116 +1972 181 24.06 18.06 22.41 0.02 638.85 271.17 56078 +1972 182 27.52 21.52 25.87 1.33 768.23 258.94 56035 +1972 183 19.03 13.03 17.38 1.67 483.95 284.9 55987 +1972 184 15.97 9.97 14.32 3.92 406.36 291.51 55935 +1972 185 16.79 10.79 15.14 2.58 426.03 289.76 55879 +1972 186 13.64 7.64 11.99 0.47 354.63 295.61 55818 +1972 187 17.3 11.3 15.65 0.63 438.67 288.33 55753 +1972 188 16.39 10.39 14.74 0.8 416.33 290.05 55684 +1972 189 18.42 12.42 16.77 0.58 467.55 285.48 55611 +1972 190 16.27 10.27 14.62 1.23 413.46 289.87 55533 +1972 191 19.74 13.74 18.09 0.15 503.65 281.83 55451 +1972 192 24.12 18.12 22.47 0.15 640.93 269.24 55366 +1972 193 27.17 21.17 25.52 0 754.21 344.65 55276 +1972 194 26.71 20.71 25.06 0 736.11 346.71 55182 +1972 195 26.4 20.4 24.75 0 724.13 347.96 55085 +1972 196 26.61 20.61 24.96 0.05 732.23 259.92 54984 +1972 197 25.67 19.67 24.02 0 696.55 350.56 54879 +1972 198 24.18 18.18 22.53 0.23 643.01 267.55 54770 +1972 199 24.78 18.78 23.13 0.49 664.13 265.36 54658 +1972 200 24.14 18.14 22.49 0.46 641.62 267.13 54542 +1972 201 25.09 19.09 23.44 0.75 675.27 263.7 54423 +1972 202 22.13 16.13 20.48 0.38 575.07 272.39 54301 +1972 203 19.54 13.54 17.89 0.08 498.04 278.82 54176 +1972 204 19.99 13.99 18.34 0.16 510.75 277.32 54047 +1972 205 19.44 13.44 17.79 0.17 495.25 278.29 53915 +1972 206 21.57 15.57 19.92 0 557.61 363.19 53780 +1972 207 24.25 18.25 22.6 0.16 645.44 264.03 53643 +1972 208 24.2 18.2 22.55 0 643.7 351.61 53502 +1972 209 25.92 19.92 24.27 0.57 705.89 257.56 53359 +1972 210 25.98 19.98 24.33 0.7 708.15 256.91 53213 +1972 211 28.15 22.15 26.5 0.24 794.02 248.39 53064 +1972 212 30.26 24.26 28.61 0.47 885.79 239.18 52913 +1972 213 27.58 21.58 25.93 0 770.65 332.64 52760 +1972 214 23.99 17.99 22.34 0 636.44 348.26 52604 +1972 215 20.86 14.86 19.21 0.43 536.12 269.55 52445 +1972 216 18.93 12.93 17.28 0.32 481.23 273.51 52285 +1972 217 21 15 19.35 0 540.3 357.02 52122 +1972 218 20.16 14.16 18.51 0.21 515.63 269.28 51958 +1972 219 22.99 16.99 21.34 0 602.79 347.91 51791 +1972 220 25.54 19.54 23.89 0.64 691.73 252.34 51622 +1972 221 24.05 18.05 22.4 0 638.51 341.82 51451 +1972 222 20.5 14.5 18.85 0 525.5 353.9 51279 +1972 223 17.11 11.11 15.46 0.16 433.92 272.25 51105 +1972 224 18.62 12.62 16.97 0.21 472.87 268.21 50929 +1972 225 18.48 12.48 16.83 1.21 469.14 267.66 50751 +1972 226 17.16 11.16 15.51 0.08 435.17 269.59 50572 +1972 227 18.34 12.34 16.69 0.02 465.43 266.13 50392 +1972 228 24.53 18.53 22.88 0.39 655.26 249.08 50210 +1972 229 22.79 16.79 21.14 0.28 596.25 253.28 50026 +1972 230 19.88 13.88 18.23 0 507.62 346.43 49842 +1972 231 23.9 17.9 22.25 0 633.35 330.8 49656 +1972 232 25.53 19.53 23.88 0.65 691.36 242.1 49469 +1972 233 25.32 19.32 23.67 0.36 683.64 241.76 49280 +1972 234 19.71 13.71 18.06 3.27 502.81 255.99 49091 +1972 235 12.87 6.87 11.22 1.72 338.83 267.87 48900 +1972 236 15.88 9.88 14.23 0.2 404.24 261.69 48709 +1972 237 20.48 14.48 18.83 0 524.91 334.37 48516 +1972 238 18.49 12.49 16.84 0 469.41 338.69 48323 +1972 239 21.67 15.67 20.02 0 560.7 327.32 48128 +1972 240 22.02 16.02 20.37 0 571.61 324.41 47933 +1972 241 27.5 21.5 25.85 0 767.42 300.81 47737 +1972 242 27.44 21.44 25.79 0 765.01 299.48 47541 +1972 243 25.29 19.29 23.64 0 682.55 307.03 47343 +1972 244 18.94 12.94 17.29 0 481.5 326.99 47145 +1972 245 16.73 10.73 15.08 0 424.56 331.02 46947 +1972 246 18.54 12.54 16.89 0 470.74 324.31 46747 +1972 247 18.68 12.68 17.03 0 474.48 322.07 46547 +1972 248 19.77 13.77 18.12 0 504.5 317.05 46347 +1972 249 19.73 13.73 18.08 0.07 503.37 236.34 46146 +1972 250 18.01 12.01 16.36 0 456.79 317.93 45945 +1972 251 16.62 10.62 14.97 0.57 421.88 239.48 45743 +1972 252 14.8 8.8 13.15 0.36 379.63 240.94 45541 +1972 253 14.15 8.15 12.5 0.15 365.44 240.35 45339 +1972 254 14.21 8.21 12.56 0.05 366.73 238.63 45136 +1972 255 15.55 9.55 13.9 0 396.58 313.03 44933 +1972 256 14.26 8.26 12.61 0 367.81 313.47 44730 +1972 257 12.18 6.18 10.53 0 325.18 315.23 44527 +1972 258 11.3 5.3 9.65 0 308.46 314.35 44323 +1972 259 18.31 12.31 16.66 0 464.64 297.29 44119 +1972 260 17.13 11.13 15.48 0 434.42 297.81 43915 +1972 261 20.71 14.71 19.06 0 531.67 286.05 43711 +1972 262 17.55 11.55 15.9 0 444.98 292.01 43507 +1972 263 14.69 8.69 13.04 0.16 377.2 221.86 43303 +1972 264 14.05 8.05 12.4 0.82 363.3 220.85 43099 +1972 265 13.01 7.01 11.36 0.14 341.66 220.49 42894 +1972 266 16.45 10.45 14.8 0 417.77 284.7 42690 +1972 267 18.16 12.16 16.51 0 460.7 278.14 42486 +1972 268 17.3 11.3 15.65 0 438.67 277.61 42282 +1972 269 16.68 10.68 15.03 0.45 423.34 207.36 42078 +1972 270 12.61 6.61 10.96 0 333.63 281.64 41875 +1972 271 13.59 7.59 11.94 0 353.59 277.3 41671 +1972 272 13.43 7.43 11.78 0 350.26 274.83 41468 +1972 273 14.75 8.75 13.1 0 378.52 269.9 41265 +1972 274 14.4 8.4 12.75 0 370.85 267.88 41062 +1972 275 16.14 10.14 14.49 0 410.37 261.79 40860 +1972 276 16.95 10.95 15.3 0 429.96 257.47 40658 +1972 277 16.02 10.02 14.37 0 407.53 256.72 40456 +1972 278 15.64 9.64 13.99 0.53 398.66 190.96 40255 +1972 279 14.18 8.18 12.53 0.03 366.09 190.86 40054 +1972 280 10.37 4.37 8.72 0.16 291.59 193.26 39854 +1972 281 10.87 4.87 9.22 0.1 300.56 190.68 39654 +1972 282 8.82 2.82 7.17 0.38 265.24 190.6 39455 +1972 283 8.3 2.3 6.65 0.03 256.87 188.91 39256 +1972 284 10.87 4.87 9.22 0.36 300.56 184.18 39058 +1972 285 9.39 3.39 7.74 0.01 274.68 183.61 38861 +1972 286 10.51 4.51 8.86 0 294.08 240.6 38664 +1972 287 7.77 1.77 6.12 0.06 248.57 180.68 38468 +1972 288 6.28 0.28 4.63 0 226.47 239.61 38273 +1972 289 6.73 0.73 5.08 0 232.96 236.47 38079 +1972 290 8.25 2.25 6.6 0 256.08 231.96 37885 +1972 291 9.18 3.18 7.53 0 271.17 228.18 37693 +1972 292 12.14 6.14 10.49 0 324.4 221.74 37501 +1972 293 11.4 5.4 9.75 0 310.32 220 37311 +1972 294 10.07 4.07 8.42 0 286.32 218.76 37121 +1972 295 10.96 4.96 9.31 0 302.2 214.83 36933 +1972 296 10.06 4.06 8.41 0 286.15 213.32 36745 +1972 297 10.05 4.05 8.4 0 285.98 210.59 36560 +1972 298 8.29 2.29 6.64 0 256.71 209.88 36375 +1972 299 11.78 5.78 10.13 0.02 317.49 152.34 36191 +1972 300 11.5 5.5 9.85 0 312.19 200.81 36009 +1972 301 15.33 9.33 13.68 0 391.55 193.06 35829 +1972 302 15.29 9.29 13.64 0.01 390.64 142.93 35650 +1972 303 15.64 9.64 13.99 0.36 398.66 140.64 35472 +1972 304 17.87 11.87 16.22 0.25 453.17 136.13 35296 +1972 305 12.13 6.13 10.48 0.46 324.21 140.41 35122 +1972 306 8.79 2.79 7.14 0 264.75 188.63 34950 +1972 307 7.38 1.38 5.73 0 242.61 187.43 34779 +1972 308 10.62 4.62 8.97 0 296.05 181.64 34610 +1972 309 9.2 3.2 7.55 0 271.5 180.8 34444 +1972 310 10.67 4.67 9.02 0.12 296.95 132.65 34279 +1972 311 11.21 5.21 9.56 0.13 306.79 130.59 34116 +1972 312 14.39 8.39 12.74 0 370.63 167.72 33956 +1972 313 14.89 8.89 13.24 0.12 381.63 123.75 33797 +1972 314 11.23 5.23 9.58 0 307.16 167.47 33641 +1972 315 10.76 4.76 9.11 0.02 298.57 124.09 33488 +1972 316 7.89 1.89 6.24 0.66 250.43 124.47 33337 +1972 317 4.62 -1.38 2.97 0.13 203.85 124.68 33188 +1972 318 6.06 0.06 4.41 0 223.35 162.87 33042 +1972 319 3.77 -2.23 2.12 0.44 193.04 122.05 32899 +1972 320 4.31 -1.69 2.66 0.48 199.85 120.37 32758 +1972 321 8.64 2.64 6.99 0 262.32 155.15 32620 +1972 322 7.47 1.47 5.82 0.23 243.98 115.72 32486 +1972 323 8.96 2.96 7.31 1.24 267.53 113.6 32354 +1972 324 9.65 3.65 8 0.21 279.08 111.62 32225 +1972 325 6.41 0.41 4.76 0.42 228.32 112.28 32100 +1972 326 1.67 -4.33 0.02 0.6 168.43 113.36 31977 +1972 327 2.8 -3.2 1.15 0.06 181.32 111.51 31858 +1972 328 7.62 1.62 5.97 0.04 246.26 107.66 31743 +1972 329 6.35 0.35 4.7 0.09 227.47 107.24 31631 +1972 330 8.79 2.79 7.14 1.31 264.75 104.79 31522 +1972 331 5.32 -0.68 3.67 0.73 213.14 105.68 31417 +1972 332 5.73 -0.27 4.08 0.46 218.75 104.25 31316 +1972 333 5.67 -0.33 4.02 0.03 217.92 103.46 31218 +1972 334 5.77 -0.23 4.12 0 219.3 136.79 31125 +1972 335 0 -6 -1.65 0 150.84 138.71 31035 +1972 336 -2.39 -8.39 -4.04 0 128.44 138.58 30949 +1972 337 0.26 -5.74 -1.39 0 153.47 135.83 30867 +1972 338 -2.43 -8.43 -4.08 0 128.09 135.96 30790 +1972 339 -0.75 -6.75 -2.4 0 143.48 134.5 30716 +1972 340 -1.79 -7.79 -3.44 0 133.78 134.17 30647 +1972 341 1.47 -4.53 -0.18 0 166.24 131.86 30582 +1972 342 4.94 -1.06 3.29 0 208.05 129.26 30521 +1972 343 5.09 -0.91 3.44 0 210.05 128.35 30465 +1972 344 6.65 0.65 5 0 231.79 126.25 30413 +1972 345 5.97 -0.03 4.32 0 222.09 126.26 30366 +1972 346 5.81 -0.19 4.16 0 219.85 125.81 30323 +1972 347 5.68 -0.32 4.03 0 218.05 125.3 30284 +1972 348 0.66 -5.34 -0.99 0 157.6 127.55 30251 +1972 349 -1.85 -7.85 -3.5 0 133.23 128.17 30221 +1972 350 1.34 -4.66 -0.31 0 164.82 126.52 30197 +1972 351 0.86 -5.14 -0.79 0 159.69 126.52 30177 +1972 352 1.11 -4.89 -0.54 0 162.35 126.31 30162 +1972 353 4.03 -1.97 2.38 0 196.29 124.81 30151 +1972 354 3.1 -2.9 1.45 0 184.88 125.26 30145 +1972 355 3.02 -2.98 1.37 0 183.92 125.3 30144 +1972 356 1.49 -4.51 -0.16 0 166.46 126.07 30147 +1972 357 1.41 -4.59 -0.24 0 165.58 126.16 30156 +1972 358 1.58 -4.42 -0.07 0 167.44 126.17 30169 +1972 359 4.63 -1.37 2.98 0 203.98 124.73 30186 +1972 360 6.97 0.97 5.32 0.07 236.48 92.75 30208 +1972 361 7.89 1.89 6.24 0.65 250.43 92.53 30235 +1972 362 6.08 0.08 4.43 0 223.63 125 30267 +1972 363 10.94 4.94 9.29 0.01 301.83 91.51 30303 +1972 364 6.19 0.19 4.54 0 225.19 125.9 30343 +1972 365 3.25 -2.75 1.6 0.2 186.68 96.12 30388 +1973 1 5.8 -0.2 4.15 0 219.72 127.6 30438 +1973 2 -0.91 -6.91 -2.56 0 141.95 131.71 30492 +1973 3 -3.42 -9.42 -5.07 0 119.71 133.58 30551 +1973 4 -0.82 -6.82 -2.47 0 142.8 133.54 30614 +1973 5 1.88 -4.12 0.23 0 170.77 133 30681 +1973 6 -1.72 -7.72 -3.37 0.05 134.41 144.67 30752 +1973 7 -0.32 -6.32 -1.97 0 147.66 178.67 30828 +1973 8 1.28 -4.72 -0.37 0 164.17 136.47 30907 +1973 9 4.48 -1.52 2.83 0 202.04 136.03 30991 +1973 10 0.65 -5.35 -1 0.77 157.49 104.5 31079 +1973 11 0.65 -5.35 -1 0.14 157.49 105.25 31171 +1973 12 2.89 -3.11 1.24 0.18 182.38 105.17 31266 +1973 13 3.74 -2.26 2.09 0 192.67 141.38 31366 +1973 14 3.18 -2.82 1.53 0.09 185.83 107.38 31469 +1973 15 2 -4 0.35 0.18 172.11 108.94 31575 +1973 16 -2.01 -8.01 -3.66 0.39 131.8 154.14 31686 +1973 17 1.73 -4.27 0.08 0 169.1 190.85 31800 +1973 18 4.41 -1.59 2.76 1.09 201.13 153.32 31917 +1973 19 0.64 -5.36 -1.01 0 157.39 194.3 32038 +1973 20 -1.5 -7.5 -3.15 0 136.42 196.72 32161 +1973 21 -6.43 -12.43 -8.08 0 97.09 200.38 32289 +1973 22 -1.61 -7.61 -3.26 0.35 135.41 161.47 32419 +1973 23 -1.42 -7.42 -3.07 0 137.16 202.82 32552 +1973 24 0.8 -5.2 -0.85 0.1 159.06 163.08 32688 +1973 25 -0.1 -6.1 -1.75 0.05 149.84 164.82 32827 +1973 26 3.17 -2.83 1.52 0 185.71 205.47 32969 +1973 27 2.41 -3.59 0.76 0 176.78 207.49 33114 +1973 28 7.64 1.64 5.99 0 246.57 165.45 33261 +1973 29 11.39 5.39 9.74 0 310.13 164.26 33411 +1973 30 12.95 6.95 11.3 0 340.44 164.69 33564 +1973 31 10.89 4.89 9.24 0 300.92 169.29 33718 +1973 32 11.12 5.12 9.47 0 305.13 171.11 33875 +1973 33 9.03 3.03 7.38 0.01 268.69 131.85 34035 +1973 34 8.63 2.63 6.98 0 262.15 178.36 34196 +1973 35 4.8 -1.2 3.15 0.01 206.2 137.76 34360 +1973 36 1.19 -4.81 -0.46 0.45 163.21 141.44 34526 +1973 37 1.86 -4.14 0.21 0.1 170.54 142.97 34694 +1973 38 1.87 -4.13 0.22 0 170.65 193.38 34863 +1973 39 3.83 -2.17 2.18 0 193.79 194.68 35035 +1973 40 5.88 -0.12 4.23 0 220.83 195.71 35208 +1973 41 5.28 -0.72 3.63 0 212.6 198.81 35383 +1973 42 4.71 -1.29 3.06 0 205.02 201.82 35560 +1973 43 7.87 1.87 6.22 0.82 250.12 151.31 35738 +1973 44 10.15 4.15 8.5 0 287.72 201.89 35918 +1973 45 9.77 3.77 8.12 0.02 281.14 153.67 36099 +1973 46 8.83 2.83 7.18 0 265.4 208.57 36282 +1973 47 4.59 -1.41 2.94 0 203.46 215.32 36466 +1973 48 3.57 -2.43 1.92 0 190.57 218.94 36652 +1973 49 0.79 -5.21 -0.86 0 158.96 223.7 36838 +1973 50 -0.06 -6.06 -1.71 0 150.24 226.94 37026 +1973 51 2.03 -3.97 0.38 0 172.45 228.55 37215 +1973 52 1.42 -4.58 -0.23 0.2 165.69 173.88 37405 +1973 53 3.8 -2.2 2.15 0.16 193.42 174.77 37596 +1973 54 0.67 -5.33 -0.98 0.01 157.7 178.59 37788 +1973 55 3.35 -2.65 1.7 0 187.89 239.17 37981 +1973 56 3.97 -2.03 2.32 0 195.54 241.37 38175 +1973 57 5.69 -0.31 4.04 0 218.19 242.71 38370 +1973 58 5.08 -0.92 3.43 0 209.91 246.22 38565 +1973 59 6.76 0.76 5.11 0 233.39 247.28 38761 +1973 60 6.82 0.82 5.17 0.02 234.27 187.57 38958 +1973 61 7.21 1.21 5.56 0 240.06 252.6 39156 +1973 62 8.04 2.04 6.39 0 252.77 254.45 39355 +1973 63 10.42 4.42 8.77 0.07 292.48 190.83 39553 +1973 64 12.65 6.65 11 0 334.42 254.05 39753 +1973 65 12.35 6.35 10.7 0 328.5 257.34 39953 +1973 66 11.71 5.71 10.06 0 316.16 261.01 40154 +1973 67 11.49 5.49 9.84 0 312.01 264.19 40355 +1973 68 11.8 5.8 10.15 0 317.87 266.55 40556 +1973 69 10.24 4.24 8.59 0 289.3 271.43 40758 +1973 70 7 1 5.35 0 236.93 278.4 40960 +1973 71 7.88 1.88 6.23 0.75 250.27 210.2 41163 +1973 72 5.22 -0.78 3.57 0 211.79 286.12 41366 +1973 73 7.26 1.26 5.61 0.1 240.81 214.88 41569 +1973 74 3.9 -2.1 2.25 0 194.66 292.92 41772 +1973 75 2.35 -3.65 0.7 0 176.09 297.12 41976 +1973 76 0.89 -5.11 -0.76 0 160.01 301.04 42179 +1973 77 3.22 -2.78 1.57 0 186.32 301.64 42383 +1973 78 1.77 -4.23 0.12 0 169.54 305.67 42587 +1973 79 4.16 -1.84 2.51 0 197.94 306.18 42791 +1973 80 4.51 -1.49 2.86 0 202.42 308.38 42996 +1973 81 11.2 5.2 9.55 0 306.61 302.12 43200 +1973 82 11.8 5.8 10.15 0 317.87 303.75 43404 +1973 83 12.82 6.82 11.17 0.28 337.82 228.32 43608 +1973 84 10.58 4.58 8.93 0.01 295.33 233.06 43812 +1973 85 11.59 5.59 9.94 0 313.89 311.56 44016 +1973 86 9.31 3.31 7.66 0 273.34 317.59 44220 +1973 87 8.25 2.25 6.6 0.01 256.08 241.24 44424 +1973 88 13.34 7.34 11.69 0.08 348.4 236.69 44627 +1973 89 12.09 6.09 10.44 0.22 323.43 240.12 44831 +1973 90 10.06 4.06 8.41 0 286.15 325.96 45034 +1973 91 12.57 6.57 10.92 0 332.83 323.86 45237 +1973 92 11.22 5.22 9.57 0 306.98 328.52 45439 +1973 93 12.17 6.17 10.52 0.2 324.99 246.76 45642 +1973 94 13 7 11.35 0.13 341.45 247.19 45843 +1973 95 9.12 3.12 7.47 0.43 270.17 253.85 46045 +1973 96 11.66 5.66 10.01 0.51 315.21 252.25 46246 +1973 97 14.14 8.14 12.49 0 365.23 333.5 46446 +1973 98 13.09 7.09 11.44 0.02 343.28 253.2 46647 +1973 99 11.88 5.88 10.23 0.08 319.39 256.45 46846 +1973 100 11.22 5.22 9.57 0.05 306.98 258.82 47045 +1973 101 10.38 4.38 8.73 0.04 291.77 261.38 47243 +1973 102 13.11 7.11 11.46 0 343.69 345.3 47441 +1973 103 13.04 7.04 11.39 0 342.26 347.27 47638 +1973 104 10.4 4.4 8.75 0.46 292.12 265.55 47834 +1973 105 11.52 5.52 9.87 0.06 312.57 265.38 48030 +1973 106 14.6 8.6 12.95 0 375.22 349.14 48225 +1973 107 13.52 7.52 11.87 0.87 352.13 264.88 48419 +1973 108 11.89 5.89 10.24 1.97 319.59 268.66 48612 +1973 109 10.65 4.65 9 2.07 296.59 271.61 48804 +1973 110 9.43 3.43 7.78 1.6 275.36 274.27 48995 +1973 111 10.77 4.77 9.12 0.03 298.75 273.69 49185 +1973 112 7.18 1.18 5.53 0 239.61 372.33 49374 +1973 113 5.42 -0.58 3.77 0.32 214.49 282.11 49561 +1973 114 7.82 1.82 6.17 0.47 249.34 280.7 49748 +1973 115 11.23 5.23 9.58 0.27 307.16 277.42 49933 +1973 116 6.36 0.36 4.71 0 227.61 379.12 50117 +1973 117 9.83 3.83 8.18 0 282.17 375.01 50300 +1973 118 8.62 2.62 6.97 0.04 261.99 283.79 50481 +1973 119 11.43 5.43 9.78 0.01 310.88 280.95 50661 +1973 120 14.91 8.91 13.26 0.38 382.08 276.18 50840 +1973 121 21.44 15.44 19.79 0.13 553.62 262.67 51016 +1973 122 19.55 13.55 17.9 0 498.32 357.69 51191 +1973 123 17.29 11.29 15.64 0 438.42 365.41 51365 +1973 124 14.51 8.51 12.86 0 373.25 373.62 51536 +1973 125 18.12 12.12 16.47 0 459.66 365.07 51706 +1973 126 22.7 16.7 21.05 0 593.32 350.67 51874 +1973 127 22.21 16.21 20.56 0.66 577.6 265.02 52039 +1973 128 18.83 12.83 17.18 0.3 478.52 274.32 52203 +1973 129 18.11 12.11 16.46 0.04 459.4 276.58 52365 +1973 130 19.62 13.62 17.97 0 500.28 364.89 52524 +1973 131 16.89 10.89 15.24 0 428.48 373.83 52681 +1973 132 20.07 14.07 18.42 0 513.04 364.99 52836 +1973 133 20.26 14.26 18.61 0 518.51 365.05 52989 +1973 134 21.24 15.24 19.59 0 547.53 362.34 53138 +1973 135 19.81 13.81 18.16 0 505.63 367.92 53286 +1973 136 20.48 14.48 18.83 0 524.91 366.29 53430 +1973 137 16.87 10.87 15.22 0 427.99 378.14 53572 +1973 138 13.47 7.47 11.82 0 351.09 387.31 53711 +1973 139 16.4 10.4 14.75 0 416.57 380.72 53848 +1973 140 17.92 11.92 16.27 0 454.46 376.89 53981 +1973 141 19.13 13.13 17.48 0 486.69 373.61 54111 +1973 142 18.09 12.09 16.44 0 458.88 377.32 54238 +1973 143 15.28 9.28 13.63 0.02 390.41 289.22 54362 +1973 144 17.14 11.14 15.49 0 434.67 381.1 54483 +1973 145 16.19 10.19 14.54 0 411.56 384.2 54600 +1973 146 16.24 10.24 14.59 0 412.74 384.45 54714 +1973 147 19.97 13.97 18.32 0 510.18 373.66 54824 +1973 148 13.16 7.16 11.51 0 344.71 392.93 54931 +1973 149 19.7 13.7 18.05 0.11 502.53 281.44 55034 +1973 150 17.74 11.74 16.09 0.13 449.83 286.29 55134 +1973 151 15.99 9.99 14.34 0 406.83 387.03 55229 +1973 152 18.82 12.82 17.17 0.87 478.25 284.19 55321 +1973 153 16.41 10.41 14.76 0.18 416.81 289.69 55409 +1973 154 20.59 14.59 18.94 0 528.14 373.6 55492 +1973 155 18 12 16.35 0 456.53 382.19 55572 +1973 156 19.81 13.81 18.16 0 505.63 376.77 55648 +1973 157 20.7 14.7 19.05 0 531.38 373.88 55719 +1973 158 24.98 18.98 23.33 0 671.3 357.04 55786 +1973 159 24.38 18.38 22.73 0.71 649.98 269.93 55849 +1973 160 24.63 18.63 22.98 0.11 658.8 269.25 55908 +1973 161 25.35 19.35 23.7 0.1 684.74 266.88 55962 +1973 162 25.48 19.48 23.83 1.24 689.52 266.48 56011 +1973 163 24.17 18.17 22.52 0.28 642.66 270.99 56056 +1973 164 23.15 17.15 21.5 0.01 608.07 274.2 56097 +1973 165 23.64 17.64 21.99 0 624.48 363.69 56133 +1973 166 21.07 15.07 19.42 0.38 542.4 280.29 56165 +1973 167 20.64 14.64 18.99 0.83 529.61 281.39 56192 +1973 168 19.88 13.88 18.23 0.01 507.62 283.41 56214 +1973 169 17.21 11.21 15.56 0 436.41 386.22 56231 +1973 170 21.13 15.13 19.48 0.02 544.21 280.15 56244 +1973 171 25.48 19.48 23.83 0.51 689.52 266.86 56252 +1973 172 27.24 21.24 25.59 0.15 757 260.48 56256 +1973 173 22.76 16.76 21.11 0 595.27 367.4 56255 +1973 174 22.31 16.31 20.66 0.81 580.78 276.81 56249 +1973 175 21.81 15.81 20.16 0.76 565.04 278.21 56238 +1973 176 21.28 15.28 19.63 0 548.75 372.87 56223 +1973 177 15.36 9.36 13.71 1.98 392.23 293.29 56203 +1973 178 14.98 8.98 13.33 0.13 383.64 294.04 56179 +1973 179 14.13 8.13 12.48 1.31 365.02 295.53 56150 +1973 180 14.75 8.75 13.1 0 378.52 392.4 56116 +1973 181 14.4 8.4 12.75 0 370.85 393.19 56078 +1973 182 20.91 14.91 19.26 0 537.61 373.69 56035 +1973 183 21.99 15.99 20.34 0 570.66 369.55 55987 +1973 184 22.1 16.1 20.45 0 574.13 368.98 55935 +1973 185 17.58 11.58 15.93 0.05 445.74 288.05 55879 +1973 186 21.15 15.15 19.5 0 544.81 372.16 55818 +1973 187 22.98 16.98 21.33 0 602.46 365.03 55753 +1973 188 27.92 21.92 26.27 0.31 784.52 256.59 55684 +1973 189 24.7 18.7 23.05 0.26 661.28 268.05 55611 +1973 190 26.41 20.41 24.76 0.17 724.51 261.88 55533 +1973 191 20.59 14.59 18.94 0.02 528.14 279.66 55451 +1973 192 21.97 15.97 20.32 0.61 570.04 275.69 55366 +1973 193 21.9 15.9 20.25 0.61 567.85 275.68 55276 +1973 194 22.07 16.07 20.42 0.19 573.18 275.04 55182 +1973 195 21.32 15.32 19.67 0.48 549.96 276.92 55085 +1973 196 21.31 15.31 19.66 0.43 549.66 276.64 54984 +1973 197 20.96 14.96 19.31 0.39 539.11 277.24 54879 +1973 198 22.71 16.71 21.06 0 593.64 362.72 54770 +1973 199 23.04 17.04 21.39 0 604.44 361.07 54658 +1973 200 26.97 20.97 25.32 0 746.3 343.25 54542 +1973 201 23.79 17.79 22.14 0 629.58 357.18 54423 +1973 202 22.81 16.81 21.16 0.6 596.9 270.43 54301 +1973 203 20.18 14.18 18.53 0.3 516.2 277.23 54176 +1973 204 23.08 17.08 21.43 1.67 605.76 268.89 54047 +1973 205 22 16 20.35 0 570.98 362.16 53915 +1973 206 22.2 16.2 20.55 0 577.29 360.85 53780 +1973 207 23.03 17.03 21.38 0 604.11 357.01 53643 +1973 208 21.02 15.02 19.37 0.94 540.9 272.89 53502 +1973 209 21.34 15.34 19.69 0.29 550.57 271.55 53359 +1973 210 23.3 17.3 21.65 0.11 613.06 265.54 53213 +1973 211 24.94 18.94 23.29 0.41 669.86 259.85 53064 +1973 212 26.09 20.09 24.44 0 712.3 340.54 52913 +1973 213 25.65 19.65 24 0.2 695.8 256.37 52760 +1973 214 21.82 15.82 20.17 0.02 565.35 267.5 52604 +1973 215 17.44 11.44 15.79 0.53 442.19 277.59 52445 +1973 216 20.49 14.49 18.84 0.1 525.2 269.74 52285 +1973 217 24.49 18.49 22.84 0 653.85 343.68 52122 +1973 218 26.2 20.2 24.55 0 716.48 335.37 51958 +1973 219 23.82 17.82 22.17 0 630.61 344.63 51791 +1973 220 27.78 21.78 26.13 0.2 778.79 244.43 51622 +1973 221 24.4 18.4 22.75 0 650.69 340.38 51451 +1973 222 24.4 18.4 22.75 0 650.69 339.37 51279 +1973 223 22.96 16.96 21.31 0.03 601.8 257.99 51105 +1973 224 23.25 17.25 21.6 0 611.39 341.84 50929 +1973 225 23.05 17.05 21.4 0 604.77 341.49 50751 +1973 226 24.5 18.5 22.85 0 654.2 334.63 50572 +1973 227 22.35 16.35 20.7 0.02 582.06 256.3 50392 +1973 228 24.04 18.04 22.39 0 638.16 334.09 50210 +1973 229 27.05 21.05 25.4 0.66 749.45 239.88 50026 +1973 230 23.49 17.49 21.84 0.64 619.42 250.36 49842 +1973 231 22.78 16.78 21.13 0 595.92 335.07 49656 +1973 232 23.17 17.17 21.52 0 608.73 332.3 49469 +1973 233 22.2 16.2 20.55 0.15 577.29 250.85 49280 +1973 234 24.61 18.61 22.96 0 658.09 323.93 49091 +1973 235 22.93 16.93 21.28 0 600.82 328.98 48900 +1973 236 25.54 19.54 23.89 0 691.73 317.29 48709 +1973 237 26.87 20.87 25.22 0 742.37 309.91 48516 +1973 238 27.07 21.07 25.42 0 750.24 307.43 48323 +1973 239 20.74 14.74 19.09 0 532.56 330.39 48128 +1973 240 20.5 14.5 18.85 0.04 525.5 247.06 47933 +1973 241 20.17 14.17 18.52 0.84 515.92 246.55 47737 +1973 242 17.91 11.91 16.26 0 454.2 333.53 47541 +1973 243 14.39 8.39 12.74 1.4 370.63 255.15 47343 +1973 244 14.1 8.1 12.45 0.02 364.37 254.22 47145 +1973 245 18.66 12.66 17.01 0.08 473.94 244.45 46947 +1973 246 16.67 10.67 15.02 0 423.1 329.18 46747 +1973 247 20.52 14.52 18.87 0 526.08 316.72 46547 +1973 248 21.38 15.38 19.73 0 551.79 312.12 46347 +1973 249 26.22 20.22 24.57 0 717.24 292.39 46146 +1973 250 23.59 17.59 21.94 0 622.79 300.73 45945 +1973 251 24.17 18.17 22.52 0.02 642.66 222.45 45743 +1973 252 23.65 17.65 22 0 624.82 296.43 45541 +1973 253 24.85 18.85 23.2 0 666.63 290 45339 +1973 254 23.94 17.94 22.29 0 634.72 291.34 45136 +1973 255 20.63 14.63 18.98 0.67 529.31 224.98 44933 +1973 256 21.57 15.57 19.92 1.83 557.61 221.18 44730 +1973 257 22.77 16.77 21.12 0.09 595.59 216.73 44527 +1973 258 18.58 12.58 16.93 0 471.8 299 44323 +1973 259 13.63 7.63 11.98 0 354.42 307.68 44119 +1973 260 16.66 10.66 15.01 0 422.85 298.9 43915 +1973 261 15.54 9.54 13.89 0 396.35 298.92 43711 +1973 262 13.72 7.72 12.07 0.08 356.31 225.14 43507 +1973 263 14.79 8.79 13.14 0 379.41 295.61 43303 +1973 264 12.53 6.53 10.88 0 332.04 297.25 43099 +1973 265 16.12 10.12 14.47 0.28 409.89 215.91 42894 +1973 266 20.64 14.64 18.99 1.19 529.61 205.77 42690 +1973 267 19.29 13.29 17.64 0.18 491.09 206.51 42486 +1973 268 18.94 12.94 17.29 1.58 481.5 205.29 42282 +1973 269 22.23 16.23 20.58 2.19 578.24 196.74 42078 +1973 270 17.75 11.75 16.1 1.87 450.08 203.62 41875 +1973 271 17.2 11.2 15.55 0 436.16 270.14 41671 +1973 272 18.41 12.41 16.76 0.24 467.28 198.53 41468 +1973 273 16.4 10.4 14.75 0.61 416.57 199.99 41265 +1973 274 11.33 5.33 9.68 0 309.02 272.99 41062 +1973 275 8.56 2.56 6.91 0 261.02 274.01 40860 +1973 276 9.53 3.53 7.88 0 277.05 269.99 40658 +1973 277 10.05 4.05 8.4 0.59 285.98 199.93 40456 +1973 278 7.24 1.24 5.59 0 240.5 267.16 40255 +1973 279 7.35 1.35 5.7 0 242.16 264.15 40054 +1973 280 6.58 0.58 4.93 0 230.78 262.28 39854 +1973 281 10.76 4.76 9.11 0 298.57 254.39 39654 +1973 282 11.97 5.97 10.32 0 321.12 249.9 39455 +1973 283 17.35 11.35 15.7 0 439.92 237.74 39256 +1973 284 13.65 7.65 12 0.05 354.84 181.09 39058 +1973 285 15.45 9.45 13.8 0.04 394.29 176.84 38861 +1973 286 11.35 5.35 9.7 0 309.39 239.47 38664 +1973 287 11.86 5.86 10.21 0 319.01 235.81 38468 +1973 288 12.89 6.89 11.24 0.01 339.23 173.65 38273 +1973 289 12.31 6.31 10.66 1.19 327.71 172.31 38079 +1973 290 12.14 6.14 10.49 0.6 324.4 170.35 37885 +1973 291 9.46 3.46 7.81 0 275.86 227.85 37693 +1973 292 9.36 3.36 7.71 0.03 274.18 168.94 37501 +1973 293 10.97 4.97 9.32 1.1 302.38 165.42 37311 +1973 294 11.56 5.56 9.91 0.02 313.32 162.68 37121 +1973 295 10.18 4.18 8.53 0 288.25 215.78 36933 +1973 296 10.5 4.5 8.85 0.02 293.9 159.6 36745 +1973 297 14.95 8.95 13.3 0 382.97 204 36560 +1973 298 15.38 9.38 13.73 0.31 392.69 150.58 36375 +1973 299 14.72 8.72 13.07 0 377.86 199.06 36191 +1973 300 14.09 8.09 12.44 0 364.16 197.37 36009 +1973 301 14.95 8.95 13.3 0 382.97 193.63 35829 +1973 302 14.4 8.4 12.75 0 370.85 191.88 35650 +1973 303 15.42 9.42 13.77 0.12 393.6 140.89 35472 +1973 304 15.93 9.93 14.28 0 405.42 184.68 35296 +1973 305 9.05 3.05 7.4 0.43 269.02 142.97 35122 +1973 306 8.39 2.39 6.74 1.05 258.3 141.77 34950 +1973 307 6.26 0.26 4.61 0.08 226.18 141.29 34779 +1973 308 3.85 -2.15 2.2 0.32 194.04 140.7 34610 +1973 309 4.76 -1.24 3.11 0.5 205.68 138.44 34444 +1973 310 3.88 -2.12 2.23 0 194.41 182.74 34279 +1973 311 6.08 0.08 4.43 0 223.63 178.91 34116 +1973 312 4.79 -1.21 3.14 0 206.07 177.22 33956 +1973 313 5.11 -0.89 3.46 0.06 210.31 131.13 33797 +1973 314 3.4 -2.6 1.75 0 188.49 174.04 33641 +1973 315 5.74 -0.26 4.09 0 218.88 169.86 33488 +1973 316 12.24 6.24 10.59 0 326.35 161.72 33337 +1973 317 10.16 4.16 8.51 0 287.9 161.71 33188 +1973 318 8.05 2.05 6.4 0 252.93 161.3 33042 +1973 319 5.14 -0.86 3.49 0 210.72 161.82 32899 +1973 320 6.18 0.18 4.53 0 225.05 159.2 32758 +1973 321 -0.07 -6.07 -1.72 0 150.14 160.83 32620 +1973 322 -3.34 -9.34 -4.99 0 120.37 160.37 32486 +1973 323 -1.63 -7.63 -3.28 0 135.23 158.02 32354 +1973 324 4.98 -1.02 3.33 1.25 208.58 114.31 32225 +1973 325 5.62 -0.38 3.97 0 217.23 150.25 32100 +1973 326 5.95 -0.05 4.3 0.05 221.81 111.43 31977 +1973 327 6.46 0.46 4.81 0.05 229.04 109.77 31858 +1973 328 10.44 4.44 8.79 0.04 292.83 105.91 31743 +1973 329 10.32 4.32 8.67 0 290.71 139.85 31631 +1973 330 12.09 6.09 10.44 0 323.43 136.77 31522 +1973 331 13.51 7.51 11.86 0 351.92 134.04 31417 +1973 332 8.69 2.69 7.04 0.08 263.12 102.65 31316 +1973 333 4.64 -1.36 2.99 0 204.11 138.6 31218 +1973 334 5.43 -0.57 3.78 0.01 214.63 102.75 31125 +1973 335 4.96 -1.04 3.31 0 208.32 136.12 31035 +1973 336 2.4 -3.6 0.75 0 176.66 136.48 30949 +1973 337 6.03 0.03 4.38 0 222.93 132.72 30867 +1973 338 10.26 4.26 8.61 0 289.65 128.66 30790 +1973 339 7.33 1.33 5.68 0 241.86 130.13 30716 +1973 340 1.68 -4.32 0.03 0.66 168.54 99.51 30647 +1973 341 -3.06 -9.06 -4.71 0.1 122.7 143.75 30582 +1973 342 -3.92 -9.92 -5.57 0 115.67 176.77 30521 +1973 343 -3.6 -9.6 -5.25 0.03 118.24 142.94 30465 +1973 344 -2.65 -8.65 -4.3 0.09 126.19 142.19 30413 +1973 345 -3.03 -9.03 -4.68 0.04 122.96 142.16 30366 +1973 346 -0.01 -6.01 -1.66 0 150.74 173.14 30323 +1973 347 3.72 -2.28 2.07 0 192.42 170.33 30284 +1973 348 2.5 -3.5 0.85 0 177.82 126.69 30251 +1973 349 3.09 -2.91 1.44 0 184.76 126.01 30221 +1973 350 4.81 -1.19 3.16 0 206.34 124.75 30197 +1973 351 -0.26 -6.26 -1.91 0.13 148.25 139.4 30177 +1973 352 0.94 -5.06 -0.71 0.13 160.54 138.84 30162 +1973 353 3.31 -2.69 1.66 0 187.4 125.19 30151 +1973 354 2.87 -3.13 1.22 0 182.14 125.38 30145 +1973 355 3.56 -2.44 1.91 0 190.45 125.02 30144 +1973 356 6.46 0.46 4.81 0 229.04 123.37 30147 +1973 357 9.18 3.18 7.53 0 271.17 121.54 30156 +1973 358 7.22 1.22 5.57 0 240.2 123.02 30169 +1973 359 9.55 3.55 7.9 0 277.38 121.46 30186 +1973 360 6.05 0.05 4.4 0.73 223.21 93.19 30208 +1973 361 4.22 -1.78 2.57 0 198.7 125.66 30235 +1973 362 5.88 -0.12 4.23 0 220.83 125.12 30267 +1973 363 7.54 1.54 5.89 0.26 245.04 93.47 30303 +1973 364 2.79 -3.21 1.14 0 181.2 127.83 30343 +1973 365 4.88 -1.12 3.23 0 207.26 127.26 30388 +1974 1 2.64 -3.36 0.99 0 179.44 129.37 30438 +1974 2 2.95 -3.05 1.3 0 183.09 129.95 30492 +1974 3 5.84 -0.16 4.19 0.03 220.27 96.93 30551 +1974 4 4.66 -1.34 3.01 0 204.37 130.86 30614 +1974 5 6.62 0.62 4.97 0 231.36 130.28 30681 +1974 6 5.53 -0.47 3.88 0.71 215.99 98.9 30752 +1974 7 3.69 -2.31 2.04 0.05 192.05 100.31 30828 +1974 8 1.59 -4.41 -0.06 0 167.55 136.32 30907 +1974 9 0.65 -5.35 -1 0.02 157.49 103.52 30991 +1974 10 4.21 -1.79 2.56 0.02 198.57 103.12 31079 +1974 11 3.85 -2.15 2.2 0 194.04 138.68 31171 +1974 12 -0.64 -6.64 -2.29 0 144.54 141.93 31266 +1974 13 1.2 -4.8 -0.45 0.04 163.31 107.04 31366 +1974 14 -0.47 -6.47 -2.12 0 146.19 144.99 31469 +1974 15 2.41 -3.59 0.76 0 176.78 145.04 31575 +1974 16 3.69 -2.31 2.04 0.2 192.05 109.21 31686 +1974 17 3.98 -2.02 2.33 0 195.67 147.12 31800 +1974 18 5.42 -0.58 3.77 0 214.49 148.1 31917 +1974 19 6.8 0.8 5.15 0 233.98 149.06 32038 +1974 20 8.68 2.68 7.03 0 262.96 149.15 32161 +1974 21 10.88 4.88 9.23 0 300.74 149.15 32289 +1974 22 6.05 0.05 4.4 0 223.21 154.9 32419 +1974 23 6.96 0.96 5.31 0.07 236.34 116.99 32552 +1974 24 6.95 0.95 5.3 0.05 236.19 118.53 32688 +1974 25 8.84 2.84 7.19 1.01 265.57 118.76 32827 +1974 26 5.61 -0.39 3.96 1.13 217.09 122.12 32969 +1974 27 0.57 -5.43 -1.08 0.99 156.66 125.97 33114 +1974 28 3.62 -2.38 1.97 0 191.19 168.41 33261 +1974 29 0.62 -5.38 -1.03 0 157.18 172.55 33411 +1974 30 -1.74 -7.74 -3.39 0 134.23 175.98 33564 +1974 31 3.34 -2.66 1.69 0.01 187.77 131.69 33718 +1974 32 7.8 1.8 6.15 0 249.03 174.33 33875 +1974 33 10.63 4.63 8.98 0 296.23 174.21 34035 +1974 34 10.7 4.7 9.05 0 297.48 176.29 34196 +1974 35 10.22 4.22 8.57 0.03 288.95 134.17 34360 +1974 36 6.27 0.27 4.62 0.18 226.32 138.78 34526 +1974 37 8.75 2.75 7.1 0 264.1 185.23 34694 +1974 38 6.08 0.08 4.43 0 223.63 190.34 34863 +1974 39 10.47 4.47 8.82 0.22 293.37 141.54 35035 +1974 40 10.42 4.42 8.77 0 292.48 191.34 35208 +1974 41 11.39 5.39 9.74 0 310.13 192.79 35383 +1974 42 14.26 8.26 12.61 0 367.81 191.54 35560 +1974 43 12.67 6.67 11.02 0.01 334.82 147.24 35738 +1974 44 5.16 -0.84 3.51 0.09 210.98 155.04 35918 +1974 45 7.65 1.65 6 0.37 246.72 155.33 36099 +1974 46 4.25 -1.75 2.6 0.48 199.08 159.58 36282 +1974 47 6.25 0.25 4.6 0.06 226.04 160.42 36466 +1974 48 6.44 0.44 4.79 0.07 228.76 162.39 36652 +1974 49 10.6 4.6 8.95 0.13 295.69 161.13 36838 +1974 50 10.58 4.58 8.93 0 295.33 217.48 37026 +1974 51 8.25 2.25 6.6 0.18 256.08 167.31 37215 +1974 52 10.26 4.26 8.61 0.32 289.65 167.68 37405 +1974 53 5.52 -0.48 3.87 0.43 215.86 173.65 37596 +1974 54 2.98 -3.02 1.33 0 183.44 236.45 37788 +1974 55 0.62 -5.38 -1.03 0.27 157.18 180.89 37981 +1974 56 3.31 -2.69 1.66 0 187.4 241.91 38175 +1974 57 5.71 -0.29 4.06 0.15 218.47 182.02 38370 +1974 58 5.99 -0.01 4.34 0 222.37 245.35 38565 +1974 59 4.2 -1.8 2.55 0 198.45 249.74 38761 +1974 60 9.06 3.06 7.41 0 269.18 247.56 38958 +1974 61 10.79 4.79 9.14 0.24 299.11 186.17 39156 +1974 62 12.63 6.63 10.98 0.65 334.03 186.22 39355 +1974 63 10.26 4.26 8.61 0.04 289.65 191 39553 +1974 64 11.93 5.93 10.28 0.02 320.35 191.36 39753 +1974 65 9.81 3.81 8.16 0 281.82 260.99 39953 +1974 66 8.83 2.83 7.18 0.45 265.4 198.73 40154 +1974 67 10.31 4.31 8.66 0 290.53 265.89 40355 +1974 68 14.45 8.45 12.8 0 371.94 262.13 40556 +1974 69 14.15 8.15 12.5 0.01 365.44 198.91 40758 +1974 70 7.84 1.84 6.19 0.17 249.65 208.05 40960 +1974 71 2.87 -3.13 1.22 0 182.14 285.54 41163 +1974 72 5.3 -0.7 3.65 0 212.87 286.03 41366 +1974 73 5.79 -0.21 4.14 0 219.58 288.2 41569 +1974 74 8.89 2.89 7.24 0 266.38 287.18 41772 +1974 75 6.89 0.89 5.24 0 235.3 292.44 41976 +1974 76 6.77 0.77 5.12 0.01 233.54 221.42 42179 +1974 77 8.69 2.69 7.04 0.34 263.12 221.55 42383 +1974 78 13.56 7.56 11.91 0.24 352.96 217.74 42587 +1974 79 12.77 6.77 11.12 0.01 336.82 220.81 42791 +1974 80 11.86 5.86 10.21 0 319.01 298.48 42996 +1974 81 12.75 6.75 11.1 0 336.42 299.48 43200 +1974 82 11.42 5.42 9.77 0.18 310.69 228.29 43404 +1974 83 14.65 8.65 13 0.33 376.32 225.68 43608 +1974 84 13.23 7.23 11.58 0 346.14 306.16 43812 +1974 85 14.71 8.71 13.06 0 377.64 305.71 44016 +1974 86 10.25 4.25 8.6 0 289.48 316.15 44220 +1974 87 7.68 1.68 6.03 0 247.19 322.44 44424 +1974 88 10.1 4.1 8.45 0.02 286.85 240.94 44627 +1974 89 13.95 7.95 12.3 0.07 361.17 237.47 44831 +1974 90 12.84 6.84 11.19 0.71 338.22 240.84 45034 +1974 91 18.59 12.59 16.94 0.44 472.07 232.73 45237 +1974 92 15.01 9.01 13.36 0 384.31 321.14 45439 +1974 93 14.57 8.57 12.92 0 374.56 324.25 45642 +1974 94 15.33 9.33 13.68 1.47 391.55 243.53 45843 +1974 95 10.54 4.54 8.89 0 294.62 336.18 46045 +1974 96 13.31 7.31 11.66 0 347.78 333.18 46246 +1974 97 11.12 5.12 9.47 0 305.13 339.34 46446 +1974 98 7.36 1.36 5.71 0 242.31 347.25 46647 +1974 99 10.02 4.02 8.37 0 285.45 345.21 46846 +1974 100 7.13 1.13 5.48 0 238.86 351.58 47045 +1974 101 5.81 -0.19 4.16 0 219.85 355.31 47243 +1974 102 7.45 1.45 5.8 0 243.67 355.02 47441 +1974 103 7.01 1.01 5.36 0 237.08 357.52 47638 +1974 104 8.72 2.72 7.07 0 263.61 356.84 47834 +1974 105 10.13 4.13 8.48 0 287.37 356.34 48030 +1974 106 18.01 12.01 16.36 0 456.79 340.61 48225 +1974 107 18.43 12.43 16.78 0 467.81 341.05 48419 +1974 108 15.22 9.22 13.57 0 389.05 351.09 48612 +1974 109 16.62 10.62 14.97 0 421.88 349.22 48804 +1974 110 14.24 8.24 12.59 0 367.38 356.33 48995 +1974 111 13.68 7.68 12.03 0 355.47 359.11 49185 +1974 112 16.89 10.89 15.24 0 428.48 352.91 49374 +1974 113 17.78 11.78 16.13 0 450.85 351.8 49561 +1974 114 15.51 9.51 13.86 0 395.66 359.21 49748 +1974 115 15.79 9.79 14.14 0.24 402.14 269.95 49933 +1974 116 13.58 7.58 11.93 0 353.38 366.32 50117 +1974 117 10.77 4.77 9.12 0 298.75 373.32 50300 +1974 118 9.26 3.26 7.61 0 272.5 377.33 50481 +1974 119 11.38 5.38 9.73 0.54 309.95 281.02 50661 +1974 120 11.43 5.43 9.78 0 310.88 375.79 50840 +1974 121 12.26 6.26 10.61 0.09 326.74 281.45 51016 +1974 122 13.15 7.15 11.5 0.2 344.5 280.94 51191 +1974 123 14.88 8.88 13.23 1.33 381.41 278.75 51365 +1974 124 17.36 11.36 15.71 0.21 440.17 274.71 51536 +1974 125 14.36 8.36 12.71 0 369.98 374.97 51706 +1974 126 15.15 9.15 13.5 0 387.46 374.06 51874 +1974 127 16.13 10.13 14.48 0.01 410.13 279.34 52039 +1974 128 12.58 6.58 10.93 0 333.03 381.85 52203 +1974 129 17.17 11.17 15.52 0 435.41 371.47 52365 +1974 130 12.91 6.91 11.26 0.02 339.63 287.1 52524 +1974 131 11.83 5.83 10.18 0.2 318.44 289.41 52681 +1974 132 12.48 6.48 10.83 0 331.05 385.37 52836 +1974 133 17.97 11.97 16.32 0 455.76 372.26 52989 +1974 134 15.88 9.88 14.23 0.03 404.24 284.08 53138 +1974 135 14.42 8.42 12.77 0.39 371.28 287.34 53286 +1974 136 16.53 10.53 14.88 0 419.7 378.37 53430 +1974 137 17.67 11.67 16.02 0.34 448.04 281.9 53572 +1974 138 17.84 11.84 16.19 0.02 452.4 281.97 53711 +1974 139 18.98 12.98 17.33 0 482.59 373.18 53848 +1974 140 20.56 14.56 18.91 0 527.26 368.44 53981 +1974 141 20.82 14.82 19.17 0 534.93 367.96 54111 +1974 142 20.16 14.16 18.51 0 515.63 370.72 54238 +1974 143 24.33 18.33 22.68 0.06 648.23 266.52 54362 +1974 144 22.61 16.61 20.96 1.55 590.41 272.12 54483 +1974 145 19.92 13.92 18.27 0.01 508.76 279.74 54600 +1974 146 18.97 12.97 17.32 0 482.32 376.45 54714 +1974 147 15.1 9.1 13.45 1.02 386.34 290.93 54824 +1974 148 15 9 13.35 2.22 384.09 291.41 54931 +1974 149 16.27 10.27 14.62 0.13 413.46 289.16 55034 +1974 150 16.17 10.17 14.52 0.05 411.08 289.61 55134 +1974 151 17.21 11.21 15.56 0 436.41 383.65 55229 +1974 152 25.25 19.25 23.6 0 681.09 354.48 55321 +1974 153 23.83 17.83 22.18 0.03 630.95 270.66 55409 +1974 154 26.87 20.87 25.22 1.04 742.37 260.51 55492 +1974 155 25.46 19.46 23.81 1.46 688.78 265.67 55572 +1974 156 25.48 19.48 23.83 0 689.52 354.45 55648 +1974 157 27.73 21.73 26.08 2.02 776.75 257.73 55719 +1974 158 25.55 19.55 23.9 0.89 692.1 265.84 55786 +1974 159 20.96 14.96 19.31 0 539.11 373.37 55849 +1974 160 17.82 11.82 16.17 0 451.88 383.83 55908 +1974 161 17.85 11.85 16.2 0.41 452.65 287.86 55962 +1974 162 16.44 10.44 14.79 1.13 417.53 290.94 56011 +1974 163 16.61 10.61 14.96 0.2 421.64 290.75 56056 +1974 164 17.02 11.02 15.37 0.07 431.69 289.92 56097 +1974 165 13.04 7.04 11.39 0.76 342.26 297.57 56133 +1974 166 10.95 4.95 9.3 0 302.02 401.26 56165 +1974 167 15.71 9.71 14.06 0 400.28 390.28 56192 +1974 168 17.48 11.48 15.83 0.13 443.2 289.07 56214 +1974 169 16.83 10.83 15.18 0.28 427.01 290.48 56231 +1974 170 11.53 5.53 9.88 0 312.76 400.14 56244 +1974 171 9.25 3.25 7.6 0.04 272.34 303.42 56252 +1974 172 13.68 7.68 12.03 0 355.47 395.47 56256 +1974 173 15.48 9.48 13.83 0.54 394.97 293.25 56255 +1974 174 16.11 10.11 14.46 0 409.66 389.24 56249 +1974 175 16.97 10.97 15.32 0 430.45 386.83 56238 +1974 176 19.09 13.09 17.44 0 485.59 380.38 56223 +1974 177 20.72 14.72 19.07 0 531.97 374.78 56203 +1974 178 20.4 14.4 18.75 0 522.58 375.92 56179 +1974 179 21.34 15.34 19.69 0.14 550.57 279.36 56150 +1974 180 23.59 17.59 21.94 0 622.79 363.6 56116 +1974 181 23.07 17.07 21.42 0 605.43 365.66 56078 +1974 182 23.06 17.06 21.41 0 605.1 365.55 56035 +1974 183 23.12 17.12 21.47 0 607.08 365.14 55987 +1974 184 25.81 19.81 24.16 0 701.77 353.3 55935 +1974 185 24.78 18.78 23.13 0 664.13 357.9 55879 +1974 186 23.98 17.98 22.33 0.3 636.09 270.83 55818 +1974 187 23.13 17.13 21.48 0.09 607.41 273.32 55753 +1974 188 25.9 19.9 24.25 1.03 705.14 264.09 55684 +1974 189 23 17 21.35 0 603.12 364.51 55611 +1974 190 19.04 13.04 17.39 0 484.22 378.32 55533 +1974 191 21.97 15.97 20.32 0.48 570.04 275.91 55451 +1974 192 21.05 15.05 19.4 0 541.8 370.96 55366 +1974 193 21.3 15.3 19.65 0.03 549.35 277.34 55276 +1974 194 24.1 18.1 22.45 0 640.23 358.59 55182 +1974 195 22.32 16.32 20.67 0.1 581.1 274.12 55085 +1974 196 17.73 11.73 16.08 0.08 449.57 285.43 54984 +1974 197 20.81 14.81 19.16 1.27 534.64 277.64 54879 +1974 198 22.03 16.03 20.38 0 571.92 365.32 54770 +1974 199 21.26 15.26 19.61 0 548.14 367.81 54658 +1974 200 22.91 16.91 21.26 0.06 600.17 270.89 54542 +1974 201 17.34 11.34 15.69 0.08 439.67 284.67 54423 +1974 202 17.22 11.22 15.57 0.21 436.66 284.5 54301 +1974 203 16.08 10.08 14.43 0 408.95 381.96 54176 +1974 204 17.42 11.42 15.77 0 441.69 377.73 54047 +1974 205 23.45 17.45 21.8 0.03 618.08 267.39 53915 +1974 206 24.49 18.49 22.84 0.45 653.85 263.74 53780 +1974 207 24.01 18.01 22.36 0.7 637.13 264.78 53643 +1974 208 24.23 18.23 22.58 0.61 644.75 263.61 53502 +1974 209 21.44 15.44 19.79 0 553.62 361.71 53359 +1974 210 19.75 13.75 18.1 0 503.94 366.88 53213 +1974 211 23.31 17.31 21.66 0 613.39 353.25 53064 +1974 212 25.23 19.23 23.58 0.11 680.36 258.32 52913 +1974 213 23.73 17.73 22.08 2.45 627.54 262.53 52760 +1974 214 24.44 18.44 22.79 0.01 652.09 259.79 52604 +1974 215 18.86 12.86 17.21 0.48 479.33 274.44 52445 +1974 216 21.5 15.5 19.85 0.17 555.46 267.11 52285 +1974 217 23.27 17.27 21.62 0.07 612.06 261.48 52122 +1974 218 23.73 17.73 22.08 0.09 627.54 259.51 51958 +1974 219 23.75 17.75 22.1 0.05 628.22 258.69 51791 +1974 220 27.43 21.43 25.78 0 764.6 327.64 51622 +1974 221 25.54 19.54 23.89 1.17 691.73 251.62 51451 +1974 222 24.9 18.9 23.25 0.65 668.43 252.95 51279 +1974 223 25.61 19.61 23.96 0.29 694.32 249.82 51105 +1974 224 27.56 21.56 25.91 0.45 769.85 242.27 50929 +1974 225 27.91 21.91 26.26 0.2 784.11 240.18 50751 +1974 226 26.07 20.07 24.42 1.64 711.55 245.9 50572 +1974 227 28.64 22.64 26.99 0.07 814.58 235.73 50392 +1974 228 24.75 18.75 23.1 0.45 663.06 248.39 50210 +1974 229 24.51 18.51 22.86 0 654.55 330.99 50026 +1974 230 21.91 15.91 20.26 0 568.16 339.66 49842 +1974 231 21.99 15.99 20.34 0.08 570.66 253.45 49656 +1974 232 22.68 16.68 21.03 0.17 592.67 250.59 49469 +1974 233 24.15 18.15 22.5 1.01 641.97 245.35 49280 +1974 234 22.65 16.65 21 0 591.7 331.46 49091 +1974 235 20.98 14.98 19.33 0.27 539.7 251.84 48900 +1974 236 22.27 16.27 20.62 0.02 579.51 247.48 48709 +1974 237 26.73 20.73 25.08 0 736.89 310.54 48516 +1974 238 25.49 19.49 23.84 0.12 689.89 235.76 48323 +1974 239 23.82 17.82 22.17 0.26 630.61 239.69 48128 +1974 240 20.73 14.73 19.08 0.97 532.26 246.51 47933 +1974 241 20.84 14.84 19.19 2.25 535.53 244.97 47737 +1974 242 20.48 14.48 18.83 0.84 524.91 244.54 47541 +1974 243 19.28 13.28 17.63 0.52 490.81 245.87 47343 +1974 244 15.35 9.35 13.7 0.02 392 252.14 47145 +1974 245 21.21 15.21 19.56 0.1 546.63 238.72 46947 +1974 246 18.04 12.04 16.39 0 457.57 325.66 46747 +1974 247 17.42 11.42 15.77 0 441.69 325.43 46547 +1974 248 15.18 9.18 13.53 0 388.14 328.84 46347 +1974 249 22.97 16.97 21.32 0 602.13 304.8 46146 +1974 250 22.32 16.32 20.67 0 581.1 305.14 45945 +1974 251 20.71 14.71 19.06 0 531.67 308.22 45743 +1974 252 20.87 14.87 19.22 0 536.42 305.61 45541 +1974 253 23.01 17.01 21.36 0 603.45 296.63 45339 +1974 254 19.06 13.06 17.41 0.2 484.77 229.99 45136 +1974 255 15.4 9.4 13.75 0 393.14 313.36 44933 +1974 256 14.13 8.13 12.48 0 365.02 313.74 44730 +1974 257 14.68 8.68 13.03 1.12 376.98 232.81 44527 +1974 258 17.35 11.35 15.7 0.08 439.92 226.56 44323 +1974 259 17.47 11.47 15.82 0.06 442.95 224.53 44119 +1974 260 22.04 16.04 20.39 0 572.24 284.44 43915 +1974 261 18.99 12.99 17.34 0 482.86 290.77 43711 +1974 262 18.63 12.63 16.98 0.14 473.14 217.02 43507 +1974 263 22.53 16.53 20.88 0.92 587.83 206.93 43303 +1974 264 22.11 16.11 20.46 0.06 574.44 206.06 43099 +1974 265 18.56 12.56 16.91 0 471.27 282.24 42894 +1974 266 22.4 16.4 20.75 0 583.66 269.22 42690 +1974 267 18.3 12.3 16.65 0 464.38 277.8 42486 +1974 268 18.2 12.2 16.55 0 461.75 275.52 42282 +1974 269 17.72 11.72 16.07 1.24 449.31 205.62 42078 +1974 270 18.12 12.12 16.47 0.18 459.66 202.98 41875 +1974 271 13.55 7.55 11.9 0.73 352.75 208.03 41671 +1974 272 17.33 11.33 15.68 1.43 439.42 200.37 41468 +1974 273 16.94 10.94 15.29 0.82 429.71 199.14 41265 +1974 274 5.21 -0.79 3.56 0.02 211.65 210.52 41062 +1974 275 8.19 2.19 6.54 0 255.13 274.47 40860 +1974 276 13.05 7.05 11.4 0 342.47 264.74 40658 +1974 277 13.09 7.09 11.44 0.02 343.28 196.5 40456 +1974 278 12.33 6.33 10.68 0.67 328.11 195.26 40255 +1974 279 15.66 9.66 14.01 0.93 399.12 188.85 40054 +1974 280 15.13 9.13 13.48 0.43 387.01 187.62 39854 +1974 281 15.34 9.34 13.69 0 391.77 247.08 39654 +1974 282 14.46 8.46 12.81 1.3 372.15 184.44 39455 +1974 283 11.08 5.08 9.43 0.17 304.4 186.25 39256 +1974 284 11.26 5.26 9.61 0.55 307.72 183.78 39058 +1974 285 12.12 6.12 10.47 1.82 324.02 180.87 38861 +1974 286 9.83 3.83 8.18 1.19 282.17 181.11 38664 +1974 287 11.7 5.7 10.05 0.83 315.97 177.03 38468 +1974 288 3.71 -2.29 2.06 0 192.3 241.95 38273 +1974 289 -0.01 -6.01 -1.66 0.08 150.74 216.33 38079 +1974 290 6.63 0.63 4.98 0.14 231.5 175.24 37885 +1974 291 5.61 -0.39 3.96 0.35 217.09 173.9 37693 +1974 292 6.19 0.19 4.54 0.93 225.19 171.43 37501 +1974 293 5.82 -0.18 4.17 0.83 219.99 169.6 37311 +1974 294 10.61 4.61 8.96 0.15 295.87 163.58 37121 +1974 295 12.25 6.25 10.6 0 326.54 213.16 36933 +1974 296 9.02 3.02 7.37 0.27 268.52 160.87 36745 +1974 297 8.21 2.21 6.56 0.32 255.44 159.45 36560 +1974 298 5.5 -0.5 3.85 0.58 215.58 159.38 36375 +1974 299 7.52 1.52 5.87 0.69 244.74 155.88 36191 +1974 300 7.69 1.69 6.04 0.14 247.34 153.73 36009 +1974 301 9.8 3.8 8.15 0.03 281.65 150.2 35829 +1974 302 11.21 5.21 9.56 1.09 306.79 147.04 35650 +1974 303 10.72 4.72 9.07 0.14 297.85 145.54 35472 +1974 304 10.41 4.41 8.76 0.05 292.3 143.95 35296 +1974 305 9.2 3.2 7.55 0.03 271.5 142.86 35122 +1974 306 10.01 4.01 8.36 0.21 285.28 140.54 34950 +1974 307 12.44 6.44 10.79 0.02 330.27 136.6 34779 +1974 308 12.13 6.13 10.48 0 324.21 179.93 34610 +1974 309 13.93 7.93 12.28 0 360.75 175.41 34444 +1974 310 11.9 5.9 10.25 0 319.78 175.5 34279 +1974 311 11.48 5.48 9.83 0.01 311.82 130.37 34116 +1974 312 9.85 3.85 8.2 0 282.51 172.92 33956 +1974 313 10.11 4.11 8.46 0 287.02 170.55 33797 +1974 314 10.26 4.26 8.61 0 289.65 168.47 33641 +1974 315 8.64 2.64 6.99 0 262.32 167.48 33488 +1974 316 11 5 9.35 0 302.93 163.05 33337 +1974 317 9.22 3.22 7.57 0 271.84 162.6 33188 +1974 318 7.62 1.62 5.97 0 246.26 161.65 33042 +1974 319 7.25 1.25 5.6 0.18 240.65 120.19 32899 +1974 320 5.36 -0.64 3.71 0.02 213.68 119.84 32758 +1974 321 2.82 -3.18 1.17 1.81 181.55 119.47 32620 +1974 322 0.68 -5.32 -0.97 0.08 157.8 118.95 32486 +1974 323 -1.27 -7.27 -2.92 0.16 138.55 159.67 32354 +1974 324 -1.68 -7.68 -3.33 0 134.77 197.4 32225 +1974 325 6.76 0.76 5.11 0.16 233.39 112.09 32100 +1974 326 12.07 6.07 10.42 0 323.05 143.41 31977 +1974 327 11.39 5.39 9.74 0 310.13 142.27 31858 +1974 328 11.46 5.46 9.81 0 311.44 140.26 31743 +1974 329 9.85 3.85 8.2 0 282.51 140.26 31631 +1974 330 5.81 -0.19 4.16 0.01 219.85 106.43 31522 +1974 331 5.35 -0.65 3.7 0 213.54 140.89 31417 +1974 332 3.59 -2.41 1.94 0.15 190.82 105.23 31316 +1974 333 3.8 -2.2 2.15 0.41 193.42 104.32 31218 +1974 334 5.6 -0.4 3.95 0 216.95 136.9 31125 +1974 335 3.87 -2.13 2.22 0.69 194.29 102.57 31035 +1974 336 0.3 -5.7 -1.35 0.14 153.88 103.12 30949 +1974 337 4.24 -1.76 2.59 0 198.96 133.81 30867 +1974 338 4.09 -1.91 2.44 0 197.05 132.96 30790 +1974 339 3.44 -2.56 1.79 0 188.98 132.53 30716 +1974 340 3.25 -2.75 1.6 0 186.68 131.89 30647 +1974 341 3.07 -2.93 1.42 0.01 184.52 98.3 30582 +1974 342 3.79 -2.21 2.14 0.87 193.29 97.44 30521 +1974 343 3.05 -2.95 1.4 0.1 184.28 97.11 30465 +1974 344 4.72 -1.28 3.07 0 205.16 127.43 30413 +1974 345 7.16 1.16 5.51 0 239.31 125.49 30366 +1974 346 10.15 4.15 8.5 0 287.72 122.73 30323 +1974 347 9.31 3.31 7.66 0 273.34 122.81 30284 +1974 348 9.02 3.02 7.37 0 268.52 122.68 30251 +1974 349 4.72 -1.28 3.07 0.59 205.16 93.85 30221 +1974 350 0.73 -5.27 -0.92 0 158.33 126.8 30197 +1974 351 0.6 -5.4 -1.05 0.21 156.97 94.97 30177 +1974 352 5.59 -0.41 3.94 0 216.82 123.98 30162 +1974 353 8.48 2.48 6.83 0 259.74 122.01 30151 +1974 354 9.85 3.85 8.2 0 282.51 120.95 30145 +1974 355 7.15 1.15 5.5 0 239.16 122.9 30144 +1974 356 9.36 3.36 7.71 0 274.18 121.35 30147 +1974 357 12.51 6.51 10.86 0 331.65 118.75 30156 +1974 358 12.34 6.34 10.69 0 328.3 118.99 30169 +1974 359 16.67 10.67 15.02 0.09 423.1 85.92 30186 +1974 360 7.58 1.58 5.93 0 245.65 123.25 30208 +1974 361 10.76 4.76 9.11 0 298.57 121.17 30235 +1974 362 6.6 0.6 4.95 0 231.07 124.67 30267 +1974 363 6.78 0.78 5.13 0.1 233.69 93.85 30303 +1974 364 7.49 1.49 5.84 0.01 244.28 93.79 30343 +1974 365 4.96 -1.04 3.31 0 208.32 127.22 30388 +1975 1 3.2 -2.8 1.55 0 186.07 129.08 30438 +1975 2 2.06 -3.94 0.41 0.3 172.79 97.8 30492 +1975 3 -1.47 -7.47 -3.12 0.08 136.7 143.12 30551 +1975 4 1.08 -4.92 -0.57 0 162.03 175.95 30614 +1975 5 -0.59 -6.59 -2.24 0 145.02 177.24 30681 +1975 6 -0.62 -6.62 -2.27 0 144.73 178.05 30752 +1975 7 -1.6 -7.6 -3.25 0 135.5 179.14 30828 +1975 8 0.91 -5.09 -0.74 0 160.22 136.65 30907 +1975 9 4.08 -1.92 2.43 0 196.93 136.26 30991 +1975 10 4.48 -1.52 2.83 0 202.04 137.33 31079 +1975 11 8.1 2.1 6.45 0.04 253.71 101.91 31171 +1975 12 9.91 3.91 8.26 0 283.55 135.41 31266 +1975 13 4.55 -1.45 2.9 0 202.94 140.9 31366 +1975 14 9.32 3.32 7.67 0.18 273.51 104.22 31469 +1975 15 7.71 1.71 6.06 0 247.65 141.65 31575 +1975 16 7.6 1.6 5.95 0 245.96 143 31686 +1975 17 8.87 2.87 7.22 0 266.06 143.66 31800 +1975 18 7.99 1.99 6.34 0 251.99 146.24 31917 +1975 19 8.46 2.46 6.81 0 259.42 147.77 32038 +1975 20 5.79 -0.21 4.14 0 219.58 151.35 32161 +1975 21 4.97 -1.03 3.32 0 208.45 153.91 32289 +1975 22 5.86 -0.14 4.21 0 220.55 155.04 32419 +1975 23 7.05 1.05 5.4 0 237.67 155.92 32552 +1975 24 3.95 -2.05 2.3 0 195.29 160.15 32688 +1975 25 6.53 0.53 4.88 0 230.05 160.24 32827 +1975 26 8.2 2.2 6.55 0 255.28 160.8 32969 +1975 27 12.06 6.06 10.41 0 322.85 159.06 33114 +1975 28 11.89 5.89 10.24 0 319.59 161.4 33261 +1975 29 16.35 10.35 14.7 0 415.37 158.11 33411 +1975 30 13.63 7.63 11.98 0 354.42 163.87 33564 +1975 31 15.05 9.05 13.4 0 385.21 164.33 33718 +1975 32 15.62 9.62 13.97 0 398.2 165.56 33875 +1975 33 15.75 9.75 14.1 0 401.21 167.9 34035 +1975 34 14.14 8.14 12.49 0 365.23 172.21 34196 +1975 35 11.01 5.01 9.36 0 303.11 178.05 34360 +1975 36 11.1 5.1 9.45 0 304.76 180.41 34526 +1975 37 10.57 4.57 8.92 0 295.15 183.36 34694 +1975 38 8.88 2.88 7.23 0 266.22 187.81 34863 +1975 39 3.03 -2.97 1.38 0 184.04 195.24 35035 +1975 40 3.67 -2.33 2.02 0 191.8 197.42 35208 +1975 41 4.73 -1.27 3.08 0 205.29 199.25 35383 +1975 42 6.13 0.13 4.48 0 224.34 200.65 35560 +1975 43 6.26 0.26 4.61 0 226.18 203.23 35738 +1975 44 3.88 -2.12 2.23 0 194.41 207.73 35918 +1975 45 1.14 -4.86 -0.51 0 162.67 212.28 36099 +1975 46 3.14 -2.86 1.49 0 185.35 213.62 36282 +1975 47 4.21 -1.79 2.56 0 198.57 215.63 36466 +1975 48 -1.22 -7.22 -2.87 0 139.02 222.1 36652 +1975 49 -3.12 -9.12 -4.77 0 122.2 225.92 36838 +1975 50 -4.77 -10.77 -6.42 0 109.06 229.41 37026 +1975 51 -5.96 -11.96 -7.61 0 100.35 232.94 37215 +1975 52 1.42 -4.58 -0.23 0 165.69 231.83 37405 +1975 53 -1.66 -7.66 -3.31 0 134.96 236.76 37596 +1975 54 -3.03 -9.03 -4.68 0 122.96 240.31 37788 +1975 55 0.25 -5.75 -1.4 0 153.37 241.43 37981 +1975 56 2.19 -3.81 0.54 0 174.26 242.79 38175 +1975 57 4.54 -1.46 2.89 0 202.81 243.77 38370 +1975 58 5.02 -0.98 3.37 0 209.11 246.28 38565 +1975 59 3.93 -2.07 2.28 0 195.04 249.97 38761 +1975 60 8.39 2.39 6.74 0 258.3 248.35 38958 +1975 61 11.32 5.32 9.67 0 308.83 247.49 39156 +1975 62 13.42 7.42 11.77 0.15 350.05 185.28 39355 +1975 63 13.59 7.59 11.94 0.26 353.59 187.28 39553 +1975 64 12.01 6.01 10.36 1.22 321.89 191.27 39753 +1975 65 11.52 5.52 9.87 0.11 312.57 193.95 39953 +1975 66 13.19 7.19 11.54 0 345.32 258.68 40154 +1975 67 11.58 5.58 9.93 0.13 313.7 198.04 40355 +1975 68 11.28 5.28 9.63 0.51 308.09 200.5 40556 +1975 69 11.25 5.25 9.6 1.3 307.53 202.47 40758 +1975 70 9.8 3.8 8.15 0.04 281.65 206.14 40960 +1975 71 7.71 1.71 6.06 0.5 247.65 210.35 41163 +1975 72 6.01 0.01 4.36 0.55 222.65 213.95 41366 +1975 73 5.33 -0.67 3.68 0.02 213.27 216.52 41569 +1975 74 5.21 -0.79 3.56 0 211.65 291.59 41772 +1975 75 7.38 1.38 5.73 0 242.61 291.85 41976 +1975 76 8.59 2.59 6.94 0.01 261.51 219.7 42179 +1975 77 7.76 1.76 6.11 0 248.42 296.62 42383 +1975 78 9.04 3.04 7.39 0 268.85 297.58 42587 +1975 79 7.95 1.95 6.3 0 251.36 301.77 42791 +1975 80 7.57 1.57 5.92 0 245.5 304.81 42996 +1975 81 11.74 5.74 10.09 0 316.72 301.23 43200 +1975 82 8.55 2.55 6.9 0 260.86 308.74 43404 +1975 83 9.94 3.94 8.29 0 284.07 309.21 43608 +1975 84 7.06 1.06 5.41 0.03 237.82 236.83 43812 +1975 85 10 4 8.35 0 285.11 314.14 44016 +1975 86 8.67 2.67 7.02 0 262.8 318.52 44220 +1975 87 9.93 3.93 8.28 0 283.89 319.18 44424 +1975 88 10.12 4.12 8.47 0.75 287.2 240.92 44627 +1975 89 7.36 1.36 5.71 0.86 242.31 245.65 44831 +1975 90 12.27 6.27 10.62 0 326.93 322.18 45034 +1975 91 16.27 10.27 14.62 0 413.46 316.11 45237 +1975 92 14.89 8.89 13.24 0.24 381.63 241.05 45439 +1975 93 13.93 7.93 12.28 0 360.75 325.59 45642 +1975 94 13.28 7.28 11.63 0 347.17 329.03 45843 +1975 95 13.12 7.12 11.47 0.04 343.89 248.6 46045 +1975 96 13.06 7.06 11.41 0.99 342.67 250.26 46246 +1975 97 6.75 0.75 5.1 0.53 233.25 259.57 46446 +1975 98 8.47 2.47 6.82 0 259.58 345.64 46647 +1975 99 7.85 1.85 6.2 0 249.81 348.58 46846 +1975 100 11.82 5.82 10.17 0 318.25 343.99 47045 +1975 101 17.98 11.98 16.33 0 456.02 331.96 47243 +1975 102 15.9 9.9 14.25 0 404.71 339.12 47441 +1975 103 15.62 9.62 13.97 0 398.2 341.59 47638 +1975 104 15.23 9.23 13.58 0.06 389.27 258.23 47834 +1975 105 15.04 9.04 13.39 0.02 384.99 259.88 48030 +1975 106 12.87 6.87 11.22 0 338.83 352.86 48225 +1975 107 11.62 5.62 9.97 0 314.45 356.99 48419 +1975 108 9.75 3.75 8.1 0 280.79 362.09 48612 +1975 109 12.85 6.85 11.2 0 338.42 357.91 48804 +1975 110 6.96 0.96 5.31 0.07 236.34 277.14 48995 +1975 111 9.98 3.98 8.33 0 284.76 366.32 49185 +1975 112 11.27 5.27 9.62 0.18 307.9 274.14 49374 +1975 113 13.27 7.27 11.62 1.44 346.96 272.14 49561 +1975 114 16.11 10.11 14.46 0 409.66 357.71 49748 +1975 115 17.07 11.07 15.42 0.01 432.93 267.46 49933 +1975 116 15.34 9.34 13.69 0 391.77 362.24 50117 +1975 117 12.35 6.35 10.7 0 328.5 370.24 50300 +1975 118 8.8 2.8 7.15 0 264.91 378.09 50481 +1975 119 11.03 5.03 9.38 0 303.48 375.37 50661 +1975 120 13.06 7.06 11.41 0 342.67 372.45 50840 +1975 121 16.04 10.04 14.39 0 408 366.55 51016 +1975 122 17.29 11.29 15.64 0.02 438.42 273.29 51191 +1975 123 18.48 12.48 16.83 1.84 469.14 271.48 51365 +1975 124 15.71 9.71 14.06 0 400.28 370.68 51536 +1975 125 16.86 10.86 15.21 0.38 427.74 276.47 51706 +1975 126 24.32 18.32 22.67 0 647.88 344.21 51874 +1975 127 19.69 13.69 18.04 0.2 502.24 271.56 52039 +1975 128 19.1 13.1 17.45 0.24 485.86 273.7 52203 +1975 129 19.3 13.3 17.65 0.04 491.36 273.85 52365 +1975 130 19.55 13.55 17.9 0.11 498.32 273.83 52524 +1975 131 19.64 13.64 17.99 1.15 500.84 274.2 52681 +1975 132 21.7 15.7 20.05 0 561.62 359.32 52836 +1975 133 19.7 13.7 18.05 0 502.53 366.9 52989 +1975 134 18.69 12.69 17.04 0.5 474.75 278.09 53138 +1975 135 16.21 10.21 14.56 0.32 412.03 283.95 53286 +1975 136 13.57 7.57 11.92 0.4 353.17 289.32 53430 +1975 137 10.68 4.68 9.03 2.4 297.12 294.4 53572 +1975 138 8.49 2.49 6.84 0 259.9 397.08 53711 +1975 139 8.05 2.05 6.4 0 252.93 398.51 53848 +1975 140 11.89 5.89 10.24 0 319.59 391.94 53981 +1975 141 16.29 10.29 14.64 0.04 413.94 286.46 54111 +1975 142 16.2 10.2 14.55 0.09 411.79 287.01 54238 +1975 143 17.7 11.7 16.05 0 448.8 379.01 54362 +1975 144 23.77 17.77 22.12 0 628.9 358.16 54483 +1975 145 25.51 19.51 23.86 0 690.62 351.05 54600 +1975 146 25.6 19.6 23.95 0 693.95 350.98 54714 +1975 147 22.76 16.76 21.11 0 595.27 363.52 54824 +1975 148 24.59 18.59 22.94 0 657.38 356.32 54931 +1975 149 22.29 16.29 20.64 0 580.15 366.01 55034 +1975 150 24.31 18.31 22.66 0 647.54 358.14 55134 +1975 151 20.13 14.13 18.48 0 514.76 374.52 55229 +1975 152 19.07 13.07 17.42 0 485.04 378.12 55321 +1975 153 22.36 16.36 20.71 0.82 582.38 275.09 55409 +1975 154 21.97 15.97 20.32 0 570.04 368.59 55492 +1975 155 22.72 16.72 21.07 0.04 593.97 274.41 55572 +1975 156 20.94 14.94 19.29 0.18 538.51 279.65 55648 +1975 157 20.48 14.48 18.83 0.09 524.91 280.99 55719 +1975 158 19.43 13.43 17.78 0 494.97 378.37 55786 +1975 159 20.06 14.06 18.41 0.05 512.76 282.38 55849 +1975 160 23.8 17.8 22.15 0 629.93 362.56 55908 +1975 161 21.62 15.62 19.97 0 559.15 371.22 55962 +1975 162 20.61 14.61 18.96 0 528.72 374.92 56011 +1975 163 22.5 16.5 20.85 0 586.86 368.14 56056 +1975 164 24.5 18.5 22.85 0 654.2 359.94 56097 +1975 165 24.52 18.52 22.87 0 654.91 359.94 56133 +1975 166 26.2 20.2 24.55 0 716.48 352.34 56165 +1975 167 27.08 21.08 25.43 0.23 750.64 260.99 56192 +1975 168 21.64 15.64 19.99 0.77 559.77 278.74 56214 +1975 169 23.23 17.23 21.58 0.69 610.73 274.11 56231 +1975 170 21.31 15.31 19.66 0.4 549.66 279.66 56244 +1975 171 19.22 13.22 17.57 0.64 489.16 285.1 56252 +1975 172 17.95 11.95 16.3 0.12 455.24 288.07 56256 +1975 173 15.53 9.53 13.88 1.88 396.12 293.15 56255 +1975 174 15.71 9.71 14.06 1.64 400.28 292.73 56249 +1975 175 13.6 7.6 11.95 0.59 353.8 296.64 56238 +1975 176 14.16 8.16 12.51 0.35 365.66 295.62 56223 +1975 177 14.91 8.91 13.26 1.39 382.08 294.15 56203 +1975 178 15.52 9.52 13.87 3.05 395.89 293 56179 +1975 179 16.35 10.35 14.7 0.15 415.37 291.25 56150 +1975 180 12.72 6.72 11.07 0 335.82 397.16 56116 +1975 181 10.17 4.17 8.52 0.09 288.07 301.72 56078 +1975 182 15.78 9.78 14.13 0 401.91 389.53 56035 +1975 183 18.92 12.92 17.27 0.22 480.96 285.16 55987 +1975 184 22.67 16.67 21.02 0 592.35 366.78 55935 +1975 185 26.62 20.62 24.97 0.38 732.62 262.02 55879 +1975 186 27.62 21.62 25.97 0.54 772.27 258.08 55818 +1975 187 26.97 20.97 25.32 0.15 746.3 260.41 55753 +1975 188 24.91 18.91 23.26 1.34 668.79 267.48 55684 +1975 189 21.33 15.33 19.68 0.22 550.27 278.16 55611 +1975 190 22.5 16.5 20.85 1.84 586.86 274.59 55533 +1975 191 20.84 14.84 19.19 0.55 535.53 279.01 55451 +1975 192 24.34 18.34 22.69 0.12 648.58 268.53 55366 +1975 193 26.22 20.22 24.57 0.14 717.24 261.96 55276 +1975 194 21.85 15.85 20.2 0.72 566.28 275.66 55182 +1975 195 18.02 12.02 16.37 0.16 457.05 285.09 55085 +1975 196 17.09 11.09 15.44 0 433.42 382.43 54984 +1975 197 19.62 13.62 17.97 0 500.28 374.23 54879 +1975 198 20.99 14.99 19.34 0 540 369.13 54770 +1975 199 19.96 13.96 18.31 0 509.9 372.32 54658 +1975 200 21.11 15.11 19.46 2.82 543.61 275.96 54542 +1975 201 18.46 12.46 16.81 0.41 468.61 282.18 54423 +1975 202 20.67 14.67 19.02 0.02 530.49 276.35 54301 +1975 203 21.31 15.31 19.66 0.3 549.66 274.28 54176 +1975 204 18.79 12.79 17.14 0 477.44 373.63 54047 +1975 205 25.05 19.05 23.4 0.01 673.83 262.32 53915 +1975 206 23.36 17.36 21.71 0.94 615.06 267.25 53780 +1975 207 27.18 21.18 25.53 0 754.61 338.64 53643 +1975 208 30.13 24.13 28.48 2.21 879.89 241.69 53502 +1975 209 25.56 19.56 23.91 0 692.47 345.06 53359 +1975 210 24.65 18.65 23 0.12 659.51 261.35 53213 +1975 211 24.34 18.34 22.69 0.23 648.58 261.77 53064 +1975 212 24.74 18.74 23.09 0 662.71 346.56 52913 +1975 213 19.63 13.63 17.98 2.46 500.56 273.7 52760 +1975 214 23.03 17.03 21.38 0.64 604.11 264.08 52604 +1975 215 22.46 16.46 20.81 0.01 585.58 265.22 52445 +1975 216 25.18 19.18 23.53 0 678.54 341.57 52285 +1975 217 23.93 17.93 22.28 0 634.38 346 52122 +1975 218 26.09 20.09 24.44 0 712.3 335.87 51958 +1975 219 26.46 20.46 24.81 0 726.43 333.16 51791 +1975 220 22.05 16.05 20.4 0.16 572.55 262.89 51622 +1975 221 25.4 19.4 23.75 0 686.58 336.11 51451 +1975 222 26.6 20.6 24.95 0.2 731.84 247.27 51279 +1975 223 25.33 19.33 23.68 0.07 684.01 250.74 51105 +1975 224 19.64 13.64 17.99 0.19 500.84 265.86 50929 +1975 225 20.36 14.36 18.71 0 521.41 351.03 50751 +1975 226 23.46 17.46 21.81 0.74 618.41 254.1 50572 +1975 227 21.35 15.35 19.7 0.32 550.88 258.97 50392 +1975 228 21.47 15.47 19.82 0 554.54 343.67 50210 +1975 229 22.27 16.27 20.62 0 579.51 339.62 50026 +1975 230 25.1 19.1 23.45 0.02 675.64 245.49 49842 +1975 231 19.64 13.64 17.99 0.81 500.84 259.29 49656 +1975 232 20.21 14.21 18.56 0.33 517.07 256.93 49469 +1975 233 20.04 14.04 18.39 0.28 512.18 256.28 49280 +1975 234 17.8 11.8 16.15 0.28 451.37 260.17 49091 +1975 235 20.68 14.68 19.03 0.21 530.79 252.58 48900 +1975 236 19.82 13.82 18.17 0.09 505.92 253.55 48709 +1975 237 22.16 16.16 20.51 0.42 576.02 246.56 48516 +1975 238 15.42 9.42 13.77 0.31 393.6 259.99 48323 +1975 239 17.07 11.07 15.42 0.3 432.93 255.76 48128 +1975 240 23.79 17.79 22.14 0.14 629.58 238.51 47933 +1975 241 19.65 13.65 18 0.02 501.12 247.74 47737 +1975 242 23.68 17.68 22.03 0 625.84 315.09 47541 +1975 243 22.07 16.07 20.42 0 573.18 319.04 47343 +1975 244 19.31 13.31 17.66 0 491.64 325.92 47145 +1975 245 18.41 12.41 16.76 0 467.28 326.63 46947 +1975 246 15.32 9.32 13.67 0 391.32 332.38 46747 +1975 247 15.66 9.66 14.01 0 399.12 329.72 46547 +1975 248 16.46 10.46 14.81 0.29 418.01 244.4 46347 +1975 249 18.74 12.74 17.09 0 476.09 317.92 46146 +1975 250 19.91 13.91 18.26 0 508.47 312.68 45945 +1975 251 20.58 14.58 18.93 0.2 527.84 231.46 45743 +1975 252 16.02 10.02 14.37 0 407.53 318.54 45541 +1975 253 21.27 15.27 19.62 0.01 548.44 226.74 45339 +1975 254 20.72 14.72 19.07 0 531.97 301.91 45136 +1975 255 19.21 13.21 17.56 0.06 488.88 228.01 44933 +1975 256 18.42 12.42 16.77 0 467.55 303.88 44730 +1975 257 19.67 13.67 18.02 0.19 501.68 223.79 44527 +1975 258 20.4 14.4 18.75 0.52 522.58 220.52 44323 +1975 259 22.29 16.29 20.64 0 580.15 285.94 44119 +1975 260 18.63 12.63 16.98 0 473.14 294.11 43915 +1975 261 20.35 14.35 18.7 0.02 521.12 215.31 43711 +1975 262 19.39 13.39 17.74 0 493.86 287.38 43507 +1975 263 20.02 14.02 18.37 0.02 511.61 212.46 43303 +1975 264 23.19 17.19 21.54 0 609.4 271.34 43099 +1975 265 26.17 20.17 24.52 0.15 715.34 193.99 42894 +1975 266 27.71 21.71 26.06 0 775.93 250.32 42690 +1975 267 23.28 17.28 21.63 0 612.39 263.91 42486 +1975 268 21.34 15.34 19.69 0 550.57 267.32 42282 +1975 269 23.52 17.52 21.87 0 620.43 258.35 42078 +1975 270 27.65 21.65 26 0 773.49 241.15 41875 +1975 271 26.96 20.96 25.31 0 745.9 241.46 41671 +1975 272 24.42 18.42 22.77 0.01 651.39 185.94 41468 +1975 273 22.76 16.76 21.11 0.7 595.27 188.06 41265 +1975 274 11.97 5.97 10.32 0 321.12 272 41062 +1975 275 13.77 7.77 12.12 0 357.36 266.23 40860 +1975 276 10.38 4.38 8.73 0.17 291.77 201.62 40658 +1975 277 10.59 4.59 8.94 1.43 295.51 199.37 40456 +1975 278 12.03 6.03 10.38 0.01 322.28 195.6 40255 +1975 279 13.74 7.74 12.09 0.07 356.73 191.42 40054 +1975 280 7.93 1.93 6.28 0.06 251.05 195.58 39854 +1975 281 10.1 4.1 8.45 0.06 286.85 191.47 39654 +1975 282 12.07 6.07 10.42 0 323.05 249.75 39455 +1975 283 9.76 3.76 8.11 0 280.97 250.09 39256 +1975 284 9.07 3.07 7.42 0.24 269.35 185.92 39058 +1975 285 11.01 5.01 9.36 0.18 303.11 182.04 38861 +1975 286 11.65 5.65 10 0.17 315.02 179.29 38664 +1975 287 8.9 2.9 7.25 0.04 266.55 179.72 38468 +1975 288 12.66 6.66 11.01 0 334.62 231.88 38273 +1975 289 9.17 3.17 7.52 0 271 233.82 38079 +1975 290 14.98 8.98 13.33 0 383.64 222.8 37885 +1975 291 17.02 11.02 15.37 0 431.69 216.58 37693 +1975 292 14 8 12.35 0 362.24 219.04 37501 +1975 293 16.55 10.55 14.9 0 420.19 212.15 37311 +1975 294 11.57 5.57 9.92 0.24 313.51 162.67 37121 +1975 295 12.52 6.52 10.87 0.31 331.84 159.6 36933 +1975 296 13.4 7.4 11.75 0.28 349.64 156.75 36745 +1975 297 15.1 9.1 13.45 0.71 386.34 152.82 36560 +1975 298 13.81 7.81 12.16 0.02 358.21 152.36 36375 +1975 299 13.7 7.7 12.05 0 355.89 200.55 36191 +1975 300 18.53 12.53 16.88 0 470.47 190.08 36009 +1975 301 14.68 8.68 13.03 0.88 376.98 145.53 35829 +1975 302 14.74 8.74 13.09 0.67 378.3 143.54 35650 +1975 303 14.53 8.53 12.88 0 373.68 189.16 35472 +1975 304 14.32 8.32 12.67 1.19 369.11 140.29 35296 +1975 305 7.44 1.44 5.79 0.27 243.52 144.13 35122 +1975 306 8.22 2.22 6.57 0 255.6 189.18 34950 +1975 307 7.86 1.86 6.21 0 249.96 187 34779 +1975 308 8.77 2.77 7.12 0.07 264.42 137.65 34610 +1975 309 7.79 1.79 6.14 0 248.88 182.12 34444 +1975 310 5.65 -0.35 4 0.03 217.64 136.09 34279 +1975 311 3.01 -2.99 1.36 0.11 183.8 135.83 34116 +1975 312 5.14 -0.86 3.49 0 210.72 176.97 33956 +1975 313 -1.43 -7.43 -3.08 0.02 137.07 173.15 33797 +1975 314 -0.57 -6.57 -2.22 0.35 145.22 172.51 33641 +1975 315 4.51 -1.49 2.86 0.18 202.42 167.99 33488 +1975 316 1.77 -4.23 0.12 0 169.54 210.15 33337 +1975 317 3.74 -2.26 2.09 0 192.67 166.83 33188 +1975 318 6.94 0.94 5.29 0 236.04 162.2 33042 +1975 319 6.13 0.13 4.48 0 224.34 161.11 32899 +1975 320 6.48 0.48 4.83 0 229.33 158.98 32758 +1975 321 8.95 2.95 7.3 0.06 267.37 116.16 32620 +1975 322 9.28 3.28 7.63 0.08 272.84 114.59 32486 +1975 323 7.86 1.86 6.21 0 249.96 152.37 32354 +1975 324 5.5 -0.5 3.85 0 215.58 152.06 32225 +1975 325 3.52 -2.48 1.87 1.87 189.96 113.69 32100 +1975 326 5.62 -0.38 3.97 0 217.23 148.79 31977 +1975 327 5.45 -0.55 3.8 0 214.9 147.06 31858 +1975 328 7.56 1.56 5.91 0 245.35 143.6 31743 +1975 329 10.47 4.47 8.82 0 293.37 139.72 31631 +1975 330 9.2 3.2 7.55 0.2 271.5 104.54 31522 +1975 331 8.84 2.84 7.19 0 265.57 138.38 31417 +1975 332 8.78 2.78 7.13 0 264.59 136.8 31316 +1975 333 5.51 -0.49 3.86 0 215.72 138.05 31218 +1975 334 5.82 -0.18 4.17 0 219.99 136.76 31125 +1975 335 2.51 -3.49 0.86 0.14 177.93 103.13 31035 +1975 336 1.76 -4.24 0.11 0 169.43 136.8 30949 +1975 337 2.08 -3.92 0.43 0 173.01 134.97 30867 +1975 338 1.55 -4.45 -0.1 0 167.11 134.28 30790 +1975 339 -0.85 -6.85 -2.5 0 142.52 134.55 30716 +1975 340 -0.8 -6.8 -2.45 0 143 133.78 30647 +1975 341 1.02 -4.98 -0.63 0 161.39 132.07 30582 +1975 342 0.31 -5.69 -1.34 0.02 153.98 98.71 30521 +1975 343 1.47 -4.53 -0.18 0 166.24 130.26 30465 +1975 344 -0.32 -6.32 -1.97 0 147.66 129.91 30413 +1975 345 5.38 -0.62 3.73 0 213.95 126.62 30366 +1975 346 4.56 -1.44 2.91 0 203.07 126.55 30323 +1975 347 1.2 -4.8 -0.45 0 163.31 127.66 30284 +1975 348 0.56 -5.44 -1.09 0 156.56 127.59 30251 +1975 349 -0.1 -6.1 -1.75 0 149.84 127.49 30221 +1975 350 3.78 -2.22 2.13 0 193.17 125.32 30197 +1975 351 0.26 -5.74 -1.39 0 153.47 126.78 30177 +1975 352 3.52 -2.48 1.87 0 189.96 125.14 30162 +1975 353 4.84 -1.16 3.19 0.12 206.73 93.27 30151 +1975 354 8.16 2.16 6.51 0.24 254.65 91.65 30145 +1975 355 8.27 2.27 6.62 0 256.39 122.13 30144 +1975 356 8.21 2.21 6.56 0.35 255.44 91.65 30147 +1975 357 9.44 3.44 7.79 1.06 275.52 91.01 30156 +1975 358 8.69 2.69 7.04 0.01 263.12 91.49 30169 +1975 359 4.43 -1.57 2.78 0 201.39 124.84 30186 +1975 360 6.07 0.07 4.42 0 223.49 124.24 30208 +1975 361 3.47 -2.53 1.82 1.41 189.35 94.54 30235 +1975 362 0.28 -5.72 -1.37 0 153.68 128.01 30267 +1975 363 5.14 -0.86 3.49 0 210.72 126.15 30303 +1975 364 2.6 -3.4 0.95 0 178.98 127.93 30343 +1975 365 -0.55 -6.55 -2.2 0 145.41 129.92 30388 +1976 1 -0.98 -6.98 -2.63 0.46 141.28 143.06 30438 +1976 2 -0.19 -6.19 -1.84 0.18 148.95 143.86 30492 +1976 3 -0.26 -6.26 -1.91 0.03 148.25 144.61 30551 +1976 4 0.43 -5.57 -1.22 0.14 155.21 144.92 30614 +1976 5 6.07 0.07 4.42 0.35 223.49 142.25 30681 +1976 6 5.57 -0.43 3.92 0.1 216.54 142.31 30752 +1976 7 5.4 -0.6 3.75 0 214.22 132.74 30828 +1976 8 1.35 -4.65 -0.3 0.21 164.93 102.33 30907 +1976 9 0.89 -5.11 -0.76 0.06 160.01 103.44 30991 +1976 10 0.36 -5.64 -1.29 0.99 154.5 104.6 31079 +1976 11 0.45 -5.55 -1.2 0.04 155.42 105.32 31171 +1976 12 4.64 -1.36 2.99 0 204.11 139.22 31266 +1976 13 3.84 -2.16 2.19 0 193.91 141.32 31366 +1976 14 0.5 -5.5 -1.15 0 155.94 144.55 31469 +1976 15 0.48 -5.52 -1.17 0 155.73 146.01 31575 +1976 16 5.86 -0.14 4.21 0 220.55 144.25 31686 +1976 17 7.43 1.43 5.78 0 243.37 144.8 31800 +1976 18 3.84 -2.16 2.19 0 193.91 149.1 31917 +1976 19 4.4 -1.6 2.75 0.01 201 113.02 32038 +1976 20 1.18 -4.82 -0.47 0 163.1 154.11 32161 +1976 21 6.72 0.72 5.07 0 232.81 152.68 32289 +1976 22 5.5 -0.5 3.85 0 215.58 155.29 32419 +1976 23 8.04 2.04 6.39 0.14 252.77 116.35 32552 +1976 24 9.06 3.06 7.41 0.09 269.18 117.23 32688 +1976 25 8.81 2.81 7.16 0 265.08 158.38 32827 +1976 26 10.34 4.34 8.69 0 291.06 158.86 32969 +1976 27 7.67 1.67 6.02 0.2 247.03 122.43 33114 +1976 28 6.3 0.3 4.65 0.03 226.75 124.89 33261 +1976 29 4.95 -1.05 3.3 0 208.18 169.89 33411 +1976 30 0.78 -5.22 -0.87 0.03 158.85 131.05 33564 +1976 31 1.29 -4.71 -0.36 0.52 164.28 132.63 33718 +1976 32 3.38 -2.62 1.73 0 188.25 177.68 33875 +1976 33 3.71 -2.29 2.06 0 192.3 180.1 34035 +1976 34 0.35 -5.65 -1.3 0 154.39 184.36 34196 +1976 35 0.93 -5.07 -0.72 0 160.43 186.2 34360 +1976 36 -1.65 -7.65 -3.3 0.14 135.05 181.2 34526 +1976 37 0.4 -5.6 -1.25 0.02 154.91 182 34694 +1976 38 -0.18 -6.18 -1.83 0.12 149.05 184.46 34863 +1976 39 0.17 -5.83 -1.48 0.31 152.56 186.09 35035 +1976 40 -1.99 -7.99 -3.64 0 131.98 238.94 35208 +1976 41 1.61 -4.39 -0.04 0 167.77 239.2 35383 +1976 42 4.1 -1.9 2.45 0 197.18 202.29 35560 +1976 43 8.22 2.22 6.57 0 255.6 201.41 35738 +1976 44 6.8 0.8 5.15 0 233.98 205.3 35918 +1976 45 5.35 -0.65 3.7 0 213.54 209.19 36099 +1976 46 3.48 -2.52 1.83 0 189.47 213.36 36282 +1976 47 3.55 -2.45 1.9 0.1 190.33 162.11 36466 +1976 48 4.85 -1.15 3.2 0 206.86 217.92 36652 +1976 49 3.7 -2.3 2.05 0 192.17 221.63 36838 +1976 50 3.93 -2.07 2.28 0 195.04 224.13 37026 +1976 51 1.94 -4.06 0.29 0 171.44 228.61 37215 +1976 52 1.8 -4.2 0.15 0 169.87 231.57 37405 +1976 53 2.84 -3.16 1.19 0 181.79 233.78 37596 +1976 54 3.69 -2.31 2.04 0 192.05 235.88 37788 +1976 55 4.88 -1.12 3.23 0 207.26 237.87 37981 +1976 56 3.7 -2.3 2.05 0 192.17 241.59 38175 +1976 57 4.69 -1.31 3.04 0.1 204.76 182.73 38370 +1976 58 3.49 -2.51 1.84 0 189.59 247.62 38565 +1976 59 4.6 -1.4 2.95 0 203.59 249.38 38761 +1976 60 10.8 4.8 9.15 0 299.29 245.32 38958 +1976 61 8.1 2.1 6.45 0 253.71 251.6 39156 +1976 62 7.88 1.88 6.23 0.04 250.27 190.98 39355 +1976 63 7.97 1.97 6.32 0 251.67 257.53 39553 +1976 64 4.19 -1.81 2.54 0.32 198.32 198.27 39753 +1976 65 6.26 0.26 4.61 0.01 226.18 198.91 39953 +1976 66 5.04 -0.96 3.39 0.07 209.38 201.91 40154 +1976 67 7.6 1.6 5.95 0.01 245.96 202.02 40355 +1976 68 4.55 -1.45 2.9 0.06 202.94 206.63 40556 +1976 69 4.49 -1.51 2.84 0.47 202.16 208.66 40758 +1976 70 3.39 -2.61 1.74 0 188.37 282.12 40960 +1976 71 2.42 -3.58 0.77 0.18 176.89 214.45 41163 +1976 72 4.6 -1.4 2.95 0.07 203.59 215.07 41366 +1976 73 3.22 -2.78 1.57 0.42 186.32 218.09 41569 +1976 74 6.06 0.06 4.41 0 223.35 290.66 41772 +1976 75 3.44 -2.56 1.79 0 188.98 296.12 41976 +1976 76 4.31 -1.69 2.66 0.84 199.85 223.45 42179 +1976 77 3.05 -2.95 1.4 0.09 184.28 226.35 42383 +1976 78 1.14 -4.86 -0.51 0 162.67 306.21 42587 +1976 79 5.52 -0.48 3.87 0 215.86 304.72 42791 +1976 80 12.25 6.25 10.6 0 326.54 297.82 42996 +1976 81 8.86 2.86 7.21 0 265.89 305.66 43200 +1976 82 4.06 -1.94 2.41 0 196.67 314.15 43404 +1976 83 7.82 1.82 6.17 0 249.34 312.23 43608 +1976 84 3.36 -2.64 1.71 0 188.01 319.97 43812 +1976 85 5.41 -0.59 3.76 0 214.36 320.3 44016 +1976 86 5.92 -0.08 4.27 0 221.39 322.13 44220 +1976 87 6.09 0.09 4.44 0 223.77 324.48 44424 +1976 88 1.23 -4.77 -0.42 0.22 163.64 248.98 44627 +1976 89 5.34 -0.66 3.69 0.14 213.41 247.55 44831 +1976 90 4.75 -1.25 3.1 0 205.55 333.15 45034 +1976 91 12.56 6.56 10.91 1.01 332.64 242.91 45237 +1976 92 11.75 5.75 10.1 0.24 316.91 245.69 45439 +1976 93 13.65 7.65 12 0.36 354.84 244.62 45642 +1976 94 13.42 7.42 11.77 2.14 350.05 246.56 45843 +1976 95 10.2 4.2 8.55 0.63 288.6 252.56 46045 +1976 96 10.16 4.16 8.51 0.05 287.9 254.2 46246 +1976 97 9.75 3.75 8.1 0.78 280.79 256.24 46446 +1976 98 6.84 0.84 5.19 0.08 234.57 260.97 46647 +1976 99 2.44 -3.56 0.79 0 177.12 355.21 46846 +1976 100 5.05 -0.95 3.4 0 209.51 354.29 47045 +1976 101 1.21 -4.79 -0.44 0 163.42 360.42 47243 +1976 102 3.89 -2.11 2.24 0.06 194.54 269.69 47441 +1976 103 6.37 0.37 4.72 0.38 227.75 268.8 47638 +1976 104 8.18 2.18 6.53 0.05 254.97 268.25 47834 +1976 105 11.18 5.18 9.53 0 306.24 354.47 48030 +1976 106 11.45 5.45 9.8 0 311.26 355.63 48225 +1976 107 16.82 10.82 15.17 0.01 426.76 259.06 48419 +1976 108 17.24 11.24 15.59 0 437.16 346.02 48612 +1976 109 17.57 11.57 15.92 0 445.49 346.7 48804 +1976 110 18.78 12.78 17.13 0 477.17 344.65 48995 +1976 111 17.59 11.59 15.94 0.03 446 262.15 49185 +1976 112 16.47 10.47 14.82 0.12 418.26 265.5 49374 +1976 113 19.19 13.19 17.54 0 488.33 347.7 49561 +1976 114 22.09 16.09 20.44 0 573.81 339.58 49748 +1976 115 20.66 14.66 19.01 0.01 530.2 259.4 49933 +1976 116 22.39 16.39 20.74 0.31 583.34 255.75 50117 +1976 117 19.54 13.54 17.89 0 498.04 351.9 50300 +1976 118 17.85 11.85 16.2 0.02 452.65 268.66 50481 +1976 119 16.86 10.86 15.21 0.01 427.74 271.59 50661 +1976 120 13.22 7.22 11.57 1.07 345.94 279.08 50840 +1976 121 14.49 8.49 12.84 0 372.81 370.37 51016 +1976 122 19.15 13.15 17.5 0.06 487.23 269.21 51191 +1976 123 21.66 15.66 20.01 0.08 560.39 263.69 51365 +1976 124 18.42 12.42 16.77 0 467.55 363.22 51536 +1976 125 15.53 9.53 13.88 2.83 396.12 279.09 51706 +1976 126 14.86 8.86 13.21 1.75 380.96 281.08 51874 +1976 127 14.81 8.81 13.16 1.13 379.85 281.84 52039 +1976 128 16.87 10.87 15.22 0 427.99 371.46 52203 +1976 129 18.28 12.28 16.63 0 463.85 368.27 52365 +1976 130 18.72 12.72 17.07 0.21 475.56 275.79 52524 +1976 131 14.95 8.95 13.3 0.03 382.97 284.16 52681 +1976 132 13.89 7.89 12.24 0 359.9 382.24 52836 +1976 133 18.35 12.35 16.7 0 465.7 371.13 52989 +1976 134 19.23 13.23 17.58 0 489.43 369.1 53138 +1976 135 16.82 10.82 15.17 0 426.76 376.94 53286 +1976 136 15.21 9.21 13.56 0 388.82 381.83 53430 +1976 137 16.18 10.18 14.53 0 411.32 380.02 53572 +1976 138 16.92 10.92 15.27 0 429.22 378.6 53711 +1976 139 22.1 16.1 20.45 0.17 574.13 271.82 53848 +1976 140 23.49 17.49 21.84 0 619.42 357.45 53981 +1976 141 18.57 12.57 16.92 0.1 471.54 281.52 54111 +1976 142 16.31 10.31 14.66 0 414.42 382.39 54238 +1976 143 19.84 13.84 18.19 0 506.48 372.32 54362 +1976 144 20.79 14.79 19.14 0 534.04 369.54 54483 +1976 145 20.16 14.16 18.51 0.04 515.63 279.13 54600 +1976 146 20.56 14.56 18.91 0.19 527.26 278.38 54714 +1976 147 16.88 10.88 15.23 0.28 428.23 287.37 54824 +1976 148 17.21 11.21 15.56 0.06 436.41 286.96 54931 +1976 149 17.8 11.8 16.15 0.01 451.37 285.9 55034 +1976 150 17.81 11.81 16.16 0.05 451.62 286.13 55134 +1976 151 16.58 10.58 14.93 0 420.91 385.43 55229 +1976 152 19.81 13.81 18.16 0 505.63 375.71 55321 +1976 153 23.39 17.39 21.74 0 616.06 362.7 55409 +1976 154 21.03 15.03 19.38 0 541.2 372.04 55492 +1976 155 19.9 13.9 18.25 0.03 508.19 282.11 55572 +1976 156 26.87 20.87 25.22 0.07 742.37 260.87 55648 +1976 157 26.3 20.3 24.65 0.11 720.29 263.07 55719 +1976 158 25.99 19.99 24.34 0.09 708.52 264.3 55786 +1976 159 21.41 15.41 19.76 0 552.71 371.75 55849 +1976 160 23.05 17.05 21.4 0 604.77 365.63 55908 +1976 161 20.26 14.26 18.61 0 518.51 376.07 55962 +1976 162 19.54 13.54 17.89 0 498.04 378.56 56011 +1976 163 20.52 14.52 18.87 0 526.08 375.45 56056 +1976 164 16.34 10.34 14.69 0.49 415.13 291.34 56097 +1976 165 16.71 10.71 15.06 0.32 424.07 290.65 56133 +1976 166 18.93 12.93 17.28 0.03 481.23 285.73 56165 +1976 167 18.39 12.39 16.74 0.72 466.76 286.96 56192 +1976 168 16.84 10.84 15.19 0 427.25 387.27 56214 +1976 169 18.93 12.93 17.28 0 481.23 381 56231 +1976 170 24.45 18.45 22.8 0.19 652.44 270.27 56244 +1976 171 21.09 15.09 19.44 0 543 373.74 56252 +1976 172 18.05 12.05 16.4 0 457.83 383.79 56256 +1976 173 22.23 16.23 20.58 0 578.24 369.47 56255 +1976 174 18.92 12.92 17.27 0.45 480.96 285.74 56249 +1976 175 19.32 13.32 17.67 1.48 491.92 284.75 56238 +1976 176 23.6 17.6 21.95 0.29 623.13 272.89 56223 +1976 177 25.53 19.53 23.88 0.88 691.36 266.48 56203 +1976 178 26.49 20.49 24.84 0.18 727.59 263.1 56179 +1976 179 19.63 13.63 17.98 0.01 500.56 283.82 56150 +1976 180 21.3 15.3 19.65 0.03 549.35 279.38 56116 +1976 181 19.16 13.16 17.51 0.18 487.51 284.83 56078 +1976 182 19.02 13.02 17.37 0.16 483.68 285.06 56035 +1976 183 15.21 9.21 13.56 1 388.82 293.12 55987 +1976 184 16.69 10.69 15.04 2.89 423.59 290.03 55935 +1976 185 14.24 8.24 12.59 0.07 367.38 294.74 55879 +1976 186 13.69 7.69 12.04 0 355.68 394.03 55818 +1976 187 12.07 6.07 10.42 0 323.05 397.44 55753 +1976 188 17.01 11.01 15.36 0 431.44 385 55684 +1976 189 20.86 14.86 19.21 0.75 536.12 279.43 55611 +1976 190 21.34 15.34 19.69 0 550.57 370.48 55533 +1976 191 23.93 17.93 22.28 0.29 634.38 270.06 55451 +1976 192 24.3 18.3 22.65 0 647.19 358.22 55366 +1976 193 22.3 16.3 20.65 0.03 580.46 274.55 55276 +1976 194 27.52 21.52 25.87 0 768.23 342.67 55182 +1976 195 23.48 17.48 21.83 0 619.08 360.9 55085 +1976 196 23.6 17.6 21.95 0 623.13 360.01 54984 +1976 197 24.71 18.71 23.06 0 661.64 354.86 54879 +1976 198 22.55 16.55 20.9 0.05 588.47 272.5 54770 +1976 199 25.58 19.58 23.93 0.07 693.21 262.67 54658 +1976 200 25.22 19.22 23.57 0 679.99 351.47 54542 +1976 201 27.32 21.32 25.67 0.05 760.19 255.8 54423 +1976 202 27.64 21.64 25.99 0.07 773.09 254.19 54301 +1976 203 20.33 14.33 18.68 0 520.54 369.13 54176 +1976 204 20.67 14.67 19.02 0.01 530.49 275.59 54047 +1976 205 22.61 16.61 20.96 0 590.41 359.84 53915 +1976 206 27.47 21.47 25.82 0 766.21 337.81 53780 +1976 207 30.49 24.49 28.84 0.8 896.31 240.56 53643 +1976 208 29.85 23.85 28.2 1.1 867.29 242.89 53502 +1976 209 33.48 27.48 31.83 0 1042.97 300.56 53359 +1976 210 32.57 26.57 30.92 0 996.35 306.12 53213 +1976 211 31.65 25.65 30 0 951 311.29 53064 +1976 212 28.76 22.76 27.11 0 819.68 327.25 52913 +1976 213 19.68 13.68 18.03 0.01 501.96 273.58 52760 +1976 214 19.86 13.86 18.21 0 507.05 363.43 52604 +1976 215 20.63 14.63 18.98 0 529.31 360.19 52445 +1976 216 15.86 9.86 14.21 0 403.78 373.35 52285 +1976 217 18.41 12.41 16.76 0.11 467.28 274.02 52122 +1976 218 17.59 11.59 15.94 0 446 366.92 51958 +1976 219 20.1 14.1 18.45 0 513.9 358.2 51791 +1976 220 22.51 16.51 20.86 0.47 587.18 261.61 51622 +1976 221 21.08 15.08 19.43 0.52 542.7 264.73 51451 +1976 222 23.61 17.61 21.96 0 623.47 342.57 51279 +1976 223 21.29 15.29 19.64 0.18 549.05 262.55 51105 +1976 224 23.72 17.72 22.07 0.03 627.2 255 50929 +1976 225 17.84 11.84 16.19 0 452.4 358.73 50751 +1976 226 17.81 11.81 16.16 0.92 451.62 268.24 50572 +1976 227 16.95 10.95 15.3 0.54 429.96 269.04 50392 +1976 228 15.34 9.34 13.69 0 391.77 361.6 50210 +1976 229 17.57 11.57 15.92 0.05 445.49 265.91 50026 +1976 230 16.88 10.88 15.23 0.18 428.23 266.34 49842 +1976 231 19.82 13.82 18.17 0.01 505.92 258.87 49656 +1976 232 21.78 15.78 20.13 0 564.11 337.34 49469 +1976 233 21.65 15.65 20 0 560.08 336.39 49280 +1976 234 21.22 15.22 19.57 0 546.93 336.46 49091 +1976 235 20.35 14.35 18.7 0.4 521.12 253.37 48900 +1976 236 19.95 13.95 18.3 0.27 509.61 253.25 48709 +1976 237 19.55 13.55 17.9 0 498.32 337.25 48516 +1976 238 17.09 11.09 15.44 0 433.42 342.5 48323 +1976 239 18.61 12.61 16.96 0 472.61 336.83 48128 +1976 240 18.67 12.67 17.02 0 474.21 334.9 47933 +1976 241 18.88 12.88 17.23 0 479.87 332.57 47737 +1976 242 24.73 18.73 23.08 0.04 662.35 233.29 47541 +1976 243 25.32 19.32 23.67 0.08 683.64 230.18 47343 +1976 244 20.85 14.85 19.2 1.43 535.82 240.94 47145 +1976 245 18.87 12.87 17.22 0.8 479.6 244.01 46947 +1976 246 16.49 10.49 14.84 0.16 418.74 247.22 46747 +1976 247 16.02 10.02 14.37 0 407.53 328.88 46547 +1976 248 21.54 15.54 19.89 0 556.69 311.6 46347 +1976 249 19.03 13.03 17.38 0.04 483.95 237.84 46146 +1976 250 21.82 15.82 20.17 0.37 565.35 230.09 45945 +1976 251 22.11 16.11 20.46 0 574.44 303.79 45743 +1976 252 20.49 14.49 18.84 0.05 525.2 230.07 45541 +1976 253 18.71 12.71 17.06 0.25 475.29 232.29 45339 +1976 254 12.01 6.01 10.36 0 321.89 322.4 45136 +1976 255 9.83 3.83 8.18 0 282.17 323.72 44933 +1976 256 10.34 4.34 8.69 0.11 291.06 240.43 44730 +1976 257 7.56 1.56 5.91 0.07 245.35 241.8 44527 +1976 258 9.42 3.42 7.77 0.23 275.19 238 44323 +1976 259 11.83 5.83 10.18 0 318.44 310.96 44119 +1976 260 10.88 4.88 9.23 0 300.74 310.1 43915 +1976 261 14.91 8.91 13.26 0 382.08 300.24 43711 +1976 262 17.71 11.71 16.06 0.31 449.06 218.72 43507 +1976 263 17.56 11.56 15.91 0.01 445.23 217.16 43303 +1976 264 22.73 16.73 21.08 0 594.29 272.82 43099 +1976 265 17.09 11.09 15.44 0.44 433.42 214.3 42894 +1976 266 19.59 13.59 17.94 0.24 499.44 207.89 42690 +1976 267 20.11 14.11 18.46 0 514.19 273.2 42486 +1976 268 18.82 12.82 17.17 0 478.25 274.01 42282 +1976 269 17.77 11.77 16.12 0 450.6 274.05 42078 +1976 270 19.11 13.11 17.46 0 486.14 268.26 41875 +1976 271 20.33 14.33 18.68 2.6 520.54 196.95 41671 +1976 272 19.27 13.27 17.62 1.72 490.54 196.98 41468 +1976 273 16.76 10.76 15.11 0.14 425.29 199.42 41265 +1976 274 13.53 7.53 11.88 0 352.34 269.42 41062 +1976 275 13.4 7.4 11.75 0 349.64 266.87 40860 +1976 276 16.48 10.48 14.83 0 418.5 258.43 40658 +1976 277 14.67 8.67 13.02 0 376.76 259.27 40456 +1976 278 19.2 13.2 17.55 0 488.61 247.08 40255 +1976 279 18.38 12.38 16.73 0 466.49 246.22 40054 +1976 280 15.68 9.68 14.03 1.45 399.59 186.85 39854 +1976 281 13.45 7.45 11.8 0.08 350.68 187.76 39654 +1976 282 9.61 3.61 7.96 0.04 278.4 189.86 39455 +1976 283 9.31 3.31 7.66 0 273.34 250.66 39256 +1976 284 4.68 -1.32 3.03 0 204.63 252.55 39058 +1976 285 4.94 -1.06 3.29 0 208.05 249.59 38861 +1976 286 7.79 1.79 6.14 0 248.88 243.88 38664 +1976 287 13.73 7.73 12.08 0 356.52 233.02 38468 +1976 288 14.59 8.59 12.94 0 375 228.87 38273 +1976 289 15.76 9.76 14.11 0.07 401.44 168.22 38079 +1976 290 18.23 12.23 16.58 0 462.54 216.86 37885 +1976 291 18.69 12.69 17.04 0.37 474.75 160 37693 +1976 292 16.84 10.84 15.19 0 427.25 214.29 37501 +1976 293 18.35 12.35 16.7 0.11 465.7 156.59 37311 +1976 294 12.16 6.16 10.51 0.09 324.79 162.08 37121 +1976 295 10.31 4.31 8.66 0.58 290.53 161.72 36933 +1976 296 7.29 1.29 5.64 0.05 241.26 162.21 36745 +1976 297 6.05 0.05 4.4 0 223.21 214.67 36560 +1976 298 9.03 3.03 7.38 0 268.69 209.11 36375 +1976 299 11.01 5.01 9.36 0 303.11 204.06 36191 +1976 300 18.3 12.3 16.65 0 464.38 190.5 36009 +1976 301 18.88 12.88 17.23 0.24 479.87 140.26 35829 +1976 302 18.02 12.02 16.37 0.34 457.05 139.56 35650 +1976 303 17.5 11.5 15.85 1.27 443.71 138.38 35472 +1976 304 13.32 7.32 11.67 0.78 347.99 141.31 35296 +1976 305 9.77 3.77 8.12 0.85 281.14 142.42 35122 +1976 306 11.36 5.36 9.71 0 309.57 185.9 34950 +1976 307 12.84 6.84 11.19 0.06 338.22 136.23 34779 +1976 308 9.08 3.08 7.43 0 269.51 183.23 34610 +1976 309 11.6 5.6 9.95 0 314.07 178.26 34444 +1976 310 11.84 5.84 10.19 0 318.63 175.57 34279 +1976 311 10.64 4.64 8.99 0.01 296.41 131.05 34116 +1976 312 7.78 1.78 6.13 0 248.73 174.85 33956 +1976 313 8.22 2.22 6.57 0.14 255.6 129.25 33797 +1976 314 7.52 1.52 5.87 0 244.74 170.99 33641 +1976 315 6.12 0.12 4.47 0 224.2 169.57 33488 +1976 316 4.31 -1.69 2.66 0 199.85 168.67 33337 +1976 317 4.49 -1.51 2.84 0 202.16 166.33 33188 +1976 318 3.34 -2.66 1.69 0.63 187.77 123.54 33042 +1976 319 3.6 -2.4 1.95 0 190.94 162.84 32899 +1976 320 7.42 1.42 5.77 0 243.22 158.25 32758 +1976 321 9.74 3.74 8.09 0.05 280.62 115.63 32620 +1976 322 10.13 4.13 8.48 0.59 287.37 114.01 32486 +1976 323 9.05 3.05 7.4 0 269.02 151.38 32354 +1976 324 7.51 1.51 5.86 0 244.59 150.6 32225 +1976 325 8.55 2.55 6.9 0.3 260.86 111.04 32100 +1976 326 7.94 1.94 6.29 1.89 251.21 110.33 31977 +1976 327 8.43 2.43 6.78 0.14 258.94 108.66 31858 +1976 328 10.94 4.94 9.29 0 301.83 140.75 31743 +1976 329 11.27 5.27 9.62 0 307.9 138.98 31631 +1976 330 15.1 9.1 13.45 0 386.34 133.52 31522 +1976 331 9.48 3.48 7.83 0 276.2 137.85 31417 +1976 332 11.61 5.61 9.96 0 314.26 134.34 31316 +1976 333 12.75 6.75 11.1 0 336.42 132.18 31218 +1976 334 13.27 7.27 11.62 0 346.96 130.59 31125 +1976 335 4.09 -1.91 2.44 0.39 197.05 102.48 31035 +1976 336 5.04 -0.96 3.39 0.28 209.38 101.25 30949 +1976 337 7.57 1.57 5.92 0.83 245.5 98.75 30867 +1976 338 6.65 0.65 5 0 231.79 131.37 30790 +1976 339 7.04 1.04 5.39 0.1 237.52 97.75 30716 +1976 340 7.66 1.66 6.01 0.05 246.88 96.88 30647 +1976 341 1.47 -4.53 -0.18 1.34 166.24 98.89 30582 +1976 342 2.13 -3.87 0.48 0.08 173.58 98.08 30521 +1976 343 3.53 -2.47 1.88 0.4 190.08 96.92 30465 +1976 344 -0.2 -6.2 -1.85 0.03 148.85 140.89 30413 +1976 345 2.95 -3.05 1.3 0.04 183.09 95.98 30366 +1976 346 3.84 -2.16 2.19 0 193.91 126.95 30323 +1976 347 2.81 -3.19 1.16 0.01 181.43 95.17 30284 +1976 348 3.15 -2.85 1.5 0 185.47 126.37 30251 +1976 349 7.3 1.3 5.65 0 241.41 123.53 30221 +1976 350 2.37 -3.63 0.72 0 176.32 126.04 30197 +1976 351 3.69 -2.31 2.04 0.02 192.05 93.86 30177 +1976 352 4.67 -1.33 3.02 0 204.5 124.52 30162 +1976 353 2.62 -3.38 0.97 1.43 179.21 94.15 30151 +1976 354 1.21 -4.79 -0.44 0.6 163.42 94.63 30145 +1976 355 0.64 -5.36 -1.01 0.08 157.39 94.81 30144 +1976 356 -2.03 -8.03 -3.68 0.42 131.62 140.75 30147 +1976 357 0.19 -5.81 -1.46 0.22 152.76 140.11 30156 +1976 358 4.43 -1.57 2.78 0.08 201.39 138.02 30169 +1976 359 -1.1 -7.1 -2.75 0.04 140.15 140.14 30186 +1976 360 -2.4 -8.4 -4.05 0.38 128.35 141.95 30208 +1976 361 -1.04 -7.04 -2.69 0 140.71 173.82 30235 +1976 362 1.54 -4.46 -0.11 0 167 172.91 30267 +1976 363 5.61 -0.39 3.96 0.08 217.09 139.06 30303 +1976 364 2.36 -3.64 0.71 0 176.2 172.33 30343 +1976 365 1.35 -4.65 -0.3 1 164.93 140.86 30388 +1977 1 1.83 -4.17 0.18 0.01 170.21 141.05 30438 +1977 2 1.12 -4.88 -0.53 0.05 162.45 141.63 30492 +1977 3 5.18 -0.82 3.53 0 211.25 129.65 30551 +1977 4 5.25 -0.75 3.6 0 212.19 130.51 30614 +1977 5 3.36 -2.64 1.71 0 188.01 132.24 30681 +1977 6 3.04 -2.96 1.39 0.44 184.16 99.97 30752 +1977 7 -0.59 -6.59 -2.24 0.01 145.02 144.71 30828 +1977 8 1.24 -4.76 -0.41 1.19 163.74 102.37 30907 +1977 9 -2.17 -8.17 -3.82 0.79 130.38 149.44 30991 +1977 10 1.89 -4.11 0.24 1.79 170.88 148.73 31079 +1977 11 2.88 -3.12 1.23 0 182.26 183.38 31171 +1977 12 5.96 -0.04 4.31 0 221.95 181.65 31266 +1977 13 10.48 4.48 8.83 0.03 293.55 102.38 31366 +1977 14 6.79 0.79 5.14 0.13 233.83 105.67 31469 +1977 15 8.26 2.26 6.61 0.14 256.23 105.92 31575 +1977 16 4.45 -1.55 2.8 0.02 201.65 108.87 31686 +1977 17 4.57 -1.43 2.92 0.14 203.2 110.07 31800 +1977 18 2.29 -3.71 0.64 0 175.4 149.99 31917 +1977 19 4.87 -1.13 3.22 0 207.13 150.39 32038 +1977 20 3.4 -2.6 1.75 0 188.49 152.89 32161 +1977 21 0.98 -5.02 -0.67 0.01 160.96 117.17 32289 +1977 22 1.07 -4.93 -0.58 0.77 161.92 118.46 32419 +1977 23 4.31 -1.69 2.66 0.28 199.85 118.39 32552 +1977 24 2.95 -3.05 1.3 0.17 183.09 120.57 32688 +1977 25 3.1 -2.9 1.45 0 184.88 162.56 32827 +1977 26 3.66 -2.34 2.01 0.01 191.68 123.11 32969 +1977 27 4.1 -1.9 2.45 0 197.18 165.88 33114 +1977 28 0.76 -5.24 -0.89 0.04 158.64 127.56 33261 +1977 29 1.97 -4.03 0.32 0 171.77 171.8 33411 +1977 30 5.08 -0.92 3.43 0 209.91 172.03 33564 +1977 31 4.6 -1.4 2.95 0 203.59 174.74 33718 +1977 32 6.9 0.9 5.25 0 235.45 175.09 33875 +1977 33 9.99 3.99 8.34 0 284.93 174.86 34035 +1977 34 13.51 7.51 11.86 0 351.92 173.02 34196 +1977 35 11.19 5.19 9.54 0.26 306.42 133.39 34360 +1977 36 10.3 4.3 8.65 0.01 290.36 135.95 34526 +1977 37 12.26 6.26 10.61 0.12 326.74 136.07 34694 +1977 38 11.82 5.82 10.17 0.46 318.25 138.47 34863 +1977 39 8.42 2.42 6.77 0 258.78 190.83 35035 +1977 40 4.89 -1.11 3.24 0.1 207.39 147.38 35208 +1977 41 4.68 -1.32 3.03 0.31 204.63 149.46 35383 +1977 42 3.85 -2.15 2.2 0.02 194.04 151.85 35560 +1977 43 3.32 -2.68 1.67 1.96 187.52 154.18 35738 +1977 44 4 -2 2.35 0.19 195.92 155.73 35918 +1977 45 6.49 0.49 4.84 0 229.48 208.19 36099 +1977 46 6.14 0.14 4.49 0 224.48 211.18 36282 +1977 47 8.76 2.76 7.11 0.05 264.26 158.57 36466 +1977 48 11.58 5.58 9.93 0.76 313.7 158.17 36652 +1977 49 11.77 5.77 10.12 0.05 317.3 160.02 36838 +1977 50 8.75 2.75 7.1 0.69 264.1 164.7 37026 +1977 51 5.65 -0.35 4 0.35 217.64 169.22 37215 +1977 52 3.96 -2.04 2.31 0.15 195.41 172.44 37405 +1977 53 1.93 -4.07 0.28 0.03 171.33 175.85 37596 +1977 54 0.71 -5.29 -0.94 0.01 158.12 178.57 37788 +1977 55 4.95 -1.05 3.3 0 208.18 237.81 37981 +1977 56 8.19 2.19 6.54 0 255.13 237.25 38175 +1977 57 5.55 -0.45 3.9 0 216.27 242.84 38370 +1977 58 4.02 -1.98 2.37 0.04 196.17 185.38 38565 +1977 59 3.63 -2.37 1.98 0.23 191.31 187.67 38761 +1977 60 10.98 4.98 9.33 0 302.56 245.08 38958 +1977 61 13.99 7.99 12.34 0 362.02 243.4 39156 +1977 62 11.75 5.75 10.1 0.17 316.91 187.21 39355 +1977 63 8.09 2.09 6.44 0 253.55 257.39 39553 +1977 64 9.62 3.62 7.97 0 278.57 258.38 39753 +1977 65 6.82 0.82 5.17 0 234.27 264.61 39953 +1977 66 8.38 2.38 6.73 0 258.14 265.53 40154 +1977 67 9.27 3.27 7.62 0 272.67 267.29 40355 +1977 68 13.53 7.53 11.88 0 352.34 263.74 40556 +1977 69 15.58 9.58 13.93 0 397.27 262.55 40758 +1977 70 17.78 11.78 16.13 0 450.85 260.7 40960 +1977 71 16.16 10.16 14.51 0 410.84 266.95 41163 +1977 72 12.63 6.63 10.98 0.9 334.03 207.17 41366 +1977 73 15.28 9.28 13.63 0 390.41 274.02 41569 +1977 74 14.83 8.83 13.18 0.17 380.3 208.17 41772 +1977 75 12.81 6.81 11.16 0.95 337.62 212.93 41976 +1977 76 7.29 1.29 5.64 0 241.26 294.6 42179 +1977 77 9.09 3.09 7.44 0.49 269.68 221.14 42383 +1977 78 11.51 5.51 9.86 0.43 312.38 220.4 42587 +1977 79 11.36 5.36 9.71 0 309.57 296.8 42791 +1977 80 10.92 4.92 9.27 0.2 301.47 225.01 42996 +1977 81 13.09 7.09 11.44 0 343.28 298.87 43200 +1977 82 12.89 6.89 11.24 0.01 339.23 226.38 43404 +1977 83 10.97 4.97 9.32 0.3 302.38 230.7 43608 +1977 84 11.55 5.55 9.9 0 313.13 309.15 43812 +1977 85 12.15 6.15 10.5 0 324.6 310.59 44016 +1977 86 10.91 4.91 9.26 0 301.29 315.09 44220 +1977 87 10.82 4.82 9.17 0.27 299.65 238.31 44424 +1977 88 7.21 1.21 5.56 0 240.06 325.43 44627 +1977 89 11.71 5.71 10.06 0 316.16 320.84 44831 +1977 90 13.07 7.07 11.42 0.03 342.87 240.51 45034 +1977 91 11.52 5.52 9.87 0 312.57 325.76 45237 +1977 92 14.17 8.17 12.52 0.01 365.87 242.19 45439 +1977 93 9.76 3.76 8.11 0 280.97 333.15 45642 +1977 94 13.61 7.61 11.96 0 354.01 328.37 45843 +1977 95 14.17 8.17 12.52 0 365.87 329.33 46045 +1977 96 16.56 10.56 14.91 0.2 420.43 244.49 46246 +1977 97 15.08 9.08 13.43 0.05 385.89 248.59 46446 +1977 98 14.19 8.19 12.54 0.69 366.3 251.49 46647 +1977 99 12.21 6.21 10.56 0.45 325.76 255.98 46846 +1977 100 12.99 6.99 11.34 0 341.25 341.73 47045 +1977 101 11.55 5.55 9.9 0 313.13 346.42 47243 +1977 102 11 5 9.35 0 302.93 349.32 47441 +1977 103 11.48 5.48 9.83 0 311.82 350.3 47638 +1977 104 9.54 3.54 7.89 0 277.21 355.52 47834 +1977 105 13.51 7.51 11.86 0.09 351.92 262.42 48030 +1977 106 12.34 6.34 10.69 0.04 328.3 265.44 48225 +1977 107 10.93 4.93 9.28 0 301.65 358.27 48419 +1977 108 11.78 5.78 10.13 0.02 317.49 268.82 48612 +1977 109 14.16 8.16 12.51 0.02 365.66 266.33 48804 +1977 110 9.59 3.59 7.94 0.11 278.06 274.07 48995 +1977 111 5.6 -0.4 3.95 2.11 216.95 279.72 49185 +1977 112 4.5 -1.5 2.85 0.29 202.29 281.94 49374 +1977 113 6.03 0.03 4.38 0.11 222.93 281.5 49561 +1977 114 10.01 4.01 8.36 0.23 285.28 278.01 49748 +1977 115 11.01 5.01 9.36 0 303.11 370.31 49933 +1977 116 14.42 8.42 12.77 0.16 371.28 273.32 50117 +1977 117 13.13 7.13 11.48 0.11 344.1 276.45 50300 +1977 118 12.28 6.28 10.63 0.27 327.13 278.78 50481 +1977 119 8.63 2.63 6.98 0.02 262.15 284.69 50661 +1977 120 9.84 3.84 8.19 0 282.34 378.73 50840 +1977 121 12.5 6.5 10.85 0 331.45 374.77 51016 +1977 122 16.59 10.59 14.94 0 421.16 366.3 51191 +1977 123 14.19 8.19 12.54 0 366.3 373.29 51365 +1977 124 14.79 8.79 13.14 0 379.41 372.96 51536 +1977 125 10.79 4.79 9.14 0.29 299.11 286.88 51706 +1977 126 12.53 6.53 10.88 0 332.04 380.04 51874 +1977 127 11.45 5.45 9.8 0 311.26 383.15 52039 +1977 128 14 8 12.35 0 362.24 378.7 52203 +1977 129 14.51 8.51 12.86 0 373.25 378.35 52365 +1977 130 20.73 14.73 19.08 0.08 532.26 270.89 52524 +1977 131 17.26 11.26 15.61 0 437.66 372.79 52681 +1977 132 15.65 9.65 14 0 398.89 377.95 52836 +1977 133 17.32 11.32 15.67 0 439.17 374.14 52989 +1977 134 18.73 12.73 17.08 0 475.82 370.67 53138 +1977 135 15.17 9.17 13.52 0 387.92 381.29 53286 +1977 136 12.98 6.98 11.33 0 341.05 387.08 53430 +1977 137 16.96 10.96 15.31 0 430.2 377.89 53572 +1977 138 20.52 14.52 18.87 0 526.08 367.43 53711 +1977 139 21.83 15.83 20.18 0 565.66 363.43 53848 +1977 140 23.65 17.65 22 0.02 624.82 267.6 53981 +1977 141 24.12 18.12 22.47 0.01 640.93 266.44 54111 +1977 142 28.9 22.9 27.25 0.01 825.67 249.54 54238 +1977 143 28.4 22.4 26.75 0.14 804.45 251.93 54362 +1977 144 26.9 20.9 25.25 0 743.54 344.02 54483 +1977 145 24.93 18.93 23.28 0.18 669.5 265.24 54600 +1977 146 19.62 13.62 17.97 1.98 500.28 280.76 54714 +1977 147 14.8 8.8 13.15 0.02 379.63 291.49 54824 +1977 148 15.78 9.78 14.13 0 401.91 386.54 54931 +1977 149 13.18 7.18 11.53 0 345.12 393.21 55034 +1977 150 15.76 9.76 14.11 0.07 401.44 290.43 55134 +1977 151 12.99 6.99 11.34 0.01 341.25 295.78 55229 +1977 152 17.07 11.07 15.42 1.59 432.93 288.12 55321 +1977 153 15.63 9.63 13.98 1.26 398.43 291.26 55409 +1977 154 16.61 10.61 14.96 0 421.64 386.02 55492 +1977 155 16.87 10.87 15.22 0 427.99 385.49 55572 +1977 156 19.14 13.14 17.49 0 486.96 378.97 55648 +1977 157 20.82 14.82 19.17 0.15 534.93 280.1 55719 +1977 158 20 14 18.35 0.11 511.04 282.35 55786 +1977 159 18.43 12.43 16.78 0.03 467.81 286.34 55849 +1977 160 17.51 11.51 15.86 0 443.96 384.74 55908 +1977 161 20.02 14.02 18.37 0 511.61 376.89 55962 +1977 162 18.9 12.9 17.25 0 480.41 380.63 56011 +1977 163 18.14 12.14 16.49 0 460.18 383.21 56056 +1977 164 21.78 15.78 20.13 0.06 564.11 278.2 56097 +1977 165 19.44 13.44 17.79 0 495.25 379.24 56133 +1977 166 23.73 17.73 22.08 0 627.54 363.39 56165 +1977 167 26.76 20.76 25.11 0 738.06 349.57 56192 +1977 168 30.47 24.47 28.82 0 895.39 329.43 56214 +1977 169 26.88 20.88 25.23 0 742.76 349.06 56231 +1977 170 26.37 20.37 24.72 0.83 722.97 263.67 56244 +1977 171 21.87 15.87 20.22 0.25 566.91 278.15 56252 +1977 172 20.08 14.08 18.43 0 513.33 377.27 56256 +1977 173 20.18 14.18 18.53 0.44 516.2 282.68 56255 +1977 174 29.26 23.26 27.61 0 841.24 336.43 56249 +1977 175 29.08 23.08 27.43 0 833.43 337.41 56238 +1977 176 28.4 22.4 26.75 0 804.45 341.1 56223 +1977 177 21.38 15.38 19.73 0.04 551.79 279.3 56203 +1977 178 22.3 16.3 20.65 0 580.46 368.98 56179 +1977 179 21.23 15.23 19.58 0 547.23 372.88 56150 +1977 180 19.59 13.59 17.94 0 499.44 378.44 56116 +1977 181 23.89 17.89 22.24 0.17 633 271.71 56078 +1977 182 26.85 20.85 25.2 0.07 741.58 261.47 56035 +1977 183 27.16 21.16 25.51 0 753.81 346.91 55987 +1977 184 24.63 18.63 22.98 0.11 658.8 268.98 55935 +1977 185 22.25 16.25 20.6 0.54 578.87 276.24 55879 +1977 186 20.82 14.82 19.17 0 534.93 373.34 55818 +1977 187 22.86 16.86 21.21 0.54 598.53 274.13 55753 +1977 188 23.8 17.8 22.15 0 629.93 361.42 55684 +1977 189 22.71 16.71 21.06 0 593.64 365.66 55611 +1977 190 28.26 22.26 26.61 0 798.6 339.81 55533 +1977 191 31.92 25.92 30.27 0 964.12 318.12 55451 +1977 192 29.01 23.01 27.36 0 830.4 335.22 55366 +1977 193 27.52 21.52 25.87 0.11 768.23 257.16 55276 +1977 194 24.88 18.88 23.23 0.06 667.71 266.41 55182 +1977 195 19.18 13.18 17.53 0 488.06 376.52 55085 +1977 196 17.74 11.74 16.09 0 449.83 380.54 54984 +1977 197 19.88 13.88 18.23 0.06 507.62 280.03 54879 +1977 198 25.5 19.5 23.85 0 690.25 350.93 54770 +1977 199 25.06 19.06 23.41 0.47 674.19 264.43 54658 +1977 200 23.93 17.93 22.28 0.68 634.38 267.79 54542 +1977 201 20.67 14.67 19.02 0.8 530.49 276.77 54423 +1977 202 17.94 11.94 16.29 3.69 454.98 282.93 54301 +1977 203 14.76 8.76 13.11 0.85 378.75 289 54176 +1977 204 13.17 7.17 11.52 0 344.91 388.54 54047 +1977 205 17.23 11.23 15.58 0 436.91 377.74 53915 +1977 206 18.15 12.15 16.5 0 460.44 374.49 53780 +1977 207 21.48 15.48 19.83 0 554.85 362.86 53643 +1977 208 20.84 14.84 19.19 0 535.53 364.48 53502 +1977 209 23.32 17.32 21.67 0 613.72 354.58 53359 +1977 210 18.11 12.11 16.46 1.15 459.4 278.99 53213 +1977 211 15.34 9.34 13.69 0 391.77 378.78 53064 +1977 212 17.98 11.98 16.33 0 456.02 370.78 52913 +1977 213 19.64 13.64 17.99 0 500.84 364.9 52760 +1977 214 20.16 14.16 18.51 0 515.63 362.45 52604 +1977 215 21.65 15.65 20 0 560.08 356.62 52445 +1977 216 23.13 17.13 21.48 0.32 607.41 262.54 52285 +1977 217 19.18 13.18 17.53 1.05 488.06 272.26 52122 +1977 218 18.75 12.75 17.1 1.15 476.36 272.63 51958 +1977 219 19.79 13.79 18.14 0.01 505.07 269.4 51791 +1977 220 21.41 15.41 19.76 0 552.71 352.81 51622 +1977 221 22.36 16.36 20.71 0 582.38 348.39 51451 +1977 222 23.9 17.9 22.25 0 633.35 341.41 51279 +1977 223 23.4 17.4 21.75 0.02 616.4 256.71 51105 +1977 224 22.79 16.79 21.14 0.34 596.25 257.7 50929 +1977 225 25.9 19.9 24.25 0 705.14 329.71 50751 +1977 226 26.26 20.26 24.61 0 718.77 327.01 50572 +1977 227 25.79 19.79 24.14 0.48 701.02 245.92 50392 +1977 228 24.02 18.02 22.37 0.21 637.47 250.63 50210 +1977 229 19.01 13.01 17.36 0.3 483.41 262.79 50026 +1977 230 19.97 13.97 18.32 1.05 510.18 259.61 49842 +1977 231 21.14 15.14 19.49 0 544.51 340.87 49656 +1977 232 23.74 17.74 22.09 0 627.88 330.12 49469 +1977 233 21.33 15.33 19.68 0.06 550.27 253.11 49280 +1977 234 21.61 15.61 19.96 0.17 558.84 251.35 49091 +1977 235 21.76 15.76 20.11 0 563.48 333.15 48900 +1977 236 23.67 17.67 22.02 0.04 625.5 243.62 48709 +1977 237 22.31 16.31 20.66 0 580.78 328.22 48516 +1977 238 18.61 12.61 16.96 0.25 472.61 253.76 48323 +1977 239 22.35 16.35 20.7 0.28 582.06 243.73 48128 +1977 240 21.52 15.52 19.87 0 556.07 326.1 47933 +1977 241 20.82 14.82 19.17 0.17 534.93 245.02 47737 +1977 242 16.94 10.94 15.29 0 429.71 336.07 47541 +1977 243 14.5 8.5 12.85 0.03 373.03 254.97 47343 +1977 244 11.87 5.87 10.22 0.1 319.2 257.57 47145 +1977 245 10.95 4.95 9.3 0.47 302.02 257.38 46947 +1977 246 10.93 4.93 9.28 1.04 301.65 255.88 46747 +1977 247 8.81 2.81 7.16 0.11 265.08 257.03 46547 +1977 248 9.81 3.81 8.16 0.12 281.82 254.33 46347 +1977 249 10.82 4.82 9.17 1.04 299.65 251.47 46146 +1977 250 13.55 7.55 11.9 0.09 352.75 246.16 45945 +1977 251 15.98 9.98 14.33 0 406.59 320.81 45743 +1977 252 19.3 13.3 17.65 0 491.36 310.2 45541 +1977 253 17.75 11.75 16.1 0 450.08 312.22 45339 +1977 254 16.63 10.63 14.98 0.05 422.13 234.63 45136 +1977 255 17.08 11.08 15.43 0 433.18 309.5 44933 +1977 256 15.57 9.57 13.92 0.04 397.04 233.03 44730 +1977 257 13.16 7.16 11.51 0 344.71 313.43 44527 +1977 258 13.05 7.05 11.4 0 342.47 311.25 44323 +1977 259 16.73 10.73 15.08 0 424.56 301.12 44119 +1977 260 22.57 16.57 20.92 0 589.12 282.76 43915 +1977 261 21.96 15.96 20.31 0 569.72 282.33 43711 +1977 262 22.33 16.33 20.68 0.07 581.42 209.17 43507 +1977 263 20.59 14.59 18.94 0.33 528.14 211.27 43303 +1977 264 19.59 13.59 17.94 0.52 499.44 211.44 43099 +1977 265 21.17 15.17 19.52 0 545.42 275.25 42894 +1977 266 16.34 10.34 14.69 0 415.13 284.93 42690 +1977 267 14.19 8.19 12.54 0 366.3 286.61 42486 +1977 268 17.4 11.4 15.75 0 441.18 277.38 42282 +1977 269 18.87 12.87 17.22 0.01 479.6 203.57 42078 +1977 270 21.05 15.05 19.4 0 541.8 263.18 41875 +1977 271 20.89 14.89 19.24 0 537.02 261.1 41671 +1977 272 17.53 11.53 15.88 0 444.47 266.72 41468 +1977 273 22.51 16.51 20.86 0 587.18 251.49 41265 +1977 274 21.26 15.26 19.61 0 548.14 252.47 41062 +1977 275 17.53 11.53 15.88 0 444.47 258.88 40860 +1977 276 12.4 6.4 10.75 0.97 329.48 199.35 40658 +1977 277 13.54 7.54 11.89 0 352.55 261.25 40456 +1977 278 10.63 4.63 8.98 0 296.23 262.86 40255 +1977 279 11.17 5.17 9.52 0 306.05 259.25 40054 +1977 280 12.2 6.2 10.55 0 325.57 255.04 39854 +1977 281 11.93 5.93 10.28 0.08 320.35 189.53 39654 +1977 282 8.94 2.94 7.29 0 267.2 253.99 39455 +1977 283 9.53 3.53 7.88 0.03 277.05 187.79 39256 +1977 284 11.86 5.86 10.21 0 319.01 244.19 39058 +1977 285 14.02 8.02 12.37 0.45 362.66 178.67 38861 +1977 286 11.87 5.87 10.22 0 319.2 238.75 38664 +1977 287 12.67 6.67 11.02 0 334.82 234.64 38468 +1977 288 13.61 7.61 11.96 0.02 354.01 172.83 38273 +1977 289 15.61 9.61 13.96 0 397.97 224.55 38079 +1977 290 15.5 9.5 13.85 0 395.43 221.93 37885 +1977 291 11.18 5.18 9.53 0 306.24 225.72 37693 +1977 292 8.83 2.83 7.18 0 265.4 225.85 37501 +1977 293 9.09 3.09 7.44 0 269.68 222.8 37311 +1977 294 11.88 5.88 10.23 0 319.39 216.49 37121 +1977 295 11.95 5.95 10.3 0 320.74 213.56 36933 +1977 296 14.89 8.89 13.24 0 381.63 206.77 36745 +1977 297 15.17 9.17 13.52 0 387.92 203.66 36560 +1977 298 16.16 10.16 14.51 0 410.84 199.51 36375 +1977 299 16.39 10.39 14.74 0 416.33 196.42 36191 +1977 300 18.26 12.26 16.61 0.38 463.33 142.93 36009 +1977 301 19.3 13.3 17.65 0 491.36 186.21 35829 +1977 302 20.47 14.47 18.82 0 524.62 181.4 35650 +1977 303 23.08 17.08 21.43 0 605.76 173.27 35472 +1977 304 21.29 15.29 19.64 0.29 549.05 131.23 35296 +1977 305 11.43 5.43 9.78 0.78 310.88 141.04 35122 +1977 306 7.79 1.79 6.14 0.22 248.88 142.19 34950 +1977 307 10.01 4.01 8.36 0.6 285.28 138.66 34779 +1977 308 8.38 2.38 6.73 0.01 258.14 137.93 34610 +1977 309 11.55 5.55 9.9 0.14 313.13 133.74 34444 +1977 310 8.1 2.1 6.45 0.08 253.71 134.54 34279 +1977 311 6.02 0.02 4.37 0.65 222.79 134.22 34116 +1977 312 4.28 -1.72 2.63 0 199.47 177.58 33956 +1977 313 2.81 -3.19 1.16 0.36 181.43 132.3 33797 +1977 314 3.26 -2.74 1.61 0.43 186.8 130.6 33641 +1977 315 1 -5 -0.65 0 161.18 172.9 33488 +1977 316 3.73 -2.27 2.08 0 192.55 169.05 33337 +1977 317 9.3 3.3 7.65 0 273.17 162.53 33188 +1977 318 7.58 1.58 5.93 0.3 245.65 121.27 33042 +1977 319 5.61 -0.39 3.96 0 217.09 161.49 32899 +1977 320 4.15 -1.85 2.5 0 197.81 160.6 32758 +1977 321 6.62 0.62 4.97 0.39 231.36 117.57 32620 +1977 322 8.54 2.54 6.89 0.15 260.7 115.07 32486 +1977 323 7.49 1.49 5.84 0.1 244.28 114.5 32354 +1977 324 8.3 2.3 6.65 0 256.87 149.97 32225 +1977 325 12.25 6.25 10.6 0.17 326.54 108.48 32100 +1977 326 12.74 6.74 11.09 0 336.22 142.71 31977 +1977 327 12.79 6.79 11.14 0 337.22 140.86 31858 +1977 328 15.42 9.42 13.77 0 393.6 135.96 31743 +1977 329 12.78 6.78 11.13 0.44 337.02 103.11 31631 +1977 330 10.82 4.82 9.17 0.33 299.65 103.48 31522 +1977 331 10.18 4.18 8.53 0.77 288.25 102.94 31417 +1977 332 9.48 3.48 7.83 0.3 276.2 102.17 31316 +1977 333 13.77 7.77 12.12 0 357.36 131.12 31218 +1977 334 16.13 10.13 14.48 0.09 410.13 95.52 31125 +1977 335 5.49 -0.51 3.84 0.14 215.45 101.85 31035 +1977 336 2.09 -3.91 0.44 0.01 173.13 102.48 30949 +1977 337 0.8 -5.2 -0.85 0 159.06 135.59 30867 +1977 338 2.22 -3.78 0.57 0.1 174.6 100.47 30790 +1977 339 0.4 -5.6 -1.25 0 154.91 134.02 30716 +1977 340 0.74 -5.26 -0.91 0 158.43 133.12 30647 +1977 341 3.63 -2.37 1.98 0 191.31 130.76 30582 +1977 342 -0.56 -6.56 -2.21 0 145.31 131.98 30521 +1977 343 4.2 -1.8 2.55 0 198.45 128.86 30465 +1977 344 5.07 -0.93 3.42 0 209.78 127.23 30413 +1977 345 4.21 -1.79 2.56 0 198.57 127.29 30366 +1977 346 9.88 3.88 8.23 0 283.03 122.95 30323 +1977 347 6.8 0.8 5.15 0.02 233.98 93.44 30284 +1977 348 5.54 -0.46 3.89 0 216.13 125.03 30251 +1977 349 6.85 0.85 5.2 0.26 234.71 92.87 30221 +1977 350 4.73 -1.27 3.08 0 205.29 124.79 30197 +1977 351 5.03 -0.97 3.38 0 209.25 124.4 30177 +1977 352 6.36 0.36 4.71 0 227.61 123.5 30162 +1977 353 3.21 -2.79 1.56 0.16 186.2 93.93 30151 +1977 354 5.53 -0.47 3.88 0.02 215.99 92.94 30145 +1977 355 3.41 -2.59 1.76 0.61 188.62 93.82 30144 +1977 356 0.54 -5.46 -1.11 0 156.35 126.49 30147 +1977 357 0.56 -5.44 -1.09 1.01 156.56 94.9 30156 +1977 358 -1.41 -7.41 -3.06 1 137.25 142.5 30169 +1977 359 -2.38 -8.38 -4.03 0.56 128.53 144.61 30186 +1977 360 -2.37 -8.37 -4.02 0 128.62 176.92 30208 +1977 361 -1.82 -7.82 -3.47 0.05 133.5 145.07 30235 +1977 362 -2.32 -8.32 -3.97 0 129.05 177.75 30267 +1977 363 -1.74 -7.74 -3.39 0 134.23 178.07 30303 +1977 364 -2.64 -8.64 -4.29 0.05 126.27 146.36 30343 +1977 365 -5.1 -11.1 -6.75 0 106.58 180.19 30388 +1978 1 0.65 -5.35 -1 0 157.49 178.83 30438 +1978 2 -3.63 -9.63 -5.28 0 118 181.12 30492 +1978 3 -4.39 -10.39 -6.04 0.56 111.97 150.52 30551 +1978 4 -2.43 -8.43 -4.08 0.23 128.09 151.34 30614 +1978 5 2.07 -3.93 0.42 0 172.9 183.24 30681 +1978 6 0.77 -5.23 -0.88 0 158.75 184.53 30752 +1978 7 0.03 -5.97 -1.62 0.08 151.15 151.65 30828 +1978 8 -0.16 -6.16 -1.81 0 149.25 186.98 30907 +1978 9 1.34 -4.66 -0.31 0.25 164.82 152.83 30991 +1978 10 2.12 -3.88 0.47 0 173.47 187.76 31079 +1978 11 2.14 -3.86 0.49 0 173.69 188.32 31171 +1978 12 8.26 2.26 6.61 0 256.23 184.24 31266 +1978 13 9.23 3.23 7.58 0 272 183.74 31366 +1978 14 7.06 1.06 5.41 0 237.82 185.81 31469 +1978 15 6.74 0.74 5.09 0 233.1 186.45 31575 +1978 16 3.03 -2.97 1.38 0 184.04 189.55 31686 +1978 17 5.9 -0.1 4.25 0 221.11 188.54 31800 +1978 18 2.56 -3.44 0.91 0 178.51 192.01 31917 +1978 19 -1.8 -7.8 -3.45 0 133.69 195.89 32038 +1978 20 -3.47 -9.47 -5.12 0 119.3 198 32161 +1978 21 -0.62 -6.62 -2.27 0 144.73 198.69 32289 +1978 22 2.09 -3.91 0.44 0.01 173.13 159.31 32419 +1978 23 -1.24 -7.24 -2.89 0 138.83 201.93 32552 +1978 24 6.3 0.3 4.65 0 226.75 158.54 32688 +1978 25 7.65 1.65 6 0.02 246.72 119.52 32827 +1978 26 5.06 -0.94 3.41 0 209.65 163.22 32969 +1978 27 6.38 0.38 4.73 0.27 227.89 123.2 33114 +1978 28 6.15 0.15 4.5 0 224.62 166.64 33261 +1978 29 7.47 1.47 5.82 0 243.98 167.95 33411 +1978 30 12.47 6.47 10.82 0 330.86 165.25 33564 +1978 31 11.46 5.46 9.81 0.19 311.44 126.51 33718 +1978 32 7.98 1.98 6.33 0.05 251.83 130.63 33875 +1978 33 4.1 -1.9 2.45 0.44 197.18 134.87 34035 +1978 34 2.59 -3.41 0.94 0 178.86 183.04 34196 +1978 35 1.05 -4.95 -0.6 0 161.71 186.14 34360 +1978 36 1.74 -4.26 0.09 0.61 169.21 141.19 34526 +1978 37 1.11 -4.89 -0.54 0 162.35 191.08 34694 +1978 38 4.48 -1.52 2.83 0 202.04 191.59 34863 +1978 39 -1.11 -7.11 -2.76 0 140.05 197.71 35035 +1978 40 -1.69 -7.69 -3.34 0 134.68 200.66 35208 +1978 41 -1.33 -7.33 -2.98 0 137.99 203.13 35383 +1978 42 1.96 -4.04 0.31 0 171.66 203.79 35560 +1978 43 2.56 -3.44 0.91 0 178.51 206.11 35738 +1978 44 0.33 -5.67 -1.32 0.01 154.19 157.6 35918 +1978 45 0.9 -5.1 -0.75 0 160.12 212.43 36099 +1978 46 0.13 -5.87 -1.52 0 152.15 215.62 36282 +1978 47 2.52 -3.48 0.87 0 178.05 216.9 36466 +1978 48 -1.28 -7.28 -2.93 0 138.46 222.13 36652 +1978 49 -0.57 -6.57 -2.22 0 145.22 224.54 36838 +1978 50 -2.07 -8.07 -3.72 0 131.26 228.09 37026 +1978 51 0.38 -5.62 -1.27 0 154.7 229.66 37215 +1978 52 3.12 -2.88 1.47 0 185.11 230.59 37405 +1978 53 4.13 -1.87 2.48 0 197.56 232.75 37596 +1978 54 6.8 0.8 5.15 0.02 233.98 174.8 37788 +1978 55 7.43 1.43 5.78 0 243.37 235.4 37981 +1978 56 6.82 0.82 5.17 0 234.27 238.71 38175 +1978 57 9.69 3.69 8.04 0 279.77 238.35 38370 +1978 58 8.31 2.31 6.66 0 257.03 242.89 38565 +1978 59 7.68 1.68 6.03 1.14 247.19 184.72 38761 +1978 60 13.08 7.08 11.43 0 343.08 242.01 38958 +1978 61 13.88 7.88 12.23 0 359.69 243.58 39156 +1978 62 16.13 10.13 14.48 0 410.13 242.29 39355 +1978 63 14.14 8.14 12.49 0 365.23 248.78 39553 +1978 64 13.7 7.7 12.05 0 355.89 252.35 39753 +1978 65 14.5 8.5 12.85 0 373.03 253.78 39953 +1978 66 16.24 10.24 14.59 0 412.74 253.17 40154 +1978 67 15.66 9.66 14.01 0 399.12 257.09 40355 +1978 68 13.58 7.58 11.93 0 353.38 263.66 40556 +1978 69 13.02 7.02 11.37 0 341.86 267.16 40758 +1978 70 11.46 5.46 9.81 0 311.44 272.45 40960 +1978 71 10.82 4.82 9.17 0 299.65 276.29 41163 +1978 72 7.86 1.86 6.21 0 249.96 283.11 41366 +1978 73 8.04 2.04 6.39 0 252.77 285.55 41569 +1978 74 6.64 0.64 4.99 0.02 231.65 217.5 41772 +1978 75 5.13 -0.87 3.48 0.07 210.58 220.82 41976 +1978 76 5.95 -0.05 4.3 0.66 221.81 222.14 42179 +1978 77 6.48 0.48 4.83 0.43 229.33 223.64 42383 +1978 78 10.17 4.17 8.52 0.09 288.07 221.96 42587 +1978 79 10.71 4.71 9.06 0 297.67 297.83 42791 +1978 80 10.49 4.49 8.84 0 293.72 300.69 42996 +1978 81 5.14 -0.86 3.49 0 210.72 310.31 43200 +1978 82 7.39 1.39 5.74 0 242.76 310.29 43404 +1978 83 9.78 3.78 8.13 0 281.31 309.46 43608 +1978 84 9.27 3.27 7.62 0.01 272.67 234.56 43812 +1978 85 10.61 4.61 8.96 1.08 295.87 234.88 44016 +1978 86 9.76 3.76 8.11 0.21 280.97 237.68 44220 +1978 87 7.71 1.71 6.06 0.03 247.65 241.8 44424 +1978 88 7.05 1.05 5.4 0.83 237.67 244.23 44627 +1978 89 6.5 0.5 4.85 0.59 229.62 246.49 44831 +1978 90 4.35 -1.65 2.7 0 200.36 333.6 45034 +1978 91 9.88 3.88 8.23 0.03 283.03 246.37 45237 +1978 92 9.61 3.61 7.96 0.18 278.4 248.38 45439 +1978 93 8.23 2.23 6.58 0 255.76 335.47 45642 +1978 94 3.19 -2.81 1.54 0.19 185.95 257.92 45843 +1978 95 4.07 -1.93 2.42 0.22 196.8 258.85 46045 +1978 96 4.02 -1.98 2.37 0 196.17 347.35 46246 +1978 97 7.42 1.42 5.77 0 243.22 345.17 46446 +1978 98 10.51 4.51 8.86 0.13 294.08 256.78 46647 +1978 99 13.79 7.79 12.14 0.05 357.78 253.62 46846 +1978 100 14.84 8.84 13.19 0 380.52 337.81 47045 +1978 101 9.47 3.47 7.82 0 276.03 350.02 47243 +1978 102 12.25 6.25 10.6 0 326.54 347 47441 +1978 103 10.32 4.32 8.67 0 290.71 352.37 47638 +1978 104 12.01 6.01 10.36 0 321.89 351.12 47834 +1978 105 16.5 10.5 14.85 1.03 418.98 257.24 48030 +1978 106 17.64 11.64 15.99 0 447.27 341.62 48225 +1978 107 14.22 8.22 12.57 0 366.95 351.65 48419 +1978 108 14.59 8.59 12.94 0.12 375 264.41 48612 +1978 109 12.77 6.77 11.12 0.26 336.82 268.56 48804 +1978 110 8.75 2.75 7.1 0 264.1 366.8 48995 +1978 111 13.17 7.17 11.52 0 344.91 360.21 49185 +1978 112 12.04 6.04 10.39 0 322.47 364.04 49374 +1978 113 13.23 7.23 11.58 0 346.14 362.94 49561 +1978 114 13.62 7.62 11.97 0.39 354.21 272.69 49748 +1978 115 12.76 6.76 11.11 0.21 336.62 275.14 49933 +1978 116 14.22 8.22 12.57 0.89 366.95 273.67 50117 +1978 117 16.42 10.42 14.77 0.12 417.05 270.61 50300 +1978 118 16.18 10.18 14.53 0.42 411.32 272.05 50481 +1978 119 18.18 12.18 16.53 0.51 461.23 268.83 50661 +1978 120 17.49 11.49 15.84 0.18 443.46 271.16 50840 +1978 121 17.12 11.12 15.47 1.01 434.17 272.76 51016 +1978 122 16.99 10.99 15.34 0.16 430.95 273.91 51191 +1978 123 14.33 8.33 12.68 0.51 369.33 279.72 51365 +1978 124 13.36 7.36 11.71 0.28 348.81 282.19 51536 +1978 125 13.16 7.16 11.51 0.39 344.71 283.26 51706 +1978 126 17.14 11.14 15.49 0.25 434.67 276.63 51874 +1978 127 17.77 11.77 16.12 0 450.6 367.94 52039 +1978 128 22.18 16.18 20.53 0.05 576.65 265.82 52203 +1978 129 21.32 15.32 19.67 0.06 549.96 268.77 52365 +1978 130 19.33 13.33 17.68 0.47 492.19 274.36 52524 +1978 131 15.11 9.11 13.46 0.03 386.56 283.87 52681 +1978 132 17.57 11.57 15.92 0.03 445.49 279.55 52836 +1978 133 13.18 7.18 11.53 0.39 345.12 288.42 52989 +1978 134 11.65 5.65 10 1.74 315.02 291.4 53138 +1978 135 13.82 7.82 12.17 0.43 358.42 288.4 53286 +1978 136 13.57 7.57 11.92 0.64 353.17 289.32 53430 +1978 137 17.35 11.35 15.7 0.17 439.92 282.59 53572 +1978 138 18.14 12.14 16.49 0 460.18 375.07 53711 +1978 139 19.7 13.7 18.05 1.23 502.53 278.15 53848 +1978 140 15.05 9.05 13.4 1.31 385.21 288.54 53981 +1978 141 13.66 7.66 12.01 0.51 355.05 291.38 54111 +1978 142 14.1 8.1 12.45 0 364.37 387.99 54238 +1978 143 17.77 11.77 16.12 0.28 450.6 284.1 54362 +1978 144 15.02 9.02 13.37 0 384.54 386.77 54483 +1978 145 13.88 7.88 12.23 0 359.69 390.01 54600 +1978 146 14.2 8.2 12.55 0.11 366.52 292.23 54714 +1978 147 14.9 8.9 13.25 0 381.86 388.41 54824 +1978 148 11.42 5.42 9.77 0.23 310.69 297.49 54931 +1978 149 15.24 9.24 13.59 0.02 389.5 291.19 55034 +1978 150 16.64 10.64 14.99 0.04 422.37 288.65 55134 +1978 151 17.87 11.87 16.22 0.93 453.17 286.29 55229 +1978 152 20.58 14.58 18.93 0 527.84 373.08 55321 +1978 153 21.35 15.35 19.7 0.06 550.88 277.93 55409 +1978 154 20.44 14.44 18.79 0.04 523.74 280.59 55492 +1978 155 22.52 16.52 20.87 0.16 587.51 275 55572 +1978 156 21.22 15.22 19.57 0.82 546.93 278.9 55648 +1978 157 23.62 17.62 21.97 0.48 623.81 272.04 55719 +1978 158 23.83 17.83 22.18 0 630.95 362.02 55786 +1978 159 20.77 14.77 19.12 0.11 533.45 280.54 55849 +1978 160 21.05 15.05 19.4 0.03 541.8 279.92 55908 +1978 161 20.04 14.04 18.39 0.36 512.18 282.62 55962 +1978 162 24.6 18.6 22.95 0.3 657.73 269.44 56011 +1978 163 22.36 16.36 20.71 0.79 582.38 276.51 56056 +1978 164 23.68 17.68 22.03 0.49 625.84 272.57 56097 +1978 165 22.44 16.44 20.79 0 584.94 368.51 56133 +1978 166 22.08 16.08 20.43 0.48 573.49 277.48 56165 +1978 167 17.61 11.61 15.96 0.03 446.5 288.72 56192 +1978 168 22.12 16.12 20.47 0.22 574.76 277.38 56214 +1978 169 20.47 14.47 18.82 0.02 524.62 281.91 56231 +1978 170 21.09 15.09 19.44 0.8 543 280.26 56244 +1978 171 23.94 17.94 22.29 0 634.72 362.6 56252 +1978 172 20.27 14.27 18.62 0 518.8 376.62 56256 +1978 173 20.48 14.48 18.83 0.06 524.91 281.9 56255 +1978 174 20.37 14.37 18.72 0.74 521.7 282.13 56249 +1978 175 20.12 14.12 18.47 0 514.48 377 56238 +1978 176 16.38 10.38 14.73 0 416.09 388.44 56223 +1978 177 16.43 10.43 14.78 0.39 417.29 291.15 56203 +1978 178 15.6 9.6 13.95 0 397.74 390.45 56179 +1978 179 12.89 6.89 11.24 0.43 339.23 297.68 56150 +1978 180 18.15 12.15 16.5 0.08 460.44 287.26 56116 +1978 181 16.04 10.04 14.39 0 408 388.98 56078 +1978 182 14.83 8.83 13.18 0 380.3 391.97 56035 +1978 183 13.6 7.6 11.95 0 353.8 394.76 55987 +1978 184 12.42 6.42 10.77 0 329.87 397.24 55935 +1978 185 14.78 8.78 13.13 0.47 379.19 293.75 55879 +1978 186 16.08 10.08 14.43 0.52 408.95 291.02 55818 +1978 187 16.62 10.62 14.97 0.02 421.88 289.78 55753 +1978 188 20.75 14.75 19.1 0 532.86 373.14 55684 +1978 189 22.47 16.47 20.82 0 585.9 366.6 55611 +1978 190 20.7 14.7 19.05 0 531.38 372.77 55533 +1978 191 19.44 13.44 17.79 0 495.25 376.76 55451 +1978 192 20.41 14.41 18.76 0.31 522.87 279.91 55366 +1978 193 20.05 14.05 18.4 0 512.47 374.16 55276 +1978 194 17.7 11.7 16.05 0.59 448.8 286.02 55182 +1978 195 17.55 11.55 15.9 0.46 444.98 286.14 55085 +1978 196 19.98 13.98 18.33 0.37 510.47 280.12 54984 +1978 197 16.41 10.41 14.76 0.11 416.81 287.89 54879 +1978 198 18.51 12.51 16.86 0.1 469.94 283 54770 +1978 199 22 16 20.35 0 570.98 365.09 54658 +1978 200 22.33 16.33 20.68 0.85 581.42 272.58 54542 +1978 201 19.75 13.75 18.1 0.28 503.94 279.11 54423 +1978 202 19.89 13.89 18.24 0.06 507.9 278.34 54301 +1978 203 19.76 13.76 18.11 0.01 504.22 278.28 54176 +1978 204 22.16 16.16 20.51 0 576.02 362.07 54047 +1978 205 21.32 15.32 19.67 0.38 549.96 273.48 53915 +1978 206 24.64 18.64 22.99 0.31 659.15 263.26 53780 +1978 207 28.08 22.08 26.43 0.96 791.12 250.56 53643 +1978 208 30.13 24.13 28.48 0 879.89 322.25 53502 +1978 209 30.85 24.85 29.2 0 912.99 317.43 53359 +1978 210 30.81 24.81 29.16 0 911.12 317.11 53213 +1978 211 31.06 25.06 29.41 0 922.84 314.9 53064 +1978 212 32.37 26.37 30.72 0.25 986.34 229.52 52913 +1978 213 26.41 20.41 24.76 1 724.51 253.74 52760 +1978 214 22.18 16.18 20.53 0 576.65 355.34 52604 +1978 215 22.91 16.91 21.26 0 600.17 351.91 52445 +1978 216 22.42 16.42 20.77 0.22 584.3 264.58 52285 +1978 217 24.46 18.46 22.81 0.03 652.79 257.85 52122 +1978 218 25.72 19.72 24.07 1.29 698.41 253.16 51958 +1978 219 25.32 19.32 23.67 1.41 683.64 253.74 51791 +1978 220 25.15 19.15 23.5 0.07 677.45 253.62 51622 +1978 221 24.08 18.08 22.43 0 639.54 341.7 51451 +1978 222 22.54 16.54 20.89 0 588.15 346.69 51279 +1978 223 22.08 16.08 20.43 0 573.49 347.26 51105 +1978 224 21.65 15.65 20 0 560.08 347.76 50929 +1978 225 21.74 15.74 20.09 0 562.86 346.32 50751 +1978 226 24.15 18.15 22.5 0.05 641.97 252.04 50572 +1978 227 23.02 17.02 21.37 0 603.78 339.24 50392 +1978 228 20.83 14.83 19.18 0 535.23 345.85 50210 +1978 229 20.73 14.73 19.08 0 532.26 344.95 50026 +1978 230 19.14 13.14 17.49 0 486.96 348.72 49842 +1978 231 22.27 16.27 20.62 0 579.51 336.93 49656 +1978 232 19.43 13.43 17.78 0 494.97 345.01 49469 +1978 233 16.46 10.46 14.81 0 418.01 351.89 49280 +1978 234 14.37 8.37 12.72 0 370.19 355.47 49091 +1978 235 18.42 12.42 16.77 0 467.55 343.65 48900 +1978 236 18.76 12.76 17.11 0 476.63 341.24 48709 +1978 237 23.55 17.55 21.9 0.01 621.44 242.77 48516 +1978 238 18.97 12.97 17.32 0 482.32 337.31 48323 +1978 239 19.43 13.43 17.78 0.05 494.97 250.83 48128 +1978 240 20.83 14.83 19.18 0 535.23 328.36 47933 +1978 241 21.06 15.06 19.41 0.15 542.1 244.44 47737 +1978 242 17.4 11.4 15.75 0 441.18 334.88 47541 +1978 243 16.78 10.78 15.13 0.33 425.78 250.95 47343 +1978 244 13.39 7.39 11.74 0 349.43 340.45 47145 +1978 245 15.02 9.02 13.37 0 384.54 335.06 46947 +1978 246 16.8 10.8 15.15 0.53 426.27 246.65 46747 +1978 247 16.22 10.22 14.57 0.21 412.27 246.3 46547 +1978 248 22.71 16.71 21.06 0 593.64 307.69 46347 +1978 249 21.94 15.94 20.29 0 569.1 308.29 46146 +1978 250 22.06 16.06 20.41 0.29 572.86 229.5 45945 +1978 251 19.43 13.43 17.78 0.3 494.97 233.98 45743 +1978 252 20.62 14.62 18.97 0 529.02 306.37 45541 +1978 253 25.17 19.17 23.52 0.08 678.18 216.58 45339 +1978 254 21 15 19.35 0 540.3 301.07 45136 +1978 255 19.95 13.95 18.3 0.06 509.61 226.46 44933 +1978 256 21.7 15.7 20.05 0 561.62 294.5 44730 +1978 257 20.01 14.01 18.36 0.63 511.32 223.08 44527 +1978 258 17.4 11.4 15.75 1.64 441.18 226.47 44323 +1978 259 15.86 9.86 14.21 0 403.78 303.08 44119 +1978 260 18.56 12.56 16.91 0.2 471.27 220.72 43915 +1978 261 17.94 11.94 16.29 0 454.98 293.42 43711 +1978 262 16.79 10.79 15.14 0 426.03 293.79 43507 +1978 263 15.95 9.95 14.3 0 405.89 293.19 43303 +1978 264 15.55 9.55 13.9 0 396.58 291.46 43099 +1978 265 15.91 9.91 14.26 0.03 404.95 216.25 42894 +1978 266 15.05 9.05 13.4 0.08 385.21 215.72 42690 +1978 267 13.01 7.01 11.36 0 341.66 288.77 42486 +1978 268 12.52 6.52 10.87 0 331.84 287.02 42282 +1978 269 13.19 7.19 11.54 0 345.32 283.31 42078 +1978 270 17.02 11.02 15.37 0.11 431.69 204.85 41875 +1978 271 16.78 10.78 15.13 0 425.78 271.06 41671 +1978 272 20.15 14.15 18.5 0 515.34 260.42 41468 +1978 273 21.71 15.71 20.06 0 561.93 253.79 41265 +1978 274 18.82 12.82 17.17 0 478.25 258.66 41062 +1978 275 16.76 10.76 15.11 0.78 425.29 195.39 40860 +1978 276 14.09 8.09 12.44 0.36 364.16 197.22 40658 +1978 277 12.58 6.58 10.93 0 333.03 262.83 40456 +1978 278 11.33 5.33 9.68 0 309.02 261.86 40255 +1978 279 12.43 6.43 10.78 0 330.07 257.36 40054 +1978 280 12.86 6.86 11.21 0 338.63 254.02 39854 +1978 281 8.71 2.71 7.06 0.01 263.45 192.79 39654 +1978 282 12.92 6.92 11.27 0.34 339.83 186.34 39455 +1978 283 14.77 8.77 13.12 0 378.97 242.58 39256 +1978 284 13.55 7.55 11.9 0.02 352.75 181.21 39058 +1978 285 10.59 4.59 8.94 1.08 295.51 182.46 38861 +1978 286 10.69 4.69 9.04 0.01 297.3 180.27 38664 +1978 287 12.71 6.71 11.06 0.06 335.62 175.94 38468 +1978 288 10.52 4.52 8.87 0.18 294.26 176.12 38273 +1978 289 9.41 3.41 7.76 0 275.02 233.53 38079 +1978 290 12.43 6.43 10.78 0.36 330.07 170.04 37885 +1978 291 15.87 9.87 14.22 0.03 404.01 163.98 37693 +1978 292 13.94 7.94 12.29 0.15 360.96 164.35 37501 +1978 293 14.6 8.6 12.95 0.22 375.22 161.56 37311 +1978 294 14.53 8.53 12.88 0.83 373.68 159.5 37121 +1978 295 13.94 7.94 12.29 0 360.96 210.77 36933 +1978 296 18.19 12.19 16.54 0 461.49 201.08 36745 +1978 297 19.68 13.68 18.03 0 501.96 195.53 36560 +1978 298 18.01 12.01 16.36 0 456.79 196.28 36375 +1978 299 15.41 9.41 13.76 0 393.37 198 36191 +1978 300 14.98 8.98 13.33 0 383.64 196.06 36009 +1978 301 15.3 9.3 13.65 0 390.86 193.1 35829 +1978 302 13.68 7.68 12.03 0 355.47 192.89 35650 +1978 303 10.77 4.77 9.12 0 298.75 193.99 35472 +1978 304 9.95 3.95 8.3 0 284.24 192.44 35296 +1978 305 -1.75 -7.75 -3.4 0 134.14 198.47 35122 +1978 306 -2.04 -8.04 -3.69 0.12 131.53 185.31 34950 +1978 307 -1.87 -7.87 -3.52 0.54 133.05 184.98 34779 +1978 308 -2.35 -8.35 -4 0 128.79 231.13 34610 +1978 309 1.68 -4.32 0.03 0.39 168.54 179.95 34444 +1978 310 4.11 -1.89 2.46 0 197.3 222.26 34279 +1978 311 4.34 -1.66 2.69 0 200.23 219.56 34116 +1978 312 2.97 -3.03 1.32 0 183.33 217.64 33956 +1978 313 -0.33 -6.33 -1.98 0 147.56 217.55 33797 +1978 314 1.49 -4.51 -0.16 0.07 166.46 170.77 33641 +1978 315 2.97 -3.03 1.32 0 183.33 171.75 33488 +1978 316 0.35 -5.65 -1.3 0.01 154.39 128.26 33337 +1978 317 -1.03 -7.03 -2.68 0.09 140.81 167.13 33188 +1978 318 4.24 -1.76 2.59 0.24 198.96 123.11 33042 +1978 319 7 1 5.35 0.81 236.93 120.34 32899 +1978 320 6.61 0.61 4.96 0 231.21 158.88 32758 +1978 321 6.07 0.07 4.42 0 223.49 157.17 32620 +1978 322 3.37 -2.63 1.72 0 188.13 157.12 32486 +1978 323 6.28 0.28 4.63 0 226.47 153.57 32354 +1978 324 2.93 -3.07 1.28 0 182.85 153.68 32225 +1978 325 5.24 -0.76 3.59 0 212.06 150.51 32100 +1978 326 10.25 4.25 8.6 0 289.48 145.15 31977 +1978 327 11.54 5.54 9.89 0.05 312.94 106.59 31858 +1978 328 9.63 3.63 7.98 0.12 278.74 106.45 31743 +1978 329 7.5 1.5 5.85 0 244.43 142.15 31631 +1978 330 7.4 1.4 5.75 0 242.92 140.79 31522 +1978 331 10.13 4.13 8.48 0 287.37 137.3 31417 +1978 332 9.61 3.61 7.96 0 278.4 136.12 31316 +1978 333 11.79 5.79 10.14 0 317.68 133.12 31218 +1978 334 14.25 8.25 12.6 0 367.6 129.54 31125 +1978 335 11.68 5.68 10.03 0 315.59 131.01 31035 +1978 336 6.77 0.77 5.12 0.03 233.54 100.41 30949 +1978 337 5.62 -0.38 3.97 0 217.23 132.98 30867 +1978 338 7.11 1.11 5.46 0.06 238.56 98.3 30790 +1978 339 4.81 -1.19 3.16 0.53 206.34 98.81 30716 +1978 340 3.05 -2.95 1.4 0 184.28 132 30647 +1978 341 1.24 -4.76 -0.41 0 163.74 131.97 30582 +1978 342 0.05 -5.95 -1.6 0 151.35 131.73 30521 +1978 343 0.52 -5.48 -1.13 0 156.14 130.69 30465 +1978 344 -1.52 -7.52 -3.17 0.59 136.24 143.05 30413 +1978 345 0.6 -5.4 -1.05 0 156.97 174.34 30366 +1978 346 4.89 -1.11 3.24 0.01 207.39 139.44 30323 +1978 347 6.23 0.23 4.58 0 225.75 168.85 30284 +1978 348 2.74 -3.26 1.09 0 180.61 126.57 30251 +1978 349 1.14 -4.86 -0.51 0.15 162.67 95.21 30221 +1978 350 3.52 -2.48 1.87 0.36 189.96 94.09 30197 +1978 351 3.88 -2.12 2.23 0.51 194.41 93.78 30177 +1978 352 2.88 -3.12 1.23 0.26 182.26 94.1 30162 +1978 353 2.52 -3.48 0.87 0 178.05 125.59 30151 +1978 354 7.69 1.69 6.04 0 247.34 122.53 30145 +1978 355 6.25 0.25 4.6 0 226.04 123.48 30144 +1978 356 3.77 -2.23 2.12 0 193.04 124.94 30147 +1978 357 -0.24 -6.24 -1.89 0 148.45 126.87 30156 +1978 358 2.54 -3.46 0.89 0.32 178.28 94.29 30169 +1978 359 9.22 3.22 7.57 0.16 271.84 91.28 30186 +1978 360 5.79 -0.21 4.14 0.08 219.58 93.31 30208 +1978 361 6.28 0.28 4.63 0.93 226.47 93.33 30235 +1978 362 5.47 -0.53 3.82 0.01 215.17 94.03 30267 +1978 363 2.26 -3.74 0.61 0.2 175.06 95.77 30303 +1978 364 -0.21 -6.21 -1.86 0 148.75 129.21 30343 +1978 365 -2.24 -8.24 -3.89 0 129.76 130.57 30388 +1979 1 -6.22 -12.22 -7.87 0 98.53 132.73 30438 +1979 2 -5.72 -11.72 -7.37 0.21 102.06 143.95 30492 +1979 3 -5.74 -11.74 -7.39 0 101.91 178.17 30551 +1979 4 -1.15 -7.15 -2.8 0 139.68 177.45 30614 +1979 5 -0.55 -6.55 -2.2 0.69 145.41 146.41 30681 +1979 6 3.61 -2.39 1.96 0 191.06 178.25 30752 +1979 7 5.29 -0.71 3.64 0.03 212.73 144.06 30828 +1979 8 6.93 0.93 5.28 0 235.89 176.66 30907 +1979 9 6.3 0.3 4.65 0 226.75 134.89 30991 +1979 10 2.92 -3.08 1.27 0.16 182.73 103.66 31079 +1979 11 -0.62 -6.62 -2.27 0 144.73 140.9 31171 +1979 12 -1.24 -7.24 -2.89 0 138.83 142.18 31266 +1979 13 -0.7 -6.7 -2.35 0 143.96 143.59 31366 +1979 14 1.35 -4.65 -0.3 0.01 164.93 108.1 31469 +1979 15 0.02 -5.98 -1.63 0.01 151.05 109.67 31575 +1979 16 0.02 -5.98 -1.63 0.71 151.05 110.64 31686 +1979 17 -4.96 -10.96 -6.61 0.46 107.62 156.28 31800 +1979 18 -4.55 -10.55 -6.2 0.61 110.73 159.29 31917 +1979 19 -4.82 -10.82 -6.47 0.17 108.68 161.18 32038 +1979 20 -3.15 -9.15 -4.8 0 121.95 200.77 32161 +1979 21 -1.98 -7.98 -3.63 0.04 132.07 162.88 32289 +1979 22 -1.71 -7.71 -3.36 1.08 134.5 167.15 32419 +1979 23 -0.49 -6.49 -2.14 0.26 145.99 168.65 32552 +1979 24 1.62 -4.38 -0.03 0 167.88 209.39 32688 +1979 25 1.54 -4.46 -0.11 0 167 210.94 32827 +1979 26 1.07 -4.93 -0.58 0 161.92 212.8 32969 +1979 27 1.87 -4.13 0.22 0 170.65 213.96 33114 +1979 28 2.59 -3.41 0.94 0.14 178.86 172.98 33261 +1979 29 3.34 -2.66 1.69 0 187.77 216.55 33411 +1979 30 5.57 -0.43 3.92 0.06 216.54 173.46 33564 +1979 31 2.01 -3.99 0.36 1.2 172.22 176.58 33718 +1979 32 5.81 -0.19 4.16 1.54 219.85 175.33 33875 +1979 33 6.41 0.41 4.76 0 228.32 220.5 34035 +1979 34 4.79 -1.21 3.14 0 206.07 223.18 34196 +1979 35 7.75 1.75 6.1 0 248.26 221.81 34360 +1979 36 5.71 -0.29 4.06 0 218.47 225.16 34526 +1979 37 3.51 -2.49 1.86 0 189.84 228.61 34694 +1979 38 5.35 -0.65 3.7 0.31 213.54 181.45 34863 +1979 39 8.77 2.77 7.12 0.78 264.42 142.87 35035 +1979 40 4.72 -1.28 3.07 0.42 205.16 147.48 35208 +1979 41 4.15 -1.85 2.5 0.44 197.81 149.77 35383 +1979 42 6.45 0.45 4.8 0.25 228.9 150.28 35560 +1979 43 6.53 0.53 4.88 0.11 230.05 152.25 35738 +1979 44 6.75 0.75 5.1 0 233.25 205.35 35918 +1979 45 7.25 1.25 5.6 0 240.65 207.49 36099 +1979 46 0.84 -5.16 -0.81 0.04 159.48 161.39 36282 +1979 47 3.82 -2.18 2.17 0 193.66 215.94 36466 +1979 48 2.61 -3.39 0.96 0.07 179.09 164.74 36652 +1979 49 2.15 -3.85 0.5 0.01 173.81 167.09 36838 +1979 50 0.49 -5.51 -1.16 0.2 155.83 169.95 37026 +1979 51 -1.76 -7.76 -3.41 0 134.05 230.94 37215 +1979 52 -2.77 -8.77 -4.42 0 125.16 234.35 37405 +1979 53 0.2 -5.8 -1.45 0 152.86 235.64 37596 +1979 54 4.7 -1.3 3.05 0 204.89 235.03 37788 +1979 55 0.63 -5.37 -1.02 0.05 157.28 180.88 37981 +1979 56 6.08 0.08 4.43 0.16 223.63 179.59 38175 +1979 57 9.37 3.37 7.72 0 274.35 238.74 38370 +1979 58 6.51 0.51 4.86 0.02 229.76 183.62 38565 +1979 59 7.89 1.89 6.24 0 250.43 246.06 38761 +1979 60 16.39 10.39 14.74 1.11 416.33 177.23 38958 +1979 61 10.24 4.24 8.59 0.57 289.3 186.72 39156 +1979 62 11.3 5.3 9.65 0 308.46 250.26 39355 +1979 63 10.94 4.94 9.29 0.04 301.83 190.3 39553 +1979 64 13.09 7.09 11.44 0 343.28 253.35 39753 +1979 65 9.71 3.71 8.06 0 280.11 261.13 39953 +1979 66 10.77 4.77 9.12 0 298.75 262.38 40154 +1979 67 7.15 1.15 5.5 0.23 239.16 202.41 40355 +1979 68 10.5 4.5 8.85 0.09 293.9 201.35 40556 +1979 69 11.48 5.48 9.83 0.18 311.82 202.21 40758 +1979 70 9.74 3.74 8.09 0.17 280.62 206.21 40960 +1979 71 13 7 11.35 0.67 341.45 204.63 41163 +1979 72 13.05 7.05 11.4 0.01 342.47 206.64 41366 +1979 73 12.44 6.44 10.79 0 330.27 279.16 41569 +1979 74 13.83 7.83 12.18 0 358.63 279.43 41772 +1979 75 9.15 3.15 7.5 0 270.67 289.55 41976 +1979 76 9.58 3.58 7.93 0 277.89 291.57 42179 +1979 77 7.81 1.81 6.16 0 249.19 296.56 42383 +1979 78 13.01 7.01 11.36 0.01 341.66 218.49 42587 +1979 79 13.86 7.86 12.21 0 359.26 292.43 42791 +1979 80 11.54 5.54 9.89 0 312.94 299.01 42996 +1979 81 8.32 2.32 6.67 0.08 257.19 229.8 43200 +1979 82 11.36 5.36 9.71 0.05 309.57 228.37 43404 +1979 83 8.72 2.72 7.07 0 263.61 311 43608 +1979 84 6.97 0.97 5.32 0.66 236.48 236.91 43812 +1979 85 7.49 1.49 5.84 0 244.28 317.73 44016 +1979 86 9.21 3.21 7.56 0 271.67 317.74 44220 +1979 87 7.96 1.96 6.31 0.15 251.52 241.54 44424 +1979 88 6.73 0.73 5.08 0.6 232.96 244.54 44627 +1979 89 7.78 1.78 6.13 2.25 248.73 245.22 44831 +1979 90 3.33 -2.67 1.68 0.35 187.64 251.02 45034 +1979 91 5.96 -0.04 4.31 0.24 221.95 250.51 45237 +1979 92 6.53 0.53 4.88 0.28 230.05 251.67 45439 +1979 93 8.46 2.46 6.81 0.12 259.42 251.35 45642 +1979 94 10.12 4.12 8.47 1.39 287.2 251.05 45843 +1979 95 12.08 6.08 10.43 0.17 323.24 250.09 46045 +1979 96 7.95 1.95 6.3 0.06 251.36 256.76 46246 +1979 97 5.49 -0.51 3.84 0.07 215.45 260.78 46446 +1979 98 8.62 2.62 6.97 0.33 261.99 259.06 46647 +1979 99 11.83 5.83 10.18 0 318.44 342.03 46846 +1979 100 16.39 10.39 14.74 0 416.33 334.17 47045 +1979 101 15.44 9.44 13.79 0.04 394.06 253.75 47243 +1979 102 13.42 7.42 11.77 0 350.05 344.66 47441 +1979 103 11.36 5.36 9.71 0 309.57 350.52 47638 +1979 104 14.73 8.73 13.08 0 378.08 345.45 47834 +1979 105 13.08 7.08 11.43 0.12 343.08 263.09 48030 +1979 106 12.97 6.97 11.32 0 340.85 352.65 48225 +1979 107 11.18 5.18 9.53 0.26 306.24 268.36 48419 +1979 108 11.53 5.53 9.88 0.22 312.76 269.18 48612 +1979 109 11.21 5.21 9.56 0.39 306.79 270.84 48804 +1979 110 10.89 4.89 9.24 0.23 300.92 272.35 48995 +1979 111 13.65 7.65 12 0.14 354.84 269.38 49185 +1979 112 15.61 9.61 13.96 0.06 397.97 267.12 49374 +1979 113 15.25 9.25 13.6 0 389.73 358.36 49561 +1979 114 13.92 7.92 12.27 0 360.53 362.92 49748 +1979 115 15.21 9.21 13.56 0 388.82 361.35 49933 +1979 116 14.51 8.51 12.86 0.3 373.25 273.17 50117 +1979 117 15.8 9.8 14.15 0 402.38 362.4 50300 +1979 118 13.47 7.47 11.82 0.54 351.09 276.89 50481 +1979 119 13.14 7.14 11.49 0.04 344.3 278.32 50661 +1979 120 16.45 10.45 14.8 0.25 417.77 273.28 50840 +1979 121 21.07 15.07 19.42 0.27 542.4 263.64 51016 +1979 122 22.39 16.39 20.74 0 583.34 347.94 51191 +1979 123 19.04 13.04 17.39 0.09 484.22 270.21 51365 +1979 124 14.24 8.24 12.59 0 367.38 374.26 51536 +1979 125 14.54 8.54 12.89 0 373.9 374.54 51706 +1979 126 13.66 7.66 12.01 0 355.05 377.58 51874 +1979 127 15.21 9.21 13.56 0 388.82 374.8 52039 +1979 128 13.62 7.62 11.97 0 354.21 379.57 52203 +1979 129 12.8 6.8 11.15 0 337.42 382.24 52365 +1979 130 12.2 6.2 10.55 0 325.57 384.31 52524 +1979 131 13.12 7.12 11.47 0 343.89 383.15 52681 +1979 132 16.22 10.22 14.57 0 412.27 376.46 52836 +1979 133 12.82 6.82 11.17 0.02 337.82 289.02 52989 +1979 134 16.95 10.95 15.3 0.4 429.96 281.91 53138 +1979 135 15.61 9.61 13.96 0 397.97 380.17 53286 +1979 136 16.13 10.13 14.48 0 410.13 379.45 53430 +1979 137 18.97 12.97 17.32 0 482.32 371.93 53572 +1979 138 25.02 19.02 23.37 0 672.74 349.86 53711 +1979 139 25.06 19.06 23.41 0 674.19 350.34 53848 +1979 140 21.2 15.2 19.55 0 546.32 366.19 53981 +1979 141 24.26 18.26 22.61 0 645.79 354.67 54111 +1979 142 21.7 15.7 20.05 0.4 561.62 273.96 54238 +1979 143 23.55 17.55 21.9 0.02 621.44 268.96 54362 +1979 144 21.57 15.57 19.92 0 557.61 366.75 54483 +1979 145 21.51 15.51 19.86 0 555.77 367.43 54600 +1979 146 23.45 17.45 21.8 0 618.08 360.29 54714 +1979 147 23.97 17.97 22.32 0 635.75 358.6 54824 +1979 148 21.14 15.14 19.49 0 544.51 369.97 54931 +1979 149 20.47 14.47 18.82 0 524.62 372.64 55034 +1979 150 19 13 17.35 0 483.13 377.85 55134 +1979 151 24.69 18.69 23.04 0 660.93 356.87 55229 +1979 152 25.71 19.71 24.06 0.02 698.04 264.28 55321 +1979 153 27.01 21.01 25.36 0.03 747.87 259.77 55409 +1979 154 23.32 17.32 21.67 0.72 613.72 272.47 55492 +1979 155 20.83 14.83 19.18 0.14 535.23 279.71 55572 +1979 156 21.68 15.68 20.03 0.13 561.01 277.63 55648 +1979 157 26.1 20.1 24.45 0.04 712.68 263.79 55719 +1979 158 26.82 20.82 25.17 0.34 740.41 261.3 55786 +1979 159 28.28 22.28 26.63 0.13 799.43 255.85 55849 +1979 160 22.11 16.11 20.46 0.33 574.44 276.98 55908 +1979 161 22.46 16.46 20.81 2.88 585.58 276.02 55962 +1979 162 24.68 18.68 23.03 2.84 660.57 269.17 56011 +1979 163 22.61 16.61 20.96 0 590.41 367.71 56056 +1979 164 25.69 19.69 24.04 0 697.29 354.58 56097 +1979 165 24.73 18.73 23.08 0.6 662.35 269.27 56133 +1979 166 21.53 15.53 19.88 0.62 556.38 279.03 56165 +1979 167 23.84 17.84 22.19 0 631.29 362.88 56192 +1979 168 24.09 18.09 22.44 0.32 639.89 271.42 56214 +1979 169 24.82 18.82 23.17 0 665.56 358.73 56231 +1979 170 25.65 19.65 24 0 695.8 354.97 56244 +1979 171 21.87 15.87 20.22 0.44 566.91 278.15 56252 +1979 172 21.15 15.15 19.5 0.27 544.81 280.13 56256 +1979 173 21.29 15.29 19.64 0.03 549.05 279.74 56255 +1979 174 16.6 10.6 14.95 0 421.4 387.9 56249 +1979 175 17.28 11.28 15.63 0 438.16 385.94 56238 +1979 176 20.77 14.77 19.12 0.1 533.45 281.03 56223 +1979 177 21.26 15.26 19.61 0 548.14 372.84 56203 +1979 178 19.25 13.25 17.6 1.73 489.98 284.84 56179 +1979 179 20.36 14.36 18.71 0.76 521.41 281.97 56150 +1979 180 26.48 20.48 24.83 0 727.2 350.63 56116 +1979 181 27.72 21.72 26.07 0 776.34 344.35 56078 +1979 182 22.38 16.38 20.73 1.89 583.02 276.18 56035 +1979 183 23.79 17.79 22.14 0.58 629.58 271.79 55987 +1979 184 24.7 18.7 23.05 1.37 661.28 268.75 55935 +1979 185 18.74 12.74 17.09 0.27 476.09 285.41 55879 +1979 186 18.68 12.68 17.03 0.12 474.48 285.35 55818 +1979 187 18.03 12.03 16.38 0 457.31 382.28 55753 +1979 188 17.59 11.59 15.94 0.51 446 287.49 55684 +1979 189 19.91 13.91 18.26 0.21 508.47 281.89 55611 +1979 190 15.92 9.92 14.27 0 405.18 387.43 55533 +1979 191 17.43 11.43 15.78 0 441.94 382.96 55451 +1979 192 18.05 12.05 16.4 0 457.83 380.82 55366 +1979 193 22.42 16.42 20.77 0 584.3 365.6 55276 +1979 194 21.47 15.47 19.82 0 554.54 368.95 55182 +1979 195 21.13 15.13 19.48 0.39 544.21 277.43 55085 +1979 196 17.68 11.68 16.03 0.24 448.29 285.54 54984 +1979 197 19.74 13.74 18.09 0 503.65 373.83 54879 +1979 198 18.65 12.65 17 1.3 473.68 282.67 54770 +1979 199 19.56 13.56 17.91 1 498.6 280.23 54658 +1979 200 19.33 13.33 17.68 0 492.19 373.98 54542 +1979 201 18.04 12.04 16.39 0.17 457.57 283.14 54423 +1979 202 19.93 13.93 18.28 0.32 509.04 278.24 54301 +1979 203 20.01 14.01 18.36 1.27 511.32 277.66 54176 +1979 204 19.02 13.02 17.37 0.84 483.68 279.68 54047 +1979 205 23.4 17.4 21.75 0.86 616.4 267.54 53915 +1979 206 26.3 20.3 24.65 1.22 720.29 257.64 53780 +1979 207 23.04 17.04 21.39 0.03 604.44 267.73 53643 +1979 208 24.77 18.77 23.12 0.34 663.78 261.88 53502 +1979 209 23.73 17.73 22.08 1.18 627.54 264.69 53359 +1979 210 24.76 18.76 23.11 0.15 663.42 260.99 53213 +1979 211 24.94 18.94 23.29 0.01 669.86 259.85 53064 +1979 212 23.13 17.13 21.48 0.01 607.41 264.89 52913 +1979 213 21.51 15.51 19.86 0 555.77 358.53 52760 +1979 214 24.82 18.82 23.17 0.01 665.56 258.57 52604 +1979 215 22.43 16.43 20.78 0 584.62 353.74 52445 +1979 216 24.61 18.61 22.96 0.09 658.09 258.02 52285 +1979 217 22.09 16.09 20.44 1.11 573.81 264.85 52122 +1979 218 24.45 18.45 22.8 0.8 652.44 257.29 51958 +1979 219 18.15 12.15 16.5 0.24 460.44 273.18 51791 +1979 220 20.92 14.92 19.27 0 537.91 354.51 51622 +1979 221 18.4 12.4 16.75 0.02 467.02 271.16 51451 +1979 222 16.7 10.7 15.05 0 423.83 365.27 51279 +1979 223 18.81 12.81 17.16 0 477.98 358.11 51105 +1979 224 17.43 11.43 15.78 0.03 441.94 270.78 50929 +1979 225 18.92 12.92 17.27 0.03 480.96 266.67 50751 +1979 226 17.71 11.71 16.06 0.05 449.06 268.45 50572 +1979 227 19.35 13.35 17.7 0.11 492.75 263.86 50392 +1979 228 22.15 16.15 20.5 0 575.7 341.27 50210 +1979 229 21.99 15.99 20.34 0.55 570.66 255.47 50026 +1979 230 23.6 17.6 21.95 0 623.13 333.39 49842 +1979 231 25.03 19.03 23.38 0 673.11 326.21 49656 +1979 232 21.56 15.56 19.91 0.18 557.3 253.58 49469 +1979 233 20.2 14.2 18.55 0.6 516.78 255.9 49280 +1979 234 18.75 12.75 17.1 2.66 476.36 258.15 49091 +1979 235 20.61 14.61 18.96 0.04 528.72 252.75 48900 +1979 236 21.36 15.36 19.71 0 551.18 333.11 48709 +1979 237 25.06 19.06 23.41 0 674.19 317.73 48516 +1979 238 29.13 23.13 27.48 0.02 835.59 223.11 48323 +1979 239 27.95 21.95 26.3 0.52 785.75 226.44 48128 +1979 240 23.92 17.92 22.27 0.25 634.03 238.14 47933 +1979 241 23.73 17.73 22.08 0 627.54 316.58 47737 +1979 242 20.55 14.55 18.9 0 526.96 325.83 47541 +1979 243 23.22 17.22 21.57 0 610.39 314.99 47343 +1979 244 19.22 13.22 17.57 0.01 489.16 244.64 47145 +1979 245 18.44 12.44 16.79 0 468.08 326.54 46947 +1979 246 12.69 6.69 11.04 0 335.22 337.93 46747 +1979 247 12.83 6.83 11.18 0 338.02 335.75 46547 +1979 248 11.6 5.6 9.95 0 314.07 336.05 46347 +1979 249 15.21 9.21 13.56 0.37 388.82 245.01 46146 +1979 250 13.36 7.36 11.71 0 348.81 328.59 45945 +1979 251 13.56 7.56 11.91 0 352.96 326.03 45743 +1979 252 17.95 11.95 16.3 0.68 455.24 235.37 45541 +1979 253 18.65 12.65 17 0 473.68 309.88 45339 +1979 254 21.07 15.07 19.42 0 542.4 300.85 45136 +1979 255 22.38 16.38 20.73 0 583.02 294.52 44933 +1979 256 23.25 17.25 21.6 0 611.39 289.43 44730 +1979 257 22.8 16.8 21.15 0 596.57 288.88 44527 +1979 258 22.51 16.51 20.86 0 587.18 287.58 44323 +1979 259 26.97 20.97 25.32 0 746.3 268.95 44119 +1979 260 23.73 17.73 22.08 0 627.54 278.91 43915 +1979 261 24.08 18.08 22.43 0.25 639.54 206.54 43711 +1979 262 21.91 15.91 20.26 0.48 568.16 210.15 43507 +1979 263 23.36 17.36 21.71 0.66 615.06 204.93 43303 +1979 264 25.01 19.01 23.36 0.07 672.38 198.85 43099 +1979 265 22.11 16.11 20.46 0 574.44 272.47 42894 +1979 266 19.98 13.98 18.33 0.11 510.47 207.12 42690 +1979 267 18.93 12.93 17.28 0 481.23 276.25 42486 +1979 268 15.64 9.64 13.99 0.76 398.66 210.89 42282 +1979 269 14.35 8.35 12.7 0 369.76 281.2 42078 +1979 270 18.18 12.18 16.53 0 461.23 270.5 41875 +1979 271 19.68 13.68 18.03 0 501.96 264.28 41671 +1979 272 17.38 11.38 15.73 0 440.68 267.05 41468 +1979 273 11.91 5.91 10.26 0 319.97 274.8 41265 +1979 274 5.05 -0.95 3.4 0 209.51 280.86 41062 +1979 275 7.47 1.47 5.82 0.02 243.98 206.51 40860 +1979 276 9.46 3.46 7.81 0 275.86 270.09 40658 +1979 277 12.59 6.59 10.94 0 333.23 262.82 40456 +1979 278 16.62 10.62 14.97 0 421.88 252.7 40255 +1979 279 18.62 12.62 16.97 0.01 472.87 184.26 40054 +1979 280 15.76 9.76 14.11 0.04 401.44 186.74 39854 +1979 281 13.36 7.36 11.71 0 348.81 250.49 39654 +1979 282 15.01 9.01 13.36 0.23 384.31 183.72 39455 +1979 283 12.3 6.3 10.65 0 327.52 246.57 39256 +1979 284 8.11 2.11 6.46 0 253.87 249.02 39058 +1979 285 14.15 8.15 12.5 0 365.44 238.01 38861 +1979 286 20.41 14.41 18.76 0.02 522.87 167.18 38664 +1979 287 18.48 12.48 16.83 0.23 469.14 168.27 38468 +1979 288 16.54 10.54 14.89 0.04 419.95 169.1 38273 +1979 289 10.89 4.89 9.24 0 300.92 231.69 38079 +1979 290 15.76 9.76 14.11 0 401.44 221.48 37885 +1979 291 15.79 9.79 14.14 1.33 402.14 164.08 37693 +1979 292 15.65 9.65 14 0.04 398.89 162.28 37501 +1979 293 10.89 4.89 9.24 0.05 300.92 165.49 37311 +1979 294 11.18 5.18 9.53 0 306.24 217.39 37121 +1979 295 11.24 5.24 9.59 0.23 307.35 160.86 36933 +1979 296 10.32 4.32 8.67 0 290.71 213.01 36745 +1979 297 10.18 4.18 8.53 0.18 288.25 157.83 36560 +1979 298 10.81 4.81 9.16 0.02 299.47 155.31 36375 +1979 299 9.58 3.58 7.93 0 277.89 205.71 36191 +1979 300 5.82 -0.18 4.17 0 219.99 206.68 36009 +1979 301 11.19 5.19 9.54 0.25 306.42 149.01 35829 +1979 302 10.28 4.28 8.63 0 290 197.12 35650 +1979 303 7.93 1.93 6.28 0 251.05 196.96 35472 +1979 304 5.35 -0.65 3.7 0 213.54 196.73 35296 +1979 305 1.05 -4.95 -0.6 0.04 161.71 147.7 35122 +1979 306 -0.97 -6.97 -2.62 0 141.38 195.74 34950 +1979 307 6.08 0.08 4.43 0.74 223.63 141.41 34779 +1979 308 6.62 0.62 4.97 0.74 231.36 139.1 34610 +1979 309 7.66 1.66 6.01 0.95 246.88 136.68 34444 +1979 310 6.42 0.42 4.77 0.23 228.47 135.63 34279 +1979 311 7.45 1.45 5.8 0 243.67 177.78 34116 +1979 312 8.23 2.23 6.58 0.14 255.76 130.84 33956 +1979 313 7.75 1.75 6.1 0.84 248.26 129.56 33797 +1979 314 11.16 5.16 9.51 2.16 305.87 125.66 33641 +1979 315 11.7 5.7 10.05 1.57 315.97 123.34 33488 +1979 316 12.49 6.49 10.84 0 331.25 161.44 33337 +1979 317 10.77 4.77 9.12 0 298.75 161.11 33188 +1979 318 10.12 4.12 8.47 0 287.2 159.44 33042 +1979 319 8.94 2.94 7.29 0.03 267.2 119.13 32899 +1979 320 10.91 4.91 9.26 0.66 301.29 116.36 32758 +1979 321 8.41 2.41 6.76 0.18 258.62 116.51 32620 +1979 322 5.04 -0.96 3.39 0.13 209.38 117.04 32486 +1979 323 4.79 -1.21 3.14 0.01 206.07 115.95 32354 +1979 324 7.63 1.63 5.98 0.25 246.42 112.88 32225 +1979 325 7.04 1.04 5.39 0.07 237.52 111.93 32100 +1979 326 9.01 3.01 7.36 0.51 268.36 109.68 31977 +1979 327 8.54 2.54 6.89 0 260.7 144.79 31858 +1979 328 11.54 5.54 9.89 0 312.94 140.18 31743 +1979 329 10.54 4.54 8.89 0 294.62 139.65 31631 +1979 330 9.14 3.14 7.49 0.12 270.51 104.58 31522 +1979 331 10.81 4.81 9.16 0.4 299.47 102.52 31417 +1979 332 12.14 6.14 10.49 0.55 324.4 100.38 31316 +1979 333 12.7 6.7 11.05 0.1 335.42 99.17 31218 +1979 334 11.37 5.37 9.72 0.83 309.76 99.33 31125 +1979 335 3.41 -2.59 1.76 0.27 188.62 102.77 31035 +1979 336 -0.01 -6.01 -1.66 1.14 150.74 149.41 30949 +1979 337 2.51 -3.49 0.86 0 177.93 180.74 30867 +1979 338 2.88 -3.12 1.23 0 182.26 179.34 30790 +1979 339 0.45 -5.55 -1.2 0.37 155.42 146.27 30716 +1979 340 3.86 -2.14 2.21 0.17 194.16 144.04 30647 +1979 341 7.1 1.1 5.45 0 238.41 173.18 30582 +1979 342 4.28 -1.72 2.63 0 199.47 173.69 30521 +1979 343 8.09 2.09 6.44 0 253.55 126.39 30465 +1979 344 10.48 4.48 8.83 0 293.55 123.41 30413 +1979 345 9.24 3.24 7.59 0 272.17 123.99 30366 +1979 346 8.1 2.1 6.45 0.32 253.71 93.22 30323 +1979 347 5.56 -0.44 3.91 0.01 216.41 94.03 30284 +1979 348 9.72 3.72 8.07 0 280.28 122.15 30251 +1979 349 7.17 1.17 5.52 0.21 239.46 92.72 30221 +1979 350 6.46 0.46 4.81 0.01 229.04 92.81 30197 +1979 351 7.66 1.66 6.01 0 246.88 122.74 30177 +1979 352 8.33 2.33 6.68 0.24 257.34 91.63 30162 +1979 353 9.6 3.6 7.95 0 278.23 121.17 30151 +1979 354 7.59 1.59 5.94 0 245.81 122.6 30145 +1979 355 7.61 1.61 5.96 0.75 246.11 91.94 30144 +1979 356 8.44 2.44 6.79 0.7 259.1 91.52 30147 +1979 357 6.85 0.85 5.2 0.04 234.71 92.38 30156 +1979 358 7.07 1.07 5.42 0 237.97 123.12 30169 +1979 359 6.47 0.47 4.82 0.98 229.19 92.72 30186 +1979 360 5.4 -0.6 3.75 0.84 214.22 93.48 30208 +1979 361 8.21 2.21 6.56 0 255.44 123.14 30235 +1979 362 9.94 3.94 8.29 0 284.07 122.27 30267 +1979 363 12.6 6.6 10.95 0 333.43 120.53 30303 +1979 364 10.87 4.87 9.22 0 300.56 122.46 30343 +1979 365 11.12 5.12 9.47 0 305.13 122.8 30388 +1980 1 8.6 2.6 6.95 0 261.67 125.7 30438 +1980 2 8.5 2.5 6.85 0 260.06 126.49 30492 +1980 3 8.55 2.55 6.9 0 260.86 127.39 30551 +1980 4 5.31 -0.69 3.66 0 213 130.48 30614 +1980 5 2.11 -3.89 0.46 0 173.35 132.88 30681 +1980 6 1.61 -4.39 -0.04 0 167.77 134.02 30752 +1980 7 2.24 -3.76 0.59 0.36 174.83 100.88 30828 +1980 8 2.95 -3.05 1.3 0 183.09 135.63 30907 +1980 9 0.78 -5.22 -0.87 0.57 158.85 103.48 30991 +1980 10 -1.52 -7.52 -3.17 0.74 136.24 149.96 31079 +1980 11 -1.96 -7.96 -3.61 0.14 132.25 151.14 31171 +1980 12 -2.54 -8.54 -4.19 0 127.14 187.61 31266 +1980 13 1.13 -4.87 -0.52 0 162.56 187.39 31366 +1980 14 -0.43 -6.43 -2.08 0 146.58 189.45 31469 +1980 15 2.33 -3.67 0.68 0 175.86 189.12 31575 +1980 16 4.63 -1.37 2.98 0 203.98 188.34 31686 +1980 17 5.13 -0.87 3.48 0.25 210.58 152.29 31800 +1980 18 0.13 -5.87 -1.52 0 152.15 193.4 31917 +1980 19 0.17 -5.83 -1.48 0 152.56 195.15 32038 +1980 20 0.68 -5.32 -0.97 0 157.8 196.25 32161 +1980 21 -0.83 -6.83 -2.48 0 142.71 198.82 32289 +1980 22 -4.63 -10.63 -6.28 0 110.12 201.94 32419 +1980 23 -5.35 -11.35 -7 0 104.73 203.82 32552 +1980 24 -3.6 -9.6 -5.25 0.06 118.24 164.32 32688 +1980 25 -3.78 -9.78 -5.43 0 116.79 207.11 32827 +1980 26 -8.88 -14.88 -10.53 0 81.51 210.52 32969 +1980 27 -10.63 -16.63 -12.28 0.07 71.76 170.06 33114 +1980 28 -8.68 -14.68 -10.33 0 82.69 214.64 33261 +1980 29 -2.94 -8.94 -4.59 0 123.71 214.92 33411 +1980 30 -2.46 -8.46 -4.11 0.04 127.83 172.85 33564 +1980 31 0.11 -5.89 -1.54 0 151.95 217.9 33718 +1980 32 4.24 -1.76 2.59 0 198.96 216.84 33875 +1980 33 2.03 -3.97 0.38 0 172.45 220.48 34035 +1980 34 4.31 -1.69 2.66 0 199.85 220.5 34196 +1980 35 8.1 2.1 6.45 0 253.71 180.96 34360 +1980 36 7.48 1.48 5.83 0.03 244.13 138.01 34526 +1980 37 8.16 2.16 6.51 0.38 254.65 139.34 34694 +1980 38 6.96 0.96 5.31 0.33 236.34 142.19 34863 +1980 39 5.17 -0.83 3.52 0 211.12 193.67 35035 +1980 40 6.27 0.27 4.62 0.25 226.32 146.53 35208 +1980 41 5.29 -0.71 3.64 0 212.73 198.8 35383 +1980 42 4.87 -1.13 3.22 0 207.13 201.69 35560 +1980 43 5.95 -0.05 4.3 0 221.81 203.5 35738 +1980 44 5.27 -0.73 3.62 0 212.46 206.63 35918 +1980 45 4.2 -1.8 2.55 0 198.45 210.12 36099 +1980 46 4.67 -1.33 3.02 0.05 204.5 159.33 36282 +1980 47 6.62 0.62 4.97 0.46 231.36 160.17 36466 +1980 48 5.33 -0.67 3.68 0.03 213.27 163.13 36652 +1980 49 5.23 -0.77 3.58 0 211.92 220.37 36838 +1980 50 5.9 -0.1 4.25 0 221.11 222.44 37026 +1980 51 6.91 0.91 5.26 0 235.6 224.45 37215 +1980 52 6.1 0.1 4.45 0 223.91 228.04 37405 +1980 53 5.12 -0.88 3.47 0 210.45 231.9 37596 +1980 54 5.91 -0.09 4.26 0 221.25 233.93 37788 +1980 55 7.99 1.99 6.34 0.12 251.99 176.1 37981 +1980 56 6.5 0.5 4.85 0 229.62 239.04 38175 +1980 57 5.09 -0.91 3.44 0.4 210.05 182.46 38370 +1980 58 2.52 -3.48 0.87 0.49 178.05 186.31 38565 +1980 59 2.02 -3.98 0.37 0 172.34 251.53 38761 +1980 60 2.91 -3.09 1.26 0 182.61 253.74 38958 +1980 61 5.28 -0.72 3.63 0 212.6 254.58 39156 +1980 62 6.26 0.26 4.61 0 226.18 256.4 39355 +1980 63 11.65 5.65 10 0 315.02 252.71 39553 +1980 64 11.57 5.57 9.92 0.15 313.51 191.76 39753 +1980 65 8.98 2.98 7.33 0 267.86 262.07 39953 +1980 66 13.75 7.75 12.1 0 356.94 257.74 40154 +1980 67 8.07 2.07 6.42 0 253.24 268.8 40355 +1980 68 7.07 1.07 5.42 0.03 237.97 204.63 40556 +1980 69 3.49 -2.51 1.84 0 189.59 279.15 40758 +1980 70 5.59 -0.41 3.94 0 216.82 279.96 40960 +1980 71 9.02 3.02 7.37 0 268.52 278.81 41163 +1980 72 5.79 -0.21 4.14 0 219.58 285.51 41366 +1980 73 7.29 1.29 5.64 0 241.26 286.47 41569 +1980 74 8.41 2.41 6.76 0 258.62 287.82 41772 +1980 75 13.02 7.02 11.37 0.86 341.86 212.66 41976 +1980 76 13.87 7.87 12.22 0.38 359.47 213.45 42179 +1980 77 16.78 10.78 15.13 0.33 425.78 210.92 42383 +1980 78 15.01 9.01 13.36 0 384.31 287.54 42587 +1980 79 13.14 7.14 11.49 0.15 344.3 220.32 42791 +1980 80 7.48 1.48 5.83 0 244.13 304.92 42996 +1980 81 7.81 1.81 6.16 0.46 249.19 230.31 43200 +1980 82 11.77 5.77 10.12 0 317.3 303.8 43404 +1980 83 8.05 2.05 6.4 0.05 252.93 233.94 43608 +1980 84 2.72 -3.28 1.07 0.04 180.38 240.45 43812 +1980 85 0.75 -5.25 -0.9 0 158.54 324.93 44016 +1980 86 0.87 -5.13 -0.78 0 159.8 327.29 44220 +1980 87 2.92 -3.08 1.27 0 182.73 327.98 44424 +1980 88 6.12 0.12 4.47 0 224.2 326.82 44627 +1980 89 6.57 0.57 4.92 0 230.63 328.56 44831 +1980 90 6.09 0.09 4.44 0 223.77 331.56 45034 +1980 91 10.36 4.36 8.71 0 291.42 327.73 45237 +1980 92 14.21 8.21 12.56 0 366.73 322.84 45439 +1980 93 15.42 9.42 13.77 0 393.6 322.4 45642 +1980 94 11.55 5.55 9.9 0.32 313.13 249.21 45843 +1980 95 14.38 8.38 12.73 0 370.41 328.88 46045 +1980 96 17.85 11.85 16.2 0.12 452.65 242.04 46246 +1980 97 13.45 7.45 11.8 0.56 350.68 251.2 46446 +1980 98 11.32 5.32 9.67 0.19 308.83 255.71 46647 +1980 99 9.27 3.27 7.62 0.01 272.67 259.82 46846 +1980 100 10.8 4.8 9.15 0.05 299.29 259.38 47045 +1980 101 12.44 6.44 10.79 0 330.27 344.73 47243 +1980 102 12.77 6.77 11.12 0 336.82 345.98 47441 +1980 103 13.48 7.48 11.83 0 351.3 346.36 47638 +1980 104 14.51 8.51 12.86 0.61 373.25 259.46 47834 +1980 105 8.7 2.7 7.05 0.02 263.29 269.01 48030 +1980 106 12.33 6.33 10.68 0 328.11 353.94 48225 +1980 107 9.48 3.48 7.83 0.48 276.2 270.59 48419 +1980 108 11.19 5.19 9.54 0.47 306.42 269.66 48612 +1980 109 6.03 0.03 4.38 0.08 222.93 277.02 48804 +1980 110 4.13 -1.87 2.48 0.09 197.56 279.91 48995 +1980 111 7.11 1.11 5.46 1.02 238.56 278.16 49185 +1980 112 7.87 1.87 6.22 1.68 250.12 278.48 49374 +1980 113 8.49 2.49 6.84 0.05 259.9 278.78 49561 +1980 114 10.88 4.88 9.23 0 300.74 369.11 49748 +1980 115 10.1 4.1 8.45 0 286.85 371.97 49933 +1980 116 8.95 2.95 7.3 0.17 267.37 281.38 50117 +1980 117 7.41 1.41 5.76 0.34 243.07 284.2 50300 +1980 118 6.55 0.55 4.9 0.65 230.34 286.16 50481 +1980 119 10.23 4.23 8.58 0 289.12 376.85 50661 +1980 120 9.32 3.32 7.67 0 273.51 379.64 50840 +1980 121 13.17 7.17 11.52 0.7 344.91 280.01 51016 +1980 122 16.21 10.21 14.56 0.59 412.03 275.47 51191 +1980 123 19.66 13.66 18.01 0.38 501.4 268.75 51365 +1980 124 19.94 13.94 18.29 0 509.33 358.49 51536 +1980 125 22.66 16.66 21.01 0 592.02 349.87 51706 +1980 126 21.43 15.43 19.78 0.21 553.32 266.5 51874 +1980 127 23.81 17.81 22.16 0 630.27 347.14 52039 +1980 128 23.33 17.33 21.68 0.16 614.06 262.51 52203 +1980 129 15.97 9.97 14.32 0.45 406.36 281.03 52365 +1980 130 15.7 9.7 14.05 0 400.05 376.2 52524 +1980 131 17.42 11.42 15.77 0 441.69 372.34 52681 +1980 132 17.03 11.03 15.38 0.01 431.94 280.69 52836 +1980 133 19.57 13.57 17.92 0.19 498.88 275.49 52989 +1980 134 16.44 10.44 14.79 0 417.53 377.28 53138 +1980 135 16.49 10.49 14.84 0.08 418.74 283.38 53286 +1980 136 14.29 8.29 12.64 0.08 368.46 288.06 53430 +1980 137 8.51 2.51 6.86 0.01 260.22 297.31 53572 +1980 138 7.77 1.77 6.12 0.67 248.57 298.69 53711 +1980 139 14.86 8.86 13.21 0.5 380.96 288.53 53848 +1980 140 15.34 9.34 13.69 1.16 391.77 288 53981 +1980 141 9.05 3.05 7.4 0 269.02 397.79 54111 +1980 142 6.35 0.35 4.7 0.27 227.47 301.97 54238 +1980 143 11.48 5.48 9.83 0.43 311.82 295.71 54362 +1980 144 10.98 4.98 9.33 0 302.56 395.77 54483 +1980 145 12.97 6.97 11.32 0 340.85 392.09 54600 +1980 146 16.51 10.51 14.86 0 419.22 383.71 54714 +1980 147 15.76 9.76 14.11 0 401.44 386.21 54824 +1980 148 13.16 7.16 11.51 0 344.71 392.93 54931 +1980 149 12.34 6.34 10.69 0.49 328.3 296.29 55034 +1980 150 11.37 5.37 9.72 0 309.76 397.42 55134 +1980 151 13.84 7.84 12.19 0 358.84 392.42 55229 +1980 152 20.73 14.73 19.08 0 532.26 372.55 55321 +1980 153 25.74 19.74 24.09 0 699.15 352.46 55409 +1980 154 26.65 20.65 25 0.2 733.78 261.32 55492 +1980 155 24.18 18.18 22.53 0 643.01 359.89 55572 +1980 156 23.98 17.98 22.33 0.04 636.09 270.79 55648 +1980 157 18.34 12.34 16.69 0.33 465.43 286.24 55719 +1980 158 19.63 13.63 17.98 0 500.56 377.71 55786 +1980 159 19.42 13.42 17.77 0 494.69 378.64 55849 +1980 160 23.28 17.28 21.63 0.5 612.39 273.53 55908 +1980 161 17.9 11.9 16.25 0.17 453.94 287.74 55962 +1980 162 16.84 10.84 15.19 0.34 427.25 290.1 56011 +1980 163 19.38 13.38 17.73 2.39 493.58 284.47 56056 +1980 164 18.81 12.81 17.16 0.01 477.98 285.88 56097 +1980 165 20.37 14.37 18.72 0.07 521.7 282.08 56133 +1980 166 18.51 12.51 16.86 0.49 469.94 286.72 56165 +1980 167 21.29 15.29 19.64 0 549.05 372.87 56192 +1980 168 22.41 16.41 20.76 0 583.98 368.73 56214 +1980 169 18.48 12.48 16.83 0 469.14 382.42 56231 +1980 170 19.41 13.41 17.76 0.04 494.41 284.59 56244 +1980 171 19.01 13.01 17.36 0.22 483.41 285.61 56252 +1980 172 27.91 21.91 26.26 0.06 784.11 257.89 56256 +1980 173 25.66 19.66 24.01 0.37 696.18 266.21 56255 +1980 174 25.85 19.85 24.2 0.04 703.26 265.49 56249 +1980 175 23.32 17.32 21.67 0 613.72 365.04 56238 +1980 176 19.84 13.84 18.19 0.13 506.48 283.43 56223 +1980 177 16.42 10.42 14.77 0 417.05 388.22 56203 +1980 178 14.01 8.01 12.36 0 362.45 394.43 56179 +1980 179 12.01 6.01 10.36 0.23 321.89 299.11 56150 +1980 180 18.64 12.64 16.99 0.41 473.41 286.12 56116 +1980 181 21.08 15.08 19.43 0.1 542.7 279.92 56078 +1980 182 23.39 17.39 21.74 0.47 616.06 273.16 56035 +1980 183 25.04 19.04 23.39 0.36 673.47 267.73 55987 +1980 184 19.66 13.66 18.01 0 501.4 377.66 55935 +1980 185 18.11 12.11 16.46 0.72 459.4 286.87 55879 +1980 186 17.96 11.96 16.31 3.34 455.5 287.01 55818 +1980 187 17.41 11.41 15.76 0.26 441.43 288.09 55753 +1980 188 16.66 10.66 15.01 0.86 422.85 289.49 55684 +1980 189 18.68 12.68 17.03 0.42 474.48 284.88 55611 +1980 190 15.3 9.3 13.65 0 390.86 389.05 55533 +1980 191 18.07 12.07 16.42 0 458.35 381.06 55451 +1980 192 19.25 13.25 17.6 0 489.98 377.08 55366 +1980 193 17.93 11.93 16.28 0 454.72 380.9 55276 +1980 194 26.57 20.57 24.92 0.04 730.68 260.55 55182 +1980 195 23.69 17.69 22.04 0 626.18 360.04 55085 +1980 196 19.14 13.14 17.49 0.09 486.96 282.18 54984 +1980 197 20.24 14.24 18.59 0.07 517.94 279.12 54879 +1980 198 16.22 10.22 14.57 0 412.27 383.94 54770 +1980 199 19.79 13.79 18.14 0 505.07 372.89 54658 +1980 200 22.59 16.59 20.94 0 589.76 362.44 54542 +1980 201 21.35 15.35 19.7 0 550.88 366.62 54423 +1980 202 19.49 13.49 17.84 0 496.64 372.43 54301 +1980 203 24.01 18.01 22.36 0 637.13 355.22 54176 +1980 204 26.42 20.42 24.77 0 724.89 343.97 54047 +1980 205 26.58 20.58 24.93 0 731.07 342.72 53915 +1980 206 28.31 22.31 26.66 0 800.68 333.5 53780 +1980 207 27.57 21.57 25.92 0.2 770.25 252.52 53643 +1980 208 23.04 17.04 21.39 0.01 604.44 267.24 53502 +1980 209 21.83 15.83 20.18 0 565.66 360.29 53359 +1980 210 22.98 16.98 21.33 0 602.46 355.31 53213 +1980 211 23.21 17.21 21.56 0 610.06 353.65 53064 +1980 212 24.63 18.63 22.98 0.01 658.8 260.27 52913 +1980 213 26.63 20.63 24.98 0.23 733 252.96 52760 +1980 214 25.08 19.08 23.43 0.03 674.91 257.73 52604 +1980 215 22.83 16.83 21.18 0.04 597.55 264.16 52445 +1980 216 20.41 14.41 18.76 0 522.87 359.92 52285 +1980 217 18.25 12.25 16.6 0 463.06 365.84 52122 +1980 218 21.94 15.94 20.29 0 569.1 352.87 51958 +1980 219 20.3 14.3 18.65 0 519.67 357.54 51791 +1980 220 19.98 13.98 18.33 0 510.47 357.65 51622 +1980 221 18.31 12.31 16.66 0 464.64 361.81 51451 +1980 222 17.99 11.99 16.34 0 456.27 361.69 51279 +1980 223 22.85 16.85 21.2 0 598.2 344.4 51105 +1980 224 23.35 17.35 21.7 0 614.73 341.45 50929 +1980 225 26.57 20.57 24.92 0 730.68 326.67 50751 +1980 226 24.92 18.92 23.27 0 669.14 332.88 50572 +1980 227 26.37 20.37 24.72 0 722.97 325.3 50392 +1980 228 27.32 21.32 25.67 0 760.19 319.72 50210 +1980 229 27.62 21.62 25.97 0 772.27 317.12 50026 +1980 230 26.98 20.98 25.33 0 746.69 318.98 49842 +1980 231 21.11 15.11 19.46 0.04 543.61 255.73 49656 +1980 232 22.14 16.14 20.49 0 575.39 336.07 49469 +1980 233 25.79 19.79 24.14 0.6 701.02 240.25 49280 +1980 234 21.75 15.75 20.1 0.18 563.17 250.99 49091 +1980 235 20.16 14.16 18.51 0.25 515.63 253.82 48900 +1980 236 22.64 16.64 20.99 0 591.38 328.65 48709 +1980 237 24.76 18.76 23.11 0 663.42 318.95 48516 +1980 238 22.4 16.4 20.75 0 583.66 326.27 48323 +1980 239 23.91 17.91 22.26 0 633.69 319.25 48128 +1980 240 20.27 14.27 18.62 0 518.8 330.13 47933 +1980 241 17.29 11.29 15.64 0 438.42 336.93 47737 +1980 242 19.36 13.36 17.71 0 493.03 329.45 47541 +1980 243 18.74 12.74 17.09 3.18 476.09 247.03 47343 +1980 244 14.92 8.92 13.27 0.55 382.3 252.87 47145 +1980 245 16.12 10.12 14.47 0 409.89 332.51 46947 +1980 246 16.65 10.65 15 0 422.61 329.23 46747 +1980 247 15.78 9.78 14.13 0.08 401.91 247.08 46547 +1980 248 15.12 9.12 13.47 0.37 386.79 246.73 46347 +1980 249 14.62 8.62 12.97 0.12 375.66 245.98 46146 +1980 250 14.83 8.83 13.18 0.05 380.3 244.15 45945 +1980 251 12.45 6.45 10.8 0 330.46 328.18 45743 +1980 252 19.46 13.46 17.81 0 495.8 309.75 45541 +1980 253 16.88 10.88 15.23 0.06 428.23 235.78 45339 +1980 254 19.45 13.45 17.8 0.25 495.53 229.19 45136 +1980 255 21.96 15.96 20.31 0.02 569.72 221.91 44933 +1980 256 19.3 13.3 17.65 0 491.36 301.53 44730 +1980 257 22.74 16.74 21.09 0.62 594.62 216.81 44527 +1980 258 16.07 10.07 14.42 0.76 408.71 228.79 44323 +1980 259 13.84 7.84 12.19 0.17 358.84 230.45 44119 +1980 260 13.66 7.66 12.01 0.03 355.05 228.9 43915 +1980 261 16.91 10.91 15.26 0.17 428.97 221.91 43711 +1980 262 15.06 9.06 13.41 0.19 385.44 223.15 43507 +1980 263 17.52 11.52 15.87 0 444.22 289.64 43303 +1980 264 19.06 13.06 17.41 0 484.77 283.3 43099 +1980 265 21.35 15.35 19.7 0.14 550.88 206.05 42894 +1980 266 21.68 15.68 20.03 0 561.01 271.38 42690 +1980 267 22.6 16.6 20.95 0 590.08 266.05 42486 +1980 268 22.72 16.72 21.07 1.26 593.97 197.43 42282 +1980 269 23.59 17.59 21.94 0.74 622.79 193.59 42078 +1980 270 19.71 13.71 18.06 0.18 502.81 200.06 41875 +1980 271 20.21 14.21 18.56 0.26 517.07 197.18 41671 +1980 272 23.24 17.24 21.59 0 611.06 251.68 41468 +1980 273 25.45 19.45 23.8 0 688.41 242.11 41265 +1980 274 17.4 11.4 15.75 0 441.18 261.89 41062 +1980 275 19.44 13.44 17.79 0 495.25 254.48 40860 +1980 276 22.05 16.05 20.4 0 572.55 245.08 40658 +1980 277 22 16 20.35 0.18 570.98 182.02 40456 +1980 278 19.52 13.52 17.87 0.34 497.48 184.74 40255 +1980 279 18.19 12.19 16.54 0.44 461.49 184.98 40054 +1980 280 16.94 10.94 15.29 0 429.71 246.68 39854 +1980 281 10.81 4.81 9.16 0 299.47 254.32 39654 +1980 282 9.26 3.26 7.61 0 272.5 253.59 39455 +1980 283 9.8 3.8 8.15 0 281.65 250.04 39256 +1980 284 8.67 2.67 7.02 0.35 262.8 186.28 39058 +1980 285 8.22 2.22 6.57 0.56 255.6 184.65 38861 +1980 286 11.94 5.94 10.29 0.02 320.54 178.98 38664 +1980 287 13.61 7.61 11.96 0.76 354.01 174.91 38468 +1980 288 11.41 5.41 9.76 0 310.51 233.64 38273 +1980 289 11.95 5.95 10.3 0 320.74 230.26 38079 +1980 290 11.02 5.02 9.37 0.66 303.3 171.48 37885 +1980 291 15.03 9.03 13.38 2.01 384.76 165.04 37693 +1980 292 14.37 8.37 12.72 0 370.19 218.47 37501 +1980 293 13.38 7.38 11.73 0.79 349.23 162.95 37311 +1980 294 15.06 9.06 13.41 0.44 385.44 158.87 37121 +1980 295 11.43 5.43 9.78 0.03 310.88 160.68 36933 +1980 296 12.73 6.73 11.08 0.05 336.02 157.45 36745 +1980 297 11.51 5.51 9.86 0.35 312.38 156.62 36560 +1980 298 11.92 5.92 10.27 0.91 320.16 154.28 36375 +1980 299 9.8 3.8 8.15 0.35 281.65 154.1 36191 +1980 300 11.84 5.84 10.19 0.54 318.63 150.29 36009 +1980 301 11.62 5.62 9.97 1.1 314.45 148.62 35829 +1980 302 10.41 4.41 8.76 0 292.3 196.97 35650 +1980 303 11.23 5.23 9.58 0.18 307.16 145.09 35472 +1980 304 8.63 2.63 6.98 0 262.15 193.8 35296 +1980 305 0.62 -5.38 -1.03 0 157.18 197.19 35122 +1980 306 1.42 -4.58 -0.23 0.13 165.69 145.8 34950 +1980 307 -0.81 -6.81 -2.46 0 142.9 193.08 34779 +1980 308 1.11 -4.89 -0.54 0 162.35 189.36 34610 +1980 309 7.07 1.07 5.42 0.31 237.97 137.06 34444 +1980 310 8.22 2.22 6.57 0.34 255.6 134.46 34279 +1980 311 9.92 3.92 8.27 0.34 283.72 131.61 34116 +1980 312 12.65 6.65 11 1.39 334.42 127.41 33956 +1980 313 14.65 8.65 13 0.3 376.32 123.99 33797 +1980 314 10.95 4.95 9.3 0.03 302.02 125.82 33641 +1980 315 15.09 9.09 13.44 0 386.11 160.38 33488 +1980 316 13.94 7.94 12.29 0.37 360.96 119.8 33337 +1980 317 8.89 2.89 7.24 1.03 266.38 122.17 33188 +1980 318 7.03 1.03 5.38 0.8 237.37 121.6 33042 +1980 319 2.8 -3.2 1.15 1.35 181.32 122.49 32899 +1980 320 6.1 0.1 4.45 0 223.91 159.26 32758 +1980 321 1.2 -4.8 -0.45 1.38 163.31 120.14 32620 +1980 322 3.75 -2.25 2.1 0.19 192.79 117.67 32486 +1980 323 4.95 -1.05 3.3 0.16 208.18 115.87 32354 +1980 324 6.28 0.28 4.63 0 226.47 151.52 32225 +1980 325 6.44 0.44 4.79 0.12 228.76 112.26 32100 +1980 326 5.14 -0.86 3.49 0.04 210.72 111.84 31977 +1980 327 3.8 -2.2 2.15 0.75 193.42 111.07 31858 +1980 328 4.77 -1.23 3.12 0.01 205.81 109.14 31743 +1980 329 5.66 -0.34 4.01 0.09 217.78 107.59 31631 +1980 330 6.61 0.61 4.96 0.68 231.21 106.02 31522 +1980 331 7.89 1.89 6.24 0.16 250.43 104.34 31417 +1980 332 9.48 3.48 7.83 1.03 276.2 102.17 31316 +1980 333 6.57 0.57 4.92 0 230.63 137.35 31218 +1980 334 9.32 3.32 7.67 0 273.51 134.21 31125 +1980 335 5.06 -0.94 3.41 0.01 209.65 102.05 31035 +1980 336 2.98 -3.02 1.33 0 183.44 136.18 30949 +1980 337 4.86 -1.14 3.21 0 206.99 133.45 30867 +1980 338 3.31 -2.69 1.66 0 187.4 133.39 30790 +1980 339 6.72 0.72 5.07 0 232.81 130.55 30716 +1980 340 7.77 1.77 6.12 0 248.57 129.09 30647 +1980 341 8.14 2.14 6.49 0 254.34 127.92 30582 +1980 342 7.4 1.4 5.75 0 242.92 127.69 30521 +1980 343 6.38 0.38 4.73 0 227.89 127.55 30465 +1980 344 6.47 0.47 4.82 0 229.19 126.37 30413 +1980 345 2.82 -3.18 1.17 0.08 181.55 96.03 30366 +1980 346 3.95 -2.05 2.3 0 195.29 126.89 30323 +1980 347 2.76 -3.24 1.11 0 180.85 126.91 30284 +1980 348 2.45 -3.55 0.8 0 177.24 126.72 30251 +1980 349 4.72 -1.28 3.07 0 205.16 125.13 30221 +1980 350 3.49 -2.51 1.84 0.38 189.59 94.1 30197 +1980 351 1.88 -4.12 0.23 0 170.77 126.05 30177 +1980 352 2.15 -3.85 0.5 0.56 173.81 94.37 30162 +1980 353 2.83 -3.17 1.18 0.59 181.67 94.07 30151 +1980 354 2.98 -3.02 1.33 1 183.44 93.99 30145 +1980 355 -4.33 -10.33 -5.98 0.53 112.43 141.66 30144 +1980 356 -1.57 -7.57 -3.22 0 135.78 172.8 30147 +1980 357 -1.99 -7.99 -3.64 0 131.98 173.01 30156 +1980 358 1.61 -4.39 -0.04 0 167.77 171.38 30169 +1980 359 3.17 -2.83 1.52 0.34 185.71 138.91 30186 +1980 360 1.07 -4.93 -0.58 0.02 161.92 139.77 30208 +1980 361 2.01 -3.99 0.36 0.59 172.22 139.39 30235 +1980 362 1.51 -4.49 -0.14 0 166.68 171.51 30267 +1980 363 0.25 -5.75 -1.4 0 153.37 172.58 30303 +1980 364 1.56 -4.44 -0.09 0 167.22 172.12 30343 +1980 365 1.52 -4.48 -0.13 0 166.78 129.02 30388 +1981 1 0.77 -5.23 -0.88 0 158.75 130.26 30438 +1981 2 -1.64 -7.64 -3.29 0.35 135.14 143.38 30492 +1981 3 -3.31 -9.31 -4.96 0 120.62 177.85 30551 +1981 4 -4.93 -10.93 -6.58 0 107.85 179.21 30614 +1981 5 -1.72 -7.72 -3.37 0 134.41 178.67 30681 +1981 6 0.71 -5.29 -0.94 0.07 158.12 144.75 30752 +1981 7 1.95 -4.05 0.3 1.48 171.55 144.55 30828 +1981 8 -1.41 -7.41 -3.06 0.24 137.25 147.43 30907 +1981 9 -1.68 -7.68 -3.33 0 134.77 183.09 30991 +1981 10 -0.33 -6.33 -1.98 0 147.56 183.73 31079 +1981 11 -1.77 -7.77 -3.42 0 133.96 185.19 31171 +1981 12 -0.95 -6.95 -2.6 0 141.57 185.75 31266 +1981 13 -2.1 -8.1 -3.75 0 131 187.71 31366 +1981 14 1.16 -4.84 -0.49 0 162.88 187.49 31469 +1981 15 4.66 -1.34 3.01 0 204.37 186.26 31575 +1981 16 1.23 -4.77 -0.42 0.06 163.64 152.42 31686 +1981 17 0.11 -5.89 -1.54 0 151.95 191.22 31800 +1981 18 3.64 -2.36 1.99 0 191.43 190.66 31917 +1981 19 3.28 -2.72 1.63 0.03 187.04 113.53 32038 +1981 20 4.71 -1.29 3.06 0 205.02 152.08 32161 +1981 21 3.78 -2.22 2.13 0 193.17 154.66 32289 +1981 22 3.49 -2.51 1.84 0 189.59 156.59 32419 +1981 23 -0.05 -6.05 -1.7 0 150.34 160.29 32552 +1981 24 4.71 -1.29 3.06 0 205.02 159.65 32688 +1981 25 3.52 -2.48 1.87 0 189.96 162.31 32827 +1981 26 2.89 -3.11 1.24 0.02 182.38 123.47 32969 +1981 27 3.06 -2.94 1.41 0.07 184.4 124.91 33114 +1981 28 1.66 -4.34 0.01 0 168.32 169.59 33261 +1981 29 3.05 -2.95 1.4 0 184.28 171.15 33411 +1981 30 3.01 -2.99 1.36 0 183.8 173.42 33564 +1981 31 1.37 -4.63 -0.28 0.02 165.15 132.59 33718 +1981 32 5.69 -0.31 4.04 0 218.19 176.05 33875 +1981 33 3.97 -2.03 2.32 0 195.54 179.92 34035 +1981 34 3.95 -2.05 2.3 0 195.29 182.14 34196 +1981 35 4.87 -1.13 3.22 0 207.13 183.63 34360 +1981 36 7.05 1.05 5.4 0 237.67 184.38 34526 +1981 37 5.98 -0.02 4.33 0 222.23 187.69 34694 +1981 38 8.07 2.07 6.42 0 253.24 188.59 34863 +1981 39 5.08 -0.92 3.43 0.56 209.91 145.31 35035 +1981 40 3.82 -2.18 2.17 0.01 193.66 147.98 35208 +1981 41 6.11 0.11 4.46 0.09 224.06 148.59 35383 +1981 42 3.69 -2.31 2.04 0.25 192.05 151.94 35560 +1981 43 5.65 -0.35 4 0 217.64 203.75 35738 +1981 44 7.23 1.23 5.58 0.05 240.35 153.68 35918 +1981 45 5.37 -0.63 3.72 0 213.82 209.17 36099 +1981 46 5.4 -0.6 3.75 0.38 214.22 158.87 36282 +1981 47 2.53 -3.47 0.88 0 178.16 216.89 36466 +1981 48 1.02 -4.98 -0.63 0.02 161.39 165.56 36652 +1981 49 4.84 -1.16 3.19 0 206.73 220.71 36838 +1981 50 4.41 -1.59 2.76 0.39 201.13 167.8 37026 +1981 51 -1.66 -7.66 -3.31 0.01 134.96 208.66 37215 +1981 52 1.76 -4.24 0.11 0.15 169.43 173.7 37405 +1981 53 0.42 -5.58 -1.23 0.17 155.11 176.62 37596 +1981 54 -0.16 -6.16 -1.81 0 149.25 238.66 37788 +1981 55 -0.1 -6.1 -1.75 0 149.84 241.66 37981 +1981 56 3.13 -2.87 1.48 0 185.23 242.06 38175 +1981 57 4.44 -1.56 2.79 0.37 201.52 182.89 38370 +1981 58 7.4 1.4 5.75 0 242.92 243.9 38565 +1981 59 5.35 -0.65 3.7 0 213.54 248.68 38761 +1981 60 16.12 10.12 14.47 0.03 409.89 177.61 38958 +1981 61 11.97 5.97 10.32 0 321.12 246.55 39156 +1981 62 13.11 7.11 11.46 0 343.69 247.54 39355 +1981 63 14.5 8.5 12.85 0 373.03 248.16 39553 +1981 64 17.85 11.85 16.2 0 452.65 244.49 39753 +1981 65 16.26 10.26 14.61 0 413.22 250.5 39953 +1981 66 12.77 6.77 11.12 0.08 336.82 194.52 40154 +1981 67 13.39 7.39 11.74 0.02 349.43 195.88 40355 +1981 68 11.78 5.78 10.13 0.38 317.49 199.93 40556 +1981 69 8.92 2.92 7.27 0.21 266.88 204.91 40758 +1981 70 12.29 6.29 10.64 0.39 327.32 203.36 40960 +1981 71 6.27 0.27 4.62 0 226.32 282.15 41163 +1981 72 9.96 3.96 8.31 0 284.41 280.33 41366 +1981 73 13.27 7.27 11.62 0 346.96 277.75 41569 +1981 74 14.82 8.82 13.17 0.11 380.08 208.18 41772 +1981 75 16.88 10.88 15.23 0 428.23 275.98 41976 +1981 76 14.49 8.49 12.84 0.08 372.81 212.57 42179 +1981 77 12.91 6.91 11.26 2.61 339.63 216.65 42383 +1981 78 13.11 7.11 11.46 0.19 343.69 218.35 42587 +1981 79 10.44 4.44 8.79 0 292.83 298.25 42791 +1981 80 10.71 4.71 9.06 0.03 297.67 225.26 42996 +1981 81 4.96 -1.04 3.31 0 208.32 310.51 43200 +1981 82 3.88 -2.12 2.23 0 194.41 314.34 43404 +1981 83 8.7 2.7 7.05 0 263.29 311.03 43608 +1981 84 9.7 3.7 8.05 0 279.94 312.11 43812 +1981 85 9.46 3.46 7.81 0 275.86 314.96 44016 +1981 86 11.21 5.21 9.56 0 306.79 314.59 44220 +1981 87 11.23 5.23 9.58 0 307.16 317.07 44424 +1981 88 14.13 8.13 12.48 0 365.02 314.02 44627 +1981 89 9.41 3.41 7.76 0 275.02 324.6 44831 +1981 90 11.99 5.99 10.34 0 321.51 322.69 45034 +1981 91 15.85 9.85 14.2 0 403.54 317.08 45237 +1981 92 17.8 11.8 16.15 0 451.37 314.53 45439 +1981 93 16.37 10.37 14.72 0 415.85 320.2 45642 +1981 94 15.49 9.49 13.84 0 395.2 324.34 45843 +1981 95 14.07 8.07 12.42 0 363.73 329.54 46045 +1981 96 14.12 8.12 12.47 0 364.8 331.51 46246 +1981 97 16.66 10.66 15.01 0 422.85 327.74 46446 +1981 98 14.7 8.7 13.05 0 377.42 334.22 46647 +1981 99 17.1 11.1 15.45 0 433.67 330.5 46846 +1981 100 12.35 6.35 10.7 0 328.5 342.98 47045 +1981 101 13.9 7.9 12.25 0 360.11 341.76 47243 +1981 102 11.9 5.9 10.25 0 319.78 347.67 47441 +1981 103 12.66 6.66 11.01 0 334.62 348.03 47638 +1981 104 14.16 8.16 12.51 0 365.66 346.72 47834 +1981 105 14.05 8.05 12.4 0 363.3 348.73 48030 +1981 106 12.7 6.7 11.05 0 335.42 353.2 48225 +1981 107 9.66 3.66 8.01 0 279.26 360.48 48419 +1981 108 9.38 3.38 7.73 0 274.51 362.71 48612 +1981 109 8.38 2.38 6.73 0 258.14 365.95 48804 +1981 110 9.66 3.66 8.01 0 279.26 365.3 48995 +1981 111 6.57 0.57 4.92 0.15 230.63 278.74 49185 +1981 112 10.55 4.55 8.9 0 294.79 366.85 49374 +1981 113 13.81 7.81 12.16 0.04 358.21 271.26 49561 +1981 114 13.66 7.66 12.01 0 355.05 363.5 49748 +1981 115 13.43 7.43 11.78 1.52 350.26 274.07 49933 +1981 116 13.02 7.02 11.37 0 341.86 367.53 50117 +1981 117 16.77 10.77 15.12 0 425.54 359.89 50300 +1981 118 15.49 9.49 13.84 0 395.2 364.48 50481 +1981 119 16.49 10.49 14.84 0 418.74 363.11 50661 +1981 120 14.22 8.22 12.57 0 366.95 369.87 50840 +1981 121 16.41 10.41 14.76 0 416.81 365.59 51016 +1981 122 18.2 12.2 16.55 0 461.75 361.8 51191 +1981 123 20.97 14.97 19.32 0 539.4 354 51365 +1981 124 20.43 14.43 18.78 0 523.45 356.87 51536 +1981 125 19.19 13.19 17.54 0 488.33 361.83 51706 +1981 126 17.36 11.36 15.71 0 440.17 368.23 51874 +1981 127 14.68 8.68 13.03 0 376.98 376.09 52039 +1981 128 16.86 10.86 15.21 0 427.74 371.49 52203 +1981 129 18.63 12.63 16.98 0 473.14 367.21 52365 +1981 130 20.01 14.01 18.36 0.43 511.32 272.71 52524 +1981 131 26.47 20.47 24.82 0 726.82 338.68 52681 +1981 132 20.45 14.45 18.8 0.03 524.04 272.79 52836 +1981 133 18.38 12.38 16.73 0 466.49 371.04 52989 +1981 134 21.61 15.61 19.96 0 558.84 361.01 53138 +1981 135 23.66 17.66 22.01 0 625.16 353.79 53286 +1981 136 23.42 17.42 21.77 0.71 617.07 266.52 53430 +1981 137 18.57 12.57 16.92 0.27 471.54 279.88 53572 +1981 138 19.32 13.32 17.67 1.44 491.92 278.56 53711 +1981 139 16.18 10.18 14.53 0.77 411.32 285.99 53848 +1981 140 20.07 14.07 18.42 0 513.04 370.11 53981 +1981 141 15.41 9.41 13.76 0.11 393.37 288.19 54111 +1981 142 11.58 5.58 9.93 0 313.7 393.53 54238 +1981 143 13.12 7.12 11.47 0 343.89 390.79 54362 +1981 144 11.98 5.98 10.33 0.8 321.31 295.31 54483 +1981 145 11.97 5.97 10.32 0.89 321.12 295.69 54600 +1981 146 14.82 8.82 13.17 0.24 380.08 291.09 54714 +1981 147 15.66 9.66 14.01 0.98 399.12 289.85 54824 +1981 148 12.2 6.2 10.55 0.08 325.57 296.27 54931 +1981 149 15.1 9.1 13.45 0 386.34 388.61 55034 +1981 150 20.19 14.19 18.54 0.42 516.49 280.45 55134 +1981 151 17.83 11.83 16.18 0.48 452.14 286.38 55229 +1981 152 22.23 16.23 20.58 0.12 578.24 275.29 55321 +1981 153 20.35 14.35 18.7 0.88 521.12 280.59 55409 +1981 154 19.27 13.27 17.62 0.73 490.54 283.53 55492 +1981 155 20.16 14.16 18.51 0.05 515.63 281.45 55572 +1981 156 19.45 13.45 17.8 1.45 495.53 283.47 55648 +1981 157 19.23 13.23 17.58 0.59 489.43 284.13 55719 +1981 158 17.63 11.63 15.98 0.18 447.01 287.97 55786 +1981 159 19.89 13.89 18.24 0 507.9 377.08 55849 +1981 160 25.64 19.64 23.99 0.42 695.43 265.84 55908 +1981 161 24.66 18.66 23.01 0.43 659.86 269.2 55962 +1981 162 24.73 18.73 23.08 0.07 662.35 269.01 56011 +1981 163 23.58 17.58 21.93 0.3 622.45 272.85 56056 +1981 164 23.92 17.92 22.27 0.26 634.03 271.82 56097 +1981 165 20.74 14.74 19.09 0 532.56 374.81 56133 +1981 166 20.26 14.26 18.61 0 518.51 376.57 56165 +1981 167 20.2 14.2 18.55 0.04 516.78 282.54 56192 +1981 168 23.21 17.21 21.56 0 610.06 365.55 56214 +1981 169 25.61 19.61 23.96 0.46 694.32 266.36 56231 +1981 170 25.32 19.32 23.67 0.02 683.64 267.36 56244 +1981 171 25.66 19.66 24.01 0.9 696.18 266.23 56252 +1981 172 16.83 10.83 15.18 0 427.01 387.36 56256 +1981 173 14.78 8.78 13.13 0.17 379.19 294.59 56255 +1981 174 16.11 10.11 14.46 0.13 409.66 291.93 56249 +1981 175 17.19 11.19 15.54 0.63 435.91 289.65 56238 +1981 176 21.88 15.88 20.23 0.35 567.22 277.99 56223 +1981 177 25.57 19.57 23.92 0 692.84 355.12 56203 +1981 178 24.85 18.85 23.2 0 666.63 358.41 56179 +1981 179 26.81 20.81 25.16 0 740.02 349.13 56150 +1981 180 25.37 19.37 23.72 0.43 685.47 266.89 56116 +1981 181 25.14 19.14 23.49 0.16 677.09 267.63 56078 +1981 182 23.66 17.66 22.01 0.05 625.16 272.33 56035 +1981 183 23.96 17.96 22.31 1.46 635.41 271.25 55987 +1981 184 22.94 16.94 21.29 1.07 601.15 274.28 55935 +1981 185 20.2 14.2 18.55 0 516.78 375.76 55879 +1981 186 22.34 16.34 20.69 0.06 581.74 275.79 55818 +1981 187 22.64 16.64 20.99 0.4 591.38 274.78 55753 +1981 188 20.56 14.56 18.91 0.38 527.26 280.35 55684 +1981 189 24.44 18.44 22.79 0.06 652.09 268.89 55611 +1981 190 23 17 21.35 2.27 603.12 273.11 55533 +1981 191 20.89 14.89 19.24 1.49 537.02 278.87 55451 +1981 192 18.62 12.62 16.97 0 472.87 379.07 55366 +1981 193 18.32 12.32 16.67 0 464.91 379.72 55276 +1981 194 24.91 18.91 23.26 0 668.79 355.08 55182 +1981 195 30.93 24.93 29.28 0 916.73 323.38 55085 +1981 196 28.05 22.05 26.4 0.32 789.88 254.47 54984 +1981 197 27.73 21.73 26.08 0.3 776.75 255.4 54879 +1981 198 25.96 19.96 24.31 0 707.39 348.81 54770 +1981 199 27.74 21.74 26.09 0.01 777.15 254.81 54658 +1981 200 25.92 19.92 24.27 0.01 705.89 261.21 54542 +1981 201 26.23 20.23 24.58 0 717.62 346.37 54423 +1981 202 20.93 14.93 19.28 0.02 538.21 275.67 54301 +1981 203 18.77 12.77 17.12 0 476.9 374.21 54176 +1981 204 21.04 15.04 19.39 0 541.5 366.16 54047 +1981 205 26.39 20.39 24.74 0.29 723.74 257.72 53915 +1981 206 21.12 15.12 19.47 0 543.91 364.8 53780 +1981 207 19.33 13.33 17.68 0 492.19 370.18 53643 +1981 208 16.76 10.76 15.11 0 425.29 377.15 53502 +1981 209 14.57 8.57 12.92 0.16 374.56 286.6 53359 +1981 210 17.59 11.59 15.94 0.03 446 280.13 53213 +1981 211 21.8 15.8 20.15 0 564.73 359.02 53064 +1981 212 23.75 17.75 22.1 0 628.22 350.7 52913 +1981 213 21.54 15.54 19.89 0 556.69 358.42 52760 +1981 214 20.4 14.4 18.75 0 522.58 361.64 52604 +1981 215 20.36 14.36 18.71 0 521.41 361.1 52445 +1981 216 17.9 11.9 16.25 0 453.94 367.77 52285 +1981 217 18.77 12.77 17.12 0 476.9 364.27 52122 +1981 218 16.15 10.15 14.5 0 410.61 370.85 51958 +1981 219 15.73 9.73 14.08 0 400.75 370.86 51791 +1981 220 16.54 10.54 14.89 0.01 419.95 275.84 51622 +1981 221 17.28 11.28 15.63 0.11 438.16 273.57 51451 +1981 222 14.42 8.42 12.77 0.02 371.28 278.23 51279 +1981 223 20.89 14.89 19.24 0 537.02 351.45 51105 +1981 224 19.8 13.8 18.15 0 505.35 353.98 50929 +1981 225 22.31 16.31 20.66 0 580.78 344.26 50751 +1981 226 23.32 17.32 21.67 0 613.72 339.34 50572 +1981 227 24.99 18.99 23.34 0 671.66 331.35 50392 +1981 228 25.48 19.48 23.83 0 689.52 328.09 50210 +1981 229 26.19 20.19 24.54 0 716.1 323.79 50026 +1981 230 27.04 21.04 25.39 0.01 749.06 239.02 49842 +1981 231 30.01 24.01 28.36 0 874.47 302.29 49656 +1981 232 29.6 23.6 27.95 0 856.17 303.28 49469 +1981 233 30.63 24.63 28.98 0 902.77 296.36 49280 +1981 234 27.19 21.19 25.54 0 755 312.7 49091 +1981 235 27.95 21.95 26.3 0.14 785.75 230.78 48900 +1981 236 29.36 23.36 27.71 0.61 845.61 224.5 48709 +1981 237 30.01 24.01 28.36 0 874.47 294.4 48516 +1981 238 29.87 23.87 28.22 0.24 868.18 220.22 48323 +1981 239 24.67 18.67 23.02 0.75 660.22 237.21 48128 +1981 240 21.44 15.44 19.79 0.65 553.62 244.78 47933 +1981 241 18.9 12.9 17.25 1.27 480.41 249.39 47737 +1981 242 21.92 15.92 20.27 0.81 568.47 241.02 47541 +1981 243 21.57 15.57 19.92 0.36 557.61 240.54 47343 +1981 244 18.61 12.61 16.96 0.05 472.61 245.94 47145 +1981 245 22.51 16.51 20.86 0.09 587.18 235.47 46947 +1981 246 18.93 12.93 17.28 0.11 481.23 242.42 46747 +1981 247 15.65 9.65 14 0.48 398.89 247.31 46547 +1981 248 13.87 7.87 12.22 0.9 359.47 248.75 46347 +1981 249 13.46 7.46 11.81 0.76 350.88 247.79 46146 +1981 250 10.69 4.69 9.04 1.34 297.3 250.12 45945 +1981 251 13.45 7.45 11.8 2.03 350.68 244.69 45743 +1981 252 13.96 7.96 12.31 0 361.38 323.01 45541 +1981 253 15.52 9.52 13.87 0 395.89 317.54 45339 +1981 254 18.67 12.67 17.02 0 474.21 307.71 45136 +1981 255 18.38 12.38 16.73 0 466.49 306.23 44933 +1981 256 18.79 12.79 17.14 0 477.44 302.91 44730 +1981 257 24.45 18.45 22.8 0 652.44 283.16 44527 +1981 258 26.06 20.06 24.41 0 711.17 274.87 44323 +1981 259 23.71 17.71 22.06 0.33 626.86 210.93 44119 +1981 260 20.58 14.58 18.93 0.58 527.84 216.61 43915 +1981 261 21.66 15.66 20.01 0.53 560.39 212.43 43711 +1981 262 22.79 16.79 21.14 0.08 596.25 208.08 43507 +1981 263 26.57 20.57 24.92 0 730.68 261.66 43303 +1981 264 26.6 20.6 24.95 0 731.84 259.17 43099 +1981 265 23.68 17.68 22.03 0 625.84 267.49 42894 +1981 266 23.71 17.71 22.06 0.31 626.86 198.79 42690 +1981 267 22.53 16.53 20.88 0.84 587.83 199.7 42486 +1981 268 20.06 14.06 18.41 0.53 512.76 203.13 42282 +1981 269 17.35 11.35 15.7 0.59 439.92 206.25 42078 +1981 270 16.58 10.58 14.93 0.29 420.91 205.56 41875 +1981 271 17.24 11.24 15.59 0.29 437.16 202.54 41671 +1981 272 18.64 12.64 16.99 0 473.41 264.17 41468 +1981 273 19.08 13.08 17.43 0.78 485.32 195.48 41265 +1981 274 12.7 6.7 11.05 0 335.42 270.83 41062 +1981 275 11.25 5.25 9.6 0.02 307.53 202.73 40860 +1981 276 14.69 8.69 13.04 0.04 377.2 196.42 40658 +1981 277 14.35 8.35 12.7 1.16 369.76 194.89 40456 +1981 278 14.78 8.78 13.13 0.46 379.19 192.16 40255 +1981 279 12.34 6.34 10.69 0 328.3 257.5 40054 +1981 280 17.97 11.97 16.32 0 455.76 244.53 39854 +1981 281 18.88 12.88 17.23 0 479.87 239.89 39654 +1981 282 17.85 11.85 16.2 0.33 452.65 179.6 39455 +1981 283 19.46 13.46 17.81 0 495.8 233.2 39256 +1981 284 19.2 13.2 17.55 0.04 488.61 173.15 39058 +1981 285 18.64 12.64 16.99 0 473.41 229.54 38861 +1981 286 17.47 11.47 15.82 0.3 442.95 171.96 38664 +1981 287 16.04 10.04 14.39 0.06 408 171.83 38468 +1981 288 15.65 9.65 14 0.09 398.89 170.3 38273 +1981 289 12.85 6.85 11.2 0 338.42 228.97 38079 +1981 290 17.12 11.12 15.47 0 434.17 219.02 37885 +1981 291 19.01 13.01 17.36 0 483.41 212.67 37693 +1981 292 16.69 10.69 15.04 0.26 423.59 160.92 37501 +1981 293 11.73 5.73 10.08 0.34 316.53 164.68 37311 +1981 294 13.67 7.67 12.02 0 355.26 213.98 37121 +1981 295 14 8 12.35 0.37 362.24 158.01 36933 +1981 296 9.49 3.49 7.84 0 276.37 213.97 36745 +1981 297 12.53 6.53 10.88 0 332.04 207.5 36560 +1981 298 14.79 8.79 13.14 0.67 379.41 151.27 36375 +1981 299 12.55 6.55 10.9 0.14 332.44 151.59 36191 +1981 300 14.27 8.27 12.62 0 368.03 197.11 36009 +1981 301 15.36 9.36 13.71 0 392.23 193.01 35829 +1981 302 18.18 12.18 16.53 0 461.23 185.79 35650 +1981 303 13.76 7.76 12.11 0 357.15 190.24 35472 +1981 304 13.91 7.91 12.26 0.86 360.32 140.71 35296 +1981 305 7.17 1.17 5.52 0 239.46 192.42 35122 +1981 306 9.86 3.86 8.21 0 282.68 187.55 34950 +1981 307 12.85 6.85 11.2 1.24 338.42 136.22 34779 +1981 308 10.63 4.63 8.98 0.01 296.23 136.22 34610 +1981 309 8.59 2.59 6.94 0 261.51 181.38 34444 +1981 310 7.03 1.03 5.38 0 237.37 180.33 34279 +1981 311 7.33 1.33 5.68 0 241.86 177.88 34116 +1981 312 4.47 -1.53 2.82 0 201.91 177.45 33956 +1981 313 8.34 2.34 6.69 0.25 257.5 129.17 33797 +1981 314 7.84 1.84 6.19 0.29 249.65 128.04 33641 +1981 315 6.64 0.64 4.99 0.01 231.65 126.88 33488 +1981 316 4.58 -1.42 2.93 0 203.33 168.49 33337 +1981 317 4 -2 2.35 0 195.92 166.66 33188 +1981 318 0.92 -5.08 -0.73 0 160.33 166.11 33042 +1981 319 2.96 -3.04 1.31 0.24 183.21 122.42 32899 +1981 320 8.49 2.49 6.84 0.09 259.9 118.03 32758 +1981 321 8.34 2.34 6.69 0 257.5 155.4 32620 +1981 322 12.48 6.48 10.83 0 331.05 149.67 32486 +1981 323 14.31 8.31 12.66 0 368.89 146.04 32354 +1981 324 10.57 4.57 8.92 0 295.15 147.99 32225 +1981 325 11.53 5.53 9.88 0.05 312.76 109.03 32100 +1981 326 11.62 5.62 9.97 0 314.45 143.86 31977 +1981 327 8.06 2.06 6.41 0 253.08 145.17 31858 +1981 328 11.42 5.42 9.77 0.19 310.69 105.23 31743 +1981 329 9.9 3.9 8.25 0.6 283.37 105.16 31631 +1981 330 8.93 2.93 7.28 0.29 267.04 104.7 31522 +1981 331 10.21 4.21 8.56 0 288.77 137.23 31417 +1981 332 8.08 2.08 6.43 0.2 253.4 103.01 31316 +1981 333 3.76 -2.24 2.11 1.23 192.92 104.33 31218 +1981 334 4.88 -1.12 3.23 0.9 207.26 103.01 31125 +1981 335 -2.95 -8.95 -4.6 0.2 123.63 148.06 31035 +1981 336 1.25 -4.75 -0.4 0 163.85 180.16 30949 +1981 337 3.91 -2.09 2.26 0 194.79 134 30867 +1981 338 6.49 0.49 4.84 0.3 229.48 98.61 30790 +1981 339 7.52 1.52 5.87 0.01 244.74 97.5 30716 +1981 340 10.4 4.4 8.75 0 292.12 127.05 30647 +1981 341 10.16 4.16 8.51 1.03 287.9 94.76 30582 +1981 342 11.87 5.87 10.22 0.42 319.2 93.09 30521 +1981 343 7.64 1.64 5.99 0.16 246.57 95.03 30465 +1981 344 5.13 -0.87 3.48 0.01 210.58 95.4 30413 +1981 345 3.89 -2.11 2.24 0 194.54 127.47 30366 +1981 346 3.46 -2.54 1.81 0 189.23 127.15 30323 +1981 347 -0.89 -6.89 -2.54 0 142.14 128.54 30284 +1981 348 0.79 -5.21 -0.86 0.08 158.96 95.62 30251 +1981 349 0.64 -5.36 -1.01 0.87 157.39 95.38 30221 +1981 350 3.9 -2.1 2.25 0.4 194.66 93.94 30197 +1981 351 4.79 -1.21 3.14 0.48 206.07 93.41 30177 +1981 352 4.6 -1.4 2.95 0.63 203.59 93.42 30162 +1981 353 4.39 -1.61 2.74 0.6 200.88 93.46 30151 +1981 354 0.47 -5.53 -1.18 0 155.63 126.49 30145 +1981 355 3.14 -2.86 1.49 0.17 185.35 93.93 30144 +1981 356 1.9 -4.1 0.25 0.07 170.99 94.41 30147 +1981 357 -0.37 -6.37 -2.02 0.01 147.17 139 30156 +1981 358 4.79 -1.21 3.14 0.8 206.07 93.39 30169 +1981 359 3.21 -2.79 1.56 1.94 186.2 94.12 30186 +1981 360 0.41 -5.59 -1.24 0.36 155.01 95.38 30208 +1981 361 -3.22 -9.22 -4.87 0.07 121.37 140.55 30235 +1981 362 -3.66 -9.66 -5.31 0.08 117.76 141.2 30267 +1981 363 -4.07 -10.07 -5.72 0 114.47 174.24 30303 +1981 364 -1.37 -7.37 -3.02 0 137.62 173.65 30343 +1981 365 2.55 -3.45 0.9 0 178.39 172.1 30388 +1982 1 -3.35 -9.35 -5 0 120.29 175.36 30438 +1982 2 -1.3 -7.3 -2.95 0 138.27 175.28 30492 +1982 3 -2.16 -8.16 -3.81 0 130.46 176.48 30551 +1982 4 2.03 -3.97 0.38 0 172.45 132.27 30614 +1982 5 -0.11 -6.11 -1.76 0 149.74 133.9 30681 +1982 6 2.01 -3.99 0.36 0 172.22 133.83 30752 +1982 7 2.69 -3.31 1.04 0 180.03 134.28 30828 +1982 8 5.03 -0.97 3.38 0.01 209.25 100.84 30907 +1982 9 3.67 -2.33 2.02 0 191.8 136.5 30991 +1982 10 1.69 -4.31 0.04 0 168.65 138.84 31079 +1982 11 -2.19 -8.19 -3.84 0 130.2 141.53 31171 +1982 12 -1.2 -7.2 -2.85 0.59 139.21 150.65 31266 +1982 13 -1.36 -7.36 -3.01 0 137.72 187.76 31366 +1982 14 -4.1 -10.1 -5.75 0 114.24 190.14 31469 +1982 15 0.95 -5.05 -0.7 0.54 160.64 152.82 31575 +1982 16 -1.14 -7.14 -2.79 0.01 139.77 154.38 31686 +1982 17 4.14 -1.86 2.49 0 197.68 189.7 31800 +1982 18 7.12 1.12 5.47 0 238.71 188.53 31917 +1982 19 8.97 2.97 7.32 0 267.7 147.35 32038 +1982 20 4.15 -1.85 2.5 0 197.81 152.43 32161 +1982 21 4.53 -1.47 2.88 0.03 202.68 115.65 32289 +1982 22 1.32 -4.68 -0.33 0.15 164.61 118.36 32419 +1982 23 4.94 -1.06 3.29 0.09 208.05 118.08 32552 +1982 24 1.75 -4.25 0.1 0.09 169.32 121.09 32688 +1982 25 -3.61 -9.61 -5.26 0 118.16 165.83 32827 +1982 26 -3.44 -9.44 -5.09 0.08 119.55 166.06 32969 +1982 27 -2.52 -8.52 -4.17 0.05 127.31 167.29 33114 +1982 28 -8.6 -14.6 -10.25 0.81 83.17 172.7 33261 +1982 29 -10.49 -16.49 -12.14 0 72.5 218.86 33411 +1982 30 -9.06 -15.06 -10.71 0 80.45 220.6 33564 +1982 31 -6.7 -12.7 -8.35 0 95.25 222.13 33718 +1982 32 -2.11 -8.11 -3.76 0 130.91 222.33 33875 +1982 33 -0.8 -6.8 -2.45 0 143 224.17 34035 +1982 34 -4.55 -10.55 -6.2 0 110.73 227.87 34196 +1982 35 -2.09 -8.09 -3.74 0 131.09 228.81 34360 +1982 36 -1.56 -7.56 -3.21 0 135.87 230.91 34526 +1982 37 -1.89 -7.89 -3.54 0 132.87 233.33 34694 +1982 38 1.45 -4.55 -0.2 0 166.02 233.92 34863 +1982 39 -0.15 -6.15 -1.8 0 149.35 237.28 35035 +1982 40 -1.68 -7.68 -3.33 0 134.77 240.54 35208 +1982 41 -0.52 -6.52 -2.17 0 145.7 242.39 35383 +1982 42 2.78 -3.22 1.13 0 181.08 242.42 35560 +1982 43 2.88 -3.12 1.23 0 182.26 244.54 35738 +1982 44 1.16 -4.84 -0.49 0 162.88 247.95 35918 +1982 45 5.69 -0.31 4.04 0 218.19 246.4 36099 +1982 46 2.36 -3.64 0.71 0 176.2 251.23 36282 +1982 47 6.38 0.38 4.73 0 227.89 213.78 36466 +1982 48 7.96 1.96 6.31 0 251.52 215.04 36652 +1982 49 10.35 4.35 8.7 0 291.24 215.14 36838 +1982 50 3.98 -2.02 2.33 0 195.67 224.09 37026 +1982 51 -1.06 -7.06 -2.71 0 140.52 230.54 37215 +1982 52 1.01 -4.99 -0.64 0 161.28 232.11 37405 +1982 53 1.85 -4.15 0.2 0 170.43 234.52 37596 +1982 54 2.19 -3.81 0.54 0 174.26 237.05 37788 +1982 55 3.8 -2.2 2.15 0 193.42 238.8 37981 +1982 56 3.5 -2.5 1.85 0 189.71 241.76 38175 +1982 57 5.08 -0.92 3.43 0 209.91 243.28 38370 +1982 58 5.71 -0.29 4.06 0 218.47 245.62 38565 +1982 59 6.4 0.4 4.75 0 228.18 247.65 38761 +1982 60 9.34 3.34 7.69 0 273.84 247.21 38958 +1982 61 7.69 1.69 6.04 0 247.34 252.07 39156 +1982 62 9.89 3.89 8.24 0 283.2 252.18 39355 +1982 63 12.61 6.61 10.96 0.03 333.63 188.45 39553 +1982 64 5.75 -0.25 4.1 0.14 219.02 197.14 39753 +1982 65 10.34 4.34 8.69 0 291.06 260.28 39953 +1982 66 7.66 1.66 6.01 0 246.88 266.39 40154 +1982 67 10.46 4.46 8.81 0 293.19 265.68 40355 +1982 68 10.38 4.38 8.73 0 291.77 268.64 40556 +1982 69 13.83 7.83 12.18 0 358.63 265.78 40758 +1982 70 10.29 4.29 8.64 0.24 290.18 205.63 40960 +1982 71 10.52 4.52 8.87 0 294.26 276.73 41163 +1982 72 13.84 7.84 12.19 0 358.84 274.13 41366 +1982 73 10.14 4.14 8.49 0 287.55 282.72 41569 +1982 74 14.21 8.21 12.56 0 366.73 278.73 41772 +1982 75 15.6 9.6 13.95 0 397.74 278.68 41976 +1982 76 10.67 4.67 9.02 0.12 296.95 217.48 42179 +1982 77 9.13 3.13 7.48 0.54 270.34 221.1 42383 +1982 78 7.73 1.73 6.08 1.72 247.95 224.5 42587 +1982 79 6.79 0.79 5.14 0 233.83 303.24 42791 +1982 80 7.96 1.96 6.31 0.39 251.52 228.23 42996 +1982 81 7.43 1.43 5.78 0.04 243.37 230.68 43200 +1982 82 8.06 2.06 6.41 0 253.08 309.41 43404 +1982 83 6.3 0.3 4.65 0 226.75 314.16 43608 +1982 84 7.2 1.2 5.55 0 239.91 315.59 43812 +1982 85 5.77 -0.23 4.12 0.37 219.3 239.91 44016 +1982 86 2.59 -3.41 0.94 0 178.86 325.73 44220 +1982 87 4.11 -1.89 2.46 0 197.3 326.75 44424 +1982 88 8.11 2.11 6.46 0 253.87 324.21 44627 +1982 89 10.56 4.56 8.91 0.01 294.97 242.09 44831 +1982 90 5.68 -0.32 4.03 0.01 218.05 249.05 45034 +1982 91 5.11 -0.89 3.46 0 210.31 335.03 45237 +1982 92 10.88 4.88 9.23 0 300.74 329.1 45439 +1982 93 10.36 4.36 8.71 0.01 291.42 249.13 45642 +1982 94 11.77 5.77 10.12 0.65 317.3 248.92 45843 +1982 95 11.45 5.45 9.8 0 311.26 334.6 46045 +1982 96 13.13 7.13 11.48 0 344.1 333.54 46246 +1982 97 9.08 3.08 7.43 0 269.51 342.72 46446 +1982 98 8.18 2.18 6.53 0.1 254.97 259.55 46647 +1982 99 6.19 0.19 4.54 0.17 225.19 263.15 46846 +1982 100 8.64 2.64 6.99 0.02 262.32 262.03 47045 +1982 101 11.09 5.09 9.44 0 304.58 347.26 47243 +1982 102 13.25 7.25 11.6 0 346.55 345.01 47441 +1982 103 13.63 7.63 11.98 0 354.42 346.05 47638 +1982 104 13.76 7.76 12.11 0 357.15 347.58 47834 +1982 105 12.93 6.93 11.28 0 340.04 351.09 48030 +1982 106 13.93 7.93 12.28 0.42 360.75 262.97 48225 +1982 107 11.91 5.91 10.26 0.64 319.97 267.32 48419 +1982 108 10.09 4.09 8.44 0 286.67 361.51 48612 +1982 109 7.07 1.07 5.42 0 237.97 367.91 48804 +1982 110 12.02 6.02 10.37 0 322.08 360.99 48995 +1982 111 12.62 6.62 10.97 0 333.83 361.35 49185 +1982 112 12.09 6.09 10.44 0 323.43 363.94 49374 +1982 113 8.48 2.48 6.83 0 259.74 371.72 49561 +1982 114 10.04 4.04 8.39 0.03 285.8 277.97 49748 +1982 115 11.57 5.57 9.92 0 313.51 369.24 49933 +1982 116 10.93 4.93 9.28 0.44 301.65 278.77 50117 +1982 117 14.07 8.07 12.42 0 363.73 366.53 50300 +1982 118 12.84 6.84 11.19 0.03 338.22 277.91 50481 +1982 119 13.44 7.44 11.79 0.09 350.47 277.84 50661 +1982 120 10.79 4.79 9.14 0 299.11 377.01 50840 +1982 121 19.85 13.85 18.2 0.01 506.77 266.68 51016 +1982 122 21.71 15.71 20.06 0.07 561.93 262.81 51191 +1982 123 18.31 12.31 16.66 0 464.64 362.48 51365 +1982 124 20.99 14.99 19.34 0.01 540 266.23 51536 +1982 125 16.3 10.3 14.65 0.02 414.18 277.6 51706 +1982 126 18.22 12.22 16.57 0.46 462.28 274.31 51874 +1982 127 18.34 12.34 16.69 1.4 465.43 274.7 52039 +1982 128 21.79 15.79 20.14 0 564.42 355.86 52203 +1982 129 21.25 15.25 19.6 0.14 547.84 268.96 52365 +1982 130 20.57 14.57 18.92 0 527.55 361.74 52524 +1982 131 20.41 14.41 18.76 0.23 522.87 272.29 52681 +1982 132 21.25 15.25 19.6 0.1 547.84 270.71 52836 +1982 133 17.1 11.1 15.45 0.02 433.67 281.07 52989 +1982 134 17.16 11.16 15.51 0.28 435.17 281.47 53138 +1982 135 13.11 7.11 11.46 0.11 343.69 289.61 53286 +1982 136 14.13 8.13 12.48 0 365.02 384.46 53430 +1982 137 16.47 10.47 14.82 0 418.26 379.24 53572 +1982 138 14.24 8.24 12.59 0.33 367.38 289.14 53711 +1982 139 15.34 9.34 13.69 0 391.77 383.51 53848 +1982 140 14.73 8.73 13.08 0.46 378.08 289.14 53981 +1982 141 15.67 9.67 14.02 0 399.35 383.58 54111 +1982 142 15.77 9.77 14.12 0.86 401.68 287.87 54238 +1982 143 17.79 11.79 16.14 0.21 451.11 284.06 54362 +1982 144 20.29 14.29 18.64 0.14 519.38 278.46 54483 +1982 145 22.36 16.36 20.71 0 582.38 364.24 54600 +1982 146 20.13 14.13 18.48 0 514.76 372.65 54714 +1982 147 23.51 17.51 21.86 0 620.09 360.51 54824 +1982 148 20.89 14.89 19.24 0 537.02 370.86 54931 +1982 149 21.38 15.38 19.73 0 551.79 369.41 55034 +1982 150 19.27 13.27 17.62 0 490.54 376.98 55134 +1982 151 19.17 13.17 17.52 0 487.78 377.69 55229 +1982 152 21.37 15.37 19.72 0 551.49 370.26 55321 +1982 153 18.89 12.89 17.24 0 480.14 378.94 55409 +1982 154 17.84 11.84 16.19 0 452.4 382.48 55492 +1982 155 19.85 13.85 18.2 0.04 506.77 282.24 55572 +1982 156 20.21 14.21 18.56 0.69 517.07 281.56 55648 +1982 157 19.32 13.32 17.67 0.04 491.92 283.91 55719 +1982 158 18.84 12.84 17.19 0.52 478.79 285.2 55786 +1982 159 20.43 14.43 18.78 0.09 523.45 281.43 55849 +1982 160 21.5 15.5 19.85 0.06 555.46 278.7 55908 +1982 161 23.61 17.61 21.96 0.19 623.47 272.56 55962 +1982 162 25.37 19.37 23.72 0.17 685.47 266.85 56011 +1982 163 26.12 20.12 24.47 0.17 713.44 264.39 56056 +1982 164 26.54 20.54 24.89 0.11 729.52 262.9 56097 +1982 165 25.61 19.61 23.96 0.08 694.32 266.28 56133 +1982 166 27.28 21.28 25.63 0.53 758.59 260.27 56165 +1982 167 24.75 18.75 23.1 0 663.06 358.95 56192 +1982 168 25.47 19.47 23.82 0.17 689.15 266.84 56214 +1982 169 26.72 20.72 25.07 0 736.5 349.85 56231 +1982 170 26.36 20.36 24.71 0 722.59 351.61 56244 +1982 171 25.89 19.89 24.24 0.1 704.76 265.43 56252 +1982 172 24.28 18.28 22.63 0 646.49 361.14 56256 +1982 173 29.15 23.15 27.5 0.89 836.46 252.85 56255 +1982 174 26.23 20.23 24.58 0.83 717.62 264.14 56249 +1982 175 19.78 13.78 18.13 0 504.78 378.15 56238 +1982 176 17.84 11.84 16.19 0.36 452.4 288.19 56223 +1982 177 15.51 9.51 13.86 0.39 395.66 293 56203 +1982 178 16.48 10.48 14.83 1.45 418.5 291.06 56179 +1982 179 19.23 13.23 17.58 1.58 489.43 284.81 56150 +1982 180 21.32 15.32 19.67 0.36 549.96 279.32 56116 +1982 181 20.2 14.2 18.55 0.06 516.78 282.24 56078 +1982 182 21.47 15.47 19.82 0 554.54 371.67 56035 +1982 183 23.81 17.81 22.16 0.01 630.27 271.73 55987 +1982 184 22.28 16.28 20.63 0.04 579.83 276.22 55935 +1982 185 25.05 19.05 23.4 0.17 673.83 267.53 55879 +1982 186 24.2 18.2 22.55 0 643.7 360.17 55818 +1982 187 24.8 18.8 23.15 0.25 664.85 268.04 55753 +1982 188 22.45 16.45 20.8 0 585.26 366.86 55684 +1982 189 26.74 20.74 25.09 0.12 737.28 260.95 55611 +1982 190 25.06 19.06 23.41 0.22 674.19 266.58 55533 +1982 191 23.1 17.1 21.45 0 606.42 363.49 55451 +1982 192 21.39 15.39 19.74 0.42 552.1 277.3 55366 +1982 193 19.94 13.94 18.29 0.24 509.33 280.9 55276 +1982 194 22.22 16.22 20.57 0 577.92 366.15 55182 +1982 195 23.52 17.52 21.87 0.01 620.43 270.55 55085 +1982 196 23.84 17.84 22.19 0 631.29 359.02 54984 +1982 197 26.05 20.05 24.4 0.81 710.79 261.59 54879 +1982 198 22.45 16.45 20.8 2.14 585.26 272.79 54770 +1982 199 23.92 17.92 22.27 0.34 634.03 268.11 54658 +1982 200 23.95 17.95 22.3 0.19 635.06 267.73 54542 +1982 201 24.23 18.23 22.58 0 644.75 355.33 54423 +1982 202 22.58 16.58 20.93 0.25 589.44 271.1 54301 +1982 203 24.54 18.54 22.89 0.27 655.61 264.73 54176 +1982 204 24.09 18.09 22.44 0 639.89 354.39 54047 +1982 205 22.76 16.76 21.11 0 595.27 359.26 53915 +1982 206 29.37 23.37 27.72 0 846.05 327.76 53780 +1982 207 29.88 23.88 28.23 1.08 868.63 243.21 53643 +1982 208 26.94 20.94 25.29 0.95 745.11 254.4 53502 +1982 209 22.1 16.1 20.45 1.42 574.13 269.47 53359 +1982 210 17.36 11.36 15.71 0.19 440.17 280.62 53213 +1982 211 21.94 15.94 20.29 0.57 569.1 268.88 53064 +1982 212 22.85 16.85 21.2 0.01 598.2 265.71 52913 +1982 213 22.95 16.95 21.3 1.13 601.48 264.86 52760 +1982 214 22.12 16.12 20.47 0.08 574.76 266.67 52604 +1982 215 25.52 19.52 23.87 0.31 690.99 255.79 52445 +1982 216 23.51 17.51 21.86 0.23 620.09 261.42 52285 +1982 217 25.16 19.16 23.51 0.91 677.81 255.6 52122 +1982 218 23.93 17.93 22.28 0.46 634.38 258.9 51958 +1982 219 22.54 16.54 20.89 0.08 588.15 262.22 51791 +1982 220 22.85 16.85 21.2 0.4 598.2 260.65 51622 +1982 221 21.45 15.45 19.8 0 553.93 351.68 51451 +1982 222 19.13 13.13 17.48 0.41 486.69 268.71 51279 +1982 223 20.12 14.12 18.47 0 514.48 354.01 51105 +1982 224 20.52 14.52 18.87 0 526.08 351.64 50929 +1982 225 21.99 15.99 20.34 0 570.66 345.42 50751 +1982 226 18.56 12.56 16.91 0.05 471.27 266.61 50572 +1982 227 16.87 10.87 15.22 0 427.99 358.94 50392 +1982 228 22.71 16.71 21.06 0 593.64 339.22 50210 +1982 229 23.94 17.94 22.29 0 634.72 333.29 50026 +1982 230 21.22 15.22 19.57 0.37 546.93 256.54 49842 +1982 231 20.89 14.89 19.24 0.41 537.02 256.28 49656 +1982 232 19.06 13.06 17.41 0.24 484.77 259.6 49469 +1982 233 20.49 14.49 18.84 0 525.2 340.27 49280 +1982 234 22.51 16.51 20.86 0.07 587.18 248.97 49091 +1982 235 25.41 19.41 23.76 0.54 686.94 239.4 48900 +1982 236 25.33 19.33 23.68 0.01 684.01 238.63 48709 +1982 237 21.16 15.16 19.51 0.12 545.11 249.12 48516 +1982 238 23.37 17.37 21.72 0.06 615.39 242.06 48323 +1982 239 24.39 18.39 22.74 0.16 650.34 238.04 48128 +1982 240 27.64 21.64 25.99 0.49 773.09 226.32 47933 +1982 241 25.04 19.04 23.39 0.13 673.47 233.6 47737 +1982 242 26.89 20.89 25.24 0 743.15 301.97 47541 +1982 243 25.62 19.62 23.97 0.13 694.69 229.26 47343 +1982 244 22.66 16.66 21.01 0.52 592.02 236.42 47145 +1982 245 22.8 16.8 21.15 0.2 596.57 234.71 46947 +1982 246 20.1 14.1 18.45 0 513.9 319.82 46747 +1982 247 20.16 14.16 18.51 0 515.63 317.81 46547 +1982 248 21.56 15.56 19.91 0 557.3 311.54 46347 +1982 249 24.67 18.67 23.02 0 660.22 298.58 46146 +1982 250 24.79 18.79 23.14 0.29 664.49 222.21 45945 +1982 251 23.23 17.23 21.58 0.12 610.73 224.99 45743 +1982 252 25.7 19.7 24.05 0.07 697.66 216.52 45541 +1982 253 23.91 17.91 22.26 0 633.69 293.47 45339 +1982 254 24.15 18.15 22.5 0.07 641.97 217.93 45136 +1982 255 23.01 17.01 21.36 0.05 603.45 219.32 44933 +1982 256 22.31 16.31 20.66 0 580.78 292.56 44730 +1982 257 21.82 15.82 20.17 0 565.35 292.04 44527 +1982 258 19.18 13.18 17.53 0 488.06 297.42 44323 +1982 259 19.68 13.68 18.03 0.19 501.96 220.25 44119 +1982 260 22.58 16.58 20.93 0 589.44 282.73 43915 +1982 261 21.46 15.46 19.81 0.03 554.23 212.89 43711 +1982 262 18.95 12.95 17.3 0 481.77 288.54 43507 +1982 263 19.47 13.47 17.82 0 496.08 284.76 43303 +1982 264 20.3 14.3 18.65 0 519.67 280 43099 +1982 265 20.55 14.55 18.9 0 526.96 277.01 42894 +1982 266 21.36 15.36 19.71 0 551.18 272.32 42690 +1982 267 18.94 12.94 17.29 0.75 481.5 207.17 42486 +1982 268 21.17 15.17 19.52 0.31 545.42 200.85 42282 +1982 269 20.49 14.49 18.84 1.28 525.2 200.44 42078 +1982 270 20.2 14.2 18.55 0 516.78 265.47 41875 +1982 271 21.42 15.42 19.77 0 553.01 259.63 41671 +1982 272 20.19 14.19 18.54 0 516.49 260.32 41468 +1982 273 22.78 16.78 21.13 0 595.92 250.69 41265 +1982 274 13.81 7.81 12.16 0 358.21 268.93 41062 +1982 275 10.64 4.64 8.99 0 296.41 271.2 40860 +1982 276 13.78 7.78 12.13 0.01 357.57 197.63 40658 +1982 277 15.27 9.27 13.62 0 390.18 258.17 40456 +1982 278 19.6 13.6 17.95 0 499.72 246.13 40255 +1982 279 15.8 9.8 14.15 0.12 402.38 188.65 40054 +1982 280 19.41 13.41 17.76 0.08 494.41 180.98 39854 +1982 281 18.4 12.4 16.75 0.6 467.02 180.71 39654 +1982 282 18.06 12.06 16.41 0.02 458.09 179.26 39455 +1982 283 16.24 10.24 14.59 0.22 412.74 179.93 39256 +1982 284 18.18 12.18 16.53 0 461.23 233.08 39058 +1982 285 17.17 11.17 15.52 0 435.41 232.56 38861 +1982 286 11.96 5.96 10.31 0 320.93 238.62 38664 +1982 287 8.72 2.72 7.07 0 263.61 239.84 38468 +1982 288 13.15 7.15 11.5 0 344.5 231.15 38273 +1982 289 16.55 10.55 14.9 0.02 420.19 167.16 38079 +1982 290 13.77 7.77 12.12 0 357.36 224.74 37885 +1982 291 12.87 6.87 11.22 0.24 338.83 167.55 37693 +1982 292 13.41 7.41 11.76 0.14 349.85 164.95 37501 +1982 293 12.28 6.28 10.63 1.46 327.13 164.12 37311 +1982 294 10.75 4.75 9.1 0.52 298.39 163.45 37121 +1982 295 11.57 5.57 9.92 2.8 313.51 160.54 36933 +1982 296 13.25 7.25 11.6 0 346.55 209.21 36745 +1982 297 13.4 7.4 11.75 0 349.64 206.3 36560 +1982 298 13.66 7.66 12.01 0.14 355.05 152.52 36375 +1982 299 13.21 7.21 11.56 0 345.73 201.23 36191 +1982 300 13.5 7.5 11.85 0 351.71 198.2 36009 +1982 301 12.81 6.81 11.16 0.11 337.62 147.48 35829 +1982 302 13.74 7.74 12.09 0.94 356.73 144.61 35650 +1982 303 15.24 9.24 13.59 0 389.5 188.12 35472 +1982 304 14.99 8.99 13.34 0.26 383.87 139.57 35296 +1982 305 11.5 5.5 9.85 0 312.19 187.97 35122 +1982 306 4.93 -1.07 3.28 0.76 207.92 144 34950 +1982 307 2.33 -3.67 0.68 0 175.86 191.27 34779 +1982 308 3.86 -2.14 2.21 0.67 194.16 140.69 34610 +1982 309 3.29 -2.71 1.64 0 187.16 185.63 34444 +1982 310 1.92 -4.08 0.27 0 171.21 184.01 34279 +1982 311 1.93 -4.07 0.28 0 171.33 181.78 34116 +1982 312 1.24 -4.76 -0.41 0 163.74 179.5 33956 +1982 313 1.65 -4.35 0 0 168.21 177.1 33797 +1982 314 8.45 2.45 6.8 0.2 259.26 127.64 33641 +1982 315 9.81 3.81 8.16 0.07 281.82 124.8 33488 +1982 316 14.99 8.99 13.34 0 383.87 158.4 33337 +1982 317 11.14 5.14 9.49 0 305.5 160.74 33188 +1982 318 12.49 6.49 10.84 0 331.25 156.99 33042 +1982 319 14.2 8.2 12.55 0.05 366.52 115.01 32899 +1982 320 10.91 4.91 9.26 0 301.29 155.15 32758 +1982 321 11.65 5.65 10 0 315.02 152.33 32620 +1982 322 11.9 5.9 10.25 0 319.78 150.28 32486 +1982 323 10.9 4.9 9.25 0.01 301.11 112.27 32354 +1982 324 8.32 2.32 6.67 0.18 257.19 112.47 32225 +1982 325 10.52 4.52 8.87 0.26 294.26 109.75 32100 +1982 326 8.82 2.82 7.17 0.01 265.24 109.8 31977 +1982 327 4.84 -1.16 3.19 0 206.73 147.46 31858 +1982 328 8.21 2.21 6.56 0 255.44 143.09 31743 +1982 329 9.27 3.27 7.62 0 272.67 140.76 31631 +1982 330 8.66 2.66 7.01 0 262.64 139.82 31522 +1982 331 12.07 6.07 10.42 0 323.05 135.51 31417 +1982 332 14.31 8.31 12.66 0 368.89 131.57 31316 +1982 333 13.61 7.61 11.96 0.26 354.01 98.47 31218 +1982 334 14.23 8.23 12.58 0 367.17 129.56 31125 +1982 335 11.71 5.71 10.06 0 316.16 130.98 31035 +1982 336 13.95 7.95 12.3 0 361.17 127.7 30949 +1982 337 14.39 8.39 12.74 0 370.63 125.61 30867 +1982 338 11.95 5.95 10.3 1.29 320.74 95.37 30790 +1982 339 8.66 2.66 7.01 0.14 262.64 96.87 30716 +1982 340 10.31 4.31 8.66 0.49 290.53 95.35 30647 +1982 341 10.27 4.27 8.62 0.47 289.83 94.7 30582 +1982 342 7.33 1.33 5.68 0.2 241.86 95.8 30521 +1982 343 7.44 1.44 5.79 0.06 243.52 95.13 30465 +1982 344 7.42 1.42 5.77 0 243.22 125.73 30413 +1982 345 5.28 -0.72 3.63 0.31 212.6 95.01 30366 +1982 346 4.43 -1.57 2.78 0 201.39 126.62 30323 +1982 347 6.46 0.46 4.81 0.25 229.04 93.61 30284 +1982 348 8.9 2.9 7.25 0 266.55 122.77 30251 +1982 349 4.49 -1.51 2.84 0 202.16 125.26 30221 +1982 350 0.63 -5.37 -1.02 0.1 157.28 95.13 30197 +1982 351 -2.36 -8.36 -4.01 0.35 128.7 140.7 30177 +1982 352 1.7 -4.3 0.05 0.02 168.77 139.18 30162 +1982 353 0.06 -5.94 -1.59 0.86 151.45 139.68 30151 +1982 354 2.61 -3.39 0.96 0 179.09 169.83 30145 +1982 355 -0.08 -6.08 -1.73 0.2 150.04 140 30144 +1982 356 2.35 -3.65 0.7 0.27 176.09 138.88 30147 +1982 357 2.51 -3.49 0.86 0.31 177.93 138.52 30156 +1982 358 6.82 0.82 5.17 0 234.27 123.28 30169 +1982 359 2.17 -3.83 0.52 0.23 174.03 94.51 30186 +1982 360 7.11 1.11 5.46 0 238.56 123.57 30208 +1982 361 5.45 -0.55 3.8 0 214.9 124.95 30235 +1982 362 6.41 0.41 4.76 0 228.32 124.79 30267 +1982 363 5.11 -0.89 3.46 0.27 210.31 94.63 30303 +1982 364 6.81 0.81 5.16 0.21 234.13 94.13 30343 +1982 365 6.16 0.16 4.51 0.25 224.76 94.87 30388 +1983 1 6.82 0.82 5.17 0.38 234.27 95.21 30438 +1983 2 8.78 2.78 7.13 0.02 264.59 94.71 30492 +1983 3 13.08 7.08 11.43 0.04 343.08 92.62 30551 +1983 4 11.6 5.6 9.95 0.21 314.07 94.33 30614 +1983 5 10.69 4.69 9.04 0 297.3 127.2 30681 +1983 6 10.1 4.1 8.45 0.08 286.85 96.42 30752 +1983 7 6.91 0.91 5.26 0 235.6 131.75 30828 +1983 8 8.85 2.85 7.2 0 265.73 131.81 30907 +1983 9 5.06 -0.94 3.41 0.42 209.65 101.76 30991 +1983 10 3.68 -2.32 2.03 0 191.93 137.79 31079 +1983 11 4.37 -1.63 2.72 0.12 200.62 103.78 31171 +1983 12 1.18 -4.82 -0.47 0 163.1 141.1 31266 +1983 13 3.91 -2.09 2.26 0 194.79 141.28 31366 +1983 14 1.48 -4.52 -0.17 0 166.35 144.07 31469 +1983 15 2.61 -3.39 0.96 0 179.09 144.93 31575 +1983 16 8.18 2.18 6.53 0 254.97 142.56 31686 +1983 17 3.53 -2.47 1.88 0.57 190.08 110.54 31800 +1983 18 1.95 -4.05 0.3 0.02 171.55 112.63 31917 +1983 19 2.2 -3.8 0.55 0 174.37 151.98 32038 +1983 20 1.44 -4.56 -0.21 0.02 165.91 115.48 32161 +1983 21 4.32 -1.68 2.67 0 199.98 154.33 32289 +1983 22 6.67 0.67 5.02 0 232.08 154.45 32419 +1983 23 9.47 3.47 7.82 0 276.03 153.91 32552 +1983 24 10.97 4.97 9.32 0 302.38 154.52 32688 +1983 25 9.81 3.81 8.16 0 281.82 157.48 32827 +1983 26 8.08 2.08 6.43 1.5 253.4 120.68 32969 +1983 27 6.74 0.74 5.09 0.16 233.1 122.99 33114 +1983 28 8.28 2.28 6.63 0.19 256.55 123.68 33261 +1983 29 6.7 0.7 5.05 0 232.52 168.58 33411 +1983 30 8.54 2.54 6.89 0 260.7 169.24 33564 +1983 31 7.11 1.11 5.46 0 238.56 172.82 33718 +1983 32 6.65 0.65 5 0 231.79 175.3 33875 +1983 33 2.88 -3.12 1.23 0.39 182.26 135.48 34035 +1983 34 -1.72 -7.72 -3.37 0.57 134.41 179.26 34196 +1983 35 -4.16 -10.16 -5.81 0.2 113.76 182.07 34360 +1983 36 -5.85 -11.85 -7.5 1.19 101.13 187.58 34526 +1983 37 -5.11 -11.11 -6.76 0.51 106.5 190.43 34694 +1983 38 -2.11 -8.11 -3.76 0.04 130.91 191.44 34863 +1983 39 -2.36 -8.36 -4.01 0 128.7 242.88 35035 +1983 40 -2.29 -8.29 -3.94 0.32 129.32 195.92 35208 +1983 41 2.86 -3.14 1.21 0 182.02 245.27 35383 +1983 42 1.83 -4.17 0.18 0.11 170.21 197.13 35560 +1983 43 2.33 -3.67 0.68 0 175.86 250.01 35738 +1983 44 2.56 -3.44 0.91 1.5 178.51 199.76 35918 +1983 45 6.87 0.87 5.22 0 235.01 250.1 36099 +1983 46 4.64 -1.36 2.99 0 204.11 253.98 36282 +1983 47 5.41 -0.59 3.76 0 214.36 255.36 36466 +1983 48 2.7 -3.3 1.05 0 180.14 259.81 36652 +1983 49 5.42 -0.58 3.77 0 214.49 259.63 36838 +1983 50 3.31 -2.69 1.66 0 187.4 263.47 37026 +1983 51 2.41 -3.59 0.76 0 176.78 266.67 37215 +1983 52 2.57 -3.43 0.92 0 178.63 268.94 37405 +1983 53 3.99 -2.01 2.34 0.29 195.79 211.96 37596 +1983 54 4.65 -1.35 3 0.03 204.24 212.93 37788 +1983 55 2.26 -3.74 0.61 0.17 175.06 216.21 37981 +1983 56 5 -1 3.35 0 208.85 275.95 38175 +1983 57 7.91 1.91 6.26 0 250.74 274.9 38370 +1983 58 2.83 -3.17 1.18 0.09 181.67 186.12 38565 +1983 59 2.61 -3.39 0.96 0.01 179.09 188.3 38761 +1983 60 8.66 2.66 7.01 0.03 262.64 186.03 38958 +1983 61 9.61 3.61 7.96 0.41 278.4 187.33 39156 +1983 62 7.1 1.1 5.45 0.02 238.41 191.63 39355 +1983 63 5.4 -0.6 3.75 0.03 214.22 195.21 39553 +1983 64 7.24 1.24 5.59 0 240.5 261.26 39753 +1983 65 7.62 1.62 5.97 0 246.26 263.71 39953 +1983 66 6.47 0.47 4.82 0 229.19 267.73 40154 +1983 67 4.59 -1.41 2.94 0.03 203.46 204.43 40355 +1983 68 3.72 -2.28 2.07 0 192.42 276.29 40556 +1983 69 5.47 -0.53 3.82 0 215.17 277.22 40758 +1983 70 9.89 3.89 8.24 0 283.2 274.73 40960 +1983 71 15.43 9.43 13.78 0 393.83 268.41 41163 +1983 72 14.12 8.12 12.47 0 364.8 273.63 41366 +1983 73 15.56 9.56 13.91 0.01 396.81 205.1 41569 +1983 74 13.36 7.36 11.71 0 348.81 280.27 41772 +1983 75 12.91 6.91 11.26 0 339.63 283.73 41976 +1983 76 14.04 8.04 12.39 0 363.09 284.28 42179 +1983 77 15.58 9.58 13.93 0 397.27 283.79 42383 +1983 78 15.39 9.39 13.74 0.29 392.91 215.07 42587 +1983 79 12.15 6.15 10.5 0.01 324.6 221.62 42791 +1983 80 9.23 3.23 7.58 0 272 302.56 42996 +1983 81 9.35 3.35 7.7 0 274.01 304.96 43200 +1983 82 9.89 3.89 8.24 0.15 283.2 230.11 43404 +1983 83 6.29 0.29 4.64 0.56 226.61 235.63 43608 +1983 84 8.77 2.77 7.12 0.16 264.42 235.1 43812 +1983 85 9.61 3.61 7.96 0.18 278.4 236.05 44016 +1983 86 8.05 2.05 6.4 0.25 252.93 239.54 44220 +1983 87 9.14 3.14 7.49 0.19 270.51 240.28 44424 +1983 88 9.11 3.11 7.46 0.48 270.01 242.08 44627 +1983 89 10 4 8.35 0.03 285.11 242.76 44831 +1983 90 13.84 7.84 12.19 0.08 358.84 239.38 45034 +1983 91 21.7 15.7 20.05 0.23 561.62 225.91 45237 +1983 92 21.1 15.1 19.45 0 543.31 305.21 45439 +1983 93 16.92 10.92 15.27 0 429.22 318.88 45642 +1983 94 17.05 11.05 15.4 0 432.43 320.65 45843 +1983 95 17.21 11.21 15.56 0.96 436.41 241.74 46045 +1983 96 16.74 10.74 15.09 0.97 424.8 244.16 46246 +1983 97 16.04 10.04 14.39 0.79 408 246.93 46446 +1983 98 14.24 8.24 12.59 0.58 367.38 251.41 46647 +1983 99 17.19 11.19 15.54 0 435.91 330.27 46846 +1983 100 14.26 8.26 12.61 0.07 367.81 254.31 47045 +1983 101 8.6 2.6 6.95 0 261.67 351.39 47243 +1983 102 8.75 2.75 7.1 0 264.1 353.08 47441 +1983 103 3.13 -2.87 1.48 0 185.23 362.32 47638 +1983 104 5.26 -0.74 3.61 0 212.33 361.7 47834 +1983 105 9.37 3.37 7.72 0.06 274.35 268.21 48030 +1983 106 13.8 7.8 12.15 0.01 357.99 263.18 48225 +1983 107 12.9 6.9 11.25 0 339.43 354.46 48419 +1983 108 11.67 5.67 10.02 0 315.4 358.64 48612 +1983 109 13.79 7.79 12.14 0 357.78 355.93 48804 +1983 110 14.26 8.26 12.61 0 367.81 356.29 48995 +1983 111 15.38 9.38 13.73 0.03 392.69 266.41 49185 +1983 112 15.29 9.29 13.64 0 390.64 356.94 49374 +1983 113 19.64 13.64 17.99 0 500.84 346.32 49561 +1983 114 22.02 16.02 20.37 0 571.61 339.83 49748 +1983 115 22.95 16.95 21.3 0.04 601.48 253.33 49933 +1983 116 22.64 16.64 20.99 0 591.38 340.08 50117 +1983 117 18.42 12.42 16.77 0.01 467.55 266.47 50300 +1983 118 16.03 10.03 14.38 0 407.77 363.12 50481 +1983 119 18.14 12.14 16.49 0 460.18 358.55 50661 +1983 120 17.2 11.2 15.55 0 436.16 362.35 50840 +1983 121 23.32 17.32 21.67 0 613.72 343.27 51016 +1983 122 23.3 17.3 21.65 0 613.06 344.47 51191 +1983 123 22.98 16.98 21.33 0 602.46 346.69 51365 +1983 124 26.19 20.19 24.54 0.18 716.1 250.63 51536 +1983 125 25.64 19.64 23.99 0.68 695.43 253.18 51706 +1983 126 23.51 17.51 21.86 0.49 620.09 260.63 51874 +1983 127 21.1 15.1 19.45 0.43 543.31 268.02 52039 +1983 128 18.93 12.93 17.28 0.94 481.23 274.09 52203 +1983 129 17.59 11.59 15.94 0.18 446 277.71 52365 +1983 130 19.64 13.64 17.99 0 500.84 364.82 52524 +1983 131 15.77 9.77 14.12 0 401.68 376.82 52681 +1983 132 16.29 10.29 14.64 0.01 413.94 282.2 52836 +1983 133 20.61 14.61 18.96 0.26 528.72 272.89 52989 +1983 134 21.25 15.25 19.6 0.04 547.84 271.73 53138 +1983 135 17.03 11.03 15.38 0.72 431.94 282.27 53286 +1983 136 18.14 12.14 16.49 1.77 460.18 280.33 53430 +1983 137 14.17 8.17 12.52 0 365.87 385.07 53572 +1983 138 12.36 6.36 10.71 0.22 328.69 292.32 53711 +1983 139 14.34 8.34 12.69 0.07 369.54 289.48 53848 +1983 140 15.02 9.02 13.37 0.01 384.54 288.6 53981 +1983 141 13.22 7.22 11.57 0.53 345.94 292.14 54111 +1983 142 14.74 8.74 13.09 0 378.3 386.44 54238 +1983 143 16.81 10.81 15.16 0 426.52 381.55 54362 +1983 144 14.8 8.8 13.15 0 379.63 387.32 54483 +1983 145 17.47 11.47 15.82 0.14 442.95 285.47 54600 +1983 146 18.87 12.87 17.22 0 479.6 376.76 54714 +1983 147 19.81 13.81 18.16 1.3 505.63 280.65 54824 +1983 148 20.29 14.29 18.64 0 519.38 372.95 54931 +1983 149 23.15 17.15 21.5 0.1 608.07 271.98 55034 +1983 150 25.31 19.31 23.66 0 683.28 353.73 55134 +1983 151 25.71 19.71 24.06 0 698.04 352.28 55229 +1983 152 26.18 20.18 24.53 0.19 715.72 262.62 55321 +1983 153 25.94 19.94 24.29 0.84 706.64 263.64 55409 +1983 154 19.82 13.82 18.17 0.15 505.92 282.17 55492 +1983 155 22.65 16.65 21 1.46 591.7 274.62 55572 +1983 156 18.15 12.15 16.5 0.38 460.44 286.55 55648 +1983 157 19.11 13.11 17.46 0.01 486.14 284.42 55719 +1983 158 17.63 11.63 15.98 0 447.01 383.97 55786 +1983 159 17.03 11.03 15.38 0 431.94 385.95 55849 +1983 160 22.41 16.41 20.76 0.11 583.98 276.12 55908 +1983 161 21.35 15.35 19.7 0.51 550.88 279.16 55962 +1983 162 14.84 8.84 13.19 0.35 380.52 294.09 56011 +1983 163 15.94 9.94 14.29 0 405.65 389.49 56056 +1983 164 19.2 13.2 17.55 0 488.61 379.93 56097 +1983 165 20.35 14.35 18.7 0 521.12 376.18 56133 +1983 166 21.66 15.66 20.01 0.54 560.39 278.67 56165 +1983 167 20.48 14.48 18.83 0.33 524.91 281.81 56192 +1983 168 22.47 16.47 20.82 0 585.9 368.5 56214 +1983 169 24.23 18.23 22.58 0.17 644.75 270.98 56231 +1983 170 20.12 14.12 18.47 1.02 514.48 282.81 56244 +1983 171 21.75 15.75 20.1 0.22 563.17 278.49 56252 +1983 172 22.47 16.47 20.82 0 585.9 368.56 56256 +1983 173 23.7 17.7 22.05 0 626.52 363.58 56255 +1983 174 23.38 17.38 21.73 0 615.73 364.82 56249 +1983 175 27.3 21.3 25.65 0.39 759.39 260.16 56238 +1983 176 23.62 17.62 21.97 0 623.81 363.77 56223 +1983 177 22.89 16.89 21.24 0 599.51 366.64 56203 +1983 178 22.07 16.07 20.42 0.14 573.18 277.39 56179 +1983 179 18.85 12.85 17.2 0.49 479.06 285.72 56150 +1983 180 19.23 13.23 17.58 0.94 489.43 284.71 56116 +1983 181 14.28 8.28 12.63 0.18 368.25 295.11 56078 +1983 182 18.55 12.55 16.9 0.33 471 286.17 56035 +1983 183 20.14 14.14 18.49 0 515.05 376.2 55987 +1983 184 20.02 14.02 18.37 0 511.61 376.45 55935 +1983 185 22.33 16.33 20.68 0.17 581.42 276.01 55879 +1983 186 26.22 20.22 24.57 0 717.24 351.04 55818 +1983 187 25.68 19.68 24.03 0 696.92 353.41 55753 +1983 188 23.96 17.96 22.31 0.01 635.41 270.56 55684 +1983 189 24.69 18.69 23.04 0.38 660.93 268.08 55611 +1983 190 27.04 21.04 25.39 0.34 749.06 259.57 55533 +1983 191 27.88 21.88 26.23 0 782.88 341.56 55451 +1983 192 26.74 20.74 25.09 0 737.28 347.03 55366 +1983 193 27.2 21.2 25.55 0 755.4 344.5 55276 +1983 194 26.71 20.71 25.06 0.8 736.11 260.04 55182 +1983 195 25.23 19.23 23.58 0.15 680.36 265.05 55085 +1983 196 23.51 17.51 21.86 0.02 620.09 270.29 54984 +1983 197 25.52 19.52 23.87 0 690.99 351.25 54879 +1983 198 28.14 22.14 26.49 0 793.6 338 54770 +1983 199 27.46 21.46 25.81 0.07 765.81 255.88 54658 +1983 200 27.81 21.81 26.16 0.14 780.01 254.26 54542 +1983 201 28.19 22.19 26.54 0.29 795.68 252.45 54423 +1983 202 24.13 18.13 22.48 0.02 641.27 266.41 54301 +1983 203 28.03 22.03 26.38 0 789.05 336.44 54176 +1983 204 26.41 20.41 24.76 0.04 724.51 258.01 54047 +1983 205 28.18 22.18 26.53 0 795.27 334.7 53915 +1983 206 27.18 21.18 25.53 0 754.61 339.26 53780 +1983 207 27.25 21.25 25.6 0 757.39 338.29 53643 +1983 208 24.5 18.5 22.85 0.53 654.2 262.75 53502 +1983 209 25.64 19.64 23.99 0.06 695.43 258.52 53359 +1983 210 24.18 18.18 22.53 0 643.01 350.46 53213 +1983 211 24.73 18.73 23.08 0 662.35 347.37 53064 +1983 212 23.21 17.21 21.56 0.2 610.06 264.65 52913 +1983 213 20.64 14.64 18.99 0 529.61 361.58 52760 +1983 214 23.72 17.72 22.07 0 627.2 349.36 52604 +1983 215 22.28 16.28 20.63 0 579.83 354.3 52445 +1983 216 20.94 14.94 19.29 0 538.51 358.11 52285 +1983 217 21.75 15.75 20.1 0 563.17 354.37 52122 +1983 218 21.98 15.98 20.33 0 570.35 352.73 51958 +1983 219 21.39 15.39 19.74 0.03 552.1 265.36 51791 +1983 220 20.84 14.84 19.19 0.11 535.53 266.09 51622 +1983 221 21.76 15.76 20.11 0.14 563.48 262.93 51451 +1983 222 20.47 14.47 18.82 0.39 524.62 265.5 51279 +1983 223 21.7 15.7 20.05 0 561.62 348.63 51105 +1983 224 25.3 19.3 23.65 0.5 682.91 250.08 50929 +1983 225 23.48 17.48 21.83 0 619.08 339.83 50751 +1983 226 23.01 17.01 21.36 0.27 603.45 255.4 50572 +1983 227 21.51 15.51 19.86 1.25 555.77 258.55 50392 +1983 228 22.97 16.97 21.32 2.04 602.13 253.68 50210 +1983 229 23.74 17.74 22.09 0.14 627.88 250.56 50026 +1983 230 27.3 21.3 25.65 0 759.39 317.47 49842 +1983 231 24.34 18.34 22.69 0 648.58 329.04 49656 +1983 232 25.99 19.99 24.34 0 708.52 320.8 49469 +1983 233 27.14 21.14 25.49 0 753.02 314.25 49280 +1983 234 26.37 20.37 24.72 0.03 722.97 237.33 49091 +1983 235 28.11 22.11 26.46 0 792.36 306.92 48900 +1983 236 29.06 23.06 27.41 0.07 832.56 225.66 48709 +1983 237 26.79 20.79 25.14 0 739.23 310.27 48516 +1983 238 26.11 20.11 24.46 0 713.06 311.71 48323 +1983 239 19.19 13.19 17.54 0 488.33 335.15 48128 +1983 240 20.35 14.35 18.7 0 521.12 329.88 47933 +1983 241 21.78 15.78 20.13 0.27 564.11 242.65 47737 +1983 242 20.22 14.22 18.57 0.32 517.36 245.15 47541 +1983 243 21.17 15.17 19.52 0.32 545.42 241.52 47343 +1983 244 19.68 13.68 18.03 0.14 501.96 243.63 47145 +1983 245 21.03 15.03 19.38 0 541.2 318.87 46947 +1983 246 25.25 19.25 23.6 0 681.09 301.86 46747 +1983 247 24.23 18.23 22.58 0.31 644.75 228.05 46547 +1983 248 22.69 16.69 21.04 0.11 593 230.82 46347 +1983 249 23 17 21.35 0.17 603.12 228.52 46146 +1983 250 19.93 13.93 18.28 0 509.04 312.62 45945 +1983 251 24.55 18.55 22.9 0.18 655.97 221.39 45743 +1983 252 22.61 16.61 20.96 1.3 590.41 225.02 45541 +1983 253 18.68 12.68 17.03 0.97 474.48 232.35 45339 +1983 254 16.63 10.63 14.98 0.12 422.13 234.63 45136 +1983 255 18.34 12.34 16.69 0.13 465.43 229.75 44933 +1983 256 22.4 16.4 20.75 0 583.66 292.27 44730 +1983 257 20.31 14.31 18.66 0 519.96 296.58 44527 +1983 258 18.6 12.6 16.95 0.21 472.34 224.21 44323 +1983 259 17.64 11.64 15.99 0 447.27 298.96 44119 +1983 260 19.61 13.61 17.96 0 500 291.52 43915 +1983 261 18.29 12.29 16.64 0 464.12 292.56 43711 +1983 262 17.82 11.82 16.17 0.02 451.88 218.52 43507 +1983 263 21.85 15.85 20.2 0 566.28 278.01 43303 +1983 264 18.79 12.79 17.14 0 477.44 283.99 43099 +1983 265 14.7 8.7 13.05 0.17 377.42 218.11 42894 +1983 266 16.27 10.27 14.62 0 413.46 285.09 42690 +1983 267 16.41 10.41 14.76 0 416.81 282.12 42486 +1983 268 17.98 11.98 16.33 0 456.02 276.04 42282 +1983 269 19.6 13.6 17.95 0.13 499.72 202.2 42078 +1983 270 15.09 9.09 13.44 1.78 386.11 207.85 41875 +1983 271 13.76 7.76 12.11 0.01 357.15 207.75 41671 +1983 272 15.21 9.21 13.56 0.01 388.82 203.66 41468 +1983 273 13.92 7.92 12.27 0 360.53 271.42 41265 +1983 274 12.59 6.59 10.94 0.34 333.23 203.25 41062 +1983 275 10.63 4.63 8.98 0 296.23 271.21 40860 +1983 276 10.93 4.93 9.28 0 301.65 268.04 40658 +1983 277 14.25 8.25 12.6 0 367.6 260.02 40456 +1983 278 14.41 8.41 12.76 0 371.06 256.88 40255 +1983 279 12.59 6.59 10.94 0.93 333.23 192.83 40054 +1983 280 13.01 7.01 11.36 0.07 341.66 190.33 39854 +1983 281 16.41 10.41 14.76 0 416.81 245.06 39654 +1983 282 14.14 8.14 12.49 0.43 365.23 184.85 39455 +1983 283 11.96 5.96 10.31 0.01 320.93 185.31 39256 +1983 284 14.84 8.84 13.19 0 380.52 239.46 39058 +1983 285 19.21 13.21 17.56 0 488.88 228.3 38861 +1983 286 16.04 10.04 14.39 0 408 232 38664 +1983 287 16.84 10.84 15.19 0 427.25 227.63 38468 +1983 288 20.34 14.34 18.69 0.61 520.83 163.2 38273 +1983 289 14.44 8.44 12.79 0 371.72 226.51 38079 +1983 290 16.74 10.74 15.09 0 424.8 219.73 37885 +1983 291 14.17 8.17 12.52 0.38 365.87 166.08 37693 +1983 292 14.76 8.76 13.11 0 378.75 217.85 37501 +1983 293 16.01 10.01 14.36 0 407.3 213.09 37311 +1983 294 14.71 8.71 13.06 0 377.64 212.39 37121 +1983 295 17.13 11.13 15.48 0 434.42 205.54 36933 +1983 296 17.65 11.65 16 0 447.52 202.09 36745 +1983 297 17.35 11.35 15.7 0 439.92 199.99 36560 +1983 298 17.07 11.07 15.42 0 432.93 197.97 36375 +1983 299 12.62 6.62 10.97 1.87 333.83 151.52 36191 +1983 300 10.92 4.92 9.27 0.28 301.47 151.13 36009 +1983 301 10.11 4.11 8.46 0 287.02 199.92 35829 +1983 302 10.6 4.6 8.95 0 295.69 196.76 35650 +1983 303 9.59 3.59 7.94 0.35 278.06 146.47 35472 +1983 304 8.96 2.96 7.31 0.08 267.53 145.1 35296 +1983 305 3.17 -2.83 1.52 0 185.71 195.57 35122 +1983 306 -1.42 -7.42 -3.07 0 137.16 195.97 34950 +1983 307 1.28 -4.72 -0.37 0.08 164.17 143.94 34779 +1983 308 5.1 -0.9 3.45 0 210.18 186.68 34610 +1983 309 8.39 2.39 6.74 0 258.3 181.57 34444 +1983 310 8.89 2.89 7.24 0 266.38 178.66 34279 +1983 311 8.67 2.67 7.02 0 262.8 176.69 34116 +1983 312 7.2 1.2 5.55 0 239.91 175.34 33956 +1983 313 4.39 -1.61 2.74 0 200.88 175.36 33797 +1983 314 6.4 0.4 4.75 0 228.18 171.9 33641 +1983 315 3.69 -2.31 2.04 0.05 192.05 128.47 33488 +1983 316 5.71 -0.29 4.06 0 218.47 167.68 33337 +1983 317 11.63 5.63 9.98 0 314.64 160.22 33188 +1983 318 8.28 2.28 6.63 0 256.55 161.1 33042 +1983 319 9.78 3.78 8.13 0 281.31 158.08 32899 +1983 320 12.39 6.39 10.74 0 329.28 153.61 32758 +1983 321 12.75 6.75 11.1 0 336.42 151.16 32620 +1983 322 12.58 6.58 10.93 0.29 333.03 112.17 32486 +1983 323 11.47 5.47 9.82 0 311.63 149.14 32354 +1983 324 12.32 6.32 10.67 0 327.91 146.25 32225 +1983 325 9.15 3.15 7.5 0.57 270.67 110.67 32100 +1983 326 10.12 4.12 8.47 0 287.2 145.27 31977 +1983 327 7.64 1.64 5.99 0 246.57 145.5 31858 +1983 328 5.12 -0.88 3.47 0 210.45 145.3 31743 +1983 329 -0.09 -6.09 -1.74 0 149.94 146.63 31631 +1983 330 1.42 -4.58 -0.23 0 165.69 144.44 31522 +1983 331 -2.86 -8.86 -4.51 0 124.39 144.95 31417 +1983 332 -2.02 -8.02 -3.67 0 131.71 142.96 31316 +1983 333 -3.97 -9.97 -5.62 0.87 115.27 151.88 31218 +1983 334 -2.07 -8.07 -3.72 0.56 131.26 152.38 31125 +1983 335 -0.92 -6.92 -2.57 0 141.85 186.05 31035 +1983 336 0.91 -5.09 -0.74 0.16 160.22 149.88 30949 +1983 337 -1.61 -7.61 -3.26 0 135.41 183.7 30867 +1983 338 -0.84 -6.84 -2.49 0.25 142.61 149.5 30790 +1983 339 1.85 -4.15 0.2 0.66 170.43 147.87 30716 +1983 340 0.66 -5.34 -0.99 0 157.6 181.04 30647 +1983 341 -0.16 -6.16 -1.81 0 149.25 180.57 30582 +1983 342 6.18 0.18 4.53 0 225.05 175.76 30521 +1983 343 5.57 -0.43 3.92 0 216.54 174.67 30465 +1983 344 8.71 2.71 7.06 0 263.45 170.35 30413 +1983 345 5.33 -0.67 3.68 0 213.27 171.55 30366 +1983 346 4.61 -1.39 2.96 0 203.72 170.87 30323 +1983 347 4.07 -1.93 2.42 0 196.8 170.09 30284 +1983 348 12.04 6.04 10.39 0 322.47 120.19 30251 +1983 349 9.35 3.35 7.7 0 274.01 122.06 30221 +1983 350 8.22 2.22 6.57 0 255.6 122.56 30197 +1983 351 13.53 7.53 11.88 0.05 352.34 88.41 30177 +1983 352 13.18 7.18 11.53 0 345.12 118.13 30162 +1983 353 10.29 4.29 8.64 0 290.18 120.63 30151 +1983 354 9.73 3.73 8.08 0 280.45 121.04 30145 +1983 355 10.31 4.31 8.66 0 290.53 120.58 30144 +1983 356 4.73 -1.27 3.08 0 205.29 124.41 30147 +1983 357 2.87 -3.13 1.22 0.02 182.14 94.1 30156 +1983 358 -4.81 -10.81 -6.46 0 108.75 128.56 30169 +1983 359 -1.79 -7.79 -3.44 0 133.78 127.69 30186 +1983 360 -5.09 -11.09 -6.74 0 106.65 129.14 30208 +1983 361 -3.3 -9.3 -4.95 0 120.7 128.92 30235 +1983 362 -3.17 -9.17 -4.82 0 121.78 129.32 30267 +1983 363 0.62 -5.38 -1.03 0.31 157.18 96.34 30303 +1983 364 -1.61 -7.61 -3.26 0.07 135.41 141.05 30343 +1983 365 1.97 -4.03 0.32 0.28 171.77 96.61 30388 +1984 1 -1.48 -7.48 -3.13 0.01 136.61 141.79 30438 +1984 2 3.99 -2.01 2.34 0.39 195.79 97.04 30492 +1984 3 6.26 0.26 4.61 0.04 226.18 96.73 30551 +1984 4 7.99 1.99 6.34 0 251.99 128.7 30614 +1984 5 4.95 -1.05 3.3 0 208.18 131.34 30681 +1984 6 5.46 -0.54 3.81 0.82 215.04 98.93 30752 +1984 7 6.63 0.63 4.98 0 231.5 131.94 30828 +1984 8 9.7 3.7 8.05 0.08 279.94 98.35 30907 +1984 9 9.22 3.22 7.57 0.07 271.84 99.57 30991 +1984 10 6.25 0.25 4.6 0.07 226.04 102.16 31079 +1984 11 5.58 -0.42 3.93 0.02 216.68 103.22 31171 +1984 12 4.95 -1.05 3.3 0.01 208.18 104.27 31266 +1984 13 3.43 -2.57 1.78 0.24 188.86 106.17 31366 +1984 14 2.99 -3.01 1.34 0.44 183.56 107.46 31469 +1984 15 0.28 -5.72 -1.37 1.05 153.68 109.58 31575 +1984 16 -2.45 -8.45 -4.1 0 127.92 148.57 31686 +1984 17 -1.69 -7.69 -3.34 0 134.68 149.97 31800 +1984 18 -3.02 -9.02 -4.67 0 123.04 152.41 31917 +1984 19 -3.13 -9.13 -4.78 0.35 122.12 158.06 32038 +1984 20 -3.52 -9.52 -5.17 0 118.89 198.26 32161 +1984 21 -3.73 -9.73 -5.38 0 117.19 200.2 32289 +1984 22 -0.09 -6.09 -1.74 1.1 149.94 163.9 32419 +1984 23 1.07 -4.93 -0.58 0.45 161.92 164.49 32552 +1984 24 4.51 -1.49 2.86 0.25 202.42 163.79 32688 +1984 25 7.79 1.79 6.14 0.28 248.88 162.24 32827 +1984 26 4.53 -1.47 2.88 0.25 202.68 164.75 32969 +1984 27 1.49 -4.51 -0.16 0 166.46 209.17 33114 +1984 28 6.55 0.55 4.9 0 230.34 207.06 33261 +1984 29 4.56 -1.44 2.91 0 203.07 210.15 33411 +1984 30 5.57 -0.43 3.92 0 216.54 171.67 33564 +1984 31 6.57 0.57 4.92 0 230.63 173.26 33718 +1984 32 7.01 1.01 5.36 0 237.08 175 33875 +1984 33 0.95 -5.05 -0.7 0.02 160.64 136.35 34035 +1984 34 0.14 -5.86 -1.51 0.2 152.26 138.36 34196 +1984 35 3.07 -2.93 1.42 0.39 184.52 138.67 34360 +1984 36 6.72 0.72 5.07 0.8 232.81 138.5 34526 +1984 37 8.19 2.19 6.54 0.03 255.13 139.32 34694 +1984 38 6.97 0.97 5.32 0.03 236.48 142.19 34863 +1984 39 6.7 0.7 5.05 0 232.52 192.41 35035 +1984 40 8.25 2.25 6.6 0.27 256.08 145.19 35208 +1984 41 8.17 2.17 6.52 0 254.81 196.25 35383 +1984 42 6.2 0.2 4.55 0 225.33 200.59 35560 +1984 43 0.28 -5.72 -1.37 0.17 153.68 155.67 35738 +1984 44 -1.08 -7.08 -2.73 0.2 140.33 195.48 35918 +1984 45 -3.56 -9.56 -5.21 0.05 118.57 198.36 36099 +1984 46 -0.87 -6.87 -2.52 0 142.33 253.24 36282 +1984 47 -0.67 -6.67 -2.32 0 144.25 255.8 36466 +1984 48 -2.41 -8.41 -4.06 0 128.27 259.4 36652 +1984 49 -1.02 -7.02 -2.67 0 140.9 261.29 36838 +1984 50 0.11 -5.89 -1.54 0 151.95 263.12 37026 +1984 51 1.09 -4.91 -0.56 0.54 162.13 207.88 37215 +1984 52 2.8 -3.2 1.15 0.85 181.32 208.63 37405 +1984 53 0.62 -5.38 -1.03 0 157.18 270.62 37596 +1984 54 2.9 -3.1 1.25 0.04 182.5 177.39 37788 +1984 55 4.54 -1.46 2.89 0 202.81 238.17 37981 +1984 56 4.45 -1.55 2.8 0 201.65 240.95 38175 +1984 57 1.59 -4.41 -0.06 0.47 167.55 184.61 38370 +1984 58 6.48 0.48 4.83 0 229.33 244.86 38565 +1984 59 5.51 -0.49 3.86 0 215.72 248.53 38761 +1984 60 12.25 6.25 10.6 0.73 326.54 182.45 38958 +1984 61 9.09 3.09 7.44 0.03 269.68 187.82 39156 +1984 62 11.89 5.89 10.24 0 319.59 249.41 39355 +1984 63 8.89 2.89 7.24 0 266.38 256.43 39553 +1984 64 8.46 2.46 6.81 0 259.42 259.84 39753 +1984 65 5.28 -0.72 3.63 0 212.6 266.22 39953 +1984 66 5.91 -0.09 4.26 0 221.25 268.33 40154 +1984 67 10.22 4.22 8.57 0 288.95 266.02 40355 +1984 68 10.47 4.47 8.82 0 293.37 268.51 40556 +1984 69 7.38 1.38 5.73 0 242.61 275.11 40758 +1984 70 6.12 0.12 4.47 0 224.2 279.39 40960 +1984 71 5.98 -0.02 4.33 0 222.23 282.47 41163 +1984 72 7.39 1.39 5.74 0 242.76 283.68 41366 +1984 73 9.56 3.56 7.91 0 277.55 283.54 41569 +1984 74 10.92 4.92 9.27 0 301.47 284.28 41772 +1984 75 8.29 2.29 6.64 0 256.71 290.7 41976 +1984 76 7.4 1.4 5.75 0 242.92 294.47 42179 +1984 77 6.92 0.92 5.27 0.24 235.74 223.25 42383 +1984 78 5.8 -0.2 4.15 0 219.72 301.66 42587 +1984 79 3.52 -2.48 1.87 0 189.96 306.82 42791 +1984 80 3.91 -2.09 2.26 0 194.79 309 42996 +1984 81 4.59 -1.41 2.94 0 203.46 310.91 43200 +1984 82 5.13 -0.87 3.48 0.24 210.58 234.75 43404 +1984 83 5.13 -0.87 3.48 0.79 210.58 236.64 43608 +1984 84 1.96 -4.04 0.31 0.03 171.66 240.99 43812 +1984 85 0.56 -5.44 -1.09 0 156.56 325.09 44016 +1984 86 8.27 2.27 6.62 0.23 256.39 239.32 44220 +1984 87 9.02 3.02 7.37 0.89 268.52 240.41 44424 +1984 88 12.42 6.42 10.77 0 329.87 317.31 44627 +1984 89 14.04 8.04 12.39 0.41 363.09 237.33 44831 +1984 90 10.43 4.43 8.78 0.25 292.66 244.02 45034 +1984 91 12.23 6.23 10.58 0 326.15 324.49 45237 +1984 92 13.12 7.12 11.47 0 343.89 325.03 45439 +1984 93 11.8 5.8 10.15 0.27 317.87 247.27 45642 +1984 94 12.75 6.75 11.1 0.47 336.42 247.55 45843 +1984 95 10.97 4.97 9.32 0 302.38 335.44 46045 +1984 96 12.99 6.99 11.34 0 341.25 333.81 46246 +1984 97 12.36 6.36 10.71 0.03 328.69 252.8 46446 +1984 98 13.66 7.66 12.01 0.04 355.05 252.33 46647 +1984 99 12.5 6.5 10.85 0 331.45 340.76 46846 +1984 100 12.14 6.14 10.49 0 324.4 343.39 47045 +1984 101 9.78 3.78 8.13 0 281.31 349.51 47243 +1984 102 8.96 2.96 7.31 0 267.53 352.75 47441 +1984 103 9.86 3.86 8.21 0.47 282.68 264.86 47638 +1984 104 14.7 8.7 13.05 0 377.42 345.52 47834 +1984 105 15.71 9.71 14.06 0 400.28 344.93 48030 +1984 106 15.19 9.19 13.54 0 388.37 347.79 48225 +1984 107 13.22 7.22 11.57 0 345.94 353.8 48419 +1984 108 17.13 11.13 15.48 0 434.42 346.31 48612 +1984 109 16.24 10.24 14.59 0 412.74 350.19 48804 +1984 110 12.41 6.41 10.76 0 329.68 360.22 48995 +1984 111 13.59 7.59 11.94 0 353.59 359.31 49185 +1984 112 17.65 11.65 16 0 447.52 350.85 49374 +1984 113 17.41 11.41 15.76 0 441.43 352.82 49561 +1984 114 16.29 10.29 14.64 0.07 413.94 267.94 49748 +1984 115 11.82 5.82 10.17 0.53 318.25 276.57 49933 +1984 116 10.14 4.14 8.49 0.17 287.55 279.85 50117 +1984 117 10.24 4.24 8.59 0.3 289.3 280.71 50300 +1984 118 9.13 3.13 7.48 0 270.34 377.55 50481 +1984 119 5.02 -0.98 3.37 0.15 209.11 288.64 50661 +1984 120 6.26 0.26 4.61 2.54 226.18 288.29 50840 +1984 121 9.65 3.65 8 1.49 279.08 285.16 51016 +1984 122 12.65 6.65 11 0.08 334.42 281.75 51191 +1984 123 16.59 10.59 14.94 0 421.16 367.32 51365 +1984 124 11.69 5.69 10.04 0.47 315.78 284.82 51536 +1984 125 16.9 10.9 15.25 0 428.73 368.52 51706 +1984 126 17.13 11.13 15.48 0.04 434.42 276.66 51874 +1984 127 18.34 12.34 16.69 0 465.43 366.27 52039 +1984 128 18.27 12.27 16.62 0 463.59 367.46 52203 +1984 129 22.42 16.42 20.77 0.1 584.3 265.75 52365 +1984 130 19.27 13.27 17.62 0.51 490.54 274.5 52524 +1984 131 17.47 11.47 15.82 0.05 442.95 279.15 52681 +1984 132 16.53 10.53 14.88 0.05 419.7 281.72 52836 +1984 133 17.8 11.8 16.15 0.21 451.37 279.57 52989 +1984 134 16.24 10.24 14.59 1.07 412.74 283.36 53138 +1984 135 15.1 9.1 13.45 0.05 386.34 286.1 53286 +1984 136 12.92 6.92 11.27 0.09 339.83 290.41 53430 +1984 137 13.02 7.02 11.37 0.52 341.86 290.78 53572 +1984 138 14.71 8.71 13.06 0.2 377.64 288.29 53711 +1984 139 11.65 5.65 10 0.21 315.02 293.95 53848 +1984 140 16.5 10.5 14.85 0.11 418.98 285.7 53981 +1984 141 16.34 10.34 14.69 0.11 415.13 286.35 54111 +1984 142 19.23 13.23 17.58 0 489.43 373.78 54238 +1984 143 19.04 13.04 17.39 0.59 484.22 281.19 54362 +1984 144 20.59 14.59 18.94 0.01 528.14 277.68 54483 +1984 145 16.92 10.92 15.27 0 429.22 382.19 54600 +1984 146 18.83 12.83 17.18 0 478.52 376.89 54714 +1984 147 18.32 12.32 16.67 1.05 464.91 284.21 54824 +1984 148 19.12 13.12 17.47 0.73 486.41 282.62 54931 +1984 149 15.92 9.92 14.27 0.02 405.18 289.86 55034 +1984 150 15.12 9.12 13.47 0.39 386.79 291.68 55134 +1984 151 14.92 8.92 13.27 0.95 382.3 292.35 55229 +1984 152 20.13 14.13 18.48 0.02 514.76 280.97 55321 +1984 153 15.76 9.76 14.11 0.35 401.44 291 55409 +1984 154 17.22 11.22 15.57 0.02 436.66 288.22 55492 +1984 155 16.58 10.58 14.93 0 420.91 386.3 55572 +1984 156 18.69 12.69 17.04 0 474.75 380.4 55648 +1984 157 21.38 15.38 19.73 0 551.79 371.45 55719 +1984 158 18.77 12.77 17.12 0 476.9 380.49 55786 +1984 159 20.59 14.59 18.94 0 528.14 374.68 55849 +1984 160 24 18 22.35 0.99 636.78 271.28 55908 +1984 161 22.12 16.12 20.47 0.08 574.76 277 55962 +1984 162 25.65 19.65 24 0 695.8 354.52 56011 +1984 163 26.76 20.76 25.11 0 738.06 349.42 56056 +1984 164 25.08 19.08 23.43 0.4 674.91 268.03 56097 +1984 165 24.99 18.99 23.34 0.04 671.66 268.4 56133 +1984 166 23.36 17.36 21.71 0.11 615.06 273.69 56165 +1984 167 20.97 14.97 19.32 0.17 539.4 280.52 56192 +1984 168 19.72 13.72 18.07 0.12 503.09 283.81 56214 +1984 169 21.79 15.79 20.14 0.08 564.42 278.33 56231 +1984 170 21.65 15.65 20 0 560.08 371.63 56244 +1984 171 22.22 16.22 20.57 0.42 577.92 277.15 56252 +1984 172 20.68 14.68 19.03 0.04 530.79 281.39 56256 +1984 173 21.63 15.63 19.98 0 559.46 371.74 56255 +1984 174 19.33 13.33 17.68 0 492.19 379.66 56249 +1984 175 17.95 11.95 16.3 0.1 455.24 287.97 56238 +1984 176 19.68 13.68 18.03 1.84 501.96 283.83 56223 +1984 177 15.01 9.01 13.36 0 384.31 391.95 56203 +1984 178 13.96 7.96 12.31 0 361.38 394.55 56179 +1984 179 16.57 10.57 14.92 0.16 420.67 290.8 56150 +1984 180 16.93 10.93 15.28 0.91 429.47 289.95 56116 +1984 181 13.17 7.17 11.52 0 344.91 396.08 56078 +1984 182 16.37 10.37 14.72 0.05 415.85 290.95 56035 +1984 183 18.7 12.7 17.05 0.26 475.02 285.68 55987 +1984 184 20.23 14.23 18.58 0.21 517.65 281.8 55935 +1984 185 14.03 8.03 12.38 0.18 362.88 295.12 55879 +1984 186 18.48 12.48 16.83 0.64 469.14 285.82 55818 +1984 187 16.94 10.94 15.29 0 429.71 385.47 55753 +1984 188 18.37 12.37 16.72 0 466.23 380.98 55684 +1984 189 16.17 10.17 14.52 0 411.08 387.14 55611 +1984 190 18.28 12.28 16.63 0 463.85 380.7 55533 +1984 191 19.87 13.87 18.22 0 507.33 375.34 55451 +1984 192 25.35 19.35 23.7 0.25 684.74 265.19 55366 +1984 193 25.3 19.3 23.65 0.35 682.91 265.16 55276 +1984 194 23.83 17.83 22.18 0 630.95 359.72 55182 +1984 195 23.96 17.96 22.31 0.42 635.41 269.19 55085 +1984 196 21.39 15.39 19.74 0.05 552.1 276.42 54984 +1984 197 23.52 17.52 21.87 0.01 620.43 269.92 54879 +1984 198 20.57 14.57 18.92 1.72 527.55 277.95 54770 +1984 199 19.17 13.17 17.52 1.68 487.78 281.18 54658 +1984 200 20.78 14.78 19.13 0.41 533.75 276.83 54542 +1984 201 23.06 17.06 21.41 0.4 605.1 270.1 54423 +1984 202 25.77 19.77 24.12 0.11 700.27 260.99 54301 +1984 203 23.54 17.54 21.89 0.68 621.1 267.87 54176 +1984 204 20.36 14.36 18.71 0 521.41 368.52 54047 +1984 205 18.45 12.45 16.8 0.14 468.34 280.62 53915 +1984 206 23.43 17.43 21.78 0.7 617.4 267.04 53780 +1984 207 21.78 15.78 20.13 0.12 564.11 271.33 53643 +1984 208 23.3 17.3 21.65 0 613.06 355.29 53502 +1984 209 25.61 19.61 23.96 0 694.32 344.83 53359 +1984 210 26.02 20.02 24.37 0.39 709.66 256.77 53213 +1984 211 21.28 15.28 19.63 0.74 548.75 270.67 53064 +1984 212 20.67 14.67 19.02 0.37 530.49 271.67 52913 +1984 213 18.88 12.88 17.23 0 479.87 367.3 52760 +1984 214 20.73 14.73 19.08 0 532.26 360.52 52604 +1984 215 19.61 13.61 17.96 0 500 363.56 52445 +1984 216 18.03 12.03 16.38 0.38 457.31 275.54 52285 +1984 217 21.84 15.84 20.19 0.08 565.97 265.53 52122 +1984 218 24.47 18.47 22.82 0 653.15 342.97 51958 +1984 219 25.58 19.58 23.93 0 693.21 337.17 51791 +1984 220 31.93 25.93 30.28 0.57 964.61 227.05 51622 +1984 221 31.91 25.91 30.26 0.3 963.63 226.48 51451 +1984 222 27.75 21.75 26.1 0.04 777.56 243.11 51279 +1984 223 26.18 20.18 24.53 0 715.72 330.54 51105 +1984 224 23.88 17.88 22.23 0 632.66 339.36 50929 +1984 225 23.54 17.54 21.89 0.83 621.1 254.7 50751 +1984 226 22.25 16.25 20.6 0 578.87 343.36 50572 +1984 227 21.49 15.49 19.84 0 555.15 344.8 50392 +1984 228 18.87 12.87 17.22 0 479.6 352.05 50210 +1984 229 20.2 14.2 18.55 0 516.78 346.68 50026 +1984 230 15.44 9.44 13.79 0.18 394.06 269.08 49842 +1984 231 17.71 11.71 16.06 0.22 449.06 263.53 49656 +1984 232 17.62 11.62 15.97 0 446.76 350.26 49469 +1984 233 16.43 10.43 14.78 0 417.29 351.97 49280 +1984 234 16.76 10.76 15.11 0.03 425.29 262.26 49091 +1984 235 18.83 12.83 17.18 0 478.52 342.47 48900 +1984 236 21.42 15.42 19.77 0.39 553.01 249.68 48709 +1984 237 22.26 16.26 20.61 0.49 579.19 246.3 48516 +1984 238 23.4 17.4 21.75 0.02 616.4 241.98 48323 +1984 239 22.51 16.51 20.86 0.02 587.18 243.31 48128 +1984 240 25.09 19.09 23.44 0.16 675.27 234.68 47933 +1984 241 21.91 15.91 20.26 0.84 568.16 242.32 47737 +1984 242 16.79 10.79 15.14 0.08 426.03 252.34 47541 +1984 243 18.13 12.13 16.48 0.48 459.92 248.3 47343 +1984 244 13.8 7.8 12.15 0.11 357.99 254.7 47145 +1984 245 13.5 7.5 11.85 0 351.71 338.33 46947 +1984 246 18 12 16.35 0.08 456.53 244.33 46747 +1984 247 19.19 13.19 17.54 0 488.33 320.65 46547 +1984 248 18.32 12.32 16.67 0 464.91 321.12 46347 +1984 249 22.99 16.99 21.34 0 602.79 304.73 46146 +1984 250 26.36 20.36 24.71 0 722.59 289.99 45945 +1984 251 23.61 17.61 21.96 0.59 623.47 223.98 45743 +1984 252 24.82 18.82 23.17 0.31 665.56 219.09 45541 +1984 253 23.21 17.21 21.56 0.05 610.06 221.96 45339 +1984 254 22.95 16.95 21.3 0 601.48 294.79 45136 +1984 255 19.98 13.98 18.33 0 510.47 301.86 44933 +1984 256 17.31 11.31 15.66 0.64 438.92 230 44730 +1984 257 13.12 7.12 11.47 1.05 343.89 235.13 44527 +1984 258 14.5 8.5 12.85 0.61 373.03 231.31 44323 +1984 259 10.39 4.39 8.74 0 291.95 313.34 44119 +1984 260 9.79 3.79 8.14 0.01 281.48 233.86 43915 +1984 261 15.77 9.77 14.12 0.01 401.68 223.82 43711 +1984 262 15.49 9.49 13.84 0.08 395.2 222.48 43507 +1984 263 14.44 8.44 12.79 0 371.72 296.31 43303 +1984 264 16.1 10.1 14.45 0 409.42 290.29 43099 +1984 265 15.95 9.95 14.3 0.1 405.89 216.18 42894 +1984 266 21.19 15.19 19.54 0.81 546.02 204.6 42690 +1984 267 22.63 16.63 20.98 0.71 591.05 199.47 42486 +1984 268 22.24 16.24 20.59 0.46 578.56 198.52 42282 +1984 269 20.05 14.05 18.4 0.13 512.47 201.32 42078 +1984 270 19.09 13.09 17.44 2.33 485.59 201.23 41875 +1984 271 21.54 15.54 19.89 0.32 556.69 194.47 41671 +1984 272 20.35 14.35 18.7 0 521.12 259.9 41468 +1984 273 20.36 14.36 18.71 0.09 521.41 193.08 41265 +1984 274 14.7 8.7 13.05 0 377.42 267.32 41062 +1984 275 14.71 8.71 13.06 1.35 377.64 198.41 40860 +1984 276 12.02 6.02 10.37 0.68 322.08 199.8 40658 +1984 277 16.88 10.88 15.23 0.42 428.23 191.24 40456 +1984 278 18.03 12.03 16.38 0 457.31 249.73 40255 +1984 279 17.93 11.93 16.28 0 454.72 247.2 40054 +1984 280 18 12 16.35 0 456.53 244.47 39854 +1984 281 16.08 10.08 14.43 0 408.95 245.69 39654 +1984 282 13.23 7.23 11.58 0.1 346.14 185.97 39455 +1984 283 13.32 7.32 11.67 0.55 347.99 183.75 39256 +1984 284 8.97 2.97 7.32 0 267.7 248.01 39058 +1984 285 11.48 5.48 9.83 0.03 311.82 181.55 38861 +1984 286 15.21 9.21 13.56 0 388.82 233.48 38664 +1984 287 13.4 7.4 11.75 0.01 349.64 175.15 38468 +1984 288 16.46 10.46 14.81 0 418.01 225.62 38273 +1984 289 16.37 10.37 14.72 0 415.85 223.2 38079 +1984 290 16.22 10.22 14.57 0.01 412.27 165.5 37885 +1984 291 11.69 5.69 10.04 0.42 315.78 168.78 37693 +1984 292 10.46 4.46 8.81 0.88 293.19 167.95 37501 +1984 293 11.07 5.07 9.42 0 304.21 220.43 37311 +1984 294 17.73 11.73 16.08 0 449.57 207.19 37121 +1984 295 16.08 10.08 14.43 0 408.95 207.37 36933 +1984 296 13.77 7.77 12.12 0 357.36 208.46 36745 +1984 297 13.2 7.2 11.55 0 345.53 206.58 36560 +1984 298 12.88 6.88 11.23 0 339.03 204.44 36375 +1984 299 15.09 9.09 13.44 0 386.11 198.5 36191 +1984 300 17.47 11.47 15.82 0 442.95 191.99 36009 +1984 301 16.11 10.11 14.46 0.41 409.66 143.88 35829 +1984 302 18.63 12.63 16.98 0.03 473.14 138.73 35650 +1984 303 15.12 9.12 13.47 1.16 386.79 141.23 35472 +1984 304 10.95 4.95 9.3 0.37 302.02 143.5 35296 +1984 305 4.58 -1.42 2.93 0.2 203.33 145.92 35122 +1984 306 4.38 -1.62 2.73 0 200.75 192.41 34950 +1984 307 2.95 -3.05 1.3 0.08 183.09 143.15 34779 +1984 308 6.59 0.59 4.94 0.06 230.92 139.12 34610 +1984 309 2.19 -3.81 0.54 1.35 174.26 139.75 34444 +1984 310 4.3 -1.7 2.65 0.18 199.72 136.84 34279 +1984 311 5.99 -0.01 4.34 0 222.37 178.98 34116 +1984 312 8.89 2.89 7.24 0.33 266.38 130.38 33956 +1984 313 8.82 2.82 7.17 0.81 265.24 128.85 33797 +1984 314 6.5 0.5 4.85 0 229.62 171.82 33641 +1984 315 10.29 4.29 8.64 0 290.18 165.92 33488 +1984 316 8.13 2.13 6.48 0 254.18 165.75 33337 +1984 317 6.45 0.45 4.8 0 228.9 164.92 33188 +1984 318 6.73 0.73 5.08 0 232.96 162.36 33042 +1984 319 5.16 -0.84 3.51 0 210.98 161.81 32899 +1984 320 6.31 0.31 4.66 0 226.89 159.11 32758 +1984 321 7.39 1.39 5.74 0 242.76 156.17 32620 +1984 322 9.72 3.72 8.07 0 280.28 152.39 32486 +1984 323 5.07 -0.93 3.42 0 209.78 154.41 32354 +1984 324 10.65 4.65 9 0 296.59 147.91 32225 +1984 325 13.24 7.24 11.59 0.09 346.35 107.69 32100 +1984 326 12.17 6.17 10.52 0 324.99 143.31 31977 +1984 327 11.45 5.45 9.8 0.57 311.26 106.66 31858 +1984 328 12.36 6.36 10.71 0.26 328.69 104.53 31743 +1984 329 12.56 6.56 10.91 0 332.64 137.71 31631 +1984 330 12.6 6.6 10.95 0.09 333.43 102.2 31522 +1984 331 10.02 4.02 8.37 0 285.45 137.4 31417 +1984 332 12.85 6.85 11.2 0 338.42 133.13 31316 +1984 333 14.65 8.65 13 0.49 376.32 97.61 31218 +1984 334 11.64 5.64 9.99 0.3 314.83 99.14 31125 +1984 335 3.41 -2.59 1.76 0 188.62 137.02 31035 +1984 336 3.41 -2.59 1.76 0 188.62 135.95 30949 +1984 337 2.54 -3.46 0.89 0.16 178.28 101.06 30867 +1984 338 -0.29 -6.29 -1.94 0 147.96 135.11 30790 +1984 339 -3.58 -9.58 -5.23 0 118.4 135.56 30716 +1984 340 -4.22 -10.22 -5.87 0 113.29 135.01 30647 +1984 341 -2.24 -8.24 -3.89 0.07 129.76 143.43 30582 +1984 342 -4.08 -10.08 -5.73 0 114.39 176.73 30521 +1984 343 -3.81 -9.81 -5.46 0 116.55 175.88 30465 +1984 344 -0.81 -6.81 -2.46 0 142.9 173.73 30413 +1984 345 -3.47 -9.47 -5.12 0.79 119.3 144.17 30366 +1984 346 -2.43 -8.43 -4.08 0.05 128.09 143.7 30323 +1984 347 2.67 -3.33 1.02 0 179.79 173.08 30284 +1984 348 2.94 -3.06 1.29 0 182.97 172.25 30251 +1984 349 5.94 -0.06 4.29 0 221.67 169.44 30221 +1984 350 2.7 -3.3 1.05 0 180.14 170.58 30197 +1984 351 3.08 -2.92 1.43 0 184.64 169.79 30177 +1984 352 3.33 -2.67 1.68 0 187.64 169.14 30162 +1984 353 5.51 -0.49 3.86 0 215.72 123.96 30151 +1984 354 5.71 -0.29 4.06 0 218.47 123.81 30145 +1984 355 3.12 -2.88 1.47 0 185.11 125.25 30144 +1984 356 3.25 -2.75 1.6 0.25 186.68 93.91 30147 +1984 357 2.38 -3.62 0.73 0.03 176.43 94.28 30156 +1984 358 5.82 -0.18 4.17 0.14 219.99 92.93 30169 +1984 359 7.06 1.06 5.41 0 237.82 123.24 30186 +1984 360 11.41 5.41 9.76 0 310.51 120.29 30208 +1984 361 9.12 3.12 7.47 0 270.17 122.47 30235 +1984 362 8.78 2.78 7.13 0 264.59 123.16 30267 +1984 363 8.16 2.16 6.51 0.37 254.65 93.14 30303 +1984 364 8.9 2.9 7.25 0.3 266.55 93.03 30343 +1984 365 8.24 2.24 6.59 0.02 255.92 93.81 30388 +1985 1 4.91 -1.09 3.26 0.46 207.65 96.1 30438 +1985 2 0.61 -5.39 -1.04 0.1 157.08 98.3 30492 +1985 3 -0.17 -6.17 -1.82 0.19 149.15 143.07 30551 +1985 4 -1.8 -7.8 -3.45 0 133.69 177.64 30614 +1985 5 -4.34 -10.34 -5.99 0 112.36 179.09 30681 +1985 6 -5.66 -11.66 -7.31 0 102.49 180.29 30752 +1985 7 -5.98 -11.98 -7.63 0.1 100.21 146.98 30828 +1985 8 -8.43 -14.43 -10.08 0 84.19 183.45 30907 +1985 9 -9.07 -15.07 -10.72 0 80.4 184.76 30991 +1985 10 -6.66 -12.66 -8.31 0.28 95.52 150.72 31079 +1985 11 -8.5 -14.5 -10.15 0 83.77 187.58 31171 +1985 12 -5.95 -11.95 -7.6 0 100.42 187.8 31266 +1985 13 -5.74 -11.74 -7.39 0 101.91 189.24 31366 +1985 14 -2.47 -8.47 -4.12 0 127.74 189.49 31469 +1985 15 -1.72 -7.72 -3.37 0.08 134.41 154.01 31575 +1985 16 -2.29 -8.29 -3.94 0 129.32 192.13 31686 +1985 17 -0.12 -6.12 -1.77 0 149.64 192.76 31800 +1985 18 0.29 -5.71 -1.36 0 153.78 194.28 31917 +1985 19 0.36 -5.64 -1.29 0.2 154.5 157.76 32038 +1985 20 3.43 -2.57 1.78 0.12 188.86 157.12 32161 +1985 21 1.48 -4.52 -0.17 1.22 166.35 159.1 32289 +1985 22 1.89 -4.11 0.24 0.33 170.88 159.85 32419 +1985 23 -1.08 -7.08 -2.73 0 140.33 202.32 32552 +1985 24 -0.53 -6.53 -2.18 0 145.6 203.98 32688 +1985 25 0.02 -5.98 -1.63 0.26 151.05 164.38 32827 +1985 26 -1.86 -7.86 -3.51 0 133.14 208.09 32969 +1985 27 -1 -7 -2.65 0.07 141.09 167.59 33114 +1985 28 -2.5 -8.5 -4.15 0.01 127.48 169.61 33261 +1985 29 -6.83 -12.83 -8.48 0 94.38 216.35 33411 +1985 30 -4.74 -10.74 -6.39 0 109.28 217.73 33564 +1985 31 -1.98 -7.98 -3.63 0.09 132.07 174.46 33718 +1985 32 -0.01 -6.01 -1.66 0.2 150.74 175.72 33875 +1985 33 -0.08 -6.08 -1.73 0.19 150.04 178.08 34035 +1985 34 -1.35 -7.35 -3 0 137.81 226.35 34196 +1985 35 3.06 -2.94 1.41 0 184.4 225.46 34360 +1985 36 2.85 -3.15 1.2 0 181.9 227.59 34526 +1985 37 0.38 -5.62 -1.27 0 154.7 231.3 34694 +1985 38 0.23 -5.77 -1.42 0.29 153.17 185.34 34863 +1985 39 -1.69 -7.69 -3.34 0 134.68 237.38 35035 +1985 40 3.08 -2.92 1.43 0 184.64 236.67 35208 +1985 41 1.41 -4.59 -0.24 0.36 165.58 189.66 35383 +1985 42 -0.74 -6.74 -2.39 0.42 143.57 193.48 35560 +1985 43 3.25 -2.75 1.6 0.13 186.68 193.08 35738 +1985 44 4.24 -1.76 2.59 0 198.96 245.65 35918 +1985 45 4.54 -1.46 2.89 0 202.81 247.34 36099 +1985 46 4.7 -1.3 3.05 0 204.89 249.19 36282 +1985 47 -0.24 -6.24 -1.89 0.21 148.45 201.17 36466 +1985 48 -0.55 -6.55 -2.2 0 145.41 258.68 36652 +1985 49 -0.63 -6.63 -2.28 0 144.63 261.35 36838 +1985 50 -3.51 -9.51 -5.16 0 118.98 265.41 37026 +1985 51 -2.02 -8.02 -3.67 0.01 131.71 209.74 37215 +1985 52 -0.71 -6.71 -2.36 0.14 143.86 211.51 37405 +1985 53 1.39 -4.61 -0.26 0.64 165.37 212.4 37596 +1985 54 0.87 -5.13 -0.78 0.09 159.8 214.48 37788 +1985 55 -5.09 -11.09 -6.74 0 106.65 280.17 37981 +1985 56 -2.51 -8.51 -4.16 0 127.4 281.45 38175 +1985 57 -0.8 -6.8 -2.45 0 143 283.21 38370 +1985 58 -3.27 -9.27 -4.92 0 120.95 287.43 38565 +1985 59 -3.24 -9.24 -4.89 0 121.2 290 38761 +1985 60 6.22 0.22 4.57 0.07 225.61 222.3 38958 +1985 61 7.67 1.67 6.02 0.23 247.03 189.07 39156 +1985 62 6.7 0.7 5.05 0.06 232.52 191.96 39355 +1985 63 8.62 2.62 6.97 0 261.99 256.76 39553 +1985 64 4.04 -1.96 2.39 0.87 196.42 198.37 39753 +1985 65 5.54 -0.46 3.89 1.44 216.13 199.47 39953 +1985 66 2.27 -3.73 0.62 0.71 175.17 203.79 40154 +1985 67 2.28 -3.72 0.63 0.05 175.29 205.99 40355 +1985 68 0.21 -5.79 -1.44 0.03 152.96 209.38 40556 +1985 69 3.81 -2.19 2.16 0 193.54 278.86 40758 +1985 70 5.66 -0.34 4.01 0 217.78 279.88 40960 +1985 71 3.42 -2.58 1.77 0.15 188.74 213.78 41163 +1985 72 7.59 1.59 5.94 0 245.81 283.44 41366 +1985 73 9.03 3.03 7.38 0 268.69 284.26 41569 +1985 74 9.3 3.3 7.65 0 273.17 286.63 41772 +1985 75 11.49 5.49 9.84 1.91 312.01 214.57 41976 +1985 76 11.41 5.41 9.76 0 310.51 288.82 42179 +1985 77 6.38 0.38 4.73 0 227.89 298.3 42383 +1985 78 7.46 1.46 5.81 0 243.83 299.67 42587 +1985 79 5.41 -0.59 3.76 0 214.36 304.84 42791 +1985 80 8.82 2.82 7.17 0 265.24 303.14 42996 +1985 81 9.45 3.45 7.8 0 275.69 304.81 43200 +1985 82 10.38 4.38 8.73 0 291.77 306.06 43404 +1985 83 8.02 2.02 6.37 0 252.46 311.97 43608 +1985 84 5.11 -0.89 3.46 0.21 210.31 238.58 43812 +1985 85 2.56 -3.44 0.91 0 178.51 323.3 44016 +1985 86 3.98 -2.02 2.33 0 195.67 324.32 44220 +1985 87 9.5 3.5 7.85 0 276.54 319.84 44424 +1985 88 12.29 6.29 10.64 0 327.32 317.55 44627 +1985 89 12.82 6.82 11.17 0 337.82 318.82 44831 +1985 90 13.46 7.46 11.81 0 350.88 319.93 45034 +1985 91 19.06 13.06 17.41 0.12 484.77 231.78 45237 +1985 92 17.89 11.89 16.24 0 453.69 314.3 45439 +1985 93 18.81 12.81 17.16 0.5 477.98 235.49 45642 +1985 94 17.67 11.67 16.02 0.01 448.04 239.31 45843 +1985 95 15.34 9.34 13.69 0 391.77 326.78 46045 +1985 96 17.33 11.33 15.68 0.58 439.42 243.05 46246 +1985 97 17.37 11.37 15.72 0 440.43 325.95 46446 +1985 98 18.4 12.4 16.75 0 467.02 325.12 46647 +1985 99 17.38 11.38 15.73 0 440.68 329.78 46846 +1985 100 13.9 7.9 12.25 0 360.11 339.85 47045 +1985 101 13.62 7.62 11.97 0 354.21 342.35 47243 +1985 102 11.96 5.96 10.31 0 320.93 347.56 47441 +1985 103 12.47 6.47 10.82 0 330.86 348.41 47638 +1985 104 13.71 7.71 12.06 0 356.1 347.69 47834 +1985 105 11.65 5.65 10 0 315.02 353.6 48030 +1985 106 7.33 1.33 5.68 0 241.86 362.42 48225 +1985 107 7.34 1.34 5.69 0.07 242.01 273.08 48419 +1985 108 11.1 5.1 9.45 0 304.76 359.71 48612 +1985 109 12.06 6.06 10.41 0 322.85 359.5 48804 +1985 110 17.02 11.02 15.37 1.58 431.69 262.17 48995 +1985 111 12.36 6.36 10.71 0.38 328.69 271.4 49185 +1985 112 12.55 6.55 10.9 0.17 332.44 272.26 49374 +1985 113 10.44 4.44 8.79 0.06 292.83 276.3 49561 +1985 114 10.8 4.8 9.15 0 299.29 369.26 49748 +1985 115 12.85 6.85 11.2 0 338.42 366.66 49933 +1985 116 10.51 4.51 8.86 0 294.08 372.47 50117 +1985 117 12.4 6.4 10.75 0 329.48 370.14 50300 +1985 118 14.99 8.99 13.34 0 383.87 365.7 50481 +1985 119 11.72 5.72 10.07 0.14 316.34 280.52 50661 +1985 120 7.85 1.85 6.2 0.03 249.81 286.53 50840 +1985 121 12.55 6.55 10.9 0.04 332.44 281 51016 +1985 122 14.82 8.82 13.17 1.04 380.08 278.08 51191 +1985 123 18.29 12.29 16.64 0.58 464.12 271.91 51365 +1985 124 17.47 11.47 15.82 0 442.95 365.97 51536 +1985 125 14.85 8.85 13.2 0.4 380.74 280.35 51706 +1985 126 13.79 7.79 12.14 1.38 357.78 282.96 51874 +1985 127 19.47 13.47 17.82 0.04 496.08 272.09 52039 +1985 128 20.91 14.91 19.26 0.23 537.61 269.24 52203 +1985 129 14.6 8.6 12.95 0.51 375.22 283.6 52365 +1985 130 17.56 11.56 15.91 0.1 445.23 278.36 52524 +1985 131 18.6 12.6 16.95 0 472.34 368.86 52681 +1985 132 16.8 10.8 15.15 0.1 426.27 281.17 52836 +1985 133 18.06 12.06 16.41 0 458.09 371.99 52989 +1985 134 17.6 11.6 15.95 0.54 446.25 280.53 53138 +1985 135 20.17 14.17 18.52 0 515.92 366.72 53286 +1985 136 18.66 12.66 17.01 0 473.94 372.2 53430 +1985 137 19.98 13.98 18.33 0 510.47 368.67 53572 +1985 138 23.33 17.33 21.68 0 614.06 356.98 53711 +1985 139 23.95 17.95 22.3 0.68 635.06 266.33 53848 +1985 140 23.86 17.86 22.21 0.01 631.98 266.95 53981 +1985 141 21.71 15.71 20.06 0.6 561.93 273.57 54111 +1985 142 21.37 15.37 19.72 1.31 551.49 274.87 54238 +1985 143 16.83 10.83 15.18 0.24 427.01 286.12 54362 +1985 144 13.58 7.58 11.93 0.01 353.38 292.67 54483 +1985 145 18.68 12.68 17.03 0 474.48 376.99 54600 +1985 146 16.62 10.62 14.97 0 421.88 383.41 54714 +1985 147 19.21 13.21 17.56 0 488.88 376.16 54824 +1985 148 24.49 18.49 22.84 0.42 653.85 267.56 54931 +1985 149 24.38 18.38 22.73 0.28 649.98 268.14 55034 +1985 150 26.7 20.7 25.05 0 735.72 347.19 55134 +1985 151 27.07 21.07 25.42 0 750.24 345.74 55229 +1985 152 24.52 18.52 22.87 0.3 654.91 268.28 55321 +1985 153 24.89 18.89 23.24 0.88 668.07 267.24 55409 +1985 154 27.14 21.14 25.49 0.07 753.02 259.5 55492 +1985 155 27.57 21.57 25.92 0 770.25 344 55572 +1985 156 24.31 18.31 22.66 0 647.54 359.65 55648 +1985 157 23.97 17.97 22.32 0 635.75 361.26 55719 +1985 158 21.4 15.4 19.75 0.04 552.4 278.66 55786 +1985 159 18.63 12.63 16.98 0 473.14 381.17 55849 +1985 160 19.38 13.38 17.73 0.08 493.58 284.22 55908 +1985 161 18.49 12.49 16.84 0 469.41 381.86 55962 +1985 162 18.97 12.97 17.32 0.13 482.32 285.31 56011 +1985 163 22.61 16.61 20.96 0.3 590.41 275.78 56056 +1985 164 19.83 13.83 18.18 0.43 506.2 283.39 56097 +1985 165 21.33 15.33 19.68 0.37 550.27 279.52 56133 +1985 166 21.33 15.33 19.68 0 550.27 372.77 56165 +1985 167 19.59 13.59 17.94 0.33 499.44 284.08 56192 +1985 168 17.57 11.57 15.92 0.3 445.49 288.87 56214 +1985 169 17.38 11.38 15.73 0.72 440.68 289.3 56231 +1985 170 17.65 11.65 16 0.68 447.52 288.7 56244 +1985 171 11.69 5.69 10.04 0.47 315.78 299.9 56252 +1985 172 14.86 8.86 13.21 1.41 380.96 294.45 56256 +1985 173 15.26 9.26 13.61 0.33 389.95 293.68 56255 +1985 174 19.16 13.16 17.51 0.07 487.51 285.16 56249 +1985 175 20.37 14.37 18.72 0.1 521.7 282.11 56238 +1985 176 15.89 9.89 14.24 0 404.48 389.77 56223 +1985 177 16.01 10.01 14.36 0.05 407.3 292.01 56203 +1985 178 12.61 6.61 10.96 0 333.63 397.64 56179 +1985 179 14.26 8.26 12.61 0 367.81 393.72 56150 +1985 180 16.99 10.99 15.34 0.68 430.95 289.82 56116 +1985 181 14.39 8.39 12.74 1.73 370.63 294.91 56078 +1985 182 18.67 12.67 17.02 0 474.21 381.19 56035 +1985 183 20.77 14.77 19.12 0.26 533.45 280.51 55987 +1985 184 20.35 14.35 18.7 0.12 521.12 281.49 55935 +1985 185 20.12 14.12 18.47 0.21 514.48 282.02 55879 +1985 186 21.58 15.58 19.93 0.16 557.92 277.95 55818 +1985 187 17.61 11.61 15.96 0 446.5 383.54 55753 +1985 188 25.75 19.75 24.1 0.5 699.53 264.62 55684 +1985 189 21.92 15.92 20.27 0 568.47 368.7 55611 +1985 190 21.26 15.26 19.61 0.05 548.14 278.08 55533 +1985 191 22.52 16.52 20.87 0 587.51 365.78 55451 +1985 192 22.73 16.73 21.08 0.37 594.29 273.5 55366 +1985 193 21.32 15.32 19.67 1 549.96 277.29 55276 +1985 194 20.61 14.61 18.96 0.08 528.72 279.01 55182 +1985 195 22.98 16.98 21.33 0.36 602.46 272.19 55085 +1985 196 21.63 15.63 19.98 0.92 559.46 275.76 54984 +1985 197 26.48 20.48 24.83 0 727.2 346.75 54879 +1985 198 25.06 19.06 23.41 0.01 674.19 264.68 54770 +1985 199 22.96 16.96 21.31 0 601.8 361.39 54658 +1985 200 20.3 14.3 18.65 0 519.67 370.77 54542 +1985 201 23.31 17.31 21.66 0 613.39 359.14 54423 +1985 202 23.92 17.92 22.27 0 634.03 356.09 54301 +1985 203 27.56 21.56 25.91 0 769.85 338.85 54176 +1985 204 27.66 21.66 26.01 0 773.9 337.87 54047 +1985 205 29.21 23.21 27.56 0 839.06 329.17 53915 +1985 206 25.57 19.57 23.92 0 692.84 346.89 53780 +1985 207 26.76 20.76 25.11 0 738.06 340.69 53643 +1985 208 26.49 20.49 24.84 0 727.59 341.36 53502 +1985 209 26.49 20.49 24.84 0.55 727.59 255.56 53359 +1985 210 29.97 23.97 28.32 0 872.67 322.01 53213 +1985 211 26.09 20.09 24.44 0.38 712.3 255.97 53064 +1985 212 25.77 19.77 24.12 0 700.27 342 52913 +1985 213 27.65 21.65 26 0.32 773.49 249.22 52760 +1985 214 24.18 18.18 22.53 0.89 643.01 260.6 52604 +1985 215 22.48 16.48 20.83 2.33 586.22 265.16 52445 +1985 216 23.49 17.49 21.84 0 619.42 348.64 52285 +1985 217 21.89 15.89 20.24 0.15 567.53 265.4 52122 +1985 218 18.68 12.68 17.03 0.93 474.48 272.79 51958 +1985 219 20.87 14.87 19.22 0.03 536.42 266.71 51791 +1985 220 22.43 16.43 20.78 0 584.62 349.11 51622 +1985 221 24.54 18.54 22.89 0 655.61 339.8 51451 +1985 222 20.82 14.82 19.17 0.36 534.93 264.61 51279 +1985 223 20.27 14.27 18.62 0 518.8 353.52 51105 +1985 224 20.48 14.48 18.83 0.05 524.91 263.83 50929 +1985 225 17.6 11.6 15.95 0 446.25 359.4 50751 +1985 226 22.05 16.05 20.4 0.19 572.55 258.06 50572 +1985 227 22.1 16.1 20.45 0 574.13 342.64 50392 +1985 228 26.59 20.59 24.94 0.06 731.45 242.36 50210 +1985 229 25.35 19.35 23.7 0.88 684.74 245.61 50026 +1985 230 25.46 19.46 23.81 0.99 688.78 244.34 49842 +1985 231 23.85 17.85 22.2 0 631.63 330.99 49656 +1985 232 25.65 19.65 24 0 695.8 322.28 49469 +1985 233 25.62 19.62 23.97 0.26 694.69 240.8 49280 +1985 234 22.16 16.16 20.51 0 576.02 333.22 49091 +1985 235 21.36 15.36 19.71 1.38 551.18 250.89 48900 +1985 236 24.04 18.04 22.39 0 638.16 323.4 48709 +1985 237 20.39 14.39 18.74 0.66 522.29 250.99 48516 +1985 238 23.15 17.15 21.5 0.32 608.07 242.67 48323 +1985 239 24.95 18.95 23.3 0.3 670.22 236.36 48128 +1985 240 25.54 19.54 23.89 0.11 691.73 233.28 47933 +1985 241 24.52 18.52 22.87 1.1 654.91 235.15 47737 +1985 242 27.99 21.99 26.34 1.41 787.4 222.69 47541 +1985 243 26.85 20.85 25.2 0.23 741.58 225.3 47343 +1985 244 23.62 17.62 21.97 0 623.81 311.77 47145 +1985 245 22.6 16.6 20.95 0 590.08 313.65 46947 +1985 246 21.48 15.48 19.83 0 554.85 315.5 46747 +1985 247 19.6 13.6 17.95 0 499.72 319.47 46547 +1985 248 21.16 15.16 19.51 0.02 545.11 234.61 46347 +1985 249 20.56 14.56 18.91 0 527.26 312.66 46146 +1985 250 20.59 14.59 18.94 0 528.14 310.65 45945 +1985 251 20.35 14.35 18.7 0 521.12 309.3 45743 +1985 252 19.8 13.8 18.15 0 505.35 308.78 45541 +1985 253 22.1 16.1 20.45 0 574.13 299.67 45339 +1985 254 19.43 13.43 17.78 0.04 494.97 229.23 45136 +1985 255 19.49 13.49 17.84 0.43 496.64 227.43 44933 +1985 256 17.78 11.78 16.13 0.89 450.85 229.13 44730 +1985 257 16.09 10.09 14.44 0.06 409.18 230.52 44527 +1985 258 19.95 13.95 18.3 0 509.61 295.3 44323 +1985 259 18.91 12.91 17.26 0 480.69 295.74 44119 +1985 260 18.34 12.34 16.69 0.03 465.43 221.14 43915 +1985 261 17.65 11.65 16 0.01 447.52 220.6 43711 +1985 262 17.99 11.99 16.34 0.04 456.27 218.21 43507 +1985 263 18.65 12.65 17 0.1 473.68 215.16 43303 +1985 264 17.58 11.58 15.93 0.04 445.74 215.21 43099 +1985 265 18.37 12.37 16.72 0.04 466.23 212.03 42894 +1985 266 18.45 12.45 16.8 0 468.34 280.07 42690 +1985 267 16.43 10.43 14.78 0 417.29 282.07 42486 +1985 268 17.44 11.44 15.79 0 442.19 277.29 42282 +1985 269 19.84 13.84 18.19 0 506.48 268.98 42078 +1985 270 18.47 12.47 16.82 0.04 468.88 202.36 41875 +1985 271 21.12 15.12 19.47 1.62 543.91 195.35 41671 +1985 272 22.49 16.49 20.84 0.14 586.54 190.46 41468 +1985 273 20.34 14.34 18.69 0 520.83 257.49 41265 +1985 274 12.9 6.9 11.25 0 339.43 270.49 41062 +1985 275 11.81 5.81 10.16 0.11 318.06 202.09 40860 +1985 276 8.97 2.97 7.32 0 267.7 270.73 40658 +1985 277 10.15 4.15 8.5 0 287.72 266.44 40456 +1985 278 10.36 4.36 8.71 0 291.42 263.24 40255 +1985 279 16.02 10.02 14.37 0 407.53 251.11 40054 +1985 280 18.42 12.42 16.77 0 467.55 243.55 39854 +1985 281 19.29 13.29 17.64 0 491.09 238.96 39654 +1985 282 16.52 10.52 14.87 0 419.46 242.15 39455 +1985 283 14.46 8.46 12.81 0 372.15 243.11 39256 +1985 284 14.88 8.88 13.23 0 381.41 239.4 39058 +1985 285 17.64 11.64 15.99 0 447.27 231.62 38861 +1985 286 16.25 10.25 14.6 0 412.98 231.62 38664 +1985 287 14.89 8.89 13.24 0 381.63 231.13 38468 +1985 288 14.08 8.08 12.43 0.08 363.94 172.28 38273 +1985 289 15.8 9.8 14.15 0 402.38 224.22 38079 +1985 290 11.76 5.76 10.11 0 317.1 227.65 37885 +1985 291 13.29 7.29 11.64 0.2 347.37 167.09 37693 +1985 292 9.3 3.3 7.65 0 273.17 225.32 37501 +1985 293 7.96 1.96 6.31 0 251.52 224.03 37311 +1985 294 11.3 5.3 9.65 0 308.46 217.24 37121 +1985 295 12.87 6.87 11.22 0 338.83 212.31 36933 +1985 296 11.3 5.3 9.65 0 308.46 211.82 36745 +1985 297 12.99 6.99 11.34 0 341.25 206.87 36560 +1985 298 15.04 9.04 13.39 0.41 384.99 150.98 36375 +1985 299 14.74 8.74 13.09 0 378.3 199.03 36191 +1985 300 11.76 5.76 10.11 0 317.1 200.49 36009 +1985 301 9.18 3.18 7.53 0.11 271.17 150.7 35829 +1985 302 10.58 4.58 8.93 0 295.33 196.78 35650 +1985 303 10.83 4.83 9.18 0 299.83 193.92 35472 +1985 304 13.88 7.88 12.23 0 359.69 187.66 35296 +1985 305 1.08 -4.92 -0.57 0 162.03 196.92 35122 +1985 306 5.45 -0.55 3.8 0.2 214.9 143.69 34950 +1985 307 2.71 -3.29 1.06 0.37 180.26 143.27 34779 +1985 308 1.83 -4.17 0.18 0.25 170.21 141.69 34610 +1985 309 1.61 -4.39 -0.04 0.13 167.77 140.02 34444 +1985 310 3.16 -2.84 1.51 1.24 185.59 137.42 34279 +1985 311 0.93 -5.07 -0.72 2.3 160.43 136.77 34116 +1985 312 6.76 0.76 5.11 0.23 233.39 131.78 33956 +1985 313 5.4 -0.6 3.75 0.05 214.22 130.97 33797 +1985 314 8.56 2.56 6.91 0.62 261.02 127.56 33641 +1985 315 9.19 3.19 7.54 0.09 271.34 125.24 33488 +1985 316 9 3 7.35 0 268.19 164.98 33337 +1985 317 9.89 3.89 8.24 0.46 283.2 121.48 33188 +1985 318 8.2 2.2 6.55 0 255.28 161.17 33042 +1985 319 3.8 -2.2 2.15 0 193.42 162.71 32899 +1985 320 8.67 2.67 7.02 0 262.8 157.22 32758 +1985 321 9.84 3.84 8.19 0.94 282.34 115.56 32620 +1985 322 8.11 2.11 6.46 0 253.87 153.78 32486 +1985 323 4.93 -1.07 3.28 0.19 207.92 115.88 32354 +1985 324 3.52 -2.48 1.87 0.07 189.96 115 32225 +1985 325 5.31 -0.69 3.66 1.56 213 112.85 32100 +1985 326 1.83 -4.17 0.18 0.61 170.21 113.3 31977 +1985 327 4.43 -1.57 2.78 2.37 201.39 110.78 31858 +1985 328 3.59 -2.41 1.94 0.06 190.82 109.68 31743 +1985 329 7.45 1.45 5.8 0.46 243.67 106.64 31631 +1985 330 2.83 -3.17 1.18 0.23 181.67 107.78 31522 +1985 331 8.87 2.87 7.22 0 266.06 138.35 31417 +1985 332 7.93 1.93 6.28 0 251.05 137.45 31316 +1985 333 11.87 5.87 10.22 0.8 319.2 99.78 31218 +1985 334 11.9 5.9 10.25 0 319.78 131.94 31125 +1985 335 12.13 6.13 10.48 0 324.21 130.58 31035 +1985 336 9.15 3.15 7.5 0 270.67 132.13 30949 +1985 337 10.9 4.9 9.25 0 301.11 129.03 30867 +1985 338 14.93 8.93 13.28 0 382.52 124.11 30790 +1985 339 16.18 10.18 14.53 0 411.32 121.92 30716 +1985 340 17.31 11.31 15.66 0.46 438.92 89.88 30647 +1985 341 16.01 10.01 14.36 0.09 407.3 90.42 30582 +1985 342 15.19 9.19 13.54 0.08 388.37 90.58 30521 +1985 343 12.02 6.02 10.37 0 322.08 123.18 30465 +1985 344 10.72 4.72 9.07 0 297.85 123.21 30413 +1985 345 9.87 3.87 8.22 0.06 282.86 92.62 30366 +1985 346 11.8 5.8 10.15 0 317.87 121.32 30323 +1985 347 7.36 1.36 5.71 0.01 242.31 93.16 30284 +1985 348 7.67 1.67 6.02 0.19 247.03 92.74 30251 +1985 349 7.14 1.14 5.49 0 239.01 123.64 30221 +1985 350 7.72 1.72 6.07 0.2 247.8 92.19 30197 +1985 351 2.2 -3.8 0.55 0 174.37 125.9 30177 +1985 352 0.03 -5.97 -1.62 0 151.15 126.78 30162 +1985 353 -1.51 -7.51 -3.16 0 136.33 127.32 30151 +1985 354 -4.42 -10.42 -6.07 1.71 111.74 145.44 30145 +1985 355 -2.98 -8.98 -4.63 0.5 123.38 146.68 30144 +1985 356 -2.2 -8.2 -3.85 0 130.11 178.38 30147 +1985 357 1.31 -4.69 -0.34 0 164.5 176.84 30156 +1985 358 1.85 -4.15 0.2 0 170.43 176.41 30169 +1985 359 1.84 -4.16 0.19 0 170.32 176.26 30186 +1985 360 3.93 -2.07 2.28 0.43 195.04 143.64 30208 +1985 361 4.51 -1.49 2.86 0.89 202.42 143 30235 +1985 362 5.69 -0.31 4.04 0 218.19 173.31 30267 +1985 363 7.16 1.16 5.51 0 239.31 171.94 30303 +1985 364 9.51 3.51 7.86 0 276.71 169.3 30343 +1985 365 9.58 3.58 7.93 0 277.89 168.47 30388 +1986 1 6.43 0.43 4.78 0 228.61 170.67 30438 +1986 2 5.06 -0.94 3.41 0 209.65 128.78 30492 +1986 3 6.07 0.07 4.42 0.06 223.49 96.82 30551 +1986 4 5.07 -0.93 3.42 0.05 209.78 97.97 30614 +1986 5 2.44 -3.56 0.79 0.26 177.12 99.54 30681 +1986 6 0.77 -5.23 -0.88 0 158.75 134.41 30752 +1986 7 -0.29 -6.29 -1.94 0 147.96 135.68 30828 +1986 8 1.47 -4.53 -0.18 0.71 166.24 102.29 30907 +1986 9 -0.65 -6.65 -2.3 0 144.44 138.6 30991 +1986 10 0.19 -5.81 -1.46 0 152.76 139.55 31079 +1986 11 1.24 -4.76 -0.41 0 163.74 140.06 31171 +1986 12 0.75 -5.25 -0.9 0.07 158.54 105.98 31266 +1986 13 0.79 -5.21 -0.86 0 158.96 142.92 31366 +1986 14 0.62 -5.38 -1.03 0 157.18 144.49 31469 +1986 15 4.67 -1.33 3.02 0 204.5 143.74 31575 +1986 16 4.3 -1.7 2.65 0.07 199.72 108.94 31686 +1986 17 0.1 -5.9 -1.55 0 151.85 149.18 31800 +1986 18 1.3 -4.7 -0.35 0.18 164.39 112.88 31917 +1986 19 2.1 -3.9 0.45 0 173.24 152.03 32038 +1986 20 1.85 -4.15 0.2 0 170.43 153.76 32161 +1986 21 0.68 -5.32 -0.97 0.46 157.8 117.29 32289 +1986 22 0.93 -5.07 -0.72 0 160.43 158.02 32419 +1986 23 2.79 -3.21 1.14 0.08 181.2 119.09 32552 +1986 24 4.49 -1.51 2.84 0 202.16 159.8 32688 +1986 25 2.77 -3.23 1.12 0.25 180.96 122.07 32827 +1986 26 3.64 -2.36 1.99 0 191.43 164.16 32969 +1986 27 9.7 3.7 8.05 0 279.94 161.45 33114 +1986 28 9.81 3.81 8.16 0 281.82 163.52 33261 +1986 29 9.63 3.63 7.98 0.32 278.74 124.52 33411 +1986 30 9.16 3.16 7.51 0.15 270.84 126.51 33564 +1986 31 8.71 2.71 7.06 1.17 263.45 128.57 33718 +1986 32 -1.77 -7.77 -3.42 0.89 133.96 176.89 33875 +1986 33 2.35 -3.65 0.7 0.34 176.09 176.75 34035 +1986 34 -2.47 -8.47 -4.12 1.12 127.74 183.29 34196 +1986 35 -3.19 -9.19 -4.84 0.25 121.62 185.65 34360 +1986 36 -2.69 -8.69 -4.34 1.04 125.84 190.08 34526 +1986 37 -4.82 -10.82 -6.47 0 108.68 240.86 34694 +1986 38 -2.75 -8.75 -4.4 0.06 125.33 193.74 34863 +1986 39 -4.69 -10.69 -6.34 0 109.66 245.96 35035 +1986 40 -4.3 -10.3 -5.95 0 112.67 248.23 35208 +1986 41 0.32 -5.68 -1.33 0 154.09 248.34 35383 +1986 42 0.15 -5.85 -1.5 0 152.36 250.77 35560 +1986 43 3.51 -2.49 1.86 0 189.84 250.68 35738 +1986 44 2.41 -3.59 0.76 0.01 176.78 201.35 35918 +1986 45 1.47 -4.53 -0.18 0 166.24 256.43 36099 +1986 46 1.74 -4.26 0.09 0.41 169.21 204.89 36282 +1986 47 -0.14 -6.14 -1.79 0.01 149.44 207.72 36466 +1986 48 -0.74 -6.74 -2.39 0.05 143.57 210.03 36652 +1986 49 -1.92 -7.92 -3.57 0 132.6 268.74 36838 +1986 50 -0.7 -6.7 -2.35 0 143.96 270.54 37026 +1986 51 -0.57 -6.57 -2.22 0.16 145.22 216.1 37215 +1986 52 -1.1 -7.1 -2.75 0 140.15 276.62 37405 +1986 53 -0.86 -6.86 -2.51 0.11 142.42 220.47 37596 +1986 54 -1.72 -7.72 -3.37 0 134.41 282.63 37788 +1986 55 -0.99 -6.99 -2.64 0.18 141.19 224.93 37981 +1986 56 -0.88 -6.88 -2.53 0 142.23 287.93 38175 +1986 57 -4.88 -10.88 -6.53 0 108.22 292.8 38370 +1986 58 -1.02 -7.02 -2.67 0 140.9 293.49 38565 +1986 59 -2.38 -8.38 -4.03 0 128.53 296.84 38761 +1986 60 7.49 1.49 5.84 0 244.28 290.78 38958 +1986 61 8.95 2.95 7.3 0.03 267.37 228.22 39156 +1986 62 9.21 3.21 7.56 0 271.67 292.17 39355 +1986 63 7.49 1.49 5.84 0 244.28 296.25 39553 +1986 64 7.95 1.95 6.3 0 251.36 297.62 39753 +1986 65 7.69 1.69 6.04 0 247.34 299.84 39953 +1986 66 7.49 1.49 5.84 0.05 244.28 235.22 40154 +1986 67 3.21 -2.79 1.56 0.44 186.2 240.17 40355 +1986 68 2.58 -3.42 0.93 1.01 178.74 242.33 40556 +1986 69 4.03 -1.97 2.38 0.83 196.29 242.77 40758 +1986 70 2.98 -3.02 1.33 0 183.44 315.81 40960 +1986 71 3.78 -2.22 2.13 0 193.17 317.49 41163 +1986 72 3.12 -2.88 1.47 0 185.11 320.49 41366 +1986 73 3.59 -2.41 1.94 0 190.82 322.25 41569 +1986 74 3.27 -2.73 1.62 0 186.92 293.52 41772 +1986 75 7.79 1.79 6.14 0.02 248.88 218.5 41976 +1986 76 9.3 3.3 7.65 0.02 273.17 218.97 42179 +1986 77 4.5 -1.5 2.85 0.14 202.29 225.28 42383 +1986 78 2.5 -3.5 0.85 0.12 177.82 228.76 42587 +1986 79 0.45 -5.55 -1.2 0 155.42 309.55 42791 +1986 80 5.61 -0.39 3.96 0 217.09 307.18 42996 +1986 81 6.65 0.65 5 0 231.79 308.55 43200 +1986 82 10.29 4.29 8.64 0 290.18 306.2 43404 +1986 83 7.69 1.69 6.04 0 247.34 312.41 43608 +1986 84 12.8 6.8 11.15 0 337.42 306.96 43812 +1986 85 10.5 4.5 8.85 0 293.9 313.35 44016 +1986 86 9.06 3.06 7.41 0 269.18 317.96 44220 +1986 87 7.63 1.63 5.98 0 246.42 322.51 44424 +1986 88 4.14 -1.86 2.49 0 197.68 329.11 44627 +1986 89 4.86 -1.14 3.21 0.03 206.99 247.97 44831 +1986 90 7.96 1.96 6.31 0 251.52 329.1 45034 +1986 91 14.46 8.46 12.81 0.25 372.15 240.09 45237 +1986 92 13.39 7.39 11.74 0.37 349.43 243.37 45439 +1986 93 13.93 7.93 12.28 0.18 360.75 244.19 45642 +1986 94 14.56 8.56 12.91 0 374.34 326.39 45843 +1986 95 15.48 9.48 13.83 0 394.97 326.46 46045 +1986 96 15.93 9.93 14.28 0 405.42 327.49 46246 +1986 97 16.84 10.84 15.19 0 427.25 327.29 46446 +1986 98 17.17 11.17 15.52 0 435.41 328.37 46647 +1986 99 13.9 7.9 12.25 0.27 360.11 253.45 46846 +1986 100 13.5 7.5 11.85 0 351.71 340.69 47045 +1986 101 16.01 10.01 14.36 0 407.3 336.99 47243 +1986 102 16.62 10.62 14.97 0 421.88 337.35 47441 +1986 103 17.32 11.32 15.67 0 439.17 337.35 47638 +1986 104 15.37 9.37 13.72 0 392.46 343.98 47834 +1986 105 13.87 7.87 12.22 0.02 359.47 261.84 48030 +1986 106 9.97 3.97 8.32 0.1 284.59 268.7 48225 +1986 107 9.95 3.95 8.3 0.32 284.24 270 48419 +1986 108 9.07 3.07 7.42 0 269.35 363.22 48612 +1986 109 7.94 1.94 6.29 0 251.21 366.63 48804 +1986 110 9.43 3.43 7.78 0 275.36 365.69 48995 +1986 111 14.97 8.97 13.32 0 383.42 356.19 49185 +1986 112 15.49 9.49 13.84 0 395.2 356.45 49374 +1986 113 17.91 11.91 16.26 0.04 454.2 263.58 49561 +1986 114 18.69 12.69 17.04 0.06 474.75 262.98 49748 +1986 115 15.6 9.6 13.95 0.73 397.74 270.3 49933 +1986 116 13.28 7.28 11.63 0.19 347.17 275.23 50117 +1986 117 14.9 8.9 13.25 0 381.86 364.61 50300 +1986 118 17.12 11.12 15.47 0.03 434.17 270.19 50481 +1986 119 17.7 11.7 16.05 0 448.8 359.81 50661 +1986 120 18.47 12.47 16.82 0 468.88 358.73 50840 +1986 121 25.7 19.7 24.05 0.33 697.66 250.01 51016 +1986 122 18.73 12.73 17.08 0.08 475.82 270.17 51191 +1986 123 16.93 10.93 15.28 0.3 429.47 274.8 51365 +1986 124 15.83 9.83 14.18 0 403.08 370.37 51536 +1986 125 20.03 14.03 18.38 0 511.9 359.15 51706 +1986 126 19.18 13.18 17.53 0 488.06 362.84 51874 +1986 127 15.39 9.39 13.74 0.16 392.91 280.76 52039 +1986 128 18.61 12.61 16.96 0 472.61 366.44 52203 +1986 129 18.34 12.34 16.69 0.02 465.43 276.06 52365 +1986 130 18.47 12.47 16.82 0.1 468.88 276.36 52524 +1986 131 22.39 16.39 20.74 0.06 583.34 266.98 52681 +1986 132 23.9 17.9 22.25 0 633.35 350.8 52836 +1986 133 27.04 21.04 25.39 0 749.06 337.35 52989 +1986 134 28.1 22.1 26.45 0.08 791.95 249.49 53138 +1986 135 26.47 20.47 24.82 0.06 726.82 256.05 53286 +1986 136 25.64 19.64 23.99 0.04 695.43 259.39 53430 +1986 137 22.97 16.97 21.32 0.59 602.13 268.37 53572 +1986 138 20.77 14.77 19.12 0 533.45 366.57 53711 +1986 139 20.13 14.13 18.48 0 514.76 369.43 53848 +1986 140 22.45 16.45 20.8 0.78 585.26 271.17 53981 +1986 141 21.77 15.77 20.12 0 563.79 364.54 54111 +1986 142 21.37 15.37 19.72 0.01 551.49 274.87 54238 +1986 143 24.03 18.03 22.38 0.58 637.82 267.47 54362 +1986 144 19.16 13.16 17.51 1.01 487.51 281.25 54483 +1986 145 17.44 11.44 15.79 0.72 442.19 285.53 54600 +1986 146 17.75 11.75 16.1 0.29 450.08 285.13 54714 +1986 147 18.72 12.72 17.07 0.88 475.56 283.28 54824 +1986 148 18.71 12.71 17.06 0.09 475.29 283.59 54931 +1986 149 17.65 11.65 16 0.4 447.52 286.24 55034 +1986 150 17.15 11.15 15.5 0.28 434.92 287.57 55134 +1986 151 12.41 6.41 10.76 0.01 329.68 296.73 55229 +1986 152 16.26 10.26 14.61 0 413.22 386.42 55321 +1986 153 20.76 14.76 19.11 0 533.15 372.69 55409 +1986 154 21.32 15.32 19.67 0.02 549.96 278.25 55492 +1986 155 21.1 15.1 19.45 0 543.31 371.98 55572 +1986 156 22.33 16.33 20.68 0 581.42 367.72 55648 +1986 157 22.58 16.58 20.93 0 589.44 366.91 55719 +1986 158 21.37 15.37 19.72 0.04 551.49 278.74 55786 +1986 159 23.1 17.1 21.45 0.01 606.42 273.94 55849 +1986 160 23.49 17.49 21.84 0.97 619.42 272.88 55908 +1986 161 23.46 17.46 21.81 1.33 618.41 273.02 55962 +1986 162 27.17 21.17 25.52 0.21 754.21 260.38 56011 +1986 163 25.51 19.51 23.86 0.48 690.62 266.53 56056 +1986 164 25.45 19.45 23.8 0.03 688.41 266.77 56097 +1986 165 24.92 18.92 23.27 0.64 669.14 268.63 56133 +1986 166 20.94 14.94 19.29 2.03 538.51 280.64 56165 +1986 167 21.02 15.02 19.37 0.47 540.9 280.38 56192 +1986 168 21.01 15.01 19.36 0.26 540.6 280.47 56214 +1986 169 18.32 12.32 16.67 1.25 464.91 287.19 56231 +1986 170 18.66 12.66 17.01 0 473.94 381.86 56244 +1986 171 18.33 12.33 16.68 0 465.17 382.94 56252 +1986 172 19.46 13.46 17.81 0 495.8 379.34 56256 +1986 173 19.94 13.94 18.29 0 509.33 377.72 56255 +1986 174 22.55 16.55 20.9 0 588.47 368.14 56249 +1986 175 19.46 13.46 17.81 0.1 495.8 284.41 56238 +1986 176 17.34 11.34 15.69 1.81 439.67 289.3 56223 +1986 177 14.93 8.93 13.28 0.49 382.52 294.11 56203 +1986 178 13.73 7.73 12.08 0 356.52 395.09 56179 +1986 179 18 12 16.35 0 456.53 383.59 56150 +1986 180 17.47 11.47 15.82 0.29 442.95 288.78 56116 +1986 181 17.68 11.68 16.03 0 448.29 384.35 56078 +1986 182 18.87 12.87 17.22 0.27 479.6 285.42 56035 +1986 183 19 13 17.35 0 483.13 379.96 55987 +1986 184 18.86 12.86 17.21 0.03 479.33 285.19 55935 +1986 185 19.58 13.58 17.93 0 499.16 377.84 55879 +1986 186 25.4 19.4 23.75 0 686.58 354.87 55818 +1986 187 20.67 14.67 19.02 0 530.49 373.69 55753 +1986 188 23.45 17.45 21.8 0 618.08 362.87 55684 +1986 189 18.05 12.05 16.4 0 457.83 381.77 55611 +1986 190 20.86 14.86 19.21 0.7 536.12 279.15 55533 +1986 191 24.77 18.77 23.12 1.81 663.78 267.35 55451 +1986 192 22.01 16.01 20.36 0 571.29 367.43 55366 +1986 193 25.68 19.68 24.03 0 696.92 351.81 55276 +1986 194 25.92 19.92 24.27 0 705.89 350.49 55182 +1986 195 24.59 18.59 22.94 0.22 657.38 267.17 55085 +1986 196 24.66 18.66 23.01 0.99 659.86 266.64 54984 +1986 197 25.72 19.72 24.07 0.23 698.41 262.75 54879 +1986 198 21.64 15.64 19.99 0.33 559.77 275.08 54770 +1986 199 19.41 13.41 17.76 0 494.41 374.13 54658 +1986 200 23.85 17.85 22.2 0.04 631.63 268.04 54542 +1986 201 24.98 18.98 23.33 0.05 671.3 264.07 54423 +1986 202 24.73 18.73 23.08 0 662.35 352.64 54301 +1986 203 26.28 20.28 24.63 0.76 719.53 258.84 54176 +1986 204 24.32 18.32 22.67 0.07 647.88 265.07 54047 +1986 205 23.59 17.59 21.94 0 622.79 355.96 53915 +1986 206 27.49 21.49 25.84 0.01 767.02 253.29 53780 +1986 207 20.59 14.59 18.94 0.42 528.14 274.5 53643 +1986 208 22.5 16.5 20.85 0.29 586.86 268.82 53502 +1986 209 18.38 12.38 16.73 0.76 466.49 278.86 53359 +1986 210 14.77 8.77 13.12 0.41 378.97 285.75 53213 +1986 211 17.53 11.53 15.88 0 444.47 372.89 53064 +1986 212 21.27 15.27 19.62 0.11 548.44 270.1 52913 +1986 213 27.41 21.41 25.76 0.09 763.8 250.12 52760 +1986 214 26.73 20.73 25.08 0.64 736.89 252.07 52604 +1986 215 27.38 21.38 25.73 0 762.6 332.31 52445 +1986 216 27.23 21.23 25.58 1.04 756.6 249.06 52285 +1986 217 28.23 22.23 26.58 0 797.35 326.24 52122 +1986 218 31.16 25.16 29.51 0 927.56 309.2 51958 +1986 219 26.45 20.45 24.8 0.01 726.05 249.91 51791 +1986 220 29.01 23.01 27.36 0 830.4 319.56 51622 +1986 221 26.47 20.47 24.82 0.22 726.82 248.46 51451 +1986 222 29.08 23.08 27.43 0.92 833.43 237.98 51279 +1986 223 23.9 17.9 22.25 0.51 633.35 255.23 51105 +1986 224 24.93 18.93 23.28 0 669.5 335.03 50929 +1986 225 25.45 19.45 23.8 1.21 688.41 248.77 50751 +1986 226 27.49 21.49 25.84 0.5 767.02 240.93 50572 +1986 227 21.06 15.06 19.41 0.1 542.1 259.71 50392 +1986 228 21.31 15.31 19.66 0.78 549.66 258.17 50210 +1986 229 21.25 15.25 19.6 0.87 547.84 257.4 50026 +1986 230 19.79 13.79 18.14 1.01 505.07 260.04 49842 +1986 231 16.72 10.72 15.07 0.67 424.32 265.53 49656 +1986 232 18.27 12.27 16.62 1.84 463.59 261.33 49469 +1986 233 21.78 15.78 20.13 1.8 564.11 251.96 49280 +1986 234 24.05 18.05 22.4 0.12 638.51 244.62 49091 +1986 235 22.19 16.19 20.54 0.4 576.97 248.74 48900 +1986 236 22.37 16.37 20.72 0.55 582.7 247.22 48709 +1986 237 25.9 19.9 24.25 0.42 705.14 235.65 48516 +1986 238 22.57 16.57 20.92 0 589.12 325.67 48323 +1986 239 22.17 16.17 20.52 0 576.34 325.61 48128 +1986 240 20.26 14.26 18.61 0 518.51 330.17 47933 +1986 241 19.76 13.76 18.11 0.02 504.22 247.49 47737 +1986 242 15.21 9.21 13.56 0.7 388.82 255.2 47541 +1986 243 15.38 9.38 13.73 0.05 392.69 253.48 47343 +1986 244 9.15 3.15 7.5 0.02 270.67 261.07 47145 +1986 245 10.93 4.93 9.28 0 301.65 343.21 46947 +1986 246 14.19 8.19 12.54 0.19 366.3 251.16 46747 +1986 247 11.74 5.74 10.09 0 316.72 337.81 46547 +1986 248 11.26 5.26 9.61 0 307.72 336.66 46347 +1986 249 17.77 11.77 16.12 0 450.6 320.51 46146 +1986 250 13.36 7.36 11.71 0 348.81 328.59 45945 +1986 251 13 7 11.35 0 341.45 327.13 45743 +1986 252 16.75 10.75 15.1 0 425.05 316.82 45541 +1986 253 18.53 12.53 16.88 0 470.47 310.2 45339 +1986 254 19.38 13.38 17.73 0.89 493.58 229.33 45136 +1986 255 14.58 8.58 12.93 0 374.78 315.12 44933 +1986 256 19.39 13.39 17.74 0 493.86 301.29 44730 +1986 257 21.68 15.68 20.03 0.42 561.01 219.36 44527 +1986 258 17.38 11.38 15.73 0 440.68 302.01 44323 +1986 259 19.18 13.18 17.53 0 488.06 295.02 44119 +1986 260 19.87 13.87 18.22 0 507.33 290.81 43915 +1986 261 21.73 15.73 20.08 0 562.55 283.03 43711 +1986 262 21.35 15.35 19.7 0 550.88 281.88 43507 +1986 263 24.54 18.54 22.89 0 655.61 269.22 43303 +1986 264 23.45 17.45 21.8 0 618.08 270.49 43099 +1986 265 22.36 16.36 20.71 0.05 582.38 203.78 42894 +1986 266 22.67 16.67 21.02 0.23 592.35 201.29 42690 +1986 267 23.27 17.27 21.62 0.46 612.06 197.96 42486 +1986 268 23.22 17.22 21.57 0.47 610.39 196.26 42282 +1986 269 24.33 18.33 22.68 0.86 648.23 191.77 42078 +1986 270 20.82 14.82 19.17 0 534.93 263.81 41875 +1986 271 22.32 16.32 20.67 0 581.1 257.04 41671 +1986 272 22.36 16.36 20.71 0 582.38 254.33 41468 +1986 273 21.91 15.91 20.26 0 568.16 253.22 41265 +1986 274 14.67 8.67 13.02 0.01 376.76 200.53 41062 +1986 275 14.13 8.13 12.48 0 365.02 265.6 40860 +1986 276 11.71 5.71 10.06 0 316.16 266.88 40658 +1986 277 12.39 6.39 10.74 0 329.28 263.13 40456 +1986 278 14.05 8.05 12.4 0.14 363.3 193.13 40255 +1986 279 13.2 7.2 11.55 0.16 345.53 192.09 40054 +1986 280 9.72 3.72 8.07 0.26 280.28 193.91 39854 +1986 281 10.01 4.01 8.36 0 285.28 255.41 39654 +1986 282 9.31 3.31 7.66 0 273.34 253.53 39455 +1986 283 11.75 5.75 10.1 0 316.91 247.38 39256 +1986 284 16.4 10.4 14.75 0 416.57 236.64 39058 +1986 285 14.71 8.71 13.06 0.69 377.64 177.8 38861 +1986 286 13.48 7.48 11.83 0 351.3 236.34 38664 +1986 287 16.11 10.11 14.46 0 409.66 228.99 38468 +1986 288 16.98 10.98 15.33 2.42 430.7 168.48 38273 +1986 289 18.78 12.78 17.13 1.56 477.17 163.88 38079 +1986 290 15.12 9.12 13.47 0 386.79 222.57 37885 +1986 291 12.75 6.75 11.1 0.21 336.42 167.68 37693 +1986 292 11.96 5.96 10.31 0 320.93 221.99 37501 +1986 293 12.5 6.5 10.85 0.09 331.45 163.89 37311 +1986 294 10.13 4.13 8.48 0.07 287.37 164.02 37121 +1986 295 12.27 6.27 10.62 0 326.93 213.14 36933 +1986 296 12.59 6.59 10.94 0 333.23 210.13 36745 +1986 297 12.41 6.41 10.76 0.32 329.68 155.75 36560 +1986 298 12.09 6.09 10.44 0.1 323.43 154.12 36375 +1986 299 19.87 13.87 18.22 0 507.33 190.01 36191 +1986 300 19.39 13.39 17.74 0.28 493.86 141.32 36009 +1986 301 19 13 17.35 0.2 483.13 140.09 35829 +1986 302 17.03 11.03 15.38 0.09 431.94 140.84 35650 +1986 303 11.32 5.32 9.67 0 308.83 193.35 35472 +1986 304 14 8 12.35 0 362.24 187.5 35296 +1986 305 11.66 5.66 10.01 0.31 315.21 140.83 35122 +1986 306 10.3 4.3 8.65 0 290.36 187.08 34950 +1986 307 9.11 3.11 7.46 0 270.01 185.8 34779 +1986 308 6.94 0.94 5.29 0 236.04 185.19 34610 +1986 309 5.95 -0.05 4.3 0 221.81 183.68 34444 +1986 310 6.02 0.02 4.37 0 222.79 181.16 34279 +1986 311 8.63 2.63 6.98 0 262.15 176.72 34116 +1986 312 11.31 5.31 9.66 0 308.64 171.4 33956 +1986 313 7.25 1.25 5.6 0.1 240.65 129.88 33797 +1986 314 11.08 5.08 9.43 0 304.4 167.63 33641 +1986 315 9.09 3.09 7.44 0 269.68 167.07 33488 +1986 316 7.85 1.85 6.2 0 249.81 165.99 33337 +1986 317 5.05 -0.95 3.4 0.03 209.51 124.46 33188 +1986 318 4.18 -1.82 2.53 0.18 198.19 123.14 33042 +1986 319 4.59 -1.41 2.94 0 203.46 162.2 32899 +1986 320 8.29 2.29 6.64 0 256.71 157.54 32758 +1986 321 5.31 -0.69 3.66 1.1 213 118.28 32620 +1986 322 2.76 -3.24 1.11 0.16 180.85 118.11 32486 +1986 323 3.14 -2.86 1.49 0 185.35 155.62 32354 +1986 324 3.1 -2.9 1.45 0.13 184.88 115.18 32225 +1986 325 6.61 0.61 4.96 0.11 231.21 112.17 32100 +1986 326 8.03 2.03 6.38 0.41 252.61 110.27 31977 +1986 327 8.01 2.01 6.36 0 252.3 145.21 31858 +1986 328 9.35 3.35 7.7 0 274.01 142.17 31743 +1986 329 9.71 3.71 8.06 0 280.11 140.38 31631 +1986 330 12.33 6.33 10.68 0 328.11 136.53 31522 +1986 331 14.17 8.17 12.52 0 365.87 133.32 31417 +1986 332 13.49 7.49 11.84 0 351.51 132.46 31316 +1986 333 15.2 9.2 13.55 0 388.59 129.52 31218 +1986 334 12.86 6.86 11.21 0 338.63 131 31125 +1986 335 6.5 0.5 4.85 0 229.62 135.14 31035 +1986 336 6.18 0.18 4.53 0 225.05 134.28 30949 +1986 337 4.25 -1.75 2.6 0 199.08 133.81 30867 +1986 338 5.26 -0.74 3.61 0 212.33 132.27 30790 +1986 339 8.06 2.06 6.41 0 253.08 129.61 30716 +1986 340 9.13 3.13 7.48 0.03 270.34 96.06 30647 +1986 341 6.39 0.39 4.74 0 228.04 129.12 30582 +1986 342 10.93 4.93 9.28 0 301.65 124.96 30521 +1986 343 9.64 3.64 7.99 0 278.91 125.21 30465 +1986 344 9.61 3.61 7.96 0.93 278.4 93.09 30413 +1986 345 5.29 -0.71 3.64 0.85 212.73 95 30366 +1986 346 1.75 -4.25 0.1 0.34 169.32 96 30323 +1986 347 -0.93 -6.93 -2.58 0 141.76 128.56 30284 +1986 348 0.7 -5.3 -0.95 0.61 158.01 95.65 30251 +1986 349 -4.89 -10.89 -6.54 0 108.15 129.17 30221 +1986 350 -3.65 -9.65 -5.3 0.21 117.84 140.72 30197 +1986 351 -7.27 -13.27 -8.92 0.12 91.48 141.73 30177 +1986 352 -7.57 -13.57 -9.22 0.21 89.54 142.41 30162 +1986 353 -0.93 -6.93 -2.58 0 141.76 172.6 30151 +1986 354 0.78 -5.22 -0.87 0 158.85 171.76 30145 +1986 355 1.36 -4.64 -0.29 0 165.04 171.32 30144 +1986 356 -4.46 -10.46 -6.11 0 111.43 173.53 30147 +1986 357 -5.09 -11.09 -6.74 0 106.65 173.76 30156 +1986 358 -2.04 -8.04 -3.69 0 131.53 172.84 30169 +1986 359 1.45 -4.55 -0.2 0 166.02 171.32 30186 +1986 360 3.06 -2.94 1.41 0.36 184.4 138.98 30208 +1986 361 5.1 -0.9 3.45 0 210.18 168.96 30235 +1986 362 0.44 -5.56 -1.21 0 155.32 171.65 30267 +1986 363 4.9 -1.1 3.25 0 207.52 126.29 30303 +1986 364 5.14 -0.86 3.49 0.06 210.72 94.91 30343 +1986 365 1.44 -4.56 -0.21 0 165.91 129.06 30388 +1987 1 2.17 -3.83 0.52 0 174.03 129.6 30438 +1987 2 1.34 -4.66 -0.31 0 164.82 130.74 30492 +1987 3 -1.97 -7.97 -3.62 0 132.16 133.07 30551 +1987 4 -0.6 -6.6 -2.25 0 144.92 133.45 30614 +1987 5 0.61 -5.39 -1.04 0.03 157.08 100.19 30681 +1987 6 1.67 -4.33 0.02 0.18 168.43 100.49 30752 +1987 7 -0.23 -6.23 -1.88 0 148.55 135.66 30828 +1987 8 -1.37 -7.37 -3.02 0 137.62 137.63 30907 +1987 9 0.27 -5.73 -1.38 0.11 153.58 103.65 30991 +1987 10 -2.23 -8.23 -3.88 0.51 129.85 149.46 31079 +1987 11 0.39 -5.61 -1.26 0 154.8 184.32 31171 +1987 12 4.45 -1.55 2.8 0 201.65 182.5 31266 +1987 13 -0.38 -6.38 -2.03 0.42 147.07 151.9 31366 +1987 14 -5.41 -11.41 -7.06 0.09 104.3 154.55 31469 +1987 15 -3.56 -9.56 -5.21 1.67 118.57 160.12 31575 +1987 16 -2.38 -8.38 -4.03 0 128.53 197.73 31686 +1987 17 -2.75 -8.75 -4.4 0 125.33 199.4 31800 +1987 18 -1.23 -7.23 -2.88 0 138.93 200.53 31917 +1987 19 -3.82 -9.82 -5.47 0.06 116.47 164.83 32038 +1987 20 -4.03 -10.03 -5.68 0.6 114.79 167.7 32161 +1987 21 -3.69 -9.69 -5.34 0.13 117.51 169.32 32289 +1987 22 -2.76 -8.76 -4.41 0.59 125.24 171.93 32419 +1987 23 0.66 -5.34 -0.99 0.21 157.6 171.83 32552 +1987 24 -0.38 -6.38 -2.03 0.97 147.07 176.41 32688 +1987 25 -1.94 -7.94 -3.59 0.32 132.42 179.07 32827 +1987 26 -2.06 -8.06 -3.71 0.41 131.35 181.53 32969 +1987 27 -2.5 -8.5 -4.15 0.11 127.48 183.28 33114 +1987 28 0.74 -5.26 -0.91 0.4 158.43 183.47 33261 +1987 29 -0.84 -6.84 -2.49 0.48 142.61 187 33411 +1987 30 -0.6 -6.6 -2.25 0 144.92 232.21 33564 +1987 31 1.12 -4.88 -0.53 0 162.45 233.31 33718 +1987 32 6.01 0.01 4.36 0 222.65 231.2 33875 +1987 33 7.44 1.44 5.79 0.22 243.52 187.19 34035 +1987 34 6.53 0.53 4.88 0 230.05 233.43 34196 +1987 35 4.49 -1.51 2.84 0.12 202.16 190.38 34360 +1987 36 7.29 1.29 5.64 0.42 241.26 189.48 34526 +1987 37 5.67 -0.33 4.02 0 217.92 238.38 34694 +1987 38 6.28 0.28 4.63 0.19 226.47 192.1 34863 +1987 39 5.76 -0.24 4.11 0 219.16 241.76 35035 +1987 40 7.76 1.76 6.11 0 248.42 241.48 35208 +1987 41 5.74 -0.26 4.09 0.15 218.88 195.37 35383 +1987 42 1.44 -4.56 -0.21 1.35 165.91 199.24 35560 +1987 43 6.59 0.59 4.94 0.05 230.92 197.38 35738 +1987 44 4.03 -1.97 2.38 0 196.29 252.12 35918 +1987 45 3.55 -2.45 1.9 0.04 190.33 201.84 36099 +1987 46 1.71 -4.29 0.06 0.62 168.88 204.43 36282 +1987 47 2.33 -3.67 0.68 0 175.86 260.03 36466 +1987 48 1.63 -4.37 -0.02 0 167.99 262.94 36652 +1987 49 1.37 -4.63 -0.28 0.19 165.15 209.72 36838 +1987 50 0.1 -5.9 -1.55 0.85 151.85 212.13 37026 +1987 51 0.97 -5.03 -0.68 0.26 160.86 213.65 37215 +1987 52 1.59 -4.41 -0.06 0 167.55 273.02 37405 +1987 53 3.09 -2.91 1.44 0 184.76 274.35 37596 +1987 54 2.94 -3.06 1.29 0.49 182.97 217.6 37788 +1987 55 -0.24 -6.24 -1.89 0.05 148.45 221.47 37981 +1987 56 -0.03 -6.03 -1.68 0.11 150.54 223.5 38175 +1987 57 -0.25 -6.25 -1.9 0 148.35 287.45 38370 +1987 58 3.09 -2.91 1.44 0 184.76 287.46 38565 +1987 59 6.01 0.01 4.36 0 222.65 286.72 38761 +1987 60 7.66 1.66 6.01 0.23 246.88 224.58 38958 +1987 61 8.9 2.9 7.25 0.32 266.55 224.58 39156 +1987 62 6.92 0.92 5.27 0.68 235.74 227.47 39355 +1987 63 4.91 -1.09 3.26 0.02 207.65 230.58 39553 +1987 64 7.92 1.92 6.27 0.31 250.9 229.39 39753 +1987 65 6.31 0.31 4.66 0.15 226.89 232.1 39953 +1987 66 5.36 -0.64 3.71 0.31 213.68 201.67 40154 +1987 67 8.31 2.31 6.66 0 257.03 268.51 40355 +1987 68 0.96 -5.04 -0.69 0.08 160.75 208.96 40556 +1987 69 2.14 -3.86 0.49 0.23 173.69 210.25 40758 +1987 70 2.72 -3.28 1.07 0.04 180.38 212.04 40960 +1987 71 0.83 -5.17 -0.82 0.34 159.38 215.43 41163 +1987 72 -1.2 -7.2 -2.85 0.01 139.21 250.63 41366 +1987 73 0.17 -5.83 -1.48 0 152.56 325.1 41569 +1987 74 -1.55 -7.55 -3.2 0 135.96 328.98 41772 +1987 75 2.29 -3.71 0.64 0 175.4 297.17 41976 +1987 76 0.46 -5.54 -1.19 0.13 155.52 226.04 42179 +1987 77 2.56 -3.44 0.91 0.09 178.51 226.69 42383 +1987 78 4.91 -1.09 3.26 0 207.65 302.63 42587 +1987 79 5.96 -0.04 4.31 0 221.95 304.22 42791 +1987 80 5.28 -0.72 3.63 0.11 212.6 230.66 42996 +1987 81 7.46 1.46 5.81 0.79 243.83 230.65 43200 +1987 82 4.16 -1.84 2.51 0.07 197.94 235.54 43404 +1987 83 4.95 -1.05 3.3 0 208.18 315.72 43608 +1987 84 7.36 1.36 5.71 0.01 242.31 236.54 43812 +1987 85 7.37 1.37 5.72 0 242.46 317.89 44016 +1987 86 0.19 -5.81 -1.46 0.69 152.76 245.9 44220 +1987 87 0.71 -5.29 -0.94 0.02 158.12 247.52 44424 +1987 88 1.11 -4.89 -0.54 0 162.35 332.08 44627 +1987 89 3.02 -2.98 1.37 0 183.92 332.6 44831 +1987 90 0.5 -5.5 -1.15 0 155.94 337.37 45034 +1987 91 7.81 1.81 6.16 0.04 249.19 248.68 45237 +1987 92 10.59 4.59 8.94 0 295.51 329.59 45439 +1987 93 13.14 7.14 11.49 0 344.3 327.18 45642 +1987 94 16.31 10.31 14.66 0.78 414.42 241.83 45843 +1987 95 15.38 9.38 13.73 0.13 392.69 245.02 46045 +1987 96 13.36 7.36 11.71 0.06 348.81 249.81 46246 +1987 97 11.04 5.04 9.39 0 303.66 339.48 46446 +1987 98 14.32 8.32 12.67 0 369.11 335.05 46647 +1987 99 17.89 11.89 16.24 0 453.69 328.44 46846 +1987 100 15.02 9.02 13.37 0.06 384.54 253.05 47045 +1987 101 17.61 11.61 15.96 0.07 446.5 249.71 47243 +1987 102 13.87 7.87 12.22 0 359.47 343.71 47441 +1987 103 11.96 5.96 10.31 0 320.93 349.39 47638 +1987 104 15.79 9.79 14.14 0 402.14 342.98 47834 +1987 105 16.57 10.57 14.92 0 420.67 342.81 48030 +1987 106 20.94 14.94 19.29 0 538.51 331.79 48225 +1987 107 19.13 13.13 17.48 0 486.69 339.02 48419 +1987 108 19.12 13.12 17.47 0 486.41 340.74 48612 +1987 109 14.17 8.17 12.52 0 365.87 355.09 48804 +1987 110 15.53 9.53 13.88 0.49 396.12 264.99 48995 +1987 111 13.76 7.76 12.11 0 357.15 358.94 49185 +1987 112 12.78 6.78 11.13 0 337.02 362.54 49374 +1987 113 10.66 4.66 9.01 0 296.77 368.01 49561 +1987 114 11.41 5.41 9.76 0 310.51 368.11 49748 +1987 115 14.3 8.3 12.65 0 368.68 363.49 49933 +1987 116 12.68 6.68 11.03 0 335.02 368.24 50117 +1987 117 11.74 5.74 10.09 0.01 316.72 278.6 50300 +1987 118 13.86 7.86 12.21 0.55 359.26 276.24 50481 +1987 119 8.55 2.55 6.9 0.02 260.86 284.79 50661 +1987 120 7.49 1.49 5.84 0 244.28 382.59 50840 +1987 121 11.38 5.38 9.73 0.01 309.95 282.77 51016 +1987 122 12.44 6.44 10.79 0.14 330.27 282.07 51191 +1987 123 15.17 9.17 13.52 0.14 387.92 278.22 51365 +1987 124 17.58 11.58 15.93 0.61 445.74 274.24 51536 +1987 125 18.19 12.19 16.54 1.61 461.49 273.65 51706 +1987 126 20.11 14.11 18.46 1.34 514.19 269.89 51874 +1987 127 15.65 9.65 14 0.05 398.89 280.27 52039 +1987 128 17.62 11.62 15.97 0.02 446.76 277.02 52203 +1987 129 21.2 15.2 19.55 0.19 546.32 269.09 52365 +1987 130 22.08 16.08 20.43 0.55 573.49 267.28 52524 +1987 131 21.5 15.5 19.85 0.01 555.46 269.44 52681 +1987 132 18.26 12.26 16.61 0 463.33 370.7 52836 +1987 133 15.6 9.6 13.95 0.64 397.74 284.09 52989 +1987 134 15.68 9.68 14.03 0.58 399.59 284.47 53138 +1987 135 17.39 11.39 15.74 0.78 440.93 281.5 53286 +1987 136 17.36 11.36 15.71 0.46 440.17 282.04 53430 +1987 137 14.85 8.85 13.2 0.98 380.74 287.57 53572 +1987 138 18.54 12.54 16.89 0 470.74 373.86 53711 +1987 139 17.54 11.54 15.89 0 444.72 377.53 53848 +1987 140 14.11 8.11 12.46 0.8 364.59 290.26 53981 +1987 141 13.51 7.51 11.86 0.68 351.92 291.64 54111 +1987 142 14.86 8.86 13.21 1.02 380.96 289.61 54238 +1987 143 11.61 5.61 9.96 0.07 314.26 295.52 54362 +1987 144 10.42 4.42 8.77 0 292.48 396.85 54483 +1987 145 13.96 7.96 12.31 0.06 361.38 292.37 54600 +1987 146 14.73 8.73 13.08 0 378.08 388.35 54714 +1987 147 16.31 10.31 14.66 0 414.42 384.74 54824 +1987 148 18.1 12.1 16.45 0 459.14 379.99 54931 +1987 149 17.56 11.56 15.91 0 445.23 381.91 55034 +1987 150 19.32 13.32 17.67 0 491.92 376.82 55134 +1987 151 17.69 11.69 16.04 0 448.55 382.25 55229 +1987 152 21.55 15.55 19.9 0 557 369.6 55321 +1987 153 21.88 15.88 20.23 0.09 567.22 276.46 55409 +1987 154 21.35 15.35 19.7 0 550.88 370.89 55492 +1987 155 22.14 16.14 20.49 0.09 575.39 276.09 55572 +1987 156 23.58 17.58 21.93 0.07 622.45 272.04 55648 +1987 157 20.57 14.57 18.92 0 527.55 374.34 55719 +1987 158 17.22 11.22 15.57 0.35 436.66 288.87 55786 +1987 159 18.57 12.57 16.92 0.89 471.54 286.02 55849 +1987 160 20.28 14.28 18.63 0 519.09 375.94 55908 +1987 161 17.22 11.22 15.57 0.02 436.66 289.24 55962 +1987 162 19.37 13.37 17.72 0 493.3 379.12 56011 +1987 163 23.89 17.89 22.24 1.27 633 271.88 56056 +1987 164 26.18 20.18 24.53 1.47 715.72 264.2 56097 +1987 165 24.27 18.27 22.62 0.3 646.14 270.77 56133 +1987 166 25.2 19.2 23.55 1.08 679.27 267.75 56165 +1987 167 23.3 17.3 21.65 0 613.06 365.11 56192 +1987 168 27.71 21.71 26.06 0 775.93 344.84 56214 +1987 169 23.28 17.28 21.63 0 612.39 365.28 56231 +1987 170 24.23 18.23 22.58 0.1 644.75 270.98 56244 +1987 171 25.12 19.12 23.47 0.72 676.36 268.09 56252 +1987 172 23.09 17.09 21.44 0.13 606.09 274.57 56256 +1987 173 18.51 12.51 16.86 1.27 469.94 286.77 56255 +1987 174 20.43 14.43 18.78 0 523.45 375.96 56249 +1987 175 19.61 13.61 17.96 0.16 500 284.04 56238 +1987 176 18.48 12.48 16.83 0.88 469.14 286.73 56223 +1987 177 17.36 11.36 15.71 0.45 440.17 289.17 56203 +1987 178 16.27 10.27 14.62 0.4 413.46 291.5 56179 +1987 179 15.52 9.52 13.87 0.44 395.89 292.92 56150 +1987 180 17.14 11.14 15.49 0 434.67 386 56116 +1987 181 20.31 14.31 18.66 0 519.96 375.94 56078 +1987 182 21.5 15.5 19.85 0.23 555.46 278.67 56035 +1987 183 16.64 10.64 14.99 1.9 422.37 290.26 55987 +1987 184 15.47 9.47 13.82 0.59 394.74 292.5 55935 +1987 185 15.57 9.57 13.92 0.01 397.04 292.23 55879 +1987 186 18.03 12.03 16.38 0.01 457.31 286.85 55818 +1987 187 23.89 17.89 22.24 0 633 361.31 55753 +1987 188 28.28 22.28 26.63 0 799.43 340.22 55684 +1987 189 23.7 17.7 22.05 0 626.52 361.66 55611 +1987 190 21.85 15.85 20.2 0.04 566.28 276.45 55533 +1987 191 22.47 16.47 20.82 0.63 585.9 274.48 55451 +1987 192 23.98 17.98 22.33 0.41 636.09 269.68 55366 +1987 193 28.14 22.14 26.49 0 793.6 339.67 55276 +1987 194 27.94 21.94 26.29 0.06 785.34 255.38 55182 +1987 195 26.93 20.93 25.28 0.95 744.72 259.03 55085 +1987 196 24.58 18.58 22.93 0 657.03 355.87 54984 +1987 197 24.31 18.31 22.66 0.31 647.54 267.44 54879 +1987 198 25.83 19.83 24.18 0.06 702.51 262.06 54770 +1987 199 22.13 16.13 20.48 0 575.07 364.6 54658 +1987 200 19.35 13.35 17.7 0 492.75 373.92 54542 +1987 201 24.13 18.13 22.48 0.01 641.27 266.82 54423 +1987 202 24.03 18.03 22.38 0.36 637.82 266.72 54301 +1987 203 26.18 20.18 24.53 0 715.72 345.59 54176 +1987 204 19.14 13.14 17.49 0.12 486.96 279.4 54047 +1987 205 20.17 14.17 18.52 0.27 515.92 276.48 53915 +1987 206 20.91 14.91 19.26 1.01 537.61 274.16 53780 +1987 207 21.69 15.69 20.04 0.1 561.31 271.57 53643 +1987 208 25.31 19.31 23.66 0.01 683.28 260.1 53502 +1987 209 24.58 18.58 22.93 0.47 657.03 262.03 53359 +1987 210 23.36 17.36 21.71 0.32 615.06 265.36 53213 +1987 211 23.7 17.7 22.05 0 626.52 351.68 53064 +1987 212 23.66 17.66 22.01 2.6 625.16 263.3 52913 +1987 213 19.15 13.15 17.5 0.85 487.23 274.84 52760 +1987 214 21.84 15.84 20.19 0.04 565.97 267.45 52604 +1987 215 25.66 19.66 24.01 0 696.18 340.42 52445 +1987 216 25.07 19.07 23.42 0.04 674.55 256.54 52285 +1987 217 27.69 21.69 26.04 0.06 775.12 246.73 52122 +1987 218 28.86 22.86 27.21 0.01 823.96 241.64 51958 +1987 219 27.06 21.06 25.41 0 749.85 330.32 51791 +1987 220 22.44 16.44 20.79 0 584.94 349.08 51622 +1987 221 22.55 16.55 20.9 0 588.47 347.68 51451 +1987 222 20.02 14.02 18.37 0 511.61 355.47 51279 +1987 223 22.92 16.92 21.27 0 600.49 344.14 51105 +1987 224 22.42 16.42 20.77 0 584.3 344.98 50929 +1987 225 24.65 18.65 23 0.18 659.51 251.33 50751 +1987 226 24.66 18.66 23.01 0.08 659.86 250.47 50572 +1987 227 22.2 16.2 20.55 0 577.29 342.28 50392 +1987 228 24.51 18.51 22.86 0.72 654.55 249.14 50210 +1987 229 18.92 12.92 17.27 0.88 480.96 262.99 50026 +1987 230 20.54 14.54 18.89 0.48 526.67 258.24 49842 +1987 231 15.08 9.08 13.43 0.83 385.89 268.6 49656 +1987 232 13.98 7.98 12.33 0.01 361.81 269.45 49469 +1987 233 17.37 11.37 15.72 0.34 440.43 262.12 49280 +1987 234 20.9 14.9 19.25 0.2 537.31 253.14 49091 +1987 235 21.83 15.83 20.18 0.74 565.66 249.68 48900 +1987 236 22.04 16.04 20.39 0.18 572.24 248.09 48709 +1987 237 22.24 16.24 20.59 0 578.56 328.47 48516 +1987 238 20.34 14.34 18.69 0 520.83 333.16 48323 +1987 239 18.77 12.77 17.12 0 476.9 336.37 48128 +1987 240 17.01 11.01 15.36 1.21 431.44 254.54 47933 +1987 241 17.87 11.87 16.22 0.23 453.17 251.54 47737 +1987 242 17.8 11.8 16.15 0.44 451.37 250.37 47541 +1987 243 21.63 15.63 19.98 0.07 559.46 240.39 47343 +1987 244 23.16 17.16 21.51 0 608.4 313.44 47145 +1987 245 26.33 20.33 24.68 0 721.44 299.24 46947 +1987 246 27.86 21.86 26.21 0 782.06 290.62 46747 +1987 247 26.1 20.1 24.45 0 712.68 296.64 46547 +1987 248 26.7 20.7 25.05 1.47 735.72 219.21 46347 +1987 249 24.61 18.61 22.96 0.63 658.09 224.11 46146 +1987 250 18.07 12.07 16.42 0.92 458.35 238.33 45945 +1987 251 15.07 9.07 13.42 0.14 385.66 242.15 45743 +1987 252 17.28 11.28 15.63 0 438.16 315.52 45541 +1987 253 19.68 13.68 18.03 0.01 501.96 230.28 45339 +1987 254 23.21 17.21 21.56 0 610.06 293.9 45136 +1987 255 23.85 17.85 22.2 0 631.63 289.51 44933 +1987 256 20.85 14.85 19.2 0.41 535.82 222.83 44730 +1987 257 17.62 11.62 15.97 0 446.76 303.76 44527 +1987 258 20.56 14.56 18.91 0 527.26 293.56 44323 +1987 259 21.41 15.41 19.76 0 552.71 288.68 44119 +1987 260 19.37 13.37 17.72 0 493.3 292.17 43915 +1987 261 20.55 14.55 18.9 0 526.96 286.51 43711 +1987 262 20.76 14.76 19.11 0.01 533.15 212.7 43507 +1987 263 23.66 17.66 22.01 0 625.16 272.24 43303 +1987 264 23.61 17.61 21.96 0 623.47 269.96 43099 +1987 265 19.24 13.24 17.59 0.7 489.71 210.39 42894 +1987 266 23.01 17.01 21.36 0 603.45 267.32 42690 +1987 267 24.73 18.73 23.08 0 662.35 259.09 42486 +1987 268 22.99 16.99 21.34 0.01 602.79 196.8 42282 +1987 269 23.85 17.85 22.2 0 631.63 257.28 42078 +1987 270 20.55 14.55 18.9 0.73 526.96 198.41 41875 +1987 271 18.89 12.89 17.24 0.22 480.14 199.68 41671 +1987 272 18 12 16.35 0 456.53 265.66 41468 +1987 273 18.58 12.58 16.93 0 471.8 261.84 41265 +1987 274 14.44 8.44 12.79 0 371.72 267.8 41062 +1987 275 14.57 8.57 12.92 0 374.56 264.8 40860 +1987 276 14.98 8.98 13.33 0 383.64 261.35 40658 +1987 277 15.91 9.91 14.26 0 404.95 256.94 40456 +1987 278 19.32 13.32 17.67 0 491.92 246.8 40255 +1987 279 15.64 9.64 13.99 0 398.66 251.83 40054 +1987 280 14.79 8.79 13.14 0 379.41 250.77 39854 +1987 281 14.23 8.23 12.58 0 367.17 249.04 39654 +1987 282 13.74 7.74 12.09 0.45 356.73 185.35 39455 +1987 283 11.9 5.9 10.25 0.62 319.78 185.37 39256 +1987 284 13.22 7.22 11.57 0 345.94 242.14 39058 +1987 285 11.84 5.84 10.19 0.39 318.63 181.17 38861 +1987 286 13.49 7.49 11.84 0.13 351.51 177.24 38664 +1987 287 13.25 7.25 11.6 0.62 346.55 175.33 38468 +1987 288 19.83 13.83 18.18 0 506.2 218.76 38273 +1987 289 14.56 8.56 12.91 0.07 374.34 169.74 38079 +1987 290 14.14 8.14 12.49 0 365.23 224.16 37885 +1987 291 13.7 7.7 12.05 0 355.89 222.16 37693 +1987 292 15.71 9.71 14.06 0 400.28 216.28 37501 +1987 293 7.98 1.98 6.33 0 251.83 224.01 37311 +1987 294 7.2 1.2 5.55 0 239.91 221.88 37121 +1987 295 9.71 3.71 8.06 0.1 280.11 162.25 36933 +1987 296 11.76 5.76 10.11 0.2 317.1 158.42 36745 +1987 297 11.48 5.48 9.83 0.31 311.82 156.65 36560 +1987 298 14.31 8.31 12.66 0.6 368.89 151.81 36375 +1987 299 13.4 7.4 11.75 0 349.64 200.97 36191 +1987 300 16.19 10.19 14.54 0.05 411.56 145.62 36009 +1987 301 13.48 7.48 11.83 0.47 351.3 146.81 35829 +1987 302 17.54 11.54 15.89 0 444.72 186.92 35650 +1987 303 22.1 16.1 20.45 0.02 574.13 131.63 35472 +1987 304 19.78 13.78 18.13 0.56 504.78 133.51 35296 +1987 305 19.06 13.06 17.41 0.48 484.77 132.57 35122 +1987 306 17.39 11.39 15.74 0.14 440.93 133.14 34950 +1987 307 16.7 10.7 15.05 0 423.83 176.22 34779 +1987 308 14.55 8.55 12.9 0.37 374.12 132.63 34610 +1987 309 9.03 3.03 7.38 0.14 268.69 135.72 34444 +1987 310 7.28 1.28 5.63 0 241.11 180.12 34279 +1987 311 6.23 0.23 4.58 0 225.75 178.79 34116 +1987 312 6.76 0.76 5.11 0 233.39 175.71 33956 +1987 313 4.45 -1.55 2.8 0.67 201.65 131.49 33797 +1987 314 2.39 -3.61 0.74 0 176.55 174.67 33641 +1987 315 5.26 -0.74 3.61 0 212.33 170.21 33488 +1987 316 2.64 -3.36 0.99 0 179.44 169.74 33337 +1987 317 1.73 -4.27 0.08 0 169.1 168.04 33188 +1987 318 4.49 -1.51 2.84 0 202.16 163.98 33042 +1987 319 2.83 -3.17 1.18 0.75 181.67 122.48 32899 +1987 320 4.13 -1.87 2.48 0 197.56 160.61 32758 +1987 321 6.33 0.33 4.68 0 227.18 156.98 32620 +1987 322 6.39 0.39 4.74 0 228.04 155.11 32486 +1987 323 7.28 1.28 5.63 0.12 241.11 114.62 32354 +1987 324 5.78 -0.22 4.13 0 219.44 151.87 32225 +1987 325 2.8 -3.2 1.15 0.16 181.32 114.01 32100 +1987 326 5.16 -0.84 3.51 0.16 210.98 111.83 31977 +1987 327 9.26 3.26 7.61 0.1 272.5 108.15 31858 +1987 328 12.68 6.68 11.03 1.3 335.02 104.28 31743 +1987 329 12.75 6.75 11.1 2.21 336.42 103.14 31631 +1987 330 12.31 6.31 10.66 0 327.71 136.55 31522 +1987 331 9.87 3.87 8.22 0 282.86 137.52 31417 +1987 332 14.08 8.08 12.43 0.19 363.94 98.87 31316 +1987 333 10.13 4.13 8.48 1.43 287.37 100.96 31218 +1987 334 7.52 1.52 5.87 0.02 244.74 101.69 31125 +1987 335 8.7 2.7 7.05 0 263.29 133.54 31035 +1987 336 12.63 6.63 10.98 0 334.03 129.05 30949 +1987 337 12.17 6.17 10.52 0.3 324.99 95.9 30867 +1987 338 8.74 2.74 7.09 0 263.94 129.88 30790 +1987 339 14.05 8.05 12.4 0 363.3 124.32 30716 +1987 340 10.79 4.79 9.14 0 299.11 126.72 30647 +1987 341 9.42 3.42 7.77 0 275.19 126.95 30582 +1987 342 4.77 -1.23 3.12 0 205.81 129.36 30521 +1987 343 3.8 -2.2 2.15 0 193.42 129.08 30465 +1987 344 3.49 -2.51 1.84 0 189.59 128.12 30413 +1987 345 1.56 -4.44 -0.09 0.01 167.22 96.49 30366 +1987 346 3.98 -2.02 2.33 0 195.67 126.87 30323 +1987 347 1.17 -4.83 -0.48 0 162.99 127.67 30284 +1987 348 -1.75 -7.75 -3.4 0 134.14 128.52 30251 +1987 349 2.35 -3.65 0.7 0 176.09 126.38 30221 +1987 350 -1.84 -7.84 -3.49 0 133.32 127.83 30197 +1987 351 -3.37 -9.37 -5.02 0.19 120.12 140.45 30177 +1987 352 -2.39 -8.39 -4.04 0 128.44 172.07 30162 +1987 353 -2.39 -8.39 -4.04 0 128.44 172.02 30151 +1987 354 0.8 -5.2 -0.85 0.14 159.06 139.05 30145 +1987 355 -2.29 -8.29 -3.94 0 129.32 171.85 30144 +1987 356 3.1 -2.9 1.45 0 184.88 169.15 30147 +1987 357 2.97 -3.03 1.32 0.24 183.33 94.06 30156 +1987 358 5.77 -0.23 4.12 0.03 219.3 92.96 30169 +1987 359 5.13 -0.87 3.48 0 210.58 124.44 30186 +1987 360 8.57 2.57 6.92 0 261.19 122.55 30208 +1987 361 10.59 4.59 8.94 0 295.51 121.31 30235 +1987 362 10.14 4.14 8.49 0.31 287.55 91.58 30267 +1987 363 8.57 2.57 6.92 1.03 261.19 92.92 30303 +1987 364 7.2 1.2 5.55 0.76 239.91 93.93 30343 +1987 365 6.29 0.29 4.64 0.13 226.61 94.8 30388 +1988 1 12.57 6.57 10.92 0 332.83 122.36 30438 +1988 2 5.75 -0.25 4.1 0 219.02 128.36 30492 +1988 3 2.63 -3.37 0.98 0 179.33 131.06 30551 +1988 4 5.94 -0.06 4.29 0 221.67 130.09 30614 +1988 5 6.34 0.34 4.69 0 227.32 130.47 30681 +1988 6 6.02 0.02 4.37 0 222.79 131.56 30752 +1988 7 7.12 1.12 5.47 0 238.71 131.61 30828 +1988 8 10.4 4.4 8.75 0.12 292.12 97.91 30907 +1988 9 8.65 2.65 7 0.45 262.48 99.9 30991 +1988 10 7.17 1.17 5.52 0.02 239.46 101.69 31079 +1988 11 6.26 0.26 4.61 0.39 226.18 102.89 31171 +1988 12 3.68 -2.32 2.03 0 191.93 139.79 31266 +1988 13 4.14 -1.86 2.49 0.84 197.68 105.86 31366 +1988 14 2.78 -3.22 1.13 0 181.08 143.39 31469 +1988 15 0.37 -5.63 -1.28 0.19 154.6 109.55 31575 +1988 16 2.91 -3.09 1.26 0.14 182.61 109.54 31686 +1988 17 2.69 -3.31 1.04 0 180.03 147.87 31800 +1988 18 3.24 -2.76 1.59 0 186.56 149.46 31917 +1988 19 2.52 -3.48 0.87 0 178.05 151.8 32038 +1988 20 -0.6 -6.6 -2.25 0.3 144.92 158.17 32161 +1988 21 -0.04 -6.04 -1.69 0.01 150.44 159.35 32289 +1988 22 0.27 -5.73 -1.38 0 153.58 199.95 32419 +1988 23 1.55 -4.45 -0.1 0 167.11 200.72 32552 +1988 24 2.62 -3.38 0.97 0 179.21 201.7 32688 +1988 25 6.11 0.11 4.46 0 224.06 160.55 32827 +1988 26 6.94 0.94 5.29 0.02 236.04 121.37 32969 +1988 27 13.4 7.4 11.75 0 349.64 157.54 33114 +1988 28 15.9 9.9 14.25 0 404.71 156.47 33261 +1988 29 15.89 9.89 14.24 0 404.48 158.76 33411 +1988 30 16.03 10.03 14.38 0.09 407.77 120.53 33564 +1988 31 12.18 6.18 10.53 0 325.18 167.89 33718 +1988 32 10.61 4.61 8.96 0 295.87 171.65 33875 +1988 33 8.94 2.94 7.29 0 267.2 175.89 34035 +1988 34 7.96 1.96 6.31 0 251.52 178.97 34196 +1988 35 10.67 4.67 9.02 0 296.95 178.41 34360 +1988 36 10.97 4.97 9.32 0 302.38 180.55 34526 +1988 37 11.1 5.1 9.45 0.11 304.76 137.08 34694 +1988 38 8.22 2.22 6.57 0.85 255.6 141.33 34863 +1988 39 6.59 0.59 4.94 0.22 230.92 144.38 35035 +1988 40 3.7 -2.3 2.05 0 192.17 197.39 35208 +1988 41 1.6 -4.4 -0.05 0 167.66 201.45 35383 +1988 42 2.27 -3.73 0.62 0.97 175.17 152.69 35560 +1988 43 1.04 -4.96 -0.61 0 161.6 207.1 35738 +1988 44 5.44 -0.56 3.79 0.02 214.77 154.87 35918 +1988 45 7.22 1.22 5.57 0 240.2 207.52 36099 +1988 46 7.78 1.78 6.13 0.62 248.73 157.23 36282 +1988 47 6.99 0.99 5.34 0 236.78 213.21 36466 +1988 48 4.53 -1.47 2.88 0 202.68 218.18 36652 +1988 49 5.71 -0.29 4.06 0.44 218.47 164.96 36838 +1988 50 7.27 1.27 5.62 0.11 240.96 165.85 37026 +1988 51 6.1 0.1 4.45 0 223.91 225.22 37215 +1988 52 8.37 2.37 6.72 0 257.98 225.75 37405 +1988 53 4.91 -1.09 3.26 0 207.65 232.09 37596 +1988 54 3.02 -2.98 1.37 0 183.92 236.42 37788 +1988 55 1.28 -4.72 -0.37 0 164.17 240.73 37981 +1988 56 4.67 -1.33 3.02 0 204.5 240.76 38175 +1988 57 6.31 0.31 4.66 0 226.89 242.11 38370 +1988 58 7.48 1.48 5.83 0.75 244.13 182.86 38565 +1988 59 4.7 -1.3 3.05 0.59 204.89 186.97 38761 +1988 60 5.98 -0.02 4.33 0.42 222.23 188.22 38958 +1988 61 5.23 -0.77 3.58 0 211.92 254.63 39156 +1988 62 8.77 2.77 7.12 0.03 264.42 190.19 39355 +1988 63 7.1 1.1 5.45 0.03 238.41 193.88 39553 +1988 64 8.81 2.81 7.16 0 265.08 259.41 39753 +1988 65 6.09 0.09 4.44 0 223.77 265.4 39953 +1988 66 10.91 4.91 9.26 0 301.29 262.18 40154 +1988 67 8.63 2.63 6.98 0 262.15 268.11 40355 +1988 68 10.74 4.74 9.09 0.01 298.21 201.09 40556 +1988 69 9.48 3.48 7.83 0 276.2 272.47 40758 +1988 70 9.03 3.03 7.38 1.34 268.69 206.92 40960 +1988 71 7.29 1.29 5.64 0.17 241.26 210.73 41163 +1988 72 5.77 -0.23 4.12 0 219.3 285.53 41366 +1988 73 5.52 -0.48 3.87 0 215.86 288.49 41569 +1988 74 6.56 0.56 4.91 0.17 230.49 217.57 41772 +1988 75 1.73 -4.27 0.08 0.64 169.1 223.24 41976 +1988 76 3.25 -2.75 1.6 0.25 186.68 224.23 42179 +1988 77 3.71 -2.29 2.06 0.13 192.3 225.88 42383 +1988 78 2.53 -3.47 0.88 1.19 178.16 228.74 42587 +1988 79 4.74 -1.26 3.09 0.52 205.42 229.18 42791 +1988 80 5.4 -0.6 3.75 0 214.22 307.41 42996 +1988 81 5.74 -0.26 4.09 0 218.88 309.63 43200 +1988 82 6.83 0.83 5.18 0 234.42 311 43404 +1988 83 7.5 1.5 5.85 0 244.43 312.65 43608 +1988 84 8.53 2.53 6.88 0.01 260.54 235.35 43812 +1988 85 9.84 3.84 8.19 0 282.34 314.39 44016 +1988 86 10.85 4.85 9.2 0 300.2 315.18 44220 +1988 87 13.02 7.02 11.37 0.01 341.86 235.41 44424 +1988 88 13.99 7.99 12.34 0.36 362.02 235.73 44627 +1988 89 15.49 9.49 13.84 0.31 395.2 235.03 44831 +1988 90 11.47 5.47 9.82 0 311.63 323.61 45034 +1988 91 17.55 11.55 15.9 0 444.98 313.01 45237 +1988 92 16.32 10.32 14.67 0 414.65 318.17 45439 +1988 93 15.72 9.72 14.07 0.04 400.51 241.29 45642 +1988 94 17.48 11.48 15.83 0.03 443.2 239.67 45843 +1988 95 14.54 8.54 12.89 0 373.9 328.54 46045 +1988 96 13.69 7.69 12.04 0 355.68 332.41 46246 +1988 97 13.64 7.64 11.99 0 354.63 334.54 46446 +1988 98 13.48 7.48 11.83 0 351.3 336.81 46647 +1988 99 11.66 5.66 10.01 0 315.21 342.34 46846 +1988 100 14.1 8.1 12.45 0.02 364.37 254.57 47045 +1988 101 13.51 7.51 11.86 0 351.92 342.58 47243 +1988 102 15.73 9.73 14.08 0 400.75 339.52 47441 +1988 103 14.45 8.45 12.8 0.5 371.94 258.21 47638 +1988 104 13.8 7.8 12.15 1.12 357.99 260.62 47834 +1988 105 15.53 9.53 13.88 0.01 396.12 259.02 48030 +1988 106 14.53 8.53 12.88 0 373.68 349.3 48225 +1988 107 11.93 5.93 10.28 0.17 320.35 267.3 48419 +1988 108 11.83 5.83 10.18 0 318.44 358.33 48612 +1988 109 11.76 5.76 10.11 1.11 317.1 270.06 48804 +1988 110 13.76 7.76 12.11 0.02 357.15 268.05 48995 +1988 111 9.37 3.37 7.72 0.64 274.35 275.52 49185 +1988 112 11.81 5.81 10.16 0.38 318.06 273.37 49374 +1988 113 12.57 6.57 10.92 0 332.83 364.32 49561 +1988 114 12.05 6.05 10.4 0.01 322.66 275.15 49748 +1988 115 11.82 5.82 10.17 0 318.25 368.76 49933 +1988 116 12.21 6.21 10.56 0 325.76 369.21 50117 +1988 117 8.08 2.08 6.43 0.11 253.4 283.43 50300 +1988 118 7.91 1.91 6.26 0 250.74 379.52 50481 +1988 119 5.76 -0.24 4.11 0 219.16 383.87 50661 +1988 120 7.35 1.35 5.7 0 242.16 382.8 50840 +1988 121 10.58 4.58 8.93 0 295.33 378.54 51016 +1988 122 17.06 11.06 15.41 0.46 432.68 273.77 51191 +1988 123 13.25 7.25 11.6 0.11 346.55 281.56 51365 +1988 124 15.88 9.88 14.23 0 404.24 370.25 51536 +1988 125 17.46 11.46 15.81 0 442.7 366.97 51706 +1988 126 20.05 14.05 18.4 0 512.47 360.05 51874 +1988 127 20.14 14.14 18.49 0.05 515.05 270.46 52039 +1988 128 23.37 17.37 21.72 0.02 615.39 262.39 52203 +1988 129 22.68 16.68 21.03 0 592.67 353.35 52365 +1988 130 18.74 12.74 17.09 0 476.09 367.65 52524 +1988 131 20.2 14.2 18.55 0.52 516.78 272.82 52681 +1988 132 13.24 7.24 11.59 0.18 346.35 287.79 52836 +1988 133 11.4 5.4 9.75 0 310.32 388.31 52989 +1988 134 16.01 10.01 14.36 0.73 407.3 283.82 53138 +1988 135 18.79 12.79 17.14 0.07 477.44 278.38 53286 +1988 136 19.33 13.33 17.68 0 492.19 370.1 53430 +1988 137 19.74 13.74 18.09 0.38 503.65 277.09 53572 +1988 138 21.27 15.27 19.62 1.62 548.44 273.6 53711 +1988 139 22.47 16.47 20.82 0.31 585.9 270.77 53848 +1988 140 19.92 13.92 18.27 0.06 508.76 277.96 53981 +1988 141 18.2 12.2 16.55 0 461.75 376.49 54111 +1988 142 18.13 12.13 16.48 0 459.92 377.2 54238 +1988 143 16.43 10.43 14.78 0 417.29 382.6 54362 +1988 144 16.45 10.45 14.8 0 417.77 383.02 54483 +1988 145 21.12 15.12 19.47 0 543.91 368.84 54600 +1988 146 21.22 15.22 19.57 0 546.93 368.84 54714 +1988 147 23.95 17.95 22.3 0.06 635.06 269.01 54824 +1988 148 21.88 15.88 20.23 0.05 567.22 275.45 54931 +1988 149 23.34 17.34 21.69 0 614.39 361.87 55034 +1988 150 24.3 18.3 22.65 0 647.19 358.18 55134 +1988 151 24.35 18.35 22.7 0 648.93 358.35 55229 +1988 152 26.65 20.65 25 0 733.78 347.9 55321 +1988 153 25.7 19.7 24.05 0.4 697.66 264.48 55409 +1988 154 22.44 16.44 20.79 0.15 584.94 275.09 55492 +1988 155 20.44 14.44 18.79 1.26 523.74 280.73 55572 +1988 156 20.66 14.66 19.01 0.07 530.2 280.39 55648 +1988 157 21.75 15.75 20.1 0 563.17 370.08 55719 +1988 158 20.46 14.46 18.81 0 524.33 374.9 55786 +1988 159 20.91 14.91 19.26 0 537.61 373.55 55849 +1988 160 21.45 15.45 19.8 0 553.93 371.78 55908 +1988 161 21.82 15.82 20.17 0.71 565.35 277.85 55962 +1988 162 22.97 16.97 21.32 0.07 602.13 274.56 56011 +1988 163 21.82 15.82 20.17 0.16 565.35 278.06 56056 +1988 164 21.02 15.02 19.37 0 540.9 373.72 56097 +1988 165 20.09 14.09 18.44 0.03 513.62 282.8 56133 +1988 166 19.24 13.24 17.59 0 489.71 379.97 56165 +1988 167 19.85 13.85 18.2 0.04 506.77 283.43 56192 +1988 168 18.55 12.55 16.9 0.28 471 286.64 56214 +1988 169 20.75 14.75 19.1 0 532.86 374.89 56231 +1988 170 18.89 12.89 17.24 0 480.14 381.13 56244 +1988 171 21.05 15.05 19.4 0.29 541.8 280.41 56252 +1988 172 19.59 13.59 17.94 0 499.44 378.91 56256 +1988 173 19.82 13.82 18.17 0.13 505.92 283.6 56255 +1988 174 19.86 13.86 18.21 0.34 507.05 283.43 56249 +1988 175 17.73 11.73 16.08 0.45 449.57 288.46 56238 +1988 176 16.02 10.02 14.37 0.18 407.53 292.06 56223 +1988 177 19.66 13.66 18.01 0 501.4 378.41 56203 +1988 178 20.35 14.35 18.7 0 521.12 376.1 56179 +1988 179 19.29 13.29 17.64 0 491.09 379.55 56150 +1988 180 19.85 13.85 18.2 0.52 506.77 283.18 56116 +1988 181 19.57 13.57 17.92 0.07 498.88 283.83 56078 +1988 182 23.25 17.25 21.6 0.15 611.39 273.59 56035 +1988 183 22.59 16.59 20.94 0.27 589.76 275.43 55987 +1988 184 22.5 16.5 20.85 0.67 586.86 275.58 55935 +1988 185 23.54 17.54 21.89 0 621.1 363.19 55879 +1988 186 25.05 19.05 23.4 0 673.83 356.45 55818 +1988 187 25.9 19.9 24.25 0 705.14 352.38 55753 +1988 188 30.53 24.53 28.88 0 898.15 327.5 55684 +1988 189 31.49 25.49 29.84 0 943.29 321.44 55611 +1988 190 27.93 21.93 26.28 0.28 784.93 256.16 55533 +1988 191 27.31 21.31 25.66 0.22 759.79 258.36 55451 +1988 192 27.07 21.07 25.42 0.77 750.24 259.05 55366 +1988 193 24.63 18.63 22.98 0.37 658.8 267.4 55276 +1988 194 21.97 15.97 20.32 0.18 570.04 275.32 55182 +1988 195 20.14 14.14 18.49 0 515.05 373.36 55085 +1988 196 20.82 14.82 19.17 0.25 534.93 277.95 54984 +1988 197 19.47 13.47 17.82 0.33 496.08 281.04 54879 +1988 198 22.7 16.7 21.05 0 593.32 362.76 54770 +1988 199 22.06 16.06 20.41 0.5 572.86 273.65 54658 +1988 200 18.76 12.76 17.11 1.2 476.63 281.84 54542 +1988 201 17.31 11.31 15.66 0 438.92 379.65 54423 +1988 202 19.3 13.3 17.65 0 491.36 373.04 54301 +1988 203 23.5 17.5 21.85 0 619.76 357.32 54176 +1988 204 23.16 17.16 21.51 0.08 608.4 268.65 54047 +1988 205 25.68 19.68 24.03 0.01 696.92 260.2 53915 +1988 206 28.04 22.04 26.39 0 789.46 334.91 53780 +1988 207 29.15 23.15 27.5 0 836.46 328.37 53643 +1988 208 28.75 22.75 27.1 0 819.26 329.93 53502 +1988 209 29.19 23.19 27.54 0 838.19 326.95 53359 +1988 210 28.52 22.52 26.87 0 809.5 329.98 53213 +1988 211 28.31 22.31 26.66 0.02 800.68 247.77 53064 +1988 212 26.41 20.41 24.76 0.46 724.51 254.28 52913 +1988 213 29.51 23.51 27.86 0 852.2 322.46 52760 +1988 214 26.13 20.13 24.48 0.07 713.82 254.19 52604 +1988 215 24.58 18.58 22.93 0.25 657.03 258.86 52445 +1988 216 21.96 15.96 20.31 0.15 569.72 265.86 52285 +1988 217 24.71 18.71 23.06 0 661.64 342.75 52122 +1988 218 24.65 18.65 23 0 659.51 342.21 51958 +1988 219 25.72 19.72 24.07 0 698.41 336.55 51791 +1988 220 22.85 16.85 21.2 0.14 598.2 260.65 51622 +1988 221 25.05 19.05 23.4 1.73 673.83 253.22 51451 +1988 222 25.81 19.81 24.16 0 701.77 333.3 51279 +1988 223 24.2 18.2 22.55 0 643.7 339.09 51105 +1988 224 26.83 20.83 25.18 0 740.8 326.53 50929 +1988 225 25.18 19.18 23.53 0.07 678.54 249.65 50751 +1988 226 21.62 15.62 19.97 0.76 559.15 259.21 50572 +1988 227 21.46 15.46 19.81 1.57 554.23 258.68 50392 +1988 228 19.62 13.62 17.97 0.73 500.28 262.32 50210 +1988 229 22.98 16.98 21.33 0.65 602.46 252.75 50026 +1988 230 26.64 20.64 24.99 0 733.39 320.55 49842 +1988 231 22.95 16.95 21.3 0 601.48 334.44 49656 +1988 232 20.74 14.74 19.09 0.03 532.56 255.65 49469 +1988 233 21.9 15.9 20.25 0 567.85 335.52 49280 +1988 234 20.81 14.81 19.16 0.01 534.64 253.36 49091 +1988 235 21.43 15.43 19.78 0.04 553.32 250.71 48900 +1988 236 20.22 14.22 18.57 0.22 517.36 252.62 48709 +1988 237 20.91 14.91 19.26 0.19 537.61 249.73 48516 +1988 238 21.65 15.65 20 0.12 560.08 246.65 48323 +1988 239 24.47 18.47 22.82 0.2 653.15 237.8 48128 +1988 240 23.73 17.73 22.08 0 627.54 318.24 47933 +1988 241 21.26 15.26 19.61 0 548.14 325.27 47737 +1988 242 25.11 19.11 23.46 0 676 309.53 47541 +1988 243 29.33 23.33 27.68 0.13 844.3 216.5 47343 +1988 244 20.88 14.88 19.23 1.11 536.72 240.87 47145 +1988 245 18.14 12.14 16.49 1.1 460.18 245.52 46947 +1988 246 18.11 12.11 16.46 1.22 459.4 244.11 46747 +1988 247 20.46 14.46 18.81 0 524.33 316.9 46547 +1988 248 19.18 13.18 17.53 0 488.06 318.75 46347 +1988 249 19.32 13.32 17.67 0 491.92 316.3 46146 +1988 250 23.72 17.72 22.07 1.09 627.2 225.2 45945 +1988 251 22.81 16.81 21.16 0 596.9 301.44 45743 +1988 252 23.11 17.11 21.46 0.01 606.75 223.74 45541 +1988 253 23.81 17.81 22.16 0.01 630.27 220.38 45339 +1988 254 19.43 13.43 17.78 0.03 494.97 229.23 45136 +1988 255 15.68 9.68 14.03 1.04 399.59 234.56 44933 +1988 256 12.54 6.54 10.89 0.12 332.24 237.6 44730 +1988 257 20.23 14.23 18.58 0 517.65 296.81 44527 +1988 258 19.65 13.65 18 0.71 501.12 222.1 44323 +1988 259 21.5 15.5 19.85 0 555.46 288.4 44119 +1988 260 20.8 14.8 19.15 0 534.34 288.17 43915 +1988 261 18.15 12.15 16.5 0.19 460.44 219.68 43711 +1988 262 15.14 9.14 13.49 0 387.24 297.37 43507 +1988 263 15.69 9.69 14.04 0 399.82 293.75 43303 +1988 264 16.26 10.26 14.61 0 413.22 289.95 43099 +1988 265 18.62 12.62 16.97 0.42 472.87 211.57 42894 +1988 266 17.18 11.18 15.53 0 435.66 283.07 42690 +1988 267 19.9 13.9 18.25 0.46 508.19 205.32 42486 +1988 268 21.78 15.78 20.13 0 564.11 266.05 42282 +1988 269 16.73 10.73 15.08 0.44 424.56 207.28 42078 +1988 270 15.38 9.38 13.73 0 392.69 276.56 41875 +1988 271 19.25 13.25 17.6 0 489.98 265.35 41671 +1988 272 22.69 16.69 21.04 0 593 253.35 41468 +1988 273 19.4 13.4 17.75 1.24 494.14 194.9 41265 +1988 274 14.69 8.69 13.04 0 377.2 267.34 41062 +1988 275 12.62 6.62 10.97 0.57 333.83 201.13 40860 +1988 276 13.18 7.18 11.53 0 345.12 264.53 40658 +1988 277 10.65 4.65 9 0 296.59 265.74 40456 +1988 278 12.69 6.69 11.04 0.02 335.22 194.83 40255 +1988 279 16.05 10.05 14.4 0 408.24 251.05 40054 +1988 280 13.83 7.83 12.18 0.28 358.63 189.32 39854 +1988 281 13.94 7.94 12.29 0 360.96 249.53 39654 +1988 282 9.46 3.46 7.81 0.14 275.86 190 39455 +1988 283 11.38 5.38 9.73 0 309.95 247.91 39256 +1988 284 11.49 5.49 9.84 0.1 312.01 183.54 39058 +1988 285 14.27 8.27 12.62 0 368.03 237.81 38861 +1988 286 18.06 12.06 16.41 0.51 458.09 171.06 38664 +1988 287 17.02 11.02 15.37 0.37 431.69 170.46 38468 +1988 288 17.99 11.99 16.34 0.08 456.27 167 38273 +1988 289 17.6 11.6 15.95 0.15 446.25 165.67 38079 +1988 290 16.06 10.06 14.41 0 408.48 220.95 37885 +1988 291 18.15 12.15 16.5 0 460.44 214.41 37693 +1988 292 16.29 10.29 14.64 0 413.94 215.27 37501 +1988 293 15.67 9.67 14.02 0.03 399.35 160.25 37311 +1988 294 15.5 9.5 13.85 0 395.43 211.12 37121 +1988 295 16.87 10.87 15.22 0 427.99 206 36933 +1988 296 13.48 7.48 11.83 0 351.3 208.88 36745 +1988 297 9.92 3.92 8.27 0.16 283.72 158.06 36560 +1988 298 12.35 6.35 10.7 0.91 328.5 153.86 36375 +1988 299 11.76 5.76 10.11 0.91 317.1 152.36 36191 +1988 300 9.35 3.35 7.7 1.07 274.01 152.46 36009 +1988 301 8.57 2.57 6.92 0 261.19 201.56 35829 +1988 302 9.26 3.26 7.61 0 272.5 198.22 35650 +1988 303 9.82 3.82 8.17 0 282 195.04 35472 +1988 304 12.84 6.84 11.19 0 338.22 189.04 35296 +1988 305 -0.24 -6.24 -1.89 0 148.45 197.68 35122 +1988 306 -1.86 -7.86 -3.51 0 133.14 196.19 34950 +1988 307 0.66 -5.34 -0.99 0 157.6 192.28 34779 +1988 308 2.12 -3.88 0.47 0 173.47 188.74 34610 +1988 309 1.61 -4.39 -0.04 0 167.77 186.69 34444 +1988 310 -0.09 -6.09 -1.74 0 149.94 185.15 34279 +1988 311 1.77 -4.23 0.12 0.53 169.54 136.41 34116 +1988 312 0.99 -5.01 -0.66 0.51 161.07 134.73 33956 +1988 313 2.31 -3.69 0.66 0.75 175.63 132.53 33797 +1988 314 0.27 -5.73 -1.38 0.11 153.58 131.9 33641 +1988 315 1.98 -4.02 0.33 0 171.89 172.34 33488 +1988 316 0.27 -5.73 -1.38 0 153.58 171.06 33337 +1988 317 -0.93 -6.93 -2.58 0 141.76 169.41 33188 +1988 318 1.53 -4.47 -0.12 0 166.89 165.78 33042 +1988 319 4.04 -1.96 2.39 0 196.42 162.56 32899 +1988 320 7.22 1.22 5.57 0.01 240.2 118.81 32758 +1988 321 3.35 -2.65 1.7 0.19 187.89 119.23 32620 +1988 322 5.19 -0.81 3.54 1.45 211.39 116.97 32486 +1988 323 8.62 2.62 6.97 0.2 261.99 113.81 32354 +1988 324 10.09 4.09 8.44 0.04 286.67 111.32 32225 +1988 325 12.93 6.93 11.28 0.18 340.04 107.94 32100 +1988 326 11.96 5.96 10.31 0 320.93 143.52 31977 +1988 327 7.26 1.26 5.61 0 240.81 145.78 31858 +1988 328 7.87 1.87 6.22 0 250.12 143.36 31743 +1988 329 9.61 3.61 7.96 0 278.4 140.47 31631 +1988 330 7.25 1.25 5.6 0.49 240.65 105.67 31522 +1988 331 9.08 3.08 7.43 0 269.51 138.18 31417 +1988 332 7.79 1.79 6.14 0 248.88 137.56 31316 +1988 333 5.2 -0.8 3.55 0 211.52 138.25 31218 +1988 334 -0.37 -6.37 -2.02 0 147.17 140.06 31125 +1988 335 -3.15 -9.15 -4.8 0 121.95 139.95 31035 +1988 336 0.41 -5.59 -1.24 0.39 155.01 103.08 30949 +1988 337 5.99 -0.01 4.34 0 222.37 132.75 30867 +1988 338 6.48 0.48 4.83 0 229.33 131.49 30790 +1988 339 7.45 1.45 5.8 0 243.67 130.04 30716 +1988 340 6.22 0.22 4.57 0 225.61 130.15 30647 +1988 341 4.4 -1.6 2.75 0.34 201 97.75 30582 +1988 342 4.66 -1.34 3.01 0.02 204.37 97.07 30521 +1988 343 9.35 3.35 7.7 0.22 274.01 94.08 30465 +1988 344 8.36 2.36 6.71 0 257.82 125.07 30413 +1988 345 5.72 -0.28 4.07 0.07 218.61 94.81 30366 +1988 346 5.99 -0.01 4.34 0 222.37 125.7 30323 +1988 347 5.01 -0.99 3.36 0 208.98 125.69 30284 +1988 348 4.59 -1.41 2.94 1.28 203.46 94.19 30251 +1988 349 1.97 -4.03 0.32 0.02 171.77 94.93 30221 +1988 350 1.42 -4.58 -0.23 0 165.69 126.49 30197 +1988 351 0.02 -5.98 -1.63 0 151.05 126.88 30177 +1988 352 2.43 -3.57 0.78 0 177.01 125.69 30162 +1988 353 6.07 0.07 4.42 0.07 223.49 92.72 30151 +1988 354 3.34 -2.66 1.69 0 187.77 125.14 30145 +1988 355 4.52 -1.48 2.87 0 202.55 124.5 30144 +1988 356 5.26 -0.74 3.61 0 212.33 124.1 30147 +1988 357 8.41 2.41 6.76 0 258.62 122.11 30156 +1988 358 10.14 4.14 8.49 0 287.55 120.88 30169 +1988 359 8.16 2.16 6.51 0 254.65 122.49 30186 +1988 360 6.69 0.69 5.04 0 232.37 123.85 30208 +1988 361 6.25 0.25 4.6 0.77 226.04 93.34 30235 +1988 362 2.65 -3.35 1 0.16 179.56 95.19 30267 +1988 363 1.99 -4.01 0.34 0 172 127.83 30303 +1988 364 3.83 -2.17 2.18 0 193.79 127.29 30343 +1988 365 3.82 -2.18 2.17 0.01 193.66 95.9 30388 +1989 1 -0.38 -6.38 -2.03 0 147.07 130.75 30438 +1989 2 2.18 -3.82 0.53 0 174.15 130.34 30492 +1989 3 1.21 -4.79 -0.44 0 163.42 131.74 30551 +1989 4 2.83 -3.17 1.18 0 181.67 131.87 30614 +1989 5 4.8 -1.2 3.15 0 206.2 131.43 30681 +1989 6 3.05 -2.95 1.4 0 184.28 133.29 30752 +1989 7 -0.11 -6.11 -1.76 0 149.74 135.6 30828 +1989 8 1.62 -4.38 -0.03 0 167.88 136.31 30907 +1989 9 -1.23 -7.23 -2.88 0 138.93 138.84 30991 +1989 10 -2.36 -8.36 -4.01 0 128.7 140.59 31079 +1989 11 0.6 -5.4 -1.05 0 156.97 140.36 31171 +1989 12 0.98 -5.02 -0.67 0.09 160.96 105.9 31266 +1989 13 -1.26 -7.26 -2.91 0.01 138.65 149.99 31366 +1989 14 2.66 -3.34 1.01 0 179.67 143.46 31469 +1989 15 1.41 -4.59 -0.24 0 165.58 145.56 31575 +1989 16 3.38 -2.62 1.73 0 188.25 145.79 31686 +1989 17 -3.63 -9.63 -5.28 0 118 150.71 31800 +1989 18 -0.92 -6.92 -2.57 0 141.85 151.56 31917 +1989 19 -0.7 -6.7 -2.35 0 143.96 153.41 32038 +1989 20 1.66 -4.34 0.01 0 168.32 153.86 32161 +1989 21 4.82 -1.18 3.17 0 206.47 154.01 32289 +1989 22 5.87 -0.13 4.22 0 220.69 155.03 32419 +1989 23 8.41 2.41 6.76 0 258.62 154.83 32552 +1989 24 5.92 -0.08 4.27 0 221.39 158.81 32688 +1989 25 8.48 2.48 6.83 0 259.74 158.66 32827 +1989 26 9.22 3.22 7.57 0.06 271.84 119.93 32969 +1989 27 5.87 -0.13 4.22 0.02 220.69 123.49 33114 +1989 28 6.02 0.02 4.37 0 222.79 166.74 33261 +1989 29 3.78 -2.22 2.13 0 193.17 170.68 33411 +1989 30 4.05 -1.95 2.4 0 196.55 172.75 33564 +1989 31 3.53 -2.47 1.88 0 190.08 175.47 33718 +1989 32 7.63 1.63 5.98 0 246.42 174.48 33875 +1989 33 9.35 3.35 7.7 0 274.01 175.5 34035 +1989 34 8.43 2.43 6.78 0 258.94 178.54 34196 +1989 35 5.88 -0.12 4.23 0.23 220.83 137.14 34360 +1989 36 5.35 -0.65 3.7 0.13 213.54 139.33 34526 +1989 37 5.59 -0.41 3.94 0 216.82 188 34694 +1989 38 2.67 -3.33 1.02 0 179.79 192.86 34863 +1989 39 3.17 -2.83 1.52 0 185.71 195.14 35035 +1989 40 5.07 -0.93 3.42 0 209.78 196.36 35208 +1989 41 3.68 -2.32 2.03 0 191.93 200.03 35383 +1989 42 4.36 -1.64 2.71 0 200.49 202.09 35560 +1989 43 9.09 3.09 7.44 0.01 269.68 150.39 35738 +1989 44 6.64 0.64 4.99 0 231.65 205.45 35918 +1989 45 3.9 -2.1 2.25 0 194.66 210.35 36099 +1989 46 4.49 -1.51 2.84 0.43 202.16 159.43 36282 +1989 47 3.93 -2.07 2.28 0 195.04 215.85 36466 +1989 48 5.63 -0.37 3.98 0 217.37 217.25 36652 +1989 49 7.9 1.9 6.25 0 250.58 217.86 36838 +1989 50 10.46 4.46 8.81 0 293.19 217.62 37026 +1989 51 8.78 2.78 7.13 0 264.59 222.5 37215 +1989 52 9.57 3.57 7.92 0 277.72 224.39 37405 +1989 53 11.33 5.33 9.68 0 309.02 225.12 37596 +1989 54 13.48 7.48 11.83 0 351.3 224.77 37788 +1989 55 15.05 9.05 13.4 0 385.21 225.16 37981 +1989 56 12.89 6.89 11.24 0.01 339.23 173.39 38175 +1989 57 9.04 3.04 7.39 0 268.85 239.14 38370 +1989 58 7.23 1.23 5.58 0.84 240.35 183.06 38565 +1989 59 3.76 -2.24 2.11 0.57 192.92 187.59 38761 +1989 60 8.08 2.08 6.43 0.02 253.4 186.53 38958 +1989 61 8.1 2.1 6.45 0 253.71 251.6 39156 +1989 62 4.65 -1.35 3 0.1 204.24 193.49 39355 +1989 63 7 1 5.35 1.09 236.93 193.97 39553 +1989 64 8.2 2.2 6.55 0.23 255.28 195.11 39753 +1989 65 7.51 1.51 5.86 0 244.59 263.84 39953 +1989 66 5.02 -0.98 3.37 0.59 209.11 201.93 40154 +1989 67 2.93 -3.07 1.28 0 182.85 274.09 40355 +1989 68 3.99 -2.01 2.34 0 195.79 276.04 40556 +1989 69 8.38 2.38 6.73 0 258.14 273.9 40758 +1989 70 13.26 7.26 11.61 0 346.76 269.54 40960 +1989 71 16.06 10.06 14.41 0 408.48 267.16 41163 +1989 72 18.32 12.32 16.67 0 464.91 264.94 41366 +1989 73 17.29 11.29 15.64 0 438.42 269.82 41569 +1989 74 17.21 11.21 15.56 0 436.41 272.63 41772 +1989 75 14.74 8.74 13.09 0.01 378.3 210.29 41976 +1989 76 15.56 9.56 13.91 0.22 396.81 210.99 42179 +1989 77 9.37 3.37 7.72 0.02 274.35 220.84 42383 +1989 78 7.95 1.95 6.3 0.15 251.36 224.28 42587 +1989 79 11.57 5.57 9.92 0.58 313.51 222.34 42791 +1989 80 14.79 8.79 13.14 0 379.41 293.1 42996 +1989 81 13.82 7.82 12.17 0.62 358.42 223.13 43200 +1989 82 10.78 4.78 9.13 0.03 298.93 229.07 43404 +1989 83 14.44 8.44 12.79 0 371.72 301.34 43608 +1989 84 15.78 9.78 14.13 0 401.91 301.01 43812 +1989 85 13.61 7.61 11.96 0 354.01 307.9 44016 +1989 86 15.37 9.37 13.72 0 392.46 306.66 44220 +1989 87 17.79 11.79 16.14 0.01 451.11 227.63 44424 +1989 88 18.94 12.94 17.29 0.13 481.5 227.08 44627 +1989 89 17.82 11.82 16.17 0 451.88 307.87 44831 +1989 90 18.93 12.93 17.28 0 481.23 307.24 45034 +1989 91 21.07 15.07 19.42 0 542.4 303.19 45237 +1989 92 18.82 12.82 17.17 0.56 478.25 233.88 45439 +1989 93 14.31 8.31 12.66 0.59 368.89 243.6 45642 +1989 94 12.81 6.81 11.16 0.52 337.62 247.46 45843 +1989 95 14.2 8.2 12.55 0 366.52 329.26 46045 +1989 96 14.99 8.99 13.34 0 383.87 329.63 46246 +1989 97 17.48 11.48 15.83 0 443.2 325.67 46446 +1989 98 16.57 10.57 14.92 0 420.67 329.87 46647 +1989 99 16.53 10.53 14.88 0.84 419.7 248.95 46846 +1989 100 16.98 10.98 15.33 0.03 430.7 249.53 47045 +1989 101 17.77 11.77 16.12 0 450.6 332.52 47243 +1989 102 16.34 10.34 14.69 0 415.13 338.05 47441 +1989 103 14.49 8.49 12.84 0 372.81 344.19 47638 +1989 104 15.94 9.94 14.29 0 405.65 342.61 47834 +1989 105 16.87 10.87 15.22 0.03 427.99 256.53 48030 +1989 106 14.52 8.52 12.87 0.26 373.46 261.99 48225 +1989 107 13.26 7.26 11.61 0.11 346.76 265.29 48419 +1989 108 12.97 6.97 11.32 0.11 340.85 267.05 48612 +1989 109 16.07 10.07 14.42 0.27 408.71 262.96 48804 +1989 110 13.99 7.99 12.34 0.89 362.02 267.67 48995 +1989 111 13.74 7.74 12.09 0.77 356.73 269.24 49185 +1989 112 12.78 6.78 11.13 0.11 337.02 271.9 49374 +1989 113 11.39 5.39 9.74 0.64 310.13 274.99 49561 +1989 114 14.97 8.97 13.32 0.17 383.42 270.38 49748 +1989 115 9.69 3.69 8.04 0 279.77 372.68 49933 +1989 116 8.68 2.68 7.03 0.72 262.96 281.71 50117 +1989 117 12.5 6.5 10.85 0.09 331.45 277.45 50300 +1989 118 10.58 4.58 8.93 0.1 295.33 281.25 50481 +1989 119 10.84 4.84 9.19 0.11 300.02 281.79 50661 +1989 120 11.44 5.44 9.79 0.3 311.07 281.82 50840 +1989 121 15.81 9.81 14.16 0 402.61 367.14 51016 +1989 122 15.84 9.84 14.19 0 403.31 368.25 51191 +1989 123 15.21 9.21 13.56 0 388.82 370.86 51365 +1989 124 16.84 10.84 15.19 0.24 427.25 275.78 51536 +1989 125 17.67 11.67 16.02 0.64 448.04 274.78 51706 +1989 126 15.95 9.95 14.3 1.69 405.89 279.03 51874 +1989 127 15.9 9.9 14.25 0 404.71 373.05 52039 +1989 128 11.94 5.94 10.29 0 320.54 383.18 52203 +1989 129 18.46 12.46 16.81 0 468.61 367.73 52365 +1989 130 23.03 17.03 21.38 0.46 604.11 264.56 52524 +1989 131 17.27 11.27 15.62 0.88 437.91 279.57 52681 +1989 132 16.6 10.6 14.95 0.72 421.4 281.58 52836 +1989 133 17.37 11.37 15.72 2.59 440.43 280.5 52989 +1989 134 17.98 11.98 16.33 0.07 456.02 279.7 53138 +1989 135 21.81 15.81 20.16 0.2 565.04 270.72 53286 +1989 136 18.92 12.92 17.27 0.24 480.96 278.54 53430 +1989 137 19.71 13.71 18.06 0 502.81 369.56 53572 +1989 138 17.97 11.97 16.32 0.45 455.76 281.69 53711 +1989 139 18.35 12.35 16.7 0.37 465.7 281.34 53848 +1989 140 18.84 12.84 17.19 0 478.79 374.09 53981 +1989 141 18.62 12.62 16.97 0.1 472.87 281.41 54111 +1989 142 16.87 10.87 15.22 0 427.99 380.85 54238 +1989 143 17.92 11.92 16.27 0.12 454.46 283.77 54362 +1989 144 17.42 11.42 15.77 0 441.69 380.3 54483 +1989 145 20.32 14.32 18.67 0 520.25 371.64 54600 +1989 146 18.32 12.32 16.67 0 464.91 378.47 54714 +1989 147 19.4 13.4 17.75 0.46 494.14 281.66 54824 +1989 148 18.5 12.5 16.85 0 469.67 378.77 54931 +1989 149 15.04 9.04 13.39 0 384.99 388.77 55034 +1989 150 13.04 7.04 11.39 0.93 342.26 295.4 55134 +1989 151 15.64 9.64 13.99 0 398.66 387.96 55229 +1989 152 17.39 11.39 15.74 0.01 440.93 287.43 55321 +1989 153 15.68 9.68 14.03 0.34 399.59 291.16 55409 +1989 154 14.88 8.88 13.23 0 381.41 390.59 55492 +1989 155 19.49 13.49 17.84 0.37 496.64 283.13 55572 +1989 156 23.18 17.18 21.53 0 609.06 364.36 55648 +1989 157 19.9 13.9 18.25 0.05 508.19 282.48 55719 +1989 158 17.19 11.19 15.54 0.23 435.91 288.94 55786 +1989 159 19.18 13.18 17.53 2.01 488.06 284.57 55849 +1989 160 20.03 14.03 18.38 0 511.9 376.79 55908 +1989 161 22.5 16.5 20.85 0 586.86 367.87 55962 +1989 162 22.14 16.14 20.49 0.11 575.39 276.99 56011 +1989 163 21.8 15.8 20.15 0.15 564.73 278.11 56056 +1989 164 24.32 18.32 22.67 0.63 647.88 270.54 56097 +1989 165 23.66 17.66 22.01 2.99 625.16 272.7 56133 +1989 166 20.08 14.08 18.43 0.75 513.33 282.89 56165 +1989 167 22.22 16.22 20.57 0 577.92 369.39 56192 +1989 168 19.33 13.33 17.68 0.2 492.19 284.78 56214 +1989 169 15.86 9.86 14.21 0.16 403.78 292.48 56231 +1989 170 16.63 10.63 14.98 0.51 422.13 290.9 56244 +1989 171 18.71 12.71 17.06 0 475.29 381.76 56252 +1989 172 24.2 18.2 22.55 0.08 643.7 271.11 56256 +1989 173 22.81 16.81 21.16 0.49 596.9 275.4 56255 +1989 174 19.3 13.3 17.65 0 491.36 379.76 56249 +1989 175 15.66 9.66 14.01 0.03 399.12 292.81 56238 +1989 176 14.68 8.68 13.03 0 376.98 392.88 56223 +1989 177 18.11 12.11 16.46 0.15 459.4 287.5 56203 +1989 178 19.42 13.42 17.77 0 494.69 379.23 56179 +1989 179 17.16 11.16 15.51 0.97 435.17 289.55 56150 +1989 180 19.79 13.79 18.14 0 505.07 377.78 56116 +1989 181 23.4 17.4 21.75 0.27 616.4 273.24 56078 +1989 182 25.98 19.98 24.33 0 708.15 352.82 56035 +1989 183 25.83 19.83 24.18 0.39 702.51 265.02 55987 +1989 184 25.39 19.39 23.74 0 686.21 355.24 55935 +1989 185 27.33 21.33 25.68 0.02 760.59 259.37 55879 +1989 186 24.7 18.7 23.05 0.58 661.28 268.5 55818 +1989 187 23.75 17.75 22.1 0.42 628.22 271.42 55753 +1989 188 22.89 16.89 21.24 0.45 599.51 273.85 55684 +1989 189 23.82 17.82 22.17 1.11 630.61 270.87 55611 +1989 190 20.73 14.73 19.08 1.31 532.26 279.49 55533 +1989 191 20.59 14.59 18.94 0 528.14 372.88 55451 +1989 192 19.85 13.85 18.2 0.03 506.77 281.33 55366 +1989 193 21.72 15.72 20.07 0.45 562.24 276.19 55276 +1989 194 21.2 15.2 19.55 0 546.32 369.93 55182 +1989 195 25.52 19.52 23.87 0.27 690.99 264.06 55085 +1989 196 24.1 18.1 22.45 0.25 640.23 268.45 54984 +1989 197 24.17 18.17 22.52 0.5 642.66 267.89 54879 +1989 198 19.97 13.97 18.32 0.05 510.18 279.48 54770 +1989 199 20.17 14.17 18.52 0.76 515.92 278.71 54658 +1989 200 19.55 13.55 17.9 0 498.32 373.27 54542 +1989 201 17.9 11.9 16.25 0 453.94 377.93 54423 +1989 202 22.77 16.77 21.12 0.3 595.59 270.54 54301 +1989 203 22.61 16.61 20.96 0.01 590.41 270.64 54176 +1989 204 25.57 19.57 23.92 0.62 692.84 260.95 54047 +1989 205 25.03 19.03 23.38 0.75 673.11 262.39 53915 +1989 206 22.51 16.51 20.86 0.44 587.18 269.76 53780 +1989 207 23.71 17.71 22.06 0.53 626.86 265.71 53643 +1989 208 24.62 18.62 22.97 0 658.44 349.82 53502 +1989 209 26.91 20.91 25.26 0.21 743.94 254.05 53359 +1989 210 27.24 21.24 25.59 0.11 757 252.4 53213 +1989 211 29.03 23.03 27.38 0.24 831.27 244.9 53064 +1989 212 29.43 23.43 27.78 0 848.68 323.6 52913 +1989 213 26.85 20.85 25.2 0 741.58 336.23 52760 +1989 214 29.92 23.92 28.27 0.17 870.42 239.62 52604 +1989 215 29.24 23.24 27.59 1.12 840.37 241.99 52445 +1989 216 27.52 21.52 25.87 0.07 768.23 247.99 52285 +1989 217 28.63 22.63 26.98 1.02 814.16 243.12 52122 +1989 218 26.57 20.57 24.92 1.81 730.68 250.23 51958 +1989 219 23.77 17.77 22.12 0.31 628.9 258.63 51791 +1989 220 22.44 16.44 20.79 1.36 584.94 261.81 51622 +1989 221 26.31 20.31 24.66 0.62 720.68 249.02 51451 +1989 222 27.16 21.16 25.51 1.5 753.81 245.27 51279 +1989 223 26.94 20.94 25.29 0.75 745.11 245.26 51105 +1989 224 25.24 19.24 23.59 0.12 680.72 250.28 50929 +1989 225 26.95 20.95 25.3 0.05 745.51 243.67 50751 +1989 226 26.05 20.05 24.4 1.87 710.79 245.97 50572 +1989 227 19.9 13.9 18.25 0.74 508.19 262.57 50392 +1989 228 19.13 13.13 17.48 1.08 486.69 263.45 50210 +1989 229 17.69 11.69 16.04 2.53 448.55 265.66 50026 +1989 230 14.35 8.35 12.7 1.29 369.76 271.01 49842 +1989 231 18.23 12.23 16.58 0 462.54 349.91 49656 +1989 232 17.71 11.71 16.06 1.14 449.06 262.51 49469 +1989 233 15.55 9.55 13.9 0.37 396.58 265.62 49280 +1989 234 16.25 10.25 14.6 1.52 412.98 263.24 49091 +1989 235 14.99 8.99 13.34 0.25 383.87 264.39 48900 +1989 236 17.09 11.09 15.44 0 433.42 345.85 48709 +1989 237 17.31 11.31 15.66 0.07 438.92 257.7 48516 +1989 238 22.54 16.54 20.89 0.1 588.15 244.33 48323 +1989 239 21.97 15.97 20.32 0.1 570.04 244.72 48128 +1989 240 23.83 17.83 22.18 0.21 630.95 238.39 47933 +1989 241 23.47 17.47 21.82 0.43 618.75 238.16 47737 +1989 242 23.47 17.47 21.82 0 618.75 315.87 47541 +1989 243 25.89 19.89 24.24 0.12 704.76 228.41 47343 +1989 244 21.26 15.26 19.61 0 548.14 319.94 47145 +1989 245 24.01 18.01 22.36 1.3 637.13 231.41 46947 +1989 246 17.87 11.87 16.22 0 453.17 326.12 46747 +1989 247 15.25 9.25 13.6 0 389.73 330.66 46547 +1989 248 17.49 11.49 15.84 0 443.46 323.3 46347 +1989 249 15.63 9.63 13.98 0.08 398.43 244.3 46146 +1989 250 15.38 9.38 13.73 1.31 392.69 243.24 45945 +1989 251 15.61 9.61 13.96 0 397.97 321.66 45743 +1989 252 17.95 11.95 16.3 0 455.24 313.82 45541 +1989 253 19.12 13.12 17.47 0.14 486.41 231.45 45339 +1989 254 15.81 9.81 14.16 0.06 402.61 236.05 45136 +1989 255 18.38 12.38 16.73 0.2 466.49 229.67 44933 +1989 256 16.34 10.34 14.69 0.09 415.13 231.73 44730 +1989 257 14.47 8.47 12.82 1.24 372.37 233.14 44527 +1989 258 17.72 11.72 16.07 0.42 449.31 225.88 44323 +1989 259 18.72 12.72 17.07 0 475.56 296.23 44119 +1989 260 16.14 10.14 14.49 0 410.37 300.07 43915 +1989 261 15.91 9.91 14.26 0.05 404.95 223.59 43711 +1989 262 15.04 9.04 13.39 0 384.99 297.58 43507 +1989 263 21 15 19.35 0 540.3 280.52 43303 +1989 264 21.63 15.63 19.98 0.22 559.46 207.14 43099 +1989 265 22.43 16.43 20.78 0.19 584.62 203.62 42894 +1989 266 23 17 21.35 0 603.12 267.35 42690 +1989 267 20.65 14.65 19 0 529.9 271.73 42486 +1989 268 20.82 14.82 19.17 0.88 534.93 201.59 42282 +1989 269 21.91 15.91 20.26 0.18 568.16 197.45 42078 +1989 270 26.2 20.2 24.55 0.28 716.48 185.02 41875 +1989 271 25.32 19.32 23.67 0 683.64 247.42 41671 +1989 272 24.89 18.89 23.24 0 668.07 246.36 41468 +1989 273 22.38 16.38 20.73 0 583.02 251.87 41265 +1989 274 15.55 9.55 13.9 0 396.58 265.7 41062 +1989 275 18.1 12.1 16.45 0.02 459.14 193.22 40860 +1989 276 18.03 12.03 16.38 0.21 457.31 191.35 40658 +1989 277 21.64 15.64 19.99 0.08 559.77 182.76 40456 +1989 278 18.75 12.75 17.1 0.02 476.36 186.09 40255 +1989 279 16.53 10.53 14.88 0 419.7 250.11 40054 +1989 280 20.77 14.77 19.12 0 533.45 238 39854 +1989 281 24.25 18.25 22.6 0.29 645.44 169.34 39654 +1989 282 17.71 11.71 16.06 0 449.06 239.76 39455 +1989 283 15.36 9.36 13.71 0 392.23 241.54 39256 +1989 284 9.42 3.42 7.77 0 275.19 247.46 39058 +1989 285 9.21 3.21 7.56 0 271.67 245.04 38861 +1989 286 12.78 6.78 11.13 0 337.02 237.42 38664 +1989 287 13.17 7.17 11.52 0 344.91 233.89 38468 +1989 288 15.58 9.58 13.93 0 397.27 227.19 38273 +1989 289 14.65 8.65 13 0 376.32 226.17 38079 +1989 290 17.11 11.11 15.46 0 433.92 219.04 37885 +1989 291 12.17 6.17 10.52 0 324.99 224.39 37693 +1989 292 9.98 3.98 8.33 0 284.76 224.52 37501 +1989 293 8.75 2.75 7.1 0 264.1 223.18 37311 +1989 294 4.73 -1.27 3.08 0 205.29 224.14 37121 +1989 295 9.95 3.95 8.3 0 284.24 216.05 36933 +1989 296 5.19 -0.81 3.54 0 211.39 218.2 36745 +1989 297 13.98 7.98 12.33 0 361.81 205.46 36560 +1989 298 19.72 13.72 18.07 2.09 503.09 144.73 36375 +1989 299 19.99 13.99 18.34 0.11 510.75 142.32 36191 +1989 300 13.88 7.88 12.23 0.07 359.69 148.25 36009 +1989 301 11.68 5.68 10.03 0 315.59 198.08 35829 +1989 302 10.96 4.96 9.31 0 302.2 196.34 35650 +1989 303 13.01 7.01 11.36 0 341.66 191.25 35472 +1989 304 12.55 6.55 10.9 0 332.44 189.41 35296 +1989 305 8.27 2.27 6.62 0.04 256.39 143.55 35122 +1989 306 4.99 -1.01 3.34 0 208.72 191.95 34950 +1989 307 7.11 1.11 5.46 0.02 238.56 140.75 34779 +1989 308 7.15 1.15 5.5 0 239.16 185.01 34610 +1989 309 6.93 0.93 5.28 0 235.89 182.87 34444 +1989 310 9.77 3.77 8.12 0 281.14 177.8 34279 +1989 311 8.37 2.37 6.72 0.06 257.98 132.72 34116 +1989 312 9.89 3.89 8.24 0.51 283.2 129.66 33956 +1989 313 8.29 2.29 6.64 0.38 256.71 129.21 33797 +1989 314 13.58 7.58 11.93 0 353.38 164.78 33641 +1989 315 12.75 6.75 11.1 0.71 336.42 122.46 33488 +1989 316 11.21 5.21 9.56 0 306.79 162.83 33337 +1989 317 5.6 -0.4 3.95 0.16 216.95 124.17 33188 +1989 318 3.44 -2.56 1.79 0 188.98 164.66 33042 +1989 319 7.29 1.29 5.64 0 241.26 160.22 32899 +1989 320 5.01 -0.99 3.36 0.13 208.98 120.02 32758 +1989 321 6.26 0.26 4.61 0.65 226.18 117.77 32620 +1989 322 4.97 -1.03 3.32 0 208.45 156.11 32486 +1989 323 2.05 -3.95 0.4 0 172.67 156.24 32354 +1989 324 2.08 -3.92 0.43 0 173.01 154.15 32225 +1989 325 3.91 -2.09 2.26 0 194.79 151.36 32100 +1989 326 3.38 -2.62 1.73 0 188.25 150.2 31977 +1989 327 0.22 -5.78 -1.43 0.12 153.07 112.5 31858 +1989 328 3.55 -2.45 1.9 0 190.33 146.26 31743 +1989 329 5.07 -0.93 3.42 0.06 209.78 107.87 31631 +1989 330 5.85 -0.15 4.2 0 220.41 141.88 31522 +1989 331 8.55 2.55 6.9 0.54 260.86 103.96 31417 +1989 332 9.06 3.06 7.41 0.07 269.18 102.43 31316 +1989 333 8.5 2.5 6.85 0 260.06 135.95 31218 +1989 334 10.49 4.49 8.84 0 293.72 133.23 31125 +1989 335 9.41 3.41 7.76 0 275.02 132.98 31035 +1989 336 5.96 -0.04 4.31 0 221.95 134.42 30949 +1989 337 4.32 -1.68 2.67 0 199.98 133.77 30867 +1989 338 7.52 1.52 5.87 0 244.74 130.77 30790 +1989 339 9.09 3.09 7.44 0 269.68 128.83 30716 +1989 340 7.47 1.47 5.82 0 243.98 129.31 30647 +1989 341 4.83 -1.17 3.18 0 206.6 130.09 30582 +1989 342 1.47 -4.53 -0.18 0 166.24 131.09 30521 +1989 343 3.43 -2.57 1.78 0 188.86 129.28 30465 +1989 344 5.36 -0.64 3.71 0 213.68 127.06 30413 +1989 345 2.08 -3.92 0.43 0 173.01 128.4 30366 +1989 346 -0.68 -6.68 -2.33 0 144.15 129.06 30323 +1989 347 -0.14 -6.14 -1.79 0.02 149.44 139.83 30284 +1989 348 4.12 -1.88 2.47 0.26 197.43 94.39 30251 +1989 349 5.6 -0.4 3.95 0 216.95 124.62 30221 +1989 350 4.11 -1.89 2.46 0.04 197.3 93.85 30197 +1989 351 8.41 2.41 6.76 0 258.62 122.21 30177 +1989 352 9.79 3.79 8.14 0 281.48 121.09 30162 +1989 353 6.45 0.45 4.8 0 228.9 123.38 30151 +1989 354 6.03 0.03 4.38 0 222.93 123.61 30145 +1989 355 6.12 0.12 4.47 0 224.2 123.56 30144 +1989 356 3.69 -2.31 2.04 0 192.05 124.98 30147 +1989 357 3.06 -2.94 1.41 0 184.4 125.37 30156 +1989 358 2.61 -3.39 0.96 0.09 179.09 94.26 30169 +1989 359 5.94 -0.06 4.29 0.21 221.67 92.97 30186 +1989 360 2.65 -3.35 1 0 179.56 126.15 30208 +1989 361 5.17 -0.83 3.52 0 211.12 125.11 30235 +1989 362 6.17 0.17 4.52 0 224.9 124.94 30267 +1989 363 6.01 0.01 4.36 0 222.65 125.62 30303 +1989 364 7.65 1.65 6 0 246.72 124.94 30343 +1989 365 7.03 1.03 5.38 0.01 237.37 94.44 30388 +1990 1 2.69 -3.31 1.04 0 180.03 129.35 30438 +1990 2 -1.52 -7.52 -3.17 0 136.24 131.94 30492 +1990 3 0.46 -5.54 -1.19 0 155.52 132.08 30551 +1990 4 -1.36 -7.36 -3.01 0 137.72 133.76 30614 +1990 5 0.28 -5.72 -1.37 0 153.68 133.74 30681 +1990 6 -0.88 -6.88 -2.53 0 142.23 135.12 30752 +1990 7 1.43 -4.57 -0.22 0 165.8 134.91 30828 +1990 8 0.64 -5.36 -1.01 0 157.39 136.77 30907 +1990 9 4.69 -1.31 3.04 0.11 204.76 101.93 30991 +1990 10 7.42 1.42 5.77 0 243.22 135.4 31079 +1990 11 6.22 0.22 4.57 0 225.61 137.21 31171 +1990 12 6.81 0.81 5.16 0.01 234.13 103.36 31266 +1990 13 6.83 0.83 5.18 0 234.42 139.4 31366 +1990 14 2.68 -3.32 1.03 0 179.91 143.45 31469 +1990 15 1.07 -4.93 -0.58 0 161.92 145.73 31575 +1990 16 0.94 -5.06 -0.71 0.02 160.54 110.32 31686 +1990 17 0.82 -5.18 -0.83 0.13 159.27 111.63 31800 +1990 18 0.7 -5.3 -0.95 0.12 158.01 113.11 31917 +1990 19 2.75 -3.25 1.1 0 180.73 151.67 32038 +1990 20 10.56 4.56 8.91 0 294.97 147.49 32161 +1990 21 10.17 4.17 8.52 0.01 288.07 112.37 32289 +1990 22 8.5 2.5 6.85 0.02 260.06 114.75 32419 +1990 23 6.17 0.17 4.52 0 224.9 156.58 32552 +1990 24 8.07 2.07 6.42 0 253.24 157.15 32688 +1990 25 3.95 -2.05 2.3 0 195.29 162.03 32827 +1990 26 1.12 -4.88 -0.53 0 162.45 165.63 32969 +1990 27 0.11 -5.89 -1.54 0 151.95 168.19 33114 +1990 28 -0.39 -6.39 -2.04 0 146.97 170.67 33261 +1990 29 -1.77 -7.77 -3.42 0 133.96 173.72 33411 +1990 30 -2.42 -8.42 -4.07 0 128.18 176.28 33564 +1990 31 -1.66 -7.66 -3.31 0.1 134.96 173.19 33718 +1990 32 9.04 3.04 7.39 0 268.85 173.2 33875 +1990 33 7.02 1.02 5.37 0.97 237.22 133.2 34035 +1990 34 5.33 -0.67 3.68 1.91 213.27 135.86 34196 +1990 35 4.54 -1.46 2.89 0 202.81 183.87 34360 +1990 36 2.19 -3.81 0.54 0.01 174.26 140.99 34526 +1990 37 2.13 -3.87 0.48 0.03 173.58 142.84 34694 +1990 38 5.54 -0.46 3.89 0 216.13 190.77 34863 +1990 39 5.62 -0.38 3.97 0 217.23 193.31 35035 +1990 40 11.71 5.71 10.06 0 316.16 189.85 35208 +1990 41 13.83 7.83 12.18 0.09 358.63 142.26 35383 +1990 42 12.82 6.82 11.17 0 337.82 193.5 35560 +1990 43 12.15 6.15 10.5 0 324.6 196.99 35738 +1990 44 16.88 10.88 15.23 0 428.23 192.51 35918 +1990 45 17.86 11.86 16.21 0 452.91 193.28 36099 +1990 46 18.66 12.66 17.01 0 473.94 194.32 36282 +1990 47 15.92 9.92 14.27 0 405.18 201.86 36466 +1990 48 14.07 8.07 12.42 0.61 363.73 155.59 36652 +1990 49 9.55 3.55 7.9 0 277.38 216.07 36838 +1990 50 11.26 5.26 9.61 0 307.72 216.63 37026 +1990 51 6.9 0.9 5.25 0 235.45 224.46 37215 +1990 52 8.02 2.02 6.37 0.01 252.46 169.59 37405 +1990 53 5.6 -0.4 3.95 0 216.95 231.47 37596 +1990 54 5.25 -0.75 3.6 0 212.19 234.54 37788 +1990 55 5.14 -0.86 3.49 0 210.72 237.64 37981 +1990 56 6.92 0.92 5.27 0 235.74 238.61 38175 +1990 57 8.92 2.92 7.27 0 266.88 239.28 38370 +1990 58 14.27 8.27 12.62 0 368.03 234.67 38565 +1990 59 14.66 8.66 13.01 0 376.54 236.64 38761 +1990 60 16.09 10.09 14.44 0.04 409.18 177.65 38958 +1990 61 15.32 9.32 13.67 0.01 391.32 180.83 39156 +1990 62 13.2 7.2 11.55 1.03 345.53 185.55 39355 +1990 63 16.08 10.08 14.43 0 408.95 245.28 39553 +1990 64 15.22 9.22 13.57 0 389.05 249.69 39753 +1990 65 15.03 9.03 13.38 0 384.76 252.83 39953 +1990 66 13.01 7.01 11.36 0 341.66 258.97 40154 +1990 67 11 5 9.35 0.01 302.93 198.68 40355 +1990 68 13.68 7.68 12.03 0 355.47 263.49 40556 +1990 69 15.04 9.04 13.39 0.53 384.99 197.69 40758 +1990 70 13.88 7.88 12.23 0.63 359.69 201.35 40960 +1990 71 8.37 2.37 6.72 0.77 257.98 209.74 41163 +1990 72 8.62 2.62 6.97 0 261.99 282.14 41366 +1990 73 8.44 2.44 6.79 0.07 259.1 213.78 41569 +1990 74 15.77 9.77 14.12 0.03 401.68 206.77 41772 +1990 75 16.65 10.65 15 0 422.61 276.48 41976 +1990 76 15.54 9.54 13.89 0.82 396.35 211.02 42179 +1990 77 8.05 2.05 6.4 0.04 252.93 222.18 42383 +1990 78 8.85 2.85 7.2 0.1 265.73 223.38 42587 +1990 79 13 7 11.35 0 341.45 294.01 42791 +1990 80 12.29 6.29 10.64 0 327.32 297.75 42996 +1990 81 12.98 6.98 11.33 0.11 341.05 224.3 43200 +1990 82 9.23 3.23 7.58 0 272 307.78 43404 +1990 83 9.3 3.3 7.65 0 273.17 310.17 43608 +1990 84 10.13 4.13 8.48 0 287.37 311.45 43812 +1990 85 11.86 5.86 10.21 0 319.01 311.09 44016 +1990 86 10.62 4.62 8.97 0.2 296.05 236.67 44220 +1990 87 13.48 7.48 11.83 0 351.3 313 44424 +1990 88 13.9 7.9 12.25 0 360.11 314.49 44627 +1990 89 12.57 6.57 10.92 0 332.83 319.29 44831 +1990 90 13.47 7.47 11.82 0 351.09 319.91 45034 +1990 91 16.49 10.49 14.84 0 418.74 315.59 45237 +1990 92 21.9 15.9 20.25 0.07 567.85 227.01 45439 +1990 93 18.8 12.8 17.15 0 477.71 314.01 45642 +1990 94 18.02 12.02 16.37 0.55 457.05 238.63 45843 +1990 95 13.99 7.99 12.34 1.24 362.02 247.28 46045 +1990 96 14.67 8.67 13.02 0.1 376.76 247.75 46246 +1990 97 12.59 6.59 10.94 0.31 333.23 252.47 46446 +1990 98 7.98 1.98 6.33 1.7 251.83 259.77 46647 +1990 99 10.27 4.27 8.62 0.18 289.83 258.59 46846 +1990 100 11.38 5.38 9.73 0.03 309.95 258.6 47045 +1990 101 10.32 4.32 8.67 0 290.71 348.6 47243 +1990 102 12.51 6.51 10.86 0 331.65 346.49 47441 +1990 103 10.78 4.78 9.13 0 298.93 351.56 47638 +1990 104 8.99 2.99 7.34 0.03 268.03 267.31 47834 +1990 105 13.31 7.31 11.66 1.22 347.78 262.73 48030 +1990 106 11.75 5.75 10.1 0.47 316.91 266.3 48225 +1990 107 6.07 0.07 4.42 0 223.49 365.88 48419 +1990 108 7.67 1.67 6.02 0 247.03 365.4 48612 +1990 109 8.21 2.21 6.56 0.01 255.44 274.66 48804 +1990 110 7.54 1.54 5.89 0 245.04 368.67 48995 +1990 111 10.83 4.83 9.18 0 299.83 364.81 49185 +1990 112 9.44 3.44 7.79 0.1 275.52 276.59 49374 +1990 113 11.95 5.95 10.3 0 320.74 365.56 49561 +1990 114 16.36 10.36 14.71 0 415.61 357.07 49748 +1990 115 17.71 11.71 16.06 0 449.06 354.85 49933 +1990 116 15.8 9.8 14.15 0.23 402.38 270.83 50117 +1990 117 15.43 9.43 13.78 0.29 393.83 272.49 50300 +1990 118 15.03 9.03 13.38 0 384.76 365.6 50481 +1990 119 13.79 7.79 12.14 0 357.78 369.67 50661 +1990 120 11.23 5.23 9.58 0.06 307.16 282.13 50840 +1990 121 19.5 13.5 17.85 0 496.92 356.69 51016 +1990 122 19.95 13.95 18.3 0 509.61 356.41 51191 +1990 123 16.64 10.64 14.99 0.61 422.37 275.39 51365 +1990 124 14.05 8.05 12.4 0.3 363.3 281.02 51536 +1990 125 19.62 13.62 17.97 0 500.28 360.48 51706 +1990 126 16.59 10.59 14.94 0 421.16 370.35 51874 +1990 127 19.03 13.03 17.38 0.52 483.95 273.13 52039 +1990 128 16.85 10.85 15.2 0 427.5 371.51 52203 +1990 129 17.11 11.11 15.46 0 433.92 371.64 52365 +1990 130 19.04 13.04 17.39 0 484.22 366.73 52524 +1990 131 19.16 13.16 17.51 0 487.51 367.13 52681 +1990 132 17.94 11.94 16.29 0 454.98 371.65 52836 +1990 133 21.19 15.19 19.54 0 546.02 361.84 52989 +1990 134 17.4 11.4 15.75 0.57 441.18 280.96 53138 +1990 135 16.03 10.03 14.38 0 407.77 379.07 53286 +1990 136 16.39 10.39 14.74 0 416.33 378.75 53430 +1990 137 24.8 18.8 23.15 0 664.85 350.25 53572 +1990 138 25.83 19.83 24.18 0 702.51 346.2 53711 +1990 139 23.39 17.39 21.74 0 616.06 357.4 53848 +1990 140 24.45 18.45 22.8 0 652.44 353.45 53981 +1990 141 22.7 16.7 21.05 0 593.32 361.01 54111 +1990 142 19.88 13.88 18.23 0 507.62 371.66 54238 +1990 143 20.81 14.81 19.16 0 534.64 369.01 54362 +1990 144 23.42 17.42 21.77 0.28 617.07 269.7 54483 +1990 145 21.42 15.42 19.77 0.57 553.01 275.82 54600 +1990 146 19.44 13.44 17.79 0.01 495.25 281.2 54714 +1990 147 18.69 12.69 17.04 0 474.75 377.8 54824 +1990 148 19.29 13.29 17.64 0 491.09 376.28 54931 +1990 149 19.43 13.43 17.78 0.18 494.97 282.1 55034 +1990 150 17.77 11.77 16.12 0 450.6 381.63 55134 +1990 151 20.51 14.51 18.86 0 525.79 373.22 55229 +1990 152 19.5 13.5 17.85 0 496.92 376.73 55321 +1990 153 20.38 14.38 18.73 0.01 522 280.51 55409 +1990 154 20.19 14.19 18.54 0 516.49 374.98 55492 +1990 155 23.41 17.41 21.76 0 616.73 363.11 55572 +1990 156 26.51 20.51 24.86 0 728.36 349.59 55648 +1990 157 27.44 21.44 25.79 0 765.01 345.13 55719 +1990 158 23.79 17.79 22.14 0 629.58 362.18 55786 +1990 159 22.72 16.72 21.07 0 593.97 366.77 55849 +1990 160 23.52 17.52 21.87 0.05 620.43 272.79 55908 +1990 161 19.88 13.88 18.23 0 507.62 377.37 55962 +1990 162 21.59 15.59 19.94 0.29 558.23 278.54 56011 +1990 163 19.35 13.35 17.7 0.76 492.75 284.55 56056 +1990 164 15.73 9.73 14.08 0.77 400.75 292.57 56097 +1990 165 15.54 9.54 13.89 0.75 396.35 293.02 56133 +1990 166 19.19 13.19 17.54 0 488.33 380.13 56165 +1990 167 19.78 13.78 18.13 0 504.78 378.14 56192 +1990 168 17.99 11.99 16.34 0.04 456.27 287.93 56214 +1990 169 18.47 12.47 16.82 0.12 468.88 286.84 56231 +1990 170 19.36 13.36 17.71 0 493.03 379.62 56244 +1990 171 18.58 12.58 16.93 0 471.8 382.17 56252 +1990 172 20.04 14.04 18.39 0 512.18 377.4 56256 +1990 173 17.17 11.17 15.52 0 435.41 386.37 56255 +1990 174 18.44 12.44 16.79 0 468.08 382.49 56249 +1990 175 22.9 16.9 21.25 0 599.84 366.73 56238 +1990 176 25.13 19.13 23.48 0.1 676.72 267.93 56223 +1990 177 26.99 20.99 25.34 0.27 747.08 261.23 56203 +1990 178 27.17 21.17 25.52 0.74 754.21 260.58 56179 +1990 179 24.88 18.88 23.23 2.24 667.71 268.64 56150 +1990 180 19.8 13.8 18.15 1.46 505.35 283.31 56116 +1990 181 21.79 15.79 20.14 0 564.42 370.62 56078 +1990 182 26.36 20.36 24.71 0 722.59 351.01 56035 +1990 183 29.2 23.2 27.55 0 838.63 336.07 55987 +1990 184 23.72 17.72 22.07 0.21 627.2 271.9 55935 +1990 185 21.12 15.12 19.47 0.59 543.91 279.39 55879 +1990 186 22.67 16.67 21.02 0.16 592.35 274.83 55818 +1990 187 21.02 15.02 19.37 0 540.9 372.45 55753 +1990 188 24.77 18.77 23.12 0 663.78 357.26 55684 +1990 189 22.98 16.98 21.33 0 602.46 364.59 55611 +1990 190 22.25 16.25 20.6 0 578.87 367.08 55533 +1990 191 20.37 14.37 18.72 0 521.7 373.65 55451 +1990 192 17.64 11.64 15.99 0.27 447.27 286.53 55366 +1990 193 19.46 13.46 17.81 0.66 495.8 282.09 55276 +1990 194 21.39 15.39 19.74 0 552.1 369.24 55182 +1990 195 20.9 14.9 19.25 1.77 537.31 278.04 55085 +1990 196 24.72 18.72 23.07 0.26 661.99 266.45 54984 +1990 197 21.7 15.7 20.05 0 561.62 366.97 54879 +1990 198 22.33 16.33 20.68 0.01 581.42 273.14 54770 +1990 199 23.6 17.6 21.95 0.75 623.13 269.11 54658 +1990 200 23.41 17.41 21.76 0 616.73 359.19 54542 +1990 201 21.17 15.17 19.52 0 545.42 367.27 54423 +1990 202 21.75 15.75 20.1 0 563.17 364.6 54301 +1990 203 22.35 16.35 20.7 0 582.06 361.85 54176 +1990 204 25.52 19.52 23.87 0 690.99 348.16 54047 +1990 205 24.74 18.74 23.09 0.04 662.71 263.34 53915 +1990 206 26.98 20.98 25.33 0 746.69 340.25 53780 +1990 207 23.81 17.81 22.16 0 630.27 353.87 53643 +1990 208 26.06 20.06 24.41 0 711.17 343.39 53502 +1990 209 23.37 17.37 21.72 0 615.39 354.38 53359 +1990 210 21.82 15.82 20.17 1.69 565.35 269.78 53213 +1990 211 19.73 13.73 18.08 0 503.37 366.17 53064 +1990 212 22.67 16.67 21.02 0 592.35 354.97 52913 +1990 213 22.04 16.04 20.39 0 572.24 356.6 52760 +1990 214 23.35 17.35 21.7 0 614.73 350.84 52604 +1990 215 23.29 17.29 21.64 0.05 612.72 262.82 52445 +1990 216 20.61 14.61 18.96 0 528.72 359.25 52285 +1990 217 19.68 13.68 18.03 0 501.96 361.43 52122 +1990 218 14.4 8.4 12.75 0 370.85 375.19 51958 +1990 219 17.35 11.35 15.7 0 439.92 366.54 51791 +1990 220 21.08 15.08 19.43 0 542.7 353.96 51622 +1990 221 21.43 15.43 19.78 0 553.32 351.75 51451 +1990 222 20.6 14.6 18.95 0 528.43 353.56 51279 +1990 223 23.01 17.01 21.36 0 603.45 343.8 51105 +1990 224 21.57 15.57 19.92 0.01 557.61 261.03 50929 +1990 225 21.94 15.94 20.29 0.07 569.1 259.2 50751 +1990 226 26.22 20.22 24.57 0.15 717.24 245.39 50572 +1990 227 27.03 21.03 25.38 0.29 748.66 241.68 50392 +1990 228 27.67 21.67 26.02 0.18 774.3 238.52 50210 +1990 229 24.01 18.01 22.36 0 637.13 333.01 50026 +1990 230 22.1 16.1 20.45 0 574.13 338.98 49842 +1990 231 21.08 15.08 19.43 0 542.7 341.07 49656 +1990 232 24.25 18.25 22.6 0 645.44 328.1 49469 +1990 233 25.84 19.84 24.19 0 702.89 320.11 49280 +1990 234 24.83 18.83 23.18 0.01 665.92 242.27 49091 +1990 235 26.71 20.71 25.06 0 736.11 313.51 48900 +1990 236 27.04 21.04 25.39 0 749.06 310.67 48709 +1990 237 26.74 20.74 25.09 0 737.28 310.49 48516 +1990 238 29.52 23.52 27.87 0 852.64 295.47 48323 +1990 239 32.9 26.9 31.25 0.05 1013.05 206.21 48128 +1990 240 27.9 21.9 26.25 0.2 783.7 225.4 47933 +1990 241 25.76 19.76 24.11 0.54 699.9 231.37 47737 +1990 242 26.13 20.13 24.48 0 713.82 305.28 47541 +1990 243 26.04 20.04 24.39 0.15 710.41 227.94 47343 +1990 244 19.74 13.74 18.09 0.18 503.65 243.5 47145 +1990 245 21.44 15.44 19.79 1.59 553.62 238.16 46947 +1990 246 19.72 13.72 18.07 0.8 503.09 240.71 46747 +1990 247 21 15 19.35 0.29 540.3 236.42 46547 +1990 248 21.13 15.13 19.48 0 544.21 312.91 46347 +1990 249 21.24 15.24 19.59 0 547.53 310.55 46146 +1990 250 18.26 12.26 16.61 1.03 463.33 237.96 45945 +1990 251 19.87 13.87 18.22 0.35 507.33 233.03 45743 +1990 252 21.62 15.62 19.97 0 559.15 303.27 45541 +1990 253 19.97 13.97 18.32 0.36 510.18 229.66 45339 +1990 254 22.7 16.7 21.05 0 593.32 295.64 45136 +1990 255 19.87 13.87 18.22 0.51 507.33 226.63 44933 +1990 256 16.48 10.48 14.83 0.37 418.5 231.48 44730 +1990 257 17.08 11.08 15.43 0.49 433.18 228.8 44527 +1990 258 19.01 13.01 17.36 0.32 483.41 223.4 44323 +1990 259 18.14 12.14 16.49 0 460.18 297.72 44119 +1990 260 14.62 8.62 12.97 0 375.66 303.3 43915 +1990 261 14.15 8.15 12.5 0 365.44 301.77 43711 +1990 262 13.5 7.5 11.85 0.02 351.71 225.46 43507 +1990 263 16.01 10.01 14.36 0.18 407.3 219.79 43303 +1990 264 15.15 9.15 13.5 0.11 387.46 219.22 43099 +1990 265 17.11 11.11 15.46 0.19 433.92 214.27 42894 +1990 266 12.32 6.32 10.67 0.1 327.91 219.51 42690 +1990 267 11.22 5.22 9.57 0.58 306.98 218.82 42486 +1990 268 12.97 6.97 11.32 0.03 340.85 214.68 42282 +1990 269 14.48 8.48 12.83 0.25 372.59 210.71 42078 +1990 270 17.17 11.17 15.52 0 435.41 272.8 41875 +1990 271 16.56 10.56 14.91 0.38 420.43 203.65 41671 +1990 272 17.28 11.28 15.63 0 438.16 267.27 41468 +1990 273 16.08 10.08 14.43 0 408.95 267.3 41265 +1990 274 12.2 6.2 10.55 0.21 325.57 203.73 41062 +1990 275 16.05 10.05 14.4 0.66 408.24 196.48 40860 +1990 276 16.02 10.02 14.37 0.04 407.53 194.52 40658 +1990 277 13.68 7.68 12.03 0.38 355.47 195.76 40456 +1990 278 11.86 5.86 10.21 0 319.01 261.06 40255 +1990 279 14.76 8.76 13.11 0 378.75 253.46 40054 +1990 280 16.52 10.52 14.87 0 419.46 247.52 39854 +1990 281 16.91 10.91 15.26 0 428.97 244.07 39654 +1990 282 13.82 7.82 12.17 0 358.42 247 39455 +1990 283 15.52 9.52 13.87 0.87 395.89 180.94 39256 +1990 284 13.89 7.89 12.24 0.02 359.9 180.8 39058 +1990 285 16.49 10.49 14.84 1.2 418.74 175.41 38861 +1990 286 18.29 12.29 16.64 0.77 464.12 170.71 38664 +1990 287 17.11 11.11 15.46 1.07 433.92 170.33 38468 +1990 288 16.11 10.11 14.46 0 409.66 226.25 38273 +1990 289 13.04 7.04 11.39 0 342.26 228.69 38079 +1990 290 9.71 3.71 8.06 0 280.11 230.28 37885 +1990 291 12.92 6.92 11.27 0 339.83 223.32 37693 +1990 292 16.88 10.88 15.23 0 428.23 214.22 37501 +1990 293 16.33 10.33 14.68 0 414.89 212.53 37311 +1990 294 12.5 6.5 10.85 0 331.45 215.65 37121 +1990 295 16.32 10.32 14.67 0 414.65 206.96 36933 +1990 296 16.9 10.9 15.25 0 428.73 203.44 36745 +1990 297 15.99 9.99 14.34 0.12 406.83 151.75 36560 +1990 298 15.95 9.95 14.3 0.01 405.89 149.89 36375 +1990 299 9.78 3.78 8.13 0.2 281.31 154.12 36191 +1990 300 8.45 2.45 6.8 0 259.26 204.22 36009 +1990 301 8.47 2.47 6.82 0.01 259.58 151.25 35829 +1990 302 9.65 3.65 8 0 279.08 197.81 35650 +1990 303 12.08 6.08 10.43 0 323.24 192.43 35472 +1990 304 15.69 9.69 14.04 0 399.82 185.05 35296 +1990 305 7.8 1.8 6.15 0 249.03 191.84 35122 +1990 306 7.3 1.3 5.65 0 241.41 190.03 34950 +1990 307 6.4 0.4 4.75 0 228.18 188.28 34779 +1990 308 7.56 1.56 5.91 0 245.35 184.65 34610 +1990 309 6.51 0.51 4.86 0 229.76 183.22 34444 +1990 310 5.06 -0.94 3.41 0.82 209.65 136.42 34279 +1990 311 4.54 -1.46 2.89 0.24 202.81 135.05 34116 +1990 312 6.01 0.01 4.36 0.13 222.65 132.23 33956 +1990 313 5.39 -0.61 3.74 0 214.09 174.64 33797 +1990 314 6.84 0.84 5.19 0 234.57 171.55 33641 +1990 315 6.99 0.99 5.34 0 236.78 168.89 33488 +1990 316 4.79 -1.21 3.14 0 206.07 168.34 33337 +1990 317 8.49 2.49 6.84 0 259.9 163.25 33188 +1990 318 8.51 2.51 6.86 0.05 260.22 120.68 33042 +1990 319 7.87 1.87 6.22 0.45 250.12 119.81 32899 +1990 320 4.7 -1.3 3.05 1.17 204.89 120.18 32758 +1990 321 2.45 -3.55 0.8 1.59 177.24 119.63 32620 +1990 322 1.8 -4.2 0.15 0.1 169.87 118.51 32486 +1990 323 5.8 -0.2 4.15 0 219.72 153.91 32354 +1990 324 10.55 4.55 8.9 0 294.79 148.01 32225 +1990 325 10.15 4.15 8.5 0 287.72 146.68 32100 +1990 326 11.09 5.09 9.44 0 304.58 144.37 31977 +1990 327 10.3 4.3 8.65 0 290.36 143.29 31858 +1990 328 13.67 7.67 12.02 0 355.26 137.99 31743 +1990 329 13.71 7.71 12.06 0.33 356.1 102.37 31631 +1990 330 11.73 5.73 10.08 1.36 316.53 102.84 31522 +1990 331 16.26 10.26 14.61 0.11 413.22 98.13 31417 +1990 332 17.89 11.89 16.24 0.1 453.69 95.35 31316 +1990 333 19.64 13.64 17.99 0.38 500.84 92.7 31218 +1990 334 16.89 10.89 15.24 0.31 428.48 94.81 31125 +1990 335 7.65 1.65 6 0 246.72 134.33 31035 +1990 336 7.05 1.05 5.4 0 237.67 133.69 30949 +1990 337 5.04 -0.96 3.39 0 209.38 133.34 30867 +1990 338 2.62 -3.38 0.97 0 179.21 133.75 30790 +1990 339 3.55 -2.45 1.9 0 190.33 132.47 30716 +1990 340 5.83 -0.17 4.18 0 220.13 130.39 30647 +1990 341 8.34 2.34 6.69 0.06 257.5 95.83 30582 +1990 342 8.55 2.55 6.9 0 260.86 126.86 30521 +1990 343 11.33 5.33 9.68 0 309.02 123.8 30465 +1990 344 8.28 2.28 6.63 0 256.55 125.13 30413 +1990 345 7.79 1.79 6.14 0 248.88 125.05 30366 +1990 346 9.44 3.44 7.79 0 275.52 123.29 30323 +1990 347 3.67 -2.33 2.02 0.02 191.8 94.83 30284 +1990 348 6.92 0.92 5.27 0.37 235.74 93.12 30251 +1990 349 4.86 -1.14 3.21 0.18 206.99 93.79 30221 +1990 350 3.98 -2.02 2.33 0 195.67 125.21 30197 +1990 351 1.37 -4.63 -0.28 0.02 165.15 94.72 30177 +1990 352 1.44 -4.56 -0.21 0.17 165.91 94.62 30162 +1990 353 4.09 -1.91 2.44 0.64 197.05 93.58 30151 +1990 354 -0.29 -6.29 -1.94 0 147.96 126.81 30145 +1990 355 -1.32 -7.32 -2.97 0 138.09 127.21 30144 +1990 356 1.71 -4.29 0.06 0.13 168.88 94.47 30147 +1990 357 -2.8 -8.8 -4.45 0 124.9 127.83 30156 +1990 358 -4.57 -10.57 -6.22 0 110.58 128.49 30169 +1990 359 -6.29 -12.29 -7.94 0 98.05 129.1 30186 +1990 360 -3.46 -9.46 -5.11 0 119.39 128.63 30208 +1990 361 -3.84 -9.84 -5.49 0.07 116.3 140.7 30235 +1990 362 2.96 -3.04 1.31 0 183.21 126.76 30267 +1990 363 5.26 -0.74 3.61 0 212.33 126.08 30303 +1990 364 2.93 -3.07 1.28 0.29 182.85 95.82 30343 +1990 365 4.8 -1.2 3.15 1.31 206.2 95.48 30388 +1991 1 6.54 0.54 4.89 0.01 230.2 95.35 30438 +1991 2 6.98 0.98 5.33 0 236.63 127.56 30492 +1991 3 5.01 -0.99 3.36 0 208.98 129.75 30551 +1991 4 2.51 -3.49 0.86 0 177.93 132.03 30614 +1991 5 0.7 -5.3 -0.95 0 158.01 133.55 30681 +1991 6 3.84 -2.16 2.19 0 193.91 132.86 30752 +1991 7 1.38 -4.62 -0.27 0 165.26 134.93 30828 +1991 8 -2.29 -8.29 -3.94 0 129.32 137.98 30907 +1991 9 -0.18 -6.18 -1.83 0 149.05 138.4 30991 +1991 10 2.28 -3.72 0.63 0.01 175.29 103.91 31079 +1991 11 5.59 -0.41 3.94 0 216.82 137.62 31171 +1991 12 2.19 -3.81 0.54 0 174.26 140.6 31266 +1991 13 4.56 -1.44 2.91 0 203.07 140.89 31366 +1991 14 1.88 -4.12 0.23 0 170.77 143.87 31469 +1991 15 3.44 -2.56 1.79 0 188.98 144.47 31575 +1991 16 2.43 -3.57 0.78 0 177.01 146.32 31686 +1991 17 4.9 -1.1 3.25 0.55 207.52 109.91 31800 +1991 18 5.34 -0.66 3.69 0 213.41 148.16 31917 +1991 19 4.52 -1.48 2.87 0 202.55 150.61 32038 +1991 20 7.79 1.79 6.14 0 248.88 149.87 32161 +1991 21 7.02 1.02 5.37 0 237.22 152.46 32289 +1991 22 6.81 0.81 5.16 0 234.13 154.35 32419 +1991 23 7.18 1.18 5.53 0.17 239.61 116.86 32552 +1991 24 7.08 1.08 5.43 0.61 238.11 118.46 32688 +1991 25 6.01 0.01 4.36 0 222.65 160.62 32827 +1991 26 3.8 -2.2 2.15 0 193.42 164.06 32969 +1991 27 -2.55 -8.55 -4.2 0.03 127.05 167.01 33114 +1991 28 -1.65 -7.65 -3.3 0.08 135.05 168.45 33261 +1991 29 -1.2 -7.2 -2.85 0.01 139.21 169.95 33411 +1991 30 1.74 -4.26 0.09 0.01 169.21 170.11 33564 +1991 31 1.67 -4.33 0.02 0 168.43 176.62 33718 +1991 32 2.92 -3.08 1.27 0.55 182.73 133.49 33875 +1991 33 -1.16 -7.16 -2.81 0.15 139.58 176.39 34035 +1991 34 3.89 -2.11 2.24 0 194.54 182.18 34196 +1991 35 5.46 -0.54 3.81 0 215.04 183.18 34360 +1991 36 0.73 -5.27 -0.92 0.11 158.33 141.64 34526 +1991 37 4.48 -1.52 2.83 0.02 202.04 141.64 34694 +1991 38 2.09 -3.91 0.44 0 173.13 193.24 34863 +1991 39 4.66 -1.34 3.01 0.04 204.37 145.55 35035 +1991 40 1.74 -4.26 0.09 0 169.21 198.72 35208 +1991 41 1.28 -4.72 -0.37 0 164.17 201.65 35383 +1991 42 -0.17 -6.17 -1.82 0 149.15 205.09 35560 +1991 43 5 -1 3.35 0 208.85 204.29 35738 +1991 44 1.41 -4.59 -0.24 0 165.58 209.46 35918 +1991 45 1.19 -4.81 -0.46 0.1 163.21 159.18 36099 +1991 46 2.76 -3.24 1.11 0 180.85 213.89 36282 +1991 47 -0.61 -6.61 -2.26 0 144.83 218.91 36466 +1991 48 1.29 -4.71 -0.36 0 164.28 220.57 36652 +1991 49 0.5 -5.5 -1.15 0 155.94 223.89 36838 +1991 50 3.42 -2.58 1.77 0.33 188.74 168.4 37026 +1991 51 4.73 -1.27 3.08 0.38 205.29 169.83 37215 +1991 52 0.1 -5.9 -1.55 0 151.85 232.71 37405 +1991 53 0.2 -5.8 -1.45 0 152.86 235.64 37596 +1991 54 -0.77 -6.77 -2.42 0 143.28 239.04 37788 +1991 55 -0.45 -6.45 -2.1 0 146.39 241.88 37981 +1991 56 -0.32 -6.32 -1.97 0 147.66 244.53 38175 +1991 57 -4.87 -10.87 -6.52 0.14 108.3 222.23 38370 +1991 58 -4.55 -10.55 -6.2 0 110.73 287.39 38565 +1991 59 -3.22 -9.22 -4.87 0 121.37 289.3 38761 +1991 60 6.68 0.68 5.03 0 232.23 250.24 38958 +1991 61 10.76 4.76 9.11 0 298.57 248.26 39156 +1991 62 12.91 6.91 11.26 0.11 339.63 185.89 39355 +1991 63 15.48 9.48 13.83 0 394.97 246.41 39553 +1991 64 13.62 7.62 11.97 0.11 354.21 189.36 39753 +1991 65 15.74 9.74 14.09 0 400.98 251.51 39953 +1991 66 15.26 9.26 13.61 0 389.95 255.05 40154 +1991 67 13.36 7.36 11.71 0.02 348.81 195.92 40355 +1991 68 13.51 7.51 11.86 0 351.92 263.78 40556 +1991 69 15.3 9.3 13.65 0 390.86 263.09 40758 +1991 70 14.97 8.97 13.32 0.02 383.42 199.85 40960 +1991 71 18.82 12.82 17.17 0 478.25 261.08 41163 +1991 72 18.31 12.31 16.66 0 464.64 264.96 41366 +1991 73 12.3 6.3 10.65 0 327.52 279.39 41569 +1991 74 9.08 3.08 7.43 0 269.51 286.93 41772 +1991 75 8.81 2.81 7.16 0.01 265.08 217.51 41976 +1991 76 9.21 3.21 7.56 0 271.67 292.09 42179 +1991 77 11.38 5.38 9.73 0 309.95 291.44 42383 +1991 78 13.33 7.33 11.68 0.14 348.2 218.05 42587 +1991 79 9.61 3.61 7.96 0 278.4 299.48 42791 +1991 80 8.79 2.79 7.14 0.24 264.75 227.38 42996 +1991 81 3.88 -2.12 2.23 0 194.41 311.65 43200 +1991 82 3.04 -2.96 1.39 0.12 184.16 236.38 43404 +1991 83 5.97 -0.03 4.32 0.14 222.09 235.92 43608 +1991 84 4.76 -1.24 3.11 0 205.68 318.5 43812 +1991 85 5.51 -0.49 3.86 0 215.72 320.18 44016 +1991 86 7.41 1.41 5.76 0.44 243.07 240.19 44220 +1991 87 12.58 6.58 10.93 0.07 333.03 236.02 44424 +1991 88 9.95 3.95 8.3 0.31 284.24 241.12 44627 +1991 89 7.18 1.18 5.53 0 239.61 327.77 44831 +1991 90 8.51 2.51 6.86 0.04 260.22 246.23 45034 +1991 91 7.47 1.47 5.82 0 243.98 332.05 45237 +1991 92 9.54 3.54 7.89 0 277.21 331.28 45439 +1991 93 8.67 2.67 7.02 0 262.8 334.83 45642 +1991 94 9.78 3.78 8.13 0 281.31 335.28 45843 +1991 95 14.02 8.02 12.37 0 362.66 329.64 46045 +1991 96 11.8 5.8 10.15 0 317.87 336.07 46246 +1991 97 8.81 2.81 7.16 0 265.08 343.14 46446 +1991 98 6.76 0.76 5.11 0 233.39 348.07 46647 +1991 99 8.94 2.94 7.29 0 267.2 346.95 46846 +1991 100 10.01 4.01 8.36 0 285.28 347.19 47045 +1991 101 14.22 8.22 12.57 1 366.95 255.81 47243 +1991 102 18.13 12.13 16.48 0.14 459.92 250.04 47441 +1991 103 17.94 11.94 16.29 0 454.98 335.69 47638 +1991 104 17.17 11.17 15.52 0.42 435.41 254.64 47834 +1991 105 20.42 14.42 18.77 0 523.16 331.9 48030 +1991 106 15.94 9.94 14.29 0.03 405.65 259.49 48225 +1991 107 18.95 12.95 17.3 0 481.77 339.55 48419 +1991 108 22.06 16.06 20.41 0.1 572.86 248.43 48612 +1991 109 16.37 10.37 14.72 0 415.85 349.86 48804 +1991 110 12.44 6.44 10.79 0.01 330.27 270.12 48995 +1991 111 11.7 5.7 10.05 0 315.97 363.17 49185 +1991 112 13.23 7.23 11.58 0.25 346.14 271.2 49374 +1991 113 12.74 6.74 11.09 0 336.22 363.97 49561 +1991 114 13.92 7.92 12.27 0 360.53 362.92 49748 +1991 115 6.29 0.29 4.64 0.13 226.61 283.47 49933 +1991 116 8.22 2.22 6.57 0.17 255.6 282.26 50117 +1991 117 6.27 0.27 4.62 0 226.32 380.59 50300 +1991 118 5.3 -0.7 3.65 0.01 212.87 287.44 50481 +1991 119 7.89 1.89 6.24 0 250.43 380.77 50661 +1991 120 9.77 3.77 8.12 0 281.14 378.86 50840 +1991 121 12.15 6.15 10.5 0 324.6 375.49 51016 +1991 122 12.93 6.93 11.28 0 340.04 375.07 51191 +1991 123 13.23 7.23 11.58 0.14 346.14 281.59 51365 +1991 124 15.88 9.88 14.23 0.51 404.24 277.68 51536 +1991 125 16.06 10.06 14.41 1.2 408.48 278.07 51706 +1991 126 15.77 9.77 14.12 1.13 401.68 279.37 51874 +1991 127 17.86 11.86 16.21 0.16 452.91 275.76 52039 +1991 128 18.3 12.3 16.65 0 464.38 367.37 52203 +1991 129 18.08 12.08 16.43 0.44 458.62 276.64 52365 +1991 130 18 12 16.35 0.6 456.53 277.41 52524 +1991 131 17.86 11.86 16.21 0.52 452.91 278.3 52681 +1991 132 16.87 10.87 15.22 0.05 427.99 281.02 52836 +1991 133 9.81 3.81 8.16 0.91 281.82 293.49 52989 +1991 134 10.55 4.55 8.9 0.13 294.79 293.01 53138 +1991 135 12.17 6.17 10.52 0.2 324.99 291.13 53286 +1991 136 17.23 11.23 15.58 1.52 436.91 282.32 53430 +1991 137 14.21 8.21 12.56 0.46 366.73 288.73 53572 +1991 138 17.35 11.35 15.7 0.82 439.92 283.04 53711 +1991 139 13.86 7.86 12.21 0.32 359.26 290.33 53848 +1991 140 17.75 11.75 16.1 0 450.08 377.4 53981 +1991 141 20.65 14.65 19 0 529.9 368.55 54111 +1991 142 21.75 15.75 20.1 0.1 563.17 273.82 54238 +1991 143 17.66 11.66 16.01 0.73 447.78 284.34 54362 +1991 144 15.36 9.36 13.71 1.88 392.23 289.43 54483 +1991 145 13.37 7.37 11.72 1.65 349.02 293.39 54600 +1991 146 14.99 8.99 13.34 0.71 383.87 290.78 54714 +1991 147 13.93 7.93 12.28 0.07 360.75 293.07 54824 +1991 148 13.49 7.49 11.84 0.26 351.51 294.13 54931 +1991 149 9.77 3.77 8.12 0.35 281.14 300.11 55034 +1991 150 7.66 1.66 6.01 0.31 246.88 303.09 55134 +1991 151 12.92 6.92 11.27 0.03 339.83 295.89 55229 +1991 152 25.56 19.56 23.91 0 692.47 353.06 55321 +1991 153 26.28 20.28 24.63 0.02 719.53 262.44 55409 +1991 154 23.65 17.65 22 0.46 624.82 271.46 55492 +1991 155 22.19 16.19 20.54 1.17 576.97 275.95 55572 +1991 156 19.91 13.91 18.26 0.15 508.47 282.33 55648 +1991 157 17.59 11.59 15.94 0.21 446 287.93 55719 +1991 158 17.15 11.15 15.5 0 434.92 385.36 55786 +1991 159 15.59 9.59 13.94 0.15 397.51 292.41 55849 +1991 160 15.55 9.55 13.9 0.03 396.58 292.63 55908 +1991 161 16.21 10.21 14.56 0.3 412.03 291.36 55962 +1991 162 18.13 12.13 16.48 0 459.92 383.02 56011 +1991 163 17.47 11.47 15.82 0.64 442.95 288.91 56056 +1991 164 16.8 10.8 15.15 0 426.27 387.18 56097 +1991 165 18.42 12.42 16.77 0.01 467.55 286.87 56133 +1991 166 19.83 13.83 18.18 0 506.2 378.03 56165 +1991 167 21.13 15.13 19.48 0 544.21 373.45 56192 +1991 168 19.73 13.73 18.08 0 503.37 378.39 56214 +1991 169 19.18 13.18 17.53 0.06 488.06 285.15 56231 +1991 170 22.9 16.9 21.25 0 599.84 366.81 56244 +1991 171 24.64 18.64 22.99 0.15 659.15 269.69 56252 +1991 172 24.2 18.2 22.55 0.12 643.7 271.11 56256 +1991 173 27.39 21.39 25.74 0.01 763 259.9 56255 +1991 174 25.8 19.8 24.15 0 701.39 354.22 56249 +1991 175 24.17 18.17 22.52 0 642.66 361.49 56238 +1991 176 26.12 20.12 24.47 0 713.44 352.65 56223 +1991 177 27.79 21.79 26.14 0 779.19 344.23 56203 +1991 178 23.29 17.29 21.64 0 612.72 365.05 56179 +1991 179 23.47 17.47 21.82 0.05 618.75 273.16 56150 +1991 180 18.73 12.73 17.08 0.09 475.82 285.91 56116 +1991 181 17.41 11.41 15.76 0.41 441.43 288.86 56078 +1991 182 23.26 17.26 21.61 1.79 611.72 273.56 56035 +1991 183 23.69 17.69 22.04 0.24 626.18 272.1 55987 +1991 184 24.42 18.42 22.77 0.45 651.39 269.67 55935 +1991 185 26.94 20.94 25.29 2.93 745.11 260.84 55879 +1991 186 26.33 20.33 24.68 1.82 721.44 262.89 55818 +1991 187 29.01 23.01 27.36 1.66 830.4 252.38 55753 +1991 188 30.42 24.42 28.77 0.39 893.1 246.12 55684 +1991 189 31.31 25.31 29.66 0 934.69 322.57 55611 +1991 190 26.94 20.94 25.29 0 745.11 346.58 55533 +1991 191 25.39 19.39 23.74 0.11 686.21 265.27 55451 +1991 192 22.06 16.06 20.41 1.15 572.86 275.43 55366 +1991 193 21.31 15.31 19.66 0.26 549.66 277.31 55276 +1991 194 21.94 15.94 20.29 0 569.1 367.21 55182 +1991 195 24.85 18.85 23.2 0.14 666.63 266.31 55085 +1991 196 29.15 23.15 27.5 0 836.46 333.37 54984 +1991 197 25.11 19.11 23.46 0.12 676 264.82 54879 +1991 198 25.61 19.61 23.96 0 694.32 350.43 54770 +1991 199 23.67 17.67 22.02 0.02 625.5 268.89 54658 +1991 200 24.91 18.91 23.26 1.83 668.79 264.64 54542 +1991 201 21.93 15.93 20.28 0.06 568.78 273.37 54423 +1991 202 23.57 17.57 21.92 0 622.12 357.53 54301 +1991 203 24.47 18.47 22.82 0 653.15 353.27 54176 +1991 204 28.93 22.93 27.28 0.04 826.96 248.38 54047 +1991 205 26.09 20.09 24.44 0.93 712.3 258.78 53915 +1991 206 21.8 15.8 20.15 0.04 564.73 271.76 53780 +1991 207 20.41 14.41 18.76 0.07 522.87 274.96 53643 +1991 208 24.79 18.79 23.14 1.05 664.49 261.82 53502 +1991 209 25.63 19.63 23.98 0.11 695.06 258.55 53359 +1991 210 23.46 17.46 21.81 0.37 618.41 265.06 53213 +1991 211 22.84 16.84 21.19 0.06 597.88 266.32 53064 +1991 212 23.85 17.85 22.2 0.16 631.63 262.72 52913 +1991 213 23.78 17.78 22.13 0 629.24 349.84 52760 +1991 214 25.82 19.82 24.17 1.02 702.14 255.25 52604 +1991 215 24.55 18.55 22.9 0 655.97 345.27 52445 +1991 216 25.71 19.71 24.06 0 698.04 339.22 52285 +1991 217 25.25 19.25 23.6 0 681.09 340.41 52122 +1991 218 26.19 20.19 24.54 0.13 716.1 251.56 51958 +1991 219 24.86 18.86 23.21 0.37 666.99 255.23 51791 +1991 220 20.14 14.14 18.49 0.61 515.05 267.85 51622 +1991 221 21.28 15.28 19.63 0 548.75 352.27 51451 +1991 222 20.42 14.42 18.77 1 523.16 265.62 51279 +1991 223 26.46 20.46 24.81 0.24 726.43 246.94 51105 +1991 224 25.13 19.13 23.48 0.04 676.72 250.63 50929 +1991 225 25.33 19.33 23.68 0.16 684.01 249.16 50751 +1991 226 24.35 18.35 22.7 0 648.93 335.24 50572 +1991 227 25.73 19.73 24.08 0 698.78 328.16 50392 +1991 228 22.63 16.63 20.98 0.26 591.05 254.64 50210 +1991 229 24.34 18.34 22.69 0.01 648.58 248.76 50026 +1991 230 21.3 15.3 19.65 0 549.35 341.78 49842 +1991 231 21.27 15.27 19.62 0 548.44 340.43 49656 +1991 232 21.23 15.23 19.58 0 547.23 339.23 49469 +1991 233 23.64 17.64 21.99 0.59 624.48 246.85 49280 +1991 234 23.63 17.63 21.98 0.02 624.15 245.85 49091 +1991 235 24.44 18.44 22.79 0 652.09 323.18 48900 +1991 236 26.35 20.35 24.7 0.12 722.21 235.34 48709 +1991 237 27.55 21.55 25.9 0.33 769.44 230.07 48516 +1991 238 22.89 16.89 21.24 0.6 599.51 243.39 48323 +1991 239 21.17 15.17 19.52 0.01 545.42 246.74 48128 +1991 240 22.63 16.63 20.98 0.29 591.05 241.7 47933 +1991 241 17.77 11.77 16.12 0 450.6 335.65 47737 +1991 242 19.95 13.95 18.3 1.16 509.61 245.76 47541 +1991 243 17.75 11.75 16.1 0.64 450.08 249.06 47343 +1991 244 13.7 7.7 12.05 0 355.89 339.81 47145 +1991 245 17.48 11.48 15.83 0.01 443.2 246.83 46947 +1991 246 19.79 13.79 18.14 0.53 505.07 240.56 46747 +1991 247 20.22 14.22 18.57 0 517.36 317.63 46547 +1991 248 22.41 16.41 20.76 0 583.98 308.72 46347 +1991 249 22.05 16.05 20.4 1.08 572.55 230.94 46146 +1991 250 19.32 13.32 17.67 0.85 491.92 235.78 45945 +1991 251 20.9 14.9 19.25 0 537.31 307.63 45743 +1991 252 25.42 19.42 23.77 0 687.31 289.8 45541 +1991 253 24 18 22.35 0.25 636.78 219.86 45339 +1991 254 20.53 14.53 18.88 0 526.38 302.48 45136 +1991 255 20.24 14.24 18.59 0.07 517.94 225.84 44933 +1991 256 19.57 13.57 17.92 0.17 498.88 225.59 44730 +1991 257 21.21 15.21 19.56 0 546.63 293.92 44527 +1991 258 22.65 16.65 21 0 591.7 287.12 44323 +1991 259 26.86 20.86 25.21 0.96 741.97 202.05 44119 +1991 260 25.11 19.11 23.46 0.22 676 205.5 43915 +1991 261 25.96 19.96 24.31 0.29 707.39 201.38 43711 +1991 262 21.84 15.84 20.19 1.07 565.97 210.31 43507 +1991 263 18.74 12.74 17.09 0.51 476.09 214.99 43303 +1991 264 17.22 11.22 15.57 0.44 436.66 215.84 43099 +1991 265 14.6 8.6 12.95 0.16 375.22 218.26 42894 +1991 266 16.12 10.12 14.47 0.2 409.89 214.06 42690 +1991 267 18.43 12.43 16.78 0 467.81 277.49 42486 +1991 268 22.2 16.2 20.55 0 577.29 264.81 42282 +1991 269 19.21 13.21 17.56 0 488.88 270.58 42078 +1991 270 19.39 13.39 17.74 0 493.86 267.56 41875 +1991 271 15.23 9.23 13.58 0 389.27 274.24 41671 +1991 272 16.28 10.28 14.63 0 413.7 269.41 41468 +1991 273 19.55 13.55 17.9 0 498.32 259.49 41265 +1991 274 16.83 10.83 15.18 0.02 427.01 197.33 41062 +1991 275 13.89 7.89 12.24 0.81 359.9 199.51 40860 +1991 276 14.08 8.08 12.43 0.03 363.94 197.24 40658 +1991 277 11.81 5.81 10.16 0.02 318.06 198.03 40456 +1991 278 11.15 5.15 9.5 0 305.68 262.12 40255 +1991 279 13.28 7.28 11.63 0.01 347.17 192 40054 +1991 280 15.26 9.26 13.61 1.54 389.95 187.44 39854 +1991 281 8.44 2.44 6.79 0.5 259.1 193.04 39654 +1991 282 9.87 3.87 8.22 0.05 282.86 189.61 39455 +1991 283 12.73 6.73 11.08 0 336.02 245.92 39256 +1991 284 11.18 5.18 9.53 0.04 306.24 183.86 39058 +1991 285 12.53 6.53 10.88 0.02 332.04 180.41 38861 +1991 286 16.96 10.96 15.31 0 430.2 230.27 38664 +1991 287 17.67 11.67 16.02 0 448.04 226.01 38468 +1991 288 14.09 8.09 12.44 0 364.16 229.69 38273 +1991 289 14.19 8.19 12.54 0 366.3 226.92 38079 +1991 290 14.33 8.33 12.68 0 369.33 223.86 37885 +1991 291 14.99 8.99 13.34 0 383.87 220.12 37693 +1991 292 15.39 9.39 13.74 0 392.91 216.82 37501 +1991 293 11.15 5.15 9.5 0.53 305.68 165.24 37311 +1991 294 13.13 7.13 11.48 0.12 344.1 161.07 37121 +1991 295 12.92 6.92 11.27 1.66 339.83 159.18 36933 +1991 296 11.11 5.11 9.46 0 304.95 212.05 36745 +1991 297 11.15 5.15 9.5 0.43 305.68 156.96 36560 +1991 298 6.45 0.45 4.8 0.03 228.9 158.75 36375 +1991 299 4.79 -1.21 3.14 0 206.07 210.26 36191 +1991 300 9.09 3.09 7.44 0.31 269.68 152.67 36009 +1991 301 7.68 1.68 6.03 0.05 247.19 151.83 35829 +1991 302 10.73 4.73 9.08 0 298.03 196.61 35650 +1991 303 13.29 7.29 11.64 0 347.37 190.88 35472 +1991 304 12.22 6.22 10.57 0 325.96 189.82 35296 +1991 305 9.73 3.73 8.08 0.26 280.45 142.45 35122 +1991 306 9.68 3.68 8.03 0.51 279.6 140.8 34950 +1991 307 14.71 8.71 13.06 0.43 377.64 134.38 34779 +1991 308 15.75 9.75 14.1 0.04 401.21 131.35 34610 +1991 309 17.41 11.41 15.76 0.11 441.43 127.76 34444 +1991 310 15.18 9.18 13.53 0 388.14 171.34 34279 +1991 311 11.06 5.06 9.41 0.08 304.03 130.72 34116 +1991 312 12.45 6.45 10.8 0 330.46 170.12 33956 +1991 313 10.63 4.63 8.98 0 296.23 170.03 33797 +1991 314 7.18 1.18 5.53 0 239.61 171.27 33641 +1991 315 8.43 2.43 6.78 0 258.94 167.67 33488 +1991 316 8.09 2.09 6.44 0.17 253.55 124.34 33337 +1991 317 9.42 3.42 7.77 0.61 275.19 121.81 33188 +1991 318 8.23 2.23 6.58 0.1 255.76 120.86 33042 +1991 319 9.37 3.37 7.72 0.14 274.35 118.84 32899 +1991 320 8.53 2.53 6.88 0.8 260.54 118 32758 +1991 321 12.06 6.06 10.41 0.03 322.85 113.92 32620 +1991 322 9.95 3.95 8.3 0.01 284.24 114.14 32486 +1991 323 8.24 2.24 6.59 0 255.92 152.06 32354 +1991 324 7.16 1.16 5.51 0.45 239.31 113.15 32225 +1991 325 4.19 -1.81 2.54 0.34 198.32 113.39 32100 +1991 326 3.94 -2.06 2.29 0 195.16 149.87 31977 +1991 327 4.92 -1.08 3.27 0 207.79 147.4 31858 +1991 328 6.42 0.42 4.77 0 228.47 144.42 31743 +1991 329 3.75 -2.25 2.1 0.13 192.79 108.48 31631 +1991 330 4.22 -1.78 2.57 0 198.7 142.91 31522 +1991 331 3.02 -2.98 1.37 0.13 183.92 106.7 31417 +1991 332 -0.23 -6.23 -1.88 0 148.55 142.22 31316 +1991 333 2.77 -3.23 1.12 0 180.96 139.66 31218 +1991 334 7.22 1.22 5.57 0 240.2 135.81 31125 +1991 335 0.26 -5.74 -1.39 0 153.47 138.59 31035 +1991 336 4.83 -1.17 3.18 0 206.6 135.13 30949 +1991 337 9.42 3.42 7.77 0 275.19 130.27 30867 +1991 338 6.77 0.77 5.12 0.1 233.54 98.47 30790 +1991 339 7.85 1.85 6.2 0 249.81 129.76 30716 +1991 340 11.53 5.53 9.88 0 312.76 126.07 30647 +1991 341 8.7 2.7 7.05 0 263.29 127.5 30582 +1991 342 7.71 1.71 6.06 0 247.65 127.47 30521 +1991 343 2.45 -3.55 0.8 0.03 177.24 97.34 30465 +1991 344 -0.33 -6.33 -1.98 0 147.56 129.91 30413 +1991 345 -1.52 -7.52 -3.17 0 136.24 129.95 30366 +1991 346 -3.05 -9.05 -4.7 0 122.79 129.94 30323 +1991 347 2.47 -3.53 0.82 0 177.47 127.06 30284 +1991 348 -1.12 -7.12 -2.77 0 139.96 128.28 30251 +1991 349 -1.85 -7.85 -3.5 0 133.23 128.17 30221 +1991 350 1.68 -4.32 0.03 0.01 168.54 94.78 30197 +1991 351 1.17 -4.83 -0.48 0.01 162.99 94.79 30177 +1991 352 2.41 -3.59 0.76 0.19 176.78 94.28 30162 +1991 353 4.27 -1.73 2.62 0.56 199.34 93.51 30151 +1991 354 5.45 -0.55 3.8 0 214.9 123.97 30145 +1991 355 2.65 -3.35 1 0.06 179.56 94.11 30144 +1991 356 1.81 -4.19 0.16 0.01 169.99 94.44 30147 +1991 357 -0.87 -6.87 -2.52 0.21 142.33 139.78 30156 +1991 358 0.92 -5.08 -0.73 0.1 160.33 139.15 30169 +1991 359 -0.39 -6.39 -2.04 0.6 146.97 141.54 30186 +1991 360 0.97 -5.03 -0.68 0.13 160.86 141.22 30208 +1991 361 0.25 -5.75 -1.4 0.02 153.37 141.63 30235 +1991 362 3.27 -2.73 1.62 0.03 186.92 140.41 30267 +1991 363 4.11 -1.89 2.46 0 197.3 171.6 30303 +1991 364 3.58 -2.42 1.93 0 190.7 171.75 30343 +1991 365 3.41 -2.59 1.76 0 188.62 171.89 30388 +1992 1 6.75 0.75 5.1 0 233.25 126.99 30438 +1992 2 9.48 3.48 7.83 0 276.2 125.74 30492 +1992 3 6.55 0.55 4.9 0 230.34 128.78 30551 +1992 4 7.07 1.07 5.42 0 237.97 129.34 30614 +1992 5 6.71 0.71 5.06 0 232.66 130.22 30681 +1992 6 10.05 4.05 8.4 0 285.98 128.61 30752 +1992 7 5.87 -0.13 4.22 0 220.69 132.44 30828 +1992 8 7.97 1.97 6.32 0.17 251.67 99.36 30907 +1992 9 1.06 -4.94 -0.59 0 161.81 137.84 30991 +1992 10 0.05 -5.95 -1.6 0 151.35 139.61 31079 +1992 11 -0.34 -6.34 -1.99 0 147.46 140.78 31171 +1992 12 -0.75 -6.75 -2.4 0 143.48 141.98 31266 +1992 13 3.57 -2.43 1.92 0 190.57 141.47 31366 +1992 14 8.75 2.75 7.1 0 264.1 139.42 31469 +1992 15 11.47 5.47 9.82 0 311.63 138.45 31575 +1992 16 11.23 5.23 9.58 0.04 307.16 104.94 31686 +1992 17 9.81 3.81 8.16 0.41 281.82 107.15 31800 +1992 18 4.38 -1.62 2.73 0 200.75 148.77 31917 +1992 19 5.18 -0.82 3.53 0 211.25 150.19 32038 +1992 20 4.01 -1.99 2.36 0.05 196.04 114.39 32161 +1992 21 1.97 -4.03 0.32 0 171.77 155.71 32289 +1992 22 0.17 -5.83 -1.48 0 152.56 158.4 32419 +1992 23 3.24 -2.76 1.59 0.25 186.56 118.89 32552 +1992 24 3.67 -2.33 2.02 0.05 191.8 120.24 32688 +1992 25 4.07 -1.93 2.42 0 196.8 161.96 32827 +1992 26 4.45 -1.55 2.8 0 201.65 163.63 32969 +1992 27 -1.15 -7.15 -2.8 0.03 139.68 166.55 33114 +1992 28 -0.88 -6.88 -2.53 0 142.23 210.68 33261 +1992 29 2.7 -3.3 1.05 0 180.14 171.37 33411 +1992 30 -0.14 -6.14 -1.79 0 149.44 175.21 33564 +1992 31 1.75 -4.25 0.1 0 169.32 176.57 33718 +1992 32 5.25 -0.75 3.6 0 212.19 176.38 33875 +1992 33 6.43 0.43 4.78 0 228.61 178.09 34035 +1992 34 12.01 6.01 10.36 0 321.89 174.84 34196 +1992 35 11.33 5.33 9.68 0 309.02 177.69 34360 +1992 36 8.12 2.12 6.47 0.58 254.02 137.57 34526 +1992 37 7.37 1.37 5.72 0 242.46 186.51 34694 +1992 38 9.85 3.85 8.2 0 282.51 186.82 34863 +1992 39 9.12 3.12 7.47 0 270.17 190.14 35035 +1992 40 7.11 1.11 5.46 0.05 238.56 145.98 35208 +1992 41 4.99 -1.01 3.34 0.34 208.72 149.28 35383 +1992 42 4.22 -1.78 2.57 0 198.7 202.19 35560 +1992 43 2.07 -3.93 0.42 0 172.9 206.44 35738 +1992 44 3.98 -2.02 2.33 0 195.67 207.66 35918 +1992 45 5.42 -0.58 3.77 0 214.49 209.13 36099 +1992 46 5.86 -0.14 4.21 0.06 220.55 158.57 36282 +1992 47 7.25 1.25 5.6 0 240.65 212.96 36466 +1992 48 5.23 -0.77 3.58 0 211.92 217.6 36652 +1992 49 8.12 2.12 6.47 0 254.02 217.63 36838 +1992 50 10.69 4.69 9.04 0 297.3 217.34 37026 +1992 51 7.02 1.02 5.37 0 237.22 224.34 37215 +1992 52 7.31 1.31 5.66 0 241.56 226.86 37405 +1992 53 7.14 1.14 5.49 0 239.01 229.98 37596 +1992 54 6.25 0.25 4.6 0 226.04 233.61 37788 +1992 55 7.25 1.25 5.6 0.02 240.65 176.69 37981 +1992 56 4.89 -1.11 3.24 0.06 207.39 180.42 38175 +1992 57 7.04 1.04 5.39 0.07 237.52 181.02 38370 +1992 58 6.5 0.5 4.85 0 229.62 244.84 38565 +1992 59 6.15 0.15 4.5 0 224.62 247.9 38761 +1992 60 9.43 3.43 7.78 0 275.36 247.1 38958 +1992 61 14.22 8.22 12.57 0 366.95 243.01 39156 +1992 62 12.05 6.05 10.4 0 322.66 249.17 39355 +1992 63 13.38 7.38 11.73 0.19 349.23 187.53 39553 +1992 64 10.82 4.82 9.17 1.75 299.65 192.57 39753 +1992 65 5.03 -0.97 3.38 0 209.25 266.47 39953 +1992 66 5.56 -0.44 3.91 0 216.41 268.69 40154 +1992 67 6.48 0.48 4.83 0.23 229.33 202.97 40355 +1992 68 10.73 4.73 9.08 0.23 298.03 201.1 40556 +1992 69 14.51 8.51 12.86 0 373.25 264.56 40758 +1992 70 12.9 6.9 11.25 0.14 339.43 202.61 40960 +1992 71 12.65 6.65 11 0.09 334.42 205.07 41163 +1992 72 7.23 1.23 5.58 0 240.35 283.87 41366 +1992 73 8.17 2.17 6.52 0.13 254.81 214.04 41569 +1992 74 7.92 1.92 6.27 0.05 250.9 216.33 41772 +1992 75 5.64 -0.36 3.99 0.2 217.5 220.4 41976 +1992 76 4.87 -1.13 3.22 0.21 207.13 223.02 42179 +1992 77 6.05 0.05 4.4 0 223.21 298.69 42383 +1992 78 7.82 1.82 6.17 0 249.34 299.21 42587 +1992 79 9.22 3.22 7.57 0 271.84 300.04 42791 +1992 80 10.84 4.84 9.19 0 300.02 300.14 42996 +1992 81 7.75 1.75 6.1 0 248.26 307.16 43200 +1992 82 12.73 6.73 11.08 0 336.02 302.13 43404 +1992 83 11.04 5.04 9.39 0 303.66 307.48 43608 +1992 84 8.11 2.11 6.46 0 253.87 314.39 43812 +1992 85 9.54 3.54 7.89 0.01 277.21 236.13 44016 +1992 86 6.18 0.18 4.53 0 225.05 321.82 44220 +1992 87 5.35 -0.65 3.7 0 213.54 325.37 44424 +1992 88 6.61 0.61 4.96 0.52 231.21 244.66 44627 +1992 89 7.92 1.92 6.27 0 250.9 326.77 44831 +1992 90 9.61 3.61 7.96 0.72 278.4 245 45034 +1992 91 11.96 5.96 10.31 0.49 320.93 243.73 45237 +1992 92 13.37 7.37 11.72 0 349.02 324.54 45439 +1992 93 13.97 7.97 12.32 0 361.6 325.51 45642 +1992 94 14.95 8.95 13.3 0 382.97 325.55 45843 +1992 95 17.77 11.77 16.12 0 450.6 320.89 46045 +1992 96 14.25 8.25 12.6 0 367.6 331.24 46246 +1992 97 15.93 9.93 14.28 0 405.42 329.49 46446 +1992 98 11.8 5.8 10.15 0 317.87 340.08 46647 +1992 99 10.77 4.77 9.12 0 298.75 343.93 46846 +1992 100 13.06 7.06 11.41 0.33 342.67 256.19 47045 +1992 101 17 11 15.35 0 431.19 334.53 47243 +1992 102 15.26 9.26 13.61 0 389.95 340.63 47441 +1992 103 20.18 14.18 18.53 0.62 516.2 246.89 47638 +1992 104 18.16 12.16 16.51 0.22 460.7 252.64 47834 +1992 105 21.87 15.87 20.22 0.01 566.91 245.34 48030 +1992 106 17.46 11.46 15.81 0 442.7 342.1 48225 +1992 107 15.25 9.25 13.6 0 389.73 349.3 48419 +1992 108 15.65 9.65 14 0 398.89 350.06 48612 +1992 109 14.48 8.48 12.83 0.18 372.59 265.79 48804 +1992 110 11.27 5.27 9.62 0 307.9 362.43 48995 +1992 111 18.47 12.47 16.82 0 468.88 347.06 49185 +1992 112 16.07 10.07 14.42 0 408.71 355.02 49374 +1992 113 14.23 8.23 12.58 0.29 367.17 270.56 49561 +1992 114 15.96 9.96 14.31 0 406.12 358.09 49748 +1992 115 14.23 8.23 12.58 0 367.17 363.65 49933 +1992 116 12.04 6.04 10.39 0 322.47 369.55 50117 +1992 117 12.93 6.93 11.28 1.05 340.04 276.77 50300 +1992 118 9.06 3.06 7.41 0.14 269.18 283.25 50481 +1992 119 9.32 3.32 7.67 1.6 273.51 283.83 50661 +1992 120 12.58 6.58 10.93 0.03 333.03 280.1 50840 +1992 121 16.24 10.24 14.59 0 412.74 366.04 51016 +1992 122 16.21 10.21 14.56 0 412.03 367.3 51191 +1992 123 12.49 6.49 10.84 0 331.25 377.04 51365 +1992 124 14.08 8.08 12.43 0 363.94 374.63 51536 +1992 125 13.75 7.75 12.1 0 356.94 376.37 51706 +1992 126 15.67 9.67 14.02 0.39 399.35 279.57 51874 +1992 127 19.91 13.91 18.26 0 508.47 361.37 52039 +1992 128 20.12 14.12 18.47 1.58 514.48 271.24 52203 +1992 129 19.9 13.9 18.25 0.82 508.19 272.4 52365 +1992 130 18.62 12.62 16.97 0 472.87 368.02 52524 +1992 131 18.09 12.09 16.44 0.12 458.88 277.8 52681 +1992 132 18.2 12.2 16.55 0 461.75 370.88 52836 +1992 133 20.75 14.75 19.1 0 532.86 363.37 52989 +1992 134 18.84 12.84 17.19 0 478.79 370.33 53138 +1992 135 18.28 12.28 16.63 0.05 463.85 279.55 53286 +1992 136 18.93 12.93 17.28 0 481.23 371.36 53430 +1992 137 18.87 12.87 17.22 0 479.6 372.24 53572 +1992 138 16.2 10.2 14.55 0 411.79 380.57 53711 +1992 139 15.59 9.59 13.94 0 397.51 382.87 53848 +1992 140 16.2 10.2 14.55 0 411.79 381.75 53981 +1992 141 18.66 12.66 17.01 0 473.94 375.08 54111 +1992 142 19.64 13.64 17.99 0 500.84 372.45 54238 +1992 143 21.34 15.34 19.69 0 550.57 367.12 54362 +1992 144 21.07 15.07 19.42 0 542.4 368.55 54483 +1992 145 20 14 18.35 0 511.04 372.72 54600 +1992 146 17.84 11.84 16.19 0.24 452.4 284.93 54714 +1992 147 21.55 15.55 19.9 0 557 368.11 54824 +1992 148 20.34 14.34 18.69 0 520.83 372.78 54931 +1992 149 25.8 19.8 24.15 0 701.39 351.17 55034 +1992 150 23.43 17.43 21.78 0 617.4 361.82 55134 +1992 151 23.59 17.59 21.94 0 622.79 361.55 55229 +1992 152 24.09 18.09 22.44 0.23 639.89 269.67 55321 +1992 153 21.98 15.98 20.33 0 570.35 368.24 55409 +1992 154 19.4 13.4 17.75 0.56 494.14 283.21 55492 +1992 155 21.28 15.28 19.63 0 548.75 371.33 55572 +1992 156 24.3 18.3 22.65 0 647.19 359.69 55648 +1992 157 21.26 15.26 19.61 0 548.14 371.88 55719 +1992 158 24.79 18.79 23.14 0 664.49 357.89 55786 +1992 159 22.99 16.99 21.34 0 602.79 365.69 55849 +1992 160 20.66 14.66 19.01 0 530.2 374.62 55908 +1992 161 15.35 9.35 13.7 0 392 390.76 55962 +1992 162 16.07 10.07 14.42 1.63 408.71 291.69 56011 +1992 163 17.27 11.27 15.62 0 437.91 385.79 56056 +1992 164 18.8 12.8 17.15 0.53 477.71 285.9 56097 +1992 165 17.51 11.51 15.86 1.2 443.96 288.92 56133 +1992 166 18.75 12.75 17.1 0 476.36 381.54 56165 +1992 167 20.42 14.42 18.77 0.55 523.16 281.97 56192 +1992 168 19.62 13.62 17.97 0.75 500.28 284.06 56214 +1992 169 21.01 15.01 19.36 0 540.6 373.97 56231 +1992 170 22.6 16.6 20.95 0 590.08 368 56244 +1992 171 22.93 16.93 21.28 0 600.82 366.75 56252 +1992 172 21.52 15.52 19.87 0 556.07 372.16 56256 +1992 173 22.51 16.51 20.86 0.02 587.18 276.29 56255 +1992 174 25.93 19.93 24.28 0.08 706.27 265.21 56249 +1992 175 24.48 18.48 22.83 0.04 653.5 270.11 56238 +1992 176 27.42 21.42 25.77 0.07 764.2 259.68 56223 +1992 177 27.71 21.71 26.06 1.15 775.93 258.49 56203 +1992 178 27.29 21.29 25.64 0.01 758.99 260.12 56179 +1992 179 25.37 19.37 23.72 0.39 685.47 266.98 56150 +1992 180 24.92 18.92 23.27 0.38 669.14 268.41 56116 +1992 181 24.04 18.04 22.39 2.45 638.16 271.24 56078 +1992 182 23.19 17.19 21.54 0.5 609.4 273.77 56035 +1992 183 24.79 18.79 23.14 0 664.49 358.09 55987 +1992 184 25.91 19.91 24.26 0 705.51 352.83 55935 +1992 185 27.56 21.56 25.91 0.03 769.85 258.49 55879 +1992 186 25.75 19.75 24.1 0.06 699.53 264.94 55818 +1992 187 22.19 16.19 20.54 0.3 576.97 276.09 55753 +1992 188 24.19 18.19 22.54 0 643.35 359.78 55684 +1992 189 21.65 15.65 20 1.62 560.08 277.28 55611 +1992 190 22.47 16.47 20.82 0 585.9 366.23 55533 +1992 191 21.62 15.62 19.97 0.95 559.15 276.89 55451 +1992 192 19.68 13.68 18.03 0 501.96 375.67 55366 +1992 193 22.03 16.03 20.38 0.04 571.92 275.32 55276 +1992 194 19.84 13.84 18.19 0 506.48 374.64 55182 +1992 195 19.99 13.99 18.34 0 510.75 373.86 55085 +1992 196 19.08 13.08 17.43 0.01 485.32 282.33 54984 +1992 197 23.47 17.47 21.82 0.06 618.75 270.07 54879 +1992 198 22.27 16.27 20.62 0.11 579.51 273.31 54770 +1992 199 18.62 12.62 16.97 0.01 472.87 282.47 54658 +1992 200 19.72 13.72 18.07 0.35 503.09 279.54 54542 +1992 201 22.48 16.48 20.83 0.01 586.22 271.8 54423 +1992 202 21.35 15.35 19.7 0 550.88 366.06 54301 +1992 203 24.01 18.01 22.36 0 637.13 355.22 54176 +1992 204 25.96 19.96 24.31 0 707.39 346.14 54047 +1992 205 24.35 18.35 22.7 1 648.93 264.59 53915 +1992 206 25.51 19.51 23.86 0 690.62 347.17 53780 +1992 207 29.17 23.17 27.52 0.1 837.32 246.19 53643 +1992 208 29.14 23.14 27.49 0 836.02 327.82 53502 +1992 209 29.66 23.66 28.01 0.57 858.83 243.25 53359 +1992 210 30.64 24.64 28.99 0.01 903.23 238.59 53213 +1992 211 27.94 21.94 26.29 0.04 785.34 249.21 53064 +1992 212 30.38 24.38 28.73 0.04 891.26 238.66 52913 +1992 213 27.2 21.2 25.55 0 755.4 334.53 52760 +1992 214 27.2 21.2 25.55 0 755.4 333.82 52604 +1992 215 27.2 21.2 25.55 0 755.4 333.19 52445 +1992 216 27.2 21.2 25.55 0.12 755.4 249.17 52285 +1992 217 27.2 21.2 25.55 0 755.4 331.39 52122 +1992 218 27.2 21.2 25.55 0.03 755.4 247.97 51958 +1992 219 27.2 21.2 25.55 0 755.4 329.64 51791 +1992 220 27.2 21.2 25.55 0.04 755.4 246.57 51622 +1992 221 27.2 21.2 25.55 0 755.4 327.82 51451 +1992 222 27.2 21.2 25.55 0 755.4 326.84 51279 +1992 223 27.2 21.2 25.55 0 755.4 325.77 51105 +1992 224 27.2 21.2 25.55 0 755.4 324.78 50929 +1992 225 27.2 21.2 25.55 0 755.4 323.7 50751 +1992 226 27.2 21.2 25.55 0.35 755.4 241.97 50572 +1992 227 27.2 21.2 25.55 0 755.4 321.43 50392 +1992 228 27.2 21.2 25.55 0 755.4 320.29 50210 +1992 229 27.2 21.2 25.55 0 755.4 319.13 50026 +1992 230 27.2 21.2 25.55 0.31 755.4 238.46 49842 +1992 231 27.2 21.2 25.55 0 755.4 316.56 49656 +1992 232 27.2 21.2 25.55 0 755.4 315.3 49469 +1992 233 27.2 21.2 25.55 0 755.4 313.97 49280 +1992 234 27.2 21.2 25.55 0 755.4 312.65 49091 +1992 235 27.2 21.2 25.55 0 755.4 311.26 48900 +1992 236 27.2 21.2 25.55 0 755.4 309.94 48709 +1992 237 27.2 21.2 25.55 0 755.4 308.4 48516 +1992 238 27.2 21.2 25.55 0.09 755.4 230.13 48323 +1992 239 27.2 21.2 25.55 0 755.4 305.43 48128 +1992 240 27.2 21.2 25.55 0 755.4 303.79 47933 +1992 241 27.2 21.2 25.55 0 755.4 302.19 47737 +1992 242 27.2 21.2 25.55 0 755.4 300.57 47541 +1992 243 27.2 21.2 25.55 0 755.4 298.84 47343 +1992 244 20.5 14.5 18.85 0.31 525.5 241.76 47145 +1992 245 18.89 12.89 17.24 0 480.14 325.29 46947 +1992 246 19.47 13.47 17.82 0 496.08 321.68 46747 +1992 247 20.09 14.09 18.44 0.02 513.62 238.51 46547 +1992 248 20.89 14.89 19.24 0 537.02 313.67 46347 +1992 249 23.2 17.2 21.55 0 609.73 303.99 46146 +1992 250 19.18 13.18 17.53 0 488.06 314.77 45945 +1992 251 19.76 13.76 18.11 0 504.22 311.03 45743 +1992 252 19.52 13.52 17.87 0.56 497.48 232.18 45541 +1992 253 16.48 10.48 14.83 0.14 418.5 236.5 45339 +1992 254 17.09 11.09 15.44 0.51 433.42 233.8 45136 +1992 255 12.05 6.05 10.4 0.01 322.66 240.01 44933 +1992 256 12.75 6.75 11.1 0 336.42 316.41 44730 +1992 257 15.78 9.78 14.13 0 401.91 308.06 44527 +1992 258 21.3 15.3 19.65 0.21 549.35 218.53 44323 +1992 259 23.12 17.12 21.47 0.2 607.08 212.43 44119 +1992 260 16.16 10.16 14.51 0 410.84 300.03 43915 +1992 261 20.43 14.43 18.78 0 523.45 286.85 43711 +1992 262 18.57 12.57 16.92 0 471.54 289.51 43507 +1992 263 22.98 16.98 21.33 1.01 602.46 205.86 43303 +1992 264 21.04 15.04 19.39 0.18 541.5 208.44 43099 +1992 265 19.4 13.4 17.75 0 494.14 280.1 42894 +1992 266 17.52 11.52 15.87 0 444.22 282.29 42690 +1992 267 19.78 13.78 18.13 0.76 504.78 205.56 42486 +1992 268 21.92 15.92 20.27 0 568.47 265.64 42282 +1992 269 21.34 15.34 19.69 0 550.57 264.91 42078 +1992 270 24.78 18.78 23.13 0 664.13 251.72 41875 +1992 271 27.44 21.44 25.79 0.15 765.01 179.71 41671 +1992 272 21.69 15.69 20.04 0 561.31 256.26 41468 +1992 273 20.3 14.3 18.65 0.03 519.67 193.19 41265 +1992 274 17.66 11.66 16.01 0 447.78 261.32 41062 +1992 275 14.94 8.94 13.29 0.73 382.75 198.09 40860 +1992 276 14.95 8.95 13.3 0.35 382.97 196.06 40658 +1992 277 11.91 5.91 10.26 0.37 319.97 197.91 40456 +1992 278 11.45 5.45 9.8 0.7 311.26 196.26 40255 +1992 279 10.38 4.38 8.73 1.12 291.77 195.27 40054 +1992 280 9.12 3.12 7.47 0.07 270.17 194.49 39854 +1992 281 8.9 2.9 7.25 1.94 266.55 192.62 39654 +1992 282 11.38 5.38 9.73 1.62 309.95 188.07 39455 +1992 283 9.5 3.5 7.85 0.63 276.54 187.82 39256 +1992 284 5.2 -0.8 3.55 0.1 211.52 189.05 39058 +1992 285 6.73 0.73 5.08 0.36 232.96 185.87 38861 +1992 286 8.03 2.03 6.38 0.01 252.61 182.71 38664 +1992 287 9.55 3.55 7.9 0 277.38 238.85 38468 +1992 288 9.77 3.77 8.12 0 281.14 235.76 38273 +1992 289 11.82 5.82 10.17 0.36 318.25 172.83 38079 +1992 290 13.67 7.67 12.02 0.03 355.26 168.67 37885 +1992 291 12.87 6.87 11.22 0 338.83 223.4 37693 +1992 292 15.07 9.07 13.42 0.29 385.66 163.01 37501 +1992 293 14.43 8.43 12.78 0.55 371.5 161.76 37311 +1992 294 12.71 6.71 11.06 0 335.62 215.36 37121 +1992 295 16.39 10.39 14.74 0 416.33 206.84 36933 +1992 296 16.49 10.49 14.84 0 418.74 204.15 36745 +1992 297 17.88 11.88 16.23 1.05 453.43 149.27 36560 +1992 298 16.31 10.31 14.66 0 414.42 199.26 36375 +1992 299 16.3 10.3 14.65 0.99 414.18 147.42 36191 +1992 300 15.63 9.63 13.98 0.53 398.43 146.29 36009 +1992 301 10.73 4.73 9.08 0 298.03 199.22 35829 +1992 302 10.16 4.16 8.51 0.22 287.9 147.94 35650 +1992 303 14.09 8.09 12.44 0 364.16 189.79 35472 +1992 304 9.95 3.95 8.3 0 284.24 192.44 35296 +1992 305 2.64 -3.36 0.99 0 179.44 195.93 35122 +1992 306 3.52 -2.48 1.87 0 189.96 193.03 34950 +1992 307 4.24 -1.76 2.59 0 198.96 189.96 34779 +1992 308 4.11 -1.89 2.46 0 197.3 187.41 34610 +1992 309 5.99 -0.01 4.34 0 222.37 183.65 34444 +1992 310 4.17 -1.83 2.52 0 198.07 182.54 34279 +1992 311 3.56 -2.44 1.91 0 190.45 180.75 34116 +1992 312 6.18 0.18 4.53 0 225.05 176.17 33956 +1992 313 7.29 1.29 5.64 0.16 241.26 129.86 33797 +1992 314 11.02 5.02 9.37 0 303.3 167.69 33641 +1992 315 11.21 5.21 9.56 0.02 306.79 123.74 33488 +1992 316 13.94 7.94 12.29 0 360.96 159.73 33337 +1992 317 11.73 5.73 10.08 0.15 316.53 120.09 33188 +1992 318 12.38 6.38 10.73 2.47 329.09 117.83 33042 +1992 319 8.3 2.3 6.65 1 256.87 119.54 32899 +1992 320 5.24 -0.76 3.59 0.51 212.06 119.9 32758 +1992 321 10.18 4.18 8.53 0.11 288.25 115.33 32620 +1992 322 7.92 1.92 6.27 0 250.9 153.93 32486 +1992 323 9.34 3.34 7.69 0.19 273.84 113.35 32354 +1992 324 6.36 0.36 4.71 0 227.61 151.46 32225 +1992 325 13.56 7.56 11.91 0.15 352.96 107.43 32100 +1992 326 15.42 9.42 13.77 0 393.6 139.64 31977 +1992 327 10.69 4.69 9.04 0 297.3 142.93 31858 +1992 328 12.11 6.11 10.46 0.04 323.82 104.72 31743 +1992 329 8.78 2.78 7.13 0.71 264.59 105.87 31631 +1992 330 9.96 3.96 8.31 0.35 284.41 104.06 31522 +1992 331 11.89 5.89 10.24 0.83 319.59 101.76 31417 +1992 332 9.97 3.97 8.32 0 284.59 135.82 31316 +1992 333 7.71 1.71 6.06 0.95 247.65 102.41 31218 +1992 334 7.09 1.09 5.44 1.99 238.26 101.92 31125 +1992 335 3.29 -2.71 1.64 0.27 187.16 102.82 31035 +1992 336 4.51 -1.49 2.86 0.29 202.42 101.49 30949 +1992 337 2.99 -3.01 1.34 0 183.56 134.51 30867 +1992 338 4.86 -1.14 3.21 0.03 206.99 99.38 30790 +1992 339 3.68 -2.32 2.03 0 191.93 132.39 30716 +1992 340 5.98 -0.02 4.33 0.21 222.23 97.72 30647 +1992 341 4.69 -1.31 3.04 0.01 204.76 97.63 30582 +1992 342 2.72 -3.28 1.07 0 180.38 130.48 30521 +1992 343 4.36 -1.64 2.71 0 200.49 128.77 30465 +1992 344 4.68 -1.32 3.03 0.02 204.63 95.59 30413 +1992 345 5.27 -0.73 3.62 0 212.46 126.68 30366 +1992 346 3.56 -2.44 1.91 0 190.45 127.1 30323 +1992 347 2.72 -3.28 1.07 0 180.38 126.93 30284 +1992 348 3.12 -2.88 1.47 0 185.11 126.38 30251 +1992 349 3.99 -2.01 2.34 0.12 195.79 94.16 30221 +1992 350 6.97 0.97 5.32 0.01 236.48 92.57 30197 +1992 351 5.36 -0.64 3.71 0 213.68 124.21 30177 +1992 352 5.61 -0.39 3.96 0 217.09 123.97 30162 +1992 353 3.75 -2.25 2.1 0.72 192.79 93.72 30151 +1992 354 4.28 -1.72 2.63 0.11 199.47 93.48 30145 +1992 355 3.69 -2.31 2.04 0.28 192.05 93.71 30144 +1992 356 0.41 -5.59 -1.24 0.7 155.01 94.91 30147 +1992 357 2.16 -3.84 0.51 0.08 173.92 94.36 30156 +1992 358 1.55 -4.45 -0.1 0 167.11 126.19 30169 +1992 359 3.34 -2.66 1.69 0 187.77 125.43 30186 +1992 360 0.16 -5.84 -1.49 0 152.46 127.29 30208 +1992 361 -2.01 -8.01 -3.66 0 131.8 128.47 30235 +1992 362 1.69 -4.31 0.04 0.04 168.65 95.54 30267 +1992 363 -0.3 -6.3 -1.95 0.21 147.86 140.86 30303 +1992 364 -2.7 -8.7 -4.35 0.57 125.76 143.59 30343 +1992 365 -3.07 -9.07 -4.72 0 122.62 176.76 30388 +1993 1 4.67 -1.33 3.02 0 204.5 173.48 30438 +1993 2 5.43 -0.57 3.78 0 214.63 172.96 30492 +1993 3 3.74 -2.26 2.09 0 192.67 174.3 30551 +1993 4 2.4 -3.6 0.75 0 176.66 175.51 30614 +1993 5 4.7 -1.3 3.05 0.35 204.89 98.61 30681 +1993 6 2.32 -3.68 0.67 0 175.74 133.67 30752 +1993 7 0.79 -5.21 -0.86 0 158.96 135.21 30828 +1993 8 5.41 -0.59 3.76 0 214.36 134.21 30907 +1993 9 1.09 -4.91 -0.56 0.33 162.13 103.37 30991 +1993 10 0.61 -5.39 -1.04 0.1 157.08 104.52 31079 +1993 11 2.83 -3.17 1.18 0.61 181.67 104.44 31171 +1993 12 5.69 -0.31 4.04 0 218.19 138.56 31266 +1993 13 7.79 1.79 6.14 0 248.88 138.71 31366 +1993 14 7.71 1.71 6.06 0.44 247.65 105.17 31469 +1993 15 7.51 1.51 5.86 0 244.59 141.8 31575 +1993 16 4.92 -1.08 3.27 0 207.79 144.86 31686 +1993 17 4.46 -1.54 2.81 0.07 201.78 110.12 31800 +1993 18 7.91 1.91 6.26 0 250.74 146.3 31917 +1993 19 9.13 3.13 7.48 0 270.34 147.22 32038 +1993 20 4.2 -1.8 2.55 0 198.45 152.4 32161 +1993 21 3.31 -2.69 1.66 0.06 187.4 116.21 32289 +1993 22 4.3 -1.7 2.65 0 199.72 156.09 32419 +1993 23 4.74 -1.26 3.09 0 205.42 157.57 32552 +1993 24 4.32 -1.68 2.67 0 199.98 159.91 32688 +1993 25 3.31 -2.69 1.66 0 187.4 162.44 32827 +1993 26 1.28 -4.72 -0.37 0 164.17 165.54 32969 +1993 27 1.54 -4.46 -0.11 0 167 167.43 33114 +1993 28 -0.23 -6.23 -1.88 0.01 148.55 167.66 33261 +1993 29 3.98 -2.02 2.33 0.31 195.67 127.91 33411 +1993 30 6.05 0.05 4.4 0 223.21 171.31 33564 +1993 31 0.73 -5.27 -0.92 0 158.33 177.15 33718 +1993 32 1.16 -4.84 -0.49 0 162.88 179.04 33875 +1993 33 3.01 -2.99 1.36 0 183.8 180.56 34035 +1993 34 1.92 -4.08 0.27 0.17 171.21 137.59 34196 +1993 35 -0.36 -6.36 -2.01 0 147.27 186.91 34360 +1993 36 2.76 -3.24 1.11 0 180.85 187.62 34526 +1993 37 3.6 -2.4 1.95 0 190.94 189.48 34694 +1993 38 0.31 -5.69 -1.34 0 153.98 194.3 34863 +1993 39 2.83 -3.17 1.18 0 181.67 195.38 35035 +1993 40 3.61 -2.39 1.96 0 191.06 197.46 35208 +1993 41 1.12 -4.88 -0.53 0 162.45 201.74 35383 +1993 42 4.38 -1.62 2.73 0 200.75 202.07 35560 +1993 43 4.22 -1.78 2.57 0 198.7 204.9 35738 +1993 44 4.33 -1.67 2.68 0 200.11 207.39 35918 +1993 45 7.76 1.76 6.11 0 248.42 207 36099 +1993 46 7.64 1.64 5.99 0 246.57 209.78 36282 +1993 47 5.61 -0.39 3.96 0.39 217.09 160.85 36466 +1993 48 4.91 -1.09 3.26 0 207.65 217.87 36652 +1993 49 3.32 -2.68 1.67 0 187.52 221.93 36838 +1993 50 2.11 -3.89 0.46 0 173.35 225.5 37026 +1993 51 3.31 -2.69 1.66 0 187.4 227.6 37215 +1993 52 2.47 -3.53 0.82 0.79 177.47 173.31 37405 +1993 53 -3.04 -9.04 -4.69 0 122.87 237.51 37596 +1993 54 -1.84 -7.84 -3.49 0 133.32 239.67 37788 +1993 55 0.74 -5.26 -0.91 0 158.43 241.11 37981 +1993 56 2.31 -3.69 0.66 0 175.63 242.7 38175 +1993 57 6.24 0.24 4.59 0 225.9 242.18 38370 +1993 58 2.7 -3.3 1.05 0 180.14 248.26 38565 +1993 59 3.43 -2.57 1.78 0.13 188.86 187.8 38761 +1993 60 9.31 3.31 7.66 0 273.34 247.25 38958 +1993 61 5.96 -0.04 4.31 0 221.95 253.91 39156 +1993 62 4.17 -1.83 2.52 0.25 198.07 193.82 39355 +1993 63 3.48 -2.52 1.83 0 189.47 262.07 39553 +1993 64 3.36 -2.64 1.71 0.08 188.01 198.83 39753 +1993 65 2.1 -3.9 0.45 0 173.24 269.08 39953 +1993 66 3.2 -2.8 1.55 0.17 186.07 203.2 40154 +1993 67 8.32 2.32 6.67 0.79 257.19 201.37 40355 +1993 68 8.58 2.58 6.93 0 261.35 271.03 40556 +1993 69 10.79 4.79 9.14 0 299.11 270.64 40758 +1993 70 5.95 -0.05 4.3 0.65 221.81 209.68 40960 +1993 71 6.12 0.12 4.47 0.25 224.2 211.74 41163 +1993 72 9.32 3.32 7.67 0.78 273.51 210.91 41366 +1993 73 8.02 2.02 6.37 0 252.46 285.57 41569 +1993 74 11.15 5.15 9.5 0 305.68 283.93 41772 +1993 75 13.1 7.1 11.45 0 343.48 283.4 41976 +1993 76 8.61 2.61 6.96 0.09 261.83 219.68 42179 +1993 77 11.73 5.73 10.08 0.32 316.53 218.15 42383 +1993 78 7.61 1.61 5.96 0 246.11 299.48 42587 +1993 79 7.3 1.3 5.65 0 241.41 302.61 42791 +1993 80 8.1 2.1 6.45 0 253.71 304.12 42996 +1993 81 8.31 2.31 6.66 0 257.03 306.42 43200 +1993 82 5.12 -0.88 3.47 0 210.45 313.01 43404 +1993 83 7.3 1.3 5.65 0 241.41 312.91 43608 +1993 84 8.84 2.84 7.19 0 265.57 313.37 43812 +1993 85 10.45 4.45 8.8 0 293.01 313.43 44016 +1993 86 10.28 4.28 8.63 0 290 316.1 44220 +1993 87 9.15 3.15 7.5 0.02 270.67 240.27 44424 +1993 88 10.56 4.56 8.91 0 294.97 320.52 44627 +1993 89 6.82 0.82 5.17 0 234.27 328.24 44831 +1993 90 4.8 -1.2 3.15 0 206.2 333.1 45034 +1993 91 12.47 6.47 10.82 0 330.86 324.05 45237 +1993 92 12.93 6.93 11.28 0 340.04 325.39 45439 +1993 93 14.51 8.51 12.86 0 373.25 324.38 45642 +1993 94 14.73 8.73 13.08 0 378.08 326.03 45843 +1993 95 17.47 11.47 15.82 0 442.95 321.66 46045 +1993 96 16.62 10.62 14.97 0 421.88 325.84 46246 +1993 97 17.96 11.96 16.31 0 455.5 324.41 46446 +1993 98 12.91 6.91 11.26 0 339.63 337.96 46647 +1993 99 14.63 8.63 12.98 0.01 375.88 252.27 46846 +1993 100 17.55 11.55 15.9 0.16 444.98 248.42 47045 +1993 101 17.42 11.42 15.77 0 441.69 333.44 47243 +1993 102 14.94 8.94 13.29 0.61 382.75 256.02 47441 +1993 103 10.63 4.63 8.98 0 296.23 351.83 47638 +1993 104 7.38 1.38 5.73 0 242.61 358.85 47834 +1993 105 8.64 2.64 6.99 0 262.32 358.78 48030 +1993 106 13.6 7.6 11.95 0 353.8 351.34 48225 +1993 107 11.19 5.19 9.54 0 306.42 357.79 48419 +1993 108 10.77 4.77 9.12 0.58 298.75 270.23 48612 +1993 109 9.78 3.78 8.13 0 281.31 363.67 48804 +1993 110 10.25 4.25 8.6 1.36 289.48 273.21 48995 +1993 111 11.45 5.45 9.8 0 311.26 363.65 49185 +1993 112 15.04 9.04 13.39 0 384.99 357.53 49374 +1993 113 15.42 9.42 13.77 0 393.6 357.95 49561 +1993 114 20.56 14.56 18.91 0 527.26 344.82 49748 +1993 115 18.52 12.52 16.87 0 470.21 352.53 49933 +1993 116 19.44 13.44 17.79 0 495.25 350.94 50117 +1993 117 17.04 11.04 15.39 0 432.18 359.17 50300 +1993 118 15.16 9.16 13.51 0.15 387.69 273.97 50481 +1993 119 11.33 5.33 9.68 0.83 309.02 281.09 50661 +1993 120 12.78 6.78 11.13 0.43 337.02 279.79 50840 +1993 121 16.39 10.39 14.74 0.23 416.33 274.23 51016 +1993 122 14.08 8.08 12.43 0.54 363.94 279.39 51191 +1993 123 16.81 10.81 15.16 0 426.52 366.72 51365 +1993 124 19.63 13.63 17.98 0 500.56 359.49 51536 +1993 125 18.31 12.31 16.66 0.05 464.64 273.38 51706 +1993 126 21.05 15.05 19.4 0.12 541.8 267.5 51874 +1993 127 20.89 14.89 19.24 0 537.02 358.08 52039 +1993 128 26.52 20.52 24.87 0.03 728.75 252.15 52203 +1993 129 23.5 17.5 21.85 0 619.76 350.14 52365 +1993 130 21.86 15.86 20.21 0 566.6 357.18 52524 +1993 131 21.07 15.07 19.42 0 542.4 360.78 52681 +1993 132 23.67 17.67 22.02 0 625.5 351.74 52836 +1993 133 24.78 18.78 23.13 0 664.13 347.75 52989 +1993 134 24.42 18.42 22.77 0 651.39 349.96 53138 +1993 135 24.81 18.81 23.16 0 665.2 348.94 53286 +1993 136 27.26 21.26 25.61 0.04 757.79 253.61 53430 +1993 137 25.24 19.24 23.59 0 680.72 348.31 53572 +1993 138 26.39 20.39 24.74 0 723.74 343.58 53711 +1993 139 26.06 20.06 24.41 0 711.17 345.79 53848 +1993 140 24.18 18.18 22.53 0 643.01 354.6 53981 +1993 141 23.57 17.57 21.92 0 622.12 357.54 54111 +1993 142 21.23 15.23 19.58 0 547.23 366.99 54238 +1993 143 14.94 8.94 13.29 0 382.75 386.49 54362 +1993 144 17.45 11.45 15.8 0 442.44 380.21 54483 +1993 145 18.47 12.47 16.82 0.24 468.88 283.23 54600 +1993 146 18.86 12.86 17.21 0 479.33 376.8 54714 +1993 147 19.4 13.4 17.75 0.37 494.14 281.66 54824 +1993 148 20.5 14.5 18.85 0 525.5 372.23 54931 +1993 149 17.28 11.28 15.63 0 438.16 382.72 55034 +1993 150 14.74 8.74 13.09 0 378.3 389.85 55134 +1993 151 15.3 9.3 13.65 0 390.86 388.84 55229 +1993 152 14.75 8.75 13.1 0.01 378.52 292.75 55321 +1993 153 18.03 12.03 16.38 0.01 457.31 286.2 55409 +1993 154 19.15 13.15 17.5 0 487.23 378.43 55492 +1993 155 18.81 12.81 17.16 0.12 477.98 284.77 55572 +1993 156 17.09 11.09 15.44 0 433.42 385.19 55648 +1993 157 16.71 10.71 15.06 0.5 424.07 289.82 55719 +1993 158 16.62 10.62 14.97 0 421.88 386.86 55786 +1993 159 16.34 10.34 14.69 0.01 415.13 290.91 55849 +1993 160 14.36 8.36 12.71 0 369.98 393.17 55908 +1993 161 18.79 12.79 17.14 0 477.44 380.92 55962 +1993 162 17.81 11.81 16.16 0 451.62 383.99 56011 +1993 163 21.32 15.32 19.67 0 549.96 372.59 56056 +1993 164 20.36 14.36 18.71 1.09 521.41 282.04 56097 +1993 165 23.6 17.6 21.95 0.25 623.13 272.89 56133 +1993 166 24.06 18.06 22.41 0.48 638.85 271.5 56165 +1993 167 26.19 20.19 24.54 0.75 716.1 264.25 56192 +1993 168 28.14 22.14 26.49 1.03 793.6 256.94 56214 +1993 169 28.34 22.34 26.69 0.23 801.94 256.15 56231 +1993 170 26.81 20.81 25.16 0.21 740.02 262.06 56244 +1993 171 27.53 21.53 25.88 0 768.63 345.84 56252 +1993 172 31.41 25.41 29.76 0 939.46 323.71 56256 +1993 173 30.06 24.06 28.41 0 876.72 331.91 56255 +1993 174 27.38 21.38 25.73 0 762.6 346.5 56249 +1993 175 25.16 19.16 23.51 0 677.81 357.13 56238 +1993 176 20.02 14.02 18.37 0 511.61 377.3 56223 +1993 177 24.81 18.81 23.16 0.01 665.2 268.92 56203 +1993 178 22.59 16.59 20.94 0 589.76 367.85 56179 +1993 179 20.51 14.51 18.86 0.01 525.79 281.58 56150 +1993 180 20.76 14.76 19.11 0.78 533.15 280.83 56116 +1993 181 20.11 14.11 18.46 0.73 514.19 282.47 56078 +1993 182 20.11 14.11 18.46 1.14 514.19 282.36 56035 +1993 183 21.66 15.66 20.01 0.05 560.39 278.09 55987 +1993 184 25.02 19.02 23.37 0 672.74 356.91 55935 +1993 185 19.13 13.13 17.48 0.14 486.69 284.48 55879 +1993 186 17.92 11.92 16.27 2.29 454.46 287.1 55818 +1993 187 16.67 10.67 15.02 0.02 423.1 289.67 55753 +1993 188 15.28 9.28 13.63 0.58 390.41 292.25 55684 +1993 189 20.98 14.98 19.33 0.41 539.7 279.11 55611 +1993 190 19.89 13.89 18.24 0.68 507.9 281.66 55533 +1993 191 18.86 12.86 17.21 0.78 479.33 283.97 55451 +1993 192 20.15 14.15 18.5 0.17 515.34 280.57 55366 +1993 193 22.35 16.35 20.7 0 582.06 365.87 55276 +1993 194 25.53 19.53 23.88 0 691.36 352.29 55182 +1993 195 27.19 21.19 25.54 0 755 344.09 55085 +1993 196 29.5 23.5 27.85 0 851.75 331.41 54984 +1993 197 30.59 24.59 28.94 0.88 900.92 243.48 54879 +1993 198 28.79 22.79 27.14 0.07 820.96 250.89 54770 +1993 199 28.92 22.92 27.27 0 826.53 333.49 54658 +1993 200 27.15 21.15 25.5 0 753.41 342.36 54542 +1993 201 26.11 20.11 24.46 0.11 713.06 260.21 54423 +1993 202 24.29 18.29 22.64 0.33 646.84 265.9 54301 +1993 203 26.09 20.09 24.44 0.22 712.3 259.51 54176 +1993 204 24.62 18.62 22.97 0.68 658.44 264.1 54047 +1993 205 20.68 14.68 19.03 0 530.79 366.9 53915 +1993 206 19.55 13.55 17.9 0 498.32 370.13 53780 +1993 207 19.95 13.95 18.3 0.25 509.61 276.12 53643 +1993 208 18.77 12.77 17.12 0 476.9 371.28 53502 +1993 209 18.05 12.05 16.4 0 457.83 372.8 53359 +1993 210 22.57 16.57 20.92 0 589.12 356.9 53213 +1993 211 22.87 16.87 21.22 0 598.86 354.98 53064 +1993 212 24.8 18.8 23.15 0 664.85 346.3 52913 +1993 213 24.7 18.7 23.05 0.86 661.28 259.5 52760 +1993 214 22.4 16.4 20.75 0.82 583.66 265.89 52604 +1993 215 18.9 12.9 17.25 0.71 480.41 274.35 52445 +1993 216 22.73 16.73 21.08 0 594.29 351.6 52285 +1993 217 26.95 20.95 25.3 0 745.51 332.6 52122 +1993 218 24.02 18.02 22.37 0.03 637.47 258.63 51958 +1993 219 22.85 16.85 21.2 1.1 598.2 261.34 51791 +1993 220 19.54 13.54 17.89 1.53 498.04 269.3 51622 +1993 221 23.75 17.75 22.1 1.77 628.22 257.27 51451 +1993 222 24.89 18.89 23.24 0.04 668.07 252.98 51279 +1993 223 22.42 16.42 20.77 0 584.3 346.02 51105 +1993 224 20.88 14.88 19.23 1.36 536.72 262.82 50929 +1993 225 19.78 13.78 18.13 0 504.78 352.9 50751 +1993 226 24.1 18.1 22.45 0 640.23 336.26 50572 +1993 227 22.67 16.67 21.02 0 592.35 340.56 50392 +1993 228 24.15 18.15 22.5 0.38 641.97 250.24 50210 +1993 229 24.85 18.85 23.2 0.93 666.63 247.19 50026 +1993 230 23.05 17.05 21.4 0.44 604.77 251.62 49842 +1993 231 22.3 16.3 20.65 0.92 580.46 252.62 49656 +1993 232 19.32 13.32 17.67 0.12 491.92 259.01 49469 +1993 233 22.27 16.27 20.62 0.35 579.51 250.66 49280 +1993 234 22.19 16.19 20.54 0 576.97 333.11 49091 +1993 235 24.52 18.52 22.87 0 654.91 322.86 48900 +1993 236 25.41 19.41 23.76 0.12 686.94 238.38 48709 +1993 237 26.93 20.93 25.28 0.08 744.72 232.23 48516 +1993 238 27.93 21.93 26.28 0 784.93 303.41 48323 +1993 239 29.03 23.03 27.38 0.1 831.27 222.47 48128 +1993 240 26.92 20.92 25.27 0 744.33 305.06 47933 +1993 241 25.38 19.38 23.73 0.24 685.84 232.56 47737 +1993 242 22.91 16.91 21.26 0 600.17 317.91 47541 +1993 243 22.49 16.49 20.84 0.49 586.54 238.19 47343 +1993 244 23.15 17.15 21.5 0 608.07 313.48 47145 +1993 245 23.15 17.15 21.5 0.3 608.07 233.78 46947 +1993 246 21.08 15.08 19.43 0 542.7 316.79 46747 +1993 247 18.93 12.93 17.28 0.06 481.23 241.03 46547 +1993 248 18.85 12.85 17.2 0 479.06 319.67 46347 +1993 249 21.49 15.49 19.84 0.25 555.15 232.31 46146 +1993 250 22.58 16.58 20.93 0 589.44 304.26 45945 +1993 251 21.4 15.4 19.75 0 552.4 306.08 45743 +1993 252 21.11 15.11 19.46 0.29 543.61 228.66 45541 +1993 253 21.13 15.13 19.48 0.04 544.21 227.06 45339 +1993 254 21.82 15.82 20.17 0.53 565.35 223.88 45136 +1993 255 20.29 14.29 18.64 0.4 519.38 225.73 44933 +1993 256 20.28 14.28 18.63 0.29 519.09 224.08 44730 +1993 257 19.94 13.94 18.29 0 509.33 297.63 44527 +1993 258 18.02 12.02 16.37 0 457.05 300.43 44323 +1993 259 15.55 9.55 13.9 0.02 396.58 227.82 44119 +1993 260 13.59 7.59 11.94 0.08 353.59 229 43915 +1993 261 11.49 5.49 9.84 0.2 312.01 229.94 43711 +1993 262 17.18 11.18 15.53 0.17 435.66 219.67 43507 +1993 263 13.28 7.28 11.63 0.01 347.17 223.89 43303 +1993 264 14.07 8.07 12.42 0 363.73 294.43 43099 +1993 265 17.94 11.94 16.29 0 454.98 283.75 42894 +1993 266 21.25 15.25 19.6 0.16 547.84 204.48 42690 +1993 267 19.75 13.75 18.1 0.24 503.94 205.61 42486 +1993 268 16.57 10.57 14.92 1.24 420.67 209.42 42282 +1993 269 16.09 10.09 14.44 0 409.18 277.74 42078 +1993 270 12.13 6.13 10.48 0.01 324.21 211.83 41875 +1993 271 12.38 6.38 10.73 1.25 329.09 209.53 41671 +1993 272 13.68 7.68 12.03 2.69 355.47 205.79 41468 +1993 273 11.94 5.94 10.29 0.36 320.54 206.07 41265 +1993 274 12.72 6.72 11.07 0 335.82 270.79 41062 +1993 275 11.36 5.36 9.71 0.03 309.57 202.6 40860 +1993 276 15.75 9.75 14.1 0.01 401.21 194.92 40658 +1993 277 13.45 7.45 11.8 0.48 350.68 196.05 40456 +1993 278 12.4 6.4 10.75 0.44 329.48 195.17 40255 +1993 279 14.55 8.55 12.9 0.13 374.12 190.37 40054 +1993 280 14.9 8.9 13.25 0.3 381.86 187.93 39854 +1993 281 10.31 4.31 8.66 0 290.53 255.01 39654 +1993 282 12.72 6.72 11.07 0 335.82 248.76 39455 +1993 283 11.11 5.11 9.46 0 304.95 248.29 39256 +1993 284 13.99 7.99 12.34 0.05 362.02 180.67 39058 +1993 285 15.19 9.19 13.54 0.99 388.37 177.18 38861 +1993 286 14.42 8.42 12.77 0.46 371.28 176.12 38664 +1993 287 14.99 8.99 13.34 0.24 383.87 173.22 38468 +1993 288 13.53 7.53 11.88 0.9 352.34 172.93 38273 +1993 289 11.99 5.99 10.34 0 321.51 230.2 38079 +1993 290 11.4 5.4 9.75 0.03 310.32 171.11 37885 +1993 291 14.13 8.13 12.48 0 365.02 221.5 37693 +1993 292 14.08 8.08 12.43 0 363.94 218.92 37501 +1993 293 11.23 5.23 9.58 2.42 307.16 165.17 37311 +1993 294 14.58 8.58 12.93 0.37 374.78 159.44 37121 +1993 295 13.82 7.82 12.17 0.23 358.42 158.21 36933 +1993 296 12.84 6.84 11.19 0 338.22 209.79 36745 +1993 297 14.68 8.68 13.03 0 376.98 204.42 36560 +1993 298 13.51 7.51 11.86 0.02 351.92 152.68 36375 +1993 299 15.22 9.22 13.57 0.07 389.05 148.72 36191 +1993 300 17.15 11.15 15.5 0.05 434.92 144.41 36009 +1993 301 18.06 12.06 16.41 0 458.09 188.52 35829 +1993 302 16.6 10.6 14.95 0.16 421.4 141.38 35650 +1993 303 16.83 10.83 15.18 0.63 427.01 139.22 35472 +1993 304 15.54 9.54 13.89 0.05 396.35 138.96 35296 +1993 305 2.38 -3.62 0.73 0.2 176.43 147.08 35122 +1993 306 1.99 -4.01 0.34 0.55 172 145.53 34950 +1993 307 3.29 -2.71 1.64 0.09 187.16 142.97 34779 +1993 308 0.68 -5.32 -0.97 0 157.8 189.6 34610 +1993 309 2.18 -3.82 0.53 0 174.15 186.34 34444 +1993 310 0.23 -5.77 -1.42 0 153.17 184.98 34279 +1993 311 4.19 -1.81 2.54 0 198.32 180.32 34116 +1993 312 4.23 -1.77 2.58 0 198.83 177.62 33956 +1993 313 5.17 -0.83 3.52 0 211.12 174.8 33797 +1993 314 2.63 -3.37 0.98 0 179.33 174.53 33641 +1993 315 6.26 0.26 4.61 0 226.18 169.46 33488 +1993 316 7.48 1.48 5.83 0 244.13 166.3 33337 +1993 317 8.26 2.26 6.61 0 256.23 163.45 33188 +1993 318 11.09 5.09 9.44 0.17 304.58 118.86 33042 +1993 319 8.38 2.38 6.73 0.41 258.14 119.49 32899 +1993 320 6.66 0.66 5.01 0.36 231.94 119.13 32758 +1993 321 3.95 -2.05 2.3 0.07 195.29 118.95 32620 +1993 322 1.59 -4.41 -0.06 0.63 167.55 118.6 32486 +1993 323 -2.12 -8.12 -3.77 0 130.82 158.23 32354 +1993 324 0.83 -5.17 -0.82 0 159.38 154.8 32225 +1993 325 5.5 -0.5 3.85 0 215.58 150.34 32100 +1993 326 2.2 -3.8 0.55 0.01 174.37 113.15 31977 +1993 327 5.44 -0.56 3.79 0.41 214.77 110.3 31858 +1993 328 3.42 -2.58 1.77 0.64 188.74 109.75 31743 +1993 329 5.44 -0.56 3.79 0 214.77 143.59 31631 +1993 330 5.23 -0.77 3.58 0.79 211.92 106.71 31522 +1993 331 4.87 -1.13 3.22 2.01 207.13 105.89 31417 +1993 332 8.8 2.8 7.15 0.42 264.91 102.59 31316 +1993 333 3.9 -2.1 2.25 0.95 194.66 104.27 31218 +1993 334 3.44 -2.56 1.79 1.76 188.98 103.64 31125 +1993 335 5.48 -0.52 3.83 0.4 215.31 101.85 31035 +1993 336 7 1 5.35 0.03 236.93 100.3 30949 +1993 337 9.55 3.55 7.9 0.03 277.38 97.62 30867 +1993 338 7.27 1.27 5.62 0.02 240.96 98.21 30790 +1993 339 3.4 -2.6 1.75 0.61 188.49 99.41 30716 +1993 340 3.3 -2.7 1.65 0.02 187.28 98.9 30647 +1993 341 1.11 -4.89 -0.54 0 162.35 132.03 30582 +1993 342 1.73 -4.27 0.08 0 169.1 130.97 30521 +1993 343 0.48 -5.52 -1.17 0 155.73 130.71 30465 +1993 344 7.06 1.06 5.41 0 237.82 125.98 30413 +1993 345 6.29 0.29 4.64 0 226.61 126.05 30366 +1993 346 6.55 0.55 4.9 0.01 230.34 94.01 30323 +1993 347 2.09 -3.91 0.44 0 173.13 127.24 30284 +1993 348 5.62 -0.38 3.97 0 217.23 124.98 30251 +1993 349 7.47 1.47 5.82 0.29 243.98 92.56 30221 +1993 350 8.3 2.3 6.65 0.47 256.87 91.88 30197 +1993 351 8.99 2.99 7.34 0 268.03 121.79 30177 +1993 352 7.62 1.62 5.97 0 246.26 122.68 30162 +1993 353 6.25 0.25 4.6 0.07 226.04 92.63 30151 +1993 354 8.53 2.53 6.88 0 260.54 121.94 30145 +1993 355 6.13 0.13 4.48 0.14 224.34 92.66 30144 +1993 356 2.7 -3.3 1.05 0.53 180.14 94.12 30147 +1993 357 -0.74 -6.74 -2.39 0.19 143.57 139.68 30156 +1993 358 1.27 -4.73 -0.38 0.51 164.07 138.92 30169 +1993 359 1.84 -4.16 0.19 0.21 170.32 138.55 30186 +1993 360 4.39 -1.61 2.74 0.22 200.88 93.92 30208 +1993 361 6.56 0.56 4.91 0.25 230.49 93.19 30235 +1993 362 4.36 -1.64 2.71 0.19 200.49 94.51 30267 +1993 363 3.86 -2.14 2.21 0.17 194.16 95.16 30303 +1993 364 3.59 -2.41 1.94 0.77 190.82 95.56 30343 +1993 365 0.62 -5.38 -1.03 0.6 157.18 97.07 30388 +1994 1 -0.78 -6.78 -2.43 0 143.19 130.91 30438 +1994 2 0.45 -5.55 -1.2 0 155.42 131.14 30492 +1994 3 -1.89 -7.89 -3.54 0 132.87 133.04 30551 +1994 4 4.55 -1.45 2.9 0 202.94 130.93 30614 +1994 5 4.31 -1.69 2.66 0.35 199.85 98.78 30681 +1994 6 4.31 -1.69 2.66 0 199.85 132.6 30752 +1994 7 9.42 3.42 7.77 0 275.19 129.89 30828 +1994 8 6.71 0.71 5.06 0 232.66 133.37 30907 +1994 9 3.75 -2.25 2.1 0.37 192.79 102.34 30991 +1994 10 1.94 -4.06 0.29 0 171.44 138.72 31079 +1994 11 3.88 -2.12 2.23 0.24 194.41 104 31171 +1994 12 8.37 2.37 6.72 0 257.98 136.66 31266 +1994 13 8.26 2.26 6.61 0 256.23 138.35 31366 +1994 14 7.48 1.48 5.83 0 244.13 140.4 31469 +1994 15 7.47 1.47 5.82 0 243.98 141.83 31575 +1994 16 10.79 4.79 9.14 0 299.11 140.34 31686 +1994 17 12.25 6.25 10.6 0 326.54 140.56 31800 +1994 18 12.34 6.34 10.69 0 328.3 142.32 31917 +1994 19 11.67 5.67 10.02 0.58 315.4 108.66 32038 +1994 20 5.91 -0.09 4.26 0.09 221.25 113.45 32161 +1994 21 3.14 -2.86 1.49 0.37 185.35 116.29 32289 +1994 22 8.69 2.69 7.04 0.05 263.12 114.63 32419 +1994 23 13.82 7.82 12.17 0.11 358.42 112.08 32552 +1994 24 7.41 1.41 5.76 0 243.07 157.68 32688 +1994 25 7.92 1.92 6.27 0 250.9 159.14 32827 +1994 26 10.72 4.72 9.07 0 297.85 158.49 32969 +1994 27 6.94 0.94 5.29 0 236.04 163.83 33114 +1994 28 7.71 1.71 6.06 0 247.65 165.39 33261 +1994 29 7.81 1.81 6.16 0.04 249.19 125.75 33411 +1994 30 5.98 -0.02 4.33 0.03 222.23 128.52 33564 +1994 31 2.9 -3.1 1.25 0.14 182.5 131.91 33718 +1994 32 0.44 -5.56 -1.21 0 155.32 179.43 33875 +1994 33 3.37 -2.63 1.72 0 188.13 180.32 34035 +1994 34 5.68 -0.32 4.03 0 218.05 180.87 34196 +1994 35 3.35 -2.65 1.7 0.06 187.89 138.53 34360 +1994 36 3.98 -2.02 2.33 0.16 195.67 140.09 34526 +1994 37 5.76 -0.24 4.11 0.11 219.16 140.9 34694 +1994 38 3.18 -2.82 1.53 0.57 185.83 144.39 34863 +1994 39 1.38 -4.62 -0.27 0.17 165.26 147.23 35035 +1994 40 6.17 0.17 4.52 0.03 224.9 146.6 35208 +1994 41 6.21 0.21 4.56 0 225.47 198.04 35383 +1994 42 7.53 1.53 5.88 0 244.89 199.39 35560 +1994 43 7.88 1.88 6.23 0 250.27 201.74 35738 +1994 44 3.62 -2.38 1.97 0 191.19 207.93 35918 +1994 45 3.32 -2.68 1.67 0 187.52 210.78 36099 +1994 46 4.13 -1.87 2.48 0 197.56 212.86 36282 +1994 47 5.94 -0.06 4.29 0 221.67 214.18 36466 +1994 48 5.34 -0.66 3.69 0 213.41 217.5 36652 +1994 49 9.4 3.4 7.75 0 274.85 216.24 36838 +1994 50 11.62 5.62 9.97 0 314.45 216.16 37026 +1994 51 10.36 4.36 8.71 0 291.42 220.67 37215 +1994 52 12.25 6.25 10.6 0.22 326.54 165.74 37405 +1994 53 10.8 4.8 9.15 0 299.29 225.81 37596 +1994 54 10.18 4.18 8.53 0 288.25 229.3 37788 +1994 55 6.89 0.89 5.24 0 235.3 235.96 37981 +1994 56 4.95 -1.05 3.3 0 208.18 240.51 38175 +1994 57 1.32 -4.68 -0.33 0 164.61 246.35 38370 +1994 58 2.4 -3.6 0.75 0.05 176.66 186.38 38565 +1994 59 4.54 -1.46 2.89 0.26 202.81 187.07 38761 +1994 60 15.04 9.04 13.39 0.01 384.99 179.08 38958 +1994 61 12.84 6.84 11.19 0 338.22 245.24 39156 +1994 62 11.69 5.69 10.04 0 315.78 249.7 39355 +1994 63 14.39 8.39 12.74 0 370.63 248.35 39553 +1994 64 13.87 7.87 12.22 0 359.47 252.06 39753 +1994 65 14.38 8.38 12.73 0 370.41 253.99 39953 +1994 66 14.23 8.23 12.58 0 367.17 256.91 40154 +1994 67 16.93 10.93 15.28 0 429.47 254.56 40355 +1994 68 14.95 8.95 13.3 0 382.97 261.21 40556 +1994 69 17.28 11.28 15.63 0.22 438.16 194.31 40758 +1994 70 14.94 8.94 13.29 0.03 382.75 199.9 40960 +1994 71 16.04 10.04 14.39 0.08 408 200.4 41163 +1994 72 14.93 8.93 13.28 0.5 382.52 204.09 41366 +1994 73 12.47 6.47 10.82 0.72 330.86 209.33 41569 +1994 74 10.21 4.21 8.56 1.27 288.77 214 41772 +1994 75 7.37 1.37 5.72 0 242.46 291.86 41976 +1994 76 6.28 0.28 4.63 0 226.47 295.8 42179 +1994 77 11.11 5.11 9.46 0 304.95 291.86 42383 +1994 78 11.03 5.03 9.38 0 303.48 294.63 42587 +1994 79 8.61 2.61 6.96 0 261.83 300.89 42791 +1994 80 6.22 0.22 4.57 0 225.61 306.47 42996 +1994 81 10.67 4.67 9.02 0 296.95 302.97 43200 +1994 82 10.01 4.01 8.36 0.26 285.28 229.97 43404 +1994 83 7.96 1.96 6.31 0 251.52 312.05 43608 +1994 84 11.5 5.5 9.85 0 312.19 309.24 43812 +1994 85 11.45 5.45 9.8 0 311.26 311.8 44016 +1994 86 11.73 5.73 10.08 0.05 316.53 235.28 44220 +1994 87 13.99 7.99 12.34 0 362.02 312 44424 +1994 88 12.08 6.08 10.43 0 323.24 317.92 44627 +1994 89 12.04 6.04 10.39 1.39 322.47 240.19 44831 +1994 90 14.82 8.82 13.17 0 380.08 317.14 45034 +1994 91 17.79 11.79 16.14 0 451.11 312.4 45237 +1994 92 18.22 12.22 16.57 0 462.28 313.44 45439 +1994 93 16.4 10.4 14.75 0 416.57 320.13 45642 +1994 94 20.9 14.9 19.25 0 537.31 309.95 45843 +1994 95 21.69 15.69 20.04 0.31 561.31 232.1 46045 +1994 96 19.62 13.62 17.97 0.61 500.28 238.38 46246 +1994 97 18.15 12.15 16.5 0.4 460.44 242.93 46446 +1994 98 14.26 8.26 12.61 0 367.81 335.18 46647 +1994 99 13.84 7.84 12.19 0 358.84 338.05 46846 +1994 100 16.96 10.96 15.31 0 430.2 332.75 47045 +1994 101 12.19 6.19 10.54 0 325.37 345.22 47243 +1994 102 11.87 5.87 10.22 0.03 319.2 260.79 47441 +1994 103 13.23 7.23 11.58 0.05 346.14 260.16 47638 +1994 104 14.12 8.12 12.47 0.01 364.8 260.1 47834 +1994 105 14.97 8.97 13.32 0.03 383.42 260.01 48030 +1994 106 9.35 3.35 7.7 1.17 274.01 269.48 48225 +1994 107 9.05 3.05 7.4 0 269.02 361.49 48419 +1994 108 6.92 0.92 5.27 0.23 235.74 274.86 48612 +1994 109 9.29 3.29 7.64 0 273.01 364.49 48804 +1994 110 8.84 2.84 7.19 0.02 265.57 274.99 48995 +1994 111 9.68 3.68 8.03 0 279.6 366.84 49185 +1994 112 9.31 3.31 7.66 0 273.34 369 49374 +1994 113 12.55 6.55 10.9 0.8 332.44 273.27 49561 +1994 114 12.48 6.48 10.83 0.31 331.05 274.5 49748 +1994 115 9.92 3.92 8.27 0 283.72 372.28 49933 +1994 116 10.21 4.21 8.56 0 288.77 373.01 50117 +1994 117 15.46 9.46 13.81 0.07 394.52 272.44 50300 +1994 118 16.09 10.09 14.44 2.13 409.18 272.23 50481 +1994 119 10.53 4.53 8.88 1.39 294.44 282.22 50661 +1994 120 8.74 2.74 7.09 1.36 263.94 285.46 50840 +1994 121 16.26 10.26 14.61 0.43 413.22 274.49 51016 +1994 122 18.77 12.77 17.12 1.62 476.9 270.08 51191 +1994 123 23.61 17.61 21.96 0.35 623.47 258.17 51365 +1994 124 24.9 18.9 23.25 0.68 668.43 254.93 51536 +1994 125 23.19 17.19 21.54 0.22 609.4 260.87 51706 +1994 126 24.08 18.08 22.43 0.28 639.54 258.9 51874 +1994 127 23.76 17.76 22.11 0 628.56 347.34 52039 +1994 128 21.59 15.59 19.94 0 558.23 356.58 52203 +1994 129 17.64 11.64 15.99 0 447.27 370.14 52365 +1994 130 19.14 13.14 17.49 0 486.96 366.41 52524 +1994 131 18.55 12.55 16.9 0.15 471 276.76 52681 +1994 132 14.67 8.67 13.02 0.07 376.76 285.3 52836 +1994 133 15.52 9.52 13.87 0 395.89 378.99 52989 +1994 134 16.02 10.02 14.37 0 407.53 378.4 53138 +1994 135 17.81 11.81 16.16 0.55 451.62 280.59 53286 +1994 136 19 13 17.35 0.72 483.13 278.36 53430 +1994 137 18.46 12.46 16.81 0.02 468.61 280.13 53572 +1994 138 16.61 10.61 14.96 0 421.64 379.46 53711 +1994 139 15.03 9.03 13.38 0 384.76 384.29 53848 +1994 140 15.78 9.78 14.13 0 401.91 382.86 53981 +1994 141 12.63 6.63 10.98 0.08 334.03 293.11 54111 +1994 142 12.62 6.62 10.97 0.38 333.83 293.51 54238 +1994 143 14.67 8.67 13.02 0.62 376.76 290.37 54362 +1994 144 13.78 7.78 12.13 0.01 357.57 292.33 54483 +1994 145 16.11 10.11 14.46 0 409.66 384.42 54600 +1994 146 17.87 11.87 16.22 0 453.17 379.82 54714 +1994 147 24.51 18.51 22.86 0 654.55 356.3 54824 +1994 148 21.87 15.87 20.22 0 566.91 367.3 54931 +1994 149 19.51 13.51 17.86 0 497.2 375.87 55034 +1994 150 19.47 13.47 17.82 0.3 496.08 282.25 55134 +1994 151 20.76 14.76 19.11 0.29 533.15 279.26 55229 +1994 152 24.01 18.01 22.36 0.89 637.13 269.92 55321 +1994 153 23.12 17.12 21.47 0.08 607.08 272.85 55409 +1994 154 20.07 14.07 18.42 0.22 513.04 281.54 55492 +1994 155 19.93 13.93 18.28 0.16 509.04 282.04 55572 +1994 156 18.9 12.9 17.25 0.02 480.41 284.8 55648 +1994 157 15.73 9.73 14.08 0.05 400.75 291.82 55719 +1994 158 16.96 10.96 15.31 0 430.2 385.9 55786 +1994 159 17.33 11.33 15.68 0.23 439.42 288.81 55849 +1994 160 19.9 13.9 18.25 0 508.19 377.23 55908 +1994 161 20.75 14.75 19.1 0.74 532.86 280.78 55962 +1994 162 25.24 19.24 23.59 0.22 680.72 267.3 56011 +1994 163 23.47 17.47 21.82 0 618.75 364.26 56056 +1994 164 24.55 18.55 22.9 0.09 655.97 269.79 56097 +1994 165 21.94 15.94 20.29 0.14 569.1 277.82 56133 +1994 166 21.92 15.92 20.27 0.35 568.47 277.94 56165 +1994 167 19.12 13.12 17.47 1.04 486.41 285.23 56192 +1994 168 19.09 13.09 17.44 0.56 485.59 285.36 56214 +1994 169 17.93 11.93 16.28 0.27 454.72 288.08 56231 +1994 170 19.76 13.76 18.11 0.07 504.22 283.72 56244 +1994 171 20.9 14.9 19.25 1.24 537.31 280.81 56252 +1994 172 25.11 19.11 23.46 0 676 357.48 56256 +1994 173 30.01 24.01 28.36 0.02 874.47 249.15 56255 +1994 174 25.01 19.01 23.36 0.22 672.38 268.38 56249 +1994 175 21.89 15.89 20.24 0 567.53 370.65 56238 +1994 176 24.74 18.74 23.09 0 662.71 358.97 56223 +1994 177 25.2 19.2 23.55 0 679.27 356.82 56203 +1994 178 21.02 15.02 19.37 0 540.9 373.74 56179 +1994 179 21.11 15.11 19.46 0 543.61 373.31 56150 +1994 180 22.53 16.53 20.88 0 587.83 367.86 56116 +1994 181 26.27 20.27 24.62 0.17 719.15 263.69 56078 +1994 182 28.43 22.43 26.78 0.16 805.71 255.35 56035 +1994 183 27.04 21.04 25.39 0.1 749.06 260.63 55987 +1994 184 27.76 21.76 26.11 0 777.97 343.7 55935 +1994 185 29.87 23.87 28.22 0 868.18 332.04 55879 +1994 186 28.47 22.47 26.82 0.01 807.4 254.72 55818 +1994 187 27.49 21.49 25.84 0.29 767.02 258.45 55753 +1994 188 26.58 20.58 24.93 0.74 731.07 261.66 55684 +1994 189 24.07 18.07 22.42 2.16 639.2 270.08 55611 +1994 190 23.26 17.26 21.61 1.22 611.72 272.33 55533 +1994 191 20.94 14.94 19.29 0.86 538.51 278.74 55451 +1994 192 20.42 14.42 18.77 0.23 523.16 279.88 55366 +1994 193 20.02 14.02 18.37 0.19 511.61 280.7 55276 +1994 194 19.22 13.22 17.57 0.01 489.16 282.5 55182 +1994 195 19.14 13.14 17.49 0 486.96 376.65 55085 +1994 196 19.54 13.54 17.89 0.09 498.04 281.21 54984 +1994 197 21.79 15.79 20.14 0.69 564.42 274.98 54879 +1994 198 23.84 17.84 22.19 0 631.29 358.16 54770 +1994 199 20.89 14.89 19.24 1.27 537.02 276.84 54658 +1994 200 23.8 17.8 22.15 0.18 629.93 268.19 54542 +1994 201 20.94 14.94 19.29 0.02 538.51 276.06 54423 +1994 202 24.8 18.8 23.15 0 664.85 352.33 54301 +1994 203 28.66 22.66 27.01 0 815.43 333.11 54176 +1994 204 30.11 24.11 28.46 0 878.98 324.55 54047 +1994 205 30.29 24.29 28.64 0 887.15 323.03 53915 +1994 206 30.68 24.68 29.03 0.31 905.08 240.17 53780 +1994 207 31.3 25.3 29.65 0 934.21 315.87 53643 +1994 208 30.91 24.91 29.26 0.12 915.8 238.24 53502 +1994 209 30.88 24.88 29.23 0 914.39 317.25 53359 +1994 210 30.21 24.21 28.56 0.31 883.51 240.48 53213 +1994 211 33.92 27.92 32.27 0.44 1066.17 222.23 53064 +1994 212 27.81 21.81 26.16 0 780.01 332.19 52913 +1994 213 29.12 23.12 27.47 0.04 835.16 243.45 52760 +1994 214 27.79 21.79 26.14 0 779.19 330.89 52604 +1994 215 27.22 21.22 25.57 2.48 756.2 249.82 52445 +1994 216 27.43 21.43 25.78 0.56 764.6 248.33 52285 +1994 217 26.61 20.61 24.96 1.42 732.23 250.67 52122 +1994 218 27.38 21.38 25.73 0.15 762.6 247.31 51958 +1994 219 27.03 21.03 25.38 0.43 748.66 247.85 51791 +1994 220 22.83 16.83 21.18 0.28 597.55 260.7 51622 +1994 221 20.16 14.16 18.51 0.82 515.63 267.05 51451 +1994 222 20.65 14.65 19 1.12 529.9 265.05 51279 +1994 223 23.85 17.85 22.2 0.6 631.63 255.38 51105 +1994 224 24.67 18.67 23.02 0 660.22 336.12 50929 +1994 225 29.12 23.12 27.47 0.96 835.16 235.52 50751 +1994 226 26.55 20.55 24.9 0.05 729.9 244.26 50572 +1994 227 22.42 16.42 20.77 0.01 584.3 256.11 50392 +1994 228 25.32 19.32 23.67 1.44 683.64 246.59 50210 +1994 229 19.31 13.31 17.66 0.02 491.64 262.11 50026 +1994 230 21.98 15.98 20.33 0 570.35 339.41 49842 +1994 231 24.52 18.52 22.87 0 654.91 328.31 49656 +1994 232 25.69 19.69 24.04 0 697.29 322.11 49469 +1994 233 22.92 16.92 21.27 0 600.49 331.85 49280 +1994 234 27.76 21.76 26.11 0 777.97 310 49091 +1994 235 23.51 17.51 21.86 0 620.09 326.81 48900 +1994 236 22.42 16.42 20.77 1.61 584.3 247.08 48709 +1994 237 19.34 13.34 17.69 0.43 492.47 253.41 48516 +1994 238 18.21 12.21 16.56 0.21 462.01 254.6 48323 +1994 239 24.32 18.32 22.67 0.89 647.88 238.24 48128 +1994 240 26.18 20.18 24.53 0.44 715.72 231.24 47933 +1994 241 23.87 17.87 22.22 0.14 632.32 237.04 47737 +1994 242 24.14 18.14 22.49 0.03 641.62 235.01 47541 +1994 243 25.11 19.11 23.46 0 676 307.76 47343 +1994 244 19.6 13.6 17.95 0.18 499.72 243.81 47145 +1994 245 22.65 16.65 21 0.03 591.7 235.1 46947 +1994 246 23.32 17.32 21.67 0.51 613.72 231.9 46747 +1994 247 19.6 13.6 17.95 0.04 499.72 239.6 46547 +1994 248 20.32 14.32 18.67 0.75 520.25 236.56 46347 +1994 249 18.29 12.29 16.64 0 464.12 319.14 46146 +1994 250 18.42 12.42 16.77 0.07 467.55 237.64 45945 +1994 251 16.72 10.72 15.07 0.01 424.32 239.3 45743 +1994 252 18.3 12.3 16.65 0 464.38 312.91 45541 +1994 253 23.05 17.05 21.4 0 604.77 296.5 45339 +1994 254 20.11 14.11 18.46 0.64 514.19 227.78 45136 +1994 255 22.43 16.43 20.78 0.28 584.62 220.77 44933 +1994 256 26.79 20.79 25.14 0.66 739.23 207.07 44730 +1994 257 21.88 15.88 20.23 0.17 567.22 218.89 44527 +1994 258 18.79 12.79 17.14 0 477.44 298.45 44323 +1994 259 16.96 10.96 15.31 0.08 430.2 225.44 44119 +1994 260 18.05 12.05 16.4 0 457.83 295.58 43915 +1994 261 21.74 15.74 20.09 0 562.86 283 43711 +1994 262 16.66 10.66 15.01 0 422.85 294.08 43507 +1994 263 20.42 14.42 18.77 0 523.16 282.17 43303 +1994 264 19.35 13.35 17.7 0 492.75 282.55 43099 +1994 265 19.33 13.33 17.68 0 492.19 280.28 42894 +1994 266 19.35 13.35 17.7 0 492.75 277.81 42690 +1994 267 22.7 16.7 21.05 0 593.32 265.74 42486 +1994 268 22.42 16.42 20.77 0 584.3 264.15 42282 +1994 269 23.67 17.67 22.02 0 625.5 257.87 42078 +1994 270 26.78 20.78 25.13 0.19 738.84 183.4 41875 +1994 271 27.45 21.45 25.8 0 765.41 239.57 41671 +1994 272 25.52 19.52 23.87 0 690.99 244.2 41468 +1994 273 21.44 15.44 19.79 0 553.62 254.54 41265 +1994 274 13.63 7.63 11.98 0.03 354.42 201.94 41062 +1994 275 14.18 8.18 12.53 0 366.09 265.51 40860 +1994 276 11.76 5.76 10.11 0 317.1 266.8 40658 +1994 277 12.32 6.32 10.67 0.2 327.91 197.43 40456 +1994 278 11.09 5.09 9.44 0.31 304.58 196.65 40255 +1994 279 7.56 1.56 5.91 0.14 245.35 197.94 40054 +1994 280 9.95 3.95 8.3 0.01 284.24 193.69 39854 +1994 281 11.98 5.98 10.33 0 321.31 252.64 39654 +1994 282 12.02 6.02 10.37 0 322.08 249.82 39455 +1994 283 14 8 12.35 0.16 362.24 182.92 39256 +1994 284 13.1 7.1 11.45 0 343.48 242.32 39058 +1994 285 15.98 9.98 14.33 2.18 406.59 176.12 38861 +1994 286 16.24 10.24 14.59 0.8 412.74 173.73 38664 +1994 287 12.78 6.78 11.13 0.49 337.02 175.86 38468 +1994 288 15.34 9.34 13.69 0.02 391.77 170.71 38273 +1994 289 12.76 6.76 11.11 0 336.62 229.1 38079 +1994 290 10.94 4.94 9.29 0 301.83 228.75 37885 +1994 291 11.14 5.14 9.49 0 305.5 225.77 37693 +1994 292 10.67 4.67 9.02 0 296.95 223.67 37501 +1994 293 14.63 8.63 12.98 0.39 375.88 161.52 37311 +1994 294 13.09 7.09 11.44 0.71 343.28 161.11 37121 +1994 295 14.73 8.73 13.08 0.34 378.08 157.17 36933 +1994 296 8.43 2.43 6.78 0.11 258.94 161.34 36745 +1994 297 5.21 -0.79 3.56 0 211.65 215.4 36560 +1994 298 8.98 2.98 7.33 0 267.86 209.16 36375 +1994 299 7.82 1.82 6.17 0.24 249.34 155.66 36191 +1994 300 8.06 2.06 6.41 0 253.08 204.61 36009 +1994 301 10.42 4.42 8.77 0 292.48 199.57 35829 +1994 302 11.88 5.88 10.23 0.06 319.39 146.43 35650 +1994 303 14.61 8.61 12.96 0 375.44 189.05 35472 +1994 304 13.46 7.46 11.81 0 350.88 188.23 35296 +1994 305 10.97 4.97 9.32 0 302.38 188.58 35122 +1994 306 15.41 9.41 13.76 0.06 393.37 135.46 34950 +1994 307 14.59 8.59 12.94 0.2 375 134.5 34779 +1994 308 11.07 5.07 9.42 0.01 304.21 135.86 34610 +1994 309 12.81 6.81 11.16 0.15 337.62 132.62 34444 +1994 310 11.1 5.1 9.45 0.22 304.76 132.3 34279 +1994 311 9.6 3.6 7.95 0 278.23 175.8 34116 +1994 312 6.3 0.3 4.65 0 226.75 176.08 33956 +1994 313 7.69 1.69 6.04 0 247.34 172.8 33797 +1994 314 9.88 3.88 8.23 0 283.03 168.84 33641 +1994 315 15.32 9.32 13.67 0 391.32 160.07 33488 +1994 316 13.11 7.11 11.46 0.02 343.69 120.54 33337 +1994 317 14.51 8.51 12.86 0.3 373.25 117.66 33188 +1994 318 10.94 4.94 9.29 0.47 301.83 118.97 33042 +1994 319 8.48 2.48 6.83 0.14 259.74 119.43 32899 +1994 320 12.03 6.03 10.38 0 322.28 154 32758 +1994 321 13.32 7.32 11.67 0 347.99 150.52 32620 +1994 322 12.88 6.88 11.23 0.02 339.03 111.93 32486 +1994 323 8.9 2.9 7.25 0.7 266.55 113.63 32354 +1994 324 6.67 0.67 5.02 0 232.08 151.24 32225 +1994 325 6.77 0.77 5.12 0 233.54 149.44 32100 +1994 326 6.02 0.02 4.37 0.01 222.79 111.39 31977 +1994 327 1.42 -4.58 -0.23 0.02 165.69 112.06 31858 +1994 328 3.67 -2.33 2.02 0 191.8 146.19 31743 +1994 329 3.77 -2.23 2.12 0 193.04 144.63 31631 +1994 330 8.35 2.35 6.7 0.27 257.66 105.05 31522 +1994 331 9.33 3.33 7.68 0.14 273.67 103.48 31417 +1994 332 12.01 6.01 10.36 0.5 321.89 100.47 31316 +1994 333 9.97 3.97 8.32 0.43 284.59 101.06 31218 +1994 334 8.88 2.88 7.23 1.02 266.22 100.92 31125 +1994 335 5.74 -0.26 4.09 0.03 218.88 101.73 31035 +1994 336 6.38 0.38 4.73 0.1 227.89 100.61 30949 +1994 337 5.34 -0.66 3.69 0 213.41 133.16 30867 +1994 338 6.14 0.14 4.49 0 224.48 131.71 30790 +1994 339 3.51 -2.49 1.86 0.45 189.84 99.37 30716 +1994 340 -0.04 -6.04 -1.69 0 150.44 133.46 30647 +1994 341 2.75 -3.25 1.1 0.01 180.73 98.42 30582 +1994 342 0.13 -5.87 -1.52 0 152.15 131.69 30521 +1994 343 1.37 -4.63 -0.28 0 165.15 130.31 30465 +1994 344 7.81 1.81 6.16 0 249.19 125.46 30413 +1994 345 6.43 0.43 4.78 0 228.61 125.97 30366 +1994 346 5.21 -0.79 3.56 0 211.65 126.17 30323 +1994 347 3.74 -2.26 2.09 0 192.67 126.41 30284 +1994 348 2.72 -3.28 1.07 0 180.38 126.58 30251 +1994 349 3.63 -2.37 1.98 0 191.31 125.73 30221 +1994 350 0.77 -5.23 -0.88 0 158.75 126.78 30197 +1994 351 1.38 -4.62 -0.27 0.42 165.26 94.71 30177 +1994 352 0.32 -5.68 -1.33 0 154.09 126.66 30162 +1994 353 5.1 -0.9 3.45 0 210.18 124.21 30151 +1994 354 4.69 -1.31 3.04 0.04 204.76 93.31 30145 +1994 355 8.15 2.15 6.5 0 254.5 122.21 30144 +1994 356 6.47 0.47 4.82 0 229.19 123.36 30147 +1994 357 3.47 -2.53 1.82 0 189.35 125.15 30156 +1994 358 6.46 0.46 4.81 0 229.04 123.51 30169 +1994 359 3.5 -2.5 1.85 0 189.71 125.35 30186 +1994 360 5.95 -0.05 4.3 0 221.81 124.31 30208 +1994 361 7.23 1.23 5.58 0.07 240.35 92.86 30235 +1994 362 8.93 2.93 7.28 0.24 267.04 92.28 30267 +1994 363 7.35 1.35 5.7 2.94 242.16 93.56 30303 +1994 364 2.88 -3.12 1.23 0 182.26 127.79 30343 +1994 365 1.27 -4.73 -0.38 0.1 164.07 96.85 30388 +1995 1 0.48 -5.52 -1.17 0 155.73 130.39 30438 +1995 2 3.5 -2.5 1.85 0 189.71 129.66 30492 +1995 3 1.98 -4.02 0.33 0 171.89 131.38 30551 +1995 4 6.08 0.08 4.43 0.05 223.63 97.5 30614 +1995 5 5.26 -0.74 3.61 0.44 212.33 98.36 30681 +1995 6 1.84 -4.16 0.19 0.52 170.32 100.43 30752 +1995 7 0.83 -5.17 -0.82 0 159.38 135.19 30828 +1995 8 1.04 -4.96 -0.61 0 161.6 136.59 30907 +1995 9 3.22 -2.78 1.57 0 186.32 136.74 30991 +1995 10 3.61 -2.39 1.96 0 191.06 137.83 31079 +1995 11 5.24 -0.76 3.59 0 212.06 137.85 31171 +1995 12 4.05 -1.95 2.4 0 196.55 139.58 31266 +1995 13 5.72 -0.28 4.07 1.43 218.61 105.12 31366 +1995 14 3.05 -2.95 1.4 0.21 184.28 107.43 31469 +1995 15 -2.09 -8.09 -3.74 0.39 131.09 153.33 31575 +1995 16 -0.77 -6.77 -2.42 0 143.28 190.72 31686 +1995 17 -1.41 -7.41 -3.06 0.05 137.25 155.23 31800 +1995 18 0.56 -5.44 -1.09 0 156.56 193.49 31917 +1995 19 -0.37 -6.37 -2.02 0.03 147.17 157.48 32038 +1995 20 -1.52 -7.52 -3.17 0 136.24 197.75 32161 +1995 21 -3.14 -9.14 -4.79 0 122.03 200.27 32289 +1995 22 0.84 -5.16 -0.81 0 159.48 200 32419 +1995 23 1.46 -4.54 -0.19 0 166.13 201.11 32552 +1995 24 4.06 -1.94 2.41 0 196.67 200.99 32688 +1995 25 5.72 -0.28 4.07 0.07 218.61 120.62 32827 +1995 26 5.52 -0.48 3.87 0.03 215.86 122.17 32969 +1995 27 7.65 1.65 6 0 246.72 163.26 33114 +1995 28 8.79 2.79 7.14 0.15 264.75 123.34 33261 +1995 29 5.58 -0.42 3.93 0.39 216.68 127.07 33411 +1995 30 3.89 -2.11 2.24 0.06 194.54 129.64 33564 +1995 31 3.3 -2.7 1.65 0 187.28 175.62 33718 +1995 32 8.2 2.2 6.55 0.41 255.28 130.48 33875 +1995 33 9.54 3.54 7.89 0 277.21 175.31 34035 +1995 34 12.23 6.23 10.58 0 326.15 174.58 34196 +1995 35 10.25 4.25 8.6 0 289.48 178.86 34360 +1995 36 10.68 4.68 9.03 0 297.12 180.87 34526 +1995 37 10.16 4.16 8.51 0.01 287.9 137.85 34694 +1995 38 12.81 6.81 11.16 0 337.62 183.42 34863 +1995 39 8.83 2.83 7.18 1.6 265.4 142.82 35035 +1995 40 3.98 -2.02 2.33 1.01 195.67 147.89 35208 +1995 41 -0.4 -6.4 -2.05 0.28 146.88 190.04 35383 +1995 42 2.81 -3.19 1.16 0 181.43 240.77 35560 +1995 43 6.77 0.77 5.12 0 233.54 202.78 35738 +1995 44 8.95 2.95 7.3 0 267.37 203.2 35918 +1995 45 10.21 4.21 8.56 0 288.77 204.4 36099 +1995 46 9.94 3.94 8.29 0 284.07 207.35 36282 +1995 47 4.59 -1.41 2.94 1.15 203.46 161.49 36466 +1995 48 8.91 2.91 7.26 0 266.71 214.04 36652 +1995 49 10.72 4.72 9.07 0 297.85 214.69 36838 +1995 50 10.25 4.25 8.6 0 289.48 217.88 37026 +1995 51 9.7 3.7 8.05 0 279.94 221.45 37215 +1995 52 8.32 2.32 6.67 0 257.19 225.8 37405 +1995 53 6.3 0.3 4.65 0 226.75 230.81 37596 +1995 54 5.53 -0.47 3.88 0.18 215.99 175.71 37788 +1995 55 3.83 -2.17 2.18 0.01 193.79 179.08 37981 +1995 56 6.5 0.5 4.85 0.24 229.62 179.28 38175 +1995 57 10.83 4.83 9.18 0.03 299.83 177.67 38370 +1995 58 14.36 8.36 12.71 0 369.98 234.53 38565 +1995 59 15.01 9.01 13.36 0.06 384.31 177.03 38761 +1995 60 16.86 10.86 15.21 0 427.74 235.41 38958 +1995 61 10.9 4.9 9.25 0 301.11 248.07 39156 +1995 62 7.8 1.8 6.15 0 249.03 254.73 39355 +1995 63 5.08 -0.92 3.43 0 209.91 260.6 39553 +1995 64 7.56 1.56 5.91 0 245.35 260.9 39753 +1995 65 9.2 3.2 7.55 0.01 271.5 196.34 39953 +1995 66 8.94 2.94 7.29 1.28 267.2 198.63 40154 +1995 67 7.57 1.57 5.92 0 245.5 269.4 40355 +1995 68 9.56 3.56 7.91 0 277.55 269.76 40556 +1995 69 8.99 2.99 7.34 0.04 268.03 204.84 40758 +1995 70 8.84 2.84 7.19 0.38 265.57 207.11 40960 +1995 71 8.5 2.5 6.85 0 260.06 279.48 41163 +1995 72 7.95 1.95 6.3 0.29 251.36 212.25 41366 +1995 73 4.51 -1.49 2.86 0.04 202.42 217.15 41569 +1995 74 7.1 1.1 5.45 0 238.41 289.45 41772 +1995 75 4.03 -1.97 2.38 0 196.29 295.55 41976 +1995 76 7.59 1.59 5.94 0 245.81 294.23 42179 +1995 77 8.64 2.64 6.99 0 262.32 295.47 42383 +1995 78 6.06 0.06 4.41 0 223.35 301.36 42587 +1995 79 5.04 -0.96 3.39 2.19 209.38 228.94 42791 +1995 80 4.71 -1.29 3.06 0 205.02 308.17 42996 +1995 81 6.13 0.13 4.48 0.01 224.34 231.88 43200 +1995 82 5.2 -0.8 3.55 0 211.52 312.92 43404 +1995 83 4.14 -1.86 2.49 0 197.68 316.6 43608 +1995 84 6.61 0.61 4.96 0.67 231.21 237.25 43812 +1995 85 6.84 0.84 5.19 0.13 234.57 238.93 44016 +1995 86 8.87 2.87 7.22 0.13 266.06 238.68 44220 +1995 87 8.04 2.04 6.39 0 252.77 321.95 44424 +1995 88 8.95 2.95 7.3 0 267.37 323.01 44627 +1995 89 10.65 4.65 9 0 296.59 322.64 44831 +1995 90 11.02 5.02 9.37 0 303.3 324.38 45034 +1995 91 16.69 10.69 15.04 0.17 423.59 236.34 45237 +1995 92 15.8 9.8 14.15 0 402.38 319.37 45439 +1995 93 11.59 5.59 9.94 1.2 313.89 247.55 45642 +1995 94 14.3 8.3 12.65 0.68 368.68 245.21 45843 +1995 95 13.2 7.2 11.55 0.19 345.53 248.48 46045 +1995 96 13.86 7.86 12.21 0.04 359.26 249.04 46246 +1995 97 16.13 10.13 14.48 0 410.13 329.02 46446 +1995 98 12.23 6.23 10.58 0 326.15 339.27 46647 +1995 99 15.49 9.49 13.84 0 395.2 334.41 46846 +1995 100 14.81 8.81 13.16 0 379.85 337.87 47045 +1995 101 17.65 11.65 16 0 447.52 332.84 47243 +1995 102 15.29 9.29 13.64 0 390.64 340.56 47441 +1995 103 17.69 11.69 16.04 0 448.55 336.37 47638 +1995 104 16.32 10.32 14.67 0.75 414.65 256.26 47834 +1995 105 11.47 5.47 9.82 1.3 311.63 265.45 48030 +1995 106 13.87 7.87 12.22 0 359.47 350.76 48225 +1995 107 10.56 4.56 8.91 0.16 294.97 269.2 48419 +1995 108 9.24 3.24 7.59 0.47 272.17 272.21 48612 +1995 109 11.91 5.91 10.26 0 319.97 359.79 48804 +1995 110 9.98 3.98 8.33 0.03 284.76 273.57 48995 +1995 111 13.49 7.49 11.84 0 351.51 359.52 49185 +1995 112 14.49 8.49 12.84 0 372.81 358.82 49374 +1995 113 14.04 8.04 12.39 0.15 363.09 270.88 49561 +1995 114 18 12 16.35 0 456.53 352.64 49748 +1995 115 14.49 8.49 12.84 0 372.81 363.05 49933 +1995 116 13.46 7.46 11.81 0 350.88 366.58 50117 +1995 117 16.59 10.59 14.94 0.05 421.16 270.28 50300 +1995 118 14.52 8.52 12.87 0.45 373.46 275.11 50481 +1995 119 15.06 9.06 13.41 0 385.44 366.71 50661 +1995 120 14.37 8.37 12.72 0 370.19 369.52 50840 +1995 121 19.79 13.79 18.14 0.17 505.07 266.82 51016 +1995 122 15.9 9.9 14.25 0.15 404.71 276.07 51191 +1995 123 13.04 7.04 11.39 0 342.26 375.87 51365 +1995 124 17.11 11.11 15.46 0 433.92 366.97 51536 +1995 125 17.51 11.51 15.86 0 443.96 366.83 51706 +1995 126 15.71 9.71 14.06 0.04 400.28 279.49 51874 +1995 127 17.65 11.65 16 0 447.52 368.29 52039 +1995 128 18.27 12.27 16.62 0 463.59 367.46 52203 +1995 129 11.84 5.84 10.19 0.71 318.63 288.18 52365 +1995 130 13.68 7.68 12.03 0.29 355.47 285.82 52524 +1995 131 15.36 9.36 13.71 0.13 392.23 283.4 52681 +1995 132 16.98 10.98 15.33 1.64 430.7 280.8 52836 +1995 133 17.49 11.49 15.84 0.38 443.46 280.24 52989 +1995 134 9.86 3.86 8.21 0.66 282.68 293.97 53138 +1995 135 11.65 5.65 10 0 315.02 389.24 53286 +1995 136 17.93 11.93 16.28 0 454.72 374.4 53430 +1995 137 21.42 15.42 19.77 1.47 553.01 272.76 53572 +1995 138 19.87 13.87 18.22 0.01 507.33 277.22 53711 +1995 139 20.99 14.99 19.34 0 540 366.47 53848 +1995 140 23.29 17.29 21.64 0.06 612.72 268.7 53981 +1995 141 21.13 15.13 19.48 0 544.21 366.87 54111 +1995 142 25.05 19.05 23.4 0 673.83 351.71 54238 +1995 143 25.87 19.87 24.22 0.93 704.01 261.37 54362 +1995 144 21.14 15.14 19.49 0.52 544.51 276.23 54483 +1995 145 20.96 14.96 19.31 0.26 539.11 277.06 54600 +1995 146 19.61 13.61 17.96 0.52 500 280.79 54714 +1995 147 18.44 12.44 16.79 0.02 468.08 283.93 54824 +1995 148 15.83 9.83 14.18 0.02 403.08 289.81 54931 +1995 149 13.84 7.84 12.19 0.07 358.84 293.76 55034 +1995 150 14.65 8.65 13 0 376.32 390.08 55134 +1995 151 18.38 12.38 16.73 0.09 466.49 285.13 55229 +1995 152 22.14 16.14 20.49 0 575.39 367.39 55321 +1995 153 19.24 13.24 17.59 0 489.71 377.82 55409 +1995 154 23.08 17.08 21.43 1.07 605.76 273.2 55492 +1995 155 17.06 11.06 15.41 0.64 432.68 288.71 55572 +1995 156 15.32 9.32 13.67 0.56 391.32 292.49 55648 +1995 157 18.53 12.53 16.88 0 470.47 381.06 55719 +1995 158 17.62 11.62 15.97 0 446.76 383.99 55786 +1995 159 19.08 13.08 17.43 0.58 485.32 284.81 55849 +1995 160 22.7 16.7 21.05 0.05 593.32 275.27 55908 +1995 161 22.02 16.02 20.37 0.99 571.61 277.29 55962 +1995 162 22.93 16.93 21.28 0 600.82 366.23 56011 +1995 163 24.9 18.9 23.25 1.16 668.43 268.6 56056 +1995 164 24.6 18.6 22.95 1.53 657.73 269.62 56097 +1995 165 23.81 17.81 22.16 1.32 630.27 272.23 56133 +1995 166 17.06 11.06 15.41 1.65 432.68 289.96 56165 +1995 167 18.24 12.24 16.59 0 462.8 383.07 56192 +1995 168 17.31 11.31 15.66 0.1 438.92 289.44 56214 +1995 169 22.27 16.27 20.62 0 579.51 369.28 56231 +1995 170 21.64 15.64 19.99 0 559.77 371.67 56244 +1995 171 19.66 13.66 18.01 0 501.4 378.69 56252 +1995 172 21.4 15.4 19.75 0 552.4 372.6 56256 +1995 173 23.25 17.25 21.6 0 611.39 365.43 56255 +1995 174 19.02 13.02 17.37 0 483.68 380.67 56249 +1995 175 21.81 15.81 20.16 0.1 565.04 278.21 56238 +1995 176 22.59 16.59 20.94 0 589.76 367.92 56223 +1995 177 19.72 13.72 18.07 0.06 503.09 283.66 56203 +1995 178 19.41 13.41 17.76 0 494.41 379.26 56179 +1995 179 16.16 10.16 14.51 0.15 410.84 291.64 56150 +1995 180 15.39 9.39 13.74 1.18 392.91 293.08 56116 +1995 181 18.11 12.11 16.46 0 459.4 383.06 56078 +1995 182 25.95 19.95 24.3 0 707.02 352.96 56035 +1995 183 28.73 22.73 27.08 0 818.41 338.68 55987 +1995 184 28.17 22.17 26.52 0 794.85 341.55 55935 +1995 185 29.69 23.69 28.04 0.3 860.16 249.81 55879 +1995 186 29.58 23.58 27.93 0.07 855.28 250.11 55818 +1995 187 28.53 22.53 26.88 0.29 809.93 254.35 55753 +1995 188 26.17 20.17 24.52 0.5 715.34 263.14 55684 +1995 189 24.88 18.88 23.23 0.01 667.71 267.45 55611 +1995 190 24.35 18.35 22.7 0 648.93 358.55 55533 +1995 191 26.94 20.94 25.29 0.61 745.11 259.75 55451 +1995 192 25.18 19.18 23.53 0 678.54 354.35 55366 +1995 193 22.02 16.02 20.37 0 571.61 367.13 55276 +1995 194 21.73 15.73 20.08 0.03 562.55 275.99 55182 +1995 195 24.65 18.65 23 0 659.51 355.96 55085 +1995 196 22.43 16.43 20.78 0 584.62 364.67 54984 +1995 197 19.79 13.79 18.14 0 505.07 373.67 54879 +1995 198 17.72 11.72 16.07 0 449.31 379.71 54770 +1995 199 21.08 15.08 19.43 0.24 542.7 276.34 54658 +1995 200 22.67 16.67 21.02 0.08 592.35 271.6 54542 +1995 201 26 20 24.35 0 708.9 347.46 54423 +1995 202 28.36 22.36 26.71 0.04 802.78 251.38 54301 +1995 203 28.41 22.41 26.76 0.1 804.87 250.83 54176 +1995 204 28.81 22.81 27.16 0 821.82 331.83 54047 +1995 205 27.66 21.66 26.01 0 773.9 337.38 53915 +1995 206 25.98 19.98 24.33 0.18 708.15 258.76 53780 +1995 207 24.33 18.33 22.68 1.8 648.23 263.77 53643 +1995 208 26.92 20.92 25.27 0 744.33 339.29 53502 +1995 209 27.52 21.52 25.87 0.36 768.23 251.79 53359 +1995 210 25.4 19.4 23.75 0.14 686.58 258.89 53213 +1995 211 25.12 19.12 23.47 0.24 676.36 259.25 53064 +1995 212 27.05 21.05 25.4 0 749.45 335.98 52913 +1995 213 24.07 18.07 22.42 0 639.2 348.65 52760 +1995 214 22.63 16.63 20.98 1.23 591.05 265.24 52604 +1995 215 18.28 12.28 16.63 0.49 463.85 275.76 52445 +1995 216 18.39 12.39 16.74 0 466.76 366.32 52285 +1995 217 19.23 13.23 17.58 0.02 489.43 272.14 52122 +1995 218 18.34 12.34 16.69 0 465.43 364.74 51958 +1995 219 23.82 17.82 22.17 0 630.61 344.63 51791 +1995 220 24.49 18.49 22.84 0 653.85 340.97 51622 +1995 221 22.39 16.39 20.74 0 583.34 348.28 51451 +1995 222 19.76 13.76 18.11 0 504.22 356.31 51279 +1995 223 19.15 13.15 17.5 0 487.23 357.08 51105 +1995 224 19.38 13.38 17.73 0 493.58 355.3 50929 +1995 225 22.38 16.38 20.73 0 583.02 344 50751 +1995 226 24.01 18.01 22.36 0 637.13 336.62 50572 +1995 227 18.64 12.64 16.99 0.8 473.41 265.47 50392 +1995 228 18.15 12.15 16.5 0.28 460.44 265.62 50210 +1995 229 18.14 12.14 16.49 0.02 460.18 264.7 50026 +1995 230 18.15 12.15 16.5 0 460.44 351.62 49842 +1995 231 16.16 10.16 14.51 0.1 410.84 266.61 49656 +1995 232 18.69 12.69 17.04 0.57 474.75 260.42 49469 +1995 233 23.69 17.69 22.04 0.26 626.18 246.7 49280 +1995 234 25.76 19.76 24.11 0.32 699.9 239.34 49091 +1995 235 25.45 19.45 23.8 1.46 688.41 239.27 48900 +1995 236 27.42 21.42 25.77 2.44 764.2 231.68 48709 +1995 237 26.25 20.25 24.6 0 718.38 312.67 48516 +1995 238 26.86 20.86 25.21 0.59 741.97 231.29 48323 +1995 239 28.04 22.04 26.39 0.16 789.46 226.12 48128 +1995 240 27.61 21.61 25.96 0 771.87 301.9 47933 +1995 241 25.47 19.47 23.82 0.64 689.15 232.28 47737 +1995 242 25.37 19.37 23.72 1.95 685.47 231.35 47541 +1995 243 25.65 19.65 24 0.11 695.8 229.16 47343 +1995 244 24.86 18.86 23.21 0.66 666.99 230.27 47145 +1995 245 24.7 18.7 23.05 0.03 661.28 229.42 46947 +1995 246 22.9 16.9 21.25 0.02 599.84 233.02 46747 +1995 247 19.82 13.82 18.17 0 505.92 318.82 46547 +1995 248 20.59 14.59 18.94 0.23 528.14 235.95 46347 +1995 249 18.35 12.35 16.7 0.14 465.7 239.23 46146 +1995 250 17.59 11.59 15.94 2.12 446 239.27 45945 +1995 251 19.28 13.28 17.63 0.98 490.81 234.29 45743 +1995 252 14.64 8.64 12.99 0.16 376.1 241.2 45541 +1995 253 15.07 9.07 13.42 0 385.66 318.52 45339 +1995 254 16.14 10.14 14.49 0.29 410.37 235.48 45136 +1995 255 13.49 7.49 11.84 0 351.51 317.32 44933 +1995 256 13.12 7.12 11.47 0.79 343.89 236.79 44730 +1995 257 17.34 11.34 15.69 0.24 439.67 228.33 44527 +1995 258 21.75 15.75 20.1 0.05 563.17 217.49 44323 +1995 259 18.68 12.68 17.03 0.21 474.48 222.25 44119 +1995 260 16.46 10.46 14.81 0 418.01 299.35 43915 +1995 261 18.73 12.73 17.08 0.01 475.82 218.58 43711 +1995 262 16.35 10.35 14.7 0.78 415.37 221.08 43507 +1995 263 14.37 8.37 12.72 3.97 370.19 222.33 43303 +1995 264 12.44 6.44 10.79 0 330.27 297.41 43099 +1995 265 13.58 7.58 11.93 0 353.38 292.96 42894 +1995 266 17.15 11.15 15.5 0 434.92 283.14 42690 +1995 267 13.36 7.36 11.71 0 348.81 288.14 42486 +1995 268 15.22 9.22 13.57 0 389.05 282.03 42282 +1995 269 18.01 12.01 16.36 1.41 456.79 205.12 42078 +1995 270 19.37 13.37 17.72 0.37 493.3 200.71 41875 +1995 271 17.49 11.49 15.84 0 443.46 269.5 41671 +1995 272 17.26 11.26 15.61 0 437.66 267.32 41468 +1995 273 13.81 7.81 12.16 0.85 358.21 203.71 41265 +1995 274 13.61 7.61 11.96 0 354.01 269.28 41062 +1995 275 14.35 8.35 12.7 0 369.76 265.2 40860 +1995 276 17.79 11.79 16.14 0 451.11 255.67 40658 +1995 277 14.14 8.14 12.49 0 365.23 260.22 40456 +1995 278 12.03 6.03 10.38 0 322.28 260.81 40255 +1995 279 11.55 5.55 9.9 0 313.13 258.69 40054 +1995 280 11.85 5.85 10.2 0 318.82 255.57 39854 +1995 281 12 6 10.35 0 321.7 252.61 39654 +1995 282 11.29 5.29 9.64 0.14 308.27 188.16 39455 +1995 283 10.48 4.48 8.83 0 293.55 249.15 39256 +1995 284 10.25 4.25 8.6 0.38 289.48 184.8 39058 +1995 285 10.29 4.29 8.64 0.16 290.18 182.76 38861 +1995 286 12.81 6.81 11.16 0 337.62 237.37 38664 +1995 287 11.4 5.4 9.75 0 310.32 236.45 38468 +1995 288 16.37 10.37 14.72 0 415.85 225.78 38273 +1995 289 17.67 11.67 16.02 0 448.04 220.75 38079 +1995 290 13.5 7.5 11.85 0 351.71 225.15 37885 +1995 291 14.65 8.65 13 0 376.32 220.68 37693 +1995 292 11.86 5.86 10.21 0 319.01 222.13 37501 +1995 293 11.98 5.98 10.33 0 321.31 219.23 37311 +1995 294 14.08 8.08 12.43 0.18 363.94 160.02 37121 +1995 295 14.76 8.76 13.11 0 378.75 209.52 36933 +1995 296 17.45 11.45 15.8 0 442.44 202.45 36745 +1995 297 20.09 14.09 18.44 0 513.62 194.68 36560 +1995 298 16.01 10.01 14.36 0 407.3 199.76 36375 +1995 299 18.48 12.48 16.83 0 469.14 192.72 36191 +1995 300 19.96 13.96 18.31 0 509.9 187.3 36009 +1995 301 19.67 13.67 18.02 0 501.68 185.49 35829 +1995 302 17.13 11.13 15.48 0 434.42 187.62 35650 +1995 303 21.28 15.28 19.63 0 548.75 177.29 35472 +1995 304 17.68 11.68 16.03 0.29 448.29 136.37 35296 +1995 305 10.07 4.07 8.42 0.4 286.32 142.18 35122 +1995 306 6.79 0.79 5.14 1.13 233.83 142.86 34950 +1995 307 4.28 -1.72 2.63 0.56 199.47 142.45 34779 +1995 308 3.88 -2.12 2.23 0.15 194.41 140.68 34610 +1995 309 4.1 -1.9 2.45 0.14 197.18 138.8 34444 +1995 310 6.55 0.55 4.9 0.64 230.34 135.55 34279 +1995 311 8.6 2.6 6.95 0 261.67 176.75 34116 +1995 312 9.67 3.67 8.02 0.04 279.43 129.82 33956 +1995 313 4.26 -1.74 2.61 0 199.21 175.45 33797 +1995 314 4.02 -1.98 2.37 0 196.17 173.63 33641 +1995 315 4.86 -1.14 3.21 0 206.99 170.5 33488 +1995 316 2.65 -3.35 1 0 179.56 169.73 33337 +1995 317 4.44 -1.56 2.79 0.01 201.52 124.78 33188 +1995 318 4.95 -1.05 3.3 0 208.18 163.67 33042 +1995 319 4.86 -1.14 3.21 0.72 206.99 121.51 32899 +1995 320 4.55 -1.45 2.9 0.01 202.94 120.25 32758 +1995 321 5.73 -0.27 4.08 0 218.75 157.41 32620 +1995 322 3.25 -2.75 1.6 0 186.68 157.19 32486 +1995 323 4.2 -1.8 2.55 0 198.45 154.98 32354 +1995 324 7.54 1.54 5.89 0 245.04 150.58 32225 +1995 325 6.11 0.11 4.46 0 224.06 149.91 32100 +1995 326 10.21 4.21 8.56 0 288.77 145.19 31977 +1995 327 10.33 4.33 8.68 0.51 290.89 107.44 31858 +1995 328 6.24 0.24 4.59 0.09 225.9 108.41 31743 +1995 329 3.81 -2.19 2.16 0.03 193.54 108.45 31631 +1995 330 1.34 -4.66 -0.31 0 164.82 144.48 31522 +1995 331 3.66 -2.34 2.01 0 191.68 141.91 31417 +1995 332 9.98 3.98 8.33 0 284.76 135.81 31316 +1995 333 7.79 1.79 6.14 0 248.88 136.48 31218 +1995 334 10.77 4.77 9.12 0 298.75 132.98 31125 +1995 335 7.33 1.33 5.68 0.22 241.86 100.92 31035 +1995 336 6.31 0.31 4.66 0.8 226.89 100.65 30949 +1995 337 7.23 1.23 5.58 0.08 240.35 98.93 30867 +1995 338 4.69 -1.31 3.04 0.52 204.76 99.46 30790 +1995 339 5.33 -0.67 3.68 1.45 213.27 98.58 30716 +1995 340 6.81 0.81 5.16 0.26 234.13 97.32 30647 +1995 341 8.66 2.66 7.01 0.07 262.64 95.65 30582 +1995 342 8.65 2.65 7 0 262.48 126.79 30521 +1995 343 7.78 1.78 6.13 0.06 248.73 94.95 30465 +1995 344 8.82 2.82 7.17 0 265.24 124.73 30413 +1995 345 7.87 1.87 6.22 0.87 250.12 93.75 30366 +1995 346 5.03 -0.97 3.38 0 209.25 126.28 30323 +1995 347 4.46 -1.54 2.81 0.45 201.78 94.51 30284 +1995 348 4.54 -1.46 2.89 1.15 202.81 94.21 30251 +1995 349 -5.2 -11.2 -6.85 0.37 105.84 141.8 30221 +1995 350 -7.17 -13.17 -8.82 0 92.13 174.34 30197 +1995 351 -1.72 -7.72 -3.37 0.1 134.41 140.91 30177 +1995 352 -2.28 -8.28 -3.93 0.06 129.41 141.2 30162 +1995 353 -1.5 -7.5 -3.15 0 136.42 172.78 30151 +1995 354 -0.33 -6.33 -1.98 0 147.56 172.3 30145 +1995 355 -0.78 -6.78 -2.43 0 143.19 172.48 30144 +1995 356 2.41 -3.59 0.76 0.59 176.78 139.37 30147 +1995 357 4.35 -1.65 2.7 0.56 200.36 138.07 30156 +1995 358 2.45 -3.55 0.8 2.26 177.24 138.53 30169 +1995 359 -2.6 -8.6 -4.25 1.33 126.62 144.4 30186 +1995 360 1.74 -4.26 0.09 0 169.21 174.73 30208 +1995 361 3.78 -2.22 2.13 0 193.17 173.49 30235 +1995 362 9.02 3.02 7.37 0 268.52 169.33 30267 +1995 363 7.45 1.45 5.8 0 243.67 169.99 30303 +1995 364 5.22 -0.78 3.57 0.11 211.79 139.42 30343 +1995 365 9.27 3.27 7.62 0.18 272.67 93.23 30388 +1996 1 4.69 -1.31 3.04 0.03 204.76 96.2 30438 +1996 2 0.83 -5.17 -0.82 1.49 159.38 98.23 30492 +1996 3 2.1 -3.9 0.45 0.06 173.24 98.49 30551 +1996 4 2.19 -3.81 0.54 0.14 174.26 99.14 30614 +1996 5 -0.37 -6.37 -2.02 0 147.17 134.01 30681 +1996 6 0.33 -5.67 -1.32 0.14 154.19 100.96 30752 +1996 7 0.62 -5.38 -1.03 0.02 157.18 101.46 30828 +1996 8 0.52 -5.48 -1.13 0 156.14 136.82 30907 +1996 9 1.14 -4.86 -0.51 0.02 162.67 103.35 30991 +1996 10 4.61 -1.39 2.96 0 203.72 137.25 31079 +1996 11 4.91 -1.09 3.26 0.15 207.65 103.54 31171 +1996 12 2.95 -3.05 1.3 0.85 183.09 105.15 31266 +1996 13 3 -3 1.35 0.27 183.68 106.34 31366 +1996 14 3.11 -2.89 1.46 0.11 184.99 107.41 31469 +1996 15 1.11 -4.89 -0.54 0 162.35 145.71 31575 +1996 16 2.96 -3.04 1.31 0 183.21 146.03 31686 +1996 17 -1.43 -7.43 -3.08 0.07 137.07 154.12 31800 +1996 18 1.5 -4.5 -0.15 0 166.57 191.79 31917 +1996 19 -5 -11 -6.65 0 107.32 196.29 32038 +1996 20 -1.14 -7.14 -2.79 0 139.77 196.27 32161 +1996 21 2.69 -3.31 1.04 0 180.03 155.31 32289 +1996 22 2.75 -3.25 1.1 0 180.73 157.03 32419 +1996 23 4.74 -1.26 3.09 0 205.42 157.57 32552 +1996 24 3.46 -2.54 1.81 0 189.23 160.45 32688 +1996 25 6.54 0.54 4.89 0.3 230.2 120.17 32827 +1996 26 2.37 -3.63 0.72 0 176.32 164.93 32969 +1996 27 4.68 -1.32 3.03 0 204.63 165.5 33114 +1996 28 7.11 1.11 5.46 0.01 238.56 124.42 33261 +1996 29 6.93 0.93 5.28 0 235.89 168.39 33411 +1996 30 5.01 -0.99 3.36 0.05 208.98 129.06 33564 +1996 31 7.26 1.26 5.61 0.13 240.81 129.52 33718 +1996 32 2.93 -3.07 1.28 0 182.85 177.98 33875 +1996 33 4.65 -1.35 3 0.19 204.24 134.58 34035 +1996 34 0.71 -5.29 -0.94 0 158.12 184.16 34196 +1996 35 -0.71 -6.71 -2.36 0 143.86 187.09 34360 +1996 36 -1.34 -7.34 -2.99 0 137.9 189.95 34526 +1996 37 -0.58 -6.58 -2.23 0 145.12 192.02 34694 +1996 38 1.53 -4.47 -0.12 0 166.89 193.59 34863 +1996 39 1.94 -4.06 0.29 0 171.44 195.96 35035 +1996 40 -1.15 -7.15 -2.8 0 139.68 200.38 35208 +1996 41 -2.06 -8.06 -3.71 0 131.35 203.5 35383 +1996 42 -2.59 -8.59 -4.24 0.34 126.7 192.8 35560 +1996 43 -1.74 -7.74 -3.39 0 134.23 246.52 35738 +1996 44 0.83 -5.17 -0.82 0.33 159.38 194.93 35918 +1996 45 1.82 -4.18 0.17 0 170.1 249.01 36099 +1996 46 4.69 -1.31 3.04 0.15 204.76 195.78 36282 +1996 47 2.53 -3.47 0.88 0 178.16 216.89 36466 +1996 48 1.76 -4.24 0.11 0 169.43 220.26 36652 +1996 49 1.37 -4.63 -0.28 0 165.15 223.32 36838 +1996 50 6.07 0.07 4.42 0.06 223.49 166.72 37026 +1996 51 2.22 -3.78 0.57 0.11 174.6 171.31 37215 +1996 52 -0.72 -6.72 -2.37 0.27 143.77 210.89 37405 +1996 53 0.02 -5.98 -1.63 0.41 151.05 212.61 37596 +1996 54 1.67 -4.33 0.02 0.63 168.43 213.51 37788 +1996 55 3.3 -2.7 1.65 1.07 187.28 214.32 37981 +1996 56 4.36 -1.64 2.71 0.29 200.49 180.77 38175 +1996 57 5 -1 3.35 0 208.85 243.36 38370 +1996 58 3.37 -2.63 1.72 0.31 188.13 185.79 38565 +1996 59 1.61 -4.39 -0.04 0 167.77 251.84 38761 +1996 60 9.67 3.67 8.02 0 279.43 246.8 38958 +1996 61 7.14 1.14 5.49 0 239.01 252.68 39156 +1996 62 7.9 1.9 6.25 0 250.58 254.61 39355 +1996 63 6.75 0.75 5.1 0 233.25 258.89 39553 +1996 64 7.01 1.01 5.36 0 237.08 261.51 39753 +1996 65 8.13 2.13 6.48 0 254.18 263.11 39953 +1996 66 12.65 6.65 11 0 334.42 259.55 40154 +1996 67 12.05 6.05 10.4 0.3 322.66 197.5 40355 +1996 68 8 2 6.35 0 252.14 271.75 40556 +1996 69 8.12 2.12 6.47 0 254.02 274.22 40758 +1996 70 1.23 -4.77 -0.42 0 163.64 283.96 40960 +1996 71 6.36 0.36 4.71 0 227.61 282.05 41163 +1996 72 6.09 0.09 4.44 0 223.77 285.18 41366 +1996 73 2.95 -3.05 1.3 0.7 183.09 218.27 41569 +1996 74 5.19 -0.81 3.54 0 211.39 291.61 41772 +1996 75 3.88 -2.12 2.23 0 194.41 295.7 41976 +1996 76 7.24 1.24 5.59 0 240.5 294.66 42179 +1996 77 0.95 -5.05 -0.7 0 160.64 303.65 42383 +1996 78 2.62 -3.38 0.97 0 179.21 304.91 42587 +1996 79 5.61 -0.39 3.96 0 217.09 304.62 42791 +1996 80 2.74 -3.26 1.09 0.09 180.61 232.61 42996 +1996 81 1.58 -4.42 -0.07 0 167.44 313.82 43200 +1996 82 6.44 0.44 4.79 0.21 228.76 233.61 43404 +1996 83 8.77 2.77 7.12 0 264.42 310.93 43608 +1996 84 4.31 -1.69 2.66 0.3 199.85 239.24 43812 +1996 85 3.2 -2.8 1.55 0.01 186.07 242.01 44016 +1996 86 3.59 -2.41 1.94 0 190.82 324.73 44220 +1996 87 6.32 0.32 4.67 0 227.04 324.2 44424 +1996 88 4.28 -1.72 2.63 0 199.47 328.96 44627 +1996 89 7.18 1.18 5.53 0.09 239.61 245.83 44831 +1996 90 5.75 -0.25 4.1 0.07 219.02 248.98 45034 +1996 91 12.87 6.87 11.22 0.03 338.83 242.47 45237 +1996 92 17.88 11.88 16.23 2 453.43 235.75 45439 +1996 93 21.71 15.71 20.06 1.12 561.93 229.02 45642 +1996 94 21.07 15.07 19.42 0.67 542.4 232.07 45843 +1996 95 16.85 10.85 15.2 0.15 427.5 242.41 46045 +1996 96 12.54 6.54 10.89 0 332.24 334.69 46246 +1996 97 17.23 11.23 15.58 0 436.91 326.31 46446 +1996 98 15.53 9.53 13.88 0 396.12 332.35 46647 +1996 99 15.98 9.98 14.33 0 406.59 333.26 46846 +1996 100 18.8 12.8 17.15 0.5 477.71 245.87 47045 +1996 101 17.5 11.5 15.85 0.01 443.71 249.93 47243 +1996 102 21.12 15.12 19.47 0 543.91 324.46 47441 +1996 103 19.74 13.74 18.09 0.18 503.65 247.9 47638 +1996 104 13.75 7.75 12.1 0 356.94 347.6 47834 +1996 105 14.18 8.18 12.53 0.14 366.09 261.34 48030 +1996 106 17.99 11.99 16.34 0 456.27 340.66 48225 +1996 107 12.42 6.42 10.77 0 329.87 355.43 48419 +1996 108 12.14 6.14 10.49 0.47 324.4 268.3 48612 +1996 109 12.1 6.1 10.45 0.11 323.63 269.57 48804 +1996 110 11.57 5.57 9.92 0 313.51 361.87 48995 +1996 111 9.64 3.64 7.99 0.01 278.91 275.18 49185 +1996 112 10.84 4.84 9.19 0 300.02 366.32 49374 +1996 113 7.96 1.96 6.31 0 251.52 372.53 49561 +1996 114 9.37 3.37 7.72 0 274.35 371.78 49748 +1996 115 9.6 3.6 7.95 0.43 278.23 279.63 49933 +1996 116 9.92 3.92 8.27 0.31 283.72 280.14 50117 +1996 117 14.77 8.77 13.12 1.96 378.97 273.69 50300 +1996 118 13.67 7.67 12.02 0.07 355.26 276.56 50481 +1996 119 10.05 4.05 8.4 0.52 285.98 282.88 50661 +1996 120 13.21 7.21 11.56 0 345.73 372.13 50840 +1996 121 19.83 13.83 18.18 0.95 506.2 266.73 51016 +1996 122 16.7 10.7 15.05 0.27 423.83 274.5 51191 +1996 123 15.96 9.96 14.31 0.04 406.12 276.73 51365 +1996 124 16.88 10.88 15.23 0 428.23 367.6 51536 +1996 125 17.75 11.75 16.1 0.14 450.08 274.61 51706 +1996 126 18.34 12.34 16.69 0.07 465.43 274.05 51874 +1996 127 16.42 10.42 14.77 0.06 417.05 278.76 52039 +1996 128 15.67 9.67 14.02 0.01 399.35 280.98 52203 +1996 129 15.2 9.2 13.55 0.66 388.59 282.5 52365 +1996 130 14.77 8.77 13.12 0 378.97 378.52 52524 +1996 131 18.5 12.5 16.85 0.12 469.67 276.88 52681 +1996 132 20.87 14.87 19.22 0.26 536.42 271.71 52836 +1996 133 18.56 12.56 16.91 0.97 471.27 277.87 52989 +1996 134 20.88 14.88 19.23 0 536.72 363.61 53138 +1996 135 20.13 14.13 18.48 0.04 514.76 275.14 53286 +1996 136 21.09 15.09 19.44 0.01 543 273.13 53430 +1996 137 22.36 16.36 20.71 1.83 582.38 270.14 53572 +1996 138 23.49 17.49 21.84 0.77 619.42 267.25 53711 +1996 139 26.48 20.48 24.83 1.28 727.2 257.85 53848 +1996 140 23.17 17.17 21.52 1.31 608.73 269.06 53981 +1996 141 21.69 15.69 20.04 0.05 561.31 273.63 54111 +1996 142 19.41 13.41 17.76 0 494.41 373.2 54238 +1996 143 21.77 15.77 20.12 0.03 563.79 274.16 54362 +1996 144 18.97 12.97 17.32 0.02 482.32 281.71 54483 +1996 145 21.19 15.19 19.54 0 546.02 368.59 54600 +1996 146 21.93 15.93 20.28 0 568.78 366.24 54714 +1996 147 21.62 15.62 19.97 0 559.15 367.85 54824 +1996 148 22.05 16.05 20.4 0 572.55 366.62 54931 +1996 149 20.99 14.99 19.34 0.16 540 278.11 55034 +1996 150 16.84 10.84 15.19 1.03 427.25 288.23 55134 +1996 151 18.7 12.7 17.05 0 475.02 379.18 55229 +1996 152 23.07 17.07 21.42 0 605.43 363.76 55321 +1996 153 23.47 17.47 21.82 0.36 618.75 271.78 55409 +1996 154 27.6 21.6 25.95 0.8 771.46 257.75 55492 +1996 155 26.4 20.4 24.75 0.15 724.13 262.36 55572 +1996 156 23.12 17.12 21.47 1.98 607.08 273.45 55648 +1996 157 18.35 12.35 16.7 0.01 465.7 286.22 55719 +1996 158 20.84 14.84 19.19 0.05 535.53 280.17 55786 +1996 159 24.06 18.06 22.41 0.23 638.85 270.96 55849 +1996 160 27.08 21.08 25.43 0 750.64 347.51 55908 +1996 161 27.27 21.27 25.62 0 758.19 346.61 55962 +1996 162 28.39 22.39 26.74 0 804.04 340.83 56011 +1996 163 27.42 21.42 25.77 0 764.2 346.11 56056 +1996 164 24.11 18.11 22.46 0 640.58 361.62 56097 +1996 165 21.56 15.56 19.91 0.08 557.3 278.89 56133 +1996 166 23.65 17.65 22 0.6 624.82 272.79 56165 +1996 167 20.32 14.32 18.67 0 520.25 376.31 56192 +1996 168 20.46 14.46 18.81 0 524.33 375.9 56214 +1996 169 23.44 17.44 21.79 0 617.74 364.62 56231 +1996 170 18.96 12.96 17.31 0.07 482.04 285.68 56244 +1996 171 16.27 10.27 14.62 0.85 413.46 291.69 56252 +1996 172 21.88 15.88 20.23 0 567.22 370.82 56256 +1996 173 21.12 15.12 19.47 0 543.91 373.6 56255 +1996 174 19.38 13.38 17.73 0 493.58 379.5 56249 +1996 175 21.04 15.04 19.39 0.98 541.5 280.33 56238 +1996 176 23.52 17.52 21.87 0 620.43 364.18 56223 +1996 177 24.77 18.77 23.12 0 663.78 358.74 56203 +1996 178 23.57 17.57 21.92 0 622.12 363.9 56179 +1996 179 21.36 15.36 19.71 0 551.18 372.4 56150 +1996 180 21.99 15.99 20.34 0 570.66 369.94 56116 +1996 181 23.42 17.42 21.77 0 617.07 364.23 56078 +1996 182 23.92 17.92 22.27 0 634.03 362.01 56035 +1996 183 23.47 17.47 21.82 0.26 618.75 272.78 55987 +1996 184 24.71 18.71 23.06 0.22 661.64 268.72 55935 +1996 185 23.12 17.12 21.47 0.21 607.08 273.68 55879 +1996 186 23.19 17.19 21.54 1.16 609.4 273.28 55818 +1996 187 21.88 15.88 20.23 0 567.22 369.29 55753 +1996 188 19.49 13.49 17.84 0.01 496.64 283.07 55684 +1996 189 17.2 11.2 15.55 0.11 436.16 288.2 55611 +1996 190 16.52 10.52 14.87 0 419.46 385.81 55533 +1996 191 17.31 11.31 15.66 0.23 438.92 287.48 55451 +1996 192 20.14 14.14 18.49 0 515.05 374.13 55366 +1996 193 26.16 20.16 24.51 0 714.96 349.57 55276 +1996 194 24.19 18.19 22.54 2.42 643.35 268.66 55182 +1996 195 22.39 16.39 20.74 1.3 583.34 273.92 55085 +1996 196 22.88 16.88 21.23 0.38 599.18 272.19 54984 +1996 197 23.68 17.68 22.03 0 625.84 359.24 54879 +1996 198 29.23 23.23 27.58 0.03 839.93 249.08 54770 +1996 199 27.2 21.2 25.55 0.01 755.4 256.86 54658 +1996 200 27.53 21.53 25.88 0 768.63 340.45 54542 +1996 201 24.58 18.58 22.93 0 657.03 353.84 54423 +1996 202 25.59 19.59 23.94 0.1 693.58 261.6 54301 +1996 203 22.31 16.31 20.66 0.11 580.78 271.5 54176 +1996 204 21.68 15.68 20.03 0.01 561.01 272.89 54047 +1996 205 17.48 11.48 15.83 0 443.2 377.03 53915 +1996 206 20.6 14.6 18.95 0 528.43 366.62 53780 +1996 207 19.58 13.58 17.93 0 499.16 369.37 53643 +1996 208 25.16 19.16 23.51 0 677.81 347.47 53502 +1996 209 23.9 17.9 22.25 0 633.35 352.23 53359 +1996 210 19.41 13.41 17.76 0 494.41 367.98 53213 +1996 211 19.64 13.64 17.99 0.52 500.84 274.84 53064 +1996 212 22.12 16.12 20.47 0 574.76 357.05 52913 +1996 213 20.83 14.83 19.18 0.29 535.23 270.69 52760 +1996 214 23.84 17.84 22.19 0.03 631.29 261.65 52604 +1996 215 23.29 17.29 21.64 0.03 612.72 262.82 52445 +1996 216 24.89 18.89 23.24 0 668.07 342.83 52285 +1996 217 23 17 21.35 0.1 603.12 262.27 52122 +1996 218 22.58 16.58 20.93 0.11 589.44 262.87 51958 +1996 219 18.91 12.91 17.26 0 480.69 361.97 51791 +1996 220 18.27 12.27 16.62 0 463.59 362.94 51622 +1996 221 19.95 13.95 18.3 0.27 509.61 267.56 51451 +1996 222 20.98 14.98 19.33 0.55 539.7 264.21 51279 +1996 223 19.19 13.19 17.54 0 488.33 356.95 51105 +1996 224 21.76 15.76 20.11 0 563.48 347.37 50929 +1996 225 23.96 17.96 22.31 0 635.41 337.93 50751 +1996 226 21.03 15.03 19.38 0.01 541.2 260.74 50572 +1996 227 19.28 13.28 17.63 0 490.81 352.03 50392 +1996 228 24.42 18.42 22.77 0 651.39 332.55 50210 +1996 229 23.69 17.69 22.04 0.58 626.18 250.71 50026 +1996 230 24.19 18.19 22.54 0.51 643.35 248.3 49842 +1996 231 25.21 19.21 23.56 0.11 679.63 244.09 49656 +1996 232 26.88 20.88 25.23 2.65 742.76 237.59 49469 +1996 233 25.82 19.82 24.17 1.18 702.14 240.15 49280 +1996 234 22.13 16.13 20.48 1.24 575.07 249.99 49091 +1996 235 22.63 16.63 20.98 1.36 591.05 247.56 48900 +1996 236 27.07 21.07 25.42 0.08 750.24 232.9 48709 +1996 237 26.97 20.97 25.32 0.11 746.3 232.09 48516 +1996 238 27 21 25.35 0.4 747.48 230.81 48323 +1996 239 24.44 18.44 22.79 0 652.09 317.19 48128 +1996 240 23.41 17.41 21.76 0 616.73 319.44 47933 +1996 241 23.48 17.48 21.83 0 619.08 317.51 47737 +1996 242 25.67 19.67 24.02 0.14 696.55 230.42 47541 +1996 243 27.62 21.62 25.97 0 772.27 296.92 47343 +1996 244 21.43 15.43 19.78 0.65 553.32 239.54 47145 +1996 245 18.87 12.87 17.22 1.88 479.6 244.01 46947 +1996 246 20.6 14.6 18.95 0.01 528.43 238.72 46747 +1996 247 20.84 14.84 19.19 0.07 535.53 236.79 46547 +1996 248 19.29 13.29 17.64 0.04 491.09 238.83 46347 +1996 249 16.48 10.48 14.83 0.07 418.5 242.8 46146 +1996 250 18.85 12.85 17.2 0 479.06 315.68 45945 +1996 251 22.06 16.06 20.41 0.86 572.86 227.96 45743 +1996 252 22.26 16.26 20.61 1.17 579.19 225.9 45541 +1996 253 24.24 18.24 22.59 0.61 645.09 219.21 45339 +1996 254 20.43 14.43 18.78 0.25 523.45 227.08 45136 +1996 255 19.29 13.29 17.64 0.32 491.09 227.85 44933 +1996 256 16.86 10.86 15.21 0.56 427.74 230.82 44730 +1996 257 15.48 9.48 13.83 1.14 394.97 231.54 44527 +1996 258 17.59 11.59 15.94 0.51 446 226.12 44323 +1996 259 17.93 11.93 16.28 0.01 454.72 223.68 44119 +1996 260 16.45 10.45 14.8 0.1 417.77 224.53 43915 +1996 261 14.95 8.95 13.3 0 382.97 300.16 43711 +1996 262 14.36 8.36 12.71 0 369.98 298.95 43507 +1996 263 14.95 8.95 13.3 0.46 382.97 221.46 43303 +1996 264 13.69 7.69 12.04 0.65 355.68 221.36 43099 +1996 265 12 6 10.35 0.09 321.7 221.81 42894 +1996 266 14.34 8.34 12.69 0.64 369.54 216.76 42690 +1996 267 13.12 7.12 11.47 0 343.89 288.57 42486 +1996 268 12.64 6.64 10.99 0.29 334.22 215.11 42282 +1996 269 12.65 6.65 11 0.75 334.42 213.18 42078 +1996 270 12.28 6.28 10.63 0.27 327.13 211.65 41875 +1996 271 11.42 5.42 9.77 0.04 310.69 210.68 41671 +1996 272 12.78 6.78 11.13 0 337.02 275.95 41468 +1996 273 11.13 5.13 9.48 1.35 305.31 207.01 41265 +1996 274 12.39 6.39 10.74 0.68 329.28 203.5 41062 +1996 275 14.54 8.54 12.89 0 373.9 264.86 40860 +1996 276 17.48 11.48 15.83 0 443.2 256.34 40658 +1996 277 20 14 18.35 0 511.04 247.93 40456 +1996 278 16.41 10.41 14.76 0.18 416.81 189.84 40255 +1996 279 16.68 10.68 15.03 0.56 423.34 187.36 40054 +1996 280 18.19 12.19 16.54 0.98 461.49 183.04 39854 +1996 281 17.83 11.83 16.18 0.51 452.14 181.63 39654 +1996 282 13.91 7.91 12.26 0.55 360.32 185.14 39455 +1996 283 12.34 6.34 10.69 0 328.3 246.51 39256 +1996 284 9.47 3.47 7.82 0.08 276.03 185.55 39058 +1996 285 9.76 3.76 8.11 0 280.97 244.36 38861 +1996 286 12.47 6.47 10.82 0 330.86 237.88 38664 +1996 287 14.97 8.97 13.32 0.03 383.42 173.24 38468 +1996 288 14.1 8.1 12.45 0.53 364.37 172.25 38273 +1996 289 15.24 9.24 13.59 0.65 389.5 168.89 38079 +1996 290 16.76 10.76 15.11 0 425.29 219.69 37885 +1996 291 14.16 8.16 12.51 0 365.66 221.45 37693 +1996 292 17.26 11.26 15.61 0 437.66 213.52 37501 +1996 293 14.91 8.91 13.26 0 382.08 214.92 37311 +1996 294 13.7 7.7 12.05 0 355.89 213.93 37121 +1996 295 17.18 11.18 15.53 0 435.66 205.45 36933 +1996 296 16 10 14.35 1.24 407.06 153.73 36745 +1996 297 19.41 13.41 17.76 0.49 494.41 147.06 36560 +1996 298 18.23 12.23 16.58 1.75 462.54 146.9 36375 +1996 299 16.94 10.94 15.29 0.3 429.71 146.62 36191 +1996 300 17.16 11.16 15.51 0.56 435.17 144.4 36009 +1996 301 14.1 8.1 12.45 0 364.37 194.88 35829 +1996 302 15.77 9.77 14.12 0 401.68 189.83 35650 +1996 303 16.67 10.67 15.02 0 423.1 185.89 35472 +1996 304 18.57 12.57 16.92 0 471.54 180.27 35296 +1996 305 12.64 6.64 10.99 0.25 334.22 139.94 35122 +1996 306 10.03 4.03 8.38 0 285.63 187.37 34950 +1996 307 11.09 5.09 9.44 0 304.58 183.71 34779 +1996 308 11.94 5.94 10.29 0.16 320.54 135.12 34610 +1996 309 12.59 6.59 10.94 0.17 333.23 132.82 34444 +1996 310 12.4 6.4 10.75 0.6 329.48 131.19 34279 +1996 311 13.13 7.13 11.48 0 344.1 171.9 34116 +1996 312 11.61 5.61 9.96 0 314.26 171.07 33956 +1996 313 10.53 4.53 8.88 0 294.44 170.13 33797 +1996 314 13.86 7.86 12.21 0 359.26 164.44 33641 +1996 315 15.42 9.42 13.77 0 393.6 159.94 33488 +1996 316 15.47 9.47 13.82 0 394.74 157.76 33337 +1996 317 15.2 9.2 13.55 0.2 388.59 117 33188 +1996 318 15.91 9.91 14.26 0 404.95 152.78 33042 +1996 319 12.62 6.62 10.97 0 333.83 155.19 32899 +1996 320 11.14 5.14 9.49 0.01 305.5 116.19 32758 +1996 321 12.07 6.07 10.42 0 323.05 151.89 32620 +1996 322 8 2 6.35 0 252.14 153.87 32486 +1996 323 10.1 4.1 8.45 0 286.85 150.45 32354 +1996 324 14.08 8.08 12.43 0.03 363.94 108.23 32225 +1996 325 9.46 3.46 7.81 0 275.86 147.29 32100 +1996 326 10.71 4.71 9.06 0.52 297.67 108.55 31977 +1996 327 12.7 6.7 11.05 0.16 335.42 105.71 31858 +1996 328 12.96 6.96 11.31 1.21 340.64 104.06 31743 +1996 329 5.7 -0.3 4.05 0 218.33 143.42 31631 +1996 330 8.04 2.04 6.39 0 252.77 140.31 31522 +1996 331 6.88 0.88 5.23 0 235.16 139.85 31417 +1996 332 8.66 2.66 7.01 0 262.64 136.89 31316 +1996 333 8.06 2.06 6.41 0 253.08 136.28 31218 +1996 334 10.52 4.52 8.87 0 294.26 133.2 31125 +1996 335 2.66 -3.34 1.01 0 179.67 137.43 31035 +1996 336 6.47 0.47 4.82 0 229.19 134.09 30949 +1996 337 7.21 1.21 5.56 0.03 240.06 98.94 30867 +1996 338 2.65 -3.35 1 1.06 179.56 100.3 30790 +1996 339 1.87 -4.13 0.22 0.03 170.65 100 30716 +1996 340 0.75 -5.25 -0.9 0 158.54 133.12 30647 +1996 341 4.76 -1.24 3.11 0 205.68 130.13 30582 +1996 342 3.92 -2.08 2.27 0 194.91 129.84 30521 +1996 343 6.04 0.04 4.39 0 223.07 127.77 30465 +1996 344 9.1 3.1 7.45 0 269.84 124.51 30413 +1996 345 10.75 4.75 9.1 0.11 298.39 92.08 30366 +1996 346 6.1 0.1 4.45 0.21 223.91 94.22 30323 +1996 347 1.37 -4.63 -0.28 0.17 165.15 95.69 30284 +1996 348 -0.86 -6.86 -2.51 0.19 142.42 140.37 30251 +1996 349 0.2 -5.8 -1.45 0.09 152.86 139.78 30221 +1996 350 4.82 -1.18 3.17 0.29 206.47 93.56 30197 +1996 351 4.16 -1.84 2.51 0 197.94 124.89 30177 +1996 352 2.19 -3.81 0.54 0.39 174.26 94.36 30162 +1996 353 -1.14 -7.14 -2.79 0 139.77 127.18 30151 +1996 354 -3.22 -9.22 -4.87 0 121.37 127.89 30145 +1996 355 -3.2 -9.2 -4.85 0 121.53 127.88 30144 +1996 356 -1.46 -7.46 -3.11 0 136.79 127.29 30147 +1996 357 -4.12 -10.12 -5.77 0.18 114.08 140.54 30156 +1996 358 4.02 -1.98 2.37 0 196.17 168.74 30169 +1996 359 2.59 -3.41 0.94 0.24 178.86 94.36 30186 +1996 360 1.36 -4.64 -0.29 0.58 165.04 95.07 30208 +1996 361 4.46 -1.54 2.81 0 201.78 125.52 30235 +1996 362 2.34 -3.66 0.69 0 175.97 127.07 30267 +1996 363 1.51 -4.49 -0.14 0 166.68 128.06 30303 +1996 364 0.93 -5.07 -0.72 0 160.43 128.72 30343 +1996 365 -1.31 -7.31 -2.96 0 138.18 130.22 30388 +1997 1 -2.65 -8.65 -4.3 0 126.19 131.62 30438 +1997 2 -0.74 -6.74 -2.39 0 143.57 131.64 30492 +1997 3 0.34 -5.66 -1.31 0 154.29 132.13 30551 +1997 4 3.3 -2.7 1.65 0 187.28 131.62 30614 +1997 5 6.27 0.27 4.62 0 226.32 130.51 30681 +1997 6 6.39 0.39 4.74 0 228.04 131.32 30752 +1997 7 4.35 -1.65 2.7 0.05 200.36 100.02 30828 +1997 8 3.44 -2.56 1.79 0 188.98 135.37 30907 +1997 9 3.94 -2.06 2.29 0 195.16 136.34 30991 +1997 10 0.76 -5.24 -0.89 0 158.64 139.29 31079 +1997 11 0.37 -5.63 -1.28 0.07 154.6 105.35 31171 +1997 12 0.84 -5.16 -0.81 0 159.48 141.27 31266 +1997 13 4.69 -1.31 3.04 0 204.76 140.81 31366 +1997 14 7.74 1.74 6.09 0 248.11 140.2 31469 +1997 15 5.04 -0.96 3.39 0 209.38 143.5 31575 +1997 16 1.46 -4.54 -0.19 0.36 166.13 110.12 31686 +1997 17 2.31 -3.69 0.66 0.22 175.63 111.06 31800 +1997 18 2.16 -3.84 0.51 0 173.92 150.06 31917 +1997 19 4.34 -1.66 2.69 0 200.23 150.73 32038 +1997 20 4.93 -1.07 3.28 0 207.92 151.93 32161 +1997 21 0.32 -5.68 -1.33 0 154.09 156.56 32289 +1997 22 0.32 -5.68 -1.33 0 154.09 158.32 32419 +1997 23 2.11 -3.89 0.46 0 173.35 159.17 32552 +1997 24 4.21 -1.79 2.56 0.16 198.57 119.99 32688 +1997 25 1.37 -4.63 -0.28 0 165.15 163.55 32827 +1997 26 6.1 0.1 4.45 0 223.91 162.47 32969 +1997 27 3.91 -2.09 2.26 0.01 194.79 124.51 33114 +1997 28 0.68 -5.32 -0.97 0 157.8 170.12 33261 +1997 29 0.34 -5.66 -1.31 0 154.29 172.7 33411 +1997 30 -0.15 -6.15 -1.8 0.08 149.35 170.97 33564 +1997 31 -1.05 -7.05 -2.7 0.75 140.62 175.05 33718 +1997 32 4.83 -1.17 3.18 0.05 206.6 173.26 33875 +1997 33 12 6 10.35 0 321.7 211.84 34035 +1997 34 12.59 6.59 10.94 0 333.23 174.15 34196 +1997 35 11.29 5.29 9.64 0 308.27 177.74 34360 +1997 36 11.4 5.4 9.75 0.03 310.32 135.05 34526 +1997 37 14.49 8.49 12.84 0 372.81 178.55 34694 +1997 38 12.58 6.58 10.93 0 333.03 183.71 34863 +1997 39 12.49 6.49 10.84 0 331.25 186.35 35035 +1997 40 12.26 6.26 10.61 0 326.74 189.18 35208 +1997 41 10.2 4.2 8.55 0 288.6 194.15 35383 +1997 42 11.96 5.96 10.31 0 320.93 194.59 35560 +1997 43 13.71 7.71 12.06 0 356.1 194.92 35738 +1997 44 13.75 7.75 12.1 0 356.94 197.35 35918 +1997 45 10.29 4.29 8.64 0 290.18 204.31 36099 +1997 46 7.05 1.05 5.4 0.11 237.67 157.76 36282 +1997 47 8.28 2.28 6.63 0.13 256.55 158.95 36466 +1997 48 6.79 0.79 5.14 0 233.83 216.19 36652 +1997 49 5.77 -0.23 4.12 0 219.3 219.9 36838 +1997 50 3.16 -2.84 1.51 0 185.59 224.73 37026 +1997 51 6.34 0.34 4.69 0.05 227.32 168.75 37215 +1997 52 5.04 -0.96 3.39 0 209.38 229.01 37405 +1997 53 4.48 -1.52 2.83 0.24 202.04 174.34 37596 +1997 54 1.16 -4.84 -0.49 0 162.88 237.79 37788 +1997 55 -1.67 -7.67 -3.32 0 134.87 242.61 37981 +1997 56 -1.2 -7.2 -2.85 0 139.21 245.08 38175 +1997 57 -1.67 -7.67 -3.32 0 134.87 248.29 38370 +1997 58 3.61 -2.39 1.96 0 191.06 247.52 38565 +1997 59 1.03 -4.97 -0.62 0 161.49 252.26 38761 +1997 60 8.05 2.05 6.4 0 252.93 248.74 38958 +1997 61 11.61 5.61 9.96 0 314.26 247.07 39156 +1997 62 7.03 1.03 5.38 0 237.37 255.59 39355 +1997 63 8.38 2.38 6.73 0.09 258.14 192.78 39553 +1997 64 5.62 -0.38 3.97 0.52 217.23 197.24 39753 +1997 65 4.3 -1.7 2.65 0.15 199.72 200.38 39953 +1997 66 9.43 3.43 7.78 0.32 275.36 198.15 40154 +1997 67 8.32 2.32 6.67 0.1 257.19 201.37 40355 +1997 68 9.66 3.66 8.01 0.09 279.26 202.22 40556 +1997 69 8.56 2.56 6.91 0.33 261.02 205.25 40758 +1997 70 11.25 5.25 9.6 0 307.53 272.77 40960 +1997 71 12.49 6.49 10.84 0 331.25 273.68 41163 +1997 72 11.63 5.63 9.98 0 314.64 277.84 41366 +1997 73 12.83 6.83 11.18 0.18 338.02 208.88 41569 +1997 74 13.34 7.34 11.69 0.29 348.4 210.23 41772 +1997 75 9.36 3.36 7.71 0.2 274.18 216.94 41976 +1997 76 9.75 3.75 8.1 0 280.79 291.33 42179 +1997 77 10.62 4.62 8.97 0 296.05 292.62 42383 +1997 78 9.87 3.87 8.22 0 282.86 296.39 42587 +1997 79 8.07 2.07 6.42 0 253.24 301.62 42791 +1997 80 11.21 5.21 9.56 0 306.79 299.55 42996 +1997 81 9.61 3.61 7.96 0 278.4 304.58 43200 +1997 82 11.96 5.96 10.31 0 320.93 303.48 43404 +1997 83 13.82 7.82 12.17 0 358.42 302.55 43608 +1997 84 12.03 6.03 10.38 0 322.28 308.33 43812 +1997 85 12.03 6.03 10.38 0 322.28 310.8 44016 +1997 86 6.31 0.31 4.66 0.08 226.89 241.24 44220 +1997 87 8.92 2.92 7.27 0.37 266.88 240.52 44424 +1997 88 7.44 1.44 5.79 0 243.52 325.13 44627 +1997 89 8.34 2.34 6.69 0 257.5 326.18 44831 +1997 90 6.51 0.51 4.86 0 229.76 331.03 45034 +1997 91 6.42 0.42 4.77 0 228.47 333.43 45237 +1997 92 7.47 1.47 5.82 1.02 243.98 250.73 45439 +1997 93 6.32 0.32 4.67 0.79 227.04 253.55 45642 +1997 94 4.82 -1.18 3.17 0.16 206.47 256.57 45843 +1997 95 5.16 -0.84 3.51 0.29 210.98 257.9 46045 +1997 96 9.22 3.22 7.57 0 271.84 340.44 46246 +1997 97 7.61 1.61 5.96 0 246.11 344.9 46446 +1997 98 6.83 0.83 5.18 0 234.42 347.98 46647 +1997 99 12.24 6.24 10.59 1.23 326.35 255.94 46846 +1997 100 11.78 5.78 10.13 0 317.49 344.06 47045 +1997 101 10.11 4.11 8.46 0 287.02 348.96 47243 +1997 102 10.36 4.36 8.71 0.02 291.42 262.84 47441 +1997 103 13.75 7.75 12.1 0 356.94 345.79 47638 +1997 104 9.59 3.59 7.94 0 278.06 355.44 47834 +1997 105 11.63 5.63 9.98 0 314.64 353.64 48030 +1997 106 12.47 6.47 10.82 0 330.86 353.66 48225 +1997 107 16.57 10.57 14.92 0 420.67 346.06 48419 +1997 108 14.17 8.17 12.52 0 365.87 353.49 48612 +1997 109 12.98 6.98 11.33 0 341.05 357.65 48804 +1997 110 10.32 4.32 8.67 0 290.71 364.16 48995 +1997 111 13.77 7.77 12.12 0 357.36 358.92 49185 +1997 112 11.24 5.24 9.59 0 307.35 365.58 49374 +1997 113 10.65 4.65 9 0 296.59 368.03 49561 +1997 114 14.86 8.86 13.21 0.13 380.96 270.58 49748 +1997 115 16.86 10.86 15.21 0 427.74 357.17 49933 +1997 116 17.59 11.59 15.94 0 446 356.38 50117 +1997 117 18.21 12.21 16.56 0 462.01 355.9 50300 +1997 118 17.9 11.9 16.25 0 453.94 358.08 50481 +1997 119 14.53 8.53 12.88 0 373.68 367.98 50661 +1997 120 15.26 9.26 13.61 0 389.95 367.39 50840 +1997 121 21.72 15.72 20.07 0.04 562.24 261.93 51016 +1997 122 16.74 10.74 15.09 2.16 424.8 274.42 51191 +1997 123 17.41 11.41 15.76 0 441.43 365.07 51365 +1997 124 19.41 13.41 17.76 0 494.41 360.18 51536 +1997 125 18.66 12.66 17.01 0.02 473.94 272.6 51706 +1997 126 20.48 14.48 18.83 0 524.91 358.62 51874 +1997 127 22.63 16.63 20.98 0 591.05 351.78 52039 +1997 128 20.26 14.26 18.61 0 518.51 361.19 52203 +1997 129 18.1 12.1 16.45 0 459.14 368.8 52365 +1997 130 17.71 11.71 16.06 0 449.06 370.72 52524 +1997 131 18.08 12.08 16.43 0.2 458.62 277.82 52681 +1997 132 17.44 11.44 15.79 0 442.19 373.1 52836 +1997 133 13.77 7.77 12.12 0 357.36 383.23 52989 +1997 134 15.85 9.85 14.2 0.02 403.54 284.13 53138 +1997 135 17.08 11.08 15.43 0.15 433.18 282.16 53286 +1997 136 16.8 10.8 15.15 0.48 426.27 283.22 53430 +1997 137 16.69 10.69 15.04 0 423.59 378.64 53572 +1997 138 21.52 15.52 19.87 0.77 556.07 272.92 53711 +1997 139 19.79 13.79 18.14 1.87 505.07 277.92 53848 +1997 140 24.7 18.7 23.05 0 661.28 352.37 53981 +1997 141 29.41 23.41 27.76 0.04 847.8 247.08 54111 +1997 142 29.18 23.18 27.53 0.05 837.76 248.38 54238 +1997 143 26.34 20.34 24.69 0 721.82 346.28 54362 +1997 144 22.04 16.04 20.39 0.01 572.24 273.75 54483 +1997 145 20.33 14.33 18.68 0 520.54 371.6 54600 +1997 146 25.21 19.21 23.56 0 679.63 352.76 54714 +1997 147 25.91 19.91 24.26 0 705.51 350 54824 +1997 148 19.57 13.57 17.92 0 498.88 375.37 54931 +1997 149 17.94 11.94 16.29 0 454.98 380.79 55034 +1997 150 18.48 12.48 16.83 0 469.14 379.48 55134 +1997 151 15.75 9.75 14.1 0 401.21 387.67 55229 +1997 152 13.86 7.86 12.21 0 359.26 392.49 55321 +1997 153 18.5 12.5 16.85 0.32 469.67 285.12 55409 +1997 154 20.76 14.76 19.11 1.05 533.15 279.75 55492 +1997 155 22.73 16.73 21.08 0.09 594.29 274.38 55572 +1997 156 24.46 18.46 22.81 0.18 652.79 269.25 55648 +1997 157 19.66 13.66 18.01 0.03 501.4 283.08 55719 +1997 158 19.51 13.51 17.86 1.32 497.2 283.58 55786 +1997 159 20.83 14.83 19.18 0.16 535.23 280.38 55849 +1997 160 17.98 11.98 16.33 0 456.02 383.35 55908 +1997 161 19.84 13.84 18.19 0 506.48 377.5 55962 +1997 162 19.33 13.33 17.68 0.26 492.19 284.43 56011 +1997 163 20.77 14.77 19.12 0 533.45 374.57 56056 +1997 164 23.42 17.42 21.77 0 617.07 364.5 56097 +1997 165 22.39 16.39 20.74 0.11 583.34 276.53 56133 +1997 166 23.4 17.4 21.75 0 616.4 364.76 56165 +1997 167 21.71 15.71 20.06 0.01 561.93 278.49 56192 +1997 168 19.91 13.91 18.26 0.13 508.47 283.34 56214 +1997 169 19.85 13.85 18.2 0.6 506.77 283.5 56231 +1997 170 16.59 10.59 14.94 0.55 421.16 290.99 56244 +1997 171 19.04 13.04 17.39 0.07 484.22 285.53 56252 +1997 172 20.53 14.53 18.88 0.75 526.38 281.79 56256 +1997 173 24 18 22.35 1.15 636.78 271.74 56255 +1997 174 25.02 19.02 23.37 0.36 672.74 268.34 56249 +1997 175 25.46 19.46 23.81 0 688.78 355.77 56238 +1997 176 29.08 23.08 27.43 0 833.43 337.38 56223 +1997 177 32.56 26.56 30.91 0 995.84 316 56203 +1997 178 27.81 21.81 26.16 0.06 780.01 258.12 56179 +1997 179 27.85 21.85 26.2 0 781.65 343.85 56150 +1997 180 24.47 18.47 22.82 1.2 653.15 269.9 56116 +1997 181 27.46 21.46 25.81 0.04 765.81 259.27 56078 +1997 182 23.21 17.21 21.56 0.57 610.06 273.71 56035 +1997 183 27.41 21.41 25.76 0 763.8 345.64 55987 +1997 184 27.12 21.12 25.47 0.19 752.22 260.22 55935 +1997 185 23.5 17.5 21.85 0.03 619.76 272.52 55879 +1997 186 22.05 16.05 20.4 0.25 572.55 276.63 55818 +1997 187 22.53 16.53 20.88 0.47 587.83 275.11 55753 +1997 188 22.4 16.4 20.75 0.78 583.66 275.29 55684 +1997 189 21.9 15.9 20.25 0.01 567.85 276.58 55611 +1997 190 23.67 17.67 22.02 0 625.5 361.42 55533 +1997 191 23.01 17.01 21.36 0 603.45 363.85 55451 +1997 192 19.49 13.49 17.84 0.22 496.64 282.22 55366 +1997 193 18.81 12.81 17.16 0 477.98 378.2 55276 +1997 194 18.36 12.36 16.71 0.77 465.96 284.53 55182 +1997 195 20.26 14.26 18.61 2.16 518.51 279.71 55085 +1997 196 21.46 15.46 19.81 1.12 554.23 276.23 54984 +1997 197 22.09 16.09 20.44 0.31 573.81 274.14 54879 +1997 198 27.68 21.68 26.03 0.3 774.71 255.29 54770 +1997 199 26.76 20.76 25.11 0 738.06 344.66 54658 +1997 200 27.11 21.11 25.46 0.16 751.83 256.92 54542 +1997 201 23.13 17.13 21.48 0.21 607.41 269.89 54423 +1997 202 25.19 19.19 23.54 0 678.9 350.61 54301 +1997 203 24.75 18.75 23.1 0.47 663.06 264.05 54176 +1997 204 23.91 17.91 22.26 2.41 633.69 266.36 54047 +1997 205 24.06 18.06 22.41 1.83 638.85 265.51 53915 +1997 206 22.56 16.56 20.91 0.21 588.79 269.61 53780 +1997 207 22.59 16.59 20.94 1.38 589.76 269.04 53643 +1997 208 22.8 16.8 21.15 0.01 596.57 267.95 53502 +1997 209 23.43 17.43 21.78 0.28 617.4 265.6 53359 +1997 210 19.43 13.43 17.78 0 494.97 367.91 53213 +1997 211 21.31 15.31 19.66 0.18 549.66 270.59 53064 +1997 212 23.1 17.1 21.45 0.62 606.42 264.98 52913 +1997 213 26.44 20.44 24.79 1.5 725.66 253.63 52760 +1997 214 23.39 17.39 21.74 0.83 616.06 263.01 52604 +1997 215 18.98 12.98 17.33 0.71 482.59 274.16 52445 +1997 216 18.66 12.66 17.01 0.08 473.94 274.13 52285 +1997 217 14.27 8.27 12.62 0.11 368.03 282.26 52122 +1997 218 14.15 8.15 12.5 0.03 365.44 281.83 51958 +1997 219 17.02 11.02 15.37 0.86 431.69 275.59 51791 +1997 220 17.95 11.95 16.3 0 455.24 363.88 51622 +1997 221 20.42 14.42 18.77 0 523.16 355.2 51451 +1997 222 22.74 16.74 21.09 0 594.62 345.94 51279 +1997 223 19.55 13.55 17.9 0.01 498.32 266.87 51105 +1997 224 26.99 20.99 25.34 0.03 747.08 244.33 50929 +1997 225 20.66 14.66 19.01 0.04 530.2 262.52 50751 +1997 226 18.97 12.97 17.32 0.01 482.32 265.69 50572 +1997 227 20.69 14.69 19.04 0 531.08 347.52 50392 +1997 228 23.74 17.74 22.09 0 627.88 335.28 50210 +1997 229 27.59 21.59 25.94 0 771.06 317.27 50026 +1997 230 23.95 17.95 22.3 0.02 635.06 249.02 49842 +1997 231 25.06 19.06 23.41 0 674.19 326.08 49656 +1997 232 26.99 20.99 25.34 0 747.08 316.28 49469 +1997 233 30.75 24.75 29.1 0.25 908.33 221.77 49280 +1997 234 28.3 22.3 26.65 0 800.27 307.37 49091 +1997 235 27.57 21.57 25.92 0 770.25 309.52 48900 +1997 236 28.41 22.41 26.76 0 804.87 304.14 48709 +1997 237 28.45 22.45 26.8 0 806.56 302.43 48516 +1997 238 28.74 22.74 27.09 0.86 818.83 224.59 48323 +1997 239 25.82 19.82 24.17 0.03 702.14 233.65 48128 +1997 240 25.19 19.19 23.54 0 678.9 312.49 47933 +1997 241 26.25 20.25 24.6 0 718.38 306.4 47737 +1997 242 24.2 18.2 22.55 0.26 643.7 234.84 47541 +1997 243 23.4 17.4 21.75 0 616.4 314.33 47343 +1997 244 19.58 13.58 17.93 0 499.16 325.13 47145 +1997 245 20.85 14.85 19.2 0.41 535.82 239.58 46947 +1997 246 20.69 14.69 19.04 0 531.08 318.01 46747 +1997 247 19.15 13.15 17.5 0.02 487.23 240.57 46547 +1997 248 21.98 15.98 20.33 0 570.35 310.16 46347 +1997 249 20.84 14.84 19.19 0.04 535.53 233.85 46146 +1997 250 18.93 12.93 17.28 0 481.23 315.46 45945 +1997 251 20.63 14.63 18.98 0 529.31 308.46 45743 +1997 252 16.02 10.02 14.37 1.29 407.53 238.9 45541 +1997 253 15.84 9.84 14.19 0 403.31 316.82 45339 +1997 254 14.74 8.74 13.09 0.87 378.3 237.8 45136 +1997 255 18.15 12.15 16.5 0.1 460.44 230.12 44933 +1997 256 17.62 11.62 15.97 0 446.76 305.91 44730 +1997 257 18.15 12.15 16.5 0 460.44 302.43 44527 +1997 258 19.89 13.89 18.24 0 507.9 295.47 44323 +1997 259 17.86 11.86 16.21 0.03 452.91 223.81 44119 +1997 260 19.72 13.72 18.07 0 503.09 291.22 43915 +1997 261 17.89 11.89 16.24 0.05 453.69 220.16 43711 +1997 262 18.94 12.94 17.29 0 481.5 288.56 43507 +1997 263 20.15 14.15 18.5 0 515.34 282.92 43303 +1997 264 20.11 14.11 18.46 0 514.19 280.52 43099 +1997 265 20.2 14.2 18.55 1.37 516.78 208.48 42894 +1997 266 20.02 14.02 18.37 0.01 511.61 207.04 42690 +1997 267 17.11 11.11 15.46 0.29 433.92 210.43 42486 +1997 268 17.92 11.92 16.27 0 454.46 276.18 42282 +1997 269 22.9 16.9 21.25 0 599.84 260.29 42078 +1997 270 20.95 14.95 19.3 0.01 538.81 197.59 41875 +1997 271 25.67 19.67 24.02 0 696.55 246.19 41671 +1997 272 25.3 19.3 23.65 0.66 682.91 183.72 41468 +1997 273 23.01 17.01 21.36 2.17 603.45 187.5 41265 +1997 274 12.92 6.92 11.27 0 339.83 270.46 41062 +1997 275 13.09 7.09 11.44 0.34 343.28 200.54 40860 +1997 276 9.51 3.51 7.86 0 276.71 270.02 40658 +1997 277 14.79 8.79 13.14 0 379.41 259.05 40456 +1997 278 13.4 7.4 11.75 0 349.64 258.61 40255 +1997 279 11.06 5.06 9.41 0.41 304.03 194.55 40054 +1997 280 13.56 7.56 11.91 0.2 352.96 189.66 39854 +1997 281 11.99 5.99 10.34 0 321.51 252.62 39654 +1997 282 14.55 8.55 12.9 0 374.12 245.76 39455 +1997 283 11.11 5.11 9.46 0.01 304.95 186.22 39256 +1997 284 13.73 7.73 12.08 0 356.52 241.32 39058 +1997 285 12.12 6.12 10.47 0.09 324.02 180.87 38861 +1997 286 12.4 6.4 10.75 0 329.48 237.98 38664 +1997 287 12.9 6.9 11.25 0.57 339.43 175.73 38468 +1997 288 10.53 4.53 8.88 1.04 294.44 176.11 38273 +1997 289 9.84 3.84 8.19 0.47 282.34 174.76 38079 +1997 290 13.03 7.03 11.38 0.01 342.06 169.39 37885 +1997 291 14.59 8.59 12.94 0.15 375 165.58 37693 +1997 292 13.95 7.95 12.3 0 361.17 219.12 37501 +1997 293 11.41 5.41 9.76 0 310.51 219.99 37311 +1997 294 14.23 8.23 12.58 0 367.17 213.13 37121 +1997 295 16.26 10.26 14.61 0 413.22 207.06 36933 +1997 296 14.58 8.58 12.93 0 374.78 207.25 36745 +1997 297 17.14 11.14 15.49 0 434.67 200.37 36560 +1997 298 15.6 9.6 13.95 0 397.74 200.42 36375 +1997 299 9.54 3.54 7.89 0.21 277.21 154.31 36191 +1997 300 9.26 3.26 7.61 0 272.5 203.38 36009 +1997 301 8.97 2.97 7.32 0.32 267.7 150.86 35829 +1997 302 8.17 2.17 6.52 0.59 254.81 149.5 35650 +1997 303 8.85 2.85 7.2 0.04 265.73 147.04 35472 +1997 304 10.58 4.58 8.93 0 295.33 191.75 35296 +1997 305 7.37 1.37 5.72 0 242.46 192.24 35122 +1997 306 12.31 6.31 10.66 0 327.71 184.77 34950 +1997 307 10.35 4.35 8.7 0.02 291.24 138.39 34779 +1997 308 6.49 0.49 4.84 0.07 229.48 139.18 34610 +1997 309 11.9 5.9 10.25 0.34 319.78 133.44 34444 +1997 310 7.14 1.14 5.49 0 239.01 180.24 34279 +1997 311 7.19 1.19 5.54 0 239.76 178 34116 +1997 312 2.36 -3.64 0.71 1.85 176.2 134.13 33956 +1997 313 3.03 -2.97 1.38 0.35 184.04 132.2 33797 +1997 314 3.66 -2.34 2.01 0.39 191.68 130.4 33641 +1997 315 8.15 2.15 6.5 0.03 254.5 125.94 33488 +1997 316 9.45 3.45 7.8 0.54 275.69 123.43 33337 +1997 317 10.26 4.26 8.61 0.66 289.65 121.21 33188 +1997 318 10.67 4.67 9.02 0.94 296.95 119.18 33042 +1997 319 12.83 6.83 11.18 0 338.02 154.95 32899 +1997 320 12.24 6.24 10.59 0.5 326.35 115.33 32758 +1997 321 11.3 5.3 9.65 0 308.46 152.68 32620 +1997 322 10.44 4.44 8.79 0 292.83 151.73 32486 +1997 323 10.57 4.57 8.92 0.23 295.15 112.51 32354 +1997 324 7.51 1.51 5.86 0 244.59 150.6 32225 +1997 325 7.88 1.88 6.23 0 250.27 148.6 32100 +1997 326 7.02 1.02 5.37 0 237.22 147.8 31977 +1997 327 11.78 5.78 10.13 0.57 317.49 106.42 31858 +1997 328 15.83 9.83 14.18 0.35 403.08 101.59 31743 +1997 329 13 7 11.35 0.02 341.45 102.94 31631 +1997 330 11.85 5.85 10.2 0.09 318.82 102.76 31522 +1997 331 12.13 6.13 10.48 0 324.21 135.45 31417 +1997 332 11.63 5.63 9.98 0 314.64 134.32 31316 +1997 333 9.59 3.59 7.94 0 278.06 135.07 31218 +1997 334 9.86 3.86 8.21 0.41 282.68 100.32 31125 +1997 335 4.34 -1.66 2.69 0.74 200.23 102.37 31035 +1997 336 5.53 -0.47 3.88 0.36 215.99 101.02 30949 +1997 337 6.61 0.61 4.96 0.53 231.21 99.25 30867 +1997 338 6.39 0.39 4.74 0 228.04 131.55 30790 +1997 339 10.1 4.1 8.45 0 286.85 128.02 30716 +1997 340 8.73 2.73 7.08 0 263.77 128.39 30647 +1997 341 4.51 -1.49 2.86 0 202.42 130.27 30582 +1997 342 4.79 -1.21 3.14 0 206.07 129.35 30521 +1997 343 4.79 -1.21 3.14 0.12 206.07 96.39 30465 +1997 344 2.67 -3.33 1.02 0.01 179.79 96.41 30413 +1997 345 8.86 2.86 7.21 0.84 265.89 93.21 30366 +1997 346 8.17 2.17 6.52 0.57 254.81 93.18 30323 +1997 347 5.92 -0.08 4.27 0.42 221.39 93.86 30284 +1997 348 8.28 2.28 6.63 0.37 256.55 92.42 30251 +1997 349 5.88 -0.12 4.23 0.02 220.83 93.34 30221 +1997 350 4.56 -1.44 2.91 0 203.07 124.89 30197 +1997 351 9.41 3.41 7.76 0 275.02 121.47 30177 +1997 352 9.16 3.16 7.51 0.04 270.84 91.18 30162 +1997 353 5.48 -0.52 3.83 0 215.31 123.98 30151 +1997 354 7.46 1.46 5.81 0.02 243.83 92.02 30145 +1997 355 8.88 2.88 7.23 0 266.22 121.68 30144 +1997 356 5.33 -0.67 3.68 0 213.27 124.06 30147 +1997 357 3.61 -2.39 1.96 0 191.06 125.08 30156 +1997 358 2.85 -3.15 1.2 0.15 181.9 94.17 30169 +1997 359 4.8 -1.2 3.15 0 206.2 124.63 30186 +1997 360 7.88 1.88 6.23 0.51 250.27 92.28 30208 +1997 361 11.17 5.17 9.52 0.09 306.05 90.61 30235 +1997 362 9.16 3.16 7.51 0.9 270.84 92.15 30267 +1997 363 7.52 1.52 5.87 0.02 244.74 93.48 30303 +1997 364 5.71 -0.29 4.06 0.07 218.47 94.65 30343 +1997 365 4.49 -1.51 2.84 1.42 202.16 95.62 30388 +1998 1 0.81 -5.19 -0.84 0.19 159.17 97.68 30438 +1998 2 1.19 -4.81 -0.46 0.4 163.21 98.1 30492 +1998 3 2.45 -3.55 0.8 0 177.24 131.15 30551 +1998 4 0.17 -5.83 -1.48 0.02 152.56 99.85 30614 +1998 5 4.09 -1.91 2.44 0 197.05 131.84 30681 +1998 6 7.18 1.18 5.53 0 239.61 130.78 30752 +1998 7 7.06 1.06 5.41 0.06 237.82 98.74 30828 +1998 8 5.57 -0.43 3.92 0 216.54 134.11 30907 +1998 9 3.88 -2.12 2.23 0 194.41 136.38 30991 +1998 10 2.22 -3.78 0.57 0.01 174.6 103.93 31079 +1998 11 0.8 -5.2 -0.85 0.08 159.06 105.2 31171 +1998 12 -0.17 -6.17 -1.82 0 149.15 141.73 31266 +1998 13 1.92 -4.08 0.27 0 171.21 142.37 31366 +1998 14 7.05 1.05 5.4 0.05 237.67 105.53 31469 +1998 15 6.25 0.25 4.6 0 226.04 142.7 31575 +1998 16 5.48 -0.52 3.83 0 215.31 144.5 31686 +1998 17 5.68 -0.32 4.03 0.35 218.05 109.53 31800 +1998 18 1.49 -4.51 -0.16 0.03 166.46 112.81 31917 +1998 19 3.13 -2.87 1.48 0.43 185.23 113.59 32038 +1998 20 4.33 -1.67 2.68 0 200.11 152.32 32161 +1998 21 6.98 0.98 5.33 0 236.63 152.49 32289 +1998 22 7.61 1.61 5.96 0 246.11 153.73 32419 +1998 23 11.44 5.44 9.79 0.42 311.07 114.02 32552 +1998 24 11.61 5.61 9.96 0 314.26 153.87 32688 +1998 25 10.6 4.6 8.95 0 295.69 156.72 32827 +1998 26 13.9 7.9 12.25 0 360.11 155 32969 +1998 27 16.98 10.98 15.33 0 430.7 152.84 33114 +1998 28 16.34 10.34 14.69 0 415.13 155.85 33261 +1998 29 10 4 8.35 0 285.11 165.67 33411 +1998 30 6.82 0.82 5.17 0 234.27 170.71 33564 +1998 31 2.12 -3.88 0.47 0 173.47 176.35 33718 +1998 32 7.73 1.73 6.08 0 247.95 174.39 33875 +1998 33 7.18 1.18 5.53 0 239.61 177.47 34035 +1998 34 9.57 3.57 7.92 0 277.72 177.45 34196 +1998 35 8.86 2.86 7.21 0 265.89 180.25 34360 +1998 36 8.82 2.82 7.17 0 265.24 182.77 34526 +1998 37 8.79 2.79 7.14 0 264.75 185.19 34694 +1998 38 8.4 2.4 6.75 0 258.46 188.27 34863 +1998 39 9.04 3.04 7.39 0 268.85 190.22 35035 +1998 40 10.84 4.84 9.19 0 300.02 190.87 35208 +1998 41 8.16 2.16 6.51 0 254.65 196.26 35383 +1998 42 6.99 0.99 5.34 0 236.78 199.89 35560 +1998 43 7.08 1.08 5.43 0.02 238.11 151.87 35738 +1998 44 7.44 1.44 5.79 0 243.52 204.71 35918 +1998 45 11.2 5.2 9.55 0 306.61 203.23 36099 +1998 46 11.1 5.1 9.45 0 304.76 205.98 36282 +1998 47 11.25 5.25 9.6 0 307.53 208.56 36466 +1998 48 8.16 2.16 6.51 0 254.65 214.83 36652 +1998 49 6.85 0.85 5.2 0 234.71 218.9 36838 +1998 50 8.94 2.94 7.29 0 267.2 219.39 37026 +1998 51 9.42 3.42 7.77 0 275.19 221.78 37215 +1998 52 11.73 5.73 10.08 0 316.53 221.69 37405 +1998 53 14.09 8.09 12.44 0 364.16 221.16 37596 +1998 54 14.9 8.9 13.25 0.11 381.86 166.89 37788 +1998 55 9.94 3.94 8.29 0.09 284.07 174.41 37981 +1998 56 6.6 0.6 4.95 0 231.07 238.94 38175 +1998 57 10.12 4.12 8.47 0 287.2 237.82 38370 +1998 58 9.39 3.39 7.74 0 274.68 241.62 38565 +1998 59 9.57 3.57 7.92 0.07 277.72 183.05 38761 +1998 60 11.21 5.21 9.56 0.01 306.79 183.57 38958 +1998 61 7.61 1.61 5.96 0.01 246.11 189.12 39156 +1998 62 10.32 4.32 8.67 0 290.71 251.61 39355 +1998 63 10.86 4.86 9.21 0 300.38 253.84 39553 +1998 64 3.9 -2.1 2.25 0 194.66 264.62 39753 +1998 65 2.41 -3.59 0.76 0 176.78 268.83 39953 +1998 66 6.73 0.73 5.08 0.12 232.96 200.59 40154 +1998 67 4.51 -1.49 2.86 0.83 202.42 204.49 40355 +1998 68 3.87 -2.13 2.22 0.07 194.29 207.11 40556 +1998 69 3.67 -2.33 2.02 0 191.8 278.99 40758 +1998 70 7.07 1.07 5.42 0 237.97 278.32 40960 +1998 71 6.42 0.42 4.77 0 228.47 281.98 41163 +1998 72 6.73 0.73 5.08 0.1 232.96 213.34 41366 +1998 73 7.84 1.84 6.19 0.27 249.65 214.35 41569 +1998 74 6.09 0.09 4.44 0.07 223.77 217.97 41772 +1998 75 8.91 2.91 7.26 0.32 266.71 217.41 41976 +1998 76 6.87 0.87 5.22 0.08 235.01 221.33 42179 +1998 77 11.63 5.63 9.98 0 314.64 291.03 42383 +1998 78 9.32 3.32 7.67 0 273.51 297.18 42587 +1998 79 10.78 4.78 9.13 0 298.93 297.72 42791 +1998 80 14.57 8.57 12.92 0 374.56 293.53 42996 +1998 81 14.88 8.88 13.23 0 381.41 295.43 43200 +1998 82 15.26 9.26 13.61 0 389.95 297.23 43404 +1998 83 13.07 7.07 11.42 0 342.87 303.97 43608 +1998 84 14.43 8.43 12.78 0 371.5 303.83 43812 +1998 85 15.08 9.08 13.43 0.21 385.89 228.7 44016 +1998 86 15.34 9.34 13.69 0 391.77 306.73 44220 +1998 87 11.67 5.67 10.02 0 315.4 316.32 44424 +1998 88 8.18 2.18 6.53 0 254.97 324.12 44627 +1998 89 7.71 1.71 6.06 0 247.65 327.06 44831 +1998 90 9.25 3.25 7.6 0 272.34 327.22 45034 +1998 91 15.89 9.89 14.24 0.06 404.48 237.74 45237 +1998 92 12.59 6.59 10.94 0.07 333.23 244.53 45439 +1998 93 10.24 4.24 8.59 0.37 289.3 249.28 45642 +1998 94 11.02 5.02 9.37 0 303.3 333.22 45843 +1998 95 13.97 7.97 12.32 0.01 361.6 247.31 46045 +1998 96 13.99 7.99 12.34 0 362.02 331.79 46246 +1998 97 13.19 7.19 11.54 0 345.32 335.45 46446 +1998 98 12.57 6.57 10.92 0.34 332.83 253.97 46647 +1998 99 10.76 4.76 9.11 0.1 298.57 257.96 46846 +1998 100 10.31 4.31 8.66 0.06 290.53 260.01 47045 +1998 101 14.29 8.29 12.64 0 368.46 340.93 47243 +1998 102 15.82 9.82 14.17 0.01 402.84 254.48 47441 +1998 103 16.93 10.93 15.28 0 429.47 338.36 47638 +1998 104 13.9 7.9 12.25 0 360.11 347.28 47834 +1998 105 17.47 11.47 15.82 0 442.95 340.47 48030 +1998 106 18.83 12.83 17.18 0 478.52 338.29 48225 +1998 107 12.42 6.42 10.77 0.13 329.87 266.58 48419 +1998 108 15.13 9.13 13.48 0 387.01 351.3 48612 +1998 109 16.84 10.84 15.19 0.26 427.25 261.49 48804 +1998 110 19.86 13.86 18.21 1.39 507.05 256.04 48995 +1998 111 22.27 16.27 20.62 1.03 579.51 251.11 49185 +1998 112 20.3 14.3 18.65 1.15 519.67 257.21 49374 +1998 113 14.84 8.84 13.19 0.11 380.52 269.5 49561 +1998 114 16.83 10.83 15.18 0.3 427.01 266.88 49748 +1998 115 17.96 11.96 16.31 0.31 455.5 265.61 49933 +1998 116 12.28 6.28 10.63 0 327.13 369.06 50117 +1998 117 12.8 6.8 11.15 0 337.42 369.31 50300 +1998 118 15.47 9.47 13.82 0.03 394.74 273.4 50481 +1998 119 15.82 9.82 14.17 0 402.84 364.84 50661 +1998 120 19.04 13.04 17.39 0 484.22 357.02 50840 +1998 121 18.95 12.95 17.3 0.06 481.77 268.79 51016 +1998 122 13.58 7.58 11.93 0.98 353.38 280.23 51191 +1998 123 16.78 10.78 15.13 1.17 425.78 275.1 51365 +1998 124 16.65 10.65 15 0.69 422.61 276.17 51536 +1998 125 18.63 12.63 16.98 0 473.14 363.55 51706 +1998 126 18.19 12.19 16.54 0.4 461.49 274.38 51874 +1998 127 18.32 12.32 16.67 0.81 464.91 274.75 52039 +1998 128 18.16 12.16 16.51 0 460.7 367.79 52203 +1998 129 22.22 16.22 20.57 0 577.92 355.09 52365 +1998 130 23.78 17.78 22.13 0.1 629.24 262.32 52524 +1998 131 24.06 18.06 22.41 0.06 638.85 262.02 52681 +1998 132 20.59 14.59 18.94 0 528.14 363.24 52836 +1998 133 21.66 15.66 20.01 0.12 560.39 270.11 52989 +1998 134 20.17 14.17 18.52 0.31 515.92 274.53 53138 +1998 135 16.81 10.81 15.16 0.14 426.52 282.73 53286 +1998 136 19.41 13.41 17.76 0.53 494.41 277.38 53430 +1998 137 19.83 13.83 18.18 0.36 506.2 276.87 53572 +1998 138 20.88 14.88 19.23 0 536.72 366.18 53711 +1998 139 16.74 10.74 15.09 0 424.8 379.79 53848 +1998 140 15.39 9.39 13.74 0.02 392.91 287.9 53981 +1998 141 10.67 4.67 9.02 0 296.95 394.82 54111 +1998 142 15.13 9.13 13.48 0 387.01 385.47 54238 +1998 143 16.87 10.87 15.22 0 427.99 381.39 54362 +1998 144 17.86 11.86 16.21 0.08 452.91 284.26 54483 +1998 145 20.78 14.78 19.13 0.05 533.75 277.53 54600 +1998 146 18.44 12.44 16.79 0 468.08 378.1 54714 +1998 147 19.04 13.04 17.39 0 484.22 376.7 54824 +1998 148 19.84 13.84 18.19 0 506.48 374.47 54931 +1998 149 25.14 19.14 23.49 0.28 677.09 265.64 55034 +1998 150 23.29 17.29 21.64 0 612.72 362.39 55134 +1998 151 20.01 14.01 18.36 0 511.32 374.93 55229 +1998 152 24.32 18.32 22.67 0 647.88 358.57 55321 +1998 153 24.49 18.49 22.84 0.51 653.85 268.55 55409 +1998 154 17.56 11.56 15.91 1.06 445.23 287.48 55492 +1998 155 23.26 17.26 21.61 0.01 611.72 272.79 55572 +1998 156 24.57 18.57 22.92 0.13 656.67 268.89 55648 +1998 157 23.13 17.13 21.48 1.55 607.41 273.54 55719 +1998 158 22.15 16.15 20.5 0.21 575.7 276.56 55786 +1998 159 23.35 17.35 21.7 0.95 614.73 273.18 55849 +1998 160 25.21 19.21 23.56 0 679.63 356.42 55908 +1998 161 26.36 20.36 24.71 0.03 722.59 263.33 55962 +1998 162 25.12 19.12 23.47 0 676.36 356.94 56011 +1998 163 27.46 21.46 25.81 0 765.81 345.91 56056 +1998 164 25.31 19.31 23.66 0.04 683.28 267.25 56097 +1998 165 24.08 18.08 22.43 0 639.54 361.84 56133 +1998 166 26.2 20.2 24.55 0.7 716.48 264.26 56165 +1998 167 22.08 16.08 20.43 0 573.49 369.92 56192 +1998 168 18.57 12.57 16.92 0.09 471.54 286.6 56214 +1998 169 21.95 15.95 20.3 0 569.41 370.5 56231 +1998 170 23.6 17.6 21.95 0.03 623.13 272.97 56244 +1998 171 23.3 17.3 21.65 0.09 613.06 273.94 56252 +1998 172 19.32 13.32 17.67 0 491.92 379.8 56256 +1998 173 19.82 13.82 18.17 0 505.92 378.13 56255 +1998 174 23.33 17.33 21.68 0.23 614.06 273.77 56249 +1998 175 23.76 17.76 22.11 0.78 628.56 272.42 56238 +1998 176 22.88 16.88 21.23 0.06 599.18 275.08 56223 +1998 177 26.28 20.28 24.63 0.32 719.53 263.84 56203 +1998 178 23.76 17.76 22.11 0 628.56 363.11 56179 +1998 179 21.9 15.9 20.25 0.67 567.85 277.8 56150 +1998 180 19.62 13.62 17.97 0.25 500.28 283.76 56116 +1998 181 17.2 11.2 15.55 0.1 436.16 289.31 56078 +1998 182 19.5 13.5 17.85 0.11 496.92 283.89 56035 +1998 183 19.96 13.96 18.31 0.49 509.9 282.61 55987 +1998 184 19.43 13.43 17.78 0.13 494.97 283.81 55935 +1998 185 17.35 11.35 15.7 0.12 439.92 288.56 55879 +1998 186 17.02 11.02 15.37 0.43 431.69 289.07 55818 +1998 187 16.39 10.39 14.74 0.36 416.33 290.25 55753 +1998 188 22.93 16.93 21.28 0 600.82 364.97 55684 +1998 189 25.6 19.6 23.95 0 693.95 353.35 55611 +1998 190 27.87 21.87 26.22 2.55 782.47 256.4 55533 +1998 191 27.4 21.4 25.75 1.8 763.4 258.02 55451 +1998 192 28.86 22.86 27.21 0.6 823.96 252.03 55366 +1998 193 21.12 15.12 19.47 0.52 543.91 277.83 55276 +1998 194 23.65 17.65 22 0 624.82 360.47 55182 +1998 195 29.97 23.97 28.32 0.23 872.67 246.82 55085 +1998 196 30.41 24.41 28.76 0 892.64 326.14 54984 +1998 197 28.43 22.43 26.78 0.48 805.71 252.64 54879 +1998 198 25.71 19.71 24.06 1.12 698.04 262.48 54770 +1998 199 26.53 20.53 24.88 0 729.13 345.77 54658 +1998 200 27.48 21.48 25.83 0 766.62 340.7 54542 +1998 201 30.71 24.71 29.06 0 906.47 322.44 54423 +1998 202 26.19 20.19 24.54 0.06 716.1 259.52 54301 +1998 203 23.69 17.69 22.04 1.1 626.18 267.41 54176 +1998 204 26.26 20.26 24.61 0 718.77 344.73 54047 +1998 205 27.56 21.56 25.91 0 769.85 337.89 53915 +1998 206 25.19 19.19 23.54 0.24 678.9 261.45 53780 +1998 207 25.41 19.41 23.76 0.44 686.94 260.24 53643 +1998 208 21.76 15.76 20.11 0 563.48 361.19 53502 +1998 209 21.33 15.33 19.68 0.37 550.27 271.58 53359 +1998 210 23.02 17.02 21.37 0.56 603.78 266.37 53213 +1998 211 22.39 16.39 20.74 0.16 583.34 267.62 53064 +1998 212 20.68 14.68 19.03 0.26 530.79 271.65 52913 +1998 213 20.47 14.47 18.82 0.17 524.62 271.62 52760 +1998 214 24.42 18.42 22.77 0.69 651.39 259.85 52604 +1998 215 19.01 13.01 17.36 0.45 483.41 274.09 52445 +1998 216 21.94 15.94 20.29 0 569.1 354.56 52285 +1998 217 25.05 19.05 23.4 0 673.83 341.28 52122 +1998 218 24.19 18.19 22.54 0.11 643.35 258.1 51958 +1998 219 19.59 13.59 17.94 1.73 499.44 269.88 51791 +1998 220 21.32 15.32 19.67 0.39 549.96 264.85 51622 +1998 221 24.6 18.6 22.95 0 657.73 339.55 51451 +1998 222 26.04 20.04 24.39 1.13 710.41 249.2 51279 +1998 223 28.2 22.2 26.55 0.38 796.1 240.62 51105 +1998 224 26.25 20.25 24.6 0.81 718.38 246.92 50929 +1998 225 22.99 16.99 21.34 0.05 602.79 256.29 50751 +1998 226 26.53 20.53 24.88 0.46 729.13 244.33 50572 +1998 227 22.29 16.29 20.64 0.08 580.15 256.47 50392 +1998 228 21.84 15.84 20.19 0.02 565.97 256.78 50210 +1998 229 24.63 18.63 22.98 0 658.8 330.5 50026 +1998 230 24.92 18.92 23.27 0 669.14 328.08 49842 +1998 231 27.5 21.5 25.85 0 767.42 315.14 49656 +1998 232 29.38 23.38 27.73 0 846.48 304.45 49469 +1998 233 26.63 20.63 24.98 0 733 316.6 49280 +1998 234 31.27 25.27 29.62 0 932.78 291.46 49091 +1998 235 31.08 25.08 29.43 0.05 923.78 218.42 48900 +1998 236 32.74 26.74 31.09 0 1004.92 280.11 48709 +1998 237 28.85 22.85 27.2 0.25 823.53 225.32 48516 +1998 238 28.86 22.86 27.21 0 823.96 298.85 48323 +1998 239 27.1 21.1 25.45 0.34 751.43 229.42 48128 +1998 240 23.61 17.61 21.96 0.79 623.47 239.02 47933 +1998 241 18.51 12.51 16.86 0.56 469.94 250.22 47737 +1998 242 15.99 9.99 14.34 0.12 406.83 253.82 47541 +1998 243 19.67 13.67 18.02 0 501.68 326.68 47343 +1998 244 12.11 6.11 10.46 0 323.82 342.97 47145 +1998 245 16.03 10.03 14.38 0 407.77 332.72 46947 +1998 246 18.41 12.41 16.76 0 467.28 324.66 46747 +1998 247 16.09 10.09 14.44 0.75 409.18 246.53 46547 +1998 248 19.34 13.34 17.69 0.15 492.47 238.72 46347 +1998 249 16.98 10.98 15.33 0.02 430.7 241.88 46146 +1998 250 19.36 13.36 17.71 0.26 493.03 235.69 45945 +1998 251 18.65 12.65 17 0.02 473.68 235.6 45743 +1998 252 24 18 22.35 1.27 636.78 221.37 45541 +1998 253 16.16 10.16 14.51 0.01 410.84 237.06 45339 +1998 254 18.97 12.97 17.32 0 482.32 306.9 45136 +1998 255 19.28 13.28 17.63 0 490.81 303.82 44933 +1998 256 20.83 14.83 19.18 0.02 535.23 222.87 44730 +1998 257 19.04 13.04 17.39 0.77 484.22 225.08 44527 +1998 258 18.32 12.32 16.67 0 464.91 299.67 44323 +1998 259 17.81 11.81 16.16 0 451.62 298.54 44119 +1998 260 20.3 14.3 18.65 0.31 519.67 217.21 43915 +1998 261 24.4 18.4 22.75 0.2 650.69 205.7 43711 +1998 262 25.31 19.31 23.66 0.2 683.28 201.56 43507 +1998 263 24.09 18.09 22.44 0 639.89 270.78 43303 +1998 264 22.47 16.47 20.82 0 585.9 273.63 43099 +1998 265 20.44 14.44 18.79 0 523.74 277.31 42894 +1998 266 20.53 14.53 18.88 0 526.38 274.66 42690 +1998 267 20.66 14.66 19.01 0 530.2 271.71 42486 +1998 268 23.53 17.53 21.88 0 620.77 260.68 42282 +1998 269 20.83 14.83 19.18 0 535.23 266.33 42078 +1998 270 19.34 13.34 17.69 0.25 492.47 200.76 41875 +1998 271 18.17 12.17 16.52 2.75 460.97 200.96 41671 +1998 272 14.46 8.46 12.81 4.12 372.15 204.73 41468 +1998 273 17.49 11.49 15.84 1.23 443.46 198.24 41265 +1998 274 12.47 6.47 10.82 2.52 330.86 203.4 41062 +1998 275 13.8 7.8 12.15 0 357.99 266.18 40860 +1998 276 15.73 9.73 14.08 0 400.75 259.93 40658 +1998 277 12.77 6.77 11.12 0.14 336.82 196.9 40456 +1998 278 13.9 7.9 12.25 0 360.11 257.77 40255 +1998 279 10.95 4.95 9.3 0.51 302.02 194.67 40054 +1998 280 12.92 6.92 11.27 0.23 339.83 190.44 39854 +1998 281 15.23 9.23 13.58 0.03 389.27 185.46 39654 +1998 282 10.7 4.7 9.05 0.58 297.48 188.78 39455 +1998 283 14.79 8.79 13.14 0.18 379.41 181.91 39256 +1998 284 15.11 9.11 13.46 1.35 386.56 179.25 39058 +1998 285 16.71 10.71 15.06 1.04 424.07 175.09 38861 +1998 286 17.91 11.91 16.26 0.06 454.2 171.29 38664 +1998 287 18.81 12.81 17.16 0 477.98 223.67 38468 +1998 288 15.95 9.95 14.3 1.03 405.89 169.91 38273 +1998 289 13.99 7.99 12.34 0 362.02 227.23 38079 +1998 290 16.46 10.46 14.81 0 418.01 220.24 37885 +1998 291 17.14 11.14 15.49 0 434.67 216.35 37693 +1998 292 15.95 9.95 14.3 0 405.89 215.87 37501 +1998 293 14.45 8.45 12.8 0.75 371.94 161.73 37311 +1998 294 16.66 10.66 15.01 1.42 422.85 156.85 37121 +1998 295 16.84 10.84 15.19 0.4 427.25 154.54 36933 +1998 296 16.96 10.96 15.31 0.21 430.2 152.5 36745 +1998 297 16.56 10.56 14.91 0.02 420.43 151.03 36560 +1998 298 14.37 8.37 12.72 0 370.19 202.32 36375 +1998 299 14.43 8.43 12.78 0.04 371.5 149.62 36191 +1998 300 19 13 17.35 0.17 483.13 141.89 36009 +1998 301 18.12 12.12 16.47 0 459.66 188.41 35829 +1998 302 18.01 12.01 16.36 0.27 456.79 139.57 35650 +1998 303 16.84 10.84 15.19 0.22 427.25 139.21 35472 +1998 304 17.99 11.99 16.34 0 456.27 181.3 35296 +1998 305 7.45 1.45 5.8 0 243.67 192.17 35122 +1998 306 7.72 1.72 6.07 0.02 247.8 142.24 34950 +1998 307 10.42 4.42 8.77 0 292.48 184.45 34779 +1998 308 13.21 7.21 11.56 0 345.73 178.61 34610 +1998 309 7.24 1.24 5.59 0 240.5 182.6 34444 +1998 310 6.28 0.28 4.63 0 226.47 180.95 34279 +1998 311 6.93 0.93 5.28 0.94 235.89 133.67 34116 +1998 312 7.84 1.84 6.19 0 249.65 174.79 33956 +1998 313 9.48 3.48 7.83 0.04 276.2 128.38 33797 +1998 314 10.62 4.62 8.97 0 296.05 168.1 33641 +1998 315 11.33 5.33 9.68 0 309.02 164.86 33488 +1998 316 7.37 1.37 5.72 0.08 242.46 124.79 33337 +1998 317 5.79 -0.21 4.14 1.24 219.58 124.06 33188 +1998 318 6.26 0.26 4.61 0.15 226.18 122.04 33042 +1998 319 4.68 -1.32 3.03 0.03 204.63 121.6 32899 +1998 320 7.31 1.31 5.66 0.01 241.56 118.76 32758 +1998 321 5.1 -0.9 3.45 0 210.18 157.85 32620 +1998 322 7.83 1.83 6.18 0 249.5 154.01 32486 +1998 323 5.64 -0.36 3.99 0 217.5 154.02 32354 +1998 324 6.22 0.22 4.57 0 225.61 151.56 32225 +1998 325 5.87 -0.13 4.22 0.03 220.69 112.56 32100 +1998 326 5.98 -0.02 4.33 0.9 222.23 111.41 31977 +1998 327 5.45 -0.55 3.8 0 214.9 147.06 31858 +1998 328 3.95 -2.05 2.3 0.03 195.29 109.52 31743 +1998 329 9.06 3.06 7.41 0.07 269.18 105.7 31631 +1998 330 8.01 2.01 6.36 0.17 252.3 105.25 31522 +1998 331 7.52 1.52 5.87 0.4 244.74 104.54 31417 +1998 332 6.77 0.77 5.12 1.9 233.54 103.72 31316 +1998 333 8.53 2.53 6.88 0 260.54 135.92 31218 +1998 334 10.25 4.25 8.6 0.1 289.48 100.08 31125 +1998 335 1.93 -4.07 0.28 0 171.33 137.8 31035 +1998 336 2.75 -3.25 1.1 0 180.73 136.3 30949 +1998 337 0.2 -5.8 -1.45 0.1 152.86 101.89 30867 +1998 338 3.25 -2.75 1.6 0 186.68 133.42 30790 +1998 339 1.29 -4.71 -0.36 0 164.28 133.61 30716 +1998 340 -2.86 -8.86 -4.51 0 124.39 134.56 30647 +1998 341 -1.73 -7.73 -3.38 0 134.32 133.21 30582 +1998 342 -1.97 -7.97 -3.62 0 132.16 132.53 30521 +1998 343 1.41 -4.59 -0.24 0 165.58 130.29 30465 +1998 344 2.77 -3.23 1.12 0 180.96 128.49 30413 +1998 345 4.64 -1.36 2.99 0 204.11 127.05 30366 +1998 346 4.97 -1.03 3.32 0 208.45 126.31 30323 +1998 347 8.06 2.06 6.41 0 253.08 123.73 30284 +1998 348 7.28 1.28 5.63 0.01 241.11 92.94 30251 +1998 349 8.11 2.11 6.46 1.11 253.87 92.23 30221 +1998 350 6.98 0.98 5.33 0.15 236.63 92.56 30197 +1998 351 6.26 0.26 4.61 0 226.18 123.66 30177 +1998 352 2.58 -3.42 0.93 0.45 178.74 94.22 30162 +1998 353 1.29 -4.71 -0.36 0 164.28 126.17 30151 +1998 354 0.64 -5.36 -1.01 0 157.39 126.42 30145 +1998 355 -0.07 -6.07 -1.72 0 150.14 126.72 30144 +1998 356 2.87 -3.13 1.22 0.02 182.14 94.05 30147 +1998 357 -1.41 -7.41 -3.06 0.11 137.25 139.62 30156 +1998 358 -1.15 -7.15 -2.8 0.16 139.68 140.11 30169 +1998 359 -4.02 -10.02 -5.67 0 114.87 173.03 30186 +1998 360 -7.97 -13.97 -9.62 0 87.02 174.45 30208 +1998 361 -7.13 -13.13 -8.78 0 92.39 174.55 30235 +1998 362 -2.53 -8.53 -4.18 0 127.22 173.57 30267 +1998 363 5.1 -0.9 3.45 0 210.18 169.91 30303 +1998 364 3.79 -2.21 2.14 0 193.29 127.31 30343 +1998 365 4.93 -1.07 3.28 0 207.92 127.24 30388 +1999 1 5.59 -0.41 3.94 0 216.82 127.73 30438 +1999 2 2.4 -3.6 0.75 0.36 176.66 97.67 30492 +1999 3 4.78 -1.22 3.13 0 205.94 129.88 30551 +1999 4 6.23 0.23 4.58 0 225.75 129.9 30614 +1999 5 10.13 4.13 8.48 0 287.37 127.67 30681 +1999 6 10.21 4.21 8.56 0 288.77 128.47 30752 +1999 7 7.23 1.23 5.58 0.14 240.35 98.65 30828 +1999 8 5.22 -0.78 3.57 0.12 211.79 100.75 30907 +1999 9 5.14 -0.86 3.49 0.25 210.72 101.72 30991 +1999 10 5.36 -0.64 3.71 0 213.68 136.79 31079 +1999 11 3.32 -2.68 1.67 0.01 187.52 104.24 31171 +1999 12 0.43 -5.57 -1.22 0.17 155.21 106.09 31266 +1999 13 -0.07 -6.07 -1.72 0 150.14 143.32 31366 +1999 14 -2.61 -8.61 -4.26 0 126.53 145.86 31469 +1999 15 -0.49 -6.49 -2.14 0 145.99 146.45 31575 +1999 16 -0.28 -6.28 -1.93 0 148.06 147.66 31686 +1999 17 0.29 -5.71 -1.36 0 153.78 149.09 31800 +1999 18 3.05 -2.95 1.4 0 184.28 149.57 31917 +1999 19 5.33 -0.67 3.68 0 213.27 150.09 32038 +1999 20 4.34 -1.66 2.69 0 200.23 152.31 32161 +1999 21 2.58 -3.42 0.93 0.13 178.74 116.53 32289 +1999 22 6.09 0.09 4.44 0 223.77 154.88 32419 +1999 23 4.6 -1.4 2.95 0.31 203.59 118.25 32552 +1999 24 3.78 -2.22 2.13 0.09 193.17 120.19 32688 +1999 25 5.54 -0.46 3.89 0.01 216.13 120.72 32827 +1999 26 4.85 -1.15 3.2 0.22 206.86 122.52 32969 +1999 27 2.39 -3.61 0.74 0.23 176.55 125.21 33114 +1999 28 -2.55 -8.55 -4.2 0.1 127.05 168.72 33261 +1999 29 -3.28 -9.28 -4.93 0 120.87 214.16 33411 +1999 30 -4.19 -10.19 -5.84 0.14 113.53 172.77 33564 +1999 31 -5.94 -11.94 -7.59 0.06 100.49 175.04 33718 +1999 32 -4.6 -10.6 -6.25 0.12 110.35 176.45 33875 +1999 33 -4.64 -10.64 -6.29 0.05 110.04 178.42 34035 +1999 34 -4.55 -10.55 -6.2 0 110.73 226.55 34196 +1999 35 -6.97 -12.97 -8.62 0.66 93.45 183.84 34360 +1999 36 -4.28 -10.28 -5.93 0 112.82 232.64 34526 +1999 37 1.56 -4.44 -0.09 0 167.22 231.8 34694 +1999 38 5.16 -0.84 3.51 0 210.98 231.27 34863 +1999 39 5.07 -0.93 3.42 0 209.78 233.17 35035 +1999 40 6.35 0.35 4.7 0 227.47 233.81 35208 +1999 41 6.79 0.79 5.14 0.1 233.83 185.68 35383 +1999 42 4.26 -1.74 2.61 0.1 199.21 151.62 35560 +1999 43 4.67 -1.33 3.02 0.04 204.5 153.41 35738 +1999 44 0.59 -5.41 -1.06 1.05 156.87 157.48 35918 +1999 45 -0.71 -6.71 -2.36 0 143.86 213.38 36099 +1999 46 4.62 -1.38 2.97 0 203.85 212.47 36282 +1999 47 2.46 -3.54 0.81 0 177.35 216.94 36466 +1999 48 0.61 -5.39 -1.04 0 157.08 221.01 36652 +1999 49 3.1 -2.9 1.45 0 184.88 222.09 36838 +1999 50 3.43 -2.57 1.78 0 188.86 224.52 37026 +1999 51 5.9 -0.1 4.25 0 221.11 225.41 37215 +1999 52 5.74 -0.26 4.09 0.98 218.88 171.28 37405 +1999 53 6.8 0.8 5.15 0 233.98 230.32 37596 +1999 54 5.75 -0.25 4.1 0 219.02 234.08 37788 +1999 55 10.37 4.37 8.72 0 291.59 232.01 37981 +1999 56 8.05 2.05 6.4 0.22 252.93 178.06 38175 +1999 57 13.9 7.9 12.25 0.39 360.11 174.32 38370 +1999 58 7.13 1.13 5.48 0 238.86 244.19 38565 +1999 59 11.01 5.01 9.36 0 303.11 242.2 38761 +1999 60 14.14 8.14 12.49 0 365.23 240.3 38958 +1999 61 11.15 5.15 9.5 0 305.68 247.73 39156 +1999 62 11.32 5.32 9.67 0 308.83 250.23 39355 +1999 63 13.53 7.53 11.88 0.07 352.34 187.35 39553 +1999 64 15.54 9.54 13.89 0 396.35 249.1 39753 +1999 65 13.02 7.02 11.37 0 341.86 256.28 39953 +1999 66 10.82 4.82 9.17 0 299.65 262.31 40154 +1999 67 13.96 7.96 12.31 0 361.38 260.2 40355 +1999 68 12.04 6.04 10.39 0.53 322.47 199.63 40556 +1999 69 13.41 7.41 11.76 0.83 349.85 199.88 40758 +1999 70 10.96 4.96 9.31 0 302.2 273.2 40960 +1999 71 10.95 4.95 9.3 0 302.02 276.09 41163 +1999 72 8.82 2.82 7.17 0 265.24 281.88 41366 +1999 73 8.05 2.05 6.4 0 252.93 285.54 41569 +1999 74 11.13 5.13 9.48 0 305.31 283.96 41772 +1999 75 7.3 1.3 5.65 0 241.41 291.94 41976 +1999 76 9.79 3.79 8.14 0 281.48 291.27 42179 +1999 77 12.78 6.78 11.13 0 337.02 289.1 42383 +1999 78 17.73 11.73 16.08 0 449.57 281.62 42587 +1999 79 18.16 12.16 16.51 0 460.7 283.21 42791 +1999 80 16.43 10.43 14.78 0 417.29 289.64 42996 +1999 81 12.32 6.32 10.67 0.09 327.91 225.18 43200 +1999 82 5.67 -0.33 4.02 0 217.92 312.39 43404 +1999 83 7.55 1.55 5.9 0 245.19 312.59 43608 +1999 84 4.64 -1.36 2.99 0 204.11 318.63 43812 +1999 85 7.47 1.47 5.82 0 243.98 317.75 44016 +1999 86 12.53 6.53 10.88 0.01 332.04 234.21 44220 +1999 87 7.34 1.34 5.69 1.1 242.01 242.17 44424 +1999 88 2.63 -3.37 0.98 0.03 179.33 248 44627 +1999 89 3.57 -2.43 1.92 0 190.57 332.04 44831 +1999 90 7.33 1.33 5.68 0 241.86 329.96 45034 +1999 91 13.61 7.61 11.96 0 354.01 321.85 45237 +1999 92 13.39 7.39 11.74 0 349.43 324.5 45439 +1999 93 14.77 8.77 13.12 0.18 378.97 242.87 45642 +1999 94 14.37 8.37 12.72 0 370.19 326.8 45843 +1999 95 10.37 4.37 8.72 0 291.59 336.46 46045 +1999 96 8.95 2.95 7.3 0 267.37 340.86 46246 +1999 97 15.61 9.61 13.96 0 397.97 330.24 46446 +1999 98 12.79 6.79 11.14 0 337.22 338.19 46647 +1999 99 14.68 8.68 13.03 0 376.98 336.25 46846 +1999 100 14.76 8.76 13.11 0 378.75 337.99 47045 +1999 101 13.98 7.98 12.33 1.14 361.81 256.2 47243 +1999 102 12.8 6.8 11.15 0.15 337.42 259.44 47441 +1999 103 11.16 5.16 9.51 0 305.87 350.88 47638 +1999 104 13.2 7.2 11.55 0 345.53 348.76 47834 +1999 105 15.96 9.96 14.31 0 406.12 344.33 48030 +1999 106 14.23 8.23 12.58 0.31 367.17 262.48 48225 +1999 107 14.62 8.62 12.97 0.97 375.66 263.07 48419 +1999 108 16.61 10.61 14.96 0.67 421.64 260.75 48612 +1999 109 17.84 11.84 16.19 0.17 452.4 259.47 48804 +1999 110 16.24 10.24 14.59 0.04 412.74 263.68 48995 +1999 111 14.16 8.16 12.51 0 365.66 358.05 49185 +1999 112 15.46 9.46 13.81 0.29 394.52 267.4 49374 +1999 113 13.09 7.09 11.44 0 343.28 363.23 49561 +1999 114 13.18 7.18 11.53 0 345.12 364.53 49748 +1999 115 17.34 11.34 15.69 0.03 439.67 266.91 49933 +1999 116 18.93 12.93 17.28 0.2 481.23 264.37 50117 +1999 117 19.18 13.18 17.53 0 488.06 353.01 50300 +1999 118 22.02 16.02 20.37 0.26 571.61 258.63 50481 +1999 119 18.2 12.2 16.55 0 461.75 358.38 50661 +1999 120 20.92 14.92 19.27 0 537.91 350.95 50840 +1999 121 21.75 15.75 20.1 0.13 563.17 261.85 51016 +1999 122 20.38 14.38 18.73 0.68 522 266.25 51191 +1999 123 18.21 12.21 16.56 0.02 462.01 272.08 51365 +1999 124 17.4 11.4 15.75 0.11 441.18 274.62 51536 +1999 125 18.44 12.44 16.79 0.52 468.08 273.09 51706 +1999 126 20.96 14.96 19.31 0.23 539.11 267.74 51874 +1999 127 21.75 15.75 20.1 0.01 563.17 266.28 52039 +1999 128 21.83 15.83 20.18 0.41 565.66 266.79 52203 +1999 129 20.62 14.62 18.97 0.97 529.02 270.6 52365 +1999 130 22.62 16.62 20.97 0 590.73 354.34 52524 +1999 131 23.63 17.63 21.98 0 624.15 351.12 52681 +1999 132 22.22 16.22 20.57 0 577.92 357.4 52836 +1999 133 21.87 15.87 20.22 0.68 566.91 269.53 52989 +1999 134 19.89 13.89 18.24 0.1 507.9 275.23 53138 +1999 135 20.8 14.8 19.15 0.33 534.34 273.43 53286 +1999 136 17.77 11.77 16.12 2.43 450.6 281.15 53430 +1999 137 15.18 9.18 13.53 0.49 388.14 286.96 53572 +1999 138 14.84 8.84 13.19 0 380.52 384.07 53711 +1999 139 17.53 11.53 15.88 0.15 444.47 283.17 53848 +1999 140 14.91 8.91 13.26 0.14 382.08 288.81 53981 +1999 141 16.84 10.84 15.19 0.56 427.25 285.32 54111 +1999 142 16.48 10.48 14.83 0 418.5 381.93 54238 +1999 143 19.24 13.24 17.59 0 489.71 374.28 54362 +1999 144 16.5 10.5 14.85 0.09 418.98 287.17 54483 +1999 145 17.29 11.29 15.64 0.02 438.42 285.86 54600 +1999 146 16.89 10.89 15.24 0.4 428.48 286.99 54714 +1999 147 15.18 9.18 13.53 0.02 388.14 290.78 54824 +1999 148 15.19 9.19 13.54 0.02 388.37 291.05 54931 +1999 149 14.25 8.25 12.6 0.05 367.6 293.03 55034 +1999 150 18.57 12.57 16.92 0.73 471.54 284.4 55134 +1999 151 20.02 14.02 18.37 1.49 511.61 281.17 55229 +1999 152 23.33 17.33 21.68 1.1 614.06 272.03 55321 +1999 153 20.33 14.33 18.68 3.23 520.54 280.64 55409 +1999 154 21.72 15.72 20.07 0.08 562.24 277.14 55492 +1999 155 19.22 13.22 17.57 0.03 489.16 283.79 55572 +1999 156 23.94 17.94 22.29 0 634.72 361.22 55648 +1999 157 23.25 17.25 21.6 0.55 611.39 273.18 55719 +1999 158 22.59 16.59 20.94 0 589.76 367.04 55786 +1999 159 25.08 19.08 23.43 0 674.91 356.83 55849 +1999 160 27.69 21.69 26.04 0 775.12 344.41 55908 +1999 161 24.07 18.07 22.42 0 639.2 361.48 55962 +1999 162 23.32 17.32 21.67 1.04 613.72 273.49 56011 +1999 163 21.74 15.74 20.09 0.01 562.86 278.28 56056 +1999 164 19.69 13.69 18.04 0 502.24 378.32 56097 +1999 165 17.59 11.59 15.94 0.65 446 288.75 56133 +1999 166 19.93 13.93 18.28 0 509.04 377.69 56165 +1999 167 18.46 12.46 16.81 0 468.61 382.39 56192 +1999 168 19.74 13.74 18.09 0.01 503.65 283.76 56214 +1999 169 18.53 12.53 16.88 0.04 470.47 286.7 56231 +1999 170 17.53 11.53 15.88 0 444.47 385.29 56244 +1999 171 17.37 11.37 15.72 0.02 440.43 289.36 56252 +1999 172 19 13 17.35 0 483.13 380.83 56256 +1999 173 16.45 10.45 14.8 0 417.77 388.4 56255 +1999 174 17.31 11.31 15.66 0 438.92 385.88 56249 +1999 175 24.22 18.22 22.57 0 644.4 361.27 56238 +1999 176 27.79 21.79 26.14 0.17 779.19 258.25 56223 +1999 177 22.9 16.9 21.25 0 599.84 366.6 56203 +1999 178 22.92 16.92 21.27 0.07 600.49 274.91 56179 +1999 179 24.13 18.13 22.48 0.19 641.27 271.09 56150 +1999 180 23.14 17.14 21.49 0.85 607.74 274.08 56116 +1999 181 25.37 19.37 23.72 0 685.47 355.79 56078 +1999 182 28.95 22.95 27.3 0 827.82 337.63 56035 +1999 183 30.6 24.6 28.95 0.05 901.38 245.95 55987 +1999 184 28.99 22.99 27.34 0.28 829.54 252.83 55935 +1999 185 25.13 19.13 23.48 0 676.72 356.34 55879 +1999 186 27.79 21.79 26.14 0 779.19 343.22 55818 +1999 187 28.33 22.33 26.68 1.29 801.52 255.16 55753 +1999 188 26.95 20.95 25.3 0.24 745.51 260.3 55684 +1999 189 25.13 19.13 23.48 0 676.72 355.48 55611 +1999 190 22.25 16.25 20.6 0.05 578.87 275.31 55533 +1999 191 22.07 16.07 20.42 0 573.18 367.5 55451 +1999 192 24.1 18.1 22.45 0.09 640.23 269.3 55366 +1999 193 23.3 17.3 21.65 0.42 613.06 271.59 55276 +1999 194 23.37 17.37 21.72 1.15 615.39 271.21 55182 +1999 195 23.75 17.75 22.1 0 628.22 359.79 55085 +1999 196 22.23 16.23 20.58 1.71 578.24 274.08 54984 +1999 197 20.63 14.63 18.98 0 529.31 370.81 54879 +1999 198 18.04 12.04 16.39 0 457.57 378.76 54770 +1999 199 26.32 20.32 24.67 0 721.06 346.78 54658 +1999 200 23.82 17.82 22.17 0.17 630.61 268.13 54542 +1999 201 27.27 21.27 25.62 0 758.19 341.32 54423 +1999 202 27.43 21.43 25.78 1.76 764.6 254.98 54301 +1999 203 26.92 20.92 25.27 0.27 744.33 256.53 54176 +1999 204 25.66 19.66 24.01 0 696.18 347.52 54047 +1999 205 22.97 16.97 21.32 0 602.13 358.44 53915 +1999 206 19.87 13.87 18.22 0.24 507.33 276.81 53780 +1999 207 22.33 16.33 20.68 0.06 581.42 269.79 53643 +1999 208 20.86 14.86 19.21 3.54 536.12 273.31 53502 +1999 209 20.88 14.88 19.23 0 536.72 363.69 53359 +1999 210 19.08 13.08 17.43 0.41 485.32 276.77 53213 +1999 211 16.88 10.88 15.23 1.13 428.23 281.04 53064 +1999 212 22.61 16.61 20.96 0 590.41 355.2 52913 +1999 213 22.07 16.07 20.42 0.43 573.18 267.37 52760 +1999 214 22.46 16.46 20.81 0 585.58 354.29 52604 +1999 215 25.34 19.34 23.69 0.12 684.38 256.39 52445 +1999 216 25.71 19.71 24.06 0.32 698.04 254.42 52285 +1999 217 23.66 17.66 22.01 0 625.16 347.09 52122 +1999 218 24.26 18.26 22.61 0 645.79 343.85 51958 +1999 219 22.11 16.11 20.46 1.75 574.44 263.42 51791 +1999 220 21.58 15.58 19.93 0.01 557.92 264.16 51622 +1999 221 22.22 16.22 20.57 0.06 577.92 261.68 51451 +1999 222 20.01 14.01 18.36 0.08 511.32 266.63 51279 +1999 223 22.27 16.27 20.62 0 579.51 346.57 51105 +1999 224 19.55 13.55 17.9 0 498.32 354.77 50929 +1999 225 19.21 13.21 17.56 0 488.88 354.68 50751 +1999 226 19.78 13.78 18.13 0 504.78 351.75 50572 +1999 227 21.35 15.35 19.7 0.16 550.88 258.97 50392 +1999 228 22.86 16.86 21.21 0 598.53 338.66 50210 +1999 229 22.75 16.75 21.1 0.08 594.94 253.39 50026 +1999 230 21.53 15.53 19.88 2.33 556.38 255.74 49842 +1999 231 24.85 18.85 23.2 0.63 666.63 245.22 49656 +1999 232 24.83 18.83 23.18 0.01 665.92 244.31 49469 +1999 233 21.89 15.89 20.24 0 567.53 335.56 49280 +1999 234 18.46 12.46 16.81 0.36 468.61 258.77 49091 +1999 235 21.91 15.91 20.26 0 568.16 332.63 48900 +1999 236 28.29 22.29 26.64 0 799.85 304.73 48709 +1999 237 23.84 17.84 22.19 0 631.29 322.58 48516 +1999 238 24.86 18.86 23.21 0 666.99 316.95 48323 +1999 239 26.2 20.2 24.55 0.61 716.48 232.42 48128 +1999 240 26.31 20.31 24.66 0.47 720.68 230.82 47933 +1999 241 26.53 20.53 24.88 1 729.13 228.89 47737 +1999 242 21 15 19.35 0 540.3 324.4 47541 +1999 243 21.85 15.85 20.2 0.26 566.28 239.84 47343 +1999 244 17.81 11.81 16.16 0 451.62 330.09 47145 +1999 245 19.58 13.58 17.93 0 499.16 323.31 46947 +1999 246 19.27 13.27 17.62 0 490.54 322.26 46747 +1999 247 19.39 13.39 17.74 0 493.86 320.07 46547 +1999 248 20.94 14.94 19.29 0 538.51 313.51 46347 +1999 249 19.52 13.52 17.87 0.15 497.48 236.8 46146 +1999 250 23.62 17.62 21.97 1.2 623.81 225.47 45945 +1999 251 27.05 21.05 25.4 1.71 749.45 213.82 45743 +1999 252 25.95 19.95 24.3 0.31 707.02 215.76 45541 +1999 253 21.43 15.43 19.78 0.09 553.32 226.36 45339 +1999 254 21.82 15.82 20.17 0.97 565.35 223.88 45136 +1999 255 19.89 13.89 18.24 1.07 507.9 226.59 44933 +1999 256 18.96 12.96 17.31 0.13 482.04 226.84 44730 +1999 257 17.51 11.51 15.86 0 443.96 304.03 44527 +1999 258 16.68 10.68 15.03 0.2 423.34 227.75 44323 +1999 259 12.54 6.54 10.89 0 332.24 309.71 44119 +1999 260 13.67 7.67 12.02 0 355.26 305.18 43915 +1999 261 17.87 11.87 16.22 0.07 453.17 220.2 43711 +1999 262 20.92 14.92 19.27 0.62 537.91 212.36 43507 +1999 263 22.7 16.7 21.05 0 593.32 275.37 43303 +1999 264 21.35 15.35 19.7 0.06 550.88 207.76 43099 +1999 265 25.84 19.84 24.19 0 702.89 259.9 42894 +1999 266 25.42 19.42 23.77 0 687.31 259.15 42690 +1999 267 26.57 20.57 24.92 0.06 730.68 189.29 42486 +1999 268 29.54 23.54 27.89 0 853.52 237.8 42282 +1999 269 25.18 19.18 23.53 0.01 678.54 189.59 42078 +1999 270 23.52 17.52 21.87 0.18 620.43 191.89 41875 +1999 271 25.89 19.89 24.24 0 704.76 245.41 41671 +1999 272 23.96 17.96 22.31 0 635.41 249.42 41468 +1999 273 20.92 14.92 19.27 0 537.91 255.95 41265 +1999 274 10.71 4.71 9.06 0.01 297.67 205.43 41062 +1999 275 14.19 8.19 12.54 0 366.3 265.49 40860 +1999 276 10.74 4.74 9.09 0 298.21 268.31 40658 +1999 277 9.31 3.31 7.66 0 273.34 267.57 40456 +1999 278 10.06 4.06 8.41 0.03 286.15 197.74 40255 +1999 279 11.79 5.79 10.14 0.01 317.68 193.75 40054 +1999 280 13.51 7.51 11.86 0 351.92 252.96 39854 +1999 281 10.42 4.42 8.77 0.05 292.48 191.14 39654 +1999 282 11.52 5.52 9.87 0 312.57 250.55 39455 +1999 283 14.49 8.49 12.84 0 372.81 243.06 39256 +1999 284 12.82 6.82 11.17 0.02 337.82 182.07 39058 +1999 285 13.04 7.04 11.39 0 342.26 239.78 38861 +1999 286 12.51 6.51 10.86 0 331.65 237.82 38664 +1999 287 14.49 8.49 12.84 0 372.81 231.8 38468 +1999 288 15.55 9.55 13.9 0.42 396.58 170.44 38273 +1999 289 18.16 12.16 16.51 0 460.7 219.78 38079 +1999 290 20.58 14.58 18.93 0 527.84 211.82 37885 +1999 291 21.17 15.17 19.52 0.62 545.42 155.92 37693 +1999 292 22.23 16.23 20.58 0 578.24 202.8 37501 +1999 293 20 14 18.35 0.26 511.04 154.04 37311 +1999 294 15.86 9.86 14.21 1.88 403.78 157.89 37121 +1999 295 15.51 9.51 13.86 0.32 395.66 156.24 36933 +1999 296 12.28 6.28 10.63 0 327.13 210.55 36745 +1999 297 15.99 9.99 14.34 0 406.83 202.33 36560 +1999 298 17.54 11.54 15.89 0 444.72 197.13 36375 +1999 299 15.63 9.63 13.98 0.31 398.43 148.24 36191 +1999 300 11.95 5.95 10.3 0.13 320.74 150.19 36009 +1999 301 12.27 6.27 10.62 0.07 326.93 148.01 35829 +1999 302 14.59 8.59 12.94 0.29 375 143.7 35650 +1999 303 14.24 8.24 12.59 0 367.38 189.58 35472 +1999 304 16.05 10.05 14.4 0.08 408.24 138.37 35296 +1999 305 5.33 -0.67 3.68 0.44 213.27 145.48 35122 +1999 306 4.7 -1.3 3.05 0.56 204.89 144.13 34950 +1999 307 3.5 -2.5 1.85 0 189.71 190.49 34779 +1999 308 4.18 -1.82 2.53 0 198.19 187.36 34610 +1999 309 4.71 -1.29 3.06 0 205.02 184.63 34444 +1999 310 2.87 -3.13 1.22 0 182.14 183.42 34279 +1999 311 3.26 -2.74 1.61 0 186.8 180.95 34116 +1999 312 8.09 2.09 6.44 1.44 253.55 130.93 33956 +1999 313 10.1 4.1 8.45 0.53 286.85 127.92 33797 +1999 314 9.9 3.9 8.25 0.05 283.37 126.62 33641 +1999 315 6.53 0.53 4.88 0 230.05 169.25 33488 +1999 316 5.97 -0.03 4.32 0 222.09 167.49 33337 +1999 317 9.71 3.71 8.06 0 280.11 162.14 33188 +1999 318 4.86 -1.14 3.21 0.18 206.99 122.8 33042 +1999 319 9.49 3.49 7.84 0.02 276.37 118.76 32899 +1999 320 10.59 4.59 8.94 0 295.51 155.46 32758 +1999 321 8.39 2.39 6.74 1.25 258.3 116.52 32620 +1999 322 9.53 3.53 7.88 0.16 277.05 114.42 32486 +1999 323 6.06 0.06 4.41 0 223.35 153.73 32354 +1999 324 5.3 -0.7 3.65 0 212.87 152.2 32225 +1999 325 5.77 -0.23 4.12 0.04 219.3 112.61 32100 +1999 326 4.81 -1.19 3.16 0.06 206.34 112 31977 +1999 327 10.3 4.3 8.65 1.08 290.36 107.46 31858 +1999 328 6.82 0.82 5.17 0.42 234.27 108.11 31743 +1999 329 5.14 -0.86 3.49 0.02 210.72 107.84 31631 +1999 330 4.35 -1.65 2.7 0 200.36 142.83 31522 +1999 331 9.35 3.35 7.7 0 274.01 137.96 31417 +1999 332 11.09 5.09 9.44 0.14 304.58 101.12 31316 +1999 333 7.84 1.84 6.19 0.26 249.65 102.33 31218 +1999 334 6.71 0.71 5.06 0.22 232.66 102.12 31125 +1999 335 3.18 -2.82 1.53 0.56 185.83 102.86 31035 +1999 336 5.55 -0.45 3.9 0.19 216.27 101.01 30949 +1999 337 7.45 1.45 5.8 0.16 243.67 98.82 30867 +1999 338 2.91 -3.09 1.26 0 182.61 133.6 30790 +1999 339 7.27 1.27 5.62 0 240.96 130.17 30716 +1999 340 5.75 -0.25 4.1 0 219.02 130.44 30647 +1999 341 4.89 -1.11 3.24 0.13 207.39 97.54 30582 +1999 342 -0.03 -6.03 -1.68 0.48 150.54 143.58 30521 +1999 343 -1.42 -7.42 -3.07 0.31 137.16 144.43 30465 +1999 344 1.91 -4.09 0.26 0 171.1 174.56 30413 +1999 345 6.33 0.33 4.68 0.09 227.18 139.4 30366 +1999 346 3.35 -2.65 1.7 0 187.89 171.7 30323 +1999 347 6.68 0.68 5.03 0 232.23 168.32 30284 +1999 348 -0.24 -6.24 -1.89 0.21 148.45 140.32 30251 +1999 349 -2.22 -8.22 -3.87 1.8 129.93 146.36 30221 +1999 350 -1.34 -7.34 -2.99 0.7 137.9 148.13 30197 +1999 351 -3.02 -9.02 -4.67 0.8 123.04 150.99 30177 +1999 352 -1.28 -7.28 -2.93 0 138.46 182.31 30162 +1999 353 -0.99 -6.99 -2.64 0 141.19 182.15 30151 +1999 354 3.09 -2.91 1.44 0 184.76 179.89 30145 +1999 355 6.44 0.44 4.79 0 228.76 177.12 30144 +1999 356 5.24 -0.76 3.59 0.11 212.06 146.14 30147 +1999 357 5.19 -0.81 3.54 0 211.39 176.55 30156 +1999 358 1.46 -4.54 -0.19 0 166.13 178.36 30169 +1999 359 4.43 -1.57 2.78 0.49 201.39 145.14 30186 +1999 360 3.81 -2.19 2.16 0 193.54 176.51 30208 +1999 361 5.15 -0.85 3.5 0 210.85 175.36 30235 +1999 362 2.97 -3.03 1.32 0 183.33 176.54 30267 +1999 363 7.82 1.82 6.17 0 249.34 173.11 30303 +1999 364 3.11 -2.89 1.46 0 184.99 175.88 30343 +1999 365 0.76 -5.24 -0.89 0.31 158.64 145.06 30388 +2000 1 -2.78 -8.78 -4.43 0 125.07 179.62 30438 +2000 2 0.78 -5.22 -0.87 0 158.85 178.76 30492 +2000 3 2.28 -3.72 0.63 0 175.29 178.61 30551 +2000 4 0.79 -5.21 -0.86 0.02 158.96 146.81 30614 +2000 5 0.39 -5.61 -1.26 0.3 154.8 147.28 30681 +2000 6 -0.11 -6.11 -1.76 1.5 149.74 152.69 30752 +2000 7 -0.54 -6.54 -2.19 0 145.51 187.25 30828 +2000 8 -2.39 -8.39 -4.04 0.16 128.44 155.34 30907 +2000 9 -1.89 -7.89 -3.54 0 132.87 190.79 30991 +2000 10 2.15 -3.85 0.5 0 173.81 189.88 31079 +2000 11 1.07 -4.93 -0.58 0 161.92 191.11 31171 +2000 12 1.56 -4.44 -0.09 0.26 167.22 156.31 31266 +2000 13 5.36 -0.64 3.71 0 213.68 190.16 31366 +2000 14 4.78 -1.22 3.13 0 205.94 191.22 31469 +2000 15 5.26 -0.74 3.61 0.01 212.33 155.68 31575 +2000 16 5.72 -0.28 4.07 0.06 218.61 155.52 31686 +2000 17 4.88 -1.12 3.23 0 207.26 193.04 31800 +2000 18 4.47 -1.53 2.82 0 201.91 194.46 31917 +2000 19 3.51 -2.49 1.86 0 189.84 196.36 32038 +2000 20 5.74 -0.26 4.09 0 218.88 195.62 32161 +2000 21 7.39 1.39 5.74 0.22 242.76 157.26 32289 +2000 22 4.13 -1.87 2.48 0 197.56 198.64 32419 +2000 23 4.69 -1.31 3.04 0.01 204.76 159.89 32552 +2000 24 2.97 -3.03 1.32 0 183.33 201.9 32688 +2000 25 1.78 -4.22 0.13 0 169.65 204.09 32827 +2000 26 -2.56 -8.56 -4.21 0 126.96 207.95 32969 +2000 27 -3.82 -9.82 -5.47 0 116.47 210.33 33114 +2000 28 -3.68 -9.68 -5.33 0 117.59 212.34 33261 +2000 29 -3.73 -9.73 -5.38 0 117.19 214.59 33411 +2000 30 -4.31 -10.31 -5.96 0 112.59 216.92 33564 +2000 31 -3.85 -9.85 -5.5 0 116.22 218.97 33718 +2000 32 0.59 -5.41 -1.06 1.12 156.87 173.94 33875 +2000 33 2.5 -3.5 0.85 0.08 177.82 174.61 34035 +2000 34 6.34 0.34 4.69 0.04 227.32 135.26 34196 +2000 35 6.18 0.18 4.53 0.14 225.05 136.96 34360 +2000 36 2.8 -3.2 1.15 0 181.32 187.59 34526 +2000 37 3.04 -2.96 1.39 0.01 184.16 142.4 34694 +2000 38 2.63 -3.37 0.98 0 179.33 192.89 34863 +2000 39 7.09 1.09 5.44 0 238.26 192.07 35035 +2000 40 9.6 3.6 7.95 0 278.23 192.22 35208 +2000 41 11.2 5.2 9.55 0 306.61 193.02 35383 +2000 42 10.82 4.82 9.17 0 299.65 195.96 35560 +2000 43 9.34 3.34 7.69 0 273.84 200.26 35738 +2000 44 8.8 2.8 7.15 0 264.91 203.35 35918 +2000 45 10.65 4.65 9 0 296.59 203.89 36099 +2000 46 9.72 3.72 8.07 0 280.28 207.6 36282 +2000 47 10.27 4.27 8.62 0 289.83 209.75 36466 +2000 48 8.05 2.05 6.4 0 252.93 214.95 36652 +2000 49 9.22 3.22 7.57 0.02 271.84 162.33 36838 +2000 50 10.59 4.59 8.94 0 295.51 217.47 37026 +2000 51 10.79 4.79 9.14 0 299.11 220.13 37215 +2000 52 6.28 0.28 4.63 0 226.47 227.87 37405 +2000 53 3.11 -2.89 1.46 0 184.99 233.58 37596 +2000 54 4.91 -1.09 3.26 0 207.65 234.85 37788 +2000 55 3.91 -2.09 2.26 0 194.79 238.71 37981 +2000 56 3.81 -2.19 2.16 0 193.54 241.5 38175 +2000 57 9.04 3.04 7.39 0.47 268.85 179.35 38370 +2000 58 9.43 3.43 7.78 0 275.36 241.57 38565 +2000 59 11.95 5.95 10.3 0 320.74 240.88 38761 +2000 60 9.29 3.29 7.64 0 273.01 247.27 38958 +2000 61 12.31 6.31 10.66 0 327.71 246.05 39156 +2000 62 11.29 5.29 9.64 0 308.27 250.27 39355 +2000 63 9.61 3.61 7.96 0 278.4 255.52 39553 +2000 64 9.53 3.53 7.88 0.09 277.05 193.87 39753 +2000 65 9.05 3.05 7.4 0 269.02 261.98 39953 +2000 66 7.71 1.71 6.06 0.69 247.65 199.75 40154 +2000 67 5.53 -0.47 3.88 0.04 215.99 203.73 40355 +2000 68 7 1 5.35 0.44 236.93 204.69 40556 +2000 69 5.34 -0.66 3.69 0.39 213.41 208.02 40758 +2000 70 4.05 -1.95 2.4 0.12 196.55 211.13 40960 +2000 71 5.77 -0.23 4.12 0.08 219.3 212.02 41163 +2000 72 8.19 2.19 6.54 0 255.13 282.7 41366 +2000 73 11.21 5.21 9.56 0 306.79 281.12 41569 +2000 74 12.52 6.52 10.87 0 331.84 281.72 41772 +2000 75 10.74 4.74 9.09 0 298.21 287.25 41976 +2000 76 12.77 6.77 11.12 0 336.82 286.56 42179 +2000 77 13.64 7.64 11.99 0.36 354.63 215.67 42383 +2000 78 14.64 8.64 12.99 0.47 376.1 216.2 42587 +2000 79 13.46 7.46 11.81 0 350.88 293.17 42791 +2000 80 14.49 8.49 12.84 0.04 372.81 220.27 42996 +2000 81 12.98 6.98 11.33 0.03 341.05 224.3 43200 +2000 82 12.41 6.41 10.76 0 329.68 302.7 43404 +2000 83 12.47 6.47 10.82 1.12 330.86 228.79 43608 +2000 84 10.62 4.62 8.97 1.93 296.05 233.01 43812 +2000 85 8.61 2.61 6.96 0 261.83 316.2 44016 +2000 86 5.15 -0.85 3.5 0 210.85 323.03 44220 +2000 87 6.28 0.28 4.63 0 226.47 324.25 44424 +2000 88 8.78 2.78 7.13 0.12 264.59 242.44 44627 +2000 89 8.44 2.44 6.79 0.49 259.1 244.53 44831 +2000 90 9.39 3.39 7.74 0.08 274.68 245.25 45034 +2000 91 10.56 4.56 8.91 0 294.97 327.4 45237 +2000 92 12.6 6.6 10.95 0.06 333.43 244.52 45439 +2000 93 11.93 5.93 10.28 0 320.35 329.46 45642 +2000 94 12.72 6.72 11.07 0 335.82 330.12 45843 +2000 95 13.74 7.74 12.09 0 356.73 330.22 46045 +2000 96 15.98 9.98 14.33 0 406.59 327.37 46246 +2000 97 16.51 10.51 14.86 0 419.22 328.1 46446 +2000 98 14.72 8.72 13.07 0.09 377.86 250.63 46647 +2000 99 17.41 11.41 15.76 0.19 441.43 247.28 46846 +2000 100 17 11 15.35 0.04 431.19 249.49 47045 +2000 101 18.75 12.75 17.1 0.77 476.36 247.37 47243 +2000 102 17.19 11.19 15.54 0.02 435.91 251.92 47441 +2000 103 17.29 11.29 15.64 0 438.42 337.43 47638 +2000 104 21.66 15.66 20.01 0.07 560.39 244.61 47834 +2000 105 20.91 14.91 19.26 0.02 537.61 247.75 48030 +2000 106 20.01 14.01 18.36 0 511.32 334.75 48225 +2000 107 17.01 11.01 15.36 0.01 431.44 258.69 48419 +2000 108 18.01 12.01 16.36 0.37 456.79 257.94 48612 +2000 109 13.84 7.84 12.19 0 358.84 355.82 48804 +2000 110 11.95 5.95 10.3 0 320.74 361.13 48995 +2000 111 13.33 7.33 11.68 0 348.2 359.87 49185 +2000 112 16.13 10.13 14.48 0.05 410.13 266.15 49374 +2000 113 17.97 11.97 16.32 0.07 455.76 263.45 49561 +2000 114 21.21 15.21 19.56 0.03 546.63 256.99 49748 +2000 115 18.26 12.26 16.61 0.44 463.33 264.97 49933 +2000 116 15.85 9.85 14.2 0.75 403.54 270.74 50117 +2000 117 14.35 8.35 12.7 0.16 369.76 274.42 50300 +2000 118 20.35 14.35 18.7 0.09 521.12 262.93 50481 +2000 119 15.15 9.15 13.5 0.02 387.46 274.87 50661 +2000 120 16.4 10.4 14.75 0 416.57 364.5 50840 +2000 121 17.93 11.93 16.28 0 454.72 361.41 51016 +2000 122 21.03 15.03 19.38 0 541.2 352.8 51191 +2000 123 23.77 17.77 22.12 0 628.9 343.58 51365 +2000 124 23.63 17.63 21.98 0 624.15 345.16 51536 +2000 125 17.96 11.96 16.31 0 455.5 365.54 51706 +2000 126 14.88 8.88 13.23 0 381.41 374.72 51874 +2000 127 15.06 9.06 13.41 0 385.44 375.17 52039 +2000 128 16.2 10.2 14.55 0 411.79 373.26 52203 +2000 129 13.85 7.85 12.2 0.02 359.05 284.92 52365 +2000 130 17.39 11.39 15.74 0 440.93 371.64 52524 +2000 131 20.16 14.16 18.51 0 515.63 363.89 52681 +2000 132 26.54 20.54 24.89 0 729.52 339.11 52836 +2000 133 23.82 17.82 22.17 0 630.61 351.8 52989 +2000 134 22.53 16.53 20.88 0 587.83 357.58 53138 +2000 135 19.44 13.44 17.79 0.03 495.25 276.84 53286 +2000 136 21.93 15.93 20.28 0.18 568.78 270.85 53430 +2000 137 17.29 11.29 15.64 0.49 438.42 282.72 53572 +2000 138 18.01 12.01 16.36 1.5 456.79 281.6 53711 +2000 139 16.05 10.05 14.4 0.05 408.24 286.25 53848 +2000 140 20.08 14.08 18.43 1.06 513.33 277.56 53981 +2000 141 14.65 8.65 13 0.36 376.32 289.62 54111 +2000 142 15.14 9.14 13.49 0 387.24 385.45 54238 +2000 143 14.37 8.37 12.72 0 370.19 387.89 54362 +2000 144 16.23 10.23 14.58 0.12 412.51 287.72 54483 +2000 145 20.16 14.16 18.51 0.5 515.63 279.13 54600 +2000 146 21.06 15.06 19.41 0.17 542.1 277.06 54714 +2000 147 22.39 16.39 20.74 0.21 583.34 273.72 54824 +2000 148 21.63 15.63 19.98 0.21 559.46 276.14 54931 +2000 149 21.66 15.66 20.01 0 560.39 368.38 55034 +2000 150 20.47 14.47 18.82 0 524.62 372.97 55134 +2000 151 17.95 11.95 16.3 0 455.24 381.48 55229 +2000 152 17.76 11.76 16.11 0 450.34 382.16 55321 +2000 153 17.92 11.92 16.27 0 454.46 381.93 55409 +2000 154 20.73 14.73 19.08 0 532.26 373.11 55492 +2000 155 20.24 14.24 18.59 0.04 517.94 281.25 55572 +2000 156 19.34 13.34 17.69 0 492.47 378.32 55648 +2000 157 17.67 11.67 16.02 0 448.04 383.67 55719 +2000 158 20.39 14.39 18.74 0.3 522.29 281.35 55786 +2000 159 22.98 16.98 21.33 0.25 602.46 274.3 55849 +2000 160 25.84 19.84 24.19 0 702.89 353.52 55908 +2000 161 22.78 16.78 21.13 0 595.92 366.77 55962 +2000 162 21.75 15.75 20.1 0.01 563.17 278.09 56011 +2000 163 22.52 16.52 20.87 0.21 587.51 276.05 56056 +2000 164 22.34 16.34 20.69 0.14 581.74 276.6 56097 +2000 165 22.59 16.59 20.94 0 589.76 367.93 56133 +2000 166 22.34 16.34 20.69 0 581.74 368.98 56165 +2000 167 23.5 17.5 21.85 0.37 619.76 273.22 56192 +2000 168 24.77 18.77 23.12 0 663.78 358.94 56214 +2000 169 23.82 17.82 22.17 0 630.61 363.05 56231 +2000 170 25.46 19.46 23.81 0.13 688.78 266.88 56244 +2000 171 22.77 16.77 21.12 0.56 595.59 275.54 56252 +2000 172 22.65 16.65 21 0.41 591.7 275.89 56256 +2000 173 26.43 20.43 24.78 0 725.28 351.3 56255 +2000 174 28.05 22.05 26.4 0.17 789.88 257.27 56249 +2000 175 22.17 16.17 20.52 0.19 576.34 277.19 56238 +2000 176 23.88 17.88 22.23 0.53 632.66 272.01 56223 +2000 177 21.74 15.74 20.09 0.35 562.86 278.31 56203 +2000 178 22.53 16.53 20.88 0 587.83 368.08 56179 +2000 179 23.41 17.41 21.76 0 616.73 364.46 56150 +2000 180 25.68 19.68 24.03 0 696.92 354.43 56116 +2000 181 27.52 21.52 25.87 0 768.23 345.38 56078 +2000 182 26.33 20.33 24.68 0 721.44 351.16 56035 +2000 183 25.53 19.53 23.88 0.23 691.36 266.06 55987 +2000 184 25.95 19.95 24.3 1.65 707.02 264.48 55935 +2000 185 23.7 17.7 22.05 0.1 626.52 271.9 55879 +2000 186 19.35 13.35 17.7 0 492.75 378.33 55818 +2000 187 19.97 13.97 18.32 0.15 510.18 282.07 55753 +2000 188 21.76 15.76 20.11 0.26 563.48 277.11 55684 +2000 189 18.42 12.42 16.77 0.29 467.55 285.48 55611 +2000 190 15.53 9.53 13.88 0.17 396.12 291.35 55533 +2000 191 15.24 9.24 13.59 0 389.5 388.93 55451 +2000 192 17.08 11.08 15.43 0.11 433.18 287.75 55366 +2000 193 20.25 14.25 18.6 0 518.22 373.48 55276 +2000 194 21.72 15.72 20.07 0.03 562.24 276.02 55182 +2000 195 22.96 16.96 21.31 0 601.8 363 55085 +2000 196 25.58 19.58 23.93 0 693.21 351.41 54984 +2000 197 27.06 21.06 25.41 0.01 749.85 257.93 54879 +2000 198 28.4 22.4 26.75 1.15 804.45 252.47 54770 +2000 199 25.05 19.05 23.4 1.57 673.83 264.46 54658 +2000 200 22.88 16.88 21.23 0.34 599.18 270.98 54542 +2000 201 22.01 16.01 20.36 0 571.29 364.19 54423 +2000 202 19.51 13.51 17.86 0.23 497.2 279.27 54301 +2000 203 17.85 11.85 16.2 0 452.65 377 54176 +2000 204 18.13 12.13 16.48 0 459.92 375.65 54047 +2000 205 21.29 15.29 19.64 1.23 549.05 273.57 53915 +2000 206 20.08 14.08 18.43 0.1 513.33 276.29 53780 +2000 207 19.66 13.66 18.01 0 501.4 369.11 53643 +2000 208 20.9 14.9 19.25 0.07 537.31 273.2 53502 +2000 209 24.43 18.43 22.78 0 651.74 350.01 53359 +2000 210 28.22 22.22 26.57 0 796.93 331.56 53213 +2000 211 27.33 21.33 25.68 0.09 760.59 251.51 53064 +2000 212 28.09 22.09 26.44 0.51 791.53 248.07 52913 +2000 213 24.23 18.23 22.58 0 644.75 347.99 52760 +2000 214 24.88 18.88 23.23 0 667.71 344.51 52604 +2000 215 25.42 19.42 23.77 0 687.31 341.49 52445 +2000 216 26.83 20.83 25.18 0.13 740.8 250.51 52285 +2000 217 24.34 18.34 22.69 0.42 648.58 258.23 52122 +2000 218 22.9 16.9 21.25 0 599.84 349.28 51958 +2000 219 21.6 15.6 19.95 0 558.54 353.07 51791 +2000 220 23.53 17.53 21.88 0 620.77 344.88 51622 +2000 221 23.61 17.61 21.96 0 623.47 343.59 51451 +2000 222 27.34 21.34 25.69 0.48 760.99 244.62 51279 +2000 223 24.76 18.76 23.11 0.64 663.42 252.57 51105 +2000 224 26.45 20.45 24.8 0.27 726.05 246.23 50929 +2000 225 23.67 17.67 22.02 0.16 625.5 254.31 50751 +2000 226 23.19 17.19 21.54 0 609.4 339.84 50572 +2000 227 21.05 15.05 19.4 0 541.8 346.31 50392 +2000 228 19.05 13.05 17.4 0 484.5 351.51 50210 +2000 229 23.98 17.98 22.33 0 636.09 333.13 50026 +2000 230 29.07 23.07 27.42 0 832.99 308.66 49842 +2000 231 23.86 17.86 22.21 0 631.98 330.95 49656 +2000 232 28.74 22.74 27.09 0 818.83 307.76 49469 +2000 233 29.53 23.53 27.88 0 853.08 302.36 49280 +2000 234 28.54 22.54 26.89 0 810.35 306.17 49091 +2000 235 33.75 27.75 32.1 0 1057.16 274.89 48900 +2000 236 26.95 20.95 25.3 0 745.51 311.09 48709 +2000 237 26.15 20.15 24.5 0 714.58 313.11 48516 +2000 238 21.95 15.95 20.3 0.47 569.41 245.88 48323 +2000 239 20.12 14.12 18.47 0.03 514.48 249.26 48128 +2000 240 19.96 13.96 18.31 0 509.9 331.09 47933 +2000 241 21.01 15.01 19.36 0.35 540.6 244.56 47737 +2000 242 19.83 13.83 18.18 0.76 506.2 246.04 47541 +2000 243 17.59 11.59 15.94 0.67 446 249.38 47343 +2000 244 16.41 10.41 14.76 0.11 416.81 250.25 47145 +2000 245 16.33 10.33 14.68 0.06 414.89 249 46947 +2000 246 16.09 10.09 14.44 0.58 409.18 247.94 46747 +2000 247 17.77 11.77 16.12 0 450.6 324.52 46547 +2000 248 18.94 12.94 17.29 0.77 481.5 239.57 46347 +2000 249 20.49 14.49 18.84 0.14 525.2 234.65 46146 +2000 250 15.56 9.56 13.91 0.82 396.81 242.93 45945 +2000 251 14.39 8.39 12.74 0.06 370.63 243.24 45743 +2000 252 13.48 7.48 11.83 0.26 351.3 242.98 45541 +2000 253 14.26 8.26 12.61 0 367.81 320.24 45339 +2000 254 17.57 11.57 15.92 0 445.49 310.55 45136 +2000 255 16.01 10.01 14.36 0.12 407.3 234 44933 +2000 256 15.15 9.15 13.5 0 387.46 311.61 44730 +2000 257 19.75 13.75 18.1 0.3 503.94 223.62 44527 +2000 258 17.18 11.18 15.53 0.01 435.66 226.87 44323 +2000 259 19.96 13.96 18.31 0.38 509.9 219.67 44119 +2000 260 22.45 16.45 20.8 0 585.26 283.14 43915 +2000 261 22.4 16.4 20.75 0.29 583.66 210.71 43711 +2000 262 21.96 15.96 20.31 0 569.72 280.04 43507 +2000 263 22.36 16.36 20.71 0.55 582.38 207.33 43303 +2000 264 22.72 16.72 21.07 0.09 593.97 204.64 43099 +2000 265 23.21 17.21 21.56 0.13 610.06 201.77 42894 +2000 266 22.01 16.01 20.36 0.23 571.29 202.8 42690 +2000 267 23.68 17.68 22.03 0 625.84 262.62 42486 +2000 268 23.57 17.57 21.92 0.36 622.12 195.42 42282 +2000 269 21.86 15.86 20.21 0 566.6 263.41 42078 +2000 270 19.31 13.31 17.66 0 491.64 267.76 41875 +2000 271 21.75 15.75 20.1 0 563.17 258.7 41671 +2000 272 14.8 8.8 13.15 0 379.63 272.34 41468 +2000 273 16.27 10.27 14.62 0.12 413.46 200.19 41265 +2000 274 15.25 9.25 13.6 0.63 389.73 199.71 41062 +2000 275 18.35 12.35 16.7 0.15 465.7 192.79 40860 +2000 276 15.53 9.53 13.88 0 396.12 260.31 40658 +2000 277 14.32 8.32 12.67 0 369.11 259.9 40456 +2000 278 16 10 14.35 0 407.06 253.93 40255 +2000 279 11.08 5.08 9.43 0.33 304.4 194.53 40054 +2000 280 11.97 5.97 10.32 0 321.12 255.39 39854 +2000 281 13.7 7.7 12.05 0 355.89 249.93 39654 +2000 282 18.29 12.29 16.64 0 464.12 238.53 39455 +2000 283 19.4 13.4 17.75 0.01 494.14 175 39256 +2000 284 17.1 11.1 15.45 0.01 433.67 176.46 39058 +2000 285 14.13 8.13 12.48 0.05 365.02 178.53 38861 +2000 286 17.49 11.49 15.84 0.17 443.46 171.93 38664 +2000 287 13.55 7.55 11.9 2.16 352.75 174.98 38468 +2000 288 11.63 5.63 9.98 0 314.64 233.34 38273 +2000 289 8.99 2.99 7.34 0.05 268.03 175.52 38079 +2000 290 15.57 9.57 13.92 0 397.04 221.81 37885 +2000 291 13.93 7.93 12.28 0 360.75 221.81 37693 +2000 292 15.49 9.49 13.84 0 395.2 216.65 37501 +2000 293 19.34 13.34 17.69 0.66 492.47 155.09 37311 +2000 294 19.95 13.95 18.3 1.2 509.61 152.05 37121 +2000 295 23.29 17.29 21.64 0.23 612.72 144.18 36933 +2000 296 24.25 18.25 22.6 0 645.44 187.36 36745 +2000 297 22.81 16.81 21.16 0 596.9 188.52 36560 +2000 298 21.41 15.41 19.76 0 552.71 189.36 36375 +2000 299 19.38 13.38 17.73 0 493.58 190.99 36191 +2000 300 16.91 10.91 15.26 0 428.97 192.96 36009 +2000 301 15.29 9.29 13.64 0.03 390.64 144.84 35829 +2000 302 10.98 4.98 9.33 0.02 302.56 147.24 35650 +2000 303 11.15 5.15 9.5 0.08 305.68 145.16 35472 +2000 304 10.54 4.54 8.89 0.57 294.62 143.85 35296 +2000 305 9.45 3.45 7.8 0 275.69 190.22 35122 +2000 306 13.11 7.11 11.46 0 343.69 183.77 34950 +2000 307 7.75 1.75 6.1 0.51 248.26 140.32 34779 +2000 308 5.22 -0.78 3.57 0.78 211.79 139.94 34610 +2000 309 0.83 -5.17 -0.82 0.29 159.38 140.36 34444 +2000 310 5.25 -0.75 3.6 0.67 212.19 136.32 34279 +2000 311 9.34 3.34 7.69 0.17 273.84 132.04 34116 +2000 312 13.57 7.57 11.92 0.59 353.17 126.57 33956 +2000 313 14.92 8.92 13.27 0.55 382.3 123.72 33797 +2000 314 13.04 7.04 11.39 0.07 342.26 124.08 33641 +2000 315 13.67 7.67 12.02 0 355.26 162.19 33488 +2000 316 13.57 7.57 11.92 0.86 353.17 120.13 33337 +2000 317 12.72 6.72 11.07 0 335.82 159.03 33188 +2000 318 13.76 7.76 12.11 0 357.15 155.53 33042 +2000 319 14.89 8.89 13.24 0 381.63 152.49 32899 +2000 320 17.7 11.7 16.05 0 448.8 146.84 32758 +2000 321 19.62 13.62 17.97 0 500.28 141.84 32620 +2000 322 16.57 10.57 14.92 0 420.67 144.7 32486 +2000 323 18.37 12.37 16.72 0 466.23 140.59 32354 +2000 324 14.46 8.46 12.81 0 372.15 143.87 32225 +2000 325 10.95 4.95 9.3 0 302.02 145.93 32100 +2000 326 9.12 3.12 7.47 0.9 270.17 109.61 31977 +2000 327 2.92 -3.08 1.27 0.73 182.73 111.45 31858 +2000 328 2.54 -3.46 0.89 0 178.28 146.83 31743 +2000 329 5.13 -0.87 3.48 0 210.58 143.79 31631 +2000 330 7.95 1.95 6.3 0 251.36 140.38 31522 +2000 331 7.97 1.97 6.32 0 251.67 139.06 31417 +2000 332 10.96 4.96 9.31 0 302.2 134.95 31316 +2000 333 14.13 8.13 12.48 0 365.02 130.73 31218 +2000 334 16.99 10.99 15.34 0.19 430.95 94.71 31125 +2000 335 7.35 1.35 5.7 0.52 242.16 100.91 31035 +2000 336 5.64 -0.36 3.99 0.03 217.5 100.97 30949 +2000 337 8.78 2.78 7.13 0.01 264.59 98.08 30867 +2000 338 5.69 -0.31 4.04 0.1 218.19 99 30790 +2000 339 10.19 4.19 8.54 0.01 288.42 95.96 30716 +2000 340 8.2 2.2 6.55 0 255.28 128.78 30647 +2000 341 8.35 2.35 6.7 0.09 257.66 95.82 30582 +2000 342 7 1 5.35 0.08 236.93 95.97 30521 +2000 343 6.24 0.24 4.59 0 225.9 127.64 30465 +2000 344 10.14 4.14 8.49 0 287.55 123.69 30413 +2000 345 11.68 5.68 10.03 0 315.59 121.97 30366 +2000 346 8.22 2.22 6.57 0 255.6 124.2 30323 +2000 347 4.97 -1.03 3.32 0 208.45 125.72 30284 +2000 348 2.94 -3.06 1.29 0 182.97 126.47 30251 +2000 349 5.23 -0.77 3.58 0 211.92 124.84 30221 +2000 350 4.14 -1.86 2.49 1.46 197.68 93.84 30197 +2000 351 5.78 -0.22 4.13 0.97 219.44 92.97 30177 +2000 352 3.52 -2.48 1.87 0.06 189.96 93.86 30162 +2000 353 -0.4 -6.4 -2.05 0.09 146.88 139.23 30151 +2000 354 1.14 -4.86 -0.51 0.03 162.67 138.57 30145 +2000 355 -0.41 -6.41 -2.06 0.14 146.78 139.51 30144 +2000 356 0.34 -5.66 -1.31 0.02 154.29 139.25 30147 +2000 357 3.56 -2.44 1.91 0.15 190.45 137.66 30156 +2000 358 10 4 8.35 0.17 285.11 90.74 30169 +2000 359 8.37 2.37 6.72 0 257.98 122.34 30186 +2000 360 6.2 0.2 4.55 0 225.33 124.16 30208 +2000 361 0.86 -5.14 -0.79 0 159.69 127.32 30235 +2000 362 -0.06 -6.06 -1.71 0.27 150.24 140.59 30267 +2000 363 -0.48 -6.48 -2.13 1.11 146.09 144.62 30303 +2000 364 2.99 -3.01 1.34 0 183.56 175.2 30343 +2000 365 1.09 -4.91 -0.56 0 162.13 176.48 30388 +2001 1 2 -10 -1.3 0 67.5 173.99 30217 +2001 2 -1 -4 -1.83 0.05 68.75 57.46 30272 +2001 3 1 -4 -0.38 0 18.75 118.03 30331 +2001 4 3 -6 0.52 0 12.5 163.04 30396 +2001 5 7 0 5.08 0 11.25 142.19 30464 +2001 6 13 4 10.53 0 442.5 155.65 30537 +2001 7 7 2 5.63 0 88.75 111.18 30614 +2001 8 5 4 4.72 0.96 52.5 22.57 30695 +2001 9 7 2 5.63 0 392.5 114.45 30781 +2001 10 5 -4 2.52 0 171.25 166.19 30870 +2001 11 3 -3 1.35 0 76.67 134.79 30964 +2001 12 3 1 2.45 0 201.11 53.72 31061 +2001 13 1 -5 -0.65 0 114.44 141.2 31162 +2001 14 -1 -6 -2.38 0 100 125.52 31268 +2001 15 -1 -9 -3.2 0 84.44 171.08 31376 +2001 16 -3 -10 -4.92 0 37.78 162.92 31489 +2001 17 -1 -4 -1.83 0 120 83.76 31605 +2001 18 2 -2 0.9 0 124.46 109.25 31724 +2001 19 1 -2 0.18 0 31 101.21 31847 +2001 20 0 -2 -0.55 0 42 62.92 31974 +2001 21 0 -2 -0.55 0 80 49.01 32103 +2001 22 0 -2 -0.55 0.04 45 50.15 32236 +2001 23 1 -1 0.45 0.06 17 38.35 32372 +2001 24 3 0 2.17 0.05 2 40.26 32510 +2001 25 3 1 2.45 0.52 12 42.31 32652 +2001 26 5 2 4.17 0.03 117.58 43.3 32797 +2001 27 9 2 7.08 0.77 241 142.28 32944 +2001 28 6 2 4.9 0 95 93.06 33094 +2001 29 4 1 3.17 0 71 70.7 33247 +2001 30 2 2 2 0.05 98 44.02 33402 +2001 31 3 1 2.45 0 267 137.75 33559 +2001 32 2 -1 1.18 0 231 157.02 33719 +2001 33 3 -4 1.08 0 163 197.42 33882 +2001 34 2 -5 0.07 0 202 160.52 34046 +2001 35 8 -3 4.97 0 448 112.53 34213 +2001 36 15 2 11.43 0 479 225.08 34382 +2001 37 14 2 10.7 0 496 226.46 34552 +2001 38 16 6 13.25 0 672 174.94 34725 +2001 39 17 11 15.35 0 775 218.7 34900 +2001 40 16 6 13.25 0 553 188.22 35076 +2001 41 10 6 8.9 0 321 217.11 35254 +2001 42 10 0 7.25 0 307 278.19 35434 +2001 43 12 -2 8.15 0 458 293.15 35615 +2001 44 10 1 7.53 0 278 178.07 35798 +2001 45 9 1 6.8 0 375 273.38 35983 +2001 46 11 -2 7.43 0 339 281.71 36169 +2001 47 12 -3 7.88 0 456 295.25 36356 +2001 48 11 -4 6.88 0 280 212.97 36544 +2001 49 12 -2 8.15 0 350 251.73 36734 +2001 50 9 2 7.08 0 457 165.62 36925 +2001 51 9 3 7.35 0 383 107.13 37117 +2001 52 12 1 8.97 0 603 224.28 37310 +2001 53 10 1 7.53 0 541.82 273.68 37505 +2001 54 7 -1 4.8 0.07 162.73 138.98 37700 +2001 55 2 -4 0.35 0 201.82 176.45 37896 +2001 56 3 -8 -0.02 0 270.91 316.21 38093 +2001 57 2 -4 0.35 0 229.09 205.7 38291 +2001 58 6 -7 2.43 0 400 287.88 38490 +2001 59 5 -3 2.8 0.81 319.09 210.5 38689 +2001 60 5 -1 3.35 0 64.55 158.82 38890 +2001 61 8 -3 4.97 0.65 246.67 306.46 39091 +2001 62 9 3 7.35 0 174.17 75.36 39292 +2001 63 19 2 14.32 0 618.33 218.18 39495 +2001 64 11 6 9.63 0.32 239.17 94.54 39697 +2001 65 6 0 4.35 0 285.83 264.44 39901 +2001 66 9 -1 6.25 0 402.5 274.9 40105 +2001 67 14 3 10.98 0 356.67 224.3 40309 +2001 68 18 8 15.25 0 627.5 290.01 40514 +2001 69 16 7 13.53 0 459.17 265.15 40719 +2001 70 19 5 15.15 0.01 815.83 313.06 40924 +2001 71 21 7 17.15 0 734.17 360.51 41130 +2001 72 10 8 9.45 1.88 123.33 49.57 41336 +2001 73 14 4 11.25 0.18 291.67 243.11 41543 +2001 74 14 2 10.7 0 356.67 232.28 41749 +2001 75 18 5 14.43 0 566.67 385.14 41956 +2001 76 19 5 15.15 0 668.33 272.1 42163 +2001 77 19 8 15.98 0 830.83 332.7 42370 +2001 78 14 7 12.07 0.7 472.5 192.26 42578 +2001 79 10 3 8.07 0 192.5 289.27 42785 +2001 80 3 1 2.45 0.02 16.67 52.42 42992 +2001 81 7 3 5.9 0.03 170.74 49.38 43200 +2001 82 15 5 12.25 0 426.67 264.56 43407 +2001 83 18 9 15.53 0 630 260.62 43615 +2001 84 18 4 14.15 0.79 458.33 326.83 43822 +2001 85 15 8 13.07 0.91 321.67 304.53 44029 +2001 86 3 1 2.45 0 161.67 126.62 44236 +2001 87 5 -2 3.08 0 210 138.53 44443 +2001 88 9 2 7.08 0 169.17 177.9 44650 +2001 89 11 5 9.35 0 179.17 137.49 44857 +2001 90 14 7 12.07 0 390.83 247.15 45063 +2001 91 16 2 12.15 0 572.08 428.92 45270 +2001 92 18 3 13.88 0 729.62 462.19 45475 +2001 93 19 2 14.32 0 863.08 421.72 45681 +2001 94 21 5 16.6 0.2 1004.62 433.87 45886 +2001 95 12 9 11.18 0.3 453.85 174.61 46091 +2001 96 17 2 12.88 0 713.57 368.41 46295 +2001 97 18 7 14.98 1.24 663.57 258.14 46499 +2001 98 9 8 8.72 1.19 57.14 48.78 46702 +2001 99 12 6 10.35 0 362.14 187.64 46905 +2001 100 14 3 10.98 0.12 429.29 360.23 47107 +2001 101 12 6 10.35 0.32 165 105.38 47309 +2001 102 14 9 12.63 0 370 286.92 47510 +2001 103 7 1 5.35 0 372.14 461.91 47710 +2001 104 7 -2 4.53 0 349.29 401.47 47910 +2001 105 10 -4 6.15 0 463.57 460.78 48108 +2001 106 13 -1 9.15 0.14 456.43 292.55 48306 +2001 107 13 5 10.8 0 408.57 239.26 48504 +2001 108 14 -1 9.88 0 578.57 389.85 48700 +2001 109 15 1 11.15 0.67 359.29 272.36 48895 +2001 110 11 4 9.07 0.13 103.57 144.88 49089 +2001 111 10 6 8.9 0.01 146.43 156.2 49282 +2001 112 12 4 9.8 0.2 245.71 237.18 49475 +2001 113 15 3 11.7 0 482.86 438.07 49666 +2001 114 19 4 14.88 0 936.43 496.52 49855 +2001 115 22 4 17.05 0.1 905 451.17 50044 +2001 116 13 10 12.18 0.13 314.29 110.02 50231 +2001 117 19 3 14.6 0 785.71 475.67 50417 +2001 118 21 5 16.6 0 1000 477.28 50601 +2001 119 24 5 18.77 0 1067.86 418.98 50784 +2001 120 25 6 19.77 0 952.14 421.74 50966 +2001 121 26 12 22.15 0 1205 477.07 51145 +2001 122 27 10 22.32 0 1517.86 501.58 51324 +2001 123 26 9 21.32 0 1388.45 480.53 51500 +2001 124 27 11 22.6 1.21 1277.14 459.2 51674 +2001 125 23 11 19.7 0.07 516 400.06 51847 +2001 126 20 13 18.07 0.03 380.67 292.17 52018 +2001 127 16 12 14.9 0.18 286 166.25 52187 +2001 128 19 11 16.8 0.56 307.33 276.77 52353 +2001 129 22 13 19.52 0.78 606.67 394.77 52518 +2001 130 22 7 17.88 0 1026.67 507.62 52680 +2001 131 22 11 18.98 0.06 715.33 382.2 52840 +2001 132 18 9 15.53 0 791.33 473.93 52998 +2001 133 18 5 14.43 0 861.33 519.96 53153 +2001 134 20 6 16.15 0 940.67 497.67 53306 +2001 135 24 6 19.05 0 850 394.93 53456 +2001 136 25 12 21.43 0 1130.67 460.14 53603 +2001 137 26 11 21.88 0 1139.33 503.89 53748 +2001 138 23 15 20.8 0.49 959.33 404.59 53889 +2001 139 20 9 16.98 0 771.33 402.42 54028 +2001 140 21 4 16.32 0 844.67 418.71 54164 +2001 141 22 7 17.88 0 752.67 282.88 54297 +2001 142 23 7 18.6 0 744.17 507.16 54426 +2001 143 22 11 18.98 0 880.85 370.96 54552 +2001 144 24 5 18.77 0 1293.68 506.51 54675 +2001 145 25 7 20.05 0 1324.37 452.07 54795 +2001 146 24 13 20.98 0 1296.25 524.29 54911 +2001 147 28 10 23.05 0 1853.13 413.52 55023 +2001 148 29 17 25.7 0 1800.63 391.35 55132 +2001 149 30 19 26.98 0 1362.84 344.28 55237 +2001 150 27 17 24.25 0.52 1091.15 250.74 55339 +2001 151 24 12 20.7 0.4 1038.59 299.29 55436 +2001 152 21 12 18.52 0 730.22 329.73 55530 +2001 153 21 5 16.6 0 1016.18 489.92 55619 +2001 154 19 10 16.52 1.95 651.84 255.26 55705 +2001 155 16 8 13.8 0 504.86 316.38 55786 +2001 156 20 6 16.15 0 845 419.58 55863 +2001 157 23 5 18.05 0.22 840 399.19 55936 +2001 158 25 15 22.25 0.16 985.63 363.38 56004 +2001 159 27 11 22.6 0 1108.13 488.63 56068 +2001 160 21 12 18.52 0 855 320.78 56128 +2001 161 28 13 23.88 0 905 407.53 56183 +2001 162 15 14 14.73 1.27 165 95.46 56234 +2001 163 21 4 16.32 0 1042.42 500.28 56280 +2001 164 22 8 18.15 0 910 497.97 56321 +2001 165 23 8 18.88 0.02 672.5 236.96 56358 +2001 166 27 11 22.6 0 1315 434.32 56390 +2001 167 29 11 24.05 0.58 1278.75 414.95 56418 +2001 168 20 15 18.63 0.4 231.88 200.52 56440 +2001 169 23 13 20.25 0 828.12 297.9 56458 +2001 170 19 15 17.9 0 744.38 210.03 56472 +2001 171 20 14 18.35 0.02 748.12 137.88 56480 +2001 172 27 14 23.43 0 1497.5 474.08 56484 +2001 173 23 12 19.98 1.7 810 289.91 56482 +2001 174 25 8 20.32 0 1055.63 465.3 56476 +2001 175 26 9 21.32 0 1378.13 498.13 56466 +2001 176 27 10 22.32 0 1445 428.08 56450 +2001 177 28 13 23.88 0 1778.75 495.89 56430 +2001 178 32 12 26.5 0 1567.5 482.89 56405 +2001 179 30 14 25.6 0.83 1048.12 348.75 56375 +2001 180 28 18 25.25 0 990.63 287.54 56341 +2001 181 30 15 25.88 0.03 1743.75 473.41 56301 +2001 182 24 15 21.52 1.33 496.25 113.54 56258 +2001 183 25 15 22.25 0.01 1209.37 415.4 56209 +2001 184 24 13 20.98 0.1 1020.63 426.75 56156 +2001 185 24 14 21.25 0.12 440.63 250.5 56099 +2001 186 26 9 21.32 0 933.12 389.4 56037 +2001 187 28 13 23.88 0 880 354.6 55971 +2001 188 33 19 29.15 0 1773.75 458.54 55900 +2001 189 29 15 25.15 1.09 1701.25 385.09 55825 +2001 190 26 17 23.52 0 855.63 313.78 55746 +2001 191 29 12 24.32 0 779.38 364.72 55663 +2001 192 31 14 26.32 0.35 1521.25 468.54 55575 +2001 193 23 16 21.07 0 769.38 213.58 55484 +2001 194 28 13 23.88 0 1173.75 402.61 55388 +2001 195 30 16 26.15 0 1610.63 439.56 55289 +2001 196 24 17 22.07 0 2006.25 450.71 55186 +2001 197 33 17 28.6 0.1 2007.81 419.95 55079 +2001 198 20 14 18.35 0.6 248.75 138.4 54968 +2001 199 27 10 22.32 0.01 775.63 388.86 54854 +2001 200 27 14 23.43 0 1278.75 422.57 54736 +2001 201 23 17 21.35 0.51 391.88 227.34 54615 +2001 202 18 15 17.18 0.48 283.75 74.51 54490 +2001 203 22 16 20.35 0 881.25 180.17 54362 +2001 204 21 18 20.18 0.14 660 67.73 54231 +2001 205 23 17 21.35 0.3 526.25 173.79 54097 +2001 206 26 16 23.25 0 1017.5 283.4 53960 +2001 207 27 18 24.52 0 1015.2 328.03 53819 +2001 208 29 17 25.7 0 1364.51 403.79 53676 +2001 209 30 15 25.88 0 1631.2 454.74 53530 +2001 210 30 16 26.15 0 1573.01 435.81 53382 +2001 211 29 17 25.7 0.09 1364.51 301.09 53230 +2001 212 33 17 28.6 0 1976.48 449.03 53076 +2001 213 31 18 27.43 0 1591.34 405.94 52920 +2001 214 31 17 27.15 0 1659.16 422.53 52761 +2001 215 34 18 29.6 0 2083.07 436.44 52600 +2001 216 35 19 30.6 0 2194.48 430.22 52437 +2001 217 26 19 24.07 0 799.95 258.18 52271 +2001 218 28 14 24.15 0 1412.02 432.74 52103 +2001 219 31 12 25.77 0 1914.12 481.71 51934 +2001 220 33 14 27.77 0 2132.05 469.5 51762 +2001 221 31 17 27.15 0 1659.16 410.58 51588 +2001 222 27 17 24.25 1.26 1091.15 255.49 51413 +2001 223 20 14 18.35 0 511.04 231.95 51235 +2001 224 23 12 19.98 0 1084.29 507.23 51057 +2001 225 28 10 23.05 0 1627.14 448.17 50876 +2001 226 30 13 25.32 0 1731.58 451.55 50694 +2001 227 31 15 26.6 0 1777.09 432.9 50510 +2001 228 32 14 27.05 0 1977.1 447.86 50325 +2001 229 32 15 27.32 0 1928.51 434.22 50138 +2001 230 33 16 28.32 0 2033.89 426.76 49951 +2001 231 33 15 28.05 0 2085.65 433.26 49761 +2001 232 33 17 28.6 0 1976.48 399.52 49571 +2001 233 27 18 24.52 0 1015.2 270.56 49380 +2001 234 27 15 23.7 0 1225.04 339.55 49187 +2001 235 28 19 25.52 0 1070.83 258.89 48993 +2001 236 27 17 24.25 0 1091.15 287.29 48798 +2001 237 31 15 26.6 0 1777.09 390.08 48603 +2001 238 33 15 28.05 0 2085.65 406.17 48406 +2001 239 34 15 28.77 0 2248.67 411.07 48208 +2001 240 24 16 21.8 0 793.41 231.93 48010 +2001 241 25 9 20.6 0 1277.93 398.16 47811 +2001 242 24 7 19.32 0 1157.86 407.91 47611 +2001 243 21 10 17.98 0.33 505 137.44 47410 +2001 244 20 13 18.07 0 513.57 258.42 47209 +2001 245 22 12 19.25 0.84 726.15 186.79 47007 +2001 246 26 9 21.32 0 1256.15 373.58 46805 +2001 247 26 11 21.88 1.98 907.69 304.8 46601 +2001 248 14 13 13.73 1.46 152.31 79.81 46398 +2001 249 16 13 15.18 0.35 448.46 34.43 46194 +2001 250 22 12 19.25 0.03 840 269.52 45989 +2001 251 19 11 16.8 2.01 401.54 119.53 45784 +2001 252 14 10 12.9 0.63 173.85 179.93 45579 +2001 253 20 6 16.15 0 623.85 354.72 45373 +2001 254 17 9 14.8 0 601.54 190.34 45167 +2001 255 20 6 16.15 0.06 633.85 248.22 44961 +2001 256 22 7 17.88 0 783.33 323.52 44755 +2001 257 22 11 18.98 3.45 722.5 152.28 44548 +2001 258 14 10 12.9 0.4 100 68.09 44341 +2001 259 18 10 15.8 0.91 365 187.69 44134 +2001 260 12 9 11.18 1.65 125.83 87.27 43927 +2001 261 17 8 14.53 0.06 441.67 244.61 43719 +2001 262 17 5 13.7 0 310.83 238.25 43512 +2001 263 22 5 17.32 0 846.67 375.47 43304 +2001 264 20 7 16.43 0 740 323.5 43097 +2001 265 20 8 16.7 0.19 609.17 291.46 42890 +2001 266 15 12 14.18 1.63 82.5 72.18 42682 +2001 267 25 14 21.98 0.61 512.5 263.89 42475 +2001 268 17 14 16.18 0.77 275 145.54 42268 +2001 269 17 12 15.63 0.04 407.5 139.85 42060 +2001 270 20 6 16.15 0 683.33 356.26 41854 +2001 271 23 8 18.88 0 799.17 354.81 41647 +2001 272 20 8 16.7 0.06 327.5 255 41440 +2001 273 18 9 15.53 0.07 197.5 137.52 41234 +2001 274 22 11 18.98 0 310.83 262.96 41028 +2001 275 24 14 21.25 0 721.82 319.12 40822 +2001 276 26 10 21.6 0 892.73 327.22 40617 +2001 277 22 9 18.43 0.27 593.64 288.51 40412 +2001 278 20 10 17.25 0 450 212.8 40208 +2001 279 22 7 17.88 0 638.18 294.37 40003 +2001 280 24 9 19.88 0 591.82 259.85 39800 +2001 281 26 12 22.15 0 990 297.35 39597 +2001 282 22 10 18.7 0 616.36 252.14 39394 +2001 283 22 10 18.7 0 385.45 167.07 39192 +2001 284 23 8 18.88 0 650.91 279.04 38991 +2001 285 23 7 18.6 0 712.73 304.47 38790 +2001 286 23 4 17.77 0 561.82 303.59 38590 +2001 287 21 6 16.88 0 478.18 280.26 38391 +2001 288 21 6 16.88 0 505.45 287.16 38193 +2001 289 21 4 16.32 0 519.09 249.89 37995 +2001 290 15 8 13.07 0.02 120.91 139.59 37799 +2001 291 13 8 11.63 0.01 50 71.26 37603 +2001 292 13 12 12.73 0 39.09 29.32 37408 +2001 293 13 12 12.73 0 78.18 38.24 37214 +2001 294 23 12 19.98 0.31 768.18 227.69 37022 +2001 295 19 11 16.8 0.02 518.18 232.45 36830 +2001 296 18 6 14.7 0 635.45 284.12 36640 +2001 297 12 9 11.18 0.24 168.18 73.62 36451 +2001 298 11 9 10.45 0.01 79.09 62.12 36263 +2001 299 11 8 10.18 0 229.09 170.98 36076 +2001 300 11 0 7.97 0 263 213.24 35891 +2001 301 13 6 11.07 0 194 144.03 35707 +2001 302 12 9 11.18 0 123 66.9 35525 +2001 303 17 10 15.07 0 308 128.52 35345 +2001 304 25 11 21.15 0 1267 245.41 35166 +2001 305 14 10 12.9 0 810 164.86 34988 +2001 306 11 5 9.35 0 564 250.62 34813 +2001 307 12 0 8.7 0 323 244.77 34639 +2001 308 12 0 8.7 0 498 246.27 34468 +2001 309 13 -2 8.88 0 438.89 213.81 34298 +2001 310 10 6 8.9 0 286.67 69.06 34130 +2001 311 11 5 9.35 0 260 138.13 33964 +2001 312 11 6 9.63 1.24 446.67 77.63 33801 +2001 313 6 5 5.72 0.31 173.33 58.76 33640 +2001 314 6 2 4.9 0 277.78 132.43 33481 +2001 315 5 2 4.17 0.05 113.33 61.73 33325 +2001 316 4 3 3.73 0.66 37.78 30.57 33171 +2001 317 6 0 4.35 0.86 36.67 35.89 33019 +2001 318 5 2 4.17 0 301.11 115.76 32871 +2001 319 6 0 4.35 0 261.11 209.26 32725 +2001 320 9 -7 4.6 0 293.33 232.17 32582 +2001 321 8 -2 5.25 0 278.89 220.34 32441 +2001 322 0 -6 -1.65 0 20 58.73 32304 +2001 323 4 -1 2.63 0 58.89 42.47 32170 +2001 324 8 2 6.35 0 341.11 158.77 32039 +2001 325 11 -2 7.43 0 450 202.77 31911 +2001 326 10 -5 5.88 0.03 284.44 210.18 31786 +2001 327 5 1 3.9 0 258.89 120.16 31665 +2001 328 6 -1 4.08 0 336.67 103.81 31547 +2001 329 6 1 4.63 0 372.22 170.46 31433 +2001 330 4 -6 1.25 0.01 147.78 124.06 31322 +2001 331 3 0 2.17 0.08 36.67 36.5 31215 +2001 332 3 1 2.45 0 36.67 58 31112 +2001 333 9 -1 6.25 0.05 173.33 143.88 31012 +2001 334 3 2 2.73 0.04 31.11 29.33 30917 +2001 335 4 -4 1.8 0 140 188.03 30825 +2001 336 -3 -7 -4.1 0 20 58.09 30738 +2001 337 -1 -4 -1.83 0 20 30.12 30654 +2001 338 0 -3 -0.82 0 15.56 16.3 30575 +2001 339 2 0 1.45 0 24.44 64.99 30500 +2001 340 3 0 2.17 0.21 43.33 43.2 30430 +2001 341 4 -1 2.63 0 114.44 65.36 30363 +2001 342 0 -3 -0.82 0 131.11 150.82 30301 +2001 343 -1 -7 -2.65 0 124.44 188.93 30244 +2001 344 2 -12 -1.85 0.01 148.89 216.22 30191 +2001 345 0 -3 -0.82 0.16 30 39.35 30143 +2001 346 1 -2 0.18 0.45 21.11 43.4 30099 +2001 347 -7 -8 -7.28 0 87.5 135.31 30060 +2001 348 -7 -13 -8.65 0 83.75 154.38 30025 +2001 349 -3 -18 -7.13 0 71.25 169.94 29995 +2001 350 -2 -7 -3.38 0 108.75 118.79 29970 +2001 351 -1 -6 -2.38 0.15 117.5 54.66 29950 +2001 352 2 -3 0.63 0.01 86.25 71.03 29934 +2001 353 3 -12 -1.13 0 132.5 189.18 29924 +2001 354 6 -13 0.78 0 195 191.45 29918 +2001 355 -1 -9 -3.2 0 153.75 161.65 29916 +2001 356 1 -5 -0.65 0.41 162.5 114.99 29920 +2001 357 1 -3 -0.1 0 58.75 67.19 29928 +2001 358 -2 -18 -6.4 0 140 200.59 29941 +2001 359 -2 -12 -4.75 0 191.25 95.4 29959 +2001 360 -4 -9 -5.38 0.13 117.5 72.04 29982 +2001 361 2 -6 -0.2 0 207.5 106.45 30009 +2001 362 1 -10 -2.02 0 186.25 93.95 30042 +2001 363 6 -1 4.08 0 330 94.89 30078 +2001 364 5 3 4.45 0.05 348.75 49.15 30120 +2001 365 -2 -5 -2.83 0.01 226.25 101.61 30166 +2002 1 2 -8 -0.75 0 265 114.78 30217 +2002 2 7 -6 3.43 0 473.75 106.37 30272 +2002 3 -2 -5 -2.83 0 231.25 179.31 30331 +2002 4 -3 -15 -6.3 0 126.25 194.04 30396 +2002 5 2 -13 -2.13 0 177.5 142.48 30464 +2002 6 8 -6 4.15 0 376.25 181.44 30537 +2002 7 7 -5 3.7 0 250 147.8 30614 +2002 8 3 -4 1.08 0 120 123.47 30695 +2002 9 4 -3 2.08 0 151.25 175.89 30781 +2002 10 -2 -6 -3.1 0 20 25.97 30870 +2002 11 -4 -4 -4 0 20 20.24 30964 +2002 12 -2 -6 -3.1 0 20 49.19 31061 +2002 13 -3 -6 -3.83 0.12 20 34.18 31162 +2002 14 -3 -4.5 -3.41 0.05 28.89 39.59 31268 +2002 15 -4 -6 -4.55 0.01 50 34.82 31376 +2002 16 -5 -5 -5 0 41.11 21.13 31489 +2002 17 -3 -5 -3.55 0 21.11 26.67 31605 +2002 18 -1 -4 -1.83 0 65.56 68.52 31724 +2002 19 1 -9 -1.75 0.01 93 161.72 31847 +2002 20 9 -4 5.43 0 197 137.2 31974 +2002 21 6 -1 4.08 0 254 28.77 32103 +2002 22 11 -1 7.7 0 342 193.52 32236 +2002 23 10 -2 6.7 0 283 198.85 32372 +2002 24 9 6 8.18 0.02 352 61.3 32510 +2002 25 10 2 7.8 0 229 158.87 32652 +2002 26 8 1 6.08 0 131 58.47 32797 +2002 27 10 0 7.25 0 400 60.34 32944 +2002 28 18 6 14.7 0 610 174.94 33094 +2002 29 20 4 15.6 0 1095 172.17 33247 +2002 30 15 2 11.43 0 614 168.05 33402 +2002 31 13 3 10.25 0 498 143.58 33559 +2002 32 13 1 9.7 0 416 164.63 33719 +2002 33 15 1 11.15 0 449 218.62 33882 +2002 34 13 2 9.97 0 368 221.71 34046 +2002 35 2 -1 1.18 0 12 78.34 34213 +2002 36 14 -2 9.6 0 367 245.81 34382 +2002 37 12 1 8.97 0.11 405 172.1 34552 +2002 38 4 2 3.45 0.56 25 38.83 34725 +2002 39 9 3 7.35 0 93 111.75 34900 +2002 40 11 0 7.97 0.05 121 123.74 35076 +2002 41 11 4 9.07 0.1 353 114.08 35254 +2002 42 14 1 10.43 0 565 216.26 35434 +2002 43 15 3 11.7 0 669 177.58 35615 +2002 44 19 3 14.6 0 491 249.39 35798 +2002 45 5 5 5 0 174 38.47 35983 +2002 46 4 -1 2.63 0 329 192.98 36169 +2002 47 3 -3 1.35 0.07 266 125.88 36356 +2002 48 6 0 4.35 1.18 144 134.16 36544 +2002 49 7 2 5.63 0.31 45 84.7 36734 +2002 50 9 2 7.08 0 216 206.36 36925 +2002 51 9 -1 6.25 0 332 81.45 37117 +2002 52 8 6 7.45 0.11 274 94.06 37310 +2002 53 4 -4 1.8 0 323.64 304.43 37505 +2002 54 9 -2 5.97 0.01 419.09 160.29 37700 +2002 55 10 -1 6.97 0 552.73 228.27 37896 +2002 56 12 -3 7.88 0 600 146.53 38093 +2002 57 14 1 10.43 0 685.45 261.68 38291 +2002 58 14 6 11.8 0 591.82 187.06 38490 +2002 59 7 6 6.72 0.79 66.36 26.56 38689 +2002 60 7 3 5.9 0.08 131.82 119.14 38890 +2002 61 7 2 5.63 0.05 73.33 69.33 39091 +2002 62 4 3 3.73 0.04 251.67 61.1 39292 +2002 63 10 -1 6.97 0 311.67 300.97 39495 +2002 64 13 -1 9.15 0 538.33 295.76 39697 +2002 65 18 3 13.88 0 714.17 208.95 39901 +2002 66 17 9 14.8 0 855.83 313.58 40105 +2002 67 15 5 12.25 0 820 331.22 40309 +2002 68 14 0 10.15 0 775.83 360.46 40514 +2002 69 15 0 10.88 0 759.17 269.55 40719 +2002 70 15 -2 10.32 0 789.17 342.18 40924 +2002 71 15 -2 10.32 0 754.17 344.2 41130 +2002 72 17 -1 12.05 0 787.5 293.46 41336 +2002 73 20 2 15.05 0 1173.33 335.33 41543 +2002 74 17 6 13.98 0 624.17 310.42 41749 +2002 75 14 4 11.25 0 317.5 256.57 41956 +2002 76 17 2 12.88 0 465 314.79 42163 +2002 77 16 1 11.88 0 522.5 329.22 42370 +2002 78 16 3 12.43 0 379.17 130.91 42578 +2002 79 16 7 13.53 0.17 410 154.28 42785 +2002 80 16 7 13.53 0.2 208.33 103.71 42992 +2002 81 16 6 13.25 0.12 459.17 255.26 43200 +2002 82 7 -2 4.53 0.07 310 324.49 43407 +2002 83 6 0 4.35 0.03 215.83 177.29 43615 +2002 84 6 1 4.63 0 285.83 176.13 43822 +2002 85 7 0 5.08 0 292.5 130.72 44029 +2002 86 8 1 6.08 0 410 327.19 44236 +2002 87 11 -3 7.15 0 480.83 400.58 44443 +2002 88 15 -3 10.05 0 696.67 393.39 44650 +2002 89 19 0 13.78 0 1093.33 416.05 44857 +2002 90 19 1 14.05 0 1130 390.66 45063 +2002 91 20 3 15.32 0 1139.17 369.66 45270 +2002 92 19 3 14.6 0 893.85 391.12 45475 +2002 93 16 5 12.98 0 755.38 333.08 45681 +2002 94 13 2 9.97 0.03 574.62 394.88 45886 +2002 95 12 4 9.8 0 601.54 352.93 46091 +2002 96 9 -2 5.97 0 474.29 309.95 46295 +2002 97 10 -3 6.43 0 439.29 367.07 46499 +2002 98 12 -3 7.88 0 652.86 312.4 46702 +2002 99 10 3 8.07 0 611.43 191.47 46905 +2002 100 4 4 4 0.26 97.86 30.33 47107 +2002 101 7 3 5.9 0.04 51.43 58.44 47309 +2002 102 7 5 6.45 1.67 44.29 35.88 47510 +2002 103 12 6 10.35 0.44 48.57 106.97 47710 +2002 104 15 8 13.07 0.09 229.29 135.96 47910 +2002 105 9 7 8.45 0.02 292.14 113.57 48108 +2002 106 13 6 11.07 0 455 198.52 48306 +2002 107 14 6 11.8 0.43 287.86 169.32 48504 +2002 108 13 7 11.35 0.31 341.45 105.51 48700 +2002 109 14 8 12.35 0.02 315.71 265.97 48895 +2002 110 12 9 11.18 0.29 210.71 172.07 49089 +2002 111 18 7 14.98 0 491.43 372.6 49282 +2002 112 19 9 16.25 0 601.43 317.06 49475 +2002 113 19 7 15.7 0.69 875 383.1 49666 +2002 114 16 9 14.07 0.21 300 195.51 49855 +2002 115 17 5 13.7 0 720 403.51 50044 +2002 116 21 7 17.15 0.23 780.71 332.07 50231 +2002 117 11 10 10.73 1.23 200.71 82.83 50417 +2002 118 17 2 12.88 0 673.57 462.69 50601 +2002 119 20 6 16.15 0.29 1015 414.29 50784 +2002 120 18 8 15.25 0 860.71 345.45 50966 +2002 121 24 6 19.05 0 1153.57 463.89 51145 +2002 122 24 12 20.7 0 1494.29 463.64 51324 +2002 123 25 11 21.15 0 1700 393.73 51500 +2002 124 26 11 21.88 0.09 1696.43 389.5 51674 +2002 125 20 11 17.52 0.02 374.67 230.42 51847 +2002 126 21 9 17.7 0 584.67 376.21 52018 +2002 127 22 7 17.88 0 786.67 366.15 52187 +2002 128 23 8 18.88 0 1150.67 414.69 52353 +2002 129 18 10 15.8 0 795.33 269.29 52518 +2002 130 23 11 19.7 0 926 390.72 52680 +2002 131 24 10 20.15 0 989.33 411.14 52840 +2002 132 25 9 20.6 0.65 941.33 390.41 52998 +2002 133 23 12 19.98 0 648 340.95 53153 +2002 134 24 9 19.88 0.76 648 384.58 53306 +2002 135 24 10 20.15 0 1176 465.72 53456 +2002 136 25 9 20.6 0 1128.67 465.28 53603 +2002 137 27 11 22.6 0 1322.67 462.47 53748 +2002 138 27 13 23.15 0 1336.92 439.6 53889 +2002 139 21 13 18.8 0 672.07 302.79 54028 +2002 140 20 13 18.07 0 664 384.58 54164 +2002 141 22 11 18.98 0 772.67 336.93 54297 +2002 142 24 12 20.7 0 765.63 344.87 54426 +2002 143 26 15 22.98 0 1286.88 403.93 54552 +2002 144 26 15 22.98 0.07 1086.25 332.37 54675 +2002 145 23 13 20.25 1.67 1075 327.32 54795 +2002 146 17 13 15.9 0 280.63 147.41 54911 +2002 147 23 12 19.98 0.17 588.75 319.25 55023 +2002 148 21 11 18.25 0.01 513.75 276.98 55132 +2002 149 23 12 19.98 0 1220.63 388.84 55237 +2002 150 23 10 19.43 0 1366.88 510.84 55339 +2002 151 24 9 19.88 0 1365.62 434.72 55436 +2002 152 23 11 19.7 0 1093.75 457.77 55530 +2002 153 21 12 18.52 0 1036.88 421.3 55619 +2002 154 24 7 19.32 0 1191.88 421.9 55705 +2002 155 26 11 21.88 0 1476.25 473.88 55786 +2002 156 23 14 20.52 0.04 708.12 237.84 55863 +2002 157 24 16 21.8 0.18 710 298.55 55936 +2002 158 17 12 15.63 0.32 456.88 201.48 56004 +2002 159 24 13 20.98 0 713.13 284.43 56068 +2002 160 21 12 18.52 0.45 492.5 222 56128 +2002 161 19 13 17.35 0.57 231.25 113.49 56183 +2002 162 25 12 21.43 0 1323.12 505.99 56234 +2002 163 25 9 20.6 0 1313.12 478.97 56280 +2002 164 28 12 23.6 0 1492.5 471.26 56321 +2002 165 31 15 26.6 0 1777.09 474.61 56358 +2002 166 32 16 27.6 0 1874.54 469.96 56390 +2002 167 31 16 26.88 0 1720.98 460.12 56418 +2002 168 29 15 25.15 0 1490.67 452.15 56440 +2002 169 32 17 27.88 0 1814.9 452.1 56458 +2002 170 32 17 27.88 0 2066.88 482.92 56472 +2002 171 32 17 27.88 0 2113.75 499.01 56480 +2002 172 33 17 28.6 0 2115.63 471.77 56484 +2002 173 33 20 29.43 0 1776.92 574.43 56482 +2002 174 34 18 29.6 0 2481.25 470.59 56476 +2002 175 33 19 29.15 0.35 1893.75 426.99 56466 +2002 176 23 15 20.8 0.09 1066.25 245.84 56450 +2002 177 26 11 21.88 0 1572.5 515.91 56430 +2002 178 28 12 23.6 0 1643.13 514.41 56405 +2002 179 23 15 20.8 1.72 379.37 114.93 56375 +2002 180 23 9 19.15 0 1073.75 338.22 56341 +2002 181 23 10 19.43 0 1169.38 475.65 56301 +2002 182 27 11 22.6 0 1433.75 486.46 56258 +2002 183 29 16 25.43 0 1594.38 412.7 56209 +2002 184 30 17 26.43 0 1560 410.77 56156 +2002 185 21 18 20.18 1.53 636.88 180.54 56099 +2002 186 24 9 19.88 0 1217.5 495.69 56037 +2002 187 28 11 23.32 0.22 1368.75 457.07 55971 +2002 188 26 15 22.98 0.02 863.75 275.76 55900 +2002 189 29 13 24.6 0 1677.5 487.02 55825 +2002 190 31 14 26.32 0 1727.5 440.24 55746 +2002 191 32 17 27.88 0 1868.75 418.18 55663 +2002 192 30 19 26.98 0 1760 480.75 55575 +2002 193 29 15 25.15 0 1816.25 390.76 55484 +2002 194 31 18 27.43 0 1311.87 342.56 55388 +2002 195 29 16 25.43 1.44 1181.25 451.6 55289 +2002 196 29 17 25.7 1.74 898.75 334.42 55186 +2002 197 28 19 25.52 0 876.88 315.83 55079 +2002 198 27 15 23.7 0 1184.37 385.12 54968 +2002 199 24 16 21.8 0.69 580 142.24 54854 +2002 200 25 15 22.25 0 1052.5 344.37 54736 +2002 201 28 14 24.15 0 1435.63 420.31 54615 +2002 202 31 13 26.05 0.12 1519.38 464.22 54490 +2002 203 25 15 22.25 0.35 500.62 234.65 54362 +2002 204 26 12 22.15 0 1095 468.66 54231 +2002 205 29 14 24.88 0.87 886.25 339.63 54097 +2002 206 24 16 21.8 0 821.25 371.79 53960 +2002 207 23 11 19.7 0 1028.75 329.66 53819 +2002 208 26 14 22.7 0 1467.5 470.2 53676 +2002 209 28 15 24.43 0 1310 333.69 53530 +2002 210 31 17 27.15 0.01 1187.14 284.87 53382 +2002 211 31 16 26.88 0.44 1619.29 402.31 53230 +2002 212 24 17 22.07 0.01 566.43 239.26 53076 +2002 213 27 16 23.98 1.1 395 236.82 52920 +2002 214 28 16 24.7 0.39 1000 333.12 52761 +2002 215 29 17 25.7 0 1412.86 389.12 52600 +2002 216 26 17 23.52 1.38 705.71 293.32 52437 +2002 217 28 16 24.7 0 1167.86 381.38 52271 +2002 218 23 17 21.35 0.95 436.43 148.42 52103 +2002 219 23 16 21.07 0.85 267.14 127.68 51934 +2002 220 24 15 21.52 0 635.71 299 51762 +2002 221 26 13 22.43 0 927.14 380.27 51588 +2002 222 25 14 21.98 0 807.86 409.56 51413 +2002 223 19 16 18.18 1.91 177.86 89.33 51235 +2002 224 20 13 18.07 0.33 412.14 159.62 51057 +2002 225 24 14 21.25 0.1 910.71 200.9 50876 +2002 226 23 14 20.52 0 753.57 166.36 50694 +2002 227 24 15 21.52 0.03 946.43 314.58 50510 +2002 228 26 16 23.25 0 909.29 350.52 50325 +2002 229 28 16 24.7 0 1140.71 407.89 50138 +2002 230 27 15 23.7 0.02 1014.29 346.09 49951 +2002 231 28 15 24.43 0 1200 351.98 49761 +2002 232 27 15 23.7 0 985 349.52 49571 +2002 233 23 14 20.52 1.01 558.57 270.22 49380 +2002 234 23 15 20.8 0.06 431.43 249.61 49187 +2002 235 26 14 22.7 0 835.71 307.28 48993 +2002 236 28 14 24.15 0 944.29 407.58 48798 +2002 237 28 14 24.15 0 1152.14 393.74 48603 +2002 238 29 15 25.15 0 1272.14 383.8 48406 +2002 239 24 15 21.52 0 491.43 250.49 48208 +2002 240 25 15 22.25 0.54 515.71 247.65 48010 +2002 241 24 15 21.52 0 709.29 239.35 47811 +2002 242 28 14 24.15 0 1117.14 386.44 47611 +2002 243 28 14 24.15 0.01 1324.29 368.38 47410 +2002 244 25 15 22.25 0.1 719.29 237.62 47209 +2002 245 23 14 20.52 0 902.31 312.77 47007 +2002 246 25 12 21.43 0 1055.38 376.73 46805 +2002 247 27 12 22.88 0 1004.62 339.38 46601 +2002 248 26 12 22.15 1.05 762.31 284.95 46398 +2002 249 25 14 21.98 0 905.38 365.45 46194 +2002 250 25 11 21.15 0 912.31 317.42 45989 +2002 251 25 12 21.43 0.87 1116.15 339.74 45784 +2002 252 26 13 22.43 0 965.38 358.28 45579 +2002 253 26 12 22.15 1.87 496.92 221.89 45373 +2002 254 22 13 19.52 0 664.62 233.99 45167 +2002 255 18 10 15.8 0 909.23 362.46 44961 +2002 256 19 4 14.88 0 812.5 291.16 44755 +2002 257 21 6 16.88 0 999.17 362.51 44548 +2002 258 17 9 14.8 0.51 526.67 142.35 44341 +2002 259 18 7 14.98 0 736.67 291.19 44134 +2002 260 21 6 16.88 0 845.83 294.88 43927 +2002 261 23 4 17.77 0 1040.83 379.96 43719 +2002 262 23 8 18.88 0.02 764.17 336.2 43512 +2002 263 22 14 19.8 0.28 437.5 231.75 43304 +2002 264 20 11 17.52 0.53 704.17 267.06 43097 +2002 265 13 11 12.45 0.61 104.17 83.15 42890 +2002 266 13 10 12.18 1.48 115 89.48 42682 +2002 267 9 9 9 0.09 55.83 41.99 42475 +2002 268 9 6 8.18 0.3 114.17 80.57 42268 +2002 269 14 4 11.25 0 405 252.5 42060 +2002 270 17 7 14.25 0 493.33 207.18 41854 +2002 271 11 4 9.07 0.01 349.17 99.13 41647 +2002 272 15 8 13.07 0 660.83 345.88 41440 +2002 273 17 3 13.15 0 618.33 349.05 41234 +2002 274 19 3 14.6 0 626.67 330.39 41028 +2002 275 18 4 14.15 0 640.91 278.26 40822 +2002 276 18 6 14.7 0 523.64 278.93 40617 +2002 277 21 9 17.7 0.42 401.82 159.37 40412 +2002 278 19 8 15.98 0 696.36 300.34 40208 +2002 279 14 5 11.53 0.07 377.27 159.11 40003 +2002 280 13 7 11.35 0 562.73 267.16 39800 +2002 281 17 0 12.32 0 643.64 337.17 39597 +2002 282 9 2 7.08 0 222.73 79.18 39394 +2002 283 10 7 9.18 0.92 149.09 72.38 39192 +2002 284 10 9 9.72 1.78 30 35.46 38991 +2002 285 7 7 7 1.73 51.82 36.46 38790 +2002 286 8 3 6.63 0 170 137.79 38590 +2002 287 14 6 11.8 0 311.82 231.87 38391 +2002 288 17 6 13.98 0 311.82 218.26 38193 +2002 289 21 7 17.15 0 421.82 218.84 37995 +2002 290 20 16 18.9 2.35 901.82 178.84 37799 +2002 291 12 9 11.18 0.6 129.09 130.64 37603 +2002 292 13 4 10.53 0.08 228.18 215.27 37408 +2002 293 14 2 10.7 0 447.27 255.45 37214 +2002 294 17 2 12.88 0 507.27 192.09 37022 +2002 295 18 12 16.35 0.1 410 125.89 36830 +2002 296 22 11 18.98 0.65 846.36 258.13 36640 +2002 297 14 8 12.35 0 447.27 210.08 36451 +2002 298 15 3 11.7 0.02 350.91 257.06 36263 +2002 299 22 10 18.7 0 925 257.15 36076 +2002 300 16 5 12.98 0 454 160.86 35891 +2002 301 15 9 13.35 0 1029 277.23 35707 +2002 302 15 3 11.7 0 763 242.12 35525 +2002 303 17 3 13.15 0 428 63.75 35345 +2002 304 7 6 6.72 0.13 59 39.89 35166 +2002 305 11 6 9.63 0.01 168 119.35 34988 +2002 306 11 7 9.9 0.02 70 54.54 34813 +2002 307 7 5 6.45 0.46 179 71.97 34639 +2002 308 7 5 6.45 0.51 34 43.47 34468 +2002 309 4 2 3.45 0.04 188.89 108.27 34298 +2002 310 3 -2 1.63 0 235.56 125.2 34130 +2002 311 4 -1 2.63 0.02 63.33 58.6 33964 +2002 312 7 -2 4.53 0 188.89 89.19 33801 +2002 313 7 -1 4.8 0.02 217.78 106.06 33640 +2002 314 11 1 8.25 0 465.56 236.91 33481 +2002 315 14 -1 9.88 0 320 80.78 33325 +2002 316 15 4 11.98 0 557.78 205.91 33171 +2002 317 14 4 11.25 0 241.11 124.42 33019 +2002 318 18 11 16.07 0 673.33 92.88 32871 +2002 319 22 11 18.98 0 1120 166.82 32725 +2002 320 21 13 18.8 0.08 1054.44 87.75 32582 +2002 321 18 12 16.35 0.35 716.67 136.6 32441 +2002 322 14 11 13.18 0.01 200 118.76 32304 +2002 323 15 7 12.8 0.04 437.78 176.94 32170 +2002 324 13 4 10.53 0 327.78 185.5 32039 +2002 325 15 2 11.43 0 448.89 166.09 31911 +2002 326 11 8 10.18 1.24 137.78 54.64 31786 +2002 327 15 5 12.25 0 304.44 165.11 31665 +2002 328 14 2 10.7 0 381.11 150.53 31547 +2002 329 16 5 12.98 0 395.56 120.28 31433 +2002 330 15 8 13.07 0 301.11 111.17 31322 +2002 331 8 5 7.17 0 57.78 81.82 31215 +2002 332 8 7 7.72 0.01 30 39.96 31112 +2002 333 7 4 6.17 0.58 22.22 40.73 31012 +2002 334 10 6 8.9 0 85.56 83.32 30917 +2002 335 8 2 6.35 0.04 76.67 90.75 30825 +2002 336 4 1 3.17 0.89 23.33 15.48 30738 +2002 337 5 1 3.9 0.4 22.22 21.07 30654 +2002 338 6 5 5.72 0.95 20 12.67 30575 +2002 339 6 5 5.72 1.37 28.89 15.21 30500 +2002 340 2 2 2 0.46 38.89 19.55 30430 +2002 341 1 1 1 0.3 25.56 12.81 30363 +2002 342 -2 -2 -2 0 104.44 36.39 30301 +2002 343 -5 -6 -5.28 0.02 84.44 76.38 30244 +2002 344 -3 -8 -4.38 0 134.44 164.75 30191 +2002 345 -4 -7 -4.83 0 97.78 80.7 30143 +2002 346 -4 -5 -4.28 0.05 55.56 47.24 30099 +2002 347 -3 -5 -3.55 0 45 32.04 30060 +2002 348 -3 -4 -3.27 0.03 27.5 32.94 30025 +2002 349 -2 -3 -2.27 0.35 20 17.83 29995 +2002 350 -2 -3 -2.27 0 20 45.03 29970 +2002 351 -1 -3 -1.55 0.1 18.75 66.17 29950 +2002 352 2 -2 0.9 0.01 73.75 80.92 29934 +2002 353 2 -5 0.07 0.01 192.5 108.7 29924 +2002 354 1 -5 -0.65 0 165 183.67 29918 +2002 355 6 -5 2.98 0 137.5 110.95 29916 +2002 356 2 -2 0.9 0 48.75 62.01 29920 +2002 357 2 -1 1.18 0.02 28.75 54.81 29928 +2002 358 -1 -1 -1 0.02 177.5 34.8 29941 +2002 359 -3 -6 -3.83 0 220 48.17 29959 +2002 360 -3 -5 -3.55 0 43.75 62.09 29982 +2002 361 0 -3 -0.82 0 21.25 42.27 30009 +2002 362 10 -1 6.97 0.46 275 49.73 30042 +2002 363 6 1 4.63 0 20 76.4 30078 +2002 364 10 2 7.8 0.01 197.5 69.22 30120 +2002 365 8 5 7.17 0.53 56.25 25.68 30166 +2003 1 -1 -6 -2.38 0 172.5 123.12 30217 +2003 2 4 -4 1.8 0 52.5 77.75 30272 +2003 3 15 1 11.15 0 395 104.79 30331 +2003 4 9 1 6.8 0.43 205 94.3 30396 +2003 5 0 0 0 0.11 122.5 60.1 30464 +2003 6 -3 -6 -3.83 0.81 103.75 68.63 30537 +2003 7 -7 -7 -7 0.7 30 33.51 30614 +2003 8 -2 -12 -4.75 0.14 113.75 187.97 30695 +2003 9 -9 -14 -10.38 0.69 36.25 62.64 30781 +2003 10 -6 -11 -7.38 0.21 86.25 94.39 30870 +2003 11 -3 -7 -4.1 0 177.78 180.14 30964 +2003 12 -4 -17 -7.57 0 101.11 241.97 31061 +2003 13 -1 -13 -4.3 0 140 170.96 31162 +2003 14 3 -5 0.8 0 185.56 88.63 31268 +2003 15 9 -2 5.97 0 220 204.75 31376 +2003 16 7 -7 3.15 0 68.89 167.07 31489 +2003 17 6 -5 2.98 0 182.22 215.29 31605 +2003 18 -1 -6 -2.38 0 20 89.75 31724 +2003 19 -1 -7 -2.65 0 22 93.48 31847 +2003 20 0 -8 -2.2 0 20 97.02 31974 +2003 21 -1 -7 -2.65 0.35 20 82.79 32103 +2003 22 1 -1 0.45 0.44 21 45.36 32236 +2003 23 10 -1 6.97 0 10 169.56 32372 +2003 24 5 -3 2.8 0 94 146.12 32510 +2003 25 4 1 3.17 0 107 91.03 32652 +2003 26 4 -2 2.35 0 66 104.04 32797 +2003 27 3 -3 1.35 0.03 154 145.1 32944 +2003 28 6 -1 4.08 0 152 79.7 33094 +2003 29 6 -2 3.8 0 212 159.37 33247 +2003 30 6 -4 3.25 0 140 217.51 33402 +2003 31 0 -2 -0.55 0.23 27 56.45 33559 +2003 32 2 -3 0.63 0 164 206.07 33719 +2003 33 0 -11 -3.02 0 151 261.66 33882 +2003 34 4 -11 -0.13 0.14 257 163.62 34046 +2003 35 0 -4 -1.1 0.8 23 33.25 34213 +2003 36 5 -2 3.08 0 288 149.63 34382 +2003 37 3 -2 1.63 0 327 195.11 34552 +2003 38 5 -6 1.98 0 254 264.14 34725 +2003 39 -1 -7 -2.65 0.04 74 128.07 34900 +2003 40 1 -8 -1.48 0 138 192.7 35076 +2003 41 1 -3 -0.1 0 112 109.05 35254 +2003 42 -2 -3 -2.27 0.09 75 86.79 35434 +2003 43 0 -6 -1.65 0 111 304.79 35615 +2003 44 -1 -11 -3.75 0 154 290 35798 +2003 45 2 -12 -1.85 0 180 308.94 35983 +2003 46 2 -9 -1.02 0.03 211 252.59 36169 +2003 47 -1 -3 -1.55 0 72 117.6 36356 +2003 48 1 -6 -0.93 0 142 271.3 36544 +2003 49 1 -12 -2.57 0 174 302.06 36734 +2003 50 1 -7 -1.2 0 142 129.37 36925 +2003 51 1 -9 -1.75 0 107 129.05 37117 +2003 52 4 -7 0.98 0 130 150.37 37310 +2003 53 4 -1 2.63 0 308.18 216.12 37505 +2003 54 5 -8 1.43 0 49.09 221.45 37700 +2003 55 10 -11 4.23 0 163.64 277.19 37896 +2003 56 7 -6 3.43 0 307.27 348.32 38093 +2003 57 5 -9 1.15 0 102.73 314.18 38291 +2003 58 10 -6 5.6 0 360 338.5 38490 +2003 59 11 -5 6.6 0 280 266.92 38689 +2003 60 14 -2 9.6 0 549.09 301.17 38890 +2003 61 11 -2 7.43 0.13 405 248.79 39091 +2003 62 6 2 4.9 0.03 75.83 107.78 39292 +2003 63 11 1 8.25 0 171.67 322.86 39495 +2003 64 9 0 6.53 0 125.83 135.28 39697 +2003 65 2 0 1.45 0 136.67 89.9 39901 +2003 66 3 -1 1.9 0 189.17 83.01 40105 +2003 67 10 -2 6.7 0 269.17 298.47 40309 +2003 68 13 0 9.43 0.02 518.33 244.5 40514 +2003 69 16 4 12.7 0 614.17 284.17 40719 +2003 70 18 1 13.32 0 707.5 243.27 40924 +2003 71 18 8 15.25 0.03 662.5 144.7 41130 +2003 72 8 3 6.63 0 429.17 283.74 41336 +2003 73 4 0 2.9 0 190 99.71 41543 +2003 74 5 0 3.63 0 230 262.64 41749 +2003 75 5 1 3.9 0 255 169.72 41956 +2003 76 13 -4 8.32 0 485.83 367.57 42163 +2003 77 10 2 7.8 0 403.33 313.79 42370 +2003 78 14 3 10.98 0 602.5 262.8 42578 +2003 79 12 1 8.97 0 376.67 320.01 42785 +2003 80 8 1 6.08 0 537.5 401.32 42992 +2003 81 5 -6 1.98 0 414.17 401.78 43200 +2003 82 11 -6 6.33 0 640 402.24 43407 +2003 83 18 -3 12.23 0 1169.17 403.9 43615 +2003 84 20 1 14.78 0 1296.67 383.94 43822 +2003 85 20 2 15.05 0 1081.67 340.17 44029 +2003 86 20 2 15.05 0 1316.67 366.36 44236 +2003 87 21 3 16.05 0 1213.33 365.08 44443 +2003 88 20 5 15.88 0 1004.17 281.91 44650 +2003 89 21 5 16.6 0 992.5 284.17 44857 +2003 90 15 9 13.35 0.14 535 193.51 45063 +2003 91 14 -1 9.88 0 805.83 441.61 45270 +2003 92 16 0 11.6 0.85 759.23 233.08 45475 +2003 93 9 4 7.63 0 350.77 89.04 45681 +2003 94 11 3 8.8 0 453.08 301.64 45886 +2003 95 13 -2 8.88 0.09 557.69 259.62 46091 +2003 96 6 -2 3.8 0.02 317.14 374.22 46295 +2003 97 2 -5 0.07 0 267.86 205.69 46499 +2003 98 6 -2 3.8 0 426.43 342.32 46702 +2003 99 10 -5 5.88 0 448.57 250.29 46905 +2003 100 12 -2 8.15 0.8 601.43 180.07 47107 +2003 101 5 1 3.9 0.36 59.29 70.72 47309 +2003 102 6 -1 4.08 0.6 91.43 105.53 47510 +2003 103 16 5 12.98 0 678.57 430.51 47710 +2003 104 15 1 11.15 0 557.14 260.8 47910 +2003 105 16 7 13.53 0 647.14 199.61 48108 +2003 106 19 5 15.15 0 947.86 434.66 48306 +2003 107 17 4 13.43 0 795.71 277.79 48504 +2003 108 17 6 13.98 0 834.29 349.82 48700 +2003 109 16 3 12.43 0 616.43 392.36 48895 +2003 110 19 3 14.6 0 887.86 419.93 49089 +2003 111 19 4 14.88 0 1100 435.1 49282 +2003 112 20 3 15.32 0 1262.14 410.89 49475 +2003 113 19 6 15.43 0.01 781.43 199.99 49666 +2003 114 18 4 14.15 0 771.43 372.45 49855 +2003 115 20 4 15.6 0 1016.43 437.99 50044 +2003 116 24 7 19.32 0.78 1484.29 424.98 50231 +2003 117 15 11 13.9 0.28 300.71 172.71 50417 +2003 118 22 5 17.32 0 815 422.8 50601 +2003 119 25 10 20.88 0 1200.71 417.29 50784 +2003 120 22 10 18.7 0 1122.86 272.22 50966 +2003 121 21 15 19.35 0 962.14 345.91 51145 +2003 122 24 11 20.43 0 1290 373.59 51324 +2003 123 20 17 19.18 0 790 194.27 51500 +2003 124 22 4 17.05 0 1271.43 478.58 51674 +2003 125 25 7 20.05 0 1648 481.04 51847 +2003 126 30 10 24.5 0 2297.33 466.49 52018 +2003 127 30 11 24.77 0 2202 472.81 52187 +2003 128 29 11 24.05 0 1539.33 405.02 52353 +2003 129 29 17 25.7 0 1991 394.25 52518 +2003 130 25 12 21.43 1.1 1154.67 381.41 52680 +2003 131 25 14 21.98 0 676.67 364.71 52840 +2003 132 28 12 23.6 0.45 986.67 433.77 52998 +2003 133 26 13 22.43 0 1194.67 412.17 53153 +2003 134 13 9 11.9 0 567.33 175.59 53306 +2003 135 17 7 14.25 0 852 380.13 53456 +2003 136 18 2 13.6 0 860.67 448.1 53603 +2003 137 21 4 16.32 0 1220 463.17 53748 +2003 138 24 6 19.05 0.01 1232 462.99 53889 +2003 139 27 10 22.32 0 1460.67 409.86 54028 +2003 140 17 13 15.9 0.87 478 82.18 54164 +2003 141 15 9 13.35 0.14 559.33 164.89 54297 +2003 142 18 8 15.25 0 723.13 242.95 54426 +2003 143 23 9 19.15 0 1234.38 486.53 54552 +2003 144 25 9 20.6 0 1268.13 455.91 54675 +2003 145 28 12 23.6 0 1513.75 436.64 54795 +2003 146 28 14 24.15 0.07 1058.13 341.85 54911 +2003 147 25 13 21.7 0 701.88 311.99 55023 +2003 148 27 14 23.43 0 903.13 398.82 55132 +2003 149 26 16 23.25 0 935.63 446.58 55237 +2003 150 27 13 23.15 0 1256.25 484.83 55339 +2003 151 28 13 23.88 0.55 1504.38 451.95 55436 +2003 152 25 15 22.25 1.42 551.88 321.43 55530 +2003 153 25 13 21.7 0 1097.86 385.03 55619 +2003 154 25 13 21.7 0 1097.86 388.85 55705 +2003 155 29 14 24.88 0 1545.43 439.67 55786 +2003 156 31 15 26.6 0 1777.09 450.87 55863 +2003 157 31 15 26.6 0 1777.09 452.4 55936 +2003 158 29 15 25.15 0 1490.67 427.15 56004 +2003 159 31 17 27.15 0 1659.16 417.7 56068 +2003 160 30 17 26.43 0.04 1509.09 300.88 56128 +2003 161 31 18 27.43 0 1591.34 395.69 56183 +2003 162 34 19 29.88 1 2015.8 316.56 56234 +2003 163 32 17 27.88 0 2059.69 452.44 56280 +2003 164 32 20 28.7 0.15 2166.88 416.02 56321 +2003 165 29 18 25.98 0 1376.87 408.62 56358 +2003 166 26 16 23.25 0.01 491.88 299.25 56390 +2003 167 25 15 22.25 0.06 779.38 358.7 56418 +2003 168 27 15 23.7 0 1516.87 372.51 56440 +2003 169 19 16 18.18 0.72 475.62 122.92 56458 +2003 170 25 14 21.98 0 1189.38 384.74 56472 +2003 171 28 14 24.15 0.05 1101.88 299.55 56480 +2003 172 25 12 21.43 0 1299.37 462.07 56484 +2003 173 27 12 22.88 0 1565.63 470.68 56482 +2003 174 33 14 27.77 0.43 1996.25 448.95 56476 +2003 175 31 17 27.15 0.08 1745 319.78 56466 +2003 176 31 16 26.88 0 1723.13 401.02 56450 +2003 177 27 13 23.15 0 1461.25 432.23 56430 +2003 178 25 16 22.52 0 1313.75 378.66 56405 +2003 179 26 16.9 23.5 0 1646.87 350.7 56375 +2003 180 24 17 22.07 0 1110 249.24 56341 +2003 181 32 14 27.05 0 1709.37 461.78 56301 +2003 182 32 18 28.15 0.29 2146.25 458.36 56258 +2003 183 24 13 20.98 0.01 1005 313.53 56209 +2003 184 25 13 21.7 1.02 657.5 283.54 56156 +2003 185 21 13 18.8 0.5 437.5 225.34 56099 +2003 186 24 13 20.98 0 1248.75 356.23 56037 +2003 187 26 14 22.7 0.02 1253.75 293.57 55971 +2003 188 26 11 21.88 0 1293.13 382.91 55900 +2003 189 25 12 21.43 0 1500.63 404.13 55825 +2003 190 26 13 22.43 0.01 1413.12 289.55 55746 +2003 191 25 13 21.7 0.36 1370.63 350.56 55663 +2003 192 27 14 23.43 0 1547.5 493.04 55575 +2003 193 30 13 25.32 0.23 1585 347.52 55484 +2003 194 25 15 22.25 0.02 1282.5 286.59 55388 +2003 195 25 11 21.15 0 1403.75 470.89 55289 +2003 196 28 12 23.6 0 1851.25 460.98 55186 +2003 197 31 15 26.6 0 1887.5 437.22 55079 +2003 198 31 19 27.7 0.96 1788.13 421.89 54968 +2003 199 29 16 25.43 0 1467.5 486.74 54854 +2003 200 29 14 24.88 0 1526.25 492.9 54736 +2003 201 31 14 26.32 0 1905 468.09 54615 +2003 202 34 16 29.05 0 2139.38 446.81 54490 +2003 203 34 19 29.88 1.56 2306.25 432.38 54362 +2003 204 25 19 23.35 0.07 482.5 146.67 54231 +2003 205 29 14 24.88 1.34 1468.75 481.31 54097 +2003 206 25 15 22.25 0 725 324.9 53960 +2003 207 30 14 25.6 0 1450 468.35 53819 +2003 208 32 16 27.6 0 1996.25 459.74 53676 +2003 209 29 19 26.25 0.48 1628.67 432.11 53530 +2003 210 24 16 21.8 0 1002.86 315.75 53382 +2003 211 24 14 21.25 0.03 944.29 151.9 53230 +2003 212 23 16 21.07 0.54 456.43 141.31 53076 +2003 213 28 17 24.98 0.07 951.43 387.06 52920 +2003 214 30 16 26.15 0 1585 425.22 52761 +2003 215 33 17 28.6 0 2283.57 426.78 52600 +2003 216 34 19 29.88 0.63 2056.43 367.44 52437 +2003 217 33 20 29.43 0 2125 399.96 52271 +2003 218 31 19 27.7 0 1913.57 344.41 52103 +2003 219 30 16 26.15 0 2167.14 466.27 51934 +2003 220 33 14 27.77 0 2558.57 456.81 51762 +2003 221 32 16 27.6 0 2528.57 421.97 51588 +2003 222 33 15 28.05 0 2557.14 436.46 51413 +2003 223 30 19 26.98 0 2262.86 468.04 51235 +2003 224 33 12 27.23 0 2481.43 454.46 51057 +2003 225 37 17 31.5 0.43 3055 340.84 50876 +2003 226 36 20 31.6 0.37 2799.29 279.88 50694 +2003 227 30 18 26.7 0.06 1227.86 337.03 50510 +2003 228 29 16 25.43 0.2 1145 386.17 50325 +2003 229 32 16 27.6 0.01 1694.29 409.99 50138 +2003 230 36 17 30.77 0.04 2431.43 378.25 49951 +2003 231 31 16 26.88 0 1917.86 300.53 49761 +2003 232 30 16 26.15 0 1905 358.47 49571 +2003 233 31 16 26.88 0 2172.86 368.16 49380 +2003 234 33 16 28.32 0.06 2430 385.88 49187 +2003 235 33 21 29.7 0 2442.86 328.13 48993 +2003 236 31 18 27.43 0 1932.14 401.7 48798 +2003 237 24 17 22.07 0 1298.57 283.57 48603 +2003 238 29 12 24.32 0 1894.29 411.86 48406 +2003 239 32 14 27.05 0 2441.43 353.88 48208 +2003 240 30 16 26.15 0 1887.5 372.42 48010 +2003 241 32 25 30.07 0.3 2116.43 235.55 47811 +2003 242 25 14 21.98 1.74 749.29 228.1 47611 +2003 243 15 14 14.73 2.15 92.14 58.79 47410 +2003 244 21 7 17.15 0.01 899.29 375.02 47209 +2003 245 20 11 17.52 0 684.62 279.2 47007 +2003 246 18 6 14.7 0 857.69 372.88 46805 +2003 247 22 5 17.32 0 1003.85 285 46601 +2003 248 23 7 18.6 0 974.62 451.24 46398 +2003 249 23 9 19.15 0 764.62 240.53 46194 +2003 250 23 10 19.43 0 1305.38 353.82 45989 +2003 251 22 14 19.8 0.02 1326.92 300.14 45784 +2003 252 17 13 15.9 1.6 412.31 125.55 45579 +2003 253 16 13 15.18 0.9 133.85 76.37 45373 +2003 254 23 9 19.15 0.23 554.62 271.18 45167 +2003 255 19 8 15.98 0.1 562.31 260.81 44961 +2003 256 15 11 13.9 0.05 208.33 59.51 44755 +2003 257 19 10 16.52 0 770.83 408.94 44548 +2003 258 21 7 17.15 0 1015 437.21 44341 +2003 259 22 6 17.6 0 1106.67 416.38 44134 +2003 260 25 8 20.32 0 1310 398.67 43927 +2003 261 26 10 21.6 0 1328.33 388.48 43719 +2003 262 26 10 21.6 0 1308.33 384.37 43512 +2003 263 27 11 22.6 0 1405.83 378.13 43304 +2003 264 28 11 23.32 0 1565.83 376.16 43097 +2003 265 28 11 23.32 0 1615.83 368.41 42890 +2003 266 27 15 23.7 0.56 1694.17 368.15 42682 +2003 267 13 11 12.45 0.03 369.17 112.89 42475 +2003 268 17 5 13.7 0 810 393.62 42268 +2003 269 18 3 13.88 0 892.5 366.86 42060 +2003 270 22 5 17.32 0 931.67 339.19 41854 +2003 271 21 6 16.88 0 845 323.29 41647 +2003 272 14 13 13.73 2.41 109.17 36.27 41440 +2003 273 18 6 14.7 0 583.33 305.77 41234 +2003 274 19 7 15.7 0 622.5 313.34 41028 +2003 275 24 10 20.15 0 851.82 319.45 40822 +2003 276 23 12 19.98 0.83 541.82 295.68 40617 +2003 277 21 14 19.07 3.19 285.45 190.73 40412 +2003 278 19 12 17.07 0.13 498.18 240.06 40208 +2003 279 15 6 12.53 0 673.64 213.92 40003 +2003 280 13 2 9.97 0.15 379.09 103.9 39800 +2003 281 14 6 11.8 0.06 480.91 189.95 39597 +2003 282 15 5 12.25 0 577.27 327.59 39394 +2003 283 19 5 15.15 0.03 599.09 219.22 39192 +2003 284 20 7 16.43 0 671.82 310.12 38991 +2003 285 14 7 12.07 0 444.55 160.49 38790 +2003 286 14 7 12.07 0 500 213.17 38590 +2003 287 11 3 8.8 0 398.18 297.94 38391 +2003 288 12 0 8.7 0 351.82 296.42 38193 +2003 289 10 1 7.53 0 333.64 174.49 37995 +2003 290 10 -2 6.7 0 327.73 262.93 37799 +2003 291 10 0 7.25 0 408.02 232.96 37603 +2003 292 9 3 7.35 0 170.91 200.63 37408 +2003 293 14 1 10.43 0.14 220.91 124.95 37214 +2003 294 16 7 13.53 0.36 180 116.43 37022 +2003 295 6 4 5.45 0 263.64 90.1 36830 +2003 296 6 0 4.35 1.81 166.36 109.76 36640 +2003 297 2 0 1.45 0.02 90.91 187.21 36451 +2003 298 4 -5 1.52 0 96.36 240.26 36263 +2003 299 8 -4 4.7 0 251.82 241.5 36076 +2003 300 9 -1 6.25 0 249 144.26 35891 +2003 301 9 -2 5.97 0 351 225.02 35707 +2003 302 8 -2 5.25 0.41 124 116.57 35525 +2003 303 8 3 6.63 0.18 70 105.8 35345 +2003 304 13 1 9.7 0.06 300 215.93 35166 +2003 305 20 10 17.25 0.94 866 145.53 34988 +2003 306 10 8 9.45 0.36 160 87.7 34813 +2003 307 13 3 10.25 0 173 211.32 34639 +2003 308 17 3 13.15 0 450 240.96 34468 +2003 309 12 2 9.25 0 461.56 201.85 34298 +2003 310 6 -1 4.08 0.18 249.58 120.65 34130 +2003 311 6 3 5.17 0.03 125.14 56.33 33964 +2003 312 9 4 7.63 0 232.21 118.68 33801 +2003 313 7 6 6.72 0 47.95 34.27 33640 +2003 314 6 4 5.45 0 86.76 54.76 33481 +2003 315 7 2.7 5.82 0 181.41 108.09 33325 +2003 316 7 1 5.35 0 236.93 142.95 33171 +2003 317 7 -3 4.25 0 337.74 196.75 33019 +2003 318 4 -2 2.35 0 195.92 142.82 32871 +2003 319 9 -2 5.97 0 405.71 199.44 32725 +2003 320 3 -1 1.9 0 132.73 99.93 32582 +2003 321 13 3 10.25 0.27 490.51 138.87 32441 +2003 322 10 2 7.8 0 352.29 163.87 32304 +2003 323 20 3 15.32 0 475.56 188.42 32170 +2003 324 16 5 12.98 0 314.44 191.66 32039 +2003 325 14 0 10.15 0 192.22 177.35 31911 +2003 326 15 1 11.15 0 273.33 176.37 31786 +2003 327 15 10 13.63 0 626.67 161.68 31665 +2003 328 17 10 15.07 0 598.89 162.14 31547 +2003 329 17 11 15.35 0 543.33 172.67 31433 +2003 330 10 8 9.45 0.1 67.78 45.01 31322 +2003 331 10 8 9.45 0.01 202.22 107.86 31215 +2003 332 7 6 6.72 0.16 254.44 49.24 31112 +2003 333 14 5 11.53 0.23 131.11 86.62 31012 +2003 334 9 6 8.18 0 48.89 43.24 30917 +2003 335 5 4 4.72 0 28.89 40.74 30825 +2003 336 5 3 4.45 0 43.33 79.98 30738 +2003 337 3 2 2.73 0.02 16.67 41.78 30654 +2003 338 2 1 1.73 0.03 10 30.76 30575 +2003 339 2 1 1.73 0 62.22 27.62 30500 +2003 340 9 1 6.8 0 42.22 69.89 30430 +2003 341 3 -2 1.63 0 218.89 168.19 30363 +2003 342 2 -6 -0.2 0 177.78 221.19 30301 +2003 343 4 -7 0.98 0 213.33 199.4 30244 +2003 344 2 -6 -0.2 0 113.33 174.1 30191 +2003 345 1 -5 -0.65 0 102.22 98.68 30143 +2003 346 7 -2 4.53 0 127.78 103.31 30099 +2003 347 6 -3 3.52 0.01 221.25 149.34 30060 +2003 348 5 0 3.63 0.28 81.25 75.81 30025 +2003 349 5 -1 3.35 0.26 157.5 112.55 29995 +2003 350 4 -3 2.08 0 167.5 121.86 29970 +2003 351 0 -4 -1.1 0 221.25 36.86 29950 +2003 352 8 -2 5.25 0 286.25 146.56 29934 +2003 353 6 -4 3.25 0 177.5 176.84 29924 +2003 354 10 -5 5.88 0 190 162.45 29918 +2003 355 9 -2 5.97 0.44 310 77.5 29916 +2003 356 3 1 2.45 0.03 36.25 56.81 29920 +2003 357 0 -2 -0.55 0 261.25 160.65 29928 +2003 358 0 -7 -1.93 0 220 167.09 29941 +2003 359 1 -13 -2.85 0 210 188.53 29959 +2003 360 1 -9 -1.75 0 241.25 122.09 29982 +2003 361 2 -9 -1.02 0 90 157.69 30009 +2003 362 8 -5 4.43 0 290 97.92 30042 +2003 363 6 5 5.72 0.23 147.5 34 30078 +2003 364 4 1 3.17 0.49 25 63.9 30120 +2003 365 4 3 3.73 1.36 28.75 17.84 30166 +2004 1 1 0 0.72 0 141.25 79.76 30217 +2004 2 -2 -3 -2.27 0 143.75 44.24 30272 +2004 3 -1 -6 -2.38 0 181.25 89.15 30331 +2004 4 -4 -9 -5.38 0 170 120.66 30396 +2004 5 4 -9 0.43 0.03 123.75 86.66 30464 +2004 6 -2 -13 -5.03 0.05 131.25 176.12 30537 +2004 7 -1 -10 -3.48 0.03 108.75 82.25 30614 +2004 8 6 -6 2.7 0 126.25 130.38 30695 +2004 9 -2 -2 -2 0.1 26.25 35.32 30781 +2004 10 4 -4 1.8 0 20 85.64 30870 +2004 11 5 -4 2.52 0.08 125.56 191.38 30964 +2004 12 7 -1 4.8 0.17 175.56 99.32 31061 +2004 13 8 1 6.08 0 315.56 80.4 31162 +2004 14 13 1 9.7 0 703.33 158.15 31268 +2004 15 5 1 3.9 0 108.89 74.4 31376 +2004 16 6 -3 3.52 0 353.33 173.02 31489 +2004 17 9 4 7.63 1.1 225.56 38.8 31605 +2004 18 1 -2 0.18 0.08 13.33 75.64 31724 +2004 19 2 -2 0.9 0 179 153.49 31847 +2004 20 4 -2 2.35 0 86 77.56 31974 +2004 21 2 -4 0.35 0 267 189.49 32103 +2004 22 -2 -5 -2.83 0 153 178.72 32236 +2004 23 -1 -11 -3.75 0 166 209.36 32372 +2004 24 1 -13 -2.85 0 181 219.9 32510 +2004 25 0 -12 -3.3 0.08 169 149.59 32652 +2004 26 3 -5 0.8 0 134 174.12 32797 +2004 27 -2 -5 -2.83 0.75 45 62.63 32944 +2004 28 -1 -4 -1.83 0 75 200.73 33094 +2004 29 -1 -10 -3.48 0 89 219.4 33247 +2004 30 4 -14 -0.95 0 305 263.97 33402 +2004 31 6 -7 2.43 0 286 223.53 33559 +2004 32 9 -3 5.7 0 356 195.11 33719 +2004 33 11 -4 6.88 0.02 371 137.6 33882 +2004 34 14 3 10.98 0 177 100.56 34046 +2004 35 18 4 14.15 0 421 129.7 34213 +2004 36 23 5 18.05 0 1142 189.22 34382 +2004 37 12 9 11.18 0 683 56.25 34552 +2004 38 14 0 10.15 0 486 198.36 34725 +2004 39 11 4 9.07 0.02 310 263.18 34900 +2004 40 8 1 6.08 0.05 431 219.77 35076 +2004 41 4 -2 2.35 0.02 186 161.34 35254 +2004 42 9 -3 5.7 0.01 208 113.85 35434 +2004 43 -1 -6 -2.38 0.01 175 210.94 35615 +2004 44 -2 -7 -3.38 0.05 83 151.46 35798 +2004 45 6 -3 3.52 0 57 85.71 35983 +2004 46 4 -2 2.35 0.06 230 111.35 36169 +2004 47 5 -1 3.35 0.07 102 106.76 36356 +2004 48 8 -4 4.7 0 267 302.66 36544 +2004 49 8 -4 4.7 0 234 207.41 36734 +2004 50 4 -1 2.63 0 248 221.28 36925 +2004 51 4 -2 2.35 0 195.92 174.69 37117 +2004 52 0 -6 -1.65 0 150.84 177.79 37310 +2004 53 0 -2 -0.55 0.07 31.82 47.93 37505 +2004 54 0 0 0 1.33 10.91 32.02 37700 +2004 55 0 -2 -0.55 0.09 131.82 120.78 37896 +2004 56 2 -5 0.07 0 173.64 328.39 38093 +2004 57 1 -4 -0.38 1.74 29.09 60.82 38291 +2004 58 2 -2 0.9 0.01 95.45 178.07 38490 +2004 59 2 -2 0.9 0.77 172.73 229.5 38689 +2004 60 4 -2 2.35 0 239.09 275.25 38890 +2004 61 1 -9 -1.75 0 155 221.65 39091 +2004 62 3 -8 -0.02 0 251.67 251.19 39292 +2004 63 9 -3 5.7 0 411.67 194.85 39495 +2004 64 4 -3 2.08 0 289.17 352.99 39697 +2004 65 2 -3 0.63 0 224.17 277.88 39901 +2004 66 1 -10 -2.02 0 200 363.42 40105 +2004 67 1 -4 -0.38 1.46 112.5 146.51 40309 +2004 68 -1 -3 -1.55 0.65 22.5 119.36 40514 +2004 69 4 -2 2.35 0 165 182.66 40719 +2004 70 5 -4 2.52 0 273.33 338.08 40924 +2004 71 5 -5 2.25 0 145.83 294.77 41130 +2004 72 6 0 4.35 0 170 210.3 41336 +2004 73 9 -1 6.25 0 253.33 262.39 41543 +2004 74 9 2 7.08 0 236.67 197.54 41749 +2004 75 16 -1 11.32 0 385 361.36 41956 +2004 76 19 1 14.05 0 782.5 339.76 42163 +2004 77 23 5 18.05 0 1080.83 353.4 42370 +2004 78 23 5 18.05 0 1162.5 369.57 42578 +2004 79 24 5 18.77 0 1478.33 327.97 42785 +2004 80 20 7 16.43 0 891.67 229 42992 +2004 81 19 9 16.25 1.4 734.17 284.78 43200 +2004 82 8 5 7.17 0.4 148.33 122.92 43407 +2004 83 4 4 4 2.34 74.17 38.13 43615 +2004 84 6 3 5.17 1.68 95 42.92 43822 +2004 85 5 3 4.45 0.69 82.5 75.88 44029 +2004 86 5 0 3.63 0.06 220.83 284.7 44236 +2004 87 5 -1 3.35 0.01 128.33 154.28 44443 +2004 88 7 0 5.08 0 270 169.25 44650 +2004 89 12 0 8.7 0 456.67 373.28 44857 +2004 90 10 -1 6.97 0 435.83 374.72 45063 +2004 91 13 -1 9.15 0 513.33 377.28 45270 +2004 92 13 1 9.7 0 295.38 184.58 45475 +2004 93 16 7 13.53 0 746.15 291.63 45681 +2004 94 19 4 14.88 0 715.38 362.31 45886 +2004 95 21 8 17.43 0.73 770 337.67 46091 +2004 96 12 9 11.18 0.92 155 52.34 46295 +2004 97 8 4 6.9 1.48 132.14 138.32 46499 +2004 98 9 4 7.63 0.06 187.14 163.47 46702 +2004 99 14 -1 9.88 0 640.71 407.99 46905 +2004 100 11 0 7.97 0 415.71 222.82 47107 +2004 101 8 4 6.9 0.07 210.71 83.94 47309 +2004 102 15 1 11.15 0 387.14 320 47510 +2004 103 11 2 8.53 0.16 427.14 191.18 47710 +2004 104 10 5 8.63 0.35 434.29 83.41 47910 +2004 105 11 6 9.63 0.02 377.14 129.24 48108 +2004 106 12 2 9.25 0 447.14 267.7 48306 +2004 107 17 5 13.7 0.12 543.57 366.04 48504 +2004 108 14 8 12.35 0.03 151.43 110.03 48700 +2004 109 18 9 15.53 0.03 354.29 223.12 48895 +2004 110 18 9 15.53 1.25 540.71 312.67 49089 +2004 111 9 7 8.45 0.47 102.86 47.43 49282 +2004 112 19 8 15.98 0 743.57 397.69 49475 +2004 113 22 6 17.6 0 1040.71 399.68 49666 +2004 114 22 10 18.7 0.52 1115.71 444.35 49855 +2004 115 13 11 12.45 0.1 369.29 145.88 50044 +2004 116 13 5 10.8 0 420.71 264.1 50231 +2004 117 17 6 13.98 0 617.14 305.51 50417 +2004 118 17 4 13.43 0 620.71 470.82 50601 +2004 119 20 5 15.88 0 945.71 484.32 50784 +2004 120 24 8 19.6 0 1147.86 467.36 50966 +2004 121 20 9 16.98 0 886.43 290.18 51145 +2004 122 21 10 17.98 0 810.71 339.68 51324 +2004 123 20 8 16.7 0.12 585.71 325.03 51500 +2004 124 21 6 16.88 0 866.43 418.33 51674 +2004 125 18 9 15.53 0.16 590 247.13 51847 +2004 126 19 8 15.98 1.13 550.67 322.61 52018 +2004 127 16 10 14.35 0.35 366 248.42 52187 +2004 128 15 4 11.98 0.69 288.67 222.49 52353 +2004 129 12 5 10.07 0.26 126.67 157.51 52518 +2004 130 16 3 12.43 0.04 490.67 408.04 52680 +2004 131 16 7 13.53 0 568 354.7 52840 +2004 132 17 6 13.98 0.22 786 383.12 52998 +2004 133 22 7 17.88 0.1 944 443.93 53153 +2004 134 15 9 13.35 0.21 241.33 144.49 53306 +2004 135 16 8 13.8 0 629.33 437.03 53456 +2004 136 19 3 14.6 1.16 858 426.97 53603 +2004 137 15 8 13.07 0.01 463.33 374.83 53748 +2004 138 12 5 10.07 0 410 181.52 53889 +2004 139 21 5 16.6 0 803.33 415.54 54028 +2004 140 24 9 19.88 0 813.33 348.2 54164 +2004 141 26 10 21.6 0 1480 472.21 54297 +2004 142 26 10 21.6 0 813.75 385.45 54426 +2004 143 12 12 12 0.6 177.5 173.88 54552 +2004 144 14 6 11.8 0.09 400.63 279.44 54675 +2004 145 16 1 11.88 0 796.87 427.48 54795 +2004 146 18 5 14.43 0 820.63 396.95 54911 +2004 147 22 5 17.32 0 1283.75 496.3 55023 +2004 148 20 11 17.52 0.4 610.63 366.92 55132 +2004 149 12 10 11.45 0.25 156.25 105.15 55237 +2004 150 15 8 13.07 0 375.62 192.11 55339 +2004 151 21 8 17.43 0 935 491.55 55436 +2004 152 24 7 19.32 0 1268.13 486.33 55530 +2004 153 20 11 17.52 0.13 525.63 303.82 55619 +2004 154 17 13 15.9 1.96 186.25 160.59 55705 +2004 155 19 8 15.98 0.17 300.63 222.6 55786 +2004 156 16 13 15.18 0.04 273.75 108.6 55863 +2004 157 15 12 14.18 0.4 156.88 101.06 55936 +2004 158 20 11 17.52 0 578.13 286.71 56004 +2004 159 24 10 20.15 0 1140 466.91 56068 +2004 160 27 11 22.6 0 1379.38 481.31 56128 +2004 161 30 14 25.6 0.1 1751.87 438.8 56183 +2004 162 30 15 25.88 0.09 1291.88 369.43 56234 +2004 163 29 18 25.98 1.68 948.12 313.81 56280 +2004 164 24 16 21.8 2.57 501.87 246.46 56321 +2004 165 17 11 15.35 0.08 437.5 151.31 56358 +2004 166 22 12 19.25 0 919.38 489.25 56390 +2004 167 24 11 20.43 0.11 1181.25 472.76 56418 +2004 168 19 13 17.35 0 481.25 249.04 56440 +2004 169 22 8 18.15 0 935.62 405.37 56458 +2004 170 25 10 20.88 0.57 591.25 296.88 56472 +2004 171 23 14 20.52 0.49 578.13 311.13 56480 +2004 172 18 13 16.63 2.23 248.75 183.99 56484 +2004 173 21 12 18.52 0 568.12 307.42 56482 +2004 174 24 12 20.7 0.64 868.75 457.21 56476 +2004 175 25 10 20.88 0 790.63 476.78 56466 +2004 176 25 15 22.25 1.05 1039.38 352.88 56450 +2004 177 15 15 15 3.22 143.13 82.81 56430 +2004 178 23 9 19.15 0 848.13 426.63 56405 +2004 179 26 11 21.88 0 953.75 430.19 56375 +2004 180 28 16 24.7 0.4 881.25 308.34 56341 +2004 181 20 14 18.35 0.06 561.88 292.65 56301 +2004 182 23 11 19.7 0 711.87 358.05 56258 +2004 183 27 12 22.88 0.53 1099.38 434.77 56209 +2004 184 18 15 17.18 0.69 185.62 88.38 56156 +2004 185 24 10 20.15 0 934.37 482.34 56099 +2004 186 24 14 21.25 0 978.13 408.74 56037 +2004 187 29 13 24.6 0 1208.13 457.88 55971 +2004 188 25 16 22.52 0.24 666.25 348.38 55900 +2004 189 23 15 20.8 0 595 334.34 55825 +2004 190 29 13 24.6 0 961.25 374.34 55746 +2004 191 23 17 21.35 0 998.75 305.81 55663 +2004 192 22 10 18.7 0 975 449.92 55575 +2004 193 19 9 16.25 0.1 418.75 192.94 55484 +2004 194 21 6 16.88 0 710.63 349.76 55388 +2004 195 21 9 17.7 0 819.38 318.44 55289 +2004 196 19 12 17.07 0.08 630 184.97 55186 +2004 197 22 10 18.7 0.13 484.38 161.91 55079 +2004 198 28 15 24.43 0 979.38 404.08 54968 +2004 199 29 14 24.88 0 1133.13 420.99 54854 +2004 200 31 15 26.6 0 1410 471.76 54736 +2004 201 29 15 25.15 0.04 1211.25 393.38 54615 +2004 202 31 15 26.6 0 1240 439.84 54490 +2004 203 31 16 26.88 0 1660.63 462.94 54362 +2004 204 33 16 28.32 0.07 1296.87 386.05 54231 +2004 205 29 15 25.15 0 1148.13 384.35 54097 +2004 206 28 16 24.7 0 1131.87 361.98 53960 +2004 207 26 20 24.35 0 1070.63 278.22 53819 +2004 208 25 14 21.98 0.06 1175.63 283.54 53676 +2004 209 23 16 21.07 0 956 224.18 53530 +2004 210 19 15 17.9 0.19 775.71 180.52 53382 +2004 211 19 15 17.9 0.01 606.43 89.25 53230 +2004 212 25 12 21.43 0 792.86 230.56 53076 +2004 213 29 13 24.6 0 1806.43 483.49 52920 +2004 214 28 12 23.6 0.52 1061.43 327.56 52761 +2004 215 27 12 22.88 0.45 1273.57 362.75 52600 +2004 216 28 13 23.88 0.5 887.14 338.18 52437 +2004 217 29 12 24.32 0 1362.86 390.24 52271 +2004 218 30 12 25.05 0 1520 401.71 52103 +2004 219 28 16 24.7 0.43 1013.57 325.85 51934 +2004 220 25 16 22.52 1.26 384.29 171.71 51762 +2004 221 26 15 22.98 0 797.14 416.55 51588 +2004 222 27 13 23.15 0.5 805 320.53 51413 +2004 223 28 13 23.88 0 1100 430.68 51235 +2004 224 29 12 24.32 0 1135.71 426.06 51057 +2004 225 30 14 25.6 0 981.43 402.41 50876 +2004 226 23 19 21.9 0.52 835 139.07 50694 +2004 227 25 15 22.25 0 1025 402.86 50510 +2004 228 25 16 22.52 0 1190.71 414.87 50325 +2004 229 27 11 22.6 0 1165 450.69 50138 +2004 230 28 12 23.6 0 1193.57 446.19 49951 +2004 231 33 15 28.05 0 2058.57 445.76 49761 +2004 232 32 14 27.05 0 2087.14 428.85 49571 +2004 233 29 17 25.7 0.7 1127.14 353.65 49380 +2004 234 25 15 22.25 1.6 736.43 292.62 49187 +2004 235 22 14 19.8 0 1000 399.22 48993 +2004 236 25 10 20.88 0 960 410.75 48798 +2004 237 27 12 22.88 0.03 986.43 337.31 48603 +2004 238 23 16 21.07 0.23 912.86 251.38 48406 +2004 239 17 15 16.45 0.78 179.29 56.5 48208 +2004 240 23 11 19.7 0 1032.86 379.9 48010 +2004 241 26 9 21.32 0 1072.14 443.94 47811 +2004 242 27 11 22.6 0 1099.29 415.13 47611 +2004 243 27 12 22.88 0 956.43 402.76 47410 +2004 244 16 16 16 0.29 340 57.88 47209 +2004 245 21 13 18.8 0.01 480.77 186.13 47007 +2004 246 20 7 16.43 0 446.15 180.22 46805 +2004 247 24 9 19.88 0 691.54 333.16 46601 +2004 248 26 10 21.6 0 1066.15 370.2 46398 +2004 249 23 15 20.8 0 972.31 295.2 46194 +2004 250 26 12 22.15 0 1033.08 384.26 45989 +2004 251 25 8 20.32 0 1100.77 343.13 45784 +2004 252 25 9 20.6 0 1233.85 354.21 45579 +2004 253 18 12 16.35 0 1027.69 437.07 45373 +2004 254 20 4 15.6 0 892.31 417.6 45167 +2004 255 22 7 17.88 0 1050 397.53 44961 +2004 256 25 7 20.05 0.34 1017.5 315.74 44755 +2004 257 24 11 20.43 0 856.67 394.21 44548 +2004 258 27 9 22.05 0 1031.67 405.07 44341 +2004 259 20 16 18.9 0.34 308.33 84.5 44134 +2004 260 18 13 16.63 0 730 149.07 43927 +2004 261 19 10 16.52 0 1065 402.39 43719 +2004 262 21 2 15.78 0 950 399.81 43512 +2004 263 21 3 16.05 0 558.33 315.78 43304 +2004 264 24 10 20.15 0 645 309.02 43097 +2004 265 23 8 18.88 0.16 621.67 267.44 42890 +2004 266 18 10 15.8 0.33 345 301.13 42682 +2004 267 17 10 15.07 0.08 377.5 304.98 42475 +2004 268 12 10 11.45 0.45 126.67 48.76 42268 +2004 269 16 9 14.07 0 549.17 205.53 42060 +2004 270 16 10 14.35 0 627.5 218.61 41854 +2004 271 17 9 14.8 0 673.33 184.27 41647 +2004 272 20 11 17.52 0 563.33 193.35 41440 +2004 273 22 11 18.98 0.05 728.33 312.26 41234 +2004 274 19 11 16.8 0 400 253.49 41028 +2004 275 18 9 15.53 0.21 406.36 184.14 40822 +2004 276 17 10 15.07 0 202.73 151.97 40617 +2004 277 19 9 16.25 0.03 398.18 178.65 40412 +2004 278 21 8 17.43 0 740 321.13 40208 +2004 279 23 9 19.15 0 518.18 298.99 40003 +2004 280 23 7 18.6 0 650 314.45 39800 +2004 281 21 10 17.98 0.01 409.09 201.76 39597 +2004 282 23 8 18.88 0 555.45 304.88 39394 +2004 283 15 10 13.63 0.88 216.36 173.21 39192 +2004 284 10 8 9.45 2.08 99.09 46.41 38991 +2004 285 12 6 10.35 0 335.45 166.68 38790 +2004 286 10 3 8.07 0.16 327.27 243.34 38590 +2004 287 6 5 5.72 0.09 169.09 37.26 38391 +2004 288 7 4 6.17 0.16 64.55 36.33 38193 +2004 289 9 6 8.18 0.3 49.09 53.5 37995 +2004 290 13 7 11.35 1.62 341.45 133.7 37799 +2004 291 11 4 9.07 0.76 131.82 138.44 37603 +2004 292 15 1 11.15 0 380.91 273.63 37408 +2004 293 15 2 11.43 0 266.36 211.26 37214 +2004 294 17 5 13.7 0 368.18 228.12 37022 +2004 295 17 11 15.35 0.49 270.91 157.89 36830 +2004 296 15 13 14.45 0.71 96.36 56.66 36640 +2004 297 15 12 14.18 0 110 68.7 36451 +2004 298 18 9 15.53 0 298.18 222.17 36263 +2004 299 15 7 12.8 0 199.09 236.76 36076 +2004 300 17 6 13.98 0 502 233.47 35891 +2004 301 18 10 15.8 0 548 218.62 35707 +2004 302 21 9 17.7 0 739 230.86 35525 +2004 303 20 13 18.07 0 771 163.78 35345 +2004 304 20 15 18.63 0.18 650 109.83 35166 +2004 305 13 11 12.45 0.19 200 89.21 34988 +2004 306 14 7 12.07 0 260 121.55 34813 +2004 307 16 13 15.18 0.02 110 63.59 34639 +2004 308 13 11 12.45 0.03 60 37.17 34468 +2004 309 15 13 14.45 0 174.44 116.42 34298 +2004 310 13 6 11.07 0 286.67 116.21 34130 +2004 311 12 7 10.63 0 507.78 181.51 33964 +2004 312 9 3 7.35 0 268.89 127.6 33801 +2004 313 7 0 5.08 0.64 214.44 88.54 33640 +2004 314 3 2 2.73 1.53 31.11 49.33 33481 +2004 315 6 -1 4.08 0.24 57.78 84.44 33325 +2004 316 9 4 7.63 0 70 47.58 33171 +2004 317 12 4 9.8 0 120 49.29 33019 +2004 318 8 7 7.72 1.45 102.22 28.64 32871 +2004 319 5 4 4.72 0 290 71.59 32725 +2004 320 4 2 3.45 0.01 231.11 53.64 32582 +2004 321 5 -3 2.8 0 217.78 103.78 32441 +2004 322 12 1 8.97 0 471.11 124.82 32304 +2004 323 12 2 9.25 0 587.78 186.2 32170 +2004 324 10 2 7.8 0.12 427.78 74.72 32039 +2004 325 5 -2 3.08 0 263.33 183.16 31911 +2004 326 5 -3 2.8 0 356.67 176.98 31786 +2004 327 2 -4 0.35 0 225.56 58.29 31665 +2004 328 12 1 8.97 0.04 590 136.63 31547 +2004 329 6 3 5.17 0 533.33 212.53 31433 +2004 330 4 -2 2.35 0 384.44 206.29 31322 +2004 331 7 -6 3.43 0 376.67 192.34 31215 +2004 332 5 -5 2.25 0 193.33 71.67 31112 +2004 333 9 -3 5.7 0 220 162.48 31012 +2004 334 5 -1 3.35 0 86.67 79.68 30917 +2004 335 3 2 2.73 0.3 30 17.74 30825 +2004 336 5 3 4.45 0 30 34.59 30738 +2004 337 10 4 8.35 0 84.44 109.35 30654 +2004 338 7 0 5.08 0 90 82.93 30575 +2004 339 6 -2 3.8 0 82.22 87.92 30500 +2004 340 4 -1 2.63 0.12 32.22 61.61 30430 +2004 341 6 1 4.63 0 66.67 98.17 30363 +2004 342 5 -4 2.52 0 90 162.11 30301 +2004 343 2 1 1.73 0 84.44 20.83 30244 +2004 344 1 1 1 0 144.44 34.53 30191 +2004 345 0 -1 -0.28 0 114.44 28.83 30143 +2004 346 0 -2 -0.55 0 81.11 79.16 30099 +2004 347 -2 -4 -2.55 0 22.5 19.54 30060 +2004 348 -2 -3 -2.27 0 30 14.81 30025 +2004 349 -3 -3 -3 0 30 18.6 29995 +2004 350 -3 -4 -3.27 0 30 19.48 29970 +2004 351 -4 -4 -4 0.04 30 15.91 29950 +2004 352 -1 -4 -1.83 0.5 30 20.61 29934 +2004 353 6 -1 4.08 0.03 26.25 54.24 29924 +2004 354 3 -5 0.8 0 210 130.18 29918 +2004 355 2 -1 1.18 0 277.5 183.28 29916 +2004 356 2 -8 -0.75 0 180 171.01 29920 +2004 357 -4 -9 -5.38 0 31.25 62.92 29928 +2004 358 0 -7 -1.93 0 127.5 69.29 29941 +2004 359 6 -3 3.52 0 431.25 141.12 29959 +2004 360 10 -2 6.7 0 326.25 148.47 29982 +2004 361 7 5 6.45 0.91 150 24.07 30009 +2004 362 4 0 2.9 0.78 38.75 20.24 30042 +2004 363 3 1 2.45 0.55 47.5 28.98 30078 +2004 364 7 1 5.35 0 276.25 150.96 30120 +2004 365 4 1 3.17 0 246.25 65.02 30166 +2005 1 7 -2.9 4.28 0 197.5 66.13 30217 +2005 2 9.4 -1.7 6.35 0 306.25 127.21 30272 +2005 3 8.1 -2.7 5.13 0 482.5 198.32 30331 +2005 4 10.3 -1.5 7.06 0 456.25 71.18 30396 +2005 5 10.8 -3.9 6.76 0 483.75 156.02 30464 +2005 6 12.5 -2.8 8.29 0 450 128.02 30537 +2005 7 11.4 -2.4 7.61 0 437.5 143.02 30614 +2005 8 12.6 -3.2 8.25 0 477.5 178.61 30695 +2005 9 6.1 -3.1 3.57 0 201.25 112.78 30781 +2005 10 11.6 -3.9 7.34 0 327.5 177.51 30870 +2005 11 7.4 -4.1 4.24 0 132.22 132.57 30964 +2005 12 8.8 -5.1 4.98 0 306.67 194.08 31061 +2005 13 2.7 -4.5 0.72 0.01 108.89 61.85 31162 +2005 14 5.5 -5.4 2.5 0 284.44 126.84 31268 +2005 15 6.1 -3 3.6 0 316.67 151.47 31376 +2005 16 4.6 -7 1.41 0 290 217.2 31489 +2005 17 3.5 -8.5 0.2 0 241.11 203.91 31605 +2005 18 -0.3 -10 -2.97 0.01 44.44 49.64 31724 +2005 19 1.8 -3.6 0.32 0 99 99.65 31847 +2005 20 3.8 -8.5 0.42 0.02 219 82.34 31974 +2005 21 8.3 -0.2 5.96 0.02 311 150.04 32103 +2005 22 7.1 -5.4 3.66 0 365 175.08 32236 +2005 23 5.6 -6.4 2.3 0 255 145.21 32372 +2005 24 0.6 -6.6 -1.38 0.44 86 72.68 32510 +2005 25 0.4 -2.3 -0.34 0 149 185.01 32652 +2005 26 -2.2 -3.4 -2.53 0.02 60 65.06 32797 +2005 27 -1.5 -5.6 -2.63 0 147 155.4 32944 +2005 28 -2.3 -13.9 -5.49 0 125 208.28 33094 +2005 29 -2 -7 -3.38 0 130 146.11 33247 +2005 30 0.8 -14 -3.27 0 206 245.96 33402 +2005 31 3.8 -13.5 -0.96 0 234 104.58 33559 +2005 32 7.1 -1.7 4.68 0.02 247 154.14 33719 +2005 33 4.6 -4.7 2.04 0.97 294 127.69 33882 +2005 34 1.1 -0.7 0.61 1 30 41.64 34046 +2005 35 3.9 -8.7 0.44 0 134 138.15 34213 +2005 36 -2.2 -17 -6.27 0 89 275.53 34382 +2005 37 1 -19.7 -4.69 0 96 324.06 34552 +2005 38 -3 -20.4 -7.79 0 51 193.1 34725 +2005 39 -1.9 -22 -7.43 0 123 324.81 34900 +2005 40 -1.6 -23.5 -7.62 0 131 286.66 35076 +2005 41 1.3 -21.1 -4.86 0 171 300.13 35254 +2005 42 5.5 -4.5 2.75 0 299 154.64 35434 +2005 43 6.4 0 4.64 0.02 229 108.19 35615 +2005 44 9.6 0.9 7.21 0 367 169.18 35798 +2005 45 8.1 -2.5 5.18 0 337 256.29 35983 +2005 46 2.3 -2.4 1.01 0.03 224 142.75 36169 +2005 47 3.4 -0.8 2.25 0 149 59.95 36356 +2005 48 5.1 -1 3.42 0 243 136.77 36544 +2005 49 3.5 -1.4 2.15 0 230 169 36734 +2005 50 0.8 -4.4 -0.63 0 166 70.38 36925 +2005 51 4.1 -6 1.32 0.01 224 235.53 37117 +2005 52 1.3 -2.5 0.26 1.91 40 94.55 37310 +2005 53 2.8 -1.9 1.51 0.03 51.82 220.67 37505 +2005 54 3.8 -1.5 2.34 1.19 96.36 160.79 37700 +2005 55 6.3 -1 4.29 0 177.27 253.38 37896 +2005 56 0.2 -8.7 -2.25 0.47 30.91 109.9 38093 +2005 57 2.7 -2.4 1.3 0 192.73 286.3 38291 +2005 58 0.5 -5.4 -1.12 0 190.91 176.55 38490 +2005 59 -1.9 -14.5 -5.37 0 189.09 346.96 38689 +2005 60 -1 -20 -6.22 0 234.55 378.23 38890 +2005 61 -1.3 -21.5 -6.86 0 193.33 382.57 39091 +2005 62 -0.3 -18.2 -5.22 0.73 180.83 351.47 39292 +2005 63 -0.8 -7.1 -2.53 0.13 45 124.01 39495 +2005 64 0.1 -7.6 -2.02 0 135 255.37 39697 +2005 65 2.4 -16.3 -2.74 0 229.17 272.51 39901 +2005 66 4.2 -16.4 -1.46 0 293.33 371.45 40105 +2005 67 5.1 -3.6 2.71 0 266.67 161.77 40309 +2005 68 5.6 -2.9 3.26 0.29 141.67 132.1 40514 +2005 69 -0.1 -4.6 -1.34 0 210 380.28 40719 +2005 70 4.4 -15.2 -0.99 0 281.67 301.54 40924 +2005 71 10.3 -9.9 4.75 0.02 377.5 279.33 41130 +2005 72 11.5 -1.6 7.9 0 468.33 383.07 41336 +2005 73 11.8 -6.4 6.8 0 425.83 368.46 41543 +2005 74 12.5 -3.9 7.99 0 484.17 333.7 41749 +2005 75 19.2 -2 13.37 0 779.17 361.54 41956 +2005 76 23 -1.4 16.29 0 1274.17 368.38 42163 +2005 77 22.3 3.1 17.02 0 1217.5 314.42 42370 +2005 78 13.1 3.7 10.52 0.24 262.5 108.98 42578 +2005 79 6.5 -2 4.16 0 301.67 341.76 42785 +2005 80 9.5 -4.2 5.73 0 352.5 320.32 42992 +2005 81 12.5 -1.4 8.68 0 551.67 368.7 43200 +2005 82 14.5 -2 9.96 0 696.67 316.55 43407 +2005 83 18.3 -0.5 13.13 0 668.33 361.94 43615 +2005 84 16.1 0.6 11.84 0.15 393.33 219.37 43822 +2005 85 17.8 8 15.11 0 445.83 267.52 44029 +2005 86 18 3.7 14.07 0.32 510.83 307.37 44236 +2005 87 18.5 10.3 16.25 0.3 558.33 308.86 44443 +2005 88 16.1 6.9 13.57 0.28 555 285.65 44650 +2005 89 11.2 5 9.49 0.02 170.83 96.11 44857 +2005 90 12.3 5 10.29 0 605 352.23 45063 +2005 91 11.6 -2.2 7.8 0 591.67 438.41 45270 +2005 92 14.5 -2.6 9.8 0 693.08 447.16 45475 +2005 93 16.3 -3.1 10.97 0 850.77 441.39 45681 +2005 94 18 -2.5 12.36 0 1040.77 423.74 45886 +2005 95 20 -1.4 14.12 0 1245.38 433.37 46091 +2005 96 20.6 0.7 15.13 0 1225.71 402.43 46295 +2005 97 18.6 2 14.04 0 1127.86 327.7 46499 +2005 98 18.6 11.4 16.62 0 1060.71 389.6 46702 +2005 99 15.1 7.4 12.98 2.45 117.14 59.17 46905 +2005 100 9.5 6.1 8.56 0.2 286.43 132.92 47107 +2005 101 8.7 6.3 8.04 0.25 296.43 71.12 47309 +2005 102 12 5.9 10.32 0.23 420.71 108.4 47510 +2005 103 14.4 7.6 12.53 0.08 310 178.07 47710 +2005 104 20.5 6.3 16.59 0 771.43 322.56 47910 +2005 105 22.1 4.1 17.15 0 1031.43 436.17 48108 +2005 106 21.7 4.6 17 0.08 1047.14 437.18 48306 +2005 107 17.4 8.8 15.04 0 490.71 219.21 48504 +2005 108 14.1 4.1 11.35 0.28 451.43 114.46 48700 +2005 109 14.3 9.9 13.09 0.84 172.86 77.05 48895 +2005 110 10.6 5.5 9.2 1.05 87.86 84.69 49089 +2005 111 9.7 4 8.13 0 538.57 452.34 49282 +2005 112 13.4 -2.1 9.14 0 712.86 486.12 49475 +2005 113 18.3 -2 12.72 0 928.57 471.47 49666 +2005 114 20 4 15.6 0 824.29 428.77 49855 +2005 115 19.2 11 16.95 0.15 566.43 352.03 50044 +2005 116 19 9.4 16.36 0.03 631.43 210.48 50231 +2005 117 24.1 6.6 19.29 0.31 1155 403.21 50417 +2005 118 20.6 9 17.41 0 869.29 392.73 50601 +2005 119 20.5 2 15.41 0 899.29 475.14 50784 +2005 120 21.1 5.9 16.92 0 937.14 331.78 50966 +2005 121 25.5 5.1 19.89 0 1219.29 467.08 51145 +2005 122 29.5 7.9 23.56 0 1729.29 453.31 51324 +2005 123 28.5 10.9 23.66 2.72 1615 370.82 51500 +2005 124 23.2 13.5 20.53 0.93 509.29 271.9 51674 +2005 125 18.3 11.2 16.35 0.06 529.33 222.5 51847 +2005 126 18.9 9.4 16.29 0.02 718 394.74 52018 +2005 127 17.8 4.5 14.14 0.38 826.67 379.89 52187 +2005 128 16.6 7.8 14.18 0 562.67 321.93 52353 +2005 129 13 3.3 10.33 0.08 407.33 223.87 52518 +2005 130 13.3 0.5 9.78 0 388 306.5 52680 +2005 131 16.3 7.5 13.88 0 736.67 403.68 52840 +2005 132 18 0.4 13.16 0 830 433.31 52998 +2005 133 20 0.6 14.67 0 958 485.52 53153 +2005 134 22.7 3.7 17.48 0 1028.67 411.32 53306 +2005 135 20.3 12.7 18.21 0.05 647.33 234.1 53456 +2005 136 21.5 12.1 18.91 0.02 559.33 288.6 53603 +2005 137 22.6 14 20.23 0.5 814 298.78 53748 +2005 138 15.6 10.9 14.31 1.31 112.67 55 53889 +2005 139 13.6 8.5 12.2 0.02 327.33 118.13 54028 +2005 140 18.6 4.5 14.72 0 818.67 552.05 54164 +2005 141 23.6 3.1 17.96 0 1073.33 509.23 54297 +2005 142 24.9 7.5 20.11 0 1159.38 450.91 54426 +2005 143 27.3 10.3 22.63 0.08 1147.5 372.23 54552 +2005 144 22.3 12.4 19.58 0 1000.63 463.37 54675 +2005 145 23.7 7.5 19.25 0 1189.38 520.79 54795 +2005 146 26 9.2 21.38 0 1316.25 508.9 54911 +2005 147 28.6 9.5 23.35 0 1517.5 504.72 55023 +2005 148 30.5 11 25.14 0 1740 483.73 55132 +2005 149 31 12.6 25.94 0 1812.5 480.01 55237 +2005 150 31.7 13.5 26.7 0.12 2053.75 504.51 55339 +2005 151 27.2 16 24.12 0 892.5 348.72 55436 +2005 152 21.7 7 17.66 0 1105.62 422.91 55530 +2005 153 23.1 8 18.95 0 1155.63 391.18 55619 +2005 154 25.5 7.9 20.66 0 1385.63 486.41 55705 +2005 155 27.1 13.2 23.28 0.64 1305.63 383.55 55786 +2005 156 20.5 14.2 18.77 0.05 452.5 287.34 55863 +2005 157 22.6 10 19.14 0.01 705 295.13 55936 +2005 158 17.3 7.8 14.69 0.82 461.88 193.22 56004 +2005 159 15.2 5.9 12.64 0 583.13 231.25 56068 +2005 160 13.3 9 12.12 0.06 475.62 138.72 56128 +2005 161 18.1 9.1 15.63 0 660.63 194.37 56183 +2005 162 22.3 5.9 17.79 0.27 963.75 311.78 56234 +2005 163 22.9 11.5 19.77 0.01 576.88 259.19 56280 +2005 164 26.6 8.6 21.65 0 1217.5 490.26 56321 +2005 165 27.1 10.6 22.56 0 1308.75 420.78 56358 +2005 166 26.6 17 23.96 0.2 1029.38 301.4 56390 +2005 167 27.1 16 24.05 0 997.5 401.09 56418 +2005 168 28.6 13.6 24.48 0 1455.62 398.84 56440 +2005 169 28.5 16 25.06 0 1231.88 265.68 56458 +2005 170 24.7 14 21.76 0 1198.75 493.88 56472 +2005 171 26.9 9.5 22.11 0 1366.87 435.38 56480 +2005 172 27.9 9.8 22.92 0 1698.75 498.79 56484 +2005 173 29.9 10.5 24.56 0.27 1233.13 363.39 56482 +2005 174 27.8 15.9 24.53 0 1475 475.9 56476 +2005 175 28.4 11 23.61 0 1356.25 481.2 56466 +2005 176 31 14.9 26.57 0 1470.62 450.44 56450 +2005 177 27.3 17.2 24.52 0.14 890.63 215.73 56430 +2005 178 28 15.1 24.45 2.98 743.13 314.69 56405 +2005 179 30.7 16.3 26.74 0.16 695 339.31 56375 +2005 180 29.7 13.9 25.36 1.8 908.13 316.36 56341 +2005 181 27.6 16.7 24.6 1.2 497.5 273.41 56301 +2005 182 20.1 15.1 18.73 4.37 150 79.3 56258 +2005 183 19.4 13.2 17.69 0.16 622.5 164.87 56209 +2005 184 26.4 14.9 23.24 0 1357.5 430.77 56156 +2005 185 26.7 10.6 22.27 0 1179.37 481.8 56099 +2005 186 23.5 12.6 20.5 2.24 364.38 121.31 56037 +2005 187 23.3 8 19.09 0 1013.75 498.04 55971 +2005 188 24.4 9.5 20.3 0.7 872.5 361.48 55900 +2005 189 21.6 14.2 19.57 1.19 157.5 131.34 55825 +2005 190 17.4 13.2 16.24 0.23 193.75 139.11 55746 +2005 191 23 11.4 19.81 0 538.12 283.4 55663 +2005 192 22.4 15.7 20.56 1.67 310.63 206.68 55575 +2005 193 19.5 15.4 18.37 1.22 142.5 66.34 55484 +2005 194 26.5 15 23.34 0.06 918.13 426.87 55388 +2005 195 28.1 13.5 24.09 0 1186.88 470.6 55289 +2005 196 28.9 12 24.25 0 1396.25 472.09 55186 +2005 197 29.8 17.2 26.34 0.4 1376.25 356.73 55079 +2005 198 30.4 15 26.16 0 1173.13 395.38 54968 +2005 199 31.4 16.1 27.19 0 982.5 430.91 54854 +2005 200 26.9 18.9 24.7 0.23 940 278.4 54736 +2005 201 26.4 12.8 22.66 0.05 1292.5 476.19 54615 +2005 202 23 15.3 20.88 0.17 578.75 302.9 54490 +2005 203 26.4 10 21.89 0.51 540 348.55 54362 +2005 204 21.7 14.9 19.83 0.21 410 254.12 54231 +2005 205 25.6 14.8 22.63 0.01 728.75 372.46 54097 +2005 206 28.6 16.3 25.22 0.05 898.75 423.08 53960 +2005 207 27.1 16.3 24.13 0.09 816.88 326.44 53819 +2005 208 30.2 17.9 26.82 0 993.75 442.02 53676 +2005 209 32.7 17.5 28.52 0 1176 442.97 53530 +2005 210 33 18.5 29.01 0 1310.71 443.18 53382 +2005 211 32.2 21.4 29.23 0 1347.14 395.06 53230 +2005 212 28.4 20.2 26.14 0 1219.29 453.91 53076 +2005 213 29.3 16.3 25.73 0 1670 458.02 52920 +2005 214 29.4 12.8 24.84 0 1641.43 440.32 52761 +2005 215 23.5 15.4 21.27 2.76 346.43 130.11 52600 +2005 216 19.5 15.6 18.43 0.08 543.57 108.05 52437 +2005 217 22.3 16 20.57 0 979.29 342.17 52271 +2005 218 25.3 7.9 20.52 0.3 1046.43 344.18 52103 +2005 219 18.7 12 16.86 0.12 344.29 130.27 51934 +2005 220 20.8 8 17.28 0 879.29 421.51 51762 +2005 221 23.1 5.5 18.26 0 1030 442.75 51588 +2005 222 26 8 21.05 0.12 998.57 440.17 51413 +2005 223 24.1 12.2 20.83 0.03 707.86 365.84 51235 +2005 224 21.9 16.2 20.33 0 685.71 166.13 51057 +2005 225 25.6 8.1 20.79 0.93 931.43 405.96 50876 +2005 226 24.1 15.3 21.68 4.79 879.29 386.81 50694 +2005 227 19.7 12.5 17.72 0.08 285.71 141.42 50510 +2005 228 17.6 13 16.34 1.25 222.86 142.96 50325 +2005 229 18.1 14.5 17.11 0.89 135 63.98 50138 +2005 230 25.1 14 22.05 0 811.43 391.85 49951 +2005 231 26.6 13 22.86 0 784.29 333.21 49761 +2005 232 25.7 13.3 22.29 0.38 652.86 290.8 49571 +2005 233 21.4 17.2 20.24 1.38 165 107.28 49380 +2005 234 21.1 15 19.42 1.13 281.43 271.96 49187 +2005 235 23.7 12.6 20.65 0.1 412.86 298.38 48993 +2005 236 24.6 14.8 21.91 0 695 291.19 48798 +2005 237 26.1 10.8 21.89 0.01 940.71 436.54 48603 +2005 238 21.7 15.9 20.11 0.1 614.29 150.45 48406 +2005 239 18.6 15.1 17.64 0.63 375 157.86 48208 +2005 240 21.2 15.3 19.58 0 300 216.25 48010 +2005 241 25.5 13.1 22.09 0 790 413.13 47811 +2005 242 26.5 13.4 22.9 0 743.57 359.28 47611 +2005 243 26.2 14.5 22.98 0 775.71 337.83 47410 +2005 244 27.4 13.5 23.58 0 798.57 315.21 47209 +2005 245 25.9 15 22.9 0 585.38 316.86 47007 +2005 246 24.1 13.3 21.13 0 816.15 394.26 46805 +2005 247 22.2 12.6 19.56 0 725.38 290.49 46601 +2005 248 23.9 7.9 19.5 0 851.54 421.2 46398 +2005 249 23.9 7.9 19.5 0 916.92 424.75 46194 +2005 250 25.1 8 20.4 0 872.31 396.15 45989 +2005 251 26.9 11 22.53 0 925.38 413.63 45784 +2005 252 26.3 16.8 23.69 0.12 897.69 311.1 45579 +2005 253 24.8 18 22.93 0.06 456.92 265.09 45373 +2005 254 24.4 15 21.81 0 350.77 184.63 45167 +2005 255 26.8 13 23 0 1050 424.53 44961 +2005 256 25.7 10.5 21.52 0.67 851.67 345.29 44755 +2005 257 23.5 10.6 19.95 0 702.5 342.77 44548 +2005 258 24.6 9.5 20.45 0 735 320.73 44341 +2005 259 25.4 10.9 21.41 1.48 1035.83 388.1 44134 +2005 260 20.2 12.1 17.97 0.2 215 82.06 43927 +2005 261 12.1 9.7 11.44 0.33 215 85.54 43719 +2005 262 11.6 9 10.89 1.78 165 72.28 43512 +2005 263 11.2 9.2 10.65 0.03 211.67 93.15 43304 +2005 264 15.1 9.9 13.67 0.1 340 145.19 43097 +2005 265 17.1 12 15.7 0 310.83 124.67 42890 +2005 266 20.6 9 17.41 0 565 260.1 42682 +2005 267 21.6 6 17.31 0 629.17 320.93 42475 +2005 268 22.2 7.5 18.16 0 636.67 328.89 42268 +2005 269 22.5 7 18.24 0 518.33 346.58 42060 +2005 270 21.4 8.7 17.91 0.37 448.33 246.46 41854 +2005 271 19.2 12.2 17.27 0 216.67 194.24 41647 +2005 272 14.3 8.9 12.82 1.96 67.5 53.07 41440 +2005 273 17.1 6.4 14.16 0 545.83 317.92 41234 +2005 274 16.6 3.4 12.97 0 575 365.9 41028 +2005 275 17.1 4.6 13.66 0.19 540.91 264.71 40822 +2005 276 14.9 11.5 13.97 0.05 100 59.62 40617 +2005 277 18.7 14.5 17.55 0 258.18 109.35 40412 +2005 278 19.1 12.5 17.29 0 469.09 150 40208 +2005 279 20 6.7 16.34 0 565.45 253.64 40003 +2005 280 18.5 6 15.06 0 503.64 280.07 39800 +2005 281 15.6 5.6 12.85 0 500.91 170.43 39597 +2005 282 17.8 5.5 14.42 0 359.09 198.12 39394 +2005 283 19.2 3.4 14.85 0 630 315.66 39192 +2005 284 15.2 3 11.84 0 345.45 160.85 38991 +2005 285 15.9 5 12.9 0 520 308.17 38790 +2005 286 16 2.5 12.29 0 320.91 206.24 38590 +2005 287 16.3 4.2 12.97 0 308.86 207.02 38391 +2005 288 16.1 4.9 13.02 0 633.02 267.88 38193 +2005 289 14.3 2.5 11.06 0 505.45 325.85 37995 +2005 290 12.6 2 9.68 0 496.36 237.55 37799 +2005 291 13.8 -1.2 9.68 0 437.27 312.74 37603 +2005 292 12.1 -3.3 7.87 0 340.91 301.08 37408 +2005 293 14.1 -1.4 9.84 0 286.36 210.98 37214 +2005 294 18.1 9 15.6 0 320.91 153.8 37022 +2005 295 20.6 4 16.04 0 507.27 215.71 36830 +2005 296 22.4 3.5 17.2 0.2 505.45 185.98 36640 +2005 297 18.6 8.1 15.71 0 350.91 215.2 36451 +2005 298 19.5 7.1 16.09 0 431.82 222.97 36263 +2005 299 20.1 3.8 15.62 0 632.73 223.55 36076 +2005 300 21.4 4.3 16.7 0 668 273.54 35891 +2005 301 18.1 6.1 14.8 0 368 237.62 35707 +2005 302 15.3 6.2 12.8 0 647 256.38 35525 +2005 303 11.6 1.8 8.9 0 317 265.95 35345 +2005 304 9.3 2.6 7.46 0 248 174.23 35166 +2005 305 8.6 -2.5 5.55 0 209 129.6 34988 +2005 306 13.1 5 10.87 0 184 101.4 34813 +2005 307 11.7 4.4 9.69 0.04 161 68.81 34639 +2005 308 11.9 5.3 10.09 0 237 144.24 34468 +2005 309 12.5 4.5 10.3 0 242.22 97.82 34298 +2005 310 11.1 6.8 9.92 0 210 71.99 34130 +2005 311 11.2 5.2 9.55 0.21 235.56 99.36 33964 +2005 312 13.2 5.5 11.08 0 208.89 175.53 33801 +2005 313 12.7 0 9.21 0 264.44 205.55 33640 +2005 314 6.6 1.4 5.17 0 37.78 42.9 33481 +2005 315 7.7 4.9 6.93 0 35.56 73.87 33325 +2005 316 6.7 5 6.23 0.07 111.11 36.18 33171 +2005 317 5.4 4.4 5.13 0.05 72.22 22.86 33019 +2005 318 4.4 2.9 3.99 0.07 106.67 32.86 32871 +2005 319 10.3 2.8 8.24 0 108.89 118.04 32725 +2005 320 5 -0.3 3.54 0.49 31.11 87.08 32582 +2005 321 10.1 1.2 7.65 0 443.33 209.78 32441 +2005 322 7.6 -3.6 4.52 0.03 253.33 212.6 32304 +2005 323 4.3 -3.4 2.18 0 251.11 191.23 32170 +2005 324 3.9 -4.1 1.7 0.05 234.44 142.61 32039 +2005 325 4.3 -1.9 2.59 0 168.89 84.74 31911 +2005 326 1.8 -2.8 0.54 0.16 120 64.9 31786 +2005 327 0.2 -2.2 -0.46 0.3 106.67 180.35 31665 +2005 328 -1 -3 -1.55 0.21 43.33 45.32 31547 +2005 329 1.2 -3 0.05 1.65 102.22 142.62 31433 +2005 330 1.4 -1.2 0.68 0.99 30 61.24 31322 +2005 331 1.4 0.3 1.1 1.88 31.11 34.17 31215 +2005 332 2.9 -1.9 1.58 0.09 35.56 53.84 31112 +2005 333 1.6 -3.6 0.17 0.19 38.89 105.7 31012 +2005 334 1.6 -0.5 1.02 0 55.56 58.2 30917 +2005 335 1.3 -3.8 -0.1 0.01 177.78 68.29 30825 +2005 336 0.7 -2 -0.04 0 33.33 59.17 30738 +2005 337 9.1 -2.9 5.8 0.01 323.33 90.18 30654 +2005 338 9.8 -0.1 7.08 0 110 148.07 30575 +2005 339 9 4 7.63 1.3 136.67 30.88 30500 +2005 340 4.7 2.7 4.15 2.25 46.67 20.05 30430 +2005 341 10.1 0.5 7.46 0 346.67 168.76 30363 +2005 342 8.5 -1.8 5.67 0 218.89 159.8 30301 +2005 343 7.3 -2.6 4.58 0 203.33 188.45 30244 +2005 344 3 -1.1 1.87 0 206.67 145.55 30191 +2005 345 0.9 -7.3 -1.35 0 138.89 200.21 30143 +2005 346 2.7 -8.5 -0.38 0.25 130 162.47 30099 +2005 347 0.8 -1.5 0.17 0 66.25 58.66 30060 +2005 348 1.6 -0.5 1.02 0 150 56.3 30025 +2005 349 6.6 -3.1 3.93 0 287.5 145.94 29995 +2005 350 6.1 -1.7 3.95 0.02 287.5 51.21 29970 +2005 351 5.5 -2 3.44 0 262.5 161.7 29950 +2005 352 3.8 -3.1 1.9 0 298.75 177.75 29934 +2005 353 6.1 -6.6 2.61 0 400 117.18 29924 +2005 354 6.3 -2.8 3.8 0 361.25 107.46 29918 +2005 355 4.2 -2.7 2.3 0 241.25 154.03 29916 +2005 356 1.3 -6.5 -0.84 0 158.75 38.07 29920 +2005 357 4.6 -5.3 1.88 0.01 321.25 143.43 29928 +2005 358 5.5 -1.6 3.55 0 215 57.12 29941 +2005 359 7.4 -4.4 4.16 0 280 174.15 29959 +2005 360 1.7 -3 0.41 0.04 112.5 73.45 29982 +2005 361 0 -2.3 -0.63 1.17 35 50.87 30009 +2005 362 -0.1 -2.4 -0.73 1.31 30 58.25 30042 +2005 363 -0.9 -3.2 -1.53 1.43 36.25 48.47 30078 +2005 364 0.5 -8.2 -1.89 0 108.75 99.17 30120 +2005 365 1.7 -17.6 -3.61 0.13 150 100.21 30166 +2006 1 1.7 -7.5 -0.83 1.92 45 49.43 30217 +2006 2 2 0.4 1.56 1.66 30 32.31 30272 +2006 3 3.1 -0.2 2.19 0 80 78.84 30331 +2006 4 2.2 -0.5 1.46 0.18 93.75 45.93 30396 +2006 5 1.2 0.3 0.95 0.9 30 53.26 30464 +2006 6 2 0.3 1.53 0.16 30 45.55 30537 +2006 7 2.7 -0.5 1.82 0 33.75 97.75 30614 +2006 8 0.8 -4.3 -0.6 0 77.5 77.17 30695 +2006 9 1.7 -10.6 -1.68 0 90 244.84 30781 +2006 10 -1.3 -12.3 -4.33 0 112.5 97.67 30870 +2006 11 0 -12 -3.3 0 82.22 234.14 30964 +2006 12 -0.3 -11.5 -3.38 0 66.67 153.47 31061 +2006 13 -3 -10 -4.92 0 30 62.05 31162 +2006 14 -1.9 -4.2 -2.53 0 96.67 85 31268 +2006 15 -0.2 -6.6 -1.96 0 147.78 126.37 31376 +2006 16 -2.1 -7.6 -3.61 0 124.44 84.86 31489 +2006 17 -3.9 -12 -6.13 0 48.89 98.91 31605 +2006 18 -0.1 -6.1 -1.75 0 120 69.25 31724 +2006 19 0.5 -6.5 -1.43 0 138 195.46 31847 +2006 20 1.7 -11.5 -1.93 0 80 140.43 31974 +2006 21 6.8 -8.4 2.62 0 200 242.36 32103 +2006 22 5.1 -7.6 1.61 0 163 159.68 32236 +2006 23 -7.6 -13.7 -9.28 0 92 197.04 32372 +2006 24 -7.5 -20 -10.94 0 100 271.93 32510 +2006 25 -6.2 -21 -10.27 0 114 250.65 32652 +2006 26 -6 -17.7 -9.22 0 96 199.88 32797 +2006 27 -5.2 -18.2 -8.77 0 83 134.66 32944 +2006 28 -1 -12.9 -4.27 0 147 196.91 33094 +2006 29 -2.5 -11 -4.84 0 114 86.52 33247 +2006 30 -0.1 -3.4 -1.01 0 51 97.98 33402 +2006 31 0.7 -4 -0.59 0 92 209.5 33559 +2006 32 -0.2 -5 -1.52 0 30 133.72 33719 +2006 33 -2.7 -5.4 -3.44 0 30 105.48 33882 +2006 34 -3.6 -7.5 -4.67 0 30 82.15 34046 +2006 35 -1.3 -7 -2.87 0.03 30 95.95 34213 +2006 36 -3.3 -8.7 -4.79 0 171 291.28 34382 +2006 37 -2 -13.2 -5.08 0 166 272.1 34552 +2006 38 -0.4 -17.4 -5.07 0 167 145.52 34725 +2006 39 5.8 -2.4 3.54 0.01 265 167.16 34900 +2006 40 8.2 -4 4.84 0.03 348 292.82 35076 +2006 41 5.2 -6.5 1.98 0 266 184.49 35254 +2006 42 4.5 -6 1.61 0 243 206.61 35434 +2006 43 4.3 -5.5 1.61 0 251 213.79 35615 +2006 44 2.6 -6 0.24 0 179 160.27 35798 +2006 45 4.1 -9 0.5 0 234 204.93 35983 +2006 46 5 -6 1.98 0 222 169.41 36169 +2006 47 9.1 0 6.6 0.02 231 130.28 36356 +2006 48 7.7 -1.4 5.2 0.1 62 117.64 36544 +2006 49 11.3 -1.6 7.75 0.2 306 245.39 36734 +2006 50 12.4 -1.1 8.69 0 367 264.28 36925 +2006 51 12.2 5 10.22 0.54 541 215.68 37117 +2006 52 10.3 -1.1 7.17 0 222 274.12 37310 +2006 53 5.1 -0.2 3.64 0 191.82 155.03 37505 +2006 54 3.6 0.4 2.72 0 190 135.1 37700 +2006 55 3.1 1 2.52 0.58 141.82 61.06 37896 +2006 56 2.3 -1.2 1.34 0.85 30 136.81 38093 +2006 57 1.1 -1.8 0.3 0.09 99.09 203.29 38291 +2006 58 2 -3.6 0.46 0 231.82 313.48 38490 +2006 59 1.6 -10.6 -1.75 0 251.82 384.8 38689 +2006 60 5.1 -10.5 0.81 0 298.18 350.32 38890 +2006 61 2.4 -5.6 0.2 0 227.5 155.51 39091 +2006 62 6.6 -8.1 2.56 0 235.83 306.74 39292 +2006 63 8.6 2.4 6.89 0.11 268.32 155.69 39495 +2006 64 2.4 -1.1 1.44 0.82 114.03 96.26 39697 +2006 65 4.1 -9.1 0.47 0 324.95 342.11 39901 +2006 66 4.9 -8.8 1.13 0 260.83 377.49 40105 +2006 67 4.6 -5.9 1.71 0 300 343.18 40309 +2006 68 8.4 0 6.09 0 316.67 138.01 40514 +2006 69 6.6 0.6 4.95 0.97 118.33 52.37 40719 +2006 70 10.1 0.4 7.43 0 324.17 263.02 40924 +2006 71 4.3 -3.4 2.18 0.14 255 200.15 41130 +2006 72 1 -2 0.18 0.02 290 148.85 41336 +2006 73 1.4 -2.2 0.41 0.01 170.83 128.01 41543 +2006 74 1.2 -1.5 0.46 0.01 195 144.03 41749 +2006 75 2.3 -1.3 1.31 0.06 108.33 134.16 41956 +2006 76 4.4 -0.2 3.14 0 190 175.45 42163 +2006 77 5.1 -1.9 3.17 0 194.17 155.54 42370 +2006 78 10.3 -4.5 6.23 0 360 393.84 42578 +2006 79 13.9 -4.2 8.92 0 590.83 406.98 42785 +2006 80 14.1 -3.1 9.37 0 628.33 335.21 42992 +2006 81 15.6 3.5 12.27 0 560 333.91 43200 +2006 82 10.8 2.7 8.57 0 448.33 317.2 43407 +2006 83 10 -4 6.15 0 471.67 407.69 43615 +2006 84 12.7 -1.3 8.85 0.01 542.5 250.86 43822 +2006 85 15.1 0 10.95 0 515 158.52 44029 +2006 86 20.7 3.7 16.02 0 801.67 344.43 44236 +2006 87 18.7 4 14.66 1.24 636.67 327.34 44443 +2006 88 15.7 6.5 13.17 0.05 510.83 243.75 44650 +2006 89 17.6 1.9 13.28 0 1015 346.56 44857 +2006 90 16.6 6.4 13.8 0.14 515.83 161.57 45063 +2006 91 20.1 2.6 15.29 0 850.83 364.47 45270 +2006 92 19.1 4 14.95 0.01 806.92 386.35 45475 +2006 93 15 5.5 12.39 0.48 461.54 138.9 45681 +2006 94 14.8 1.2 11.06 0 591.54 321.22 45886 +2006 95 12.8 0.2 9.34 0.06 440 138.99 46091 +2006 96 10.7 3.3 8.66 0.01 435.71 172.57 46295 +2006 97 12.5 -1.5 8.65 0 611.43 456.92 46499 +2006 98 16.1 -3.5 10.71 0 775 453.77 46702 +2006 99 18.6 -1 13.21 0 938.57 416.07 46905 +2006 100 19.4 5.4 15.55 0.85 943.57 340.32 47107 +2006 101 15.3 4.5 12.33 1 217.14 192.77 47309 +2006 102 10.5 4.4 8.82 0 578.57 197.76 47510 +2006 103 13.5 3 10.61 0 639.29 274.87 47710 +2006 104 18.4 2.8 14.11 0 693.57 227.1 47910 +2006 105 17.2 0.4 12.58 0 539.29 330.87 48108 +2006 106 13.7 6.3 11.66 1.16 320 107.09 48306 +2006 107 18.1 5.8 14.72 0 656.43 359.76 48504 +2006 108 17.9 5.6 14.52 0.01 577.14 255.82 48700 +2006 109 19.6 8.2 16.47 0.01 989.29 398.59 48895 +2006 110 20.3 7.8 16.86 0 1092.14 428.17 49089 +2006 111 21.3 2.6 16.16 0 1036.43 439.67 49282 +2006 112 22.6 3 17.21 0 1035 333.87 49475 +2006 113 23.9 4 18.43 0.91 1104.29 432.71 49666 +2006 114 23.6 6.1 18.79 0 1087.86 462.29 49855 +2006 115 24.9 7.1 20 0 1357.86 385.46 50044 +2006 116 25 7.2 20.11 0.12 1185 359.8 50231 +2006 117 19.2 12.2 17.27 1.17 212.86 110.61 50417 +2006 118 14.9 12.2 14.16 1.15 117.86 86.86 50601 +2006 119 13.5 7.7 11.9 3.13 98.57 43.02 50784 +2006 120 7.7 5 6.96 1.32 77.14 68.46 50966 +2006 121 14.9 5.6 12.34 0.21 319.29 299.73 51145 +2006 122 17.6 4.5 14 0 367.14 341.92 51324 +2006 123 19.6 5.5 15.72 0 587.14 426.32 51500 +2006 124 18.1 4.5 14.36 0 820 467.39 51674 +2006 125 21 2.6 15.94 0 861.33 389.66 51847 +2006 126 20.6 3.6 15.93 0.09 842.67 423.01 52018 +2006 127 17.5 6.7 14.53 0.06 384.67 245.3 52187 +2006 128 19.8 5.8 15.95 0 674.67 418.84 52353 +2006 129 21.7 3.9 16.81 0 803.33 498.53 52518 +2006 130 21.6 7.1 17.61 0 1060.67 469.25 52680 +2006 131 20.6 4.8 16.26 0 956.67 456.91 52840 +2006 132 23.5 4.5 18.27 0 1217.33 475.32 52998 +2006 133 25.6 6.7 20.4 0.18 1093.33 398.84 53153 +2006 134 21.7 9.1 18.23 1.29 498.67 293.62 53306 +2006 135 22.1 8.1 18.25 0 870.67 476.89 53456 +2006 136 26.1 10.4 21.78 0.2 1018.67 406.36 53603 +2006 137 23.9 13.2 20.96 0.45 509.33 323.19 53748 +2006 138 25.7 7.8 20.78 0.19 848 464.25 53889 +2006 139 23.4 14.2 20.87 1.02 220 100.98 54028 +2006 140 19 12.2 17.13 0.08 362.67 280.95 54164 +2006 141 17.3 13.3 16.2 0.44 266 144.18 54297 +2006 142 25.8 12.3 22.09 0 841.88 468.37 54426 +2006 143 23.1 14 20.6 0.93 960 451.59 54552 +2006 144 16.3 10.4 14.68 1.48 218.75 69.26 54675 +2006 145 20.3 7.9 16.89 0 787.5 437.37 54795 +2006 146 22.7 9.5 19.07 0.05 729.38 335.18 54911 +2006 147 24.7 13.5 21.62 0 898.75 279.8 55023 +2006 148 24.5 12.9 21.31 1.48 388.75 188.3 55132 +2006 149 16.5 10.4 14.82 2.48 120.63 118.17 55237 +2006 150 11.6 9.2 10.94 1.27 113.12 55.98 55339 +2006 151 16.8 4.4 13.39 0.01 585 396.72 55436 +2006 152 17.7 3.1 13.69 0.25 525.63 326 55530 +2006 153 12.1 4.9 10.12 1.26 225.63 86.54 55619 +2006 154 13.4 9.4 12.3 0.21 178.75 95.52 55705 +2006 155 18.4 9.9 16.06 0.26 566.88 314.12 55786 +2006 156 18.2 5 14.57 0.07 655.63 336.42 55863 +2006 157 15.9 9.8 14.22 1.96 315.62 196.02 55936 +2006 158 18.9 7.8 15.85 0 615.62 411.95 56004 +2006 159 20.2 5.6 16.18 0 850.63 489.83 56068 +2006 160 20.7 6.1 16.68 0.36 938.75 478.51 56128 +2006 161 19 10.4 16.63 0.79 381.25 226.95 56183 +2006 162 20.2 10.4 17.5 0 593.75 328.13 56234 +2006 163 25 9.1 20.63 0 1045.63 486.08 56280 +2006 164 25.8 11.5 21.87 0.01 977.5 486.48 56321 +2006 165 25.6 12.5 22 0 1020 469.8 56358 +2006 166 27.2 11.6 22.91 0 1398.13 511.85 56390 +2006 167 29.7 14 25.38 0 1043.13 378.16 56418 +2006 168 28.7 16.1 25.23 0.14 1070 415.34 56440 +2006 169 29.7 17.6 26.37 0 1016.88 381.36 56458 +2006 170 31.7 16.8 27.6 0 1316.88 470.62 56472 +2006 171 31.7 18.8 28.15 0 1660.63 434.8 56480 +2006 172 31.7 17.2 27.71 0 1088.75 373.03 56484 +2006 173 29.4 19.5 26.68 0.48 1311.25 464.44 56482 +2006 174 27.1 17.3 24.41 0 901.87 455.22 56476 +2006 175 29.7 16.3 26.02 0 1258.75 475.97 56466 +2006 176 30.7 16 26.66 0 1287.5 466.74 56450 +2006 177 33.8 20 30 0 1537.5 455.24 56430 +2006 178 31.3 19.5 28.06 0.13 1227.5 456.13 56405 +2006 179 30.9 16.4 26.91 0 1361.87 464.25 56375 +2006 180 28.5 16.5 25.2 3.05 310 201.75 56341 +2006 181 26.4 17.5 23.95 0 672.5 408.64 56301 +2006 182 23.9 16.2 21.78 0.4 625.63 195.71 56258 +2006 183 21.4 15.9 19.89 0.05 431.25 197.86 56209 +2006 184 19.3 17 18.67 0.01 263.75 107.2 56156 +2006 185 24.7 15 22.03 0 850 410.4 56099 +2006 186 26.7 10.4 22.22 0 1257.5 504.61 56037 +2006 187 28.7 12.3 24.19 0 1436.25 487.68 55971 +2006 188 30.5 14.1 25.99 0.27 1431.88 446.38 55900 +2006 189 29.9 18 26.63 0.05 1165 480.33 55825 +2006 190 30.7 15.6 26.55 0 1175 418.4 55746 +2006 191 30.3 16 26.37 0 1203.13 444.56 55663 +2006 192 32.3 17.9 28.34 0 1468.13 459.81 55575 +2006 193 30.9 16.5 26.94 1.29 1270.71 438.32 55484 +2006 194 29.2 16.2 25.63 0 1445.91 407.41 55388 +2006 195 31.3 16.2 27.15 0 1754.68 437.69 55289 +2006 196 25.7 19 23.86 0 761.06 242.76 55186 +2006 197 24.6 12 21.14 0 1104.75 420.55 55079 +2006 198 26.2 9.2 21.52 0 1404.12 487.84 54968 +2006 199 29.1 10 23.85 0 1728.25 499.34 54854 +2006 200 31.5 11.3 25.95 0 2011.06 499.25 54736 +2006 201 32.3 12.6 26.88 0 2081.61 488.68 54615 +2006 202 34 13.8 28.45 0 2301.03 484.34 54490 +2006 203 34.3 16.8 29.49 0 2206.93 446.62 54362 +2006 204 32.7 16.9 28.36 0.03 1933.46 318.24 54231 +2006 205 32.3 17 28.09 1.52 1862.75 311.84 54097 +2006 206 31.5 18.5 27.93 0 1633.87 373.58 53960 +2006 207 32.5 17.9 28.48 0 1837.18 400.95 53819 +2006 208 33.6 17.4 29.15 0 2052.26 421.67 53676 +2006 209 32.9 16 28.25 0.3 2017.69 325.76 53530 +2006 210 31.7 18.3 28.02 0.07 1680.18 280.6 53382 +2006 211 31.3 18.4 27.75 0 1609.49 362.14 53230 +2006 212 31.6 15.6 27.2 0 1835.03 416.86 53076 +2006 213 26.3 17 23.74 0.37 1000.26 211.37 52920 +2006 214 22.2 18.5 21.18 0.01 385.18 91.51 52761 +2006 215 20.4 12.5 18.23 1.43 643.93 191.21 52600 +2006 216 19.2 13.5 17.63 0.4 469.1 143.71 52437 +2006 217 23.3 13.3 20.55 0.14 891.36 237.3 52271 +2006 218 23.8 14.4 21.22 0.48 879.21 226 52103 +2006 219 20.7 15.1 19.16 1.11 502.89 144.01 51934 +2006 220 25.4 15.2 22.59 0.01 1013.7 242.47 51762 +2006 221 24.9 11 21.08 0 1185.7 409.48 51588 +2006 222 24.7 11 20.93 0 1163.55 405.28 51413 +2006 223 22.7 12.1 19.79 0.21 895.14 256.3 51235 +2006 224 16.1 10.8 14.64 2.84 370.9 145.28 51057 +2006 225 19.9 12.2 17.78 0 614.47 270.97 50876 +2006 226 22.4 9.1 18.74 0.88 1005.99 304.09 50694 +2006 227 24.7 11.7 21.13 0 1130.69 391.13 50510 +2006 228 25.7 11.6 21.82 0 1249.04 409.16 50325 +2006 229 29.2 14.3 25.1 0 1556.97 411.03 50138 +2006 230 29.6 19.4 26.8 0 1269.97 314.14 49951 +2006 231 26.9 14 23.35 0 1271.01 388.77 49761 +2006 232 28.4 16 24.99 0.21 1347.48 281.74 49571 +2006 233 24.2 14.1 21.42 0.48 943 255.03 49380 +2006 234 24.2 11.6 20.73 0.12 1080.4 297.68 49187 +2006 235 23.9 12.3 20.71 0 1012.13 377.68 48993 +2006 236 24.8 10.1 20.76 2.08 1213.48 320.77 48798 +2006 237 20.2 14.3 18.58 1.32 509.94 167.21 48603 +2006 238 23.3 10.5 19.78 0 1036.45 403.55 48406 +2006 239 23.3 10.3 19.73 0.86 1045.44 305.3 48208 +2006 240 22.4 11.1 19.29 0.5 915.94 282.11 48010 +2006 241 21.6 14 19.51 0.26 669.44 210.85 47811 +2006 242 18.2 11.4 16.33 0.49 508.67 200.11 47611 +2006 243 21.7 8.4 18.04 0 966.64 414.04 47410 +2006 244 23.7 5 18.56 0 1264.41 458.03 47209 +2006 245 24.9 7.9 20.22 0 1304.94 436.05 47007 +2006 246 26.9 10.8 22.47 0 1425.2 310.62 46805 +2006 247 30.1 14.9 25.92 0 1651.04 334.9 46601 +2006 248 28.3 15 24.64 0 1395.41 361.03 46398 +2006 249 25.2 13.8 22.07 0 1076.15 329.8 46194 +2006 250 26.7 13.6 23.1 0.09 1268.17 265.7 45989 +2006 251 21.8 14.9 19.9 0.04 629.6 165.86 45784 +2006 252 21.7 6.3 17.47 0 1040.24 399.62 45579 +2006 253 22.9 5.2 18.03 0 1182.94 416.2 45373 +2006 254 22.9 5 17.98 0 1188.04 411.25 45167 +2006 255 23.6 6.9 19.01 0 1202.77 391.43 44961 +2006 256 23.7 5.5 18.7 0 1251.98 402 44755 +2006 257 25.2 6.3 20 0 1383.22 400.3 44548 +2006 258 21.5 12.1 18.91 0.17 773.59 193.98 44341 +2006 259 18.2 15.2 17.38 0.31 256.73 70.81 44134 +2006 260 23 12.7 20.17 0.02 893.67 207.95 43927 +2006 261 19.7 15.3 18.49 2.32 389.74 98.32 43719 +2006 262 19.6 15 18.34 0.3 402.37 103.68 43512 +2006 263 24.5 14 21.61 0 983.24 278.49 43304 +2006 264 22.7 8.9 18.91 0 1043.55 338.02 43097 +2006 265 23.1 9 19.22 0 1079.49 337.34 42890 +2006 266 22.8 7.7 18.65 0 1097.9 347.9 42682 +2006 267 23.2 7.1 18.77 0 1157.01 351.66 42475 +2006 268 23.2 8 19.02 0 1126.78 337.28 42268 +2006 269 24 9.5 20.01 0 1152.15 322.72 42060 +2006 270 22.9 8.8 19.02 0.01 1067.3 236.84 41854 +2006 271 24.2 10.7 20.49 0.2 1122.56 224.26 41647 +2006 272 23.6 8.5 19.45 0 1149.07 315.82 41440 +2006 273 23.7 9.8 19.88 0 1108.5 296.42 41234 +2006 274 24.8 10.1 20.76 0 1213.48 302.95 41028 +2006 275 23.1 11.1 19.8 0 987.6 266.51 40822 +2006 276 25.2 15 22.4 0.16 1002.68 172.09 40617 +2006 277 21.2 13.2 19 0.66 679.64 144.99 40412 +2006 278 18.4 10.4 16.2 0 580.05 198.16 40208 +2006 279 19.6 3.4 15.15 0 941.11 319.36 40003 +2006 280 19.5 3.5 15.1 0.33 930.61 234.78 39800 +2006 281 18.7 7.6 15.65 0 784.09 396.42 39597 +2006 282 19.3 1.9 14.52 0 640.91 358.06 39394 +2006 283 20.1 2.6 15.29 0 586.36 336.29 39192 +2006 284 20 3.3 15.41 0 566.36 295.4 38991 +2006 285 19.7 4.4 15.49 0 542.73 324.66 38790 +2006 286 18.8 5.3 15.09 0 411.82 234.88 38590 +2006 287 19.2 8.8 16.34 0 508.18 226.2 38391 +2006 288 19.1 4.5 15.09 0 278.18 301.34 38193 +2006 289 15.6 4.9 12.66 0 580.91 320.72 37995 +2006 290 14.8 -2 10.18 0 475.45 324.57 37799 +2006 291 15.2 -2.5 10.33 0 486.36 319.77 37603 +2006 292 17.5 -1.5 12.28 0 443.64 226.11 37408 +2006 293 17.7 8.6 15.2 0 508.18 144.1 37214 +2006 294 22.2 5.7 17.66 0 602.73 242.6 37022 +2006 295 20.5 8.6 17.23 0 491.82 254.39 36830 +2006 296 22.3 10.1 18.95 0 753.64 239.08 36640 +2006 297 20.8 14.3 19.01 1.62 442.73 53.54 36451 +2006 298 19.3 8.5 16.33 0 333.64 221.42 36263 +2006 299 20.7 8.1 17.23 0.03 439.09 253.39 36076 +2006 300 13.9 8.2 12.33 0.02 27 96.89 35891 +2006 301 17.7 8.7 15.23 0.01 277 111.58 35707 +2006 302 21.4 11 18.54 0.04 282 84.79 35525 +2006 303 18.4 3.1 14.19 0 393 298.81 35345 +2006 304 12.3 -2.5 8.23 0 421 277.62 35166 +2006 305 8.3 4.5 7.26 0.96 138 52.49 34988 +2006 306 6.1 -1.9 3.9 0 360 271.74 34813 +2006 307 4.7 -5.8 1.81 0.05 112 169.71 34639 +2006 308 6.2 -6 2.85 0 174 120.12 34468 +2006 309 13.2 -0.2 9.52 0 720 133.27 34298 +2006 310 12.7 2.6 9.92 0 545.56 71.95 34130 +2006 311 14.2 -2.3 9.66 0 403.33 247.07 33964 +2006 312 13.9 -2.9 9.28 0 334.44 236.02 33801 +2006 313 18.4 -1.1 13.04 0 646.67 150 33640 +2006 314 11.9 0.9 8.88 0 588.89 225.83 33481 +2006 315 9.1 -3.9 5.53 0 297.78 125.58 33325 +2006 316 10.6 1 7.96 0.12 202.22 106.94 33171 +2006 317 10.6 -0.8 7.46 0 328.89 125.68 33019 +2006 318 12 2.9 9.5 0 428.89 98.4 32871 +2006 319 17.4 2 13.16 0 365.56 175.04 32725 +2006 320 19.7 -0.5 14.15 0 583.33 216.92 32582 +2006 321 14.3 2.3 11 0 135.56 197.23 32441 +2006 322 19.1 3.9 14.92 0 488.89 143.04 32304 +2006 323 13.5 4.7 11.08 0.01 137.78 135.34 32170 +2006 324 9.4 3 7.64 0.58 41.11 32.6 32039 +2006 325 9.6 3.5 7.92 0.28 68.89 116.13 31911 +2006 326 7.7 5.1 6.99 2.24 32.22 21.53 31786 +2006 327 12.6 5.4 10.62 0 352.22 105.46 31665 +2006 328 12 0.4 8.81 0 207.78 175.21 31547 +2006 329 17.9 0.9 13.22 0 491.11 171.05 31433 +2006 330 14.3 4.4 11.58 0.07 23.33 46.53 31322 +2006 331 9.2 7.8 8.81 0.06 34.44 28.49 31215 +2006 332 9 6.8 8.39 0.01 20 42.33 31112 +2006 333 8.6 6.8 8.1 0.01 34.44 34.6 31012 +2006 334 10 6.6 9.07 0 115.56 42.84 30917 +2006 335 8.6 6.1 7.91 0 152.22 65.99 30825 +2006 336 7.2 -0.1 5.19 0 208.89 39.44 30738 +2006 337 6.7 -0.5 4.72 0 73.33 137.92 30654 +2006 338 5.7 -0.6 3.97 0 44.44 62.77 30575 +2006 339 10.3 -0.1 7.44 0 161.11 106.42 30500 +2006 340 16.4 0.4 12 0 392.22 164.81 30430 +2006 341 13.6 6.5 11.65 0 276.67 127.73 30363 +2006 342 16.2 0.9 11.99 0 470 156.38 30301 +2006 343 15.2 9.8 13.72 0.7 401.11 75.75 30244 +2006 344 10.7 4.9 9.11 0.47 91.11 52.69 30191 +2006 345 8.6 1.1 6.54 0 64.44 122.74 30143 +2006 346 5.2 -2.5 3.08 0 77.78 130.83 30099 +2006 347 4.7 -2.6 2.69 0 11.25 95.7 30060 +2006 348 3.7 -1.8 2.19 0 10 113.42 30025 +2006 349 0.3 -1.9 -0.3 0 10 41.85 29995 +2006 350 0.6 -0.9 0.19 0 10 34.95 29970 +2006 351 1 -0.6 0.56 0.58 10 17.51 29950 +2006 352 5.1 1 3.97 0 128.75 43.77 29934 +2006 353 3.7 1.7 3.15 0 213.75 72.58 29924 +2006 354 6.7 -3 4.03 0.01 232.5 138.57 29918 +2006 355 5.9 1 4.55 0.01 137.5 72.95 29916 +2006 356 7.2 -0.4 5.11 0 233.75 108.32 29920 +2006 357 5.7 -3.4 3.2 0 93.75 119.08 29928 +2006 358 1.7 -2.6 0.52 0 27.5 18.62 29941 +2006 359 6.9 -0.4 4.89 0 212.5 111.71 29959 +2006 360 5.5 -2.3 3.36 0 253.75 157.03 29982 +2006 361 4.7 -6 1.76 0 147.5 187.85 30009 +2006 362 -0.2 -6.2 -1.85 0 20 64.18 30042 +2006 363 4.7 -3.9 2.34 0 95 103.96 30078 +2006 364 1.9 -5.5 -0.14 0 85 161.17 30120 +2006 365 2.1 -1.6 1.08 0 10 61.05 30166 +2007 1 6.9 -2.6 4.29 0.08 193.75 37.3 30217 +2007 2 9.2 -0.3 6.59 0 137.5 70.17 30272 +2007 3 9.5 -3 6.06 0 342.5 104.96 30331 +2007 4 7.2 -2 4.67 0.14 355 83.05 30396 +2007 5 11.2 -1.6 7.68 0 308.75 95.59 30464 +2007 6 11.5 0.9 8.59 0 461.25 90.86 30537 +2007 7 14.4 -0.1 10.41 0 445 142.72 30614 +2007 8 9.2 -3 5.84 0 142.5 129.1 30695 +2007 9 11.2 -1.7 7.65 0.02 245 119.59 30781 +2007 10 13.8 1.4 10.39 0 377.5 146.28 30870 +2007 11 16 1 11.88 0.01 500 172.59 30964 +2007 12 12.4 4 10.09 0 651.11 185.24 31061 +2007 13 13.8 -0.7 9.81 0 745.56 157.79 31162 +2007 14 15.1 -2.3 10.32 0 411.11 164.25 31268 +2007 15 11.9 -2.8 7.86 0 387.78 184.71 31376 +2007 16 6.7 -4.5 3.62 0 152.22 173 31489 +2007 17 10.7 -2.5 7.07 0 298.89 170.35 31605 +2007 18 11.9 -2.1 8.05 0.01 356.67 97.03 31724 +2007 19 11.3 7.6 10.28 1.51 88 40.76 31847 +2007 20 8.4 2.7 6.83 0.02 83 67.19 31974 +2007 21 11.8 0.1 8.58 0 117 167.52 32103 +2007 22 8.5 3.8 7.21 0.1 84 35.09 32236 +2007 23 3.8 1.3 3.11 1.28 17 11.54 32372 +2007 24 4.4 -1.1 2.89 0.92 29 81.99 32510 +2007 25 1.1 -4 -0.3 0 48 157.82 32652 +2007 26 0.9 -7.4 -1.38 0 146 213.21 32797 +2007 27 5 -9.4 1.04 0.06 181 193.92 32944 +2007 28 7.7 -4.5 4.35 0 181 155.37 33094 +2007 29 11.1 -2.9 7.25 0 468 118.01 33247 +2007 30 13.1 -1.6 9.06 0 283 208.1 33402 +2007 31 10 -3.4 6.31 0 298 220.66 33559 +2007 32 12.9 -1.4 8.97 0 605 232.64 33719 +2007 33 10.2 -3.5 6.43 0 386 217.86 33882 +2007 34 10.1 -0.8 7.1 0.06 449 207.74 34046 +2007 35 9.7 -3.5 6.07 0 406 235.6 34213 +2007 36 12.5 -5.2 7.63 0 507 245.37 34382 +2007 37 9.9 -1.3 6.82 0.8 287 216.04 34552 +2007 38 6.3 3.2 5.45 0.03 60 68.64 34725 +2007 39 13 1.5 9.84 0 386 246.68 34900 +2007 40 11.2 4.4 9.33 0.08 220 155.8 35076 +2007 41 12.2 -0.1 8.82 0 73.75 251.58 35254 +2007 42 8.7 -0.6 6.14 0 146 157.33 35434 +2007 43 12.7 0.3 9.29 1.1 290 182.91 35615 +2007 44 13.6 5.3 11.32 0 295 111.44 35798 +2007 45 13.7 -1.1 9.63 0 589 286.59 35983 +2007 46 10.2 3.5 8.36 0.26 170 100 36169 +2007 47 6.7 1.8 5.35 0 188 52.15 36356 +2007 48 8.6 1.4 6.62 0 249 183.08 36544 +2007 49 6 -1.6 3.91 0 202 222.09 36734 +2007 50 4.4 -2.8 2.42 0 36 142.21 36925 +2007 51 12.4 -1.5 8.58 0 270 266.01 37117 +2007 52 4.8 -1.9 2.96 0 14 92.25 37310 +2007 53 10.7 4 8.86 0 121.82 161.55 37505 +2007 54 11.8 1.7 9.02 0 303.64 177.47 37700 +2007 55 9.2 2.9 7.47 0 167.27 157.49 37896 +2007 56 6.2 -0.1 4.47 1.7 162.73 137.82 38093 +2007 57 6.4 0.5 4.78 0.02 60 92.16 38291 +2007 58 11 0.1 8 0.04 295.45 255.99 38490 +2007 59 11.5 3.6 9.33 0.01 244.55 121.38 38689 +2007 60 15.4 2 11.72 0 400 146.2 38890 +2007 61 13 5.2 10.86 0.1 129.17 64.1 39091 +2007 62 9.3 0.9 6.99 0.03 79.17 78.16 39292 +2007 63 12.9 0.9 9.6 0 555 332.36 39495 +2007 64 15.4 -2.8 10.4 0 525.83 350.84 39697 +2007 65 16.9 1.6 12.69 0 587.5 319.14 39901 +2007 66 16.9 7.2 14.23 0.02 660.83 235.8 40105 +2007 67 12.8 5.7 10.85 1.25 60.83 53.16 40309 +2007 68 11.6 6.8 10.28 0 275.83 134.03 40514 +2007 69 13.4 2.9 10.51 0 415 216.58 40719 +2007 70 13 4.9 10.77 0 530 341.51 40924 +2007 71 15.8 -2.4 10.8 0 524.17 369.74 41130 +2007 72 18.3 -1 12.99 0 631.67 356.11 41336 +2007 73 19.7 -0.3 14.2 0 715.83 359.67 41543 +2007 74 14.7 5.3 12.12 0 614.17 386.01 41749 +2007 75 16.4 -1.6 11.45 0 616.67 355.71 41956 +2007 76 19.6 -1.1 13.91 0 766.67 292.52 42163 +2007 77 19.5 2.4 14.8 0.05 959.17 342.17 42370 +2007 78 15.3 1.6 11.53 4.37 40 42.96 42578 +2007 79 4 0.4 3.01 0.3 45.83 147.06 42785 +2007 80 5.7 -2.1 3.56 0 192.5 144.93 42992 +2007 81 8.7 -2.5 5.62 0 370 297.01 43200 +2007 82 10.5 -0.5 7.47 1.83 360.83 141.28 43407 +2007 83 6.8 4.3 6.11 0.5 68.33 52.25 43615 +2007 84 14.2 3.2 11.17 0 415 360.5 43822 +2007 85 13.9 -0.1 10.05 0 503.33 275.79 44029 +2007 86 13.3 1.4 10.03 0 555.83 335.87 44236 +2007 87 13.6 -1.6 9.42 0.01 599.17 334.95 44443 +2007 88 12 5.5 10.21 0 235 217.92 44650 +2007 89 13.4 -0.8 9.5 0 377.5 316.59 44857 +2007 90 15.5 6.3 12.97 0 693.33 313.06 45063 +2007 91 17 1.1 12.63 0 748.33 310.98 45270 +2007 92 17.4 3.7 13.63 0 921.54 422.46 45475 +2007 93 18.6 1 13.76 0.31 706.92 358.74 45681 +2007 94 12.1 5.8 10.37 0 364.62 250.86 45886 +2007 95 15.4 -2.1 10.59 0 726.15 454.67 46091 +2007 96 19.8 -0.3 14.27 0 940.71 424.47 46295 +2007 97 19.6 7.2 16.19 0 862.14 408.77 46499 +2007 98 17.7 7 14.76 0 808.57 438.68 46702 +2007 99 21.2 0.1 15.4 0 875.71 405.71 46905 +2007 100 23.2 2.5 17.51 0 1151.43 345.99 47107 +2007 101 19.9 4.1 15.56 0 792.14 407.53 47309 +2007 102 23.2 3.1 17.67 0 951.43 444.65 47510 +2007 103 24.5 3.9 18.84 0 1165 453.56 47710 +2007 104 24.4 4.6 18.95 0 1283.57 447.83 47910 +2007 105 22.2 3.3 17 0 1173.57 478.19 48108 +2007 106 19.6 2.9 15.01 0 1036.43 472.54 48306 +2007 107 22.2 1.7 16.56 0 1271.43 467.79 48504 +2007 108 18.4 3.7 14.36 0 629.29 225.05 48700 +2007 109 17.1 2.4 13.06 0 815 433.28 48895 +2007 110 22.7 1.1 16.76 0 1036.43 455.28 49089 +2007 111 17.9 6.6 14.79 0 750.71 456.25 49282 +2007 112 19.7 0.9 14.53 0 943.57 470.74 49475 +2007 113 23.7 1.4 17.57 0 1362.14 463.65 49666 +2007 114 21.1 7.7 17.41 0 934.29 216.47 49855 +2007 115 21.4 5.8 17.11 0 928.57 447.66 50044 +2007 116 22.7 3.4 17.39 0 984.29 426.32 50231 +2007 117 23.7 4 18.28 0 1332.14 456.99 50417 +2007 118 24.6 3 18.66 0 1575.71 487.58 50601 +2007 119 25.1 5.2 19.63 0 1190 451.73 50784 +2007 120 18.2 8.7 15.59 0 830.71 383.03 50966 +2007 121 17.9 0.6 13.14 0 896.43 475.5 51145 +2007 122 17.6 6.8 14.63 0 915.71 452.71 51324 +2007 123 21.2 2.5 16.06 0.86 960 336.31 51500 +2007 124 18.2 11.9 16.47 1.24 562.14 285.03 51674 +2007 125 20.2 12.2 18 0.54 317.33 283.4 51847 +2007 126 20.5 11.9 18.13 0.01 330.67 298.94 52018 +2007 127 24.2 10.9 20.54 0 971.33 479.31 52187 +2007 128 23.2 10.2 19.63 1.34 633.33 272.85 52353 +2007 129 17.5 12.6 16.15 0.12 159.33 180.92 52518 +2007 130 23.1 12.3 20.13 0 696.67 408.32 52680 +2007 131 27.8 10.7 23.1 0.5 1278.67 497.09 52840 +2007 132 23.3 12.7 20.39 0.09 370 290.75 52998 +2007 133 26.2 11.5 22.16 0 884 441.22 53153 +2007 134 29.6 16.6 26.03 0 1619.33 486.66 53306 +2007 135 25.6 12.8 22.08 1 404.67 102.01 53456 +2007 136 15.9 6 13.18 0.12 433.33 256.53 53603 +2007 137 19.1 5 15.22 0.44 490.67 402.78 53748 +2007 138 17.7 7 14.76 0 732 503.05 53889 +2007 139 21.2 4.5 16.61 0 745.33 373.16 54028 +2007 140 25.2 9.3 20.83 0 712.67 399.24 54164 +2007 141 27.1 10.6 22.56 0 994.67 457.72 54297 +2007 142 30.3 12.3 25.35 0 1402.5 470.58 54426 +2007 143 28.7 15.2 24.99 0 1190.62 475.37 54552 +2007 144 28.7 15.3 25.02 0 1085.62 444.23 54675 +2007 145 30.7 14.3 26.19 0 1440 459.73 54795 +2007 146 29.6 15.2 25.64 0 1277.5 458.05 54911 +2007 147 28.2 15 24.57 0 1225 413.09 55023 +2007 148 23.2 14.6 20.83 1.1 601.88 249.59 55132 +2007 149 21.1 11 18.32 0.25 536.87 346.33 55237 +2007 150 14.8 10.5 13.62 0.01 316.25 121.06 55339 +2007 151 21.4 8 17.72 0 838.75 385.98 55436 +2007 152 24.7 6.4 19.67 0 971.88 430.4 55530 +2007 153 22.8 12.9 20.08 0.22 426.88 281.44 55619 +2007 154 25 11.1 21.18 0.77 676.88 368.37 55705 +2007 155 24 15.5 21.66 0.85 451.25 283.78 55786 +2007 156 23.7 16 21.58 0.33 758.93 211.05 55863 +2007 157 25 14.6 22.14 0.14 439.38 260.34 55936 +2007 158 25.8 13.7 22.47 0.17 745 429.77 56004 +2007 159 26.9 12.6 22.97 0.01 723.12 343.52 56068 +2007 160 28.6 12.4 24.15 0 1183.75 410.96 56128 +2007 161 28.8 13.5 24.59 0 1138.13 389.75 56183 +2007 162 28.8 16.5 25.42 0 1289.38 438.46 56234 +2007 163 28.1 17.9 25.3 0 938.75 327.01 56280 +2007 164 28.7 13.4 24.49 0 1271.25 455.33 56321 +2007 165 29.7 13.9 25.36 0 1225 468.13 56358 +2007 166 30.2 15.5 26.16 0 1289.38 453.08 56390 +2007 167 27.7 17.6 24.92 0 1270 434.68 56418 +2007 168 28.4 14.1 24.47 0 1112.5 381.97 56440 +2007 169 29.6 15.6 25.75 0.41 1385.63 404.18 56458 +2007 170 29.8 18.1 26.58 0.02 1170.63 406.16 56472 +2007 171 32.5 14.5 27.55 0 1501.25 439.76 56480 +2007 172 33.9 19.1 29.83 0 1723.13 432.73 56484 +2007 173 31.2 16.3 27.1 0.04 1480.62 384.87 56482 +2007 174 28.7 13.1 24.41 0.02 995 256.11 56476 +2007 175 29.2 15.8 25.52 0 1397.5 382.87 56466 +2007 176 32.7 14.5 27.7 0 2018.75 463.25 56450 +2007 177 30 17.1 26.45 0 1099.37 268.84 56430 +2007 178 20 13.5 18.21 0.5 436.88 153.22 56405 +2007 179 22 12.7 19.44 0 650 340.84 56375 +2007 180 25.2 10.1 21.05 0.01 1046.25 348.7 56341 +2007 181 25.4 14.7 22.46 0.03 955.63 325.52 56301 +2007 182 29.4 12 24.61 0 1591.25 467.97 56258 +2007 183 31.5 14.4 26.8 0.07 1837.5 447.11 56209 +2007 184 28.2 13.8 24.24 0 1041.88 415.4 56156 +2007 185 25.2 13.1 21.87 1.27 283.75 63.48 56099 +2007 186 23.9 11.5 20.49 0 1028.13 428.09 56037 +2007 187 26.4 10.9 22.14 0 1391.25 319.72 55971 +2007 188 28.8 11.6 24.07 0.05 1460.62 444.62 55900 +2007 189 29.2 17 25.84 0.19 1520.63 408.23 55825 +2007 190 31.3 16.2 27.15 2.95 1565 403.79 55746 +2007 191 26.9 12 22.8 0.31 340 214.83 55663 +2007 192 21.4 7.1 17.47 0.04 688.12 324.22 55575 +2007 193 23.7 8.4 19.49 0 943.75 295.43 55484 +2007 194 27 11.5 22.74 0 1347.5 391.98 55388 +2007 195 31.2 11.8 25.87 0 1611.88 479.37 55289 +2007 196 33.2 15 28.2 0 1751.87 470.96 55186 +2007 197 34.5 17.6 29.85 0 2331.87 499.11 55079 +2007 198 37.2 14.7 31.01 0 2902.5 480.61 54968 +2007 199 37.1 15.4 31.13 0 2647.5 468.23 54854 +2007 200 36.2 18.8 31.42 0 2468.12 450.45 54736 +2007 201 38.5 17.5 32.73 0 2975 473.89 54615 +2007 202 35 16.3 29.86 0 2425 470.8 54490 +2007 203 34.7 20.5 30.8 0 2460 487.16 54362 +2007 204 31.9 11.5 26.29 0 1942.5 487.4 54231 +2007 205 29.8 16.4 26.12 0.61 1393.12 252.09 54097 +2007 206 27.9 12 23.53 0 1416.88 420.2 53960 +2007 207 28.8 10 23.63 0 1720 513.95 53819 +2007 208 32.2 11.1 26.4 0.04 1592.5 424.44 53676 +2007 209 32.7 18.9 28.91 0.58 1348.67 367.93 53530 +2007 210 28.2 18 25.4 1.66 1148.57 334.91 53382 +2007 211 24.8 13.9 21.8 1.46 130.71 61.7 53230 +2007 212 23.2 7.9 18.99 0 970.71 417.34 53076 +2007 213 24 8.5 19.74 0 1263.57 502.88 52920 +2007 214 27.6 7.5 22.07 0 1537.86 479.02 52761 +2007 215 24.5 12.1 21.09 0.16 539.29 131.78 52600 +2007 216 24.7 12.1 21.23 0 1334.29 452.59 52437 +2007 217 26.2 10.5 21.88 0 1454.29 474.58 52271 +2007 218 29.2 10.1 23.95 0 1590.71 438.49 52103 +2007 219 31 12.5 25.91 0.29 1851.43 435.58 51934 +2007 220 29.6 15 25.59 0 1395.71 346.88 51762 +2007 221 30.5 15.2 26.29 1.7 1456.07 330.99 51588 +2007 222 22.5 15.3 20.52 0.14 545.71 273.38 51413 +2007 223 21.3 15.5 19.7 0.62 353.57 167.48 51235 +2007 224 25.2 16 22.67 0.02 459.29 228.34 51057 +2007 225 28.6 13.9 24.56 0 1075 421.39 50876 +2007 226 28.9 12.9 24.5 0 1361.43 468.94 50694 +2007 227 30.5 14.1 25.99 0 1365 475.27 50510 +2007 228 32.2 16.1 27.77 0 1769.29 456.32 50325 +2007 229 27.6 19.7 25.43 0.23 1183.57 450.1 50138 +2007 230 26.4 12.6 22.61 0 1246.43 455.57 49951 +2007 231 25.8 15.2 22.89 0 563.57 240.32 49761 +2007 232 23 13.7 20.44 3.84 237.86 147.35 49571 +2007 233 25.7 14.3 22.57 0.22 919.29 412.31 49380 +2007 234 27.2 16.5 24.26 0.17 812.86 372.67 49187 +2007 235 29.3 17.5 26.06 0.27 1083.57 399.38 48993 +2007 236 28.7 15.3 25.02 0 1006.43 430.14 48798 +2007 237 28.8 16.9 25.53 0 1394.29 376.98 48603 +2007 238 29.8 14.7 25.65 0 1489.29 358.34 48406 +2007 239 30.1 14.1 25.7 0 1735.71 469.85 48208 +2007 240 23.1 15.3 20.96 0.01 877.14 334.8 48010 +2007 241 19.8 14.5 18.34 2.83 161.43 95.5 47811 +2007 242 15.9 12.2 14.88 0.3 120.71 69.06 47611 +2007 243 21.2 9.4 17.95 0 485.71 294.53 47410 +2007 244 24 9.7 20.07 0 701.43 243.51 47209 +2007 245 22.3 9.8 18.86 0 783.08 367.94 47007 +2007 246 24.6 11.8 21.08 1.84 960 379.1 46805 +2007 247 19.6 11.4 17.34 0 293.08 119.45 46601 +2007 248 14.5 7.6 12.6 0.56 408.46 226.87 46398 +2007 249 11.3 8 10.39 2.45 140.77 68.09 46194 +2007 250 12.7 8.9 11.65 2.27 72.31 64.11 45989 +2007 251 18.6 11.6 16.68 0 558.46 194.52 45784 +2007 252 21.2 9.3 17.93 0 496.15 146.35 45579 +2007 253 20.4 6.5 16.58 0.4 560 237.4 45373 +2007 254 19.4 11.9 17.34 0.22 496.92 328.46 45167 +2007 255 20.9 6.5 16.94 0 550.77 198.1 44961 +2007 256 20.5 8.6 17.23 0 789.17 366.08 44755 +2007 257 22.6 6.1 18.06 0.02 785 415.79 44548 +2007 258 23.1 10.4 19.61 0 747.5 275.97 44341 +2007 259 23.4 8.1 19.19 0 773.33 354.45 44134 +2007 260 25.5 8.9 20.93 0 755.83 315.75 43927 +2007 261 21.7 12 19.03 3.86 303.33 73.6 43719 +2007 262 17.6 6.3 14.49 0 598.33 397.44 43512 +2007 263 17.1 1.7 12.87 0 609.17 406.1 43304 +2007 264 18.7 2 14.11 0 685.83 439.28 43097 +2007 265 20 2 15.05 0 753.33 427.27 42890 +2007 266 20.4 3.4 15.72 0 725.83 355.86 42682 +2007 267 21.2 4.8 16.69 0 790.83 392.69 42475 +2007 268 21 5.3 16.68 0 590.83 329.44 42268 +2007 269 16.7 12.3 15.49 0.25 401.67 184.18 42060 +2007 270 15.7 11.4 14.52 3.89 155.83 131.57 41854 +2007 271 17.5 10.1 15.47 0.27 385 341.85 41647 +2007 272 20.6 9.2 17.47 0 681.67 363.93 41440 +2007 273 21.9 4.4 17.09 0 723.33 377.86 41234 +2007 274 22.2 4.5 17.33 0 745 364.03 41028 +2007 275 21.9 5.3 17.34 0 712.73 303.58 40822 +2007 276 22.8 8.9 18.98 0 405.45 264.39 40617 +2007 277 18.5 11.2 16.49 0 168.18 135.84 40412 +2007 278 18.5 9.6 16.05 0.43 133.64 119.63 40208 +2007 279 16 11.1 14.65 0 321.82 146.94 40003 +2007 280 17 6.5 14.11 0 409.09 309.62 39800 +2007 281 18.7 1.7 14.02 0 563.64 370.51 39597 +2007 282 17.6 2.9 13.56 0 430.91 326.98 39394 +2007 283 15.2 3.7 12.04 0 325.45 240.46 39192 +2007 284 16.7 7.9 14.28 0 491.82 246.49 38991 +2007 285 17.9 2.9 13.77 0.08 432.73 253.04 38790 +2007 286 13.9 6.5 11.87 0 491.82 224.09 38590 +2007 287 12.9 -1.6 8.91 0 578.18 357.19 38391 +2007 288 14.5 -2.5 9.82 0 621.82 343.2 38193 +2007 289 17.1 -1.7 11.93 0 596.36 321.68 37995 +2007 290 17.9 0.1 13 0 610.91 316.83 37799 +2007 291 10.5 1.9 8.13 0.49 193.64 67.16 37603 +2007 292 12.3 2.2 9.52 0 567.27 257.49 37408 +2007 293 6.5 -2.8 3.94 0.05 231.82 92.3 37214 +2007 294 7.2 1.2 5.55 0.03 203.64 89.53 37022 +2007 295 7.5 4 6.54 1.56 252.73 58.24 36830 +2007 296 6.9 4.7 6.3 1.7 175.45 46.39 36640 +2007 297 7.6 4.3 6.69 0.07 93.64 53.82 36451 +2007 298 9.9 6.7 9.02 0.1 149.09 60.95 36263 +2007 299 8.3 5.6 7.56 0.31 131.23 39.07 36076 +2007 300 10 6 8.9 0.09 205.05 77.54 35891 +2007 301 8.2 7.1 7.9 1.53 56.5 22.77 35707 +2007 302 13 7.7 11.54 0 309.53 82.83 35525 +2007 303 10.2 7.7 9.51 0.34 137.27 65.95 35345 +2007 304 13.9 7.3 12.09 0 387.48 263.19 35166 +2007 305 12.8 0.5 9.42 0 546.98 281.13 34988 +2007 306 15.3 -0.8 10.87 0 724.87 216.53 34813 +2007 307 15.3 7.8 13.24 0 462.63 135.2 34639 +2007 308 12 6.5 10.49 0.22 300.45 90.08 34468 +2007 309 10.6 2.2 8.29 0 378.01 216.1 34298 +2007 310 6.6 -2.2 4.18 0 221.11 98.32 34130 +2007 311 10.1 -1.8 6.83 0.02 514.44 184.46 33964 +2007 312 13.9 -0.3 10 0.01 503.33 90.99 33801 +2007 313 8.6 1 6.51 0.72 173.33 23.34 33640 +2007 314 10.5 -1.5 7.2 0 518.89 167.46 33481 +2007 315 11.2 0.2 8.17 0.34 274.44 136.77 33325 +2007 316 10.1 -0.3 7.24 0 537.78 229.26 33171 +2007 317 7.8 -1.6 5.21 0 240 193.75 33019 +2007 318 5.7 -0.7 3.94 0 176.67 82.85 32871 +2007 319 3.4 1.9 2.99 0 257.78 57.03 32725 +2007 320 3.1 0.4 2.36 0 255.56 73.84 32582 +2007 321 2.7 -0.7 1.77 0.32 194.44 85.72 32441 +2007 322 3.2 0 2.32 0.78 70 58.96 32304 +2007 323 2.7 0.4 2.07 0 92.22 127.99 32170 +2007 324 1.5 -1.6 0.65 0 140 82.81 32039 +2007 325 8.2 -0.6 5.78 0 241.11 175.12 31911 +2007 326 14.6 -0.6 10.42 0 348.89 175.19 31786 +2007 327 16.2 10.9 14.74 0 685.56 140.65 31665 +2007 328 13.8 6.2 11.71 0 323.33 148.96 31547 +2007 329 7.5 3.5 6.4 0.8 172.22 31.58 31433 +2007 330 8.3 0.4 6.13 0 412.22 178.61 31322 +2007 331 5.1 -2.3 3.06 0 191.11 93.55 31215 +2007 332 5.1 -5.1 2.29 0 262.22 199.42 31112 +2007 333 4.2 -8.9 0.6 0 278.89 214.31 31012 +2007 334 4.7 -5.4 1.92 0 178.89 133.97 30917 +2007 335 8.5 -1.6 5.72 0.01 282.22 168.24 30825 +2007 336 8.6 -1.7 5.77 0.05 186.67 133.45 30738 +2007 337 11.2 0.8 8.34 0.44 377.78 26.38 30654 +2007 338 4.5 -1.9 2.74 0.02 236.67 59.68 30575 +2007 339 8.4 -3 5.27 0 361.11 150.03 30500 +2007 340 9.3 -1.5 6.33 0 365.56 152.58 30430 +2007 341 4.2 -1.1 2.74 1.71 330 70.54 30363 +2007 342 8.9 2.2 7.06 0 243.33 96.5 30301 +2007 343 5.8 -1.8 3.71 0.28 232.22 101.34 30244 +2007 344 5.6 1.9 4.58 0 128.89 55.81 30191 +2007 345 7.8 0.3 5.74 0.56 191.11 61.33 30143 +2007 346 6 3.9 5.42 0.82 167.78 22.87 30099 +2007 347 6.1 2.5 5.11 0 346.25 101.13 30060 +2007 348 2.5 -1.9 1.29 0.33 120 46.98 30025 +2007 349 0.8 -3.5 -0.38 0.09 162.5 100.09 29995 +2007 350 0.7 -1.3 0.15 0.03 126.25 85.6 29970 +2007 351 -0.7 -2.6 -1.22 0.02 145 56.13 29950 +2007 352 -2.2 -7.8 -3.74 0 65 61.84 29934 +2007 353 -2 -11.2 -4.53 0 96.25 74.46 29924 +2007 354 -2.5 -4.6 -3.08 0 60 49.14 29918 +2007 355 -4.4 -5.9 -4.81 0 60 46.53 29916 +2007 356 -4.7 -6.1 -5.09 0 60 40.07 29920 +2007 357 -4.2 -5.1 -4.45 0 60 34.69 29928 +2007 358 -2.3 -5.5 -3.18 0 60 32.75 29941 +2007 359 -2.2 -4.6 -2.86 0.03 63.75 50.43 29959 +2007 360 -1.3 -4.5 -2.18 0 70 37.29 29982 +2007 361 -1.4 -2.5 -1.7 0 70 31.62 30009 +2007 362 -2.5 -4 -2.91 0 62.5 28.88 30042 +2007 363 -3.3 -4.4 -3.6 0 60 26.18 30078 +2007 364 -4.1 -5.1 -4.38 0 60 29.42 30120 +2007 365 -0.2 -4.8 -1.47 0.02 71.25 47.86 30166 +2008 1 1.3 -4.8 -0.38 0.04 166.45 59.32 30217 +2008 2 -0.2 -3.8 -1.19 0 98.64 55.81 30272 +2008 3 -1.1 -2.7 -1.54 0 44.9 35.64 30331 +2008 4 -2.7 -5.7 -3.53 0 71.39 44.72 30396 +2008 5 -2.7 -6 -3.61 0.03 77.54 70.3 30464 +2008 6 0.9 -3.9 -0.42 0.02 134.56 59.82 30537 +2008 7 3.4 -6 0.82 0.01 257.5 110.99 30614 +2008 8 7.6 -4.7 4.22 0 394.56 198.02 30695 +2008 9 2.1 -4.7 0.23 0 190.05 158.47 30781 +2008 10 -0.3 -2 -0.77 0 50.06 71.23 30870 +2008 11 5.1 -1.7 3.23 0 230.77 81.09 30964 +2008 12 14.1 3.9 11.3 0 530.7 129.86 31061 +2008 13 9.2 0.6 6.83 0.21 352.25 48.84 31162 +2008 14 7.3 -0.3 5.21 0 287.32 72.9 31268 +2008 15 9 -0.3 6.44 0 366.22 144.17 31376 +2008 16 10.7 3.5 8.72 0 341.15 126.35 31489 +2008 17 8.7 5 7.68 0 177.33 36.95 31605 +2008 18 9.4 1.8 7.31 0 327.49 89.41 31724 +2008 19 7.7 2.2 6.19 0.1 231.3 54.29 31847 +2008 20 17.5 2.4 13.35 0 805.44 242.77 31974 +2008 21 13.2 1 9.84 0 558.08 212.01 32103 +2008 22 7 -1.2 4.75 0 297.16 51.77 32236 +2008 23 5.7 -1 3.86 0 237.17 169.22 32372 +2008 24 7.6 -5 4.13 0 399.47 215.77 32510 +2008 25 9.1 -2.6 5.88 0 422.7 175.89 32652 +2008 26 8.5 -5.2 4.73 0 440.92 222.91 32797 +2008 27 13 -2.2 8.82 0 613.97 62.27 32944 +2008 28 10.7 3.7 8.77 0 334.19 67.18 33094 +2008 29 10.1 -1.1 7.02 0 439.24 154.88 33247 +2008 30 7.3 0.2 5.35 0 273.7 167.17 33402 +2008 31 7.5 -1.8 4.94 0 333.24 166.67 33559 +2008 32 10.2 0.2 7.45 0 413.12 171.73 33719 +2008 33 10.2 4.2 8.55 0.8 288.6 26.92 33882 +2008 34 6.2 -0.6 4.33 0.02 247.48 155.8 34046 +2008 35 10.8 2.2 8.44 0.06 388.83 172.26 34213 +2008 36 9.3 2.9 7.54 0.05 286.96 97.93 34382 +2008 37 9.6 -0.7 6.77 0.01 405.23 136.8 34552 +2008 38 9.9 -0.9 6.93 0 424.73 264.76 34725 +2008 39 8.7 0.4 6.42 0 333.37 222.98 34900 +2008 40 8.4 -4.6 4.83 0 329 273.42 35076 +2008 41 8.4 -4.6 4.83 0 291 254.77 35254 +2008 42 6.6 -3.2 3.9 0 263 199.86 35434 +2008 43 6.2 -4.4 3.29 0 288 260.39 35615 +2008 44 8.4 -6.8 4.22 0 350 302.46 35798 +2008 45 3.8 -3.5 1.79 0 199 161.53 35983 +2008 46 3.8 -0.1 2.73 0 327 194.45 36169 +2008 47 0.8 -3.6 -0.41 0 338 253.25 36356 +2008 48 0.9 -11.5 -2.51 0 331 295.36 36544 +2008 49 11.9 -7.4 6.59 0 595 150.98 36734 +2008 50 12.2 -3.9 7.77 0 583 275.27 36925 +2008 51 12.9 -5.5 7.84 0 519 299.53 37117 +2008 52 14 -3.6 9.16 0 604 249.32 37310 +2008 53 16.6 1 12.31 0.04 741.82 206.65 37505 +2008 54 17.5 2.7 13.43 0 710.91 259.32 37700 +2008 55 17.7 -1.4 12.45 0 820.91 304.28 37896 +2008 56 19.6 -1 13.94 0 980.91 313.06 38093 +2008 57 18.6 -1.3 13.13 0 805.45 312.37 38291 +2008 58 17.2 -0.6 12.31 0 782.73 232.66 38490 +2008 59 12.1 -0.5 8.63 0 500.91 205.59 38689 +2008 60 15.1 -0.5 10.81 0 600.91 226.62 38890 +2008 61 15.7 6.8 13.25 0.22 660.83 106.52 39091 +2008 62 18.7 3.8 14.6 0 889.17 274.81 39292 +2008 63 18.6 1.9 14.01 0.8 690 184.49 39495 +2008 64 14 3.8 11.2 0 389.17 100.43 39697 +2008 65 6.1 1.6 4.86 0 342.5 158.41 39901 +2008 66 4.5 -2.4 2.6 0 387.5 214.27 40105 +2008 67 6.6 0.8 5 0.3 416.67 103.56 40309 +2008 68 6.5 2.6 5.43 0.4 105 94.4 40514 +2008 69 12.6 0.1 9.16 0 300 293 40719 +2008 70 15 -1 10.6 0 647.5 360.34 40924 +2008 71 10.7 6.6 9.57 0.34 324.17 98.92 41130 +2008 72 16.7 0.5 12.24 0.14 480 191.14 41336 +2008 73 14.4 0.5 10.58 0 890.83 322.94 41543 +2008 74 13.4 -0.9 9.47 0 577.5 142.12 41749 +2008 75 14.8 4 11.83 0 605.83 279.92 41956 +2008 76 19.5 7.3 16.15 0.15 903.33 271.36 42163 +2008 77 16.8 4.5 13.42 0 568.33 277.03 42370 +2008 78 7.7 2.3 6.21 0.1 185 155.57 42578 +2008 79 9 -4 5.43 0 397.5 356.74 42785 +2008 80 8.6 -3.7 5.22 0 385 394.22 42992 +2008 81 9.9 -1.6 6.74 0.62 510 196.12 43200 +2008 82 7.5 0.9 5.69 0.19 246.67 207.91 43407 +2008 83 6.6 0.1 4.81 2.2 200.83 108.54 43615 +2008 84 7.6 0.6 5.67 0.02 285.83 184.89 43822 +2008 85 7.6 -1.6 5.07 0 458.33 315.18 44029 +2008 86 10 -3.4 6.31 0 530.83 322.95 44236 +2008 87 11.9 -0.1 8.6 0 424.17 201.15 44443 +2008 88 12.4 4.5 10.23 0 413.33 279.68 44650 +2008 89 15.2 5.7 12.59 0 475.83 273.37 44857 +2008 90 16.8 -1.2 11.85 0 851.67 439.69 45063 +2008 91 18.4 1.8 13.83 0 956.67 447.07 45270 +2008 92 19.2 2.3 14.55 0 905.38 406 45475 +2008 93 14.7 7 12.58 0.43 573.08 155.89 45681 +2008 94 13.2 -0.1 9.54 0 532.31 345.02 45886 +2008 95 12.7 5.9 10.83 0 586.15 298.81 46091 +2008 96 14.9 -0.1 10.78 0 620 353.37 46295 +2008 97 16.3 -1.7 11.35 0.05 828.57 397.94 46499 +2008 98 16.4 4.2 13.04 0.15 676.89 285.93 46702 +2008 99 9.8 3.4 8.04 0 295.89 241.15 46905 +2008 100 19.3 1 14.27 0 969.12 460.2 47107 +2008 101 21.1 11.6 18.49 0.01 761.76 235.84 47309 +2008 102 20.7 13.7 18.77 0 598.75 248.46 47510 +2008 103 16.6 8.9 14.48 0.38 508.7 213.52 47710 +2008 104 16.6 5.2 13.47 0 658.9 387.15 47910 +2008 105 17.7 0.7 13.02 0 856.92 466.7 48108 +2008 106 14.2 2.9 11.09 0.76 567.94 292.6 48306 +2008 107 15.5 1.7 11.71 0.15 684.32 326.82 48504 +2008 108 14.4 0.2 10.5 0.04 479.29 291.23 48700 +2008 109 18.4 2.6 14.06 0.03 707.86 295.73 48895 +2008 110 20.4 10.1 17.57 0.08 720 340.79 49089 +2008 111 21.9 4.1 17 0 1188.57 422.78 49282 +2008 112 23 6.5 18.46 0.5 865 360.08 49475 +2008 113 18.1 8.4 15.43 0.41 559.29 333.95 49666 +2008 114 15.6 9.1 13.81 0 547.86 345.25 49855 +2008 115 17 2.9 13.12 0 858.57 488.49 50044 +2008 116 17.7 2 13.38 0.07 627.86 276.67 50231 +2008 117 18.2 6 14.84 0.18 655.71 439.26 50417 +2008 118 20.1 3.8 15.62 0 1047.86 496.35 50601 +2008 119 21.7 1.1 16.04 0 1284.29 505.93 50784 +2008 120 18.7 6.6 15.37 0 804.29 330.99 50966 +2008 121 19.7 10.1 17.06 0 725 352.97 51145 +2008 122 19.2 10.6 16.83 1.35 531.43 234.92 51324 +2008 123 20.2 6.9 16.54 0.35 941.43 406.06 51500 +2008 124 19.9 5.3 15.89 0 980.71 508.28 51674 +2008 125 19.2 4.5 15.16 0.01 953.33 506.14 51847 +2008 126 17.7 3.4 13.77 0 564 365.07 52018 +2008 127 20.2 11.1 17.7 0.05 642.67 233.1 52187 +2008 128 20.1 5 15.95 0 960.67 492.58 52353 +2008 129 21.7 3.4 16.67 0 1141.33 517.62 52518 +2008 130 22 7.2 17.93 0 1078.67 426.96 52680 +2008 131 21.2 4.1 16.5 0 971.33 411.61 52840 +2008 132 20.7 5.7 16.57 0 1161.33 509.58 52998 +2008 133 23.2 2.9 17.62 0 1325.33 448.33 53153 +2008 134 24.2 4 18.65 0 1486 456.16 53306 +2008 135 24.4 5.7 19.26 0 1297.33 402.37 53456 +2008 136 26.7 6.5 21.15 0 1370.67 423.42 53603 +2008 137 25.5 9.7 21.16 0.56 1018 326.65 53748 +2008 138 24.8 13 21.56 0 1161.33 379.52 53889 +2008 139 22.8 17 21.2 0.2 868 203.2 54028 +2008 140 22 11.2 19.03 1.4 564 352.94 54164 +2008 141 13.7 9.2 12.46 0.23 206.67 115.28 54297 +2008 142 16.3 9.4 14.4 1.2 393.44 326.59 54426 +2008 143 19.5 10.6 17.05 0 667.19 305.15 54552 +2008 144 19.8 11.9 17.63 0.1 748.75 300.92 54675 +2008 145 24.3 12.9 21.17 0 883.13 410.7 54795 +2008 146 23.2 9.4 19.41 0 820.63 436.62 54911 +2008 147 27.3 12.7 23.29 0 925.63 396.58 55023 +2008 148 32.8 12.8 27.3 0 1761.25 493.98 55132 +2008 149 33 12.9 27.47 0 2338.13 468.06 55237 +2008 150 28.5 16.1 25.09 0 1465.62 441.3 55339 +2008 151 27.5 11.9 23.21 0.03 1256.25 435.05 55436 +2008 152 27.1 13.6 23.39 0 1433.13 498.86 55530 +2008 153 29.9 10.8 24.65 0.2 1520 458.11 55619 +2008 154 27.4 16.5 24.4 0.13 1317.5 425.46 55705 +2008 155 27 13.3 23.23 2.37 935.33 339.69 55786 +2008 156 23.1 16.2 21.2 0.37 676.3 177.72 55863 +2008 157 19.7 16.3 18.77 1.76 311.86 95.8 55936 +2008 158 23.5 15.1 21.19 0.4 799.6 218.83 56004 +2008 159 20.3 12.9 18.27 0.95 610.36 204.87 56068 +2008 160 22.7 14.9 20.56 0.06 725.21 213.7 56128 +2008 161 25.2 15 22.4 0 1002.68 356.7 56183 +2008 162 26.6 11.6 22.48 0 1355.03 460.74 56234 +2008 163 26.8 13.5 23.14 1.15 1285.97 323.9 56280 +2008 164 21.1 14.2 19.2 0 605.61 274.21 56321 +2008 165 20 12 17.8 0 635.31 323.74 56358 +2008 166 18.8 9 16.11 0.1 682.05 294.51 56390 +2008 167 20.9 10 17.9 0 822.98 421.02 56418 +2008 168 22.1 8 18.22 0.01 1019.72 362.55 56440 +2008 169 23.1 12.6 20.21 0.1 909.85 299.11 56458 +2008 170 24.9 15.2 22.23 0.05 953.98 277.98 56472 +2008 171 27.5 10.3 22.77 0 1517.22 502.08 56480 +2008 172 29.1 14 24.95 0 1559.05 463.13 56484 +2008 173 30.3 14 25.82 0 1726.55 473.18 56482 +2008 174 32 15.5 27.46 0 1902.22 464.92 56476 +2008 175 32.1 17.1 27.98 0.08 1824.53 328.69 56466 +2008 176 31.7 17 27.66 0.7 1767.57 325.7 56450 +2008 177 30.3 16 26.37 0 1616.82 433.34 56430 +2008 178 30.1 17.9 26.75 0.88 1603.75 295.38 56405 +2008 179 27.4 17.3 24.62 0.15 988.12 312.07 56375 +2008 180 27.2 16.2 24.18 0 1344.37 383.19 56341 +2008 181 29.4 14.5 25.3 0 1637.5 457.61 56301 +2008 182 27.2 16.6 24.29 0.96 823.75 224.02 56258 +2008 183 28.6 14.4 24.7 0 1647.5 452.34 56209 +2008 184 30.2 14.5 25.88 0 1724.38 467.65 56156 +2008 185 30.4 16.3 26.52 0 1735.63 439.59 56099 +2008 186 28.6 19.7 26.15 0.01 1485.63 237.51 56037 +2008 187 28 15.8 24.65 0 1778.13 416.02 55971 +2008 188 28.5 11.3 23.77 0.09 1548.13 454.65 55900 +2008 189 30.5 18.1 27.09 1.45 1608.13 385.58 55825 +2008 190 22.4 14.4 20.2 0.11 357.5 114.67 55746 +2008 191 25.1 10.3 21.03 0 1231.88 455.98 55663 +2008 192 27 15.9 23.95 0 1121.25 317.61 55575 +2008 193 30.8 14 26.18 0 1935.63 466 55484 +2008 194 31.2 15.8 26.97 0 1910.63 437.96 55388 +2008 195 29.8 16.5 26.14 3.23 1200.63 299.07 55289 +2008 196 20.6 14.4 18.9 4.06 326.88 146.33 55186 +2008 197 24.7 12.4 21.32 0 1171.88 397.21 55079 +2008 198 25.3 13.3 22 0 1556.88 388.86 54968 +2008 199 27.2 14.1 23.6 0.75 856.88 304.17 54854 +2008 200 23.2 14.9 20.92 0.01 691.88 277.48 54736 +2008 201 25.8 13.9 22.53 0 1266.25 385.98 54615 +2008 202 27.8 14.5 24.14 2.63 1226.87 308.02 54490 +2008 203 22.2 15.6 20.38 0.02 622.06 182.49 54362 +2008 204 21.5 12.9 19.13 0 727.67 312.13 54231 +2008 205 17.7 10.3 15.66 1.65 526.57 60.07 54097 +2008 206 20.3 14.5 18.7 0 505.86 110.32 53960 +2008 207 24.4 17.5 22.5 0.05 725.9 152.32 53819 +2008 208 26.8 15.9 23.8 0 1141.85 386.36 53676 +2008 209 28.9 16.1 25.38 0 1410.15 413.44 53530 +2008 210 26 15.5 23.11 0 1067.39 416.62 53382 +2008 211 29 15.2 25.21 0 1479.08 436.08 53230 +2008 212 28.1 16.5 24.91 0 1273.55 279.91 53076 +2008 213 29.8 16.2 26.06 0 1531.67 385.48 52920 +2008 214 30.1 17.1 26.53 0 1517.15 358.02 52761 +2008 215 29.7 15.9 25.91 0 1535.82 374.8 52600 +2008 216 30.6 15.3 26.39 0 1701.58 430.89 52437 +2008 217 30.8 15.6 26.62 0.51 1714.22 379.06 52271 +2008 218 24.8 18.6 23.1 0.38 682.4 292.87 52103 +2008 219 26.8 12.6 22.9 0 1332.25 450.98 51934 +2008 220 28 14.1 24.18 0 1406.59 427.78 51762 +2008 221 26.8 14.9 23.53 1.5 1205.71 297.87 51588 +2008 222 24.8 15.1 22.13 0.01 948.78 369.23 51413 +2008 223 25.3 9.7 21.01 0 1284.51 429.46 51235 +2008 224 26.6 11.9 22.56 0 1341.37 464.92 51057 +2008 225 29.3 13 24.82 0 1635.44 434.04 50876 +2008 226 27.1 16.8 24.27 0.01 1118.74 421.03 50694 +2008 227 27.9 16.3 24.71 0 1259.92 411.99 50510 +2008 228 30.9 16.1 26.83 3.46 1699.99 324.7 50325 +2008 229 25.6 13.6 22.3 0.23 1134.78 252.12 50138 +2008 230 22.3 8.1 18.4 0 1035.16 376.3 49951 +2008 231 25.8 9.8 21.4 0 1336.64 426.18 49761 +2008 232 27.4 11.4 23 0 1460.98 463.72 49571 +2008 233 26.2 12 22.3 0.02 1288.88 414.71 49380 +2008 234 26.8 16.4 23.94 0 1107.78 402.95 49187 +2008 235 28.3 12.5 23.95 0 1526.03 405.36 48993 +2008 236 24.3 15.1 21.77 2.83 890.51 254.53 48798 +2008 237 22.1 13.8 19.82 0.11 733.76 332.6 48603 +2008 238 23.3 8.8 19.31 0 1107.41 389.31 48406 +2008 239 25.6 12.5 22 0 1193.68 399.55 48208 +2008 240 27.1 13.3 23.31 0 1333.95 405.16 48010 +2008 241 28.4 12 23.89 0 1561.33 390.12 47811 +2008 242 26.2 14 22.84 0 1184.32 333.89 47611 +2008 243 23.4 14 20.81 0 860.01 229.27 47410 +2008 244 23.8 9.2 19.79 0 1143.14 403.05 47209 +2008 245 23.9 8.5 19.66 0 1179.8 338.57 47007 +2008 246 26.2 10.8 21.97 0 1342.46 372.01 46805 +2008 247 27.8 12.4 23.57 0 1466.54 394.34 46601 +2008 248 28.3 15.5 24.78 0 1614.62 330.96 46398 +2008 249 28.6 19 25.96 0 1641.54 260 46194 +2008 250 29.7 20.7 27.22 0 1833.08 241.9 45989 +2008 251 30 19.8 27.2 0.52 1736.15 201.71 45784 +2008 252 23.9 15.5 21.59 0 1121.54 242.06 45579 +2008 253 25.3 9.8 21.04 0 1306.92 377.87 45373 +2008 254 27.2 10.1 22.5 0 1358.46 388.74 45167 +2008 255 28.3 15.5 24.78 0 1524.62 197.64 44961 +2008 256 26.5 15 23.34 0.41 1045.83 172.99 44755 +2008 257 19.9 12.7 17.92 0.03 715.83 155.56 44548 +2008 258 12.7 9.6 11.85 1.32 441.67 90.49 44341 +2008 259 10.9 7.9 10.08 0.18 226.67 72.16 44134 +2008 260 10.3 8.7 9.86 0 355.83 67.07 43927 +2008 261 15.1 7.8 13.09 0 661.67 223.46 43719 +2008 262 15.3 2.9 11.89 0 679.17 208.2 43512 +2008 263 15.3 4 12.19 0 647.5 214.21 43304 +2008 264 13.4 10.1 12.49 0.09 528.33 78.56 43097 +2008 265 13.6 8.6 12.23 0.11 439.17 89.05 42890 +2008 266 13.2 8.6 11.93 0.24 415 166.12 42682 +2008 267 15.4 7.9 13.34 0 558.33 145.68 42475 +2008 268 17.3 6.2 14.25 0.06 603.33 195.06 42268 +2008 269 15.1 9.1 13.45 0.95 259.17 104.53 42060 +2008 270 14.6 8 12.79 0 500.83 207.79 41854 +2008 271 15.1 8.4 13.26 0 573.33 157.83 41647 +2008 272 17.1 6.3 14.13 0 612.5 174.32 41440 +2008 273 18 1.6 13.49 0 845 369.41 41234 +2008 274 19 3.3 14.68 0 766.67 359.13 41028 +2008 275 19.8 7.5 16.42 0 761.82 191.38 40822 +2008 276 21.7 5.9 17.36 0 767.27 168.04 40617 +2008 277 17 10.2 15.13 0.93 284.55 54.02 40412 +2008 278 12.1 7.4 10.81 0.03 366.36 100.02 40208 +2008 279 16 -0.4 11.49 0 727.27 352.26 40003 +2008 280 20 1.3 14.86 0.02 781.82 209.41 39800 +2008 281 19.9 6.8 16.3 0.05 532.73 169.21 39597 +2008 282 19.8 5.2 15.79 0 567.27 211.45 39394 +2008 283 21.1 6.7 17.14 0.17 490 181.06 39192 +2008 284 20.2 9.3 17.2 0 457.27 199.73 38991 +2008 285 20.4 6 16.44 0 562.73 306.28 38790 +2008 286 21.5 6.1 17.27 0 609.09 307.29 38590 +2008 287 22.5 6.4 18.07 0 747.27 223.61 38391 +2008 288 22.5 4.7 17.61 0 825.45 170.78 38193 +2008 289 22.5 6.8 18.18 0 780.91 192.84 37995 +2008 290 22.6 8.5 18.72 0.32 717.27 200.18 37799 +2008 291 18 6.1 14.73 0 333.64 73.39 37603 +2008 292 14 -0.2 10.1 0 446.36 271.42 37408 +2008 293 16.3 -0.9 11.57 0 535.45 201.88 37214 +2008 294 17.7 -0.6 12.67 0 523.64 284.72 37022 +2008 295 16.8 2.3 12.81 0 374.55 251.75 36830 +2008 296 19.2 2 14.47 0 390.91 186.23 36640 +2008 297 13.7 8.6 12.3 0 419.09 112.15 36451 +2008 298 13.3 1.8 10.14 0 379.09 165.85 36263 +2008 299 10.2 1.9 7.92 0 248.18 90.06 36076 +2008 300 10.4 7.2 9.52 0 345 112.47 35891 +2008 301 10.9 1.3 8.26 0 269 169.75 35707 +2008 302 20.7 1.5 15.42 0.3 678 189.33 35525 +2008 303 22.6 11.8 19.63 0.76 859 179.6 35345 +2008 304 20.3 11.3 17.82 0 754 191.32 35166 +2008 305 18.6 7.4 15.52 0.02 824 173.91 34988 +2008 306 16.8 10.5 15.07 0.64 273 135.2 34813 +2008 307 12.9 7.8 11.5 0.01 143 41.3 34639 +2008 308 20.9 9.3 17.71 0 722 136.17 34468 +2008 309 19.7 7.3 16.29 0 402.22 148.95 34298 +2008 310 18.7 9.4 16.14 0.03 416.67 147.48 34130 +2008 311 17.8 8.6 15.27 0.18 447.78 124.64 33964 +2008 312 14 11.9 13.42 1.08 74.44 34.99 33801 +2008 313 13.2 9.6 12.21 0.25 75.56 15.13 33640 +2008 314 13.5 6.8 11.66 0 186.67 100.36 33481 +2008 315 9.8 5.9 8.73 0 81.11 59.53 33325 +2008 316 9.1 6.8 8.47 0 130 44.81 33171 +2008 317 7.8 6.3 7.39 0.02 81.11 32.64 33019 +2008 318 8.8 7.2 8.36 0.57 118.89 39.94 32871 +2008 319 8.9 7.4 8.49 0 100 22.35 32725 +2008 320 11.8 6.3 10.29 0 294.44 92.11 32582 +2008 321 6.4 0.6 4.8 0.23 44.44 87.26 32441 +2008 322 9.9 2.4 7.84 0 472.22 186.94 32304 +2008 323 6.3 -4 3.47 0 281.11 182.84 32170 +2008 324 7.5 -4.2 4.28 0 288.89 145.06 32039 +2008 325 12.9 0.5 9.49 0 535.56 143.99 31911 +2008 326 6.3 -0.7 4.38 0.23 151.11 44.4 31786 +2008 327 5.3 -2.8 3.07 0.04 278.89 145.02 31665 +2008 328 5.2 -4.4 2.56 0 365.56 181.42 31547 +2008 329 4.9 -2.3 2.92 0.05 325.56 41.21 31433 +2008 330 2.8 -1.2 1.7 0 88.89 51.96 31322 +2008 331 6 -2.5 3.66 0 262.22 154.67 31215 +2008 332 6.9 -2.3 4.37 0 346.67 186.96 31112 +2008 333 3.6 -5.5 1.1 0.53 197.78 169.23 31012 +2008 334 2 -0.5 1.31 0 45.56 42.11 30917 +2008 335 8.3 -0.2 5.96 0.16 191.11 61.89 30825 +2008 336 10.9 2.3 8.54 0.4 270 74.15 30738 +2008 337 7 -0.8 4.86 0.47 193.33 101.07 30654 +2008 338 5 2.8 4.39 0.1 61.11 42.02 30575 +2008 339 5 0.2 3.68 0.06 37.78 43.62 30500 +2008 340 10.1 -0.1 7.29 0.06 275.56 51.57 30430 +2008 341 9.9 1.3 7.54 0.18 68.89 61.81 30363 +2008 342 7.4 0.1 5.39 0 226.67 68.24 30301 +2008 343 4.8 -1.1 3.18 0 172.22 46.28 30244 +2008 344 5.4 -5.1 2.51 0 190 178.25 30191 +2008 345 8.5 -3.1 5.31 0 364.44 87.63 30143 +2008 346 5.9 3.4 5.21 0.33 125.56 53.06 30099 +2008 347 4.6 2.3 3.97 0.78 76.25 10.81 30060 +2008 348 4.3 2.3 3.75 0.08 62.5 15.35 30025 +2008 349 5.2 3.3 4.68 0.01 60 32.3 29995 +2008 350 5.1 3.3 4.6 0.07 96.25 35.99 29970 +2008 351 4.9 3.9 4.63 0.3 50 19.56 29950 +2008 352 5.8 4.8 5.52 1.44 43.75 19.6 29934 +2008 353 5.7 0.8 4.35 1.63 88.75 22.2 29924 +2008 354 4.8 2.7 4.22 0.26 103.75 28.07 29918 +2008 355 5.1 -1.1 3.39 0.04 197.5 95.08 29916 +2008 356 9.1 -0.8 6.38 0.11 411.25 191.14 29920 +2008 357 8.1 -1.1 5.57 0 187.5 120.01 29928 +2008 358 8.9 -1.8 5.96 0 385 160.25 29941 +2008 359 5.2 0 3.77 0.01 212.5 56.06 29959 +2008 360 3.6 -0.7 2.42 0.06 90 45.09 29982 +2008 361 0.3 -5.9 -1.41 0 153.75 80.31 30009 +2008 362 -0.1 -1.2 -0.4 0 100 50.53 30042 +2008 363 -0.7 -4.4 -1.72 0 118.75 143.73 30078 +2008 364 -2.4 -8.6 -4.11 0 113.75 67.21 30120 +2008 365 -4 -10.1 -5.68 0 67.5 32.09 30166 +2009 1 -3.7 -4.9 -4.03 0 72.5 36.85 30217 +2009 2 -1.5 -4.2 -2.24 0 112.5 45.58 30272 +2009 3 -0.3 -6.9 -2.12 0 180 203.63 30331 +2009 4 0.4 -12.8 -3.23 0 155 205.4 30396 +2009 5 -1.5 -9.1 -3.59 0 102.5 111.48 30464 +2009 6 -2 -10.2 -4.25 0 90 69.99 30537 +2009 7 -3 -5.6 -3.71 0 100 43.77 30614 +2009 8 -0.1 -11.6 -3.26 0 191.25 184.49 30695 +2009 9 -0.8 -14.2 -4.48 0 167.5 226.71 30781 +2009 10 -4 -14.4 -6.86 0 40 72.76 30870 +2009 11 -7.3 -9.5 -7.91 0 40 40.07 30964 +2009 12 -6.3 -7.9 -6.74 0 40 20.58 31061 +2009 13 -6.4 -7.4 -6.68 0.02 40 31.25 31162 +2009 14 -2.7 -7.4 -3.99 0.86 40 25.74 31268 +2009 15 1.4 -2.8 0.24 0.01 53.33 88.56 31376 +2009 16 4.7 -3.1 2.56 0 75.56 175.9 31489 +2009 17 3.6 -4 1.51 0 133.33 213.48 31605 +2009 18 1.3 -5.4 -0.54 0.01 40 74.21 31724 +2009 19 8 -4 4.7 0 169 186.49 31847 +2009 20 13.9 3 10.9 0 476 166.97 31974 +2009 21 9.8 1.1 7.41 2.35 92 39.63 32103 +2009 22 6.4 -0.3 4.56 0 129 163.76 32236 +2009 23 3.5 -1.1 2.23 1.6 89 80.57 32372 +2009 24 2.6 -0.1 1.86 0.02 53 144.23 32510 +2009 25 5 0 3.63 0 225 101.51 32652 +2009 26 5.1 -2.2 3.09 0.03 207 123.64 32797 +2009 27 1.6 -1.1 0.86 3.85 40 29.04 32944 +2009 28 2.8 0.6 2.19 0.54 88 62.04 33094 +2009 29 3 0.8 2.4 0 183 119.63 33247 +2009 30 1.7 0 1.23 0 194 140.17 33402 +2009 31 2 -1.1 1.15 0.01 164 134.52 33559 +2009 32 0.2 -2.7 -0.6 0.44 67 77.94 33719 +2009 33 1.2 -0.8 0.65 1.05 61 67.23 33882 +2009 34 1.9 0.5 1.51 0.34 38 62.03 34046 +2009 35 3.5 0.8 2.76 0 39 91.59 34213 +2009 36 9.2 -1.1 6.37 0 81 205.86 34382 +2009 37 13.6 -2.6 9.14 0 427 225.47 34552 +2009 38 12.5 0.4 9.17 0.19 410 150.35 34725 +2009 39 9.8 3.4 8.04 1.62 79 37.65 34900 +2009 40 7.3 0.4 5.4 0 408 235.92 35076 +2009 41 10.1 -3.1 6.47 0.01 350 120.23 35254 +2009 42 8.6 1.1 6.54 0 308 185.37 35434 +2009 43 5.4 -5.3 2.46 0 248 197.97 35615 +2009 44 4.2 -3.3 2.14 0 373 234.5 35798 +2009 45 3.4 -0.8 2.25 0 391 200.35 35983 +2009 46 2.8 -1.5 1.62 0 311 233.67 36169 +2009 47 4.4 -4.1 2.06 0 342 201.49 36356 +2009 48 2.2 -3.6 0.61 0.11 233 77.35 36544 +2009 49 1.9 -5.3 -0.08 0 255 222.77 36734 +2009 50 1.9 -3.8 0.33 0 285 290.21 36925 +2009 51 4.7 -7.8 1.26 0 340 215.11 37117 +2009 52 4.2 -2.2 2.44 0.04 147 111.77 37310 +2009 53 0.2 -3 -0.68 0.28 133.64 124.74 37505 +2009 54 4.9 -1.2 3.22 0.02 106.36 137.24 37700 +2009 55 5 -1.1 3.32 0.29 127.27 159.82 37896 +2009 56 6 -0.8 4.13 0 290 225.89 38093 +2009 57 9 -1.9 6 0 364.55 202.92 38291 +2009 58 11 -1.7 7.51 0 312.73 166.8 38490 +2009 59 15.5 1 11.51 0 527.27 279.24 38689 +2009 60 12.5 -1.2 8.73 0 338.18 290.46 38890 +2009 61 6.9 2.7 5.75 0.23 105 75.45 39091 +2009 62 8.6 3.9 7.31 0.02 111.67 97.73 39292 +2009 63 9.8 4.8 8.43 0.09 140.83 107.4 39495 +2009 64 9.3 5.2 8.17 1.78 120 37.55 39697 +2009 65 7.3 5.7 6.86 0.56 93.33 71.89 39901 +2009 66 8.9 0.8 6.67 0.02 395 39.62 40105 +2009 67 13.5 -0.3 9.71 0 595.83 335.72 40309 +2009 68 9.3 2.4 7.4 0 457.5 114.06 40514 +2009 69 12 -1.7 8.23 0 665.83 323.99 40719 +2009 70 11.5 3.5 9.3 0.06 455.83 163.02 40924 +2009 71 10.4 -1.6 7.1 0.04 496.67 303.65 41130 +2009 72 13.2 1.6 10.01 0 533.33 263.19 41336 +2009 73 13.1 1.6 9.94 0 439.17 269.53 41543 +2009 74 13 -0.1 9.4 0 350.83 168.39 41749 +2009 75 12.8 2.3 9.91 0 520 201.53 41956 +2009 76 10 1.3 7.61 0 422.5 210.99 42163 +2009 77 11.5 -0.8 8.12 0.22 679.17 365.69 42370 +2009 78 5.9 0.3 4.36 0.48 63.33 151.83 42578 +2009 79 5 -2 3.08 0 260.83 262.38 42785 +2009 80 6 0.5 4.49 0 334.17 358.97 42992 +2009 81 13.8 -5.6 8.46 0 619.17 398.76 43200 +2009 82 15.4 -0.2 11.11 0 821.67 256.73 43407 +2009 83 9.8 2.3 7.74 0 476.67 165.39 43615 +2009 84 8 -2 5.25 0 486.67 322.41 43822 +2009 85 11.5 -0.9 8.09 0 428.33 295.04 44029 +2009 86 15.1 2.3 11.58 0 660 271.17 44236 +2009 87 16 7.3 13.61 0 768.33 330.76 44443 +2009 88 13.8 8.6 12.37 2.4 310.83 77.02 44650 +2009 89 10.6 5.8 9.28 0.01 296.67 270.03 44857 +2009 90 11.4 3.9 9.34 0.22 321.67 171.5 45063 +2009 91 12.6 7.6 11.23 0.05 288.37 162.16 45270 +2009 92 19 9.4 16.36 0 955.38 360.8 45475 +2009 93 19.1 3.2 14.73 0 627.69 364.61 45681 +2009 94 21.9 3.9 16.95 0 1003.08 430.84 45886 +2009 95 22.4 3.9 17.31 0 1028.46 404.29 46091 +2009 96 22.1 4.5 17.26 0 1065 360.53 46295 +2009 97 23.5 3.3 17.95 0 1343.57 424.47 46499 +2009 98 24 3.8 18.45 0 1487.86 442.12 46702 +2009 99 23.8 4.3 18.44 0 1350.71 413.15 46905 +2009 100 23.5 3.5 18 0 1555.71 426.18 47107 +2009 101 23.8 3.3 18.16 0 1595 434.7 47309 +2009 102 23.2 3.6 17.81 0 1571.43 441.5 47510 +2009 103 21.2 3.8 16.41 0 984.29 438.57 47710 +2009 104 21.2 2.7 16.11 0 927.86 442.68 47910 +2009 105 22.9 1.8 17.1 0 1260.71 451.09 48108 +2009 106 23.2 3.9 17.89 0 1375.71 385.9 48306 +2009 107 19.8 9.5 16.97 0 960 329.86 48504 +2009 108 21.5 3.1 16.44 0 929.29 417.59 48700 +2009 109 19 2.8 14.55 0.26 749.29 245.89 48895 +2009 110 21 10 17.98 0.12 752.14 354.2 49089 +2009 111 21.1 9.5 17.91 0 1056.43 366.54 49282 +2009 112 20.8 1.8 15.58 0.12 1229.29 486.96 49475 +2009 113 16.1 6.1 13.35 0.33 420.71 103.41 49666 +2009 114 19 5.4 15.26 0 862.14 447.18 49855 +2009 115 21 1.9 15.75 0 1087.79 463.53 50044 +2009 116 20.3 6.5 16.51 0 909.23 385.22 50231 +2009 117 20.5 9.9 17.59 0 790.57 312.64 50417 +2009 118 18.6 11.4 16.62 0.17 739.29 261.88 50601 +2009 119 18 9.5 15.66 0.56 347.14 250.39 50784 +2009 120 20.3 9.1 17.22 0.3 597.14 399.44 50966 +2009 121 23.8 8.3 19.54 0 1173.57 431.55 51145 +2009 122 17.9 8.3 15.26 0 961.43 248.01 51324 +2009 123 20.8 8.3 17.36 0 1014.29 395.38 51500 +2009 124 22.3 5.3 17.63 0.05 755 327.11 51674 +2009 125 17.5 8.3 14.97 0 866.67 438.08 51847 +2009 126 20.5 6.9 16.76 0 856.67 259.98 52018 +2009 127 22.2 10.7 19.04 0 1012.67 413.29 52187 +2009 128 25.9 5.7 20.34 0 1294.67 448.49 52353 +2009 129 25.4 8.2 20.67 0 1243.33 459.47 52518 +2009 130 27.4 10.4 22.72 0 1311.33 444.44 52680 +2009 131 28.3 9.6 23.16 2.77 1350 429.34 52840 +2009 132 24.3 12.6 21.08 1.15 369.33 360.34 52998 +2009 133 15.7 10.8 14.35 0.13 252.67 149.17 53153 +2009 134 14 11.2 13.23 0 129.33 88.76 53306 +2009 135 20.8 10.3 17.91 0 393.33 278.19 53456 +2009 136 22.9 11.4 19.74 0.03 702.67 360.15 53603 +2009 137 25.4 10.2 21.22 0 886.67 466.32 53748 +2009 138 27 12 22.88 0.04 809.33 393.64 53889 +2009 139 24.8 14.4 21.94 0 830 475.64 54028 +2009 140 25.5 13.9 22.31 0 1197.33 521.85 54164 +2009 141 27.5 9.4 22.52 0 1440 490.32 54297 +2009 142 27.3 14.2 23.7 1.68 1310.43 309.27 54426 +2009 143 22.4 12.3 19.62 0.02 853.3 265.93 54552 +2009 144 23.4 16 21.36 0.05 724.85 203.13 54675 +2009 145 28.3 14.4 24.48 0 1240.63 445.58 54795 +2009 146 28.5 16.2 25.12 0.31 1126.87 403.08 54911 +2009 147 25.4 15.3 22.62 1.1 313.75 110.94 55023 +2009 148 21.6 9.3 18.22 0.2 1031.88 386.58 55132 +2009 149 18.8 7.7 15.75 0.1 707.5 377.62 55237 +2009 150 13.1 7.7 11.62 0.89 201.87 151.72 55339 +2009 151 19.4 3.9 15.14 0 655.62 349.57 55436 +2009 152 18.6 10.3 16.32 0 520.63 269.62 55530 +2009 153 20.1 5.8 16.17 0.03 676.25 369.76 55619 +2009 154 25.1 10.8 21.17 0 1327.5 396.36 55705 +2009 155 20.5 9.6 17.5 0 576.88 324.58 55786 +2009 156 18.4 7.9 15.51 0 316.87 253.35 55863 +2009 157 26.3 14.3 23 0 1080 340.98 55936 +2009 158 23.8 14 21.11 0.44 380 188.17 56004 +2009 159 24.9 8.3 20.34 0 862.5 458.9 56068 +2009 160 27.3 13.6 23.53 0 1390.63 491.32 56128 +2009 161 26.2 11.5 22.16 0 1014.38 358.17 56183 +2009 162 25.4 10.3 21.25 0.82 691.25 321.31 56234 +2009 163 24.2 8.3 19.83 0.01 1323.13 470.34 56280 +2009 164 24.9 10.8 21.02 0 930 420.75 56321 +2009 165 27.2 8.8 22.14 0 1367.5 498.02 56358 +2009 166 27.7 16 24.48 0 1088.75 311.15 56390 +2009 167 28.8 17.8 25.78 0.65 1107.5 259.99 56418 +2009 168 24.2 14.6 21.56 0 1001.87 417.6 56440 +2009 169 27.9 10.3 23.06 0 1238.75 487.67 56458 +2009 170 31.2 13.4 26.31 0 1653.75 496.23 56472 +2009 171 24.9 12.9 21.6 1.2 270.63 59.29 56480 +2009 172 21.8 8.4 18.12 0 922.5 479.98 56484 +2009 173 18.9 10.4 16.56 2.59 313.12 73.6 56482 +2009 174 14.5 12.2 13.87 3.59 133.12 51.08 56476 +2009 175 18.5 13.7 17.18 0.94 185 192.73 56466 +2009 176 24.9 13.8 21.85 0.01 775.63 448.51 56450 +2009 177 24.7 12.4 21.32 6.24 433.75 264.95 56430 +2009 178 25 13.1 21.73 0 683.13 354.45 56405 +2009 179 22.7 16.6 21.02 4.72 365.63 167.53 56375 +2009 180 24 15.3 21.61 3.62 503.13 300 56341 +2009 181 28.2 14.2 24.35 0 1034.38 433.95 56301 +2009 182 28.2 17.2 25.18 1.34 751.25 352.55 56258 +2009 183 28.1 15.5 24.64 0 876.25 393.21 56209 +2009 184 28.8 16.2 25.34 0 986.88 423.58 56156 +2009 185 27.9 18.1 25.2 0.14 1005 384.76 56099 +2009 186 27 16 23.98 0.1 893.13 381.3 56037 +2009 187 27.2 15 23.84 0 788.13 341.28 55971 +2009 188 26.1 14 22.77 0.43 746.25 363.36 55900 +2009 189 22.3 15.4 20.4 0.63 251.88 187.4 55825 +2009 190 23.5 12.2 20.39 0.26 659.38 327.57 55746 +2009 191 21.1 15 19.42 0.5 244.38 128.98 55663 +2009 192 22.9 10 19.35 0.02 804.38 368.21 55575 +2009 193 24.8 10.8 20.95 0 1131.88 480.95 55484 +2009 194 28.9 14 24.8 0 1276.25 426.5 55388 +2009 195 30.6 16.2 26.64 0 1229.37 470.8 55289 +2009 196 31.4 17.4 27.55 0.61 1128.13 414.24 55186 +2009 197 30.8 18 27.28 0 1401.87 416.34 55079 +2009 198 30.7 16.5 26.8 0 1463.13 440.81 54968 +2009 199 28.4 15.2 24.77 0.51 405.63 159.23 54854 +2009 200 24 10.3 20.23 0 1122.5 495.38 54736 +2009 201 26.2 9.8 21.69 0 1090.63 430.72 54615 +2009 202 29 12.5 24.46 0 1230.62 481.09 54490 +2009 203 30.7 14.1 26.13 0 1445 486.82 54362 +2009 204 33 16.7 28.52 0 1899.38 460.38 54231 +2009 205 30.1 16.1 26.25 1.3 1508.75 479.6 54097 +2009 206 27.1 15.7 23.97 0.01 829.38 300.04 53960 +2009 207 25 9.7 20.79 0 1175 412.53 53819 +2009 208 27 9.7 22.24 0 1265.63 492.03 53676 +2009 209 27.5 12.1 23.27 0 1200.67 391.01 53530 +2009 210 29 13.6 24.77 0 1551.43 516.79 53382 +2009 211 31.2 13.6 26.36 0 1610.71 446.84 53230 +2009 212 27.4 17.4 24.65 0 1735.71 384.72 53076 +2009 213 29.5 13.4 25.07 0 1590.71 479.88 52920 +2009 214 32.5 16.6 28.13 0.01 1975.71 485.67 52761 +2009 215 29.3 14.9 25.34 0.22 1432.14 365.38 52600 +2009 216 21.2 16.8 19.99 3.52 275 89.08 52437 +2009 217 23.8 16.8 21.88 0 814.29 272.57 52271 +2009 218 26.7 15 23.48 0 1022.86 414.34 52103 +2009 219 27.1 14.9 23.75 0 1185.71 397.39 51934 +2009 220 27.9 14.5 24.22 0 1199.29 396.61 51762 +2009 221 24 17.5 22.21 0 1040.71 217.24 51588 +2009 222 28 16.5 24.84 1.12 1348.57 413.94 51413 +2009 223 27.8 16.3 24.64 0.04 815 327.35 51235 +2009 224 27.8 14.1 24.03 0.01 1243.57 402.58 51057 +2009 225 24.9 14.1 21.93 0.71 685 188.57 50876 +2009 226 23.4 17.1 21.67 0.68 578.57 314.78 50694 +2009 227 26.6 11.8 22.53 0 912.14 449.66 50510 +2009 228 28.7 14 24.66 0 1219.29 470.73 50325 +2009 229 31.5 15.5 27.1 0 1483.57 443.58 50138 +2009 230 30.7 15.6 26.55 0 1455 420.81 49951 +2009 231 27.4 14.7 23.91 0 1182.86 257.78 49761 +2009 232 28.9 16 25.35 0 1191.43 419.82 49571 +2009 233 29.3 14.7 25.29 0 1596.43 456.15 49380 +2009 234 26.9 18.4 24.56 0.96 884.29 274.82 49187 +2009 235 24.3 15.4 21.85 0 927.86 428.6 48993 +2009 236 24.5 9.9 20.48 0 854.29 399.01 48798 +2009 237 26.4 10.8 22.11 0.2 1365.87 313.18 48603 +2009 238 28.7 11.3 23.91 0 1212.5 431.21 48406 +2009 239 29.9 15 25.8 0.01 1261.43 439.97 48208 +2009 240 30.6 16 26.59 0.01 1412.86 437.65 48010 +2009 241 25.3 15.8 22.69 1.33 447.14 64.31 47811 +2009 242 23.4 12.9 20.51 0 1147.14 456.04 47611 +2009 243 24.7 7.3 19.91 0.02 1071.43 472.3 47410 +2009 244 26.5 8 21.41 0 1141.43 451.32 47209 +2009 245 27.3 11.1 22.84 0.01 986.92 348.41 47007 +2009 246 29.2 13.9 24.99 0.61 1160.77 399.05 46805 +2009 247 25 15.1 22.28 3.93 182.31 66.79 46601 +2009 248 20.7 11.5 18.17 0.01 611.54 308.95 46398 +2009 249 21.1 6.5 17.09 0 798.46 445.8 46194 +2009 250 21.5 7.1 17.54 0 848.46 365.3 45989 +2009 251 22.1 7.6 18.11 0 816.92 462.79 45784 +2009 252 23 9.8 19.37 0 797.69 378.55 45579 +2009 253 25.4 11.8 21.66 0.11 1060.77 417.12 45373 +2009 254 21.2 11.9 18.64 0.29 573.85 155.49 45167 +2009 255 23.3 14.1 20.77 0 700.77 421.79 44961 +2009 256 22.4 9.8 18.93 0.16 990 416.04 44755 +2009 257 19.3 12.4 17.4 0.01 340.83 161.78 44548 +2009 258 23.4 12.9 20.51 0 434.17 266.98 44341 +2009 259 25.1 12.4 21.61 0.1 860.83 322.59 44134 +2009 260 22.6 17 21.06 1.55 563.33 267.35 43927 +2009 261 22.2 17.1 20.8 0.17 495 162.68 43719 +2009 262 22.3 14.5 20.16 0 593.33 307.54 43512 +2009 263 24.3 13.4 21.3 0 1013.33 368.21 43304 +2009 264 25 11.3 21.23 0 1027.5 361.77 43097 +2009 265 25.6 11.1 21.61 0 1132.5 403.53 42890 +2009 266 25.4 8.7 20.81 0 1164.17 388.31 42682 +2009 267 25.8 9.4 21.29 0 1043.33 371.54 42475 +2009 268 22.3 12.4 19.58 0 834.17 385.27 42268 +2009 269 21.5 7.8 17.73 0 956.67 387.86 42060 +2009 270 23.3 6.4 18.65 0 1024.17 378.81 41854 +2009 271 24.3 7.6 19.71 0 1028.33 328.87 41647 +2009 272 23.5 10 19.79 0 970.83 272.26 41440 +2009 273 22.6 8.8 18.81 0 860.83 307.26 41234 +2009 274 23.3 9.1 19.4 0.7 700 254.12 41028 +2009 275 19.2 11.1 16.97 0.01 211.82 58.54 40822 +2009 276 17.3 5.2 13.97 0 620 328.16 40617 +2009 277 21.3 4.2 16.6 0.02 784.55 393.82 40412 +2009 278 21.2 4.7 16.66 0 840 372.09 40208 +2009 279 26 10.5 21.74 0 1111.82 363.83 40003 +2009 280 25.4 12.9 21.96 0 1020 304.39 39800 +2009 281 25.3 9.6 20.98 0 866.36 325.18 39597 +2009 282 18.3 12.3 16.65 0.1 325.45 120.52 39394 +2009 283 16 11.2 14.68 1.83 251.82 153.78 39192 +2009 284 20.6 10.3 17.77 0.36 604.55 267.81 38991 +2009 285 11.6 8.8 10.83 0.94 207.27 36.75 38790 +2009 286 11.3 6.4 9.95 0 531.82 270.95 38590 +2009 287 9.2 0.7 6.86 0 430.91 175.23 38391 +2009 288 9.8 1.5 7.52 0 481.82 178.92 38193 +2009 289 9.2 0.5 6.81 0 453.64 178.48 37995 +2009 290 9.4 1.8 7.31 0 281.82 166.86 37799 +2009 291 9.8 3.1 7.96 0.05 246.36 184.36 37603 +2009 292 9.3 -2.2 6.14 0 292.73 226.05 37408 +2009 293 11.2 3.2 9 0 353.64 181.79 37214 +2009 294 15.8 -2.8 10.69 0 454.55 277.34 37022 +2009 295 19 11.8 17.02 0.09 684.55 184.97 36830 +2009 296 16.7 9.8 14.8 0.21 247.27 142.88 36640 +2009 297 11.6 9.3 10.97 0.5 246.36 42.75 36451 +2009 298 17 3.1 13.18 0 400 259.77 36263 +2009 299 15.3 6 12.74 0 190 78.85 36076 +2009 300 18.7 7.6 15.65 0.01 632 261.81 35891 +2009 301 16.3 2.8 12.59 0 593 237.67 35707 +2009 302 13.5 3.5 10.75 0.18 262 143.04 35525 +2009 303 10.1 1.6 7.76 0 311 268.36 35345 +2009 304 9.6 -3.1 6.11 0 244 234.26 35166 +2009 305 6.1 -0.7 4.23 0 37 123.09 34988 +2009 306 4.9 -0.7 3.36 0.45 147 146.46 34813 +2009 307 3.9 1.3 3.19 0.56 72 88.55 34639 +2009 308 4.2 0.8 3.27 0.48 104 84.08 34468 +2009 309 11.5 2.8 9.11 0.17 138.89 152.97 34298 +2009 310 5.6 4.5 5.3 1 40 20.89 34130 +2009 311 7.8 2.6 6.37 0.23 70 53.21 33964 +2009 312 7.3 1.8 5.79 0.61 40 28.49 33801 +2009 313 9.9 4.4 8.39 0.02 115.56 121.86 33640 +2009 314 9 2.3 7.16 0.86 141.11 42.37 33481 +2009 315 9.2 4.2 7.82 0.02 315.56 69.48 33325 +2009 316 12.8 -1.4 8.89 0.25 419.44 240 33171 +2009 317 13.3 -0.7 9.45 0 381.11 220.93 33019 +2009 318 16 -0.8 11.38 0 345.56 198.49 32871 +2009 319 15.3 3.3 12 0 292.22 156.28 32725 +2009 320 13.8 4.1 11.13 0.01 260 167.35 32582 +2009 321 17.9 3.3 13.89 0.01 363.33 227.41 32441 +2009 322 12.1 3.6 9.76 0.08 277.78 58.75 32304 +2009 323 16.8 1.5 12.59 0.01 368.89 221.29 32170 +2009 324 15.5 -0.7 11.05 0 418.89 217.74 32039 +2009 325 5.4 1.6 4.36 0.02 40 51.45 31911 +2009 326 5.4 2.6 4.63 0.01 34.44 53.97 31786 +2009 327 10 3.6 8.24 0.09 38.89 69.73 31665 +2009 328 15.1 1.7 11.41 0.02 212.22 150.85 31547 +2009 329 14 0.5 10.29 0 373.33 202.16 31433 +2009 330 8.3 -0.2 5.96 0 194.44 91.35 31322 +2009 331 13 -0.1 9.4 0 321.11 111.2 31215 +2009 332 8.6 2.6 6.95 0.4 72.22 52.23 31112 +2009 333 12.4 -1.2 8.66 0.01 306.67 79.9 31012 +2009 334 14.9 9.4 13.39 0 452.22 110.11 30917 +2009 335 15.1 6.4 12.71 0.84 126.67 65.29 30825 +2009 336 6.5 1.8 5.21 0.28 47.78 125.6 30738 +2009 337 5.6 1.8 4.55 0 57.78 88.36 30654 +2009 338 5.1 1 3.97 0.02 67.78 20.75 30575 +2009 339 7.2 -1 4.95 0 101.11 112.79 30500 +2009 340 4.5 -0.1 3.24 0 46.67 81.13 30430 +2009 341 5 -1.1 3.32 0.26 93.33 118.21 30363 +2009 342 5.2 1.1 4.07 1.48 45.56 17.67 30301 +2009 343 9 4 7.63 0 362.22 51.27 30244 +2009 344 9.2 1.1 6.97 0.09 263.33 155.7 30191 +2009 345 6.4 2.2 5.25 0.35 117.78 61.95 30143 +2009 346 5.4 1.4 4.3 0.04 115.56 29.77 30099 +2009 347 1.4 -1.3 0.66 0 147.5 38.1 30060 +2009 348 -1.3 -3.3 -1.85 0.41 73.75 39.65 30025 +2009 349 -0.7 -3.9 -1.58 0 107.5 83.18 29995 +2009 350 -1.1 -3.9 -1.87 0.03 127.5 63.4 29970 +2009 351 -1.2 -6.1 -2.55 0 119.04 97.26 29950 +2009 352 -2.8 -10.5 -4.92 0 102.5 93.09 29934 +2009 353 -7.7 -14 -9.43 1.21 38.75 24.92 29924 +2009 354 -6.8 -20.1 -10.46 0 50 146.02 29918 +2009 355 -0.3 -20.4 -5.83 0 80 152.77 29916 +2009 356 6.9 -0.3 4.92 0.01 207.5 94.86 29920 +2009 357 15.9 4.5 12.77 0.03 338.75 92.65 29928 +2009 358 13.5 2.3 10.42 0 311.25 99.85 29941 +2009 359 17.4 7.5 14.68 1.4 541.25 101.09 29959 +2009 360 9.6 -0.6 6.79 0 505 161.15 29982 +2009 361 4 -1.2 2.57 0.21 57.5 54.79 30009 +2009 362 5.7 -1.9 3.61 0 181.25 174.64 30042 +2009 363 2.5 -4.4 0.6 0 90 128.16 30078 +2009 364 6.5 -1.1 4.41 0.01 128.75 108.17 30120 +2009 365 5.7 -0.6 3.97 0 37.5 86.12 30166 +2010 1 4.2 1.3 3.4 0.02 30 36.53 30217 +2010 2 5.1 1.7 4.17 0 215 64.19 30272 +2010 3 3.8 -5.2 1.32 0 303.75 142.58 30331 +2010 4 0.8 -8.8 -1.84 0.02 168.75 203.03 30396 +2010 5 0.1 -2.1 -0.5 0.72 48.75 43.33 30464 +2010 6 0.2 -2.9 -0.65 0.24 35 86.13 30537 +2010 7 0.1 -1.8 -0.42 0.22 57.5 54.95 30614 +2010 8 0.3 -1.4 -0.17 1.95 30 31.84 30695 +2010 9 0.8 0.3 0.66 0.97 30 26.84 30781 +2010 10 1.5 0.5 1.23 0.09 30 51.28 30870 +2010 11 0.5 -0.5 0.23 0 91.11 52.63 30964 +2010 12 0 -1.3 -0.36 0 128.89 129.42 31061 +2010 13 -0.3 -1.5 -0.63 0 70 43.01 31162 +2010 14 -0.3 -1.5 -0.63 0 80 34.14 31268 +2010 15 1 -1.1 0.42 0 131.11 82.16 31376 +2010 16 3.2 -2.7 1.58 0 180 176.37 31489 +2010 17 -0.7 -3.5 -1.47 0.37 30 56.27 31605 +2010 18 2.5 -2.1 1.23 0.27 65.56 122.02 31724 +2010 19 3.5 -0.4 2.43 0 56 131.02 31847 +2010 20 3 -2.1 1.6 0 91 132.31 31974 +2010 21 0.3 -5.3 -1.24 0.46 44 71.55 32103 +2010 22 -3.6 -5.7 -4.18 0 99 71.79 32236 +2010 23 -4 -7 -4.83 0 85 93.11 32372 +2010 24 -3.1 -5.5 -3.76 0.01 88 98.53 32510 +2010 25 -2.2 -5.8 -3.19 0 124 164.53 32652 +2010 26 -4.2 -8.4 -5.36 0 114 150.41 32797 +2010 27 -4.2 -16.4 -7.55 0 145 294.23 32944 +2010 28 -2.3 -14.1 -5.54 0 113 125.56 33094 +2010 29 1.7 -10.2 -1.57 0 173 113.93 33247 +2010 30 2.7 -1.1 1.66 0.12 144 76.71 33402 +2010 31 1.4 -3.9 -0.06 0 219 105.54 33559 +2010 32 3.9 -12.4 -0.58 0 310 255.78 33719 +2010 33 5.3 -8.3 1.56 0 284 238.35 33882 +2010 34 7.3 -4.6 4.03 0 371 110.04 34046 +2010 35 7.1 -2.2 4.54 0 200 237.85 34213 +2010 36 6 -5.6 2.81 0.11 112 117.62 34382 +2010 37 3.3 -0.9 2.14 0.75 35 71.96 34552 +2010 38 -0.5 -5 -1.74 0 126 139.05 34725 +2010 39 -2.1 -13.8 -5.32 0 122 135.19 34900 +2010 40 -3.1 -5.1 -3.65 0.04 109 86.84 35076 +2010 41 -0.2 -4 -1.25 0.72 96 111.61 35254 +2010 42 -0.6 -2.5 -1.12 0.48 36 95.17 35434 +2010 43 0.1 -3.1 -0.78 0 124 119.19 35615 +2010 44 5.6 -5.4 2.57 0 276 253.55 35798 +2010 45 2.3 -11.4 -1.47 0 214 193.04 35983 +2010 46 1.1 -4 -0.3 0 134 117.51 36169 +2010 47 2.3 -9.4 -0.92 0 134 261.18 36356 +2010 48 6.1 -2 3.87 0 142 212.39 36544 +2010 49 9.4 -4.5 5.58 0 178 195.49 36734 +2010 50 9.8 -3.7 6.09 0.71 127 147.6 36925 +2010 51 5.6 1.6 4.5 0.11 214 107.88 37117 +2010 52 8.9 -3.4 5.52 0 479 283.51 37310 +2010 53 10.2 -0.3 7.31 0 363.64 240.55 37505 +2010 54 13.2 2.8 10.34 0 442.73 219.43 37700 +2010 55 14 -1 9.88 0 415.45 234.87 37896 +2010 56 14.5 -1 10.24 0 390 285.08 38093 +2010 57 12.2 3.7 9.86 0.81 289.09 94.84 38291 +2010 58 13.4 1.9 10.24 0 796.36 341.7 38490 +2010 59 14.7 1.3 11.02 0.02 703.64 211.07 38689 +2010 60 16.8 4.5 13.42 0 424.55 274.29 38890 +2010 61 11.4 3.8 9.31 0 370.13 225.05 39091 +2010 62 8 -0.3 5.72 0 319.09 117.19 39292 +2010 63 4.3 0.8 3.34 0 175.83 76.89 39495 +2010 64 4.2 -1.1 2.74 0 341.67 333.54 39697 +2010 65 3.1 -6.7 0.41 0.01 278.33 286.58 39901 +2010 66 0.2 -3.5 -0.82 0 201.67 166.18 40105 +2010 67 1 -9.7 -1.94 0 252.5 345.38 40309 +2010 68 2.2 -3.1 0.74 0 286.67 218.11 40514 +2010 69 1.3 -3.1 0.09 1.01 165.83 114.52 40719 +2010 70 1.6 -2.1 0.58 0 61.67 113.36 40924 +2010 71 6.5 -7 2.79 0 248.33 259.96 41130 +2010 72 10 -2.3 6.62 0 473.33 215.42 41336 +2010 73 11.5 -1.8 7.84 0 611.67 267.54 41543 +2010 74 6.2 -2.7 3.75 0.03 333.33 231.09 41749 +2010 75 11.4 -2.3 7.63 0.05 290 209.14 41956 +2010 76 11.5 0.9 8.59 0.03 352.5 315.15 42163 +2010 77 15.8 -2.4 10.8 0 630 355.17 42370 +2010 78 17.5 -1.1 12.39 0 721.67 279.52 42578 +2010 79 18.5 0.7 13.61 0 776.67 322.39 42785 +2010 80 20 7.3 16.51 0 790.83 302.88 42992 +2010 81 14.2 7.1 12.25 0.47 206.67 112.6 43200 +2010 82 16.8 3.4 13.12 0.01 330.83 330.67 43407 +2010 83 17.2 1.2 12.8 0.02 485 277.13 43615 +2010 84 17.3 9.6 15.18 0 503.33 299.41 43822 +2010 85 18.7 10.5 16.45 0 771.67 318.32 44029 +2010 86 16.3 7.2 13.8 0.09 614.17 284.13 44236 +2010 87 17.5 1.1 12.99 0 785 342.44 44443 +2010 88 20.2 2.7 15.39 0 1040 377.55 44650 +2010 89 19 11.6 16.97 0.09 941.67 283.05 44857 +2010 90 13.9 6.6 11.89 0.93 205 101.47 45063 +2010 91 16.5 1.7 12.43 0.6 717.5 428.59 45270 +2010 92 12.3 3.6 9.91 0 366.15 258.54 45475 +2010 93 16.2 -1.3 11.39 0.01 644.62 438.55 45681 +2010 94 14.2 8.9 12.74 0 686.92 151.04 45886 +2010 95 12.7 6.8 11.08 1.63 256.92 77.83 46091 +2010 96 14.6 5.8 12.18 0 685.71 450.53 46295 +2010 97 15.5 -1.6 10.8 0 582.14 461.63 46499 +2010 98 18.2 -1.1 12.89 0.01 677.14 356.06 46702 +2010 99 19.2 1.2 14.25 0 814.29 410.45 46905 +2010 100 14.3 6.9 12.27 0.15 519.29 250.33 47107 +2010 101 9.7 1.8 7.53 0.16 261.43 228.97 47309 +2010 102 7.4 4.2 6.52 0.98 88.57 83.17 47510 +2010 103 10.2 5.7 8.96 0.46 105 86.44 47710 +2010 104 13.9 6.5 11.87 0.11 240 241.23 47910 +2010 105 15.3 6.7 12.94 0.81 350 249.61 48108 +2010 106 16.7 6.5 13.9 0 474.29 367.82 48306 +2010 107 15.1 3.7 11.97 0 639.29 506.92 48504 +2010 108 15.7 -0.8 11.16 0.06 455.71 258.35 48700 +2010 109 19.6 3.1 15.06 0 691.43 364.4 48895 +2010 110 22.1 2.6 16.74 0.05 1005 364.55 49089 +2010 111 20.6 5.3 16.39 0.02 991.43 380.77 49282 +2010 112 13.2 6.3 11.3 0.1 437.14 132.84 49475 +2010 113 15.2 7.4 13.06 0 417.86 203.42 49666 +2010 114 20.8 5.4 16.57 0.02 987.35 346.1 49855 +2010 115 21.8 5.1 17.21 0 1036.43 406.49 50044 +2010 116 24.3 4.7 18.91 0 1141.43 453.31 50231 +2010 117 20.5 12.1 18.19 0 840 343.2 50417 +2010 118 19.4 5.4 15.55 0 905 483.33 50601 +2010 119 22.2 2.9 16.89 0 1151.43 493.76 50784 +2010 120 27.2 5.9 21.34 0 1447.86 461.64 50966 +2010 121 23.9 10.5 20.22 0 1098.57 385.92 51145 +2010 122 22.1 9.8 18.72 0 785.71 287.95 51324 +2010 123 22 13.7 19.72 0 719.29 248.52 51500 +2010 124 20.8 9.9 17.8 0.22 443.57 254.53 51674 +2010 125 16.2 12.2 15.1 0.28 72.67 84.28 51847 +2010 126 20 11.9 17.77 0.35 651.33 477.63 52018 +2010 127 20.4 4.9 16.14 0 832 452.33 52187 +2010 128 18.4 4.4 14.55 0 528.67 294.11 52353 +2010 129 21.1 9.2 17.83 0 670 308.14 52518 +2010 130 22.1 10.1 18.8 0 837.33 397.46 52680 +2010 131 22.7 6.5 18.25 0 759.33 394.03 52840 +2010 132 19.3 12.7 17.48 0 462.67 282.84 52998 +2010 133 16.7 8.9 14.56 0.72 186 148.12 53153 +2010 134 19.1 9.3 16.41 0.68 170 212.36 53306 +2010 135 13.8 8.7 12.4 0.97 212.67 148.99 53456 +2010 136 11.2 7.4 10.15 1.14 313.33 58.66 53603 +2010 137 16.7 8.1 14.33 0.06 619.33 151.41 53748 +2010 138 18.3 8.7 15.66 0 630.67 244.97 53889 +2010 139 18.2 4.8 14.52 0 690.67 395.22 54028 +2010 140 16.2 8.6 14.11 0.17 398.67 191.66 54164 +2010 141 20.2 11.9 17.92 0.44 434.67 192.23 54297 +2010 142 23 11.3 19.78 0 706.88 407.3 54426 +2010 143 22.9 8.8 19.02 0 931.25 403.09 54552 +2010 144 26.2 9.4 21.58 0 1241.25 424.54 54675 +2010 145 28.9 12.5 24.39 0.02 1355 435.62 54795 +2010 146 26.8 13.7 23.2 0.04 1041.88 441.32 54911 +2010 147 27 11.5 22.74 0.17 935 427.63 55023 +2010 148 24.5 10.9 20.76 0 920 445.29 55132 +2010 149 23.5 14.5 21.02 0.14 718.13 380.19 55237 +2010 150 22.5 14.9 20.41 0.31 495.63 269.24 55339 +2010 151 16 11.7 14.82 0.22 395 116.43 55436 +2010 152 16 8.4 13.91 0.75 483.75 134.5 55530 +2010 153 13.4 10.2 12.52 4.37 91.88 91.55 55619 +2010 154 17.7 11.4 15.97 0.77 243.75 165.96 55705 +2010 155 21 12.9 18.77 0.52 503.12 174.38 55786 +2010 156 23.9 8.5 19.66 0 1096.25 513.64 55863 +2010 157 25.9 8.7 21.17 0.01 975 514.03 55936 +2010 158 27 10.9 22.57 0 938.75 467.22 56004 +2010 159 28.9 14.4 24.91 0 1119.37 459.7 56068 +2010 160 30 17.4 26.54 0 1453.12 493.52 56128 +2010 161 30.2 18.8 27.07 0 1746.88 435.44 56183 +2010 162 32.9 20.3 29.43 0 2296.88 470.14 56234 +2010 163 33 16.5 28.46 0 2157.5 480.71 56280 +2010 164 29.4 19.9 26.79 0 1207.5 466.4 56321 +2010 165 26.5 16.3 23.7 0.16 514.38 363.21 56358 +2010 166 27.4 12.2 23.22 0.03 1031.25 470.51 56390 +2010 167 23.5 15 21.16 3.02 116.88 60.8 56418 +2010 168 21 15.5 19.49 0.46 269.38 178.97 56440 +2010 169 25.9 14.7 22.82 1.53 639.38 354.12 56458 +2010 170 21 14.4 19.18 0 420.63 261.57 56472 +2010 171 17.2 13.6 16.21 0.51 300 111.03 56480 +2010 172 15.5 11.7 14.46 2.11 290 92.43 56484 +2010 173 20.5 13.9 18.68 0 790.62 287.25 56482 +2010 174 22.4 13.4 19.92 0 1066.88 509.88 56476 +2010 175 23.8 10.2 20.06 0 1135.63 426.05 56466 +2010 176 23.5 10.4 19.9 0.42 641.88 258.82 56450 +2010 177 22.1 13 19.6 0.03 685 144.23 56430 +2010 178 25.9 13.5 22.49 0 1236.87 498.88 56405 +2010 179 26.9 9.9 22.22 0.01 1164.38 494.91 56375 +2010 180 29 14.2 24.93 0 1436.25 489.8 56341 +2010 181 30.2 12.9 25.44 0 1648.75 503.54 56301 +2010 182 30.2 14.3 25.83 0 1645.62 438.72 56258 +2010 183 30.1 14.3 25.76 0.39 1461.25 439.02 56209 +2010 184 32 15.5 27.46 0.01 1605 460.52 56156 +2010 185 28.4 14.9 24.69 0.01 1473.13 446.32 56099 +2010 186 29 15.6 25.32 0 1273.75 320.39 56037 +2010 187 28 16.8 24.92 0.03 1116.88 277.58 55971 +2010 188 25 15 22.25 0 1281.88 368.81 55900 +2010 189 27.2 8.4 22.03 0 1388.13 491.18 55825 +2010 190 29 9.7 23.69 0 1807.5 486.83 55746 +2010 191 30.6 11.4 25.32 0 1993.75 496.86 55663 +2010 192 32.3 13.2 27.05 0.01 1930.62 477.3 55575 +2010 193 32.9 15.2 28.03 0 1901.25 466.62 55484 +2010 194 32.7 17.3 28.47 0.01 1213.12 346.51 55388 +2010 195 33.4 16.7 28.81 0 1858.12 479.4 55289 +2010 196 34 18.9 29.85 0 1628.13 433.41 55186 +2010 197 32.9 19.9 29.32 0 1758.08 428.47 55079 +2010 198 33.2 19.4 29.41 1.75 1847.96 437.66 54968 +2010 199 28.1 18 25.32 0 1165.13 368.13 54854 +2010 200 25 13.2 21.76 0 1086.9 450.95 54736 +2010 201 27.9 13.4 23.91 0 1430.57 370.91 54615 +2010 202 30.5 16.9 26.76 0 1589.98 444.6 54490 +2010 203 32.3 16.8 28.04 0 1875.02 464.56 54362 +2010 204 29.8 18.7 26.75 0.28 1356.35 380.29 54231 +2010 205 24.2 16.4 22.06 1.94 787.38 198.2 54097 +2010 206 18.7 13.9 17.38 0.04 396.45 132.4 53960 +2010 207 20.3 10.9 17.72 0.01 722.91 234.62 53819 +2010 208 25.3 13.7 22.11 0 1093.66 345.75 53676 +2010 209 27.3 15.6 24.08 0 1226.2 408.23 53530 +2010 210 26.1 13.9 22.75 2.5 1177.85 296.76 53382 +2010 211 19.5 13.7 17.91 0.22 483.74 115.37 53230 +2010 212 24.3 14.5 21.61 0 929.47 339.25 53076 +2010 213 27.7 12.4 23.49 0 1453.87 493.62 52920 +2010 214 29.2 13.6 24.91 0 1593 478.01 52761 +2010 215 26 15.9 23.22 2.23 1040.59 258.32 52600 +2010 216 25.3 14.7 22.39 0 1033.68 437.3 52437 +2010 217 25 11.7 21.34 1.79 1164.34 380.68 52271 +2010 218 22.7 16.4 20.97 1.02 616.63 198.52 52103 +2010 219 20.5 14.6 18.88 0.18 518.54 139.3 51934 +2010 220 26.7 14.5 23.34 0 1217.13 429.76 51762 +2010 221 23.6 16.1 21.54 0.13 740.2 198.8 51588 +2010 222 26.9 11.4 22.64 0 1399.96 348.32 51413 +2010 223 27.8 14.1 24.03 0 1380.48 446.81 51235 +2010 224 27.9 12.9 23.77 0 1455.52 415.53 51057 +2010 225 28.3 15.2 24.7 1.72 1383.54 404.86 50876 +2010 226 27.2 16 24.12 0.8 1187.03 368.78 50694 +2010 227 26.8 18 24.38 0.09 988.61 341.61 50510 +2010 228 25.3 14 22.19 0.03 1076.22 294.24 50325 +2010 229 25 13.7 21.89 0.3 1058.61 400.37 50138 +2010 230 23.1 14.6 20.76 0.11 788.79 285.75 49951 +2010 231 25.8 16.6 23.27 0 966.35 340.44 49761 +2010 232 25.5 16.1 22.91 0 964.92 315.36 49571 +2010 233 27.8 16.9 24.8 0 1205.13 422.04 49380 +2010 234 27.8 14.1 24.03 0 1380.48 448.07 49187 +2010 235 28.1 13.3 24.03 0 1461.57 459 48993 +2010 236 24.1 15.7 21.79 0.07 826.35 150.13 48798 +2010 237 19.5 16.7 18.73 0 259.37 180.65 48603 +2010 238 27 12.7 23.07 0 1351.94 430.94 48406 +2010 239 30.1 16.1 26.25 1.93 1581.45 342.89 48208 +2010 240 21.3 15.7 19.76 0.12 519.87 102.88 48010 +2010 241 20.6 7.4 16.97 0.01 903.8 358.93 47811 +2010 242 15.3 9 13.57 0.23 405.96 94.11 47611 +2010 243 14.9 7.4 12.84 0.21 451.89 216.65 47410 +2010 244 20.9 11.8 18.4 0 731.63 392.35 47209 +2010 245 21.4 6.6 17.33 0.05 1003.35 328.54 47007 +2010 246 18.6 10.2 16.29 0.04 607.38 236.83 46805 +2010 247 18.6 11.8 16.73 0.6 520.38 151.64 46601 +2010 248 18.2 8.9 15.64 0 636.46 383.92 46398 +2010 249 16.7 9.9 14.83 0.08 466.73 248.71 46194 +2010 250 12.7 6.4 10.97 0.05 348.29 85.9 45989 +2010 251 16.1 12.1 15 0.34 293.34 76.4 45784 +2010 252 20.4 14.7 18.83 0.26 501.66 231.98 45579 +2010 253 19.9 12.3 17.81 0 608.62 162.49 45373 +2010 254 21 13.6 18.97 0 634.77 185.43 45167 +2010 255 21.1 10.2 18.1 0 832.39 222.21 44961 +2010 256 21.8 8.5 18.14 0 972.18 342.95 44755 +2010 257 22.4 10.5 19.13 0 944.78 433.52 44548 +2010 258 23.1 13.2 20.38 0 875.69 320.79 44341 +2010 259 18.9 14.3 17.64 1.24 386.94 90.38 44134 +2010 260 15.9 14.2 15.43 3.42 133.88 74.82 43927 +2010 261 14.7 10.9 13.65 1.95 258.99 142.4 43719 +2010 262 16.7 10.3 14.94 0.13 445.63 232.97 43512 +2010 263 19.8 3.5 15.32 0 954.76 406.8 43304 +2010 264 20.9 4.4 16.36 0 1023.69 417.01 43097 +2010 265 21.6 5 17.04 0 1069.04 427.44 42890 +2010 266 21.4 4.9 16.86 0 1053.99 419.37 42682 +2010 267 22.5 7.3 18.32 0 1082.6 374.13 42475 +2010 268 17.5 10.9 15.68 4.48 477.74 124.44 42268 +2010 269 15.2 11.2 14.1 1.35 278.57 57.04 42060 +2010 270 14.9 8.1 13.03 0 420.32 163.07 41854 +2010 271 19.9 9.6 17.07 0.02 750.19 263.23 41647 +2010 272 17 7.5 14.39 0.37 602.07 255.11 41440 +2010 273 12.5 8.5 11.4 0 238 148.64 41234 +2010 274 12.7 8.7 11.6 0 240.82 149.01 41028 +2010 275 14.2 9.6 12.93 0 295.78 171.15 40822 +2010 276 13.2 10.1 12.35 0 198.68 119.74 40617 +2010 277 18.5 10.5 16.3 0 583.38 260.99 40412 +2010 278 18.4 11.9 16.61 0.76 497.06 166.26 40208 +2010 279 12 10.1 11.48 0.13 118.67 58.42 40003 +2010 280 16.6 7.3 14.04 0 579.94 265.58 39800 +2010 281 14.2 4.1 11.42 0 530.61 215.76 39597 +2010 282 15.2 0.5 11.16 0 692.56 304.62 39394 +2010 283 15.8 2 12.01 0 696.82 323.16 39192 +2010 284 15.3 0.2 11.15 0 705.3 327.4 38991 +2010 285 16.1 -0.1 11.65 0 763.07 258.04 38790 +2010 286 14.5 1.9 11.04 0 614.66 184.16 38590 +2010 287 15.1 4.3 12.13 0 583.59 291.47 38391 +2010 288 13.2 2.3 10.2 0 523.35 254.45 38193 +2010 289 13.2 6.7 11.41 0 367.46 175.09 37995 +2010 290 9.5 2.5 7.58 1.59 310.54 58.21 37799 +2010 291 8.8 6.5 8.17 0.45 117 48.98 37603 +2010 292 8.5 6.8 8.03 0.04 86.89 40.22 37408 +2010 293 7.2 4.5 6.46 0.62 122.71 52.89 37214 +2010 294 12.9 2.5 10.04 0 499.54 278.46 37022 +2010 295 13.5 -2 9.24 0 638.64 341.14 36830 +2010 296 14.6 -0.5 10.45 0 675.77 261.24 36640 +2010 297 17.5 5 14.06 0.38 732.26 244.85 36451 +2010 298 10 5.2 8.68 0.83 238.71 23.86 36263 +2010 299 8.4 3.7 7.11 0 212.84 81.08 36076 +2010 300 9.2 -1.9 6.15 0 412.99 311.54 35891 +2010 301 10 -4 6.15 0 490.15 299.71 35707 +2010 302 13 -2.5 8.74 0 619.1 309.66 35525 +2010 303 16.9 -1.4 11.87 0 838.36 295.29 35345 +2010 304 16.9 8.6 14.62 0 546.05 213.31 35166 +2010 305 17.4 5.6 14.15 0 704.73 151.33 34988 +2010 306 14.9 7.3 12.81 0 456.25 120.28 34813 +2010 307 11.5 6.3 10.07 0.09 278.8 76.98 34639 +2010 308 17.3 6 14.19 0 683.1 219.98 34468 +2010 309 20.3 3 15.54 0 1007.35 247.78 34298 +2010 310 15.6 2 11.86 0 683.47 222.73 34130 +2010 311 16.2 3.3 12.65 0 689.47 188.8 33964 +2010 312 13.4 8 11.91 0.71 321.72 39.86 33801 +2010 313 14 7.2 12.13 0.48 398.64 98.91 33640 +2010 314 11.1 7 9.97 0.42 223.67 63.97 33481 +2010 315 12.3 2.7 9.66 0 458.09 202.58 33325 +2010 316 16.2 2.7 12.49 0 705.95 133.09 33171 +2010 317 18.2 4.1 14.32 0 812.78 191.88 33019 +2010 318 18.5 1.1 13.72 0 907.11 237.92 32871 +2010 319 19.8 4.8 15.68 0 920.05 204.02 32725 +2010 320 14.6 6.1 12.26 0 485.06 121.98 32582 +2010 321 11.3 7.9 10.37 0.44 192.69 57.48 32441 +2010 322 12.9 8.3 11.64 0.18 274.08 93.8 32304 +2010 323 8.6 4.4 7.45 1.24 196.27 21.3 32170 +2010 324 7.8 5.1 7.06 0 127.29 57.27 32039 +2010 325 7.2 5.1 6.62 1.07 97.68 51.87 31911 +2010 326 10 6.9 9.15 0.24 164.42 49.68 31786 +2010 327 9.1 2.4 7.26 0 293.35 111.55 31665 +2010 328 9 -0.8 6.3 0 378.55 205.32 31547 +2010 329 8.5 -3.6 5.17 0 414.36 231.49 31433 +2010 330 2.1 -4.2 0.37 0.76 179.7 129.04 31322 +2010 331 5 -0.7 3.43 0 200.78 214.87 31215 +2010 332 0.4 -2.6 -0.43 2.17 87.64 31.95 31112 +2010 333 2.4 -1 1.46 0 111.22 76.52 31012 +2010 334 -0.6 -5.6 -1.97 0.2 125.9 93.33 30917 +2010 335 -1.7 -2.9 -2.03 1.09 32.92 44.23 30825 +2010 336 -0.1 -1.8 -0.57 1.03 50.71 37.58 30738 +2010 337 -0.6 -2.2 -1.04 1.07 46.39 62.65 30654 +2010 338 -1.8 -9.1 -3.81 0 153.99 99.78 30575 +2010 339 -2.2 -9.3 -4.15 0 146.97 74.2 30500 +2010 340 7.2 -4 4.12 0 365.55 132.7 30430 +2010 341 13.5 4 10.89 0.02 489.27 98.48 30363 +2010 342 15.3 3.1 11.95 0.12 633.82 77.93 30301 +2010 343 14 -0.1 10.12 0.52 631.17 18.62 30244 +2010 344 1.3 -5.8 -0.65 0.32 185.96 145.51 30191 +2010 345 2 -9 -1.02 0 257.29 79.95 30143 +2010 346 5.6 -5.5 2.55 0 328.01 79 30099 +2010 347 1 -4 -0.38 0 139.94 133.86 30060 +2010 348 0.7 -10.8 -2.46 0 241.33 151.36 30025 +2010 349 0.2 -5.3 -1.31 0 143.05 112.92 29995 +2010 350 -2.5 -10.2 -4.62 0 152.23 141.44 29970 +2010 351 -3.8 -11.5 -5.92 0.93 139.15 84.76 29950 +2010 352 -4.6 -8.2 -5.59 0.16 73.42 97.42 29934 +2010 353 -1.4 -15.8 -5.36 0 231.44 115.84 29924 +2010 354 3.6 -10.2 -0.19 0 320.69 173.97 29918 +2010 355 6.1 -8.5 2.09 0 388.03 156.62 29916 +2010 356 9.2 1 6.94 0 341.06 49.3 29920 +2010 357 12.8 2.6 10 0.08 490.62 113.02 29928 +2010 358 11.6 0.5 8.55 0.66 479.62 130.06 29941 +2010 359 5 0.5 3.76 0.17 166.22 49.83 29959 +2010 360 1.3 -2.9 0.15 0 123.86 75.77 29982 +2010 361 1 -6 -0.93 0 180.47 180.44 30009 +2010 362 0.3 -8.4 -2.09 0 199.54 92.44 30042 +2010 363 -1.8 -9.5 -3.92 0 159.71 129.29 30078 +2010 364 -3.9 -10.5 -5.71 0 124.17 52.55 30120 +2010 365 -4.7 -6.2 -5.11 0 33.25 25.02 30166 +2011 1 -3.7 -5.6 -4.22 0 44.3 37.7 30217 +2011 2 -1.6 -4.7 -2.45 0.09 79.06 23.52 30272 +2011 3 1.4 -8.8 -1.41 0 236.8 99.21 30331 +2011 4 -3.6 -11 -5.63 0 137.35 59.2 30396 +2011 5 -3.5 -4.6 -3.8 0 26.89 29.83 30464 +2011 6 -2.7 -5.9 -3.58 0 75.51 180.81 30537 +2011 7 12.5 -4 7.96 0 615.21 146.34 30614 +2011 8 11.9 0.6 8.79 0 493.64 58.79 30695 +2011 9 14.4 -2.6 9.73 0 700.46 154.65 30781 +2011 10 9.6 -1.1 6.66 0.05 414.56 60.47 30870 +2011 11 3.9 1.6 3.27 0 86.5 40.22 30964 +2011 12 6 -0.2 4.29 0.04 228.12 76.72 31061 +2011 13 6 -0.7 4.16 0.07 241.72 64.17 31162 +2011 14 11.3 2.6 8.91 0 404.04 80.69 31268 +2011 15 13.3 -0.4 9.53 0 596.25 141.11 31376 +2011 16 12.5 -0.8 8.84 0 559.27 159.75 31489 +2011 17 2.3 -2.9 0.87 0 157.13 84.97 31605 +2011 18 3.1 -1.8 1.75 0 157.82 96.47 31724 +2011 19 3 -2.5 1.49 0.82 171.8 27.13 31847 +2011 20 3.3 -0.9 2.14 0 140.93 111.58 31974 +2011 21 1.8 -0.7 1.11 0 81.61 124.8 32103 +2011 22 0.4 -2.1 -0.29 0 74.55 83.57 32236 +2011 23 1.4 -8.2 -1.24 0.16 228.43 224 32372 +2011 24 1.4 -3.9 -0.06 0.03 150.41 284.53 32510 +2011 25 0.5 -6.2 -1.34 0 169.17 95.69 32652 +2011 26 2.3 -4.6 0.4 0.03 194.6 98.88 32797 +2011 27 0.7 -2.6 -0.21 0.06 97.1 46.92 32944 +2011 28 -0.6 -5.3 -1.89 0 119.83 104.33 33094 +2011 29 -0.8 -7.5 -2.64 0 155.08 118.91 33247 +2011 30 -1.9 -5.9 -3 0 96.29 70.66 33402 +2011 31 -2 -3.3 -2.36 0 34.81 59.57 33559 +2011 32 -0.8 -5.7 -2.15 0 122.26 162.4 33719 +2011 33 -1.5 -5.8 -2.68 0 104.99 149.27 33882 +2011 34 3.6 -10.5 -0.28 0 323.71 222.7 34046 +2011 35 7 -4.9 3.73 0 373.06 241.09 34213 +2011 36 14.3 -3.2 9.49 0 703.44 259.99 34382 +2011 37 11 -3.6 6.99 0 532.21 229.84 34552 +2011 38 18.5 -4.5 12.18 0 980.57 282.01 34725 +2011 39 12.3 -4.5 7.68 0 611.61 263.46 34900 +2011 40 9 -3.8 5.48 0 440.42 249.39 35076 +2011 41 9.1 -4.6 5.33 0 458.19 278.06 35254 +2011 42 12 -3.1 7.85 0.05 575.17 161.96 35434 +2011 43 4.6 1.1 3.64 0.01 131.16 80.93 35615 +2011 44 4 -0.3 2.82 0.03 150.27 94.66 35798 +2011 45 0.8 -0.5 0.44 0 41.78 32.23 35983 +2011 46 -0.5 -2 -0.91 0.08 43.96 42.19 36169 +2011 47 1.1 -2.1 0.22 0.29 97.04 45.1 36356 +2011 48 0.7 -0.3 0.42 0.12 32.33 49.59 36544 +2011 49 2.9 0.5 2.24 0.01 84.39 62.89 36734 +2011 50 6.9 -0.1 4.98 0 264.18 126.35 36925 +2011 51 2.7 -0.8 1.74 0 116.24 88.41 37117 +2011 52 -0.2 -4.8 -1.47 0.03 120.94 132.32 37310 +2011 53 -2.7 -5.5 -3.47 0.01 67.2 104.81 37505 +2011 54 -0.2 -8.6 -2.51 0 188.61 295.12 37700 +2011 55 1.4 -8.7 -1.38 0 235.44 327.23 37896 +2011 56 1.7 -10.7 -1.71 0 268.37 305.28 38093 +2011 57 2.1 -5.2 0.09 0 199.91 178.75 38291 +2011 58 -0.3 -7.9 -2.39 0 175.24 103.59 38490 +2011 59 3.9 -2 2.28 0 192.19 232.22 38689 +2011 60 0.5 -4.9 -0.99 0.05 143.86 60.91 38890 +2011 61 2.1 -7.3 -0.48 0.17 236.3 200.44 39091 +2011 62 0 -2.1 -0.58 0.01 62.02 78.09 39292 +2011 63 5.1 -6.5 1.91 0 325.25 244.37 39495 +2011 64 7.2 -5.9 3.6 0 396.89 367.39 39697 +2011 65 6.9 -4.8 3.68 0 367.3 331.27 39901 +2011 66 3.7 -2.6 1.97 0 199.37 319.48 40105 +2011 67 5.9 -9.4 1.69 0 390.31 391.53 40309 +2011 68 9.2 -7.4 4.63 0 499.54 337.08 40514 +2011 69 12.7 -4.1 8.08 0 627.21 190.12 40719 +2011 70 14.5 -4 9.41 0 725.54 339.43 40924 +2011 71 15.6 -4 10.21 0 790.4 353.72 41130 +2011 72 17 7.9 14.5 0 585.08 302.73 41336 +2011 73 18.9 7.9 15.87 0 737.88 270.55 41543 +2011 74 20.1 2.1 15.15 0 1010.44 351.35 41749 +2011 75 11.6 3.4 9.35 1.1 395.21 72.92 41956 +2011 76 16 8.7 13.99 0.15 472.52 157.18 42163 +2011 77 12.6 5.8 10.73 0.23 366.81 85.45 42370 +2011 78 7.8 3.4 6.59 0 194.28 67.33 42578 +2011 79 10 3.2 8.13 0 313.44 338.2 42785 +2011 80 10.1 -1.3 6.96 0 443.68 366.02 42992 +2011 81 14.6 -3.6 9.59 0 726.26 397.67 43200 +2011 82 16.1 -1.5 11.26 0 787.66 393.59 43407 +2011 83 20 -1 14.23 0 1053.53 410.5 43615 +2011 84 21.5 -1 15.31 0 1171.33 402.79 43822 +2011 85 21.4 1.4 15.9 1.01 1129.99 330.12 44029 +2011 86 11.1 4.6 9.31 0.03 324 44.59 44236 +2011 87 10.3 3 8.29 0 336.27 166.17 44443 +2011 88 16.5 1 12.24 0 767.35 413.1 44650 +2011 89 18.2 -1.1 12.89 0 922.93 441.54 44857 +2011 90 20.1 -0.3 14.49 0.02 1051.75 359.66 45063 +2011 91 18.6 6 15.14 0 784.59 180.23 45270 +2011 92 20.7 3.1 15.86 0 1038.21 468.73 45475 +2011 93 22.3 3 16.99 0 1178.26 391.41 45681 +2011 94 23.1 4 17.85 1.18 1230.26 328.4 45886 +2011 95 16.3 5.2 13.25 0 637.16 395.01 46091 +2011 96 18.2 1 13.47 0 887.04 220.53 46295 +2011 97 26.4 8.7 21.53 0 1443.93 418.59 46499 +2011 98 21.3 12.2 18.8 0 748.29 312.76 46702 +2011 99 21.5 5 16.96 0 1060.14 472.39 46905 +2011 100 19.8 4.5 15.59 0 928.53 461.85 47107 +2011 101 19.1 8.9 16.3 0 712.08 343.99 47309 +2011 102 20.4 6 16.44 0.91 934.32 250.62 47510 +2011 103 12.6 3 9.96 0 466.52 346.07 47710 +2011 104 12.2 4 9.95 0 409.84 202.34 47910 +2011 105 12.8 -0.1 9.25 0 560.93 296.59 48108 +2011 106 13.5 4.7 11.08 0 465.13 231.06 48306 +2011 107 16.5 0.7 12.15 0 773.71 343.7 48504 +2011 108 18.2 0.4 13.31 0 898.4 354.11 48700 +2011 109 20.3 0 14.72 0 1062.97 404.63 48895 +2011 110 22.3 1.9 16.69 0 1198.56 485.54 49089 +2011 111 24.3 2.1 18.2 0 1377.85 480.69 49282 +2011 112 24.2 3.3 18.45 0 1348.57 473.54 49475 +2011 113 24.4 3.6 18.68 0 1362.44 474.35 49666 +2011 114 24.4 8.5 20.03 0 1231.83 425.82 49855 +2011 115 21 7.5 17.29 1.98 935.99 374.03 50044 +2011 116 13.1 10 12.25 1.29 197.52 68.3 50231 +2011 117 17.7 5.7 14.4 0.52 724.21 261.01 50417 +2011 118 17.8 6.5 14.69 0.13 703.42 331.85 50601 +2011 119 18 10.2 15.86 0.53 556.68 267.79 50784 +2011 120 18.5 9 15.89 0.11 656.81 309.8 50966 +2011 121 18.2 6.7 15.04 0.52 727.58 265.3 51145 +2011 122 18.8 5 15.01 0 833.01 441.63 51324 +2011 123 22.1 8.3 18.31 0.55 1008.48 333.6 51500 +2011 124 13.3 1 9.92 0 564 535.67 51674 +2011 125 14.6 0.4 10.7 0 656.97 541.72 51847 +2011 126 18.1 -1 12.85 0 914.4 553.08 52018 +2011 127 21.1 1.8 15.79 0 1097.94 537.03 52187 +2011 128 18.1 3.4 14.06 0.3 824.42 172.19 52353 +2011 129 19.5 1.5 14.55 0 975.05 494.84 52518 +2011 130 24.3 5 18.99 0 1323.3 525.48 52680 +2011 131 24.4 7 19.61 0 1280.61 521.76 52840 +2011 132 26.8 7 21.36 0.43 1539.2 493.23 52998 +2011 133 22 12.5 19.39 0 801.27 519.18 53153 +2011 134 24.9 9.7 20.72 0.8 1240.53 412.02 53306 +2011 135 18.1 10.7 16.07 0.94 538.78 126.22 53456 +2011 136 17.9 10.2 15.78 0 548.34 427.55 53603 +2011 137 19.7 7.2 16.26 0 832.78 421.07 53748 +2011 138 23.4 6.4 18.72 0 1197.99 481.98 53889 +2011 139 25.9 8 20.98 0 1410.17 487.93 54028 +2011 140 26.9 9.2 22.03 0 1484.94 508.93 54164 +2011 141 27 10.8 22.54 0 1437.21 414.66 54297 +2011 142 27 10.6 22.49 0 1445.23 493.65 54426 +2011 143 27 11.4 22.71 0 1412.07 391.71 54552 +2011 144 28.7 11.9 24.08 0 1604.55 512.42 54675 +2011 145 23.3 13.5 20.61 0 879.53 511.56 54795 +2011 146 26.3 6.7 20.91 0 1491.18 517.64 54911 +2011 147 29.4 10.4 24.17 0.13 1753.67 496.15 55023 +2011 148 19.9 10.4 17.29 0.59 711.67 217.25 55132 +2011 149 23.4 5.4 18.45 0 1225.43 454.84 55237 +2011 150 25.3 7.3 20.35 0 1366.08 515.62 55339 +2011 151 28.4 9.4 23.17 0 1659.31 507.54 55436 +2011 152 25.5 12.6 21.95 0.1 1176.89 276.31 55530 +2011 153 24.3 13.4 21.3 0.05 995.86 344.29 55619 +2011 154 26.7 15.4 23.59 0.02 1161.75 395.19 55705 +2011 155 26.6 13.2 22.91 1.11 1277.22 396.96 55786 +2011 156 26.5 13.2 22.84 0 1264.98 399.02 55863 +2011 157 26.8 14.2 23.34 0 1247.13 424.09 55936 +2011 158 28.1 13.5 24.09 2.1 1451.42 430.2 56004 +2011 159 25.3 14.7 22.39 1.41 1033.68 375.01 56068 +2011 160 20.9 15.7 19.47 0.5 478.77 245.75 56128 +2011 161 22.8 12.9 20.08 0 861.2 518.27 56183 +2011 162 24.4 9.1 20.19 0 1209.9 541.61 56234 +2011 163 24.4 9.9 20.41 0 1178.39 470.82 56280 +2011 164 25.4 11.9 21.69 0 1200.24 451.45 56321 +2011 165 25.2 15 22.4 0.08 1002.68 289.78 56358 +2011 166 27.6 14.4 23.97 0 1337.73 500.57 56390 +2011 167 28.8 11.6 24.07 0 1630.08 490.06 56418 +2011 168 25.5 14.4 22.45 0 1076.07 371.97 56440 +2011 169 28.4 18.1 25.57 2.62 1199.44 281.41 56458 +2011 170 24.3 11.1 20.67 0.6 1115.13 167.14 56472 +2011 171 23.8 7.9 19.43 0 1190.6 495.5 56480 +2011 172 27.5 11.3 23.04 0 1477.53 497.85 56484 +2011 173 29.5 13.1 24.99 0 1658.01 505.84 56482 +2011 174 27.5 17.5 24.75 2.79 1120.86 446.23 56476 +2011 175 23.2 14.7 20.86 0.49 793.15 213.47 56466 +2011 176 23.3 9.5 19.5 0 1079.65 434.92 56450 +2011 177 23.6 13.4 20.8 0.08 918.14 251.29 56430 +2011 178 25.3 13.4 22.03 0 1110.63 454.02 56405 +2011 179 26.3 13.9 22.89 0 1202.25 545.28 56375 +2011 180 28.5 12.5 24.1 0 1552.05 543.93 56341 +2011 181 30.1 13.3 25.48 0 1731.82 429.51 56301 +2011 182 23.3 12.3 20.28 0.04 947.47 451.84 56258 +2011 183 19 11.2 16.86 0.19 589.42 369.13 56209 +2011 184 20.6 7 16.86 0 918.19 233.07 56156 +2011 185 25.9 12.7 22.27 0.09 1218.77 320 56099 +2011 186 23.1 11.9 20.02 0.12 947.46 255.2 56037 +2011 187 28.8 13.1 24.48 0.01 1563.53 461.63 55971 +2011 188 31.9 13.9 26.95 0 1966.52 510.87 55900 +2011 189 32.4 19.9 28.96 0 1673.51 435.79 55825 +2011 190 33.7 13.9 28.26 0 2248.16 509.47 55746 +2011 191 32.7 16.2 28.16 0 1974.31 506.78 55663 +2011 192 30.4 16.6 26.61 0 1594.39 477.65 55575 +2011 193 30.2 14.5 25.88 0 1686.78 503.71 55484 +2011 194 33.5 15.5 28.55 0 2141.78 399.48 55388 +2011 195 30.6 19.4 27.52 3.46 1422.91 389.31 55289 +2011 196 23.6 14.4 21.07 0 856.89 297.95 55186 +2011 197 25.4 12.7 21.91 0 1160.07 446 55079 +2011 198 29.2 12.5 24.61 0.02 1644.65 507.52 54968 +2011 199 26.9 16.9 24.15 0.04 1085.29 418.22 54854 +2011 200 26.9 12.1 22.83 0.2 1368.45 390.68 54736 +2011 201 23.4 15.1 21.12 0.47 788.44 195.75 54615 +2011 202 26 14 22.7 0.12 1159.97 357.51 54490 +2011 203 25.8 13 22.28 0.32 1191.28 320.28 54362 +2011 204 19.1 14.7 17.89 0.91 376.92 115.02 54231 +2011 205 16.3 12.6 15.28 1.95 277.43 66.22 54097 +2011 206 15.9 11.6 14.72 0.04 308.4 118.97 53960 +2011 207 18.6 13.1 17.09 0 440.7 82.84 53819 +2011 208 25.8 12.7 22.2 0.03 1206.94 497.8 53676 +2011 209 21.7 15 19.86 3.2 612.19 47.84 53530 +2011 210 24.5 14.6 21.78 0 946.11 379.28 53382 +2011 211 25.6 11.2 21.64 0.02 1255.75 276.44 53230 +2011 212 23.7 14.2 21.09 0 880.67 246.83 53076 +2011 213 24.4 12.8 21.21 0.06 1040.63 308.38 52920 +2011 214 27.3 15.9 24.17 0 1206.73 473.24 52761 +2011 215 27.9 12.8 23.75 0.86 1460.37 374.56 52600 +2011 216 23.9 17.7 22.19 1.05 650.04 92.34 52437 +2011 217 26.7 14.5 23.34 0 1217.13 452.26 52271 +2011 218 26.5 13.9 23.04 0 1226.84 380.6 52103 +2011 219 30.5 16.4 26.62 0 1621.86 445.55 51934 +2011 220 24.3 15.3 21.82 1.41 877.08 258.79 51762 +2011 221 23 13.4 20.36 0.46 853.19 362.47 51588 +2011 222 21.4 11 18.54 0 822.02 353.76 51413 +2011 223 24.1 6.2 19.18 0 1273.02 517.59 51235 +2011 224 26.4 9.1 21.64 0 1430.45 442 51057 +2011 225 25.9 15.5 23.04 0 1055.02 307.52 50876 +2011 226 28.5 13.2 24.29 0 1518.93 474.66 50694 +2011 227 30 14.3 25.68 1.28 1668.69 460.87 50510 +2011 228 25.5 14.7 22.53 0 1057.62 459.57 50325 +2011 229 27.7 13.4 23.77 0 1404.81 465.7 50138 +2011 230 29.8 14.4 25.57 0 1635.21 457.55 49951 +2011 231 30.8 14.9 26.43 1.58 1752.83 359.33 49761 +2011 232 27 14.7 23.62 0 1243.17 450.57 49571 +2011 233 29.1 15.8 25.44 0 1456.93 429.77 49380 +2011 234 32 17.3 27.96 0 1795.86 433.39 49187 +2011 235 33.2 18 29.02 0 1946.62 451.94 48993 +2011 236 34 16.4 29.16 0 2177.85 462.5 48798 +2011 237 31.3 16.7 27.29 0 1724.25 445.46 48603 +2011 238 33.5 16 28.69 0 2115.79 446.39 48406 +2011 239 31.8 16.9 27.7 0.71 1789.56 432.02 48208 +2011 240 22.8 12.5 19.97 0 883.76 391.15 48010 +2011 241 26.3 10.1 21.84 0 1382.33 440.34 47811 +2011 242 24.5 12.5 21.2 0 1067.88 387.15 47611 +2011 243 25.8 13.3 22.36 0 1175.17 425.78 47410 +2011 244 28.8 12.5 24.32 0.31 1591.43 401.06 47209 +2011 245 26.6 13.4 22.97 0.09 1266.61 393.99 47007 +2011 246 27.8 13.4 23.84 0 1417.66 478.24 46805 +2011 247 30.1 13.4 25.51 0 1727.15 426.52 46601 +2011 248 28.3 17.9 25.44 0.11 1200.69 382.72 46398 +2011 249 24.6 14.1 21.71 0 988.67 413.72 46194 +2011 250 25.9 8.9 21.22 0 1380.68 374.31 45989 +2011 251 21.9 14.7 19.92 0.02 653.82 178.57 45784 +2011 252 21.5 14.4 19.55 0 632.78 182.48 45579 +2011 253 28.8 13.4 24.57 0 1548.92 424.04 45373 +2011 254 30.2 12.4 25.31 0 1785.49 428.87 45167 +2011 255 28.2 14.9 24.54 0.22 1387.87 299.06 44961 +2011 256 28.1 13 23.95 0 1476.43 407.23 44755 +2011 257 29.1 13.8 24.89 0.04 1569.33 377.41 44548 +2011 258 21.4 11.1 18.57 0 816.95 230.49 44341 +2011 259 25 12.4 21.54 0 1129.55 362.26 44134 +2011 260 26.6 10.3 22.12 0 1409.56 362.77 43927 +2011 261 28.4 10.5 23.48 0.23 1621.41 376.81 43719 +2011 262 20.6 10.2 17.74 2.37 785.56 243.52 43512 +2011 263 17.7 10 15.58 0 542.08 124.93 43304 +2011 264 22.1 11.3 19.13 0 875.76 350.06 43097 +2011 265 23.6 12.2 20.47 0 984.9 315.25 42890 +2011 266 23.3 10.4 19.75 0 1040.97 364.36 42682 +2011 267 22.4 10.2 19.04 0 958.6 311.2 42475 +2011 268 23.6 7.2 19.09 0 1193.43 379.82 42268 +2011 269 24.6 6.5 19.62 0 1315.53 375.16 42060 +2011 270 25.6 7 20.48 0 1406.87 351.21 41854 +2011 271 24.3 7.9 19.79 0 1241.96 352.42 41647 +2011 272 23.6 5.3 18.57 0 1247.33 378.73 41440 +2011 273 24.5 8.2 20.02 0 1252.75 363.85 41234 +2011 274 26.3 7.3 21.08 0 1475.13 362.51 41028 +2011 275 25.6 7.9 20.73 0 1380.32 363.99 40822 +2011 276 25.6 6.3 20.29 0 1425.53 351.85 40617 +2011 277 26.3 6.3 20.8 0 1501.18 339.76 40412 +2011 278 25.4 7 20.34 0 1385.41 339 40208 +2011 279 24.3 8.4 19.93 0 1224.87 299.77 40003 +2011 280 18.6 6 15.14 3.88 784.59 26.13 39800 +2011 281 15.1 0.1 10.98 0 694.69 252.18 39597 +2011 282 12.4 -0.5 8.85 0 547.26 228.65 39394 +2011 283 9.3 -1.3 6.38 0.08 404.58 115.1 39192 +2011 284 23.4 7.2 18.95 0 1173.54 254.92 38991 +2011 285 19.7 8.7 16.68 0.07 340.91 203.99 38790 +2011 286 13.3 8.6 12.01 0 391.82 165.99 38590 +2011 287 11.5 0.9 8.59 0 431.82 302.34 38391 +2011 288 12.9 -2.2 8.75 0 404.55 357.78 38193 +2011 289 10.8 -0.7 7.64 0 510 352.76 37995 +2011 290 12.2 -4.5 7.61 0 525.45 350.44 37799 +2011 291 14.4 -3.6 9.45 0 600 329.07 37603 +2011 292 20.4 -2.1 14.21 1.42 758.18 297.87 37408 +2011 293 15 5.2 12.31 0.39 208.18 75.38 37214 +2011 294 10.7 1.9 8.28 0 375.45 250.76 37022 +2011 295 9.8 -3.1 6.25 0 276.36 229.01 36830 +2011 296 7.9 4.8 7.05 0.73 70 40.34 36640 +2011 297 9.4 6.7 8.66 0.59 28.18 33.67 36451 +2011 298 10.7 7 9.68 0.01 50.91 60.38 36263 +2011 299 10.4 8.2 9.79 0.31 117.27 69.64 36076 +2011 300 9.6 7.9 9.13 0.06 76 53.39 35891 +2011 301 12.2 8.9 11.29 0 92 80.89 35707 +2011 302 11.8 8.9 11 0 208 80.12 35525 +2011 303 13.8 6.8 11.88 0 400 195.03 35345 +2011 304 15 1.9 11.4 0 218 256.84 35166 +2011 305 7.2 2.4 5.88 0.05 25 45.47 34988 +2011 306 7.2 6.4 6.98 0.01 53 52.73 34813 +2011 307 9.1 5 7.97 0.01 70 63.39 34639 +2011 308 18.8 5 15.01 0 488 233.18 34468 +2011 309 20.1 13 18.15 0 678.89 192.31 34298 +2011 310 15.3 5 12.47 0 300 144.54 34130 +2011 311 10.7 1.8 8.25 0 194.44 145.7 33964 +2011 312 12.2 5 10.22 0 196.67 201.43 33801 +2011 313 8.8 3.1 7.23 0.03 20 65.27 33640 +2011 314 8.5 6.4 7.92 0 16.67 44.67 33481 +2011 315 7.6 -0.5 5.37 0 312.22 229.61 33325 +2011 316 8.7 -2.8 5.54 0 243.33 207.79 33171 +2011 317 9.7 -4.6 5.77 0 298.89 234.68 33019 +2011 318 8.2 -4.4 4.73 0 175 195.39 32871 +2011 319 5 -3.9 2.55 0 86.67 196.29 32725 +2011 320 -0.1 -3.6 -1.06 0 18.89 63.75 32582 +2011 321 1.7 -2.9 0.43 0 15.56 56.75 32441 +2011 322 0.9 -1.3 0.3 0 10 53.41 32304 +2011 323 -0.5 -2 -0.91 0 20 28.98 32170 +2011 324 -0.8 -1.7 -1.05 0.03 20 21.52 32039 +2011 325 -1.7 -3.7 -2.25 0 20 22.36 31911 +2011 326 -2.7 -3.9 -3.03 0 20 22.92 31786 +2011 327 -0.4 -3.8 -1.34 0 20 27.65 31665 +2011 328 0.2 -1.1 -0.16 0.05 14.44 28.29 31547 +2011 329 0.2 -1.2 -0.19 0.01 10 20.62 31433 +2011 330 2 0 1.45 0 10 38.36 31322 +2011 331 1.1 -0.9 0.55 0 10 62.18 31215 +2011 332 11.2 -2.7 7.38 0 158.89 199.06 31112 +2011 333 3.2 -3.9 1.25 0 12.22 99.18 31012 +2011 334 0.7 -1.3 0.15 0.01 10 35.42 30917 +2011 335 0.8 -1.7 0.11 0 10 58.28 30825 +2011 336 0.5 -1.7 -0.1 0.02 10 30.55 30738 +2011 337 1.5 -0.3 1 0.03 10 31.19 30654 +2011 338 9.2 1.1 6.97 0 65.56 116.63 30575 +2011 339 12.9 3.1 10.21 0.14 505.56 18.87 30500 +2011 340 7 -1.7 4.61 0 267.78 110.25 30430 +2011 341 4.9 -2.9 2.76 0.04 166.67 91.62 30363 +2011 342 9.1 -1.2 6.27 0 545.56 194.96 30301 +2011 343 4.1 -3.5 2.01 0 301.11 65.94 30244 +2011 344 7.8 -0.1 5.63 0 283.33 96.04 30191 +2011 345 5.5 -0.4 3.88 0 202.22 43.43 30143 +2011 346 10 3.2 8.13 0.73 112.22 102.13 30099 +2011 347 8.9 -0.8 6.23 0 66.25 128.07 30060 +2011 348 12 -1.7 8.23 0.43 215 143.31 30025 +2011 349 10.3 4.3 8.65 0.82 42.5 18.54 29995 +2011 350 9.3 -1.1 6.44 1.71 115 93.23 29970 +2011 351 10.2 1 7.67 0 381.25 67.07 29950 +2011 352 7.5 -3.9 4.37 0 386.25 180.79 29934 +2011 353 1.9 -3.7 0.36 0 117.5 41.49 29924 +2011 354 3.7 -7.1 0.73 0.01 271.25 182.13 29918 +2011 355 3.2 -7.7 0.2 0 136.25 70.58 29916 +2011 356 5.5 -4.1 2.86 0 201.25 131.52 29920 +2011 357 4.9 -2.5 2.87 0.03 60 61.63 29928 +2011 358 4.8 -2.9 2.68 0 132.5 128.63 29941 +2011 359 8.7 -3.3 5.4 0 433.75 169.15 29959 +2011 360 5.2 -0.1 3.74 0 270 40.49 29982 +2011 361 8.2 0 5.94 0 157.5 79.64 30009 +2011 362 2.2 -0.6 1.43 0 13.75 32.01 30042 +2011 363 1.9 -0.9 1.13 0 26.25 29.42 30078 +2011 364 3 -0.6 2.01 0 82.5 52.87 30120 +2011 365 8.5 -3.9 5.09 0 378.75 189.57 30166 +2012 1 6 -0.6 4.19 0 166.25 71.59 30217 +2012 2 12.1 -2.4 8.11 0.44 405 150.32 30272 +2012 3 8.5 2.7 6.9 0 60 63.96 30331 +2012 4 5.9 -1.6 3.84 0.07 92.5 91.83 30396 +2012 5 6.3 -1.7 4.1 0 203.75 42.67 30464 +2012 6 8.8 -1.6 5.94 0 503.75 189.6 30537 +2012 7 8.2 -3.5 4.98 0 361.25 141.91 30614 +2012 8 8.4 -2 5.54 0 312.5 127.47 30695 +2012 9 8.3 -1.1 5.72 0.06 318.75 112.87 30781 +2012 10 8.8 -1 6.11 0.03 281.25 117.68 30870 +2012 11 9.1 -3.3 5.69 0 333.33 156.74 30964 +2012 12 10.2 -2.5 6.71 0 443.33 195.25 31061 +2012 13 9.7 -2.5 6.34 0 487.78 198.96 31162 +2012 14 5.4 -3.1 3.06 0 288.89 172.29 31268 +2012 15 4.1 -5.6 1.43 0 201.11 130.49 31376 +2012 16 3 -4 1.08 0 282.22 193.22 31489 +2012 17 4.4 -5 1.82 0 315.56 99.1 31605 +2012 18 8.2 -1.5 5.53 0 492.22 184.39 31724 +2012 19 7.8 -4 4.55 0.01 331 63.9 31847 +2012 20 5.4 -0.6 3.75 0.1 90 30.36 31974 +2012 21 5.6 -4.4 2.85 0 256 173.14 32103 +2012 22 12 -0.5 8.56 0 499 201.96 32236 +2012 23 9.6 -2.9 6.16 0.08 460 116.34 32372 +2012 24 5.9 -0.2 4.22 0.01 125 95.8 32510 +2012 25 4.2 -2.6 2.33 0 252 237.42 32652 +2012 26 2.5 -3.1 0.96 0 232 238.99 32797 +2012 27 3.1 -9.8 -0.45 0 206 268.94 32944 +2012 28 2.6 -9.2 -0.64 0 174 243.12 33094 +2012 29 -1.1 -3.8 -1.84 0 136 98.73 33247 +2012 30 0.8 -9.7 -2.09 0 171 236.79 33402 +2012 31 -2.1 -13.5 -5.23 0 182 268.76 33559 +2012 32 -2.7 -10.7 -4.9 0 138 165.19 33719 +2012 33 -4.8 -11.7 -6.7 0 154 180.51 33882 +2012 34 -8.3 -13.5 -9.73 0 108 113.64 34046 +2012 35 -7.9 -9.5 -8.34 0 186 71.69 34213 +2012 36 -6.3 -9.9 -7.29 0 159 196.35 34382 +2012 37 -7.7 -11.3 -8.69 0.49 117 91.79 34552 +2012 38 -7.3 -10.3 -8.13 0.23 80 98.33 34725 +2012 39 -3.6 -21.4 -8.5 0 149 255.29 34900 +2012 40 -3.2 -18.5 -7.41 0.1 158 250.6 35076 +2012 41 -6.8 -11.4 -8.06 0 101 194.15 35254 +2012 42 -8.3 -19.4 -11.35 0.22 67 111.04 35434 +2012 43 -6.6 -11.6 -7.97 0 126 139.25 35615 +2012 44 -0.7 -10.4 -3.37 0 224 215.21 35798 +2012 45 2.2 -14.6 -2.42 0 249 270.86 35983 +2012 46 6 -11.1 1.3 0.15 300 153.74 36169 +2012 47 4.9 -4.3 2.37 0 338 266.86 36356 +2012 48 9.7 -8.4 4.72 0 409 162.5 36544 +2012 49 9 0.2 6.58 0 417 137.58 36734 +2012 50 9.8 -5.6 5.57 0.45 408 247.94 36925 +2012 51 6.2 0.1 4.52 0 304 175.96 37117 +2012 52 6.8 -5.2 3.5 0 378 327.89 37310 +2012 53 10 -6.2 5.54 0 420.91 299.79 37505 +2012 54 9.4 -4.9 5.47 0.01 362.73 209.94 37700 +2012 55 20 0.2 14.56 0 894.55 313.92 37896 +2012 56 17.2 0.3 12.55 0.03 876.36 291.53 38093 +2012 57 10.5 -0.6 7.45 0.01 387.27 180.39 38291 +2012 58 7.5 -4.4 4.23 0 466.36 329.71 38490 +2012 59 9.1 -2 6.05 0.04 207.27 110.65 38689 +2012 60 16.5 4.2 13.12 0 584.55 185.81 38890 +2012 61 14 8.7 12.54 0 264.17 129.39 39091 +2012 62 17.7 0.3 12.91 0 440.83 292.45 39292 +2012 63 11.7 1.2 8.81 0 649.17 361.72 39495 +2012 64 9 -5.4 5.04 0 513.33 311.94 39697 +2012 65 10 -1.6 6.81 0 522.5 334.21 39901 +2012 66 7.5 -5 4.06 0 395.83 370.38 40105 +2012 67 6.5 -7.9 2.54 0 393.33 368.17 40309 +2012 68 9.2 -2.8 5.9 0 520 262.12 40514 +2012 69 10.2 -2.3 6.76 0 500 312.1 40719 +2012 70 11.2 -5.5 6.61 0 513.33 393.58 40924 +2012 71 10.6 -3 6.86 0.01 399.17 77.12 41130 +2012 72 10.6 6.5 9.47 0 236.67 54.07 41336 +2012 73 13.7 6.9 11.83 0 461.67 245.03 41543 +2012 74 13.8 -2.6 9.29 0 515 357.18 41749 +2012 75 14.6 -1 10.31 0 597.5 381.33 41956 +2012 76 20.1 -3.1 13.72 0 846.67 398.84 42163 +2012 77 22.9 -1.9 16.08 0 1335.83 395.16 42370 +2012 78 18.2 5.9 14.82 0 850.83 367.56 42578 +2012 79 14.4 4.3 11.62 0.03 519.17 243.53 42785 +2012 80 14.3 5.1 11.77 0 727.5 313.34 42992 +2012 81 19.6 -1.6 13.77 0 872.5 385.07 43200 +2012 82 20.3 -0.7 14.53 0 1005 396.42 43407 +2012 83 22.1 -0.7 15.83 0 1200 369.46 43615 +2012 84 21.8 1.2 16.14 0 1170.83 377.45 43822 +2012 85 22.3 5.2 17.6 0 1200.83 412 44029 +2012 86 17.2 2.8 13.24 0 1016.67 451.58 44236 +2012 87 19.8 -2.5 13.67 0 1143.33 422.46 44443 +2012 88 21.4 7.6 17.61 0 1065.83 397.78 44650 +2012 89 19.9 1.9 14.95 0 1207.5 136.14 44857 +2012 90 15.8 4.7 12.75 0 418.33 176.73 45063 +2012 91 21.7 -0.8 15.51 0 1192.5 395.64 45270 +2012 92 16 2.5 12.29 0 621.54 447.83 45475 +2012 93 18.3 -4.6 12 0 919.23 455.18 45681 +2012 94 21.1 -0.6 15.13 0 1053.85 465.03 45886 +2012 95 23.1 11.3 19.86 0 1065.38 401.02 46091 +2012 96 23.4 5.4 18.45 1.21 1000.71 364.52 46295 +2012 97 16.8 7.3 14.19 0.06 144.29 112.16 46499 +2012 98 10.2 8.3 9.68 0.41 69.29 70.37 46702 +2012 99 8.5 2.4 6.82 0 396.43 367.14 46905 +2012 100 10.2 -2.3 6.76 0 546.43 489.44 47107 +2012 101 15 -3.5 9.91 0 793.57 424.76 47309 +2012 102 16.9 8.8 14.67 1.52 767.14 369.73 47510 +2012 103 15.2 6.5 12.81 0.06 297.86 174.71 47710 +2012 104 17.3 0.2 12.6 0.15 402.86 351.32 47910 +2012 105 12.4 7.6 11.08 0 296.43 111.53 48108 +2012 106 13 7.6 11.52 0 315 186.26 48306 +2012 107 12.9 3.5 10.32 0.03 337.14 137.34 48504 +2012 108 11.7 5.7 10.05 0 527.86 380.99 48700 +2012 109 11.3 3.7 9.21 0.07 504.29 207.07 48895 +2012 110 18.6 1.6 13.93 0 711.43 470.42 49089 +2012 111 19.2 4.1 15.05 0 795 414.75 49282 +2012 112 17.1 3.2 13.28 0.16 432.86 258.85 49475 +2012 113 16.8 6.9 14.08 1.3 367.14 168.44 49666 +2012 114 14.4 4 11.54 0 417.86 299.25 49855 +2012 115 17.2 7.3 14.48 0.16 426.43 247.49 50044 +2012 116 19 4.8 15.1 0 738.57 485.35 50231 +2012 117 23.1 8.6 19.11 0 1307.86 525.66 50417 +2012 118 24.9 3.9 19.13 0 1205 500.85 50601 +2012 119 28.5 6.1 22.34 0 1582.86 510.75 50784 +2012 120 29.3 15.5 25.5 0 2016.43 489.95 50966 +2012 121 29.1 11.6 24.29 0 2012.86 507.12 51145 +2012 122 29.5 9.2 23.92 0 1951.43 496.58 51324 +2012 123 29.7 10.4 24.39 0 1850 471.58 51500 +2012 124 23.4 14.3 20.9 1.42 758.57 279.2 51674 +2012 125 19.8 12.5 17.79 0.72 331.33 231.2 51847 +2012 126 23.1 9.9 19.47 0 1014 511.57 52018 +2012 127 23.1 8.1 18.98 0.09 937.33 496.37 52187 +2012 128 18.2 12.1 16.52 0.04 494.67 186.95 52353 +2012 129 22 6.2 17.66 0 896.67 500.64 52518 +2012 130 24.4 7.6 19.78 0 1156 516.77 52680 +2012 131 26.1 9.1 21.43 0 1477.33 482.73 52840 +2012 132 27.5 8.3 22.22 0 1486 487.54 52998 +2012 133 28.1 10.6 23.29 1.55 1064 375.57 53153 +2012 134 14.2 7.6 12.38 0 621.33 403.37 53306 +2012 135 12.9 7.7 11.47 0 434.67 211.15 53456 +2012 136 18.8 7.7 15.75 0 696 408.43 53603 +2012 137 15.8 6.3 13.19 0 584.67 234.61 53748 +2012 138 16.7 8.8 14.53 0 796 564.66 53889 +2012 139 17.3 -1.3 12.19 0 834.67 549.33 54028 +2012 140 22.4 1.1 16.54 0 1052 541.22 54164 +2012 141 25.3 4.3 19.53 0 1192.67 515.23 54297 +2012 142 22.2 10.2 18.9 0.19 611.25 202.74 54426 +2012 143 18.5 13.6 17.15 3.57 115.63 86.96 54552 +2012 144 26.8 12.6 22.9 0.13 668.75 407.89 54675 +2012 145 26.3 14.3 23 0.18 1141.88 415.58 54795 +2012 146 22.8 10.7 19.47 0 1189.38 428.95 54911 +2012 147 20.8 7.3 17.09 0 1088.13 376.42 55023 +2012 148 22.8 5.6 18.07 0 1171.88 509.18 55132 +2012 149 23.2 5.3 18.28 0.03 776.25 289.59 55237 +2012 150 24.1 10 20.22 0.01 1100.63 440.36 55339 +2012 151 27.1 12.2 23 0.52 969.38 407.07 55436 +2012 152 22.2 11.2 19.18 0.55 531.25 309 55530 +2012 153 25.2 13.5 21.98 0 772.5 361.82 55619 +2012 154 21.4 13.5 19.23 0 456.25 214.12 55705 +2012 155 28.2 12.2 23.8 0 1072.5 485.33 55786 +2012 156 23.1 14 20.6 0.66 623.13 327.85 55863 +2012 157 22.4 12.5 19.68 0 841.87 453.99 55936 +2012 158 22.1 3.8 17.07 0 749.38 436.72 56004 +2012 159 26.9 9.8 22.2 0 1097.5 446.08 56068 +2012 160 30.7 14.5 26.25 0 1501.87 445.99 56128 +2012 161 26.3 15.4 23.3 1.22 398.75 171.51 56183 +2012 162 24.7 14.4 21.87 0.46 463.13 271.23 56234 +2012 163 22.6 13.3 20.04 0.48 212.5 207.46 56280 +2012 164 19.2 13.7 17.69 0.11 138.75 155.83 56321 +2012 165 21.9 10.7 18.82 0.17 520 262.26 56358 +2012 166 24.3 9.8 20.31 0.02 879.38 397.68 56390 +2012 167 26.9 11.2 22.58 0 968.75 481.92 56418 +2012 168 29.5 12.1 24.72 0 1520 556.72 56440 +2012 169 31.7 13.1 26.59 0 1758.75 523.77 56458 +2012 170 32.2 13.4 27.03 0 1793.13 540.45 56472 +2012 171 32.5 14.2 27.47 0 1897.5 490.9 56480 +2012 172 32.9 15.8 28.2 0 1776.87 483.4 56484 +2012 173 32.9 17.5 28.66 0 1575 488.47 56482 +2012 174 27.9 17.8 25.12 0 1412.5 320.75 56476 +2012 175 27 14.3 23.51 0 1535.63 444.6 56466 +2012 176 29.9 11.8 24.92 0.28 1591.88 496.62 56450 +2012 177 26.6 16.3 23.77 0.99 428.75 108.77 56430 +2012 178 26.2 12.2 22.35 0 1095.63 458.3 56405 +2012 179 27.7 10.3 22.91 0 1310.63 481.29 56375 +2012 180 31.8 12.2 26.41 0 1664.38 414.84 56341 +2012 181 33.5 15.1 28.44 0 1753.13 449.8 56301 +2012 182 35.7 16.9 30.53 0 2033.75 501.34 56258 +2012 183 35.3 19.3 30.9 0 2240 483.09 56209 +2012 184 35.4 20.8 31.39 0 2162.5 493.8 56156 +2012 185 35.5 17.1 30.44 0.04 2374.38 461.62 56099 +2012 186 33.7 19.2 29.71 0 1738.12 483.47 56037 +2012 187 35.5 17.3 30.49 0 1950.63 419.58 55971 +2012 188 35.4 15.9 30.04 0 2046.25 436.23 55900 +2012 189 34.5 14.3 28.95 0 2060.63 489.73 55825 +2012 190 34.1 18.4 29.78 0 2156.25 513.46 55746 +2012 191 31.6 18 27.86 0.62 1789.38 457.42 55663 +2012 192 30.9 16.6 26.97 0.02 1315 468.42 55575 +2012 193 31.8 15.8 27.4 1.15 1198.13 468.23 55484 +2012 194 23.3 17.4 21.68 0 905.63 309.73 55388 +2012 195 20.6 15.4 19.17 0.03 357.5 173.45 55289 +2012 196 30.2 12.5 25.33 2.19 878.13 394.49 55186 +2012 197 20.6 13.9 18.76 0.14 298.13 173.32 55079 +2012 198 24.2 11.1 20.6 0.01 903.13 315.86 54968 +2012 199 26 7.4 20.88 0 1170 302.12 54854 +2012 200 27.4 10 22.61 0 1328.13 309.35 54736 +2012 201 32.1 14.2 27.18 0.65 1766.25 367.93 54615 +2012 202 26.6 16.2 23.74 0 1024.38 446.94 54490 +2012 203 22.8 15.5 20.79 0.57 185 115.34 54362 +2012 204 19.5 11.3 17.25 0 584.38 255.27 54231 +2012 205 24.3 14.4 21.58 0 1070 414.63 54097 +2012 206 27.7 12 23.38 2.15 748.75 309.52 53960 +2012 207 25.7 17.5 23.45 0.08 391.88 239.34 53819 +2012 208 29.2 16.2 25.63 0.42 731.25 353.41 53676 +2012 209 30.4 15.4 26.27 0 1200.67 473.37 53530 +2012 210 32 16.3 27.68 0 1580 500.59 53382 +2012 211 30.5 17.3 26.87 1.42 797.14 384.94 53230 +2012 212 25.5 13.9 22.31 0.02 1102.14 448.25 53076 +2012 213 27.1 15.4 23.88 0 1115 379.65 52920 +2012 214 29.3 13.5 24.95 0 1684.29 543.52 52761 +2012 215 31.2 13 26.2 0 1782.14 506.98 52600 +2012 216 29.2 15.4 25.41 1.91 965.71 394.88 52437 +2012 217 30.5 17.3 26.87 0 1222.14 483.69 52271 +2012 218 33.6 17.7 29.23 0 1702.86 484.93 52103 +2012 219 34.2 16.2 29.25 0 2585 467.95 51934 +2012 220 30.1 17.8 26.72 0 1399.29 354.81 51762 +2012 221 25.8 14.9 22.8 0 1004.29 312.55 51588 +2012 222 25.8 13.3 22.36 0.1 900.71 264.52 51413 +2012 223 25.4 11.4 21.55 0.08 980.71 381.71 51235 +2012 224 21.1 13.2 18.93 0.24 563.57 206.84 51057 +2012 225 23.2 6.8 18.69 0 963.57 394.26 50876 +2012 226 24.7 9.8 20.6 0 1070.71 342.83 50694 +2012 227 26.2 11.2 22.07 0 1378.57 447.53 50510 +2012 228 30 11.2 24.83 0 1665 431.11 50325 +2012 229 29.6 11.7 24.68 0 1725.71 422.19 50138 +2012 230 30.7 16.5 26.8 0 1430.71 449.13 49951 +2012 231 29.4 14.1 25.19 0 1616.43 447.88 49761 +2012 232 32.2 13 26.92 0 2080.71 443.73 49571 +2012 233 35 11.5 28.54 0 2562.14 492.84 49380 +2012 234 34 12.2 28.01 0 1847.86 385.24 49187 +2012 235 36 15.3 30.31 0.04 2380.71 393.59 48993 +2012 236 33.5 19 29.51 0.01 1780 353.99 48798 +2012 237 36.2 16.1 30.67 0 2552.14 436.46 48603 +2012 238 33 16.8 28.54 0 2142.86 435.27 48406 +2012 239 27.5 14.7 23.98 0.54 889.23 260.96 48208 +2012 240 25.1 10.6 21.11 0 1225.55 359.94 48010 +2012 241 28.6 7.3 22.74 0 1742.61 436.44 47811 +2012 242 29 11.6 24.22 0 1656.25 385.72 47611 +2012 243 31.3 11 25.72 0 1992.63 409.95 47410 +2012 244 25 13.4 21.81 0.38 1075.73 215.65 47209 +2012 245 17.8 13.5 16.62 0.62 343.62 91.75 47007 +2012 246 26 14.5 22.84 0 1130.47 286 46805 +2012 247 27.9 13.1 23.83 0 1445.69 341.78 46601 +2012 248 26.1 15.5 23.19 0 1079.81 263.87 46398 +2012 249 28.4 12.6 24.06 0 1534.41 354.94 46194 +2012 250 23.1 15.8 21.09 0 904.62 355.86 45989 +2012 251 25.2 6.1 19.95 0 1090.77 426.42 45784 +2012 252 29.2 8.8 23.59 0 1680 437.57 45579 +2012 253 29.6 8.7 23.85 0 1640.77 427.25 45373 +2012 254 30.1 9.2 24.35 0 1851.54 413.92 45167 +2012 255 31.1 9.6 25.19 0 1854.62 401.62 44961 +2012 256 28.1 11.2 23.45 3.48 1378.33 289.21 44755 +2012 257 16.9 8.5 14.59 0.43 188.33 84.77 44548 +2012 258 15.8 10.8 14.43 0 610.83 138.17 44341 +2012 259 21.6 10.9 18.66 0 837.5 219.45 44134 +2012 260 20.5 7.7 16.98 0 810 314.8 43927 +2012 261 24 5.4 18.88 0 767.5 410.85 43719 +2012 262 24.7 7.7 20.02 0 843.33 410.39 43512 +2012 263 21.9 9.2 18.41 0.46 496.67 221.2 43304 +2012 264 17.7 9.3 15.39 0 838.33 363.11 43097 +2012 265 19.3 1 14.27 0 815 398.98 42890 +2012 266 23.4 6.8 18.84 0 910.83 357.29 42682 +2012 267 21.4 10.7 18.46 0 800 356.06 42475 +2012 268 25.1 8.4 20.51 2.17 1040.83 344.73 42268 +2012 269 23.9 11.5 20.49 0 875.83 398.57 42060 +2012 270 25.2 16.7 22.86 0 1120 307.04 41854 +2012 271 24.5 13.7 21.53 0 895.83 184.45 41647 +2012 272 21.3 7.7 17.56 0.01 765.83 347.44 41440 +2012 273 20.9 10.8 18.12 0.01 422.5 190.77 41234 +2012 274 20.4 13.4 18.47 0.03 688.33 240.16 41028 +2012 275 24 12 20.7 0.57 558.18 287.82 40822 +2012 276 16.8 12.5 15.62 0.06 216.36 73.87 40617 +2012 277 22.1 9.6 18.66 0 368.18 292.31 40412 +2012 278 22.8 5.6 18.07 0 579.09 325.12 40208 +2012 279 20.1 7.3 16.58 0 647.27 294.31 40003 +2012 280 22.7 5.7 18.02 0 634.55 333.1 39800 +2012 281 23 10.5 19.56 0.12 458.18 252.17 39597 +2012 282 15.8 2.2 12.06 0 555.45 321.67 39394 +2012 283 17.6 3 13.59 0.02 553.64 264.16 39192 +2012 284 10.7 8 9.96 0.19 280.91 54.86 38991 +2012 285 14.7 4.6 11.92 0 282.73 217.62 38790 +2012 286 12.7 7.9 11.38 0.09 200.91 74.18 38590 +2012 287 12.9 9.4 11.94 0.52 217.27 107.18 38391 +2012 288 13 7.4 11.46 0 164.55 147.69 38193 +2012 289 20.4 11.3 17.9 1.19 475.45 275.56 37995 +2012 290 14.3 7.1 12.32 1.37 60.91 58 37799 +2012 291 17.5 3.2 13.57 0 175.45 238.74 37603 +2012 292 20.8 3.2 15.96 0 530.91 290.76 37408 +2012 293 21.7 4.8 17.05 0 532.73 317.93 37214 +2012 294 17 4.7 13.62 0.03 193.64 231.93 37022 +2012 295 18.4 5.4 14.82 0.05 168.18 223.71 36830 +2012 296 19.1 5.8 15.44 0.05 333.64 279.1 36640 +2012 297 10.9 4.7 9.2 0.03 19.09 95.36 36451 +2012 298 10.2 8.9 9.84 0.04 72.73 38.39 36263 +2012 299 9.3 8.2 9 0 104.55 40.46 36076 +2012 300 10.5 7.4 9.65 1.8 88 58.65 35891 +2012 301 16.7 7.3 14.12 2.89 101 129.85 35707 +2012 302 7.3 0.6 5.46 1.07 227 76 35525 +2012 303 4.5 0.2 3.32 0 116 176.39 35345 +2012 304 8.2 -3.6 4.96 0 239 290.72 35166 +2012 305 13.2 -4.4 8.36 0.79 319 300.6 34988 +2012 306 7.8 3.3 6.56 0.22 20 29.77 34813 +2012 307 10.5 1.3 7.97 0.05 165 130.41 34639 +2012 308 16.8 0.2 12.23 0 381 237.64 34468 +2012 309 19 10.9 16.77 0.05 618.89 194.88 34298 +2012 310 16.5 7.1 13.92 4.16 58.89 44.2 34130 +2012 311 9.9 0.9 7.43 0 221.11 139.71 33964 +2012 312 12.6 -1.4 8.75 0 385.56 198.12 33801 +2012 313 13.8 0.6 10.17 0 494.44 254.81 33640 +2012 314 11.9 0.8 8.85 0 275.56 213.67 33481 +2012 315 12.5 -1.2 8.73 0 302.22 132.48 33325 +2012 316 14.3 3 11.19 0.27 245.56 139.57 33171 +2012 317 10.3 6.9 9.37 1 58.89 31.17 33019 +2012 318 12.4 7.8 11.14 0 218.89 89.64 32871 +2012 319 9.5 1 7.16 0 248.89 133.77 32725 +2012 320 10 -0.5 7.11 0 194.44 193.3 32582 +2012 321 8.3 5.4 7.5 0 167.78 61.91 32441 +2012 322 9.3 3.5 7.71 0 170 103.17 32304 +2012 323 8.1 1.7 6.34 0.03 20 45.89 32170 +2012 324 7.9 6.6 7.54 0.04 15.56 35.03 32039 +2012 325 9 6.1 8.2 0.02 16.67 138.25 31911 +2012 326 8.5 6.1 7.84 0.01 36.67 38.4 31786 +2012 327 7.8 6.8 7.52 0.04 46.67 38.61 31665 +2012 328 8.4 6.3 7.82 0.01 48.89 44.05 31547 +2012 329 10.5 7.3 9.62 0 111.11 87.83 31433 +2012 330 9.4 3.9 7.89 0 87.78 38.61 31322 +2012 331 10.1 3 8.15 0 65.56 81.74 31215 +2012 332 14.4 3.9 11.51 0 566.67 99.03 31112 +2012 333 17 10.4 15.18 0.62 572.22 144.53 31012 +2012 334 12.8 7.5 11.34 0.35 275.56 120.14 30917 +2012 335 7.5 3.2 6.32 0 265.56 68.04 30825 +2012 336 4.3 -0.2 3.06 0 195.56 90.03 30738 +2012 337 2.5 0.5 1.95 0.27 50 41.12 30654 +2012 338 5.8 -1.1 3.9 0 236.67 168.11 30575 +2012 339 3.6 -2.4 1.95 0.15 143.33 56.47 30500 +2012 340 5.3 -0.8 3.62 0 95.56 95.72 30430 +2012 341 1.3 -3.1 0.09 0 14.44 59.37 30363 +2012 342 1.7 -6 -0.42 0.55 145.56 139.76 30301 +2012 343 -1 -4.6 -1.99 0.11 76.67 52.38 30244 +2012 344 3 -10 -0.57 0 271.11 200.32 30191 +2012 345 1.9 -9 -1.1 0 205.56 167.93 30143 +2012 346 2.7 -8.9 -0.49 0 140 124.85 30099 +2012 347 1.5 -10.5 -1.8 0 241.25 194.55 30060 +2012 348 -0.6 -14.7 -4.48 0 152.5 198.89 30025 +2012 349 5 -11.6 0.44 0.01 202.5 67.58 29995 +2012 350 11 3.1 8.83 0.39 228.75 39.19 29970 +2012 351 7.4 2 5.92 0 10 85.41 29950 +2012 352 4 2.9 3.7 0 10 28.95 29934 +2012 353 3 1.3 2.53 0.15 11.25 38.55 29924 +2012 354 5.8 0.3 4.29 0.02 87.5 67.1 29918 +2012 355 4.4 -0.6 3.03 0 98.75 74.43 29916 +2012 356 0.9 -0.6 0.49 0.04 17.5 29 29920 +2012 357 1.8 -0.5 1.17 0 33.75 46.93 29928 +2012 358 1.7 -0.5 1.1 0.02 51.25 41.31 29941 +2012 359 10.8 0.1 7.86 0 215 171.64 29959 +2012 360 11.7 -1.8 7.99 0 372.5 82.55 29982 +2012 361 11.9 2.6 9.34 0.83 82.5 32.34 30009 +2012 362 9.8 -1 6.83 0.13 217.5 161.03 30042 +2012 363 7.2 1.7 5.69 0 152.5 50.92 30078 +2012 364 5.3 -4.3 2.66 0 152.5 170.07 30120 +2012 365 3 -5.3 0.72 0 142.5 185 30166 +2013 1 6.59 -4.73 3.48 0 63.75 172.69 30217 +2013 2 2.37 -3.11 0.86 0 12.5 41.3 30272 +2013 3 -0.28 -3.23 -1.09 0 200 124.23 30331 +2013 4 6.92 -1.95 4.48 0.01 333.75 116.26 30396 +2013 5 10.31 0.57 7.63 0.4 378.75 69.14 30464 +2013 6 10.97 3.94 9.04 0.08 77.5 33.14 30537 +2013 7 7.16 2.71 5.94 0.88 28.75 57.31 30614 +2013 8 5.72 -0.85 3.91 0.3 28.75 42.76 30695 +2013 9 0.12 -1.99 -0.46 0.28 36.25 53.03 30781 +2013 10 4.67 -0.21 3.33 0.03 31.25 59.58 30870 +2013 11 3.82 1.43 3.16 0 57.5 63.57 30964 +2013 12 3.4 -1.03 2.18 0 213.33 128.34 31061 +2013 13 1.6 -5.33 -0.31 0 37.78 62.33 31162 +2013 14 -0.96 -2.99 -1.52 1.78 20 51.45 31268 +2013 15 -1.52 -3.41 -2.04 1.07 32.22 92.46 31376 +2013 16 0.33 -2.58 -0.47 0.04 86.67 112.82 31489 +2013 17 0.22 -1.89 -0.36 1.23 47.78 80.72 31605 +2013 18 -0.28 -1.62 -0.65 0.24 37.78 66.94 31724 +2013 19 -1.14 -3.88 -1.89 0.35 98.89 71.99 31847 +2013 20 -1.91 -4.58 -2.64 0 83 125.07 31974 +2013 21 3.43 -4.71 1.19 0.05 15 70.98 32103 +2013 22 4.41 -0.91 2.95 0.87 34 73.66 32236 +2013 23 0.85 -0.98 0.35 0.35 10 64.51 32372 +2013 24 0.34 -1.75 -0.23 0 10 34.98 32510 +2013 25 -0.35 -1.94 -0.79 0.07 119 177.03 32652 +2013 26 -0.73 -5.21 -1.96 0 106 181.89 32797 +2013 27 -3.16 -9.83 -4.99 0 100 171.05 32944 +2013 28 -1.52 -13.28 -4.75 0 46 85.69 33094 +2013 29 -0.33 -3.59 -1.23 0.3 64 95.75 33247 +2013 30 2.47 -5.47 0.29 0.14 313 204.34 33402 +2013 31 8.44 0.3 6.2 0 880 258.66 33559 +2013 32 8.44 0.05 6.13 0 491 133.99 33719 +2013 33 6.77 2.7 5.65 1.88 74 20.72 33882 +2013 34 5.15 0.4 3.84 0 429 179.25 34046 +2013 35 4.49 -2.68 2.52 0 317 93.96 34213 +2013 36 6.42 0.05 4.67 0.26 270 65.81 34382 +2013 37 3.78 -0.68 2.55 0.23 21 64.71 34552 +2013 38 5.15 -1.39 3.35 0 284 278.58 34725 +2013 39 3.29 -3.69 1.37 0 238 248.28 34900 +2013 40 0.43 -2.35 -0.33 0.17 209 138.66 35076 +2013 41 -0.73 -3.34 -1.45 0.21 66 117.41 35254 +2013 42 1.23 -8.44 -1.43 0.48 188 221.38 35434 +2013 43 -0.03 -3.22 -0.91 0.61 27 100.01 35615 +2013 44 -0.31 -1.78 -0.71 0.58 52 83.19 35798 +2013 45 0.62 -1.44 0.05 0.43 82 106.86 35983 +2013 46 3.38 -1.18 2.13 0 108 166.44 36169 +2013 47 4.82 -1.09 3.19 0 214 258.11 36356 +2013 48 4.19 -0.74 2.83 0 153 157.98 36544 +2013 49 4.43 -0.78 3 0 185 205.28 36734 +2013 50 5.23 -1.68 3.33 0 257 237.83 36925 +2013 51 3.78 -1.36 2.37 0.01 276 168.58 37117 +2013 52 0.97 -5.01 -0.67 0.26 203 282.07 37310 +2013 53 -1.54 -5.46 -2.62 1.46 77 160.78 37505 +2013 54 1.6 -3.94 0.08 1.31 50.91 149.42 37700 +2013 55 2.88 -0.94 1.83 0.27 10 90.93 37896 +2013 56 4.16 0.74 3.22 2.29 30.91 168.99 38093 +2013 57 3.73 1.09 3 0.51 22.73 47.84 38291 +2013 58 4.78 1.24 3.81 0.05 149.09 62.78 38490 +2013 59 -0.84 -3.05 -1.45 0.1 223.64 233.39 38689 +2013 60 8.75 2.15 6.94 0 45.45 83.3 38890 +2013 61 4.76 -1.11 3.15 0 373.64 371.38 39091 +2013 62 6.74 -0.27 4.81 0 430 389.12 39292 +2013 63 9.9 -3.68 6.17 0 385.83 379.38 39495 +2013 64 8.21 -1.35 5.58 0 480.83 364.56 39697 +2013 65 10.87 -2.07 7.31 0 480.83 213.26 39901 +2013 66 13.64 4.29 11.07 0 495.83 310.07 40105 +2013 67 16.83 7.96 14.39 0 569.17 294.94 40309 +2013 68 18.13 6.44 14.92 0 292.5 242.51 40514 +2013 69 14.15 5.3 11.72 0.67 53.33 81.72 40719 +2013 70 10.64 7.65 9.82 0.55 290 303.47 40924 +2013 71 13.9 1.03 10.36 0.01 188.33 151.16 41130 +2013 72 8.66 2.09 6.85 0.01 274.17 192.22 41336 +2013 73 9.59 2.92 7.76 0.21 130.83 85.29 41543 +2013 74 7.06 -2.73 4.37 0.07 353.33 235.4 41749 +2013 75 1.1 -2.86 0.01 0 336.67 313.14 41956 +2013 76 2.89 -4.14 0.96 0 360.83 310 42163 +2013 77 4.62 -5.16 1.93 0 130.83 74.61 42370 +2013 78 3.62 0.21 2.68 1.05 484.17 258.32 42578 +2013 79 12.75 1.61 9.69 0 560.42 291.29 42785 +2013 80 14.01 -1.29 9.8 0.03 509.17 215.76 42992 +2013 81 10.33 4.87 8.83 0 391.67 457.61 43200 +2013 82 7.33 -1.28 4.96 0 200.83 207.28 43407 +2013 83 1.99 -2.62 0.72 0.04 68.33 124.35 43615 +2013 84 0.43 -4.02 -0.79 0.41 61.67 106.98 43822 +2013 85 -2.26 -4.19 -2.79 0.89 72.5 136.87 44029 +2013 86 -2.34 -4.32 -2.88 0.4 222.5 396.18 44236 +2013 87 2.66 -5.03 0.55 0 264.17 457.91 44443 +2013 88 5.82 -6.6 2.4 0.13 27.5 58.42 44650 +2013 89 3.44 1.39 2.88 0.82 60.83 107.53 44857 +2013 90 5.23 1.43 4.19 3.21 57.5 70.49 45063 +2013 91 4.34 0.3 3.23 0.94 181.67 168.67 45270 +2013 92 4.22 -0.49 2.92 0.06 14.17 59.33 45475 +2013 93 2.86 0.3 2.16 2.25 86.92 113.44 45681 +2013 94 2.08 -0.25 1.44 0.3 283.08 323.02 45886 +2013 95 9 0.33 6.62 0 85.38 114.58 46091 +2013 96 6.55 2.08 5.32 0.12 247.69 217.35 46295 +2013 97 7.47 3.01 6.24 0 217.86 244.22 46499 +2013 98 7.21 2.23 5.84 0 425.71 466.02 46702 +2013 99 10.32 -0.97 7.22 0 481.43 390.59 46905 +2013 100 14.49 1.84 11.01 0 479.29 277.02 47107 +2013 101 15.36 5.56 12.66 0.11 625.71 390.84 47309 +2013 102 17.73 2.42 13.52 0 611.43 341.18 47510 +2013 103 18.9 8.89 16.15 0.55 742.14 360.73 47710 +2013 104 17.72 5.49 14.36 0 886.43 476.88 47910 +2013 105 18.95 5.19 15.17 0 970 492.22 48108 +2013 106 18.43 5.56 14.89 0 1100 518.62 48306 +2013 107 19.41 4.08 15.19 0 931.43 313.59 48504 +2013 108 22.02 5.5 17.48 0 1241.43 444.88 48700 +2013 109 24.16 7.88 19.68 0 921.43 405.65 48895 +2013 110 22.7 9.63 19.11 0 437.14 309.51 49089 +2013 111 17.83 9.46 15.53 0 740.71 447.18 49282 +2013 112 20.86 7.04 17.06 0.01 721.43 333.79 49475 +2013 113 21.39 9.27 18.06 0.71 663.57 350.89 49666 +2013 114 20.81 8.41 17.4 0 1303.57 513.77 49855 +2013 115 23.45 6.54 18.8 0 1363.57 485.21 50044 +2013 116 25.44 7.19 20.42 0 1633.57 486.35 50231 +2013 117 26.89 9.31 22.06 0 1006.43 308.7 50417 +2013 118 23.14 14.46 20.75 0 1101.43 487.96 50601 +2013 119 24.53 12.94 21.34 0 1193.57 403.46 50784 +2013 120 25.26 11.12 21.37 0 1267.86 431.24 50966 +2013 121 26.99 11.39 22.7 0 1045 457.2 51145 +2013 122 26.2 12.49 22.43 0.05 349.29 211.94 51324 +2013 123 21.38 14.84 19.58 0.73 480.71 356.03 51500 +2013 124 22.62 12.76 19.91 0.04 567.86 318.97 51674 +2013 125 21.37 9.6 18.13 0.01 368.57 170.15 51847 +2013 126 18.16 12.29 16.55 0.74 282 208.36 52018 +2013 127 20.64 12.93 18.52 0.03 595.33 374.15 52187 +2013 128 22.66 14.12 20.31 0 690.67 414.18 52353 +2013 129 22.64 11.68 19.63 0.02 970 404.19 52518 +2013 130 24.47 10.82 20.72 0.01 1070.67 469.6 52680 +2013 131 24.64 8.99 20.34 0.49 240.67 131.74 52840 +2013 132 18.14 11.99 16.45 0.4 698.67 400.24 52998 +2013 133 18.38 10.73 16.28 0 934.67 474.95 53153 +2013 134 17.97 8.49 15.36 0.03 636.11 264.87 53306 +2013 135 20.5 7.38 16.89 0 1096 556.58 53456 +2013 136 23.16 6.99 18.71 0 862.67 383.97 53603 +2013 137 23.82 11.04 20.31 0.02 276.67 228.83 53748 +2013 138 20.77 11.12 18.12 1.14 996.67 553.51 53889 +2013 139 22.11 10.48 18.91 0 1209.33 488.86 54028 +2013 140 25.91 10.09 21.56 0.32 708.67 423.06 54164 +2013 141 20.81 10.1 17.86 0.2 969.33 484.49 54297 +2013 142 21.24 8.75 17.81 0 652.67 432.61 54426 +2013 143 19.33 7.09 15.96 0.49 601.88 356.93 54552 +2013 144 15.98 8.7 13.98 0 721.88 393.92 54675 +2013 145 15.8 7.32 13.47 0 280 215.62 54795 +2013 146 14.26 8.05 12.55 0.62 561.25 355.26 54911 +2013 147 16.57 7.78 14.15 0.25 290 197.47 55023 +2013 148 15.37 7.28 13.15 0.11 592.5 397.34 55132 +2013 149 20.45 7.97 17.02 0 923.75 397.61 55237 +2013 150 23.22 9.83 19.54 0.01 143.75 68.96 55339 +2013 151 18.41 9.36 15.92 1.6 210.62 176.9 55436 +2013 152 13.08 8.04 11.69 0.3 196.87 217.67 55530 +2013 153 16.53 8.1 14.21 0.87 155.63 189.13 55619 +2013 154 15.87 8.61 13.87 0.44 508.75 253.96 55705 +2013 155 17.87 8.57 15.31 0.03 298.13 106.68 55786 +2013 156 16.56 9.8 14.7 0.27 303.75 203.37 55863 +2013 157 18.18 12.15 16.52 0.05 523.75 372.95 55936 +2013 158 20.88 10.33 17.98 0 643.75 466.46 56004 +2013 159 23.07 11.95 20.01 0 880.63 456.02 56068 +2013 160 25.88 12.58 22.22 0.17 1120 474.35 56128 +2013 161 26.99 12.25 22.94 0 886.88 409.69 56183 +2013 162 24.48 14.7 21.79 0.47 248.75 183.45 56234 +2013 163 18.78 13.21 17.25 0.58 1026.88 450.34 56280 +2013 164 22.6 10.08 19.16 0 1295 426.5 56321 +2013 165 25.28 11.3 21.44 0 1157.5 516.04 56358 +2013 166 25.52 11.51 21.67 0 1298.75 473.3 56390 +2013 167 27.99 12.76 23.8 0 1220 370.22 56418 +2013 168 28.82 16.35 25.39 0 1546.25 488.57 56440 +2013 169 31.4 17.02 27.45 0 1706.25 486.18 56458 +2013 170 32.39 17.8 28.38 0 1653.75 481.24 56472 +2013 171 33.08 18.48 29.07 0 1667.5 469.96 56480 +2013 172 33.35 19.65 29.58 0 2202.5 512.53 56484 +2013 173 32.09 19.77 28.7 0 1278.75 465.01 56482 +2013 174 29.83 17.09 26.33 0.35 1165.63 450.76 56476 +2013 175 27.73 16.75 24.71 0.12 201.25 67.52 56466 +2013 176 22.27 11.96 19.43 1.98 516.88 182.02 56450 +2013 177 18.08 12.05 16.42 0 703.75 323.38 56430 +2013 178 19.33 8.44 16.34 0 898.75 535.53 56405 +2013 179 18.91 6.25 15.43 0 843.13 404.95 56375 +2013 180 20.38 6.66 16.61 0 984.37 425.68 56341 +2013 181 22.33 9.12 18.7 0 958.13 471.17 56301 +2013 182 22.24 10.18 18.92 0.01 1183.75 504.25 56258 +2013 183 23.98 7.91 19.56 0 1185 497.05 56209 +2013 184 26.88 10.58 22.4 0 1541.25 464.8 56156 +2013 185 27.95 12.08 23.59 0 1308.13 496.71 56099 +2013 186 28.3 13.98 24.36 0 1379.38 492.35 56037 +2013 187 28.13 15.91 24.77 0.11 941.88 468.11 55971 +2013 188 26.89 17.76 24.38 0.18 1103.75 472 55900 +2013 189 27.65 17.19 24.77 0.01 1376.87 499.54 55825 +2013 190 27.06 16.93 24.27 0 1496.25 488.63 55746 +2013 191 28.29 15.55 24.79 0 1655 463.36 55663 +2013 192 28.96 14.59 25.01 0.02 572.5 212.82 55575 +2013 193 24.64 15.57 22.15 0.24 1206.88 448.15 55484 +2013 194 24.57 10.24 20.63 0 1177.5 351.58 55388 +2013 195 25.33 11.57 21.55 0 1480.63 457.6 55289 +2013 196 26.31 12.86 22.61 0 1001.25 380.92 55186 +2013 197 26.3 13.67 22.83 0.57 1266.88 461.33 55079 +2013 198 25.74 12.03 21.97 0 1660 511 54968 +2013 199 28.33 11.28 23.64 0 1818.13 448.59 54854 +2013 200 29.57 12.8 24.96 0 1730.63 412.32 54736 +2013 201 30.31 14.24 25.89 0 1665 464.4 54615 +2013 202 29.41 16.21 25.78 0 1601.25 509.58 54490 +2013 203 27.25 14.72 23.8 0 1885 509.65 54362 +2013 204 29.87 11.7 24.87 0 2279.38 498.04 54231 +2013 205 32.02 13.8 27.01 0 1893.75 441.45 54097 +2013 206 32.02 15.44 27.46 0 1449.37 352.91 53960 +2013 207 29.83 17.02 26.31 0 1946.25 408.55 53819 +2013 208 32.97 16.28 28.38 0 2231.88 459.52 53676 +2013 209 34.4 18.16 29.93 0 2060 466.42 53530 +2013 210 35.43 19.18 30.96 0 3151.33 480.67 53382 +2013 211 37.4 20.94 32.87 0 1683.57 361.49 53230 +2013 212 28.59 18.56 25.83 0 1755 384.44 53076 +2013 213 29.53 13.39 25.09 0 1921.43 507.29 52920 +2013 214 30.6 14.77 26.25 0 2355 508.06 52761 +2013 215 33.99 14.4 28.6 0 2690 489.46 52600 +2013 216 35.96 16.72 30.67 0 2891.43 466 52437 +2013 217 35.94 18.3 31.09 0.04 1829.29 500.23 52271 +2013 218 33.01 17.39 28.71 0 2780 472.57 52103 +2013 219 36.02 18.11 31.09 0 2815 469.56 51934 +2013 220 36.02 19.99 31.61 0 3570 467.6 51762 +2013 221 38.78 18.74 33.27 0 2026.43 445.09 51588 +2013 222 34.07 19.91 30.18 1.19 1055 258.16 51413 +2013 223 25.8 16.71 23.3 0 1623.57 481.69 51235 +2013 224 28.33 12.32 23.93 0 1756.43 390.84 51057 +2013 225 29.57 16.23 25.9 0 1336.43 422.28 50876 +2013 226 28.86 14.43 24.89 0.33 304.29 89.99 50694 +2013 227 18.85 15.56 17.95 0.1 1404.29 510.44 50510 +2013 228 24.66 12.07 21.2 0 1632.14 482.65 50325 +2013 229 26.71 8.83 21.79 0 1859.29 483.31 50138 +2013 230 29.07 10.24 23.89 0 2010 471.28 49951 +2013 231 31.22 12.36 26.03 0 2069.29 427.01 49761 +2013 232 31.95 14.47 27.14 0.01 1014.29 291.26 49571 +2013 233 24.31 17.31 22.38 0.09 1122.86 372.7 49380 +2013 234 23.9 16.03 21.74 0 1352.14 424.47 49187 +2013 235 25.2 13.35 21.94 0 1265 356.65 48993 +2013 236 26.71 11.96 22.65 0.54 212.14 124.83 48798 +2013 237 21.25 15.18 19.58 0.67 138.57 119.06 48603 +2013 238 18.47 11.85 16.65 0.26 328.57 178.56 48406 +2013 239 20.8 14.03 18.94 0.21 397.14 209.94 48208 +2013 240 22.8 14.66 20.56 1.1 335.71 229.25 48010 +2013 241 20.7 15.15 19.17 0.01 1169.29 477.02 47811 +2013 242 23.65 13.62 20.89 0 1246.43 452.51 47611 +2013 243 24.13 10.02 20.25 0 1360.71 395.76 47410 +2013 244 26.04 9.43 21.47 0 590 219.45 47209 +2013 245 23.82 12.26 20.64 0.15 749.29 365.04 47007 +2013 246 20.85 9.91 17.84 0 1174.62 245.75 46805 +2013 247 23.8 14.35 21.2 0 763.08 298.94 46601 +2013 248 24.25 13.32 21.24 0 899.23 269.71 46398 +2013 249 24.96 14.11 21.98 0 1157.69 397.66 46194 +2013 250 25.42 13.89 22.25 0 1320.77 419.42 45989 +2013 251 25.75 11.15 21.73 0 1581.54 408.25 45784 +2013 252 26.29 10.18 21.86 0.01 274.62 107.52 45579 +2013 253 19.4 13.28 17.72 0.85 470 272.55 45373 +2013 254 21.54 13.73 19.39 2.7 497.69 267.17 45167 +2013 255 17.82 10.71 15.86 0.07 637.69 345.66 44961 +2013 256 18.94 10.44 16.6 0.49 437.69 335.4 44755 +2013 257 17.46 7.98 14.85 0.06 812.5 160.35 44548 +2013 258 20.41 10.14 17.59 0.02 627.5 286.93 44341 +2013 259 22.29 9.05 18.65 0 695.83 339.77 44134 +2013 260 23.12 10.48 19.64 1.35 155 105.67 43927 +2013 261 16.97 8.54 14.65 0.8 334.17 162.99 43719 +2013 262 16.04 4.96 12.99 0.15 640 302.45 43512 +2013 263 17.73 10.42 15.72 0 686.67 322.44 43304 +2013 264 19.81 6.47 16.14 0.01 768.33 254.33 43097 +2013 265 19.33 10.41 16.88 0 716.67 378.93 42890 +2013 266 18.81 9.15 16.15 0 859.17 383.94 42682 +2013 267 22.29 7.38 18.19 0 783.33 410.78 42475 +2013 268 21.77 7.92 17.96 0 566.67 381.1 42268 +2013 269 21.07 7.77 17.41 0 581.67 221.6 42060 +2013 270 22.59 10.88 19.37 0.18 221.67 71.12 41854 +2013 271 16.31 9.54 14.45 0.06 397.5 146.97 41647 +2013 272 14.17 7.58 12.36 0.01 80.83 41.93 41440 +2013 273 11.87 8.31 10.89 2.65 46.67 50.1 41234 +2013 274 9.21 7.36 8.7 0.89 465.83 326.5 41028 +2013 275 15.44 7.43 13.24 0 411.67 262.31 40822 +2013 276 12.16 4.93 10.17 0 477.27 323.06 40617 +2013 277 11.09 -0.42 7.92 0 487.27 369.2 40412 +2013 278 11.78 -1.3 8.18 0 389.09 143.03 40208 +2013 279 10.76 -0.85 7.57 0.02 102.73 100.48 40003 +2013 280 12.18 7.44 10.88 0.08 375.45 254.93 39800 +2013 281 16.57 9.18 14.54 0 794.55 367.39 39597 +2013 282 19.06 5.15 15.23 0 513.64 187.73 39394 +2013 283 17.09 8.81 14.81 0.04 282.73 191.01 39192 +2013 284 18.54 11.15 16.51 0.01 265.45 126.9 38991 +2013 285 18.86 10.34 16.52 0.54 297.27 282.54 38790 +2013 286 18.22 8.07 15.43 0.37 354.55 282.15 38590 +2013 287 18.17 9.42 15.76 0 396.36 323.29 38391 +2013 288 17.16 5.5 13.95 0 237.27 266.57 38193 +2013 289 17.3 7.08 14.49 0.23 346.36 173.72 37995 +2013 290 13.62 8.03 12.08 0.11 752.73 337.23 37799 +2013 291 17.08 5.74 13.96 0 571.82 279.11 37603 +2013 292 17.8 4.27 14.08 0.01 531.82 323.35 37408 +2013 293 16.87 3.16 13.1 0 506.36 284.1 37214 +2013 294 20.88 7.21 17.12 0 619.09 245.54 37022 +2013 295 22.49 10.61 19.22 0 580 252.11 36830 +2013 296 21.31 8.49 17.78 0 978.18 293.49 36640 +2013 297 24.02 12.43 20.83 0 576.36 178.83 36451 +2013 298 20.29 12.64 18.19 0 591.82 273.91 36263 +2013 299 22.1 8.08 18.24 0 1016.75 251.81 36076 +2013 300 20.1 8.59 16.93 0 812.62 229.78 35891 +2013 301 20.95 7.9 17.36 0 916.53 238.12 35707 +2013 302 23.05 11.64 19.91 0 955.6 213.55 35525 +2013 303 19.16 9.35 16.46 0.73 696.78 146.68 35345 +2013 304 13.06 8.36 11.77 0 281.64 106.71 35166 +2013 305 14.7 3.33 11.57 0 587.41 213.48 34988 +2013 306 16.06 5.24 13.08 0 618.58 201.12 34813 +2013 307 16.75 5.31 13.6 0 666.13 204.73 34639 +2013 308 18.31 8.12 15.51 1.62 679.9 139.81 34468 +2013 309 10.74 7.83 9.94 0.95 84 39.35 34298 +2013 310 11.07 7.32 10.04 1.26 123.33 114.54 34130 +2013 311 10.73 2.49 8.46 0.01 344.44 230.55 33964 +2013 312 15.71 5.94 13.02 0 285.56 219.23 33801 +2013 313 16.82 3.7 13.21 0 165.56 26.75 33640 +2013 314 14.19 7.1 12.24 2.74 110 87.69 33481 +2013 315 9.55 4.8 8.24 1.17 215.56 49.26 33325 +2013 316 8.54 4.82 7.52 0.21 282.22 105.75 33171 +2013 317 8.53 4.74 7.49 0 117.78 26.01 33019 +2013 318 7.61 5.89 7.14 0.19 155.56 81.1 32871 +2013 319 7.32 3.1 6.16 0.2 47.78 28.37 32725 +2013 320 6.97 4.35 6.25 0 60 169.73 32582 +2013 321 10.44 0.62 7.74 0 92.22 191.61 32441 +2013 322 10.11 0.16 7.37 0 106.67 86.6 32304 +2013 323 7.75 3.56 6.6 0 73.33 54.52 32170 +2013 324 7.54 4.81 6.79 0.39 16.67 26.81 32039 +2013 325 7.76 6.03 7.28 0.99 15.56 42.27 31911 +2013 326 7.89 3.88 6.79 0.19 45.56 37.14 31786 +2013 327 7.15 4.95 6.55 0.86 46.67 53.9 31665 +2013 328 8.91 5.83 8.06 2.29 28.89 29.67 31547 +2013 329 8 6.13 7.49 1.69 300 59.4 31433 +2013 330 6.29 0.47 4.69 0 235.56 201.9 31322 +2013 331 2.78 -0.37 1.91 0.01 216.67 151.52 31215 +2013 332 2.55 -1.29 1.49 0 284.44 241.36 31112 +2013 333 4.01 -5.33 1.44 0 364.44 189.4 31012 +2013 334 7.64 -3.49 4.58 0 168.89 106.08 30917 +2013 335 5.51 -1.01 3.72 0 217.78 231.55 30825 +2013 336 6.89 -3.57 4.01 0 223.33 169.72 30738 +2013 337 7.12 -2.9 4.36 0 153.33 193.61 30654 +2013 338 4.84 -4.75 2.2 0 147.78 214.61 30575 +2013 339 3.81 -4.76 1.45 0 130 155.94 30500 +2013 340 4.88 -4.61 2.27 0 374.44 194.59 30430 +2013 341 7.39 -1.27 5.01 0 230 143.76 30363 +2013 342 4.63 -2.14 2.77 0.01 223.21 100.73 30301 +2013 343 8.06 -0.91 5.59 0 337.28 153.96 30244 +2013 344 7.28 -2.16 4.68 0 195.56 92.4 30191 +2013 345 9.71 3.7 8.06 0.01 264.44 57.58 30143 +2013 346 4.89 -0.25 3.48 0 152.22 48.16 30099 +2013 347 3.59 0.25 2.67 0 10 27.05 30060 +2013 348 1.79 -1.27 0.95 0.01 97.58 27.47 30025 +2013 349 0.14 -1.47 -0.3 0 48.96 50.58 29995 +2013 350 0.02 -2.01 -0.54 0 5 64.22 29970 +2013 351 -0.17 -3.41 -1.06 0 10 33.81 29950 +2013 352 -2.11 -3.84 -2.59 0 10 15.87 29934 +2013 353 -2.26 -3.45 -2.59 0 6.25 82.51 29924 +2013 354 -0.01 -4.72 -1.31 0 124.82 93.44 29918 +2013 355 2.16 -2.77 0.8 0 149.25 115.46 29916 +2013 356 4.79 -2.07 2.9 0.01 227.69 32.86 29920 +2013 357 4.49 0.43 3.37 0.01 147.77 69.86 29928 +2013 358 3.16 -0.1 2.26 0 112.58 177.49 29941 +2013 359 11.86 -0.35 8.5 0 514.15 83.97 29959 +2013 360 12.64 6.98 11.08 0 319.29 51.73 29982 +2013 361 11.3 7.25 10.19 0.97 224.01 80.89 30009 +2013 362 8.34 4.32 7.23 0.01 186.18 165.86 30042 +2013 363 10.29 1 7.74 0 396.52 57.32 30078 +2013 364 7.75 2.41 6.28 0.08 226.67 92.02 30120 +2013 365 6.99 3.28 5.97 0.03 160.05 40.67 30166 +2014 1 4.97 2.58 4.31 0.02 95.78 16.86 30217 +2014 2 4.85 3.08 4.36 0 72.14 139.42 30272 +2014 3 8.89 2.5 7.13 0 279.49 183.19 30331 +2014 4 11.6 -0.17 8.36 0 495.88 96.46 30396 +2014 5 8.57 -0.85 5.98 0.04 359.42 49.36 30464 +2014 6 11.55 6.91 10.27 0.28 254.81 161.95 30537 +2014 7 10.09 3.13 8.18 0 320.63 52.91 30614 +2014 8 5.85 1.84 4.75 0.01 159.29 37.94 30695 +2014 9 4.2 1.99 3.59 0.01 85 59.68 30781 +2014 10 4.3 0.47 3.25 0.01 139 105.29 30870 +2014 11 7.82 1.88 6.19 0 247.42 43.98 30964 +2014 12 6.09 0.99 4.69 0 197.05 218.8 31061 +2014 13 9.03 -0.42 6.43 0 370.68 215.94 31162 +2014 14 7.58 -2.24 4.88 0 346.56 58.23 31268 +2014 15 8.75 -0.56 6.19 0.36 360.78 126.67 31376 +2014 16 7.27 2.05 5.83 0 216.08 157.85 31489 +2014 17 8.4 -0.27 6.02 0 336.92 123.46 31605 +2014 18 12.08 4.25 9.93 0 393.94 118.45 31724 +2014 19 13 3.65 10.43 0 469.86 78.67 31847 +2014 20 11.93 5.75 10.23 0.28 327.75 79.3 31974 +2014 21 11.23 5.61 9.68 0.01 291.85 137.15 32103 +2014 22 9.45 3.85 7.91 0 261.27 67.89 32236 +2014 23 5.03 1.95 4.18 0 120.56 40.83 32372 +2014 24 3.5 0.41 2.65 0.06 109.79 36.06 32510 +2014 25 0.82 -1.63 0.15 1.18 75.23 244.67 32652 +2014 26 -0.01 -5.16 -1.43 0 134.02 109.95 32797 +2014 27 -4.27 -10.5 -5.98 0.03 116.08 98.26 32944 +2014 28 -3.63 -7.73 -4.76 0.03 87.45 77.64 33094 +2014 29 -1.62 -4.67 -2.46 0.18 77.85 105.8 33247 +2014 30 -1.02 -3.99 -1.84 0.06 79.14 70.84 33402 +2014 31 -0.9 -5.64 -2.2 0.1 118.27 74.6 33559 +2014 32 -2.39 -5.23 -3.17 0.41 69.47 70.53 33719 +2014 33 -0.5 -2.95 -1.17 0.89 69.03 53.81 33882 +2014 34 -0.25 -3.27 -1.08 0 84.48 60.47 34046 +2014 35 -0.8 -2.73 -1.33 0 54.48 48.44 34213 +2014 36 0.3 -2.72 -0.53 0 87.58 87.02 34382 +2014 37 2.16 -1.36 1.19 0.01 112.83 89.49 34552 +2014 38 9.33 -2.05 6.2 0.63 422.32 215.63 34725 +2014 39 7.97 2.74 6.53 0.23 226 89.32 34900 +2014 40 9.48 1.47 7.28 1.59 341.47 49.87 35076 +2014 41 7.89 -1.23 5.38 0.08 337.29 200.3 35254 +2014 42 7.88 4.88 7.05 1.16 140.5 47.88 35434 +2014 43 5.66 0.61 4.27 0.47 190.29 65.06 35615 +2014 44 8.54 -2.84 5.41 0.63 401.74 252.58 35798 +2014 45 9.76 2.95 7.89 0 309.21 222.83 35983 +2014 46 12.15 0.38 8.91 0 513 279.15 36169 +2014 47 12.31 3.46 9.88 1.79 434.59 161.49 36356 +2014 48 6 2.42 5.02 0.62 145.99 66.02 36544 +2014 49 5.67 -0.12 4.08 0 212.04 92.9 36734 +2014 50 9.87 4.42 8.37 0.65 262.36 61.68 36925 +2014 51 10.71 4.22 8.93 0 316.07 163.25 37117 +2014 52 9.13 3.44 7.57 0.02 259.43 71.6 37310 +2014 53 7.37 4.47 6.57 0.55 132.15 56.04 37505 +2014 54 9.14 3.23 7.51 0.04 267.37 68.56 37700 +2014 55 11.55 0.93 8.63 0 465.83 275.43 37896 +2014 56 8.87 -0.2 6.38 0 357.42 221.9 38093 +2014 57 12.81 -0.28 9.21 0 565.51 211.13 38291 +2014 58 12.06 2.23 9.36 0 458.29 277.8 38490 +2014 59 11.2 2.57 8.83 0.01 399.4 255.25 38689 +2014 60 13.52 0.4 9.91 0 591.42 257.07 38890 +2014 61 10.22 2.78 8.17 0 339.24 198.76 39091 +2014 62 7.82 1.8 6.16 0.47 249.98 143.79 39292 +2014 63 9.39 4.11 7.94 0 248.45 117.01 39495 +2014 64 11.78 4.92 9.89 0.01 351.49 144.73 39697 +2014 65 9.9 5.35 8.65 0 227.06 134.72 39901 +2014 66 9.93 2.97 8.02 0 317.51 295.62 40105 +2014 67 12.44 1.42 9.41 0 502.89 267.36 40309 +2014 68 12.05 1.64 9.19 0 474.59 371.75 40514 +2014 69 11.14 1.28 8.43 0 434 277.69 40719 +2014 70 14.79 -0.86 10.49 0 694.34 403.36 40924 +2014 71 15.34 2.04 11.68 0 665.27 363.22 41130 +2014 72 16.07 0.25 11.72 0 754.21 379.56 41336 +2014 73 18.76 0.18 13.65 0 943.12 389.2 41543 +2014 74 17.1 2.54 13.1 0 773.22 156.71 41749 +2014 75 19.5 6.29 15.87 0 848.32 207.6 41956 +2014 76 21.5 5.76 17.17 0 1038.56 401.98 42163 +2014 77 19.43 3.64 15.09 0 921.47 380.35 42370 +2014 78 17.41 7.82 14.77 0 620.46 334.12 42578 +2014 79 20.22 3.05 15.5 0 999.66 428.74 42785 +2014 80 21.47 4.97 16.93 0 1058.3 404.17 42992 +2014 81 19.38 7.86 16.21 0 779.99 356.68 43200 +2014 82 15.69 10.07 14.14 0.75 379.68 151.01 43407 +2014 83 12.8 3.43 10.22 0.01 464.86 216.76 43615 +2014 84 10.44 -0.53 7.42 0.03 443.31 286.38 43822 +2014 85 12.37 0.95 9.23 0 511.2 294.3 44029 +2014 86 13.99 1.39 10.53 0 595.91 223.45 44236 +2014 87 17.16 5.05 13.83 0 705.16 398 44443 +2014 88 19.36 3 14.86 0 931.7 419.23 44650 +2014 89 21 3.21 16.11 0 1060.98 430.87 44857 +2014 90 20.26 3.9 15.76 0 982.48 310.1 45063 +2014 91 19.52 6.62 15.97 0 838.54 388.54 45270 +2014 92 19.99 5.24 15.93 0 922.96 395.24 45475 +2014 93 20.36 5.47 16.27 0 947.36 328.82 45681 +2014 94 19.92 7.49 16.5 0 840.8 339.59 45886 +2014 95 18.43 9.94 16.1 0.01 606 266.62 46091 +2014 96 19.52 9.39 16.73 0.74 726.26 264.15 46295 +2014 97 20.52 6.83 16.76 0 917.09 440.47 46499 +2014 98 23.74 7.34 19.23 0.37 1203 416.4 46702 +2014 99 18.02 7.65 15.17 0 676.01 338.89 46905 +2014 100 12.71 2.6 9.93 0.36 485.26 141.55 47107 +2014 101 14.75 2 11.24 0 627.98 490.32 47309 +2014 102 15.29 2.14 11.67 0 659.4 346.26 47510 +2014 103 16.58 2.44 12.69 0.06 739.06 289.45 47710 +2014 104 19.25 4.31 15.14 0.42 889.14 289.03 47910 +2014 105 10.36 3.48 8.47 0.01 323.2 264.82 48108 +2014 106 11.68 3.77 9.5 0.01 387.29 270.74 48306 +2014 107 11.89 3.88 9.69 0 395.72 199.61 48504 +2014 108 18.53 2.48 14.12 0 879.79 486.66 48700 +2014 109 18.4 8.51 15.68 0.62 670.46 314.95 48895 +2014 110 14.76 7.56 12.78 0.38 435 196.81 49089 +2014 111 18.32 8.33 15.57 0.78 671.72 217.55 49282 +2014 112 19.69 9.98 17.02 0 713.45 341.37 49475 +2014 113 19.94 9.1 16.96 0 776.42 370.25 49666 +2014 114 20.59 12.06 18.24 0.43 687.46 316.14 49855 +2014 115 17.16 12.3 15.82 1.8 367.14 67.08 50044 +2014 116 17.27 11.33 15.64 0.01 434.47 170.46 50231 +2014 117 20.63 7.14 16.92 0 915.87 473.94 50417 +2014 118 20.74 9.02 17.52 0.05 852.05 335 50601 +2014 119 19.19 8.96 16.38 0.04 717.12 344.05 50784 +2014 120 21.72 8.86 18.18 0.05 950.17 488.57 50966 +2014 121 21.86 8.14 18.09 0 991.72 476.93 51145 +2014 122 22.28 7 18.08 0.04 1071.67 361.45 51324 +2014 123 14.88 8.29 13.07 0.07 410 149.54 51500 +2014 124 15.18 6.16 12.7 0.01 522.68 495.34 51674 +2014 125 15.73 4.15 12.55 0 631.45 527.01 51847 +2014 126 20.15 2.9 15.41 0 997.35 491.27 52018 +2014 127 21.33 7.31 17.47 0.85 972.82 383.75 52187 +2014 128 20.65 9.42 17.56 0.1 826.31 394.62 52353 +2014 129 22.76 7.79 18.64 0.69 1090.85 419.39 52518 +2014 130 22.02 11.47 19.12 0.22 859.05 445.41 52680 +2014 131 19.2 8.5 16.26 2.38 738.11 132.63 52840 +2014 132 17.99 5.78 14.63 0.58 743.91 378.3 52998 +2014 133 12.46 8.06 11.25 1.23 257.34 132.05 53153 +2014 134 14.77 6.54 12.51 0.09 479.12 329.23 53306 +2014 135 11.87 7.59 10.69 0.86 242.8 136.11 53456 +2014 136 10.77 8.46 10.13 0.6 132.15 47.34 53603 +2014 137 14.76 7.81 12.85 0.31 423.75 205.89 53748 +2014 138 18.51 9.53 16.04 0.92 632.81 300.1 53889 +2014 139 22.8 7.86 18.69 0.01 1092.29 373.07 54028 +2014 140 24.19 8.99 20.01 0 1191.89 493.69 54164 +2014 141 25.67 9.99 21.36 0 1314.57 493.3 54297 +2014 142 27.1 12.93 23.2 0 1352.89 485.93 54426 +2014 143 28.18 14.23 24.34 0.16 1423.18 342.33 54552 +2014 144 26.51 15.45 23.47 0.02 1134.46 457.22 54675 +2014 145 25.13 14.75 22.28 0.01 1010.32 430.1 54795 +2014 146 25.81 13.08 22.31 0.13 1188.21 336.1 54911 +2014 147 24.78 12.98 21.54 0.18 1073.76 466.77 55023 +2014 148 19.59 11.38 17.33 0.04 632.34 234.02 55132 +2014 149 19.89 11.32 17.53 0.13 662.96 234.89 55237 +2014 150 16.04 8.99 14.1 0 461.55 308.8 55339 +2014 151 17.45 7.17 14.62 0.02 650.34 242.01 55436 +2014 152 20.66 10.13 17.76 0 794.48 213.39 55530 +2014 153 21.14 9.31 17.89 0.01 876.55 408.3 55619 +2014 154 21.08 8.56 17.64 0.59 902.47 349.54 55705 +2014 155 23.46 7.6 19.1 0 1166.43 503.36 55786 +2014 156 22.04 11.38 19.11 0.01 865.68 315.61 55863 +2014 157 25.82 9.83 21.42 0 1337.75 500.01 55936 +2014 158 28.35 11.29 23.66 0 1584.63 501.59 56004 +2014 159 30.16 13.89 25.69 0 1712.07 501.98 56068 +2014 160 31.18 14.72 26.65 0 1818.56 480.38 56128 +2014 161 32.33 15.17 27.61 0 1971.06 397.62 56183 +2014 162 33.27 16.04 28.53 0 2075.77 500.28 56234 +2014 163 29.21 18.69 26.32 0.11 1269.75 358.09 56280 +2014 164 25.89 16.07 23.19 0.1 1015.2 327.19 56321 +2014 165 23.39 14.42 20.92 0.01 832.35 416.04 56358 +2014 166 22.84 10.51 19.45 0 988.73 468.31 56390 +2014 167 22.41 10.58 19.16 0 942.03 462.93 56418 +2014 168 19.67 12.94 17.82 0 548.5 165.08 56440 +2014 169 24.98 11.79 21.35 0.05 1157.74 449.83 56458 +2014 170 26.19 10.61 21.91 0.04 1349.19 443.35 56472 +2014 171 21.46 12.53 19 0.31 745.32 294.58 56480 +2014 172 22.07 9.3 18.56 0 965.53 410.35 56484 +2014 173 26.64 9.89 22.03 0 1429.91 511.24 56482 +2014 174 27.12 13.81 23.46 1.8 1309.23 450.99 56476 +2014 175 23.62 15.48 21.38 0.39 786.92 133.58 56466 +2014 176 19.33 13 17.59 0.23 513.28 175.04 56450 +2014 177 21.93 9.66 18.56 0 936.49 532.86 56430 +2014 178 24.49 11.57 20.94 0 1113.69 458.2 56405 +2014 179 27.09 12.19 22.99 0.01 1387.54 343.73 56375 +2014 180 29.71 15.34 25.76 2.5 1570.54 502.41 56341 +2014 181 23.71 12.51 20.63 0.86 980.25 251.99 56301 +2014 182 23.38 9.36 19.52 0 1093.53 454.35 56258 +2014 183 26.44 11.28 22.27 0.53 1350.13 429.28 56209 +2014 184 25.46 13.3 22.12 0 1134.94 490.49 56156 +2014 185 26.15 11.3 22.07 0 1315.06 511.04 56099 +2014 186 26.29 14.68 23.1 0.17 1155.23 341.78 56037 +2014 187 29.6 14.65 25.49 0 1593.71 495.59 55971 +2014 188 31.07 15.46 26.78 0 1762.45 512.73 55900 +2014 189 27.56 18.06 24.95 0.03 1086.06 420.86 55825 +2014 190 22.75 14.9 20.59 0.67 730.63 285.4 55746 +2014 191 17.74 12.24 16.23 1.02 419.74 142.76 55663 +2014 192 20.53 13.18 18.51 0.28 615.19 152.96 55575 +2014 193 26.73 13.88 23.2 0.06 1256.47 384.4 55484 +2014 194 25.29 13.98 22.18 0.24 1076.22 417.42 55388 +2014 195 25.7 13.61 22.38 0.62 1146.11 368.49 55289 +2014 196 28.31 15.26 24.72 0.02 1381.28 487.4 55186 +2014 197 29.34 17.28 26.02 0 1393.72 413.14 55079 +2014 198 29.59 17.22 26.19 0.04 1434.11 482.93 54968 +2014 199 29.25 14.95 25.32 0 1528.15 484.71 54854 +2014 200 30.31 16.1 26.4 0 1612.23 468.4 54736 +2014 201 30.94 16.46 26.96 0 1684.18 469.07 54615 +2014 202 29.7 18.28 26.56 0 1373.69 311.34 54490 +2014 203 22.82 15.29 20.75 1.42 711.31 132.43 54362 +2014 204 26.91 17.54 24.33 0.03 1039 471.66 54231 +2014 205 26.76 14.37 23.35 0 1232.29 479.02 54097 +2014 206 26.91 16.26 23.98 0.16 1131.71 302.48 53960 +2014 207 28.43 15.45 24.86 0.01 1386.01 423.45 53819 +2014 208 25.73 15.87 23.02 0.59 1009.16 276.26 53676 +2014 209 24.11 17.59 22.32 0.82 683.96 181.11 53530 +2014 210 27.08 16.68 24.22 0.01 624 280.33 53382 +2014 211 27.74 16.18 24.56 2.78 582.14 279.41 53230 +2014 212 25.42 16.56 22.98 0.23 514.29 239.43 53076 +2014 213 26.31 17.9 24 0 762.86 359.63 52920 +2014 214 28.69 16.63 25.37 0 1085.71 402.27 52761 +2014 215 29.09 17.16 25.81 0 1061.43 450.67 52600 +2014 216 26.79 15.46 23.67 0.05 831.43 370.91 52437 +2014 217 25.26 16.1 22.74 0.02 968.57 360 52271 +2014 218 23.35 17.71 21.8 0 937.14 214.79 52103 +2014 219 25.5 17.23 23.23 0 1166.43 365.09 51934 +2014 220 28.25 13.63 24.23 0 1423.57 483.07 51762 +2014 221 29.9 14.94 25.79 1.22 1278.57 440.36 51588 +2014 222 28.62 16.63 25.32 0 1020 435.41 51413 +2014 223 29.78 17.22 26.33 1.31 1147.14 443.02 51235 +2014 224 22.01 16.6 20.52 1.6 505.71 183.37 51057 +2014 225 25.6 14.66 22.59 3.26 565 334.25 50876 +2014 226 22.37 13.69 19.98 2.64 233.57 147.27 50694 +2014 227 21.64 13.43 19.38 0.17 575 209.71 50510 +2014 228 21.84 10.88 18.83 0 837.14 360.78 50325 +2014 229 22.9 9.73 19.28 0 1016.43 455.16 50138 +2014 230 24.38 10.29 20.51 0 987.14 461.93 49951 +2014 231 23.87 11.88 20.57 0.02 685 307.2 49761 +2014 232 19.89 14.75 18.48 1.88 355 194.85 49571 +2014 233 21.42 12.15 18.87 0.09 732.86 443.05 49380 +2014 234 21.86 11.08 18.9 0 608.57 264.49 49187 +2014 235 21.45 12.51 18.99 0.96 373.57 218.25 48993 +2014 236 21.29 13.17 19.06 0.13 779.29 312.52 48798 +2014 237 20.51 8.83 17.3 0 801.43 420.49 48603 +2014 238 21.46 10.82 18.53 0.03 583.57 208.77 48406 +2014 239 23.23 14.53 20.84 0.12 466.43 272.13 48208 +2014 240 22.34 7.85 18.36 0 977.14 438.44 48010 +2014 241 23.37 8.81 19.37 0 915.71 450.11 47811 +2014 242 24.52 10.79 20.74 0.02 840 373.4 47611 +2014 243 22.42 14.69 20.29 2.26 472.86 216.32 47410 +2014 244 18.96 11.98 17.04 1.81 151.43 60.92 47209 +2014 245 15.23 13.16 14.66 2.53 190.71 47.74 47007 +2014 246 20.01 13.89 18.33 0.03 454.62 262.62 46805 +2014 247 22.69 15.59 20.74 0.34 575.38 189.87 46601 +2014 248 24.49 16.19 22.21 0.57 609.23 323.99 46398 +2014 249 20.8 16.23 19.54 0.06 306.15 136.04 46194 +2014 250 21.61 14.97 19.78 0 501.54 221.72 45989 +2014 251 24.62 12.6 21.31 0 786.92 393.66 45784 +2014 252 25.97 13.37 22.5 0.32 676.15 346.91 45579 +2014 253 19.1 15.17 18.02 0.31 289.23 118.29 45373 +2014 254 15.95 12.83 15.09 2.76 158.46 45.96 45167 +2014 255 15.4 12.23 14.53 3.74 158.46 114.55 44961 +2014 256 20.22 12.85 18.19 0.09 381.54 224.6 44755 +2014 257 17.77 13.44 16.58 0.72 146.67 108.02 44548 +2014 258 19.59 13.61 17.95 0.09 265.83 170.37 44341 +2014 259 20.66 13.33 18.64 0.08 430.83 231.16 44134 +2014 260 21.36 11 18.51 0 665.83 366.53 43927 +2014 261 21.33 8.41 17.78 0 751.67 409.68 43719 +2014 262 23.96 11.17 20.44 0 733.33 378.19 43512 +2014 263 24.01 13.09 21.01 0 573.33 302.16 43304 +2014 264 25.73 15.36 22.88 1.91 905 398.95 43097 +2014 265 18.49 11.78 16.64 0.01 680.83 255.05 42890 +2014 266 16.62 7.4 14.08 0 689.17 279.91 42682 +2014 267 18.25 5.35 14.7 0 616.67 400.53 42475 +2014 268 15.71 7.6 13.48 0.07 275 155.85 42268 +2014 269 14.02 8.46 12.49 0.2 227.5 47.57 42060 +2014 270 18.19 11.48 16.34 0.01 300.83 174.7 41854 +2014 271 20.9 8.22 17.41 0 671.67 405.42 41647 +2014 272 21.51 8.46 17.92 0 683.33 392.59 41440 +2014 273 17.32 8.52 14.9 0 92.5 120.88 41234 +2014 274 18.62 10.51 16.39 0.12 215.83 152.81 41028 +2014 275 18.07 13.23 16.74 0.2 312.5 118.11 40822 +2014 276 17.79 10.61 15.82 0 349.09 251.45 40617 +2014 277 15.49 8.96 13.69 0.05 200.91 94.67 40412 +2014 278 17.85 10.41 15.8 0.01 500 266.23 40208 +2014 279 17.82 6.06 14.59 0 470.91 311.16 40003 +2014 280 18.1 8.63 15.5 0 273.64 209.83 39800 +2014 281 22.22 10.71 19.05 0 580 250.91 39597 +2014 282 24.76 13.96 21.79 0 1025.45 376.59 39394 +2014 283 24.06 12.59 20.91 0 777.27 372.39 39192 +2014 284 25.1 11.19 21.27 0 925.45 355.51 38991 +2014 285 22.85 11.19 19.64 0 648.18 332.8 38790 +2014 286 25.03 11.85 21.41 0 976.36 340.59 38590 +2014 287 24.28 14.14 21.49 0.01 1117.27 306.96 38391 +2014 288 18.73 11.45 16.73 0.05 292.73 158.62 38193 +2014 289 22.09 11.87 19.28 0.12 548.18 289.71 37995 +2014 290 19.05 12.75 17.32 0.17 141.82 101.3 37799 +2014 291 20.09 7.96 16.75 0 623.64 308.52 37603 +2014 292 20.85 8.11 17.35 0 708.18 338.79 37408 +2014 293 23.36 8.81 19.36 0 753.64 311.01 37214 +2014 294 17.63 12.54 16.23 6.07 145.45 97.43 37022 +2014 295 14.68 6.15 12.33 0.31 230 117.09 36830 +2014 296 9.48 5.96 8.51 0.5 184.55 47.67 36640 +2014 297 9.27 6.99 8.64 0.18 259.09 30.28 36451 +2014 298 7.96 5.08 7.17 0.02 80.91 41.54 36263 +2014 299 8.59 3.5 7.19 0 120.91 104.14 36076 +2014 300 8.88 3.41 7.38 0 168.18 64.38 35891 +2014 301 9.59 -0.53 6.81 0 213 293.95 35707 +2014 302 9.39 -0.76 6.6 0 210 194.79 35525 +2014 303 9.18 3.79 7.7 0 257 60.57 35345 +2014 304 11.56 3.58 9.37 0 242 87.42 35166 +2014 305 14.52 3.48 11.48 0 423 263.69 34988 +2014 306 13.56 3.12 10.69 0 382 277.86 34813 +2014 307 10.93 2.65 8.65 0 168 138.03 34639 +2014 308 17.82 7.44 14.97 0 706 240.1 34468 +2014 309 19.98 9.37 17.06 0.29 887 208.51 34298 +2014 310 16.43 11.32 15.02 0.13 201.11 87.89 34130 +2014 311 16.76 10.06 14.92 0.44 205.56 112.78 33964 +2014 312 14.99 9.07 13.36 0.03 270 74.55 33801 +2014 313 12.96 8.17 11.64 0 204.44 127.81 33640 +2014 314 18.15 8.48 15.49 0 505.56 255.57 33481 +2014 315 18.07 9.56 15.73 0 636.67 199.62 33325 +2014 316 14.5 8.14 12.75 0.02 206.67 132.42 33171 +2014 317 11.66 8.09 10.68 0.01 160 62.95 33019 +2014 318 13.99 9.86 12.85 0 230 105.12 32871 +2014 319 12.69 9.35 11.77 0.03 181.11 92.96 32725 +2014 320 14.05 8.13 12.42 0 220 199.75 32582 +2014 321 10.4 7.92 9.72 1.41 37.78 65.35 32441 +2014 322 13.95 7.28 12.12 0.01 344.44 170.47 32304 +2014 323 12.44 5.2 10.45 0.02 354.44 207.97 32170 +2014 324 10.92 4.65 9.2 0 308.89 209.77 32039 +2014 325 8.59 2.16 6.82 0 305.56 134.02 31911 +2014 326 9.1 0.02 6.6 0 261.11 198.6 31786 +2014 327 7.38 -0.28 5.27 0 205.56 180.38 31665 +2014 328 4.98 1.5 4.02 0.02 135.56 33.86 31547 +2014 329 4.79 1.52 3.89 0.01 96.67 42.74 31433 +2014 330 5.17 1.14 4.06 0 205.56 93.98 31322 +2014 331 3.36 0.69 2.63 0 191.11 76.62 31215 +2014 332 2.43 0.71 1.96 0.1 20 28.61 31112 +2014 333 2.9 2 2.65 0.08 10 25.69 31012 +2014 334 3.17 2.18 2.9 0.35 10 30.82 30917 +2014 335 2.58 1.39 2.25 0.92 21.11 10.2 30825 +2014 336 1.86 0.22 1.41 0.24 21.11 22.72 30738 +2014 337 3.69 1.15 2.99 0.1 28.89 23.8 30654 +2014 338 4.48 3.12 4.11 0.15 65.56 28.96 30575 +2014 339 5 3.56 4.6 0.09 44.44 36.85 30500 +2014 340 5.24 4.04 4.91 1.66 20 13.5 30430 +2014 341 5.4 4.13 5.05 1.04 76.67 32.36 30363 +2014 342 6.55 3.03 5.58 0.01 148.89 103.73 30301 +2014 343 4.28 1.81 3.6 0 250 73.83 30244 +2014 344 4.01 -1.79 2.42 0 252.22 198.49 30191 +2014 345 5.32 -2.47 3.18 0 292.22 111.57 30143 +2014 346 7.73 -1.64 5.15 0 334.44 200.95 30099 +2014 347 11 0.37 8.08 0 592.22 163.49 30060 +2014 348 7.4 -0.32 5.28 0 118.75 65.99 30025 +2014 349 4.44 -2.09 2.64 0 345 62.21 29995 +2014 350 4.72 -1.79 2.93 0.28 237.5 55.59 29970 +2014 351 8.21 1.86 6.46 0 247.5 159.61 29950 +2014 352 9.41 1.64 7.27 0 816.25 122.9 29934 +2014 353 13.45 3.66 10.76 0 886.25 188.94 29924 +2014 354 11.92 2.98 9.46 0.01 858.75 189.15 29918 +2014 355 9.58 0.89 7.19 0 1036.25 202.43 29916 +2014 356 8.34 -2.06 5.48 0 948.75 117.89 29920 +2014 357 12.32 2.34 9.58 0 1206.25 132.03 29928 +2014 358 8.82 -1.92 5.87 0 795 160.93 29941 +2014 359 8.49 -2.18 5.56 0 580 173.78 29959 +2014 360 5.66 -1.27 3.75 0.23 605 151.72 29982 +2014 361 0.55 -3.87 -0.67 0.28 235 108.45 30009 +2014 362 0 -5.57 -1.53 0.07 90 56.99 30042 +2014 363 -1.12 -6.59 -2.62 0 288.75 182.77 30078 +2014 364 -2.55 -8.65 -4.23 0 165 86.89 30120 +2014 365 -3.86 -14.07 -6.67 0 163.75 247.17 30166 +2015 1 0.1 -6.4 -1.69 0 161.14 63.15 30217 +2015 2 6.1 -3.2 3.54 0.28 212.5 133.17 30272 +2015 3 5.8 -1.5 3.79 0.11 177.5 143.03 30331 +2015 4 6.9 -0.6 4.84 0.33 367.5 209.28 30396 +2015 5 3.5 -0.4 2.43 0 206.25 70.11 30464 +2015 6 5.2 -0.6 3.61 0 228.75 185.36 30537 +2015 7 -1 -3.8 -1.77 0 160 93.68 30614 +2015 8 0.6 -4.1 -0.69 0 111.25 99.18 30695 +2015 9 6 -2.3 3.72 0.02 158.75 64.27 30781 +2015 10 14 1.1 10.45 0 578.75 160.15 30870 +2015 11 6.4 2 5.19 0.58 165 14.49 30964 +2015 12 8.7 0.6 6.47 0 464.44 173.84 31061 +2015 13 11.7 -1.3 8.13 0 541.11 207.09 31162 +2015 14 7.5 -1.5 5.03 0.09 256.67 187.79 31268 +2015 15 8.6 -0.8 6.01 0 248.89 186.14 31376 +2015 16 13.6 -0.5 9.72 0 600 190.64 31489 +2015 17 11.4 6 9.91 0.02 610 56.68 31605 +2015 18 9.4 1.4 7.2 0 154.44 70.84 31724 +2015 19 6.5 1 4.99 0 62.22 101.09 31847 +2015 20 4.8 0.2 3.54 0.24 91 80.61 31974 +2015 21 3.8 2 3.3 0.02 46 60.44 32103 +2015 22 6.4 3.5 5.6 0.02 69 53.16 32236 +2015 23 6.9 5.3 6.46 0.87 153 29.56 32372 +2015 24 5.6 1.3 4.42 0.36 70 27.78 32510 +2015 25 4.1 1.5 3.38 0 195 56.5 32652 +2015 26 3.2 -1.3 1.96 0 242 193.86 32797 +2015 27 1.7 -2.7 0.49 0.05 103 57.22 32944 +2015 28 5.8 -3.9 3.13 0 238 263.36 33094 +2015 29 0.8 -1.8 0.09 0.2 75 35.77 33247 +2015 30 1.9 -4.2 0.22 1.61 28 23.48 33402 +2015 31 5.4 -6.6 2.1 0 166 276.61 33559 +2015 32 2 -7.3 -0.56 0.62 71 101.09 33719 +2015 33 5.1 -6.9 1.8 0.01 139 300.56 33882 +2015 34 1.3 -8 -1.26 0.01 128 204.18 34046 +2015 35 1.5 -0.3 1 0 75 50.48 34213 +2015 36 1.3 -2 0.39 0.03 119 112.34 34382 +2015 37 0.4 -2 -0.26 0 169 75.3 34552 +2015 38 1.3 -4.6 -0.32 0 205 275.35 34725 +2015 39 2.9 -6.8 0.23 0.02 198 167.07 34900 +2015 40 0.8 -1.6 0.14 0.31 110 63.33 35076 +2015 41 4.6 -1.1 3.03 0.02 284 77.83 35254 +2015 42 5 0.9 3.87 0 174 126.94 35434 +2015 43 6.1 0.4 4.53 0 195 200.24 35615 +2015 44 5.7 -2.8 3.36 0 228 302.05 35798 +2015 45 6.5 -2.3 4.08 0 189 97.33 35983 +2015 46 11.1 -0.3 7.96 0 353 187.96 36169 +2015 47 10.4 -2.1 6.96 0 364 316.51 36356 +2015 48 5.1 -2.6 2.98 0 188 231.05 36544 +2015 49 5 -0.1 3.6 0 228 187.3 36734 +2015 50 8.5 -2 5.61 0 335 297.12 36925 +2015 51 11.1 -2.6 7.33 0 465 315.7 37117 +2015 52 11.8 -0.9 8.31 0 612 320.45 37310 +2015 53 8 2.2 6.4 1.12 297 66.41 37505 +2015 54 6.8 3.5 5.89 0.22 80 71.13 37700 +2015 55 5.9 4.5 5.52 1.61 47.27 48.07 37896 +2015 56 7.7 4.6 6.85 0 342.73 100.95 38093 +2015 57 10.4 5.2 8.97 0 369.09 205.43 38291 +2015 58 10.1 -2 6.77 0 270.91 255.51 38490 +2015 59 9.8 -0.7 6.91 0 356.36 239.02 38689 +2015 60 10.5 -2.5 6.93 0 388.18 250 38890 +2015 61 11.8 2.4 9.21 0.44 400.91 98.88 39091 +2015 62 11.8 0.2 8.61 0 689.17 340.77 39292 +2015 63 11 -2.1 7.4 0 453.33 230.4 39495 +2015 64 8 2.8 6.57 0 381.67 244.63 39697 +2015 65 7.3 1.5 5.71 0 408.33 302.72 39901 +2015 66 10.2 -0.1 7.37 0 395 385.96 40105 +2015 67 10.8 -4.5 6.59 0 528.33 398.38 40309 +2015 68 11 -2.1 7.4 0 542.5 353.2 40514 +2015 69 14 -3.1 9.3 0 676.67 380.98 40719 +2015 70 9.4 -1.1 6.51 0.14 305.83 136.62 40924 +2015 71 8.5 3.3 7.07 0 435 198.48 41130 +2015 72 6.4 4.4 5.85 0 290.83 85.83 41336 +2015 73 8.8 3.8 7.43 0 306.67 147.96 41543 +2015 74 8.5 -0.1 6.13 0.1 225 126.38 41749 +2015 75 12.7 1.4 9.59 0 402.5 305.58 41956 +2015 76 13.3 3 10.47 0 528.33 310.03 42163 +2015 77 12.8 -1.5 8.87 0 623.33 392.35 42370 +2015 78 12 -2.5 8.01 0 533.33 380.32 42578 +2015 79 13 -3.1 8.57 0 560.83 349.98 42785 +2015 80 17.1 -1.8 11.9 0 823.33 405.64 42992 +2015 81 13.3 3.6 10.63 0 506.67 341.21 43200 +2015 82 13 -2.2 8.82 0 531.67 396.12 43407 +2015 83 15.7 -1.6 10.94 0 690 374.45 43615 +2015 84 15.2 1.4 11.4 0.9 560.83 182.8 43822 +2015 85 18.8 7.9 15.8 0.38 618.33 353.34 44029 +2015 86 12.8 8 11.48 0.12 387.5 87.96 44236 +2015 87 12.2 7.3 10.85 0 657.5 341.16 44443 +2015 88 15.6 0.6 11.48 0 723.33 337.51 44650 +2015 89 15.6 7.5 13.37 0.2 532.5 194.65 44857 +2015 90 18.6 0.7 13.68 0.02 753.33 262.22 45063 +2015 91 13.6 3.7 10.88 0 627.5 445.2 45270 +2015 92 13.2 0.8 9.79 0 747.5 228.52 45475 +2015 93 11.1 -1.1 7.75 0 676.15 376.93 45681 +2015 94 9.5 -0.5 6.75 0 474.62 198 45886 +2015 95 9.4 2.4 7.48 0 456.15 354.63 46091 +2015 96 8.5 1.1 6.46 0 545.38 428.59 46295 +2015 97 9.1 2.4 7.26 0 504.29 254.87 46499 +2015 98 10.2 5.5 8.91 0.02 435 67.4 46702 +2015 99 13.9 7.4 12.11 0 590.71 283.43 46905 +2015 100 18.8 2 14.18 0 922.14 473.21 47107 +2015 101 21.1 2.8 16.07 0.37 1034.29 428.33 47309 +2015 102 20.7 8 17.21 0 1043.57 426.27 47510 +2015 103 23.7 4 18.28 0 1295.71 448.78 47710 +2015 104 18 8.3 15.33 0 928.57 432.58 47910 +2015 105 24.8 4.9 19.33 0 1575 463.2 48108 +2015 106 27.7 4 21.18 0 1846.43 448.23 48306 +2015 107 21.9 7 17.8 0.69 936.43 236.59 48504 +2015 108 12.6 6.8 11 0 435.71 229.21 48700 +2015 109 13.6 0.8 10.08 0 608.57 450.69 48895 +2015 110 19.5 1.5 14.55 0 909.29 524.28 49089 +2015 111 21.5 8.2 17.84 0 1177.14 515.47 49282 +2015 112 20.8 8.2 17.34 0 1227.14 458.89 49475 +2015 113 23.2 3.2 17.7 0 1394.29 466.12 49666 +2015 114 19.6 7 16.14 0 910 314.11 49855 +2015 115 23.1 5.9 18.37 0 1087.86 498.44 50044 +2015 116 22.9 8.5 18.94 0 1159.29 374.28 50231 +2015 117 23.2 7.7 18.94 0 1196.43 463.69 50417 +2015 118 19.1 9.5 16.46 1.06 207.86 112.71 50601 +2015 119 16.5 8.8 14.38 0 867.14 539.6 50784 +2015 120 18.5 1.5 13.82 0.15 970 389.1 50966 +2015 121 18.2 5.8 14.79 0.42 646.43 295.8 51145 +2015 122 18.9 10.6 16.62 0.18 451.43 350.11 51324 +2015 123 18 9.4 15.64 0.09 320 176.04 51500 +2015 124 24.7 12.2 21.26 0 812.86 410.06 51674 +2015 125 28.3 11.7 23.73 0 1329.29 422.28 51847 +2015 126 26.8 13.8 23.23 0.07 964.67 409.05 52018 +2015 127 22.7 9.1 18.96 0 1034 548.77 52187 +2015 128 24.4 13.2 21.32 0 1203.33 486.81 52353 +2015 129 24.3 9.4 20.2 0.06 732 298.32 52518 +2015 130 22.9 11.7 19.82 0 1154.67 454.08 52680 +2015 131 20.6 10.5 17.82 0 1018 539.81 52840 +2015 132 24.5 4.5 19 0 1296 514.77 52998 +2015 133 24.8 11.4 21.12 0.71 928 436.63 53153 +2015 134 24.1 13.4 21.16 0.01 666.67 350.4 53306 +2015 135 18.1 11.5 16.29 0.5 236 118.29 53456 +2015 136 20.3 11.9 17.99 0 395.33 275.61 53603 +2015 137 20.5 10.9 17.86 0 700 405.36 53748 +2015 138 23.3 10.9 19.89 0 842.67 403.72 53889 +2015 139 28.3 10.4 23.38 0.02 1067.33 439.46 54028 +2015 140 25.4 11.3 21.52 1.98 888.67 462.8 54164 +2015 141 13.5 10.1 12.57 0.41 235.33 102.52 54297 +2015 142 13 11.1 12.48 4.42 160 58.23 54426 +2015 143 13.4 10.6 12.63 0.24 126.88 99.81 54552 +2015 144 18.3 6 14.92 0 393.13 407.01 54675 +2015 145 18.7 12.6 17.02 0.12 456.25 137.68 54795 +2015 146 17.1 13.7 16.16 0.37 298.13 161.56 54911 +2015 147 16.8 11.3 15.29 0 685.63 316.95 55023 +2015 148 17.6 8.3 15.04 0 707.5 405.38 55132 +2015 149 23.4 5.5 18.48 0 988.13 504.03 55237 +2015 150 24.7 8.3 20.19 0.12 924.38 526 55339 +2015 151 22.3 13.8 19.96 0 663.75 351.21 55436 +2015 152 26.3 11 22.09 0 1038.75 459.99 55530 +2015 153 28.6 12.8 24.26 0 1370 492.81 55619 +2015 154 30 13.1 25.35 0 1597.5 492.99 55705 +2015 155 27.9 16.7 24.82 0 1289.38 510.86 55786 +2015 156 26.8 15.8 23.78 0 1195 449.99 55863 +2015 157 29.4 11.6 24.5 0 1366.87 510.19 55936 +2015 158 29.6 14.3 25.39 0 1565 476.21 56004 +2015 159 29.7 12.6 25 0 1696.88 505.68 56068 +2015 160 26.7 16.5 23.9 0 1050 499.6 56128 +2015 161 27.1 14.1 23.53 0 990 510.8 56183 +2015 162 28.6 15.4 24.97 0 1287.5 501.27 56234 +2015 163 31 14.6 26.49 0 1628.75 489.73 56280 +2015 164 32 16.5 27.74 0 1997.5 489.61 56321 +2015 165 31.8 14 26.91 0.05 1838.75 420.71 56358 +2015 166 25.7 14 22.48 0.13 704.38 276.2 56390 +2015 167 22.2 15.7 20.41 0.03 947.5 357.85 56418 +2015 168 21.2 14.2 19.27 0 1005 405.19 56440 +2015 169 24 10.9 20.4 0 1187.5 418.65 56458 +2015 170 20.8 15.8 19.43 0.21 666.88 184.52 56472 +2015 171 20.6 9.3 17.49 0.22 591.25 339.25 56480 +2015 172 20 5.8 16.09 0 833.13 391.31 56484 +2015 173 25.4 8.4 20.72 0 1143.75 464.15 56482 +2015 174 23.2 11.4 19.95 2.67 138.13 66.53 56476 +2015 175 20.6 11.2 18.02 0 735.31 348.24 56466 +2015 176 23.5 7.9 19.21 0 1160.27 475.58 56450 +2015 177 25.6 14.6 22.58 0 1370 533.84 56430 +2015 178 25.7 15.3 22.84 0.24 797.5 211.97 56405 +2015 179 25.7 16.1 23.06 0 1018.13 429.72 56375 +2015 180 25 12.9 21.67 0 1110 371.74 56341 +2015 181 27.2 11.1 22.77 0 1398.75 464.42 56301 +2015 182 30.3 14 25.82 0 1623.75 459.22 56258 +2015 183 31.7 15.9 27.36 0 1828.75 499.83 56209 +2015 184 30.4 17.6 26.88 0 1801.88 497.85 56156 +2015 185 31.6 15 27.04 0 2052.5 523.19 56099 +2015 186 33.4 14.5 28.2 0 2082.5 513.05 56037 +2015 187 34.6 15.6 29.38 0 2108.13 466.5 55971 +2015 188 36.9 18.9 31.95 0 2431.88 478.24 55900 +2015 189 33.2 18.9 29.27 4.57 1217.5 297.43 55825 +2015 190 24.9 16 22.45 0.29 559.38 316.63 55746 +2015 191 24.5 11.4 20.9 0 1177.5 507.94 55663 +2015 192 27.6 13.3 23.67 0.1 1318.75 481.58 55575 +2015 193 31 14.2 26.38 1.71 1583.13 431.27 55484 +2015 194 27.3 18 24.74 0.1 410 179.82 55388 +2015 195 26.8 16.7 24.02 0 895 319.04 55289 +2015 196 29.6 18.8 26.63 0 1298.13 442.17 55186 +2015 197 32 18.3 28.23 0 1355 376.82 55079 +2015 198 34.8 19.2 30.51 0 1853.13 461.42 54968 +2015 199 32.3 19.4 28.75 0.63 1643.75 350.13 54854 +2015 200 35.5 18.7 30.88 0 1916.88 465.74 54736 +2015 201 32.1 19.9 28.75 0 1782.5 450.58 54615 +2015 202 34.1 18.5 29.81 0 1841.88 369.82 54490 +2015 203 35.7 19 31.11 0 2141.25 474.7 54362 +2015 204 33.4 19.5 29.58 0.3 1826.25 374.78 54231 +2015 205 34 21.7 30.62 0.12 1751.25 452.86 54097 +2015 206 32.9 18.1 28.83 2.89 1127.5 370.23 53960 +2015 207 21.5 14.7 19.63 0 590.63 170.92 53819 +2015 208 20.6 13.9 18.76 0.09 420.63 157.37 53676 +2015 209 24.2 16.3 22.03 0 788.13 271.28 53530 +2015 210 20.8 14.1 18.96 0.45 328.67 101.23 53382 +2015 211 20.4 14.8 18.86 0.08 561.43 174.87 53230 +2015 212 24.6 16 22.23 0 1270 371.65 53076 +2015 213 26.6 9 21.76 0.02 1351.43 491.91 52920 +2015 214 26.1 16.2 23.38 0.4 1182.14 350.71 52761 +2015 215 28.9 17.1 25.66 0 1195.71 426.81 52600 +2015 216 31.2 16.2 27.07 0 1473.57 395.8 52437 +2015 217 32.2 18.1 28.32 0 2064.29 480.9 52271 +2015 218 34 17.3 29.41 0 2191.43 442.06 52103 +2015 219 35.2 18.1 30.5 0 2453.57 479.18 51934 +2015 220 35.4 18.1 30.64 0 2487.86 453.94 51762 +2015 221 35.3 16.8 30.21 0 2542.14 463.4 51588 +2015 222 34.4 15.2 29.12 0 2699.29 453.25 51413 +2015 223 34.3 15.2 29.05 0 2616.43 437.78 51235 +2015 224 36.1 15.4 30.41 0 3033.57 446.12 51057 +2015 225 36.2 15.4 30.48 0 2750.71 406.28 50876 +2015 226 35.8 16.6 30.52 0 2414.29 417.12 50694 +2015 227 34.4 17.2 29.67 0.02 2207.14 396.02 50510 +2015 228 30.2 18.6 27.01 1.8 1462.86 316.94 50325 +2015 229 26.1 17.9 23.84 0.21 342.14 160.75 50138 +2015 230 22.8 16.3 21.01 0 735.71 359.58 49951 +2015 231 23.7 13.9 21 0 729.29 289.65 49761 +2015 232 19 15.1 17.93 0.02 345.71 153.84 49571 +2015 233 23.3 11.8 20.14 0 847.14 303.07 49380 +2015 234 24.4 10.2 20.49 0 869.29 432.23 49187 +2015 235 24.1 12.4 20.88 0.04 672.86 285.12 48993 +2015 236 27.5 12.1 23.27 0 1290.71 403.57 48798 +2015 237 23.2 16.3 21.3 0.26 722.14 128.11 48603 +2015 238 26.9 10.2 22.31 0 1509.29 468.65 48406 +2015 239 29.3 12.5 24.68 0 971.43 461.14 48208 +2015 240 32.7 16.2 28.16 0 1818.57 494.12 48010 +2015 241 33.6 14.3 28.29 0 2062.86 450.44 47811 +2015 242 34.7 14 29.01 0 2049.29 445.38 47611 +2015 243 34 14.9 28.75 0 2142.14 453.51 47410 +2015 244 34 15.3 28.86 0 2232.14 450.18 47209 +2015 245 28.2 14.1 24.32 0.06 1050 303.51 47007 +2015 246 25.2 15.7 22.59 0.31 930 303.78 46805 +2015 247 23.4 15.1 21.12 1.41 813.85 192.23 46601 +2015 248 19.3 13.9 17.82 0.84 134.62 86.84 46398 +2015 249 18.6 11.5 16.65 0.36 570 340.9 46194 +2015 250 20 6.1 16.18 0.02 978.46 400.6 45989 +2015 251 20.3 12.6 18.18 0 977.69 367.39 45784 +2015 252 20.2 5.2 16.07 0 866.92 386.79 45579 +2015 253 20 10.6 17.41 0.05 716.15 337.79 45373 +2015 254 20.7 12.2 18.36 0.46 321.54 188.64 45167 +2015 255 24.1 7.2 19.45 0 708.46 453.64 44961 +2015 256 24.3 8.4 19.93 0 852.31 314.93 44755 +2015 257 27.7 14.5 24.07 0 1368.33 329.73 44548 +2015 258 26.1 13.6 22.66 0 818.33 212.53 44341 +2015 259 28 18.6 25.41 0 1208.33 277.65 44134 +2015 260 32.1 21.1 29.08 0 1818.33 387.98 43927 +2015 261 27.4 15.4 24.1 0.01 1550.83 338.43 43719 +2015 262 23.2 16.5 21.36 0.1 1048.33 165.4 43512 +2015 263 21.8 15 19.93 0 1110 322.53 43304 +2015 264 20.4 7.8 16.93 0 1118.33 423.21 43097 +2015 265 22.1 3.9 17.09 0 958.33 396.89 42890 +2015 266 23.1 6.5 18.54 0.34 950 315.03 42682 +2015 267 17.7 13.2 16.46 0.64 690.83 185.83 42475 +2015 268 17 12.3 15.71 3.42 227.5 39.89 42268 +2015 269 16.8 13 15.76 0.04 487.5 169.57 42060 +2015 270 17.1 12 15.7 0 653.33 244.35 41854 +2015 271 17 9.7 14.99 0 652.5 283.79 41647 +2015 272 17.3 9 15.02 0 702.5 314.15 41440 +2015 273 14.8 9.6 13.37 0 580 199.52 41234 +2015 274 17.5 5.8 14.28 0 627.5 327.36 41028 +2015 275 18.9 2.4 14.36 0 718.33 352.29 40822 +2015 276 21.8 6.2 17.51 0 593.64 295.89 40617 +2015 277 22.8 6.9 18.43 0.02 850 294.1 40412 +2015 278 21.7 11.9 19 0 569.09 290 40208 +2015 279 20.3 8 16.92 0 432.73 238.78 40003 +2015 280 17 13.5 16.04 0.51 97.27 60.31 39800 +2015 281 16.6 12.3 15.42 0.15 215.45 110 39597 +2015 282 16.5 12.4 15.37 0.07 142.73 87.61 39394 +2015 283 14.6 9.5 13.2 1.37 175.45 65.52 39192 +2015 284 10.1 5.3 8.78 1.98 76.36 55.84 38991 +2015 285 8.5 2.9 6.96 0 341.82 211.38 38790 +2015 286 8 4.6 7.06 0.99 111.82 61.27 38590 +2015 287 9.5 7.8 9.03 2.66 37.27 45.13 38391 +2015 288 11.8 8.1 10.78 2.43 213.6 26.14 38193 +2015 289 13.9 10.8 13.05 0.37 90 151.87 37995 +2015 290 11.6 5.5 9.92 0.02 207.27 165.79 37799 +2015 291 12.4 5.7 10.56 2.91 105.45 128.58 37603 +2015 292 9.4 7.1 8.77 0 77.27 33.42 37408 +2015 293 12 5.4 10.18 0 363.64 199.55 37214 +2015 294 12.2 2 9.39 0 307.27 128.38 37022 +2015 295 12.7 4.2 10.36 0 398.18 239.09 36830 +2015 296 14.5 1.6 10.95 0 353.64 176.45 36640 +2015 297 15.3 2.5 11.78 0 370.91 343.5 36451 +2015 298 14.5 1.6 10.95 0 292.73 271.87 36263 +2015 299 13.8 4.4 11.22 0 322.73 247.61 36076 +2015 300 14.3 6.9 12.27 0 336.36 295.64 35891 +2015 301 9.2 4 7.77 0.03 95 45.87 35707 +2015 302 11.1 7.2 10.03 0.06 76 79.41 35525 +2015 303 16.3 6.3 13.55 0 522 309.39 35345 +2015 304 14.8 0 10.73 0 409 296.27 35166 +2015 305 12.2 0.9 9.09 0 533 320.67 34988 +2015 306 12 -2.4 8.04 0 453 286.85 34813 +2015 307 13.1 -1.8 9 0 430 296.76 34639 +2015 308 10.6 -0.2 7.63 0 130.25 232.18 34468 +2015 309 13.8 -2 9.46 0 313 243.09 34298 +2015 310 15 -0.5 10.74 0 336.67 265.97 34130 +2015 311 15.9 3.3 12.44 0 461.11 151.71 33964 +2015 312 21 6.5 17.01 0 744.44 242.98 33801 +2015 313 14.4 3.6 11.43 0 363.33 158.33 33640 +2015 314 21.8 10.9 18.8 0 1054.44 161.6 33481 +2015 315 21.9 6.6 17.69 0 886.67 226.28 33325 +2015 316 18.1 3.2 14 0 516.67 243.33 33171 +2015 317 15.6 4 12.41 0 393.33 234.47 33019 +2015 318 14.7 3.8 11.7 0 472.22 176.65 32871 +2015 319 12.2 3.8 9.89 0 398.89 102.75 32725 +2015 320 19.6 6 15.86 0 882.22 226.73 32582 +2015 321 11.6 1.4 8.79 0 288.89 136.88 32441 +2015 322 18.1 7.4 15.16 0 703.33 239.88 32304 +2015 323 16.3 0.3 11.9 0 336.67 236.04 32170 +2015 324 12 6.7 10.54 0.48 410 95.77 32039 +2015 325 11 4.4 9.19 0.03 227.78 33.09 31911 +2015 326 7.2 2.7 5.96 0 271.11 88.57 31786 +2015 327 5.7 -2.8 3.36 0 171.11 221.62 31665 +2015 328 4.8 -1.8 2.98 0 210 155.64 31547 +2015 329 2.2 -2.6 0.88 0.03 138.89 57.98 31433 +2015 330 3.8 -0.2 2.7 0 131.11 92.65 31322 +2015 331 4.1 2.8 3.74 0 216.67 73.68 31215 +2015 332 5.4 -1.7 3.45 0 186.67 160.38 31112 +2015 333 9.9 -2.8 6.41 0 398.89 192.1 31012 +2015 334 12.7 0.2 9.26 0 537.78 140.22 30917 +2015 335 15.7 4.7 12.67 0.06 747.78 149.59 30825 +2015 336 11.1 4.8 9.37 0 220 167.15 30738 +2015 337 9 0.7 6.72 0 45.56 58.55 30654 +2015 338 7.6 3.1 6.36 0 120 34.65 30575 +2015 339 9.7 0.2 7.09 0.01 74.44 198.1 30500 +2015 340 3.3 2.1 2.97 0 45.4 31.62 30430 +2015 341 2.7 0.1 1.99 0 89.54 71.44 30363 +2015 342 2.2 0.3 1.68 0.08 65.19 30.78 30301 +2015 343 3 1.4 2.56 0.02 1.11 36.84 30244 +2015 344 8.7 0.3 6.39 0 411.11 177.1 30191 +2015 345 6.1 -3.3 3.51 0 203.33 212.82 30143 +2015 346 2.1 -2.3 0.89 0 5.56 65.28 30099 +2015 347 3.2 -3.7 1.3 0 14.44 115.84 30060 +2015 348 6.3 -2.8 3.8 0.02 155 123.68 30025 +2015 349 4.1 0.9 3.22 0.02 8.75 47.46 29995 +2015 350 6.1 1 4.7 0 77.5 109.61 29970 +2015 351 3.4 1.8 2.96 0.01 59.96 36.08 29950 +2015 352 2.3 0.3 1.75 0 68.79 57.72 29934 +2015 353 8.8 0.6 6.54 0 51.25 147.56 29924 +2015 354 3.9 -0.1 2.8 0.01 140.58 35.27 29918 +2015 355 2.9 1.2 2.43 0 61.48 41.31 29916 +2015 356 9.6 -0.5 6.82 0 168.75 204.21 29920 +2015 357 3.7 -1.2 2.35 0 52.5 167.86 29928 +2015 358 9.5 -1.1 6.59 0 246.25 155.33 29941 +2015 359 8.8 1.4 6.77 0 108.75 183.58 29959 +2015 360 8.3 -2.8 5.25 0 297.5 218.81 29982 +2015 361 1.6 -2.3 0.53 0 7.5 99.17 30009 +2015 362 8.5 -4 5.06 0 172.5 215.71 30042 +2015 363 3.3 -1.4 2.01 0 38.75 42.53 30078 +2015 364 3.4 -2.4 1.8 0 212.5 133.39 30120 +2015 365 -1.4 -8.4 -3.33 0 85 103.83 30166 +2016 1 1.6 -6.7 -0.68 0 117.5 78.08 30217 +2016 2 -1 -6.2 -2.43 0.05 40 13.87 30272 +2016 3 -3.9 -5.9 -4.45 0 68.75 65.89 30331 +2016 4 -5.9 -7.6 -6.37 0.1 60 67.32 30396 +2016 5 -3.4 -7.6 -4.55 0.07 30 70.03 30464 +2016 6 -0.7 -4.2 -1.66 0.32 20 41.37 30537 +2016 7 2.5 -7.4 -0.22 0 11.25 187.43 30614 +2016 8 3.3 -2.3 1.76 0 26.25 95.98 30695 +2016 9 2.2 0.2 1.65 0.72 68.35 64.91 30781 +2016 10 3.5 0.4 2.65 0 110.1 91.67 30870 +2016 11 12.3 -0.6 8.75 2.32 277.5 68.45 30964 +2016 12 10.1 -2.7 6.58 0 235.56 184.35 31061 +2016 13 9.5 -3 6.06 0 295.56 148.13 31162 +2016 14 8.4 -2.9 5.29 0 423.33 140.42 31268 +2016 15 5.2 -4.3 2.59 0 218.89 64.07 31376 +2016 16 3.7 -5.5 1.17 0 200 155.24 31489 +2016 17 2.1 -4 0.42 0 160 151.44 31605 +2016 18 1.3 -8.8 -1.48 0 235.56 219.53 31724 +2016 19 1.2 -10.6 -2.04 0 157.78 174.89 31847 +2016 20 3.7 -9.8 -0.01 0 183 216.13 31974 +2016 21 2.6 -9.8 -0.81 0 186 217.84 32103 +2016 22 3.4 -10.7 -0.48 0 203 265.35 32236 +2016 23 -1.6 -11.1 -4.21 0.22 95 63.07 32372 +2016 24 6.9 -7.9 2.83 0 274 202.84 32510 +2016 25 2.8 -3 1.2 0.02 111 86.98 32652 +2016 26 12.6 -2.4 8.47 0 427 198.17 32797 +2016 27 10.7 -2.8 6.99 0 324 192.18 32944 +2016 28 16.7 0 12.11 0 555 232.58 33094 +2016 29 12.6 -2.4 8.47 0 298 190.33 33247 +2016 30 9.6 -3.7 5.94 0 216 168.17 33402 +2016 31 7.4 -0.8 5.15 0.07 250 52.97 33559 +2016 32 14.8 2.6 11.45 0 401 116.01 33719 +2016 33 9.3 0.5 6.88 0 164 71.13 33882 +2016 34 8 -0.6 5.63 2.03 23 51.85 34046 +2016 35 11.1 -0.6 7.88 0 452 210.32 34213 +2016 36 9.6 -2.9 6.16 0 331 271.79 34382 +2016 37 12.7 -2 8.66 0 442 268.28 34552 +2016 38 13.5 -1.9 9.27 0 490 175.7 34725 +2016 39 14.9 2.7 11.55 0 540 125.89 34900 +2016 40 15 -1.1 10.57 2.11 531 216.95 35076 +2016 41 9.6 0.4 7.07 1.47 46 83.15 35254 +2016 42 11.8 -2.9 7.76 0 436 261.77 35434 +2016 43 5.7 -4.3 2.95 1.12 163 121.33 35615 +2016 44 10 -1.3 6.89 0.64 60 82.88 35798 +2016 45 11 -2 7.43 0.76 191 161.57 35983 +2016 46 7.6 3.1 6.36 1.14 150 48.65 36169 +2016 47 6.7 3.2 5.74 0.1 238 77.59 36356 +2016 48 4.5 2.5 3.95 0.04 26 40.01 36544 +2016 49 7.1 3.4 6.08 1.16 160.77 43.01 36734 +2016 50 7.5 0.8 5.66 0.67 73 89.77 36925 +2016 51 11 -0.4 7.87 0.14 168 241.89 37117 +2016 52 17.1 3.5 13.36 0.08 558 200.28 37310 +2016 53 18.4 3.6 14.33 0.03 624 254.54 37505 +2016 54 15.9 4.3 12.71 0.15 510 113.52 37700 +2016 55 13.1 -1.7 9.03 0 545.45 292.9 37896 +2016 56 7.4 -2.9 4.57 0.14 187.27 124.15 38093 +2016 57 8.5 0.8 6.38 0 359.09 163.63 38291 +2016 58 10.8 -4.4 6.62 0 374.55 294.78 38490 +2016 59 11.4 0.8 8.48 0.17 174.55 133.7 38689 +2016 60 10.1 4 8.42 0.67 52.73 65.79 38890 +2016 61 11.6 3.2 9.29 0 249.09 140.02 39091 +2016 62 12.6 -3.3 8.23 0.27 258.33 222.24 39292 +2016 63 5.2 2.2 4.38 0.84 84.17 70.76 39495 +2016 64 10.4 -1.4 7.16 0 421.67 313.43 39697 +2016 65 12.1 -1.6 8.33 0 470.83 223.25 39901 +2016 66 14.7 2.1 11.23 0.45 320.83 183.92 40105 +2016 67 5.2 1.3 4.13 0.64 78.33 64.25 40309 +2016 68 10.9 0.4 8.01 0 200.83 198.38 40514 +2016 69 12.4 -2.4 8.33 0 289.17 358.05 40719 +2016 70 14 -2.1 9.57 0.06 389.17 370.48 40924 +2016 71 8.6 5.7 7.8 0.14 220 103.12 41130 +2016 72 9.4 4 7.92 0.03 255.83 133.56 41336 +2016 73 11 3.5 8.94 0 169.17 137.24 41543 +2016 74 10.9 -0.8 7.68 0 390 419.01 41749 +2016 75 7.3 0.6 5.46 0.42 170 104.76 41956 +2016 76 10 0.9 7.5 0 149.17 172.05 42163 +2016 77 15.2 -1.8 10.52 0 458.33 398.82 42370 +2016 78 17.1 -3.5 11.44 0 517.5 430.15 42578 +2016 79 12.1 1.9 9.29 0 361.67 400.56 42785 +2016 80 17.5 -0.9 12.44 0 554.17 427.28 42992 +2016 81 16.4 2.2 12.49 0 395.42 272.06 43200 +2016 82 14 0.8 10.37 0.06 453.33 258.8 43407 +2016 83 11.7 2.8 9.25 0 372.5 177.39 43615 +2016 84 12.2 -0.5 8.71 0.02 404.17 301.19 43822 +2016 85 12.4 -2.8 8.22 0 524.17 159.64 44029 +2016 86 12.7 1.3 9.56 0.08 301.67 188.23 44236 +2016 87 18.1 -2.3 12.49 0 580.83 406.22 44443 +2016 88 19.3 -0.1 13.97 0 505.83 349.6 44650 +2016 89 18.6 1.1 13.79 0.98 502.5 254.7 44857 +2016 90 21.1 1.2 15.63 0.01 552.5 299.31 45063 +2016 91 25.4 1.5 18.83 0 1018.33 416.09 45270 +2016 92 21.9 8 18.08 0 785 266.57 45475 +2016 93 17.9 1.6 13.42 0 668.46 330.75 45681 +2016 94 23.6 -0.2 17.06 0 1123.08 422.09 45886 +2016 95 26.4 7.2 21.12 0 1403.08 385.12 46091 +2016 96 27 6 21.23 0 1559.23 383.02 46295 +2016 97 21.8 6.1 17.48 0 950 414.94 46499 +2016 98 22.6 4.3 17.57 0 775.71 365.91 46702 +2016 99 12.3 8.3 11.2 0.53 281.43 85.15 46905 +2016 100 14.5 7.2 12.49 0 355 312.41 47107 +2016 101 16.6 3.5 13 0 520.71 359.69 47309 +2016 102 20.6 2.7 15.68 0 636.43 480.94 47510 +2016 103 22.4 1.8 16.73 0 555 448.65 47710 +2016 104 25.9 3.4 19.71 0 1005.71 419.4 47910 +2016 105 16.5 3.1 12.82 0.04 442.14 127.63 48108 +2016 106 22.1 1 16.3 0 987.14 423.15 48306 +2016 107 24.5 2.7 18.5 0 1390 502.56 48504 +2016 108 24.3 11.9 20.89 0 1318.57 358.11 48700 +2016 109 15.3 8.9 13.54 0 403.57 316.88 48895 +2016 110 17.5 7.9 14.86 0 782.86 387.17 49089 +2016 111 18.9 0.9 13.95 0 847.86 362.16 49282 +2016 112 23.3 -0.8 16.67 0 1026.43 502.52 49475 +2016 113 22.5 1.4 16.7 0 1015.71 495.92 49666 +2016 114 24.1 8 19.67 0.37 882.14 370.8 49855 +2016 115 10.5 4.9 8.96 0 501.43 224.78 50044 +2016 116 13.2 -1.6 9.13 0 540.71 346.18 50231 +2016 117 18.8 -2.3 13 0 797.86 470.69 50417 +2016 118 8.4 1.2 6.42 0.87 125 64.02 50601 +2016 119 16.7 -1.3 11.75 0 202.86 167.38 50784 +2016 120 21 -1.9 14.7 0 672.14 560.34 50966 +2016 121 23.1 -0.8 16.53 0 818.57 507.68 51145 +2016 122 15.4 3.5 12.13 1.56 130.71 109.84 51324 +2016 123 17.2 9.8 15.16 0.73 88.57 100.94 51500 +2016 124 20.5 10.7 17.81 0.38 635.71 367.39 51674 +2016 125 16.8 9.2 14.71 0 449.29 145.78 51847 +2016 126 20.5 8.2 17.12 0 463.33 445.07 52018 +2016 127 25.2 6.3 20 0 872 506.57 52187 +2016 128 26.7 3.8 20.4 0 990 499.78 52353 +2016 129 23.6 5.5 18.62 0 688.67 429.75 52518 +2016 130 24.6 4.6 19.1 0 779.33 441.85 52680 +2016 131 21.6 5.8 17.26 0 404 277.63 52840 +2016 132 18.3 12.3 16.65 1.17 244 127.06 52998 +2016 133 17.5 12.5 16.13 1.58 58 67.18 53153 +2016 134 24 9.8 20.09 1.26 566.67 379.74 53306 +2016 135 22.4 11.6 19.43 0.82 385.33 213.2 53456 +2016 136 16.8 2.2 12.79 0.04 529.33 243.66 53603 +2016 137 18.6 -0.1 13.46 0.12 634.67 409.66 53748 +2016 138 19.5 3.1 14.99 0 640.67 399.72 53889 +2016 139 22.7 6.6 18.27 0 724 320.76 54028 +2016 140 24.8 3.7 19 1.26 852.67 493.58 54164 +2016 141 23.5 6.9 18.93 0 660.67 388.99 54297 +2016 142 27 4.8 20.9 0 1128 493.64 54426 +2016 143 27.2 6.9 21.62 0 1336.88 530.56 54552 +2016 144 28 7.1 22.25 2.18 1279.38 517.57 54675 +2016 145 22.3 10.7 19.11 0 256.88 176.13 54795 +2016 146 24.3 8.1 19.84 0 791.88 483.84 54911 +2016 147 26.9 8.2 21.76 0 725 457.54 55023 +2016 148 28.4 9.7 23.26 0 1168.75 443.73 55132 +2016 149 30 15.5 26.01 0 1418.75 440.04 55237 +2016 150 30.5 12.6 25.58 0.21 1441.25 457.48 55339 +2016 151 27.8 12.3 23.54 0 1038.75 517.19 55436 +2016 152 28.8 8.9 23.33 0.04 1035.63 515.15 55530 +2016 153 26.5 9.9 21.93 0 850.63 396.67 55619 +2016 154 28.9 11.2 24.03 0 566.25 359.04 55705 +2016 155 28.5 12.2 24.02 0 730 366.35 55786 +2016 156 28.3 11.1 23.57 0 718.75 354.04 55863 +2016 157 27.1 11.2 22.73 0.83 392.5 214.89 55936 +2016 158 28.7 9.8 23.5 0 1026.25 484.81 56004 +2016 159 25.7 8.5 20.97 0 1216.25 500.22 56068 +2016 160 29.1 7.6 23.19 0 1136.88 464.7 56128 +2016 161 27.1 12.3 23.03 0.06 862.5 296.58 56183 +2016 162 26.5 12 22.51 0.35 427.5 300.49 56234 +2016 163 28.2 10.3 23.28 0.96 460 334.37 56280 +2016 164 25 14.6 22.14 0 431.25 246.5 56321 +2016 165 26.4 11.4 22.27 0 620.63 324.73 56358 +2016 166 28 10.6 23.22 1.23 703.75 352.75 56390 +2016 167 26.4 13.1 22.74 0.94 325 260.68 56418 +2016 168 29.6 13.4 25.15 0 1208.75 411.78 56440 +2016 169 28.6 11.7 23.95 0 1406.88 444.83 56458 +2016 170 29.8 9.8 24.3 0 977.5 477.03 56472 +2016 171 23.9 12.6 20.79 2.13 564.38 207.41 56480 +2016 172 24.5 11.8 21.01 2.54 298.13 285.77 56484 +2016 173 31.7 9.8 25.68 0 996.25 446.39 56482 +2016 174 32.5 12.5 27 0 1281.88 453.73 56476 +2016 175 34 14.2 28.56 0 1375.63 469.98 56466 +2016 176 35 16.8 29.99 0 1498.13 448.36 56450 +2016 177 33.6 18.4 29.42 0.08 1285.63 457.85 56430 +2016 178 29.2 17.3 25.93 0 1021.88 419.64 56405 +2016 179 24.1 11.6 20.66 0.16 738.75 204.72 56375 +2016 180 27.4 8.4 22.17 0 1309.38 504.8 56341 +2016 181 33.2 9.8 26.77 0 1393.13 478.93 56301 +2016 182 32 12.9 26.75 0 1456.25 449.29 56258 +2016 183 32.2 14.2 27.25 0 1396.88 409.72 56209 +2016 184 33.4 13.9 28.04 0 1361.25 447.22 56156 +2016 185 22.3 9.6 18.81 0.42 861.88 149.78 56099 +2016 186 29.5 7.9 23.56 0 1300.63 473.12 56037 +2016 187 31.1 11.3 25.66 0 1380 454.58 55971 +2016 188 30.7 14.2 26.16 0 1168.13 382.92 55900 +2016 189 29.4 9.4 23.9 0 1330.63 407.42 55825 +2016 190 30.7 11.1 25.31 0 1268.75 496.23 55746 +2016 191 32.6 14.5 27.62 0 1474.38 360.6 55663 +2016 192 34.4 13.7 28.71 0 1576.88 451.42 55575 +2016 193 35.5 14 29.59 0 1832.5 476.97 55484 +2016 194 34.7 18.6 30.27 1.51 1649.38 476.63 55388 +2016 195 28.9 17.5 25.77 0.5 807.5 392.72 55289 +2016 196 25.8 13.2 22.34 3.03 850 369.03 55186 +2016 197 23.4 10.4 19.82 0 875.63 332.58 55079 +2016 198 16.5 13.7 15.73 0.09 468.75 91.49 54968 +2016 199 25.4 13.7 22.18 0 850 205.36 54854 +2016 200 31.2 14.6 26.63 0 1181.25 406.56 54736 +2016 201 29.8 14.9 25.7 0 1271.88 462.85 54615 +2016 202 29.8 14.6 25.62 0 1181.25 440.37 54490 +2016 203 33.4 12.3 27.6 0.05 1294.38 468.95 54362 +2016 204 31.6 15.7 27.23 1.53 1055.63 456.12 54231 +2016 205 33 18.3 28.96 0 833.75 347.58 54097 +2016 206 31.5 18.3 27.87 0 1004.38 428.81 53960 +2016 207 28.4 17.7 25.46 0.72 460.63 192.87 53819 +2016 208 28.7 15.7 25.13 1.27 574.38 296.05 53676 +2016 209 32.7 15.6 28 0.05 801.88 402.05 53530 +2016 210 29.2 18.3 26.2 1.64 655.33 306.3 53382 +2016 211 20.4 14.8 18.86 0.08 1286.43 423.87 53230 +2016 212 24.6 16 22.23 0 863.57 467.18 53076 +2016 213 26.6 9 21.76 0.02 1456.86 412.35 52920 +2016 214 26.1 16.2 23.38 0.4 1032.42 221.14 52761 +2016 215 28.9 17.1 25.66 0 1343.41 333.87 52600 +2016 216 31.2 16.2 27.07 0 1739.42 395.23 52437 +2016 217 32.2 18.1 28.32 0 1774.71 375.26 52271 +2016 218 34 17.3 29.41 0 2126.43 412.71 52103 +2016 219 35.2 18.1 30.5 0 2289.18 413.27 51934 +2016 220 35.4 18.1 30.64 0 2325.51 414.99 51762 +2016 221 35.3 16.8 30.21 0 2382.18 431.1 51588 +2016 222 34.4 15.2 29.12 0 2306.29 443.13 51413 +2016 223 34.3 15.2 29.05 0 2289.43 441.83 51235 +2016 224 36.1 15.4 30.41 0 2593.88 449.07 51057 +2016 225 36.2 15.4 30.48 0 2611.94 445.66 50876 +2016 226 35.8 16.6 30.52 0 2482.59 425.37 50694 +2016 227 34.4 17.2 29.67 0.02 2201.34 300.62 50510 +2016 228 30.2 18.6 27.01 1.8 1424.39 229.15 50325 +2016 229 26.1 17.9 23.84 0.21 905.14 174.18 50138 +2016 230 22.8 16.3 21.01 0 635.34 194.76 49951 +2016 231 23.7 13.9 21 0 899.23 286.89 49761 +2016 232 19 15.1 17.93 0.02 338.11 95.8 49571 +2016 233 23.3 11.8 20.14 0 973.7 338.55 49380 +2016 234 24.4 10.2 20.49 0 1165.89 390.53 49187 +2016 235 24.1 12.4 20.88 0.04 1028.76 255.28 48993 +2016 236 27.5 12.1 23.27 0 1442.56 398.39 48798 +2016 237 23.2 16.3 21.3 0.26 680.01 159.34 48603 +2016 238 26.9 10.2 22.31 0 1448.87 415.57 48406 +2016 239 29.3 12.5 24.68 0 1658.09 407.33 48208 +2016 240 32.7 16.2 28.16 0 1974.31 386.07 48010 +2016 241 33.6 14.3 28.29 0 2214.82 411.59 47811 +2016 242 34.7 14 29.01 0 2408.91 416.6 47611 +2016 243 34 14.9 28.75 0 2253.32 399.18 47410 +2016 244 34 15.3 28.86 0 2234.4 389.27 47209 +2016 245 28.2 14.1 24.32 0.06 1432.91 253.17 47007 +2016 246 25.2 15.7 22.59 0.31 956.17 186.49 46805 +2016 247 23.4 15.1 21.12 1.41 788.44 167.82 46601 +2016 248 19.3 13.9 17.82 0.84 451.65 116.95 46398 +2016 249 18.6 11.5 16.65 0.36 537.6 155.11 46194 +2016 250 20 6.1 16.18 0.02 896.82 269.97 45989 +2016 251 20.3 12.6 18.18 0 628.48 223.55 45784 +2016 252 20.2 5.2 16.07 0 941.83 378.74 45579 +2016 253 20 10.6 17.41 0.05 710.7 203.8 45373 +2016 254 20.7 12.2 18.36 0.46 690.03 188.69 45167 +2016 255 24.1 7.2 19.45 0 1243.85 396.05 44961 +2016 256 24.3 8.4 19.93 0 1224.87 382.41 44755 +2016 257 27.7 14.5 24.07 0 1345.02 332.8 44548 +2016 258 26.1 13.6 22.66 0 1194.71 322.7 44341 +2016 259 28 18.6 25.41 0 1103.78 249.49 44134 +2016 260 32.1 21.1 29.08 0 1521.14 265.25 43927 +2016 261 27.4 15.4 24.1 0.01 1251.93 223.75 43719 +2016 262 23.2 16.5 21.36 0.1 664.82 138.37 43512 +2016 263 21.8 15 19.93 0 622.62 190.32 43304 +2016 264 20.4 7.8 16.93 0 871 320.69 43097 +2016 265 22.1 3.9 17.09 0 1141.13 379.89 42890 +2016 266 23.1 6.5 18.54 0.34 1165.82 269.61 42682 +2016 267 17.7 13.2 16.46 0.64 355.05 95.64 42475 +2016 268 17 12.3 15.71 3.42 353.85 102.07 42268 +2016 269 16.8 13 15.76 0.04 292.11 85.47 42060 +2016 270 17.1 12 15.7 0 380.68 152.72 41854 +2016 271 17 9.7 14.99 0 500.72 217.44 41647 +2016 272 17.3 9 15.02 0 558.86 246.12 41440 +2016 273 14.8 9.6 13.37 0 338.75 169.26 41234 +2016 274 17.5 5.8 14.28 0 705.41 316.58 41028 +2016 275 18.9 2.4 14.36 0 909.83 358.47 40822 +2016 276 21.8 6.2 17.51 0 1052.48 341.56 40617 +2016 277 22.8 6.9 18.43 0.02 1124.5 252.18 40412 +2016 278 21.7 11.9 19 0 804.39 254.28 40208 +2016 279 20.3 8 16.92 0 854.35 293.06 40003 +2016 280 17 13.5 16.04 0.51 275.04 77.88 39800 +2016 281 16.6 12.3 15.42 0.15 321 94.54 39597 +2016 282 16.5 12.4 15.37 0.07 306.52 92.02 39394 +2016 283 14.6 9.5 13.2 1.37 329.59 114.96 39192 +2016 284 10.1 5.3 8.78 1.98 240.16 111.73 38991 +2016 285 8.5 2.9 6.96 0 246.49 176.15 38790 +2016 286 8 4.6 7.06 0.99 157.95 85.43 38590 +2016 287 9.5 7.8 9.03 2.66 92.27 48.11 38391 +2016 288 11.8 8.1 10.78 2.43 213.6 93.33 38193 +2016 289 13.9 10.8 13.05 0.37 206.93 78.26 37995 +2016 290 11.6 5.5 9.92 0.02 318.11 147.57 37799 +2016 291 12.4 5.7 10.56 2.91 358.45 158.09 37603 +2016 292 9.4 7.1 8.77 0 121.3 82.67 37408 +2016 293 12 5.4 10.18 0 346.02 205.66 37214 +2016 294 12.2 2 9.39 0 473.01 266.57 37022 +2016 295 12.7 4.2 10.36 0 432.98 242.63 36830 +2016 296 14.5 1.6 10.95 0 622.36 282.87 36640 +2016 297 15.3 2.5 11.78 0 650.53 275.89 36451 +2016 298 14.5 1.6 10.95 0 622.36 272.37 36263 +2016 299 13.8 4.4 11.22 0 494.76 234.81 36076 +2016 300 14.3 6.9 12.27 0 431.94 197.75 35891 +2016 301 9.2 4 7.77 0.03 242.61 114.16 35707 +2016 302 11.1 7.2 10.03 0.06 214.36 86.8 35525 +2016 303 16.3 6.3 13.55 0 597.38 226.48 35345 +2016 304 14.8 0 10.73 0 677.96 258.95 35166 +2016 305 12.2 0.9 9.09 0 502.83 238.99 34988 +2016 306 12 -2.4 8.04 0 563.19 253.72 34813 +2016 307 13.1 -1.8 9 0 612.44 251.48 34639 +2016 308 10.6 -0.2 7.63 0 443.67 227.08 34468 +2016 309 13.8 -2 9.46 0 655.84 246.64 34298 +2016 310 15 -0.5 10.74 0 700.46 239.82 34130 +2016 311 15.9 3.3 12.44 0 668.73 219.95 33964 +2016 312 21 6.5 17.01 0 970.69 219.42 33801 +2016 313 14.4 3.6 11.43 0 559.62 197.43 33640 +2016 314 21.8 10.9 18.8 0 866.05 183.04 33481 +2016 315 21.9 6.6 17.69 0 1049.13 209.59 33325 +2016 316 18.1 3.2 14 0 829.66 207.91 33171 +2016 317 15.6 4 12.41 0 627.19 183.09 33019 +2016 318 14.7 3.8 11.7 0 572.95 173.26 32871 +2016 319 12.2 3.8 9.89 0 416.71 142.38 32725 +2016 320 19.6 6 15.86 0 866.41 182.52 32582 +2016 321 11.6 1.4 8.79 0 455.95 157.94 32441 +2016 322 18.1 7.4 15.16 0 692.55 152.56 32304 +2016 323 16.3 0.3 11.9 0 768.45 188.86 32170 +2016 324 12 6.7 10.54 0.48 291.69 62.9 32039 +2016 325 11 4.4 9.19 0.03 325.77 77.16 31911 +2016 326 7.2 2.7 5.96 0 190.73 74.05 31786 +2016 327 5.7 -2.8 3.36 0 280.23 131.7 31665 +2016 328 4.8 -1.8 2.98 0 221.48 107.32 31547 +2016 329 2.2 -2.6 0.88 0.03 146.46 60.86 31433 +2016 330 3.8 -0.2 2.7 0 139.68 67.75 31322 +2016 331 4.1 2.8 3.74 0 51.51 28.87 31215 +2016 332 5.4 -1.7 3.45 0 242.71 111.71 31112 +2016 333 9.9 -2.8 6.41 0 464.41 161.6 31012 +2016 334 12.7 0.2 9.26 0 548.35 156.99 30917 +2016 335 15.7 4.7 12.67 0.06 611.55 106.65 30825 +2016 336 11.1 4.8 9.37 0 316.41 95.66 30738 +2016 337 9 0.7 6.72 0 339.66 122.88 30654 +2016 338 7.6 3.1 6.36 0 195.5 72.98 30575 +2016 339 9.7 0.2 7.09 0.01 387.8 101.97 30500 +2016 340 3.3 2.1 2.97 0 45.4 27.14 30430 +2016 341 2.7 0.1 1.99 0 89.54 48.06 30363 +2016 342 2.2 0.3 1.68 0.08 65.19 28.62 30301 +2016 343 3 1.4 2.56 0.02 58.46 25.48 30244 +2016 344 8.7 0.3 6.39 0 336.09 133.47 30191 +2016 345 6.1 -3.3 3.51 0 306.86 144.76 30143 +2016 346 2.1 -2.3 0.89 0 135.57 85.05 30099 +2016 347 3.2 -3.7 1.3 0 206.36 123.15 30060 +2016 348 6.3 -2.8 3.8 0.02 304.47 107.91 30025 +2016 349 4.1 0.9 3.22 0.02 117.58 47.96 29995 +2016 350 6.1 1 4.7 0 197.17 98.57 29970 +2016 351 3.4 1.8 2.96 0.01 59.96 27.51 29950 +2016 352 2.3 0.3 1.75 0 68.79 45.4 29934 +2016 353 8.8 0.6 6.54 0 332.69 141.84 29924 +2016 354 3.9 -0.1 2.8 0.01 140.58 65.14 29918 +2016 355 2.9 1.2 2.43 0 61.48 40.98 29916 +2016 356 9.6 -0.5 6.82 0 400.42 154.13 29920 +2016 357 3.7 -1.2 2.35 0 164.01 104.34 29928 +2016 358 9.5 -1.1 6.59 0 409.69 156.73 29941 +2016 359 8.8 1.4 6.77 0 309.62 133.95 29959 +2016 360 8.3 -2.8 5.25 0 390.15 158.76 29982 +2016 361 1.6 -2.3 0.53 0 118.72 83.23 30009 +2016 362 8.5 -4 5.06 0 421.47 164.5 30042 +2016 363 3.3 -1.4 2.01 0 154.57 99.03 30078 +2016 364 3.4 -2.4 1.8 0 183.68 119.63 30120 +2016 365 -1.4 -8.4 -3.33 0 153.65 139.92 30166 diff --git a/RBBGCMuso/inst/examples/hhs/hhs.soi b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.soi similarity index 98% rename from RBBGCMuso/inst/examples/hhs/hhs.soi rename to RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.soi index 273700d..e313496 100644 --- a/RBBGCMuso/inst/examples/hhs/hhs.soi +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/hhs.soi @@ -1,64 +1,64 @@ -SOILPROP FILE - hhs muso6 ----------------------------------------------------------------------------------------- -NITROGEN AND DECOMPOSITION PARAMETERS -0.1 (prop.) denitrification rate per g of CO2 respiration of SOM -0.2 (prop.) nitrification coefficient 1 -0.1 (prop.) nitrification coefficient 2 -0.02 (prop.) coefficient of N2O emission of nitrification -0.1 (prop.) NH4 mobilen proportion -1.0 denitrification related N2/N2O ratio multiplier (soil texture effect) -10 (m) e-folding depth of decomposition rate's depth scalar -0.002 (prop.) fraction of dissolved part of SOIL1 organic matter -0.002 (prop.) fraction of dissolved part of SOIL2 organic matter -0.002 (prop.) fraction of dissolved part of SOIL3 organic matter -0.002 (prop.) fraction of dissolved part of SOIL4 organic matter -0.1 (prop.) minimum WFPS for scalar of nitrification calculation -0.45 (prop.) lower optimum WFPS for scalar of nitrification calculation -0.55 (prop.) higher optimum WFPS for scalar of nitrification calculation -0.2 (prop.) minimum value for saturated WFPS scalar of nitrification calculation -10 (ppm) C:N ratio of recaltirant SOM (slowest) ----------------------------------------------------------------------------------------- -RATE SCALARS -0.39 (DIM) respiration fractions for fluxes between compartments (l1s1) -0.55 (DIM) respiration fractions for fluxes between compartments (l2s2) -0.29 (DIM) respiration fractions for fluxes between compartments (l4s3) -0.28 (DIM) respiration fractions for fluxes between compartments (s1s2) -0.46 (DIM) respiration fractions for fluxes between compartments (s2s3) -0.55 (DIM) respiration fractions for fluxes between compartments (s3s4) -0.7 (DIM) rate constant scalar of labile litter pool -0.07 (DIM) rate constant scalar of cellulose litter pool -0.014 (DIM) rate constant scalar of lignin litter pool -0.07 (DIM) rate constant scalar of fast microbial recycling pool -0.014 (DIM) rate constant scalar of medium microbial recycling pool -0.0014 (DIM) rate constant scalar of slow microbial recycling pool -0.0001 (DIM) rate constant scalar of recalcitrant SOM (humus) pool -0.001 (DIM) rate constant scalar of physical fragmentation of coarse woody debris ----------------------------------------------------------------------------------------- -CH4 PARAMETERS -212.5 (DIM) soil CH4 emission bulk density dependence parameter1 -1.81 (DIM) soil CH4 emission bulk density dependence parameter2 --1.353 (DIM) soil CH4 emission soil water content dependence parameter1 -0.2 (DIM) soil CH4 emission soil water content dependence parameter2 -1.781 (DIM) soil CH4 emission soil water content dependence parameter3 -6.786 (DIM) soil CH4 emission soil water content dependence parameter4 -0.010 (DIM) soil CH4 emission soil temperature dependence parameter1 ----------------------------------------------------------------------------------------- -SOIL PARAMETERS -2 (m) depth of soil -6 (mm) limit of first stage evaporation -5.00 (mm) maximum height of pond water -1 (dimless) curvature of soil stress function --9999 (dimless) runoff curve number (-9999: no , model estimation) -107 (s/m) aerodynamic resistance (Wallace and Holwill, 1997) ----------------------------------------------------------------------------------------- -SOIL COMPOSITION AND CHARACTERISTIC VALUES (-9999: no measured data) -30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 (%) sand percentage by volume in rock-free soil -50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 (%) silt percentage by volume in rock-free soil -7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 (dimless) soil pH (dimless) measured runoff curve number --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (g/cm3) bulk density --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at saturation --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at field capacity --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at wilting point --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at hygroscopic water content --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (dimless) drainage coefficient --9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (cm/day) hydraulic condictivity at saturation +SOILPROP FILE - hhs muso6 +---------------------------------------------------------------------------------------- +NITROGEN AND DECOMPOSITION PARAMETERS +0.1 (prop.) denitrification rate per g of CO2 respiration of SOM +0.2 (prop.) nitrification coefficient 1 +0.1 (prop.) nitrification coefficient 2 +0.02 (prop.) coefficient of N2O emission of nitrification +0.1 (prop.) NH4 mobilen proportion +1.0 denitrification related N2/N2O ratio multiplier (soil texture effect) +10 (m) e-folding depth of decomposition rate's depth scalar +0.002 (prop.) fraction of dissolved part of SOIL1 organic matter +0.002 (prop.) fraction of dissolved part of SOIL2 organic matter +0.002 (prop.) fraction of dissolved part of SOIL3 organic matter +0.002 (prop.) fraction of dissolved part of SOIL4 organic matter +0.1 (prop.) minimum WFPS for scalar of nitrification calculation +0.45 (prop.) lower optimum WFPS for scalar of nitrification calculation +0.55 (prop.) higher optimum WFPS for scalar of nitrification calculation +0.2 (prop.) minimum value for saturated WFPS scalar of nitrification calculation +10 (ppm) C:N ratio of recaltirant SOM (slowest) +---------------------------------------------------------------------------------------- +RATE SCALARS +0.39 (DIM) respiration fractions for fluxes between compartments (l1s1) +0.55 (DIM) respiration fractions for fluxes between compartments (l2s2) +0.29 (DIM) respiration fractions for fluxes between compartments (l4s3) +0.28 (DIM) respiration fractions for fluxes between compartments (s1s2) +0.46 (DIM) respiration fractions for fluxes between compartments (s2s3) +0.55 (DIM) respiration fractions for fluxes between compartments (s3s4) +0.7 (DIM) rate constant scalar of labile litter pool +0.07 (DIM) rate constant scalar of cellulose litter pool +0.014 (DIM) rate constant scalar of lignin litter pool +0.07 (DIM) rate constant scalar of fast microbial recycling pool +0.014 (DIM) rate constant scalar of medium microbial recycling pool +0.0014 (DIM) rate constant scalar of slow microbial recycling pool +0.0001 (DIM) rate constant scalar of recalcitrant SOM (humus) pool +0.001 (DIM) rate constant scalar of physical fragmentation of coarse woody debris +---------------------------------------------------------------------------------------- +CH4 PARAMETERS +212.5 (DIM) soil CH4 emission bulk density dependence parameter1 +1.81 (DIM) soil CH4 emission bulk density dependence parameter2 +-1.353 (DIM) soil CH4 emission soil water content dependence parameter1 +0.2 (DIM) soil CH4 emission soil water content dependence parameter2 +1.781 (DIM) soil CH4 emission soil water content dependence parameter3 +6.786 (DIM) soil CH4 emission soil water content dependence parameter4 +0.010 (DIM) soil CH4 emission soil temperature dependence parameter1 +---------------------------------------------------------------------------------------- +SOIL PARAMETERS +2 (m) depth of soil +6 (mm) limit of first stage evaporation +5.00 (mm) maximum height of pond water +1 (dimless) curvature of soil stress function +-9999 (dimless) runoff curve number (-9999: no , model estimation) +107 (s/m) aerodynamic resistance (Wallace and Holwill, 1997) +---------------------------------------------------------------------------------------- +SOIL COMPOSITION AND CHARACTERISTIC VALUES (-9999: no measured data) +30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 (%) sand percentage by volume in rock-free soil +50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 (%) silt percentage by volume in rock-free soil +7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 (dimless) soil pH (dimless) measured runoff curve number +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (g/cm3) bulk density +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at saturation +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at field capacity +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at wilting point +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at hygroscopic water content +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (dimless) drainage coefficient +-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (cm/day) hydraulic condictivity at saturation diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso new file mode 100644 index 0000000..276db81 Binary files /dev/null and b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso differ diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso.exe b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso.exe new file mode 100644 index 0000000..e5df82a Binary files /dev/null and b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso.exe differ diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso7.0b7.exe b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso7.0b7.exe new file mode 100644 index 0000000..e5df82a Binary files /dev/null and b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/muso7.0b7.exe differ diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/n.ini b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/n.ini new file mode 100644 index 0000000..9e84847 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/n.ini @@ -0,0 +1,147 @@ +BBGCMuSo simulation + +MET_INPUT +hhs.mtc43 (filename) met file name +4 (int) number of header lines in met file +365 (int) number of simdays in last simyear (truncated year: <= 365) + +RESTART +1 (flag) 1 = read restart; 0 = dont read restart +0 (flag) 1 = write restart; 0 = dont write restart +hhs_MuSo6.endpoint (filename) name of the input restart file +hhs_MuSo6.endpoint (filename) name of the output restart file + +TIME_DEFINE +9 (int) number of simulation years +2007 (int) first simulation year +0 (flag) 1 = spinup run; 0 = normal run +6000 (int) maximum number of spinup years + +CO2_CONTROL +1 (flag) 0=constant; 1=vary with file +395.0 (ppm) constant atmospheric CO2 concentration +CO2.txt (filename) name of the CO2 file + +NDEP_CONTROL +1 (flag) 0=constant; 1=vary with file +0.001400 (kgN/m2/yr) wet+dry atmospheric deposition of N +Ndep.txt (filename) name of the N-dep file + +SITE +248.0 (m) site elevation +46.95 (degrees) site latitude (- for S.Hem.) +0.20 (DIM) site shortwave albedo +9.00 (Celsius) mean annual air temperature +10.15 (Celsius) mean annual air temperature range +0.50 (prop.) proprortion of NH4 flux of N-deposition + +SOIL_FILE +hhs.soi (filename) SOIL filename + +EPC_FILE +c3grass_muso6.epc (filename) EPC filename + +MANAGEMENT_FILE +hhs.mgm (filename) MGM filename (or "none") + +SIMULATION_CONTROL +1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY) +1 (flag) vegper calculation method if MODEL PHENOLOGY is used (0: original, 1: GSI) +0 (flag) transferGDD flag (1= transfer calc. from GDD 0 = transfer calc. from EPC) +1 (flag) q10 flag (1 = temperature dependent q10 value; 0= constans q10 value) +1 (flag) acclimation flag of photosynthesis (1 = acclimation 0 = no acclimation) +1 (flag) acclimation flag of respiration (1 = acclimation 0 = no acclimation) +1 (flag) CO2 conductance reduction flag (0: no effect, 1: multiplier) +0 (flag) soil temperature calculation method (0: Zheng, 1: DSSAT) +1 (flag) soil hydrological calculation method (0: Richards, 1: tipping DSSAT) +0 (int) discretization level of soil hydr.calc.[Richards-method] (0: low, 1: medium, 2: high) +0 (flag) photosynthesis calculation method (0: Farquhar, 1: DSSAT) +0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor) +0 (flag) radiation calculation method (0: SWabs, 1: Rn) +0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand) + +W_STATE +0.0 (kg/m2) water stored in snowpack +1.0 (DIM) initial soil water as a proportion of field capacity + +CN_STATE +0.001 (kgC/m2) first-year maximum leaf carbon +0.001 (kgC/m2) first-year maximum fine root carbon +0.001 (kgC/m2) first-year maximum fruit carbon +0.001 (kgC/m2) first-year maximum softstem carbon +0.001 (kgC/m2) first-year maximum live woody stem carbon +0.001 (kgC/m2) first-year maximum live coarse root carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) coarse woody debris carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, unshielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, shielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, lignin pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, fast microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, medium microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, slow microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, recalcitrant SOM (slowest) +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) litter nitrogen, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NH4 pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NO3 pool + +CLIM_CHANGE +0.0 (degC) - offset for Tmax +0.0 (degC) - offset for Tmin +1.0 (degC) - multiplier for PRCP +1.0 (degC) - multiplier for VPD +1.0 (degC) - multiplier for RAD + +CONDITIONAL_MANAGEMENT_STRATEGIES +0 (flag) conditional mowing ? 0 - no, 1 - yes +0.0 (m2/m2) fixed value of the LAI before MOWING +0.0 (m2/m2) fixed value of the LAI after MOWING +0.0 (%) transported part of plant material after MOWING +0 (flag) conditional irrigation? 0 - no, 1 - yes +0.0 (prop) SMSI before cond. IRRIGATION (-9999: SWCratio is used) +0.0 (prop) SWCratio of rootzone before cond. IRRIGATION (-9999: SMSI is used) +0.0 (prop) SWCratio of rootzone after cond. IRRIGATION +0.0 (kgH2O/m2) maximum amount of irrigated water + +OUTPUT_CONTROL +hhs_MuSo6 (filename) output prefix +1 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing annual output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +1 (flag) for on-screen progress indicator + +DAILY_OUTPUT +12 number of daily output variables +2520 proj_lai +3009 daily_GPP +3014 daily_Reco +171 evapotransp +2502 n_actphen +2603 vwc00-03cm +2604 vwc03-10cm +2605 vwc10-30cm +75 GDD +2636 rooting_depth +2716 m_soilstress +671 m_vegc_to_SNSC + +ANNUAL_OUTPUT +16 number of annual output variables +3000 annprcp +3001 anntavg +3002 annrunoff +3003 annoutflow +2734 annmax_lai +3031 cum_Closs_MGM +3032 cum_Cplus_MGM +3045 cum_Closs_SNSC +3046 cum_Cplus_STDB +3058 vegc +3064 totalc +3066 SOM_C_top30 +3070 SOM_C_30to60 +3071 SOM_C_60to90 +3068 NH4_top30 +3069 NO3_top30 + +END_INIT diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/parameters.csv b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/parameters.csv new file mode 100644 index 0000000..fd2dee0 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/parameters.csv @@ -0,0 +1,15 @@ +ABREVIATION,INDEX,min,max MuSo6 +TRANSFERGROWTHP,11,0.1,1 +T_BASE,13,0,8 +WPM,25,0,0.1 +CN_leaf,26,14.3,58.8 +CWIC,49,0.01,0.07 +CLEC,50,0.3,0.8 +FLNR,56,0.1,0.2 +MSTOMACOND,58,0.001,0.007 +ROOTDEPTH,64,0.5,3 +ROOTDISTRIB,65,0.2,5 +RELSWCCRIT1,96,0.97,1 +RELSWCCRIT2,97,0.4,1 +SENESCENCABG,101,0,0.1 +SLA,137.60,10,60 diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/s.ini b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/s.ini new file mode 100644 index 0000000..b3bfa7f --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/examples/hhs/s.ini @@ -0,0 +1,147 @@ +BBGCMuSo simulation + +MET_INPUT +hhs.mtc43 (filename) met file name +4 (int) number of header lines in met file +365 (int) number of simdays in last simyear (truncated year: <= 365) + +RESTART +0 (flag) 1 = read restart; 0 = dont read restart +1 (flag) 1 = write restart; 0 = dont write restart +hhs_MuSo6.endpoint (filename) name of the input restart file +hhs_MuSo6.endpoint (filename) name of the output restart file + +TIME_DEFINE +54 (int) number of simulation years +1961 (int) first simulation year +1 (flag) 1 = spinup run; 0 = normal run +6000 (int) maximum number of spinup years + +CO2_CONTROL +1 (flag) 0=constant; 1=vary with file +290.0 (ppm) constant atmospheric CO2 concentration +CO2.txt (filename) name of the CO2 file + +NDEP_CONTROL +1 (flag) 0=constant; 1=vary with file +0.000200 (kgN/m2/yr) wet+dry atmospheric deposition of N +Ndep.txt (filename) name of the N-dep file + +SITE +248.0 (m) site elevation +46.95 (degrees) site latitude (- for S.Hem.) +0.20 (DIM) site shortwave albedo +9.00 (Celsius) mean annual air temperature +10.15 (Celsius) mean annual air temperature range +0.50 (prop.) proprortion of NH4 flux of N-deposition + +SOIL_FILE +hhs.soi (filename) SOIL filename + +EPC_FILE +c3grass_muso6.epc (filename) EPC filename + +MANAGEMENT_FILE +none (filename) MGM filename (or "none") + +SIMULATION_CONTROL +1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY) +1 (flag) vegper calculation method if MODEL PHENOLOGY is used (0: original, 1: GSI) +0 (flag) transferGDD flag (1= transfer calc. from GDD 0 = transfer calc. from EPC) +1 (flag) q10 flag (1 = temperature dependent q10 value; 0= constans q10 value) +1 (flag) acclimation flag of photosynthesis (1 = acclimation 0 = no acclimation) +1 (flag) acclimation flag of respiration (1 = acclimation 0 = no acclimation) +1 (flag) CO2 conductance reduction flag (0: no effect, 1: multiplier) +0 (flag) soil temperature calculation method (0: Zheng, 1: DSSAT) +1 (flag) soil hydrological calculation method (0: Richards, 1: tipping DSSAT) +0 (int) discretization level of soil hydr.calc.[Richards-method] (0: low, 1: medium, 2: high) +0 (flag) photosynthesis calculation method (0: Farquhar, 1: DSSAT) +0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor) +0 (flag) radiation calculation method (0: SWabs, 1: Rn) +0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand) + +W_STATE +0.0 (kg/m2) water stored in snowpack +1.0 (DIM) initial soil water as a proportion of field capacity + +CN_STATE +0.001 (kgC/m2) first-year maximum leaf carbon +0.001 (kgC/m2) first-year maximum fine root carbon +0.001 (kgC/m2) first-year maximum fruit carbon +0.001 (kgC/m2) first-year maximum softstem carbon +0.001 (kgC/m2) first-year maximum live woody stem carbon +0.001 (kgC/m2) first-year maximum live coarse root carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) coarse woody debris carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, unshielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, shielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, lignin pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, fast microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, medium microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, slow microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, recalcitrant SOM (slowest) +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) litter nitrogen, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NH4 pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NO3 pool + +CLIM_CHANGE +0.0 (degC) - offset for Tmax +0.0 (degC) - offset for Tmin +1.0 (degC) - multiplier for PRCP +1.0 (degC) - multiplier for VPD +1.0 (degC) - multiplier for RAD + +CONDITIONAL_MANAGEMENT_STRATEGIES +0 (flag) conditional mowing ? 0 - no, 1 - yes +0.0 (m2/m2) fixed value of the LAI before MOWING +0.0 (m2/m2) fixed value of the LAI after MOWING +0.0 (%) transported part of plant material after MOWING +0 (flag) conditional irrigation? 0 - no, 1 - yes +0.0 (prop) SMSI before cond. IRRIGATION (-9999: SWCratio is used) +0.0 (prop) SWCratio of rootzone before cond. IRRIGATION (-9999: SMSI is used) +0.0 (prop) SWCratio of rootzone after cond. IRRIGATION +0.0 (kgH2O/m2) maximum amount of irrigated water + +OUTPUT_CONTROL +hhs_MuSo6_Spinup (filename) output prefix +0 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +2 (flag) writing annual output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +1 (flag) for on-screen progress indicator + +DAILY_OUTPUT +12 number of daily output variables +2502 n_actphen +2603 vwc00-03cm +2604 vwc03-10cm +2605 vwc10-30cm +75 GDD +2636 rooting_depth +2716 m_soilstress +671 m_vegc_to_SNSC +171 evapotransp +3009 daily_gpp +3014 daily_tr +2520 proj_lai + +ANNUAL_OUTPUT +16 number of annual output variables +3000 annprcp +3001 anntavg +3002 annrunoff +3003 annoutflow +2734 annmax_lai +3031 cum_Closs_MGM +3032 cum_Cplus_MGM +3045 cum_Closs_SNSC +3046 cum_Cplus_STDB +3058 vegc +3064 totalc +3066 SOM_C_top30 +3070 SOM_C_30to60 +3071 SOM_C_60to90 +3068 NH4_top30 +3069 NO3_top30 + +END_INIT diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/markdowns/parameterSweep.rmd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/markdowns/parameterSweep.rmd new file mode 100644 index 0000000..0651036 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/markdowns/parameterSweep.rmd @@ -0,0 +1,115 @@ +--- +title: "ParameterSweep" +auth or: "" +date: "`r format(Sys.time(), '%d %B, %Y')`" +output: html_document +--- + +```{r setup, include=FALSE} +knitr::opts_chunk$set(echo = TRUE) +``` + +```{r,echo=FALSE} +library("RBBGCMuso") + +quickAndDirty <- function(settings, parameters, inputDir= "./", outLoc, iterations=2, outVar=8,){ + + + + outLocPlain <- basename(outLoc) + currDir <- getwd() + inputDir <- normalizePath(inputDir) + tmp <- file.path(outLoc,"tmp/") + + if(!dir.exists(outLoc)){ + dir.create(outLoc) + warning(paste(outLoc," is not exists, so it was created")) + } + + if(dir.exists(tmp)){ + stop("There is a tmp directory inside the output location, please replace it. tmp is an important temporary directory for the function") + } + dir.create(tmp) + outLoc <- normalizePath(outLoc) + tmp <- normalizePath(tmp) + + inputFiles <- file.path(inputDir,grep(basename(outLoc),list.files(inputDir),invert = TRUE,value = TRUE)) + + + for(i in inputFiles){ + file.copy(i,tmp) + } + + setwd(tmp) + + if(is.null(settings)){ + settings <- setupMuso() + } + + + + file.copy(settings$epcInput[2],"epc-save",overwrite = TRUE) + calibrationPar <- matrix[,"INDEX"] + npar <- nrow(matrix) + paramMatrices <- list() + parameters <- matrix(nrow = npar,ncol = iterations) + paramtest <- parameters + rownames(paramtest) <- matrix[,1] + + for(i in 1:npar){ + parameters[i,] <- seq(from=matrix[i,5],to=matrix[i,6],length=iterations) + #print(parameters[i,]) + settings$calibrationPar <- calibrationPar[i] + for(j in 1:iterations){ + p <- try(calibMuso(settings,parameters =parameters[i,j],silent=TRUE)) + + if(length(p)>1){ + paramtest[i,j] <- max(p[,outVar]) + # print(paramtest) + } else { + paramtest[i,j] <- NA + # print(paramtest) + } + } + file.copy("epc-save",settings$epcInput[2],overwrite = TRUE) + } + + print("###################################################") + paramMatrices <- (function(){ + for(i in 1:nrow(paramtest)){ + matrx <- matrix(ncol = 2,nrow=iterations) + matrx[,1] <- parameters[i,] + matrx[,2] <- paramtest[i,] + paramMatrices[[i]] <- matrx + names(paramMatrices)[i] <- rownames(paramtest)[i] + } + return(paramMatrices) + })() + + + return(list(paramtest,paramMatrices)) + + +} + +``` + + +```{r, echo=FALSE,cache=TRUE} +parconstrains <- read.csv("parconstrains_extended.csv") +settings <- setupMuso() +parSeq<-quickAndDirty(settings = settings,matrix = parconstrains,outVar = 8,iterations = 5) +``` + +```{r} +parSeq +``` + +```{r,echo=FALSE} + parlist<-parSeq[[2]] + lparlist<-length(parlist) + for(i in 1:lparlist){ + title<-names(parlist)[i] + plot(x = parlist[[i]][,1], y= parlist[[i]][,2], ylim=c(0,15), main=title,ylab="LAI") + } +``` diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/markdowns/parameters.csv b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/markdowns/parameters.csv new file mode 100644 index 0000000..6848451 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/markdowns/parameters.csv @@ -0,0 +1,14 @@ +NAME,INDEX,MIN,MAX +BASETEMP,25,3,9 +WPM,36,0,0.1 +CN_lv,38,10,50 +CN_li,39,32,70 +CN_root,40,20,70 +CN_fruit,41,10.50,70 +CN_stem,42,0,70 +CLEC,55,0.4,0.8 +FLNR,61,0.05,0.8 +STOMA,63,0.003,0.015 +ROOTDEPTH,74,0.3,2. +SWCGERMIN,87,0.2,0.9 +NH4MOBILEPROP,120,0.05,0.7 diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/mtclim43 b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/mtclim43 new file mode 100644 index 0000000..8c6f896 Binary files /dev/null and b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/mtclim43 differ diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/mtclim43.exe b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/mtclim43.exe new file mode 100644 index 0000000..43bf1c1 Binary files /dev/null and b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/mtclim43.exe differ diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/tests/test_postProcMuso.R b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/tests/test_postProcMuso.R new file mode 100644 index 0000000..1234d0f --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/inst/tests/test_postProcMuso.R @@ -0,0 +1,21 @@ +context("Post processing") +library(testthat) +library(RBBGCMuso) +setwd(system.file("examples/hhs","",package = "RBBGCMuso")) + +test_that("Post processing string",{ + testMatrix1 <- data.frame(first = rep(1,5), second = rep(2,5), third = rep(3,5)) + testMatrix1c <- testMatrix1 + testMatrix1c[,"newCol"] <- testMatrix1c[,2] + 3 * testMatrix1c[,3] + expect_equal(postProcMuso(testMatrix1,"newCol <- @2 + 3*@3"),testMatrix1c) +}) + +test_that("calibMuso with postprocessing",{ + model <- calibMuso(skipSpinup = FALSE, silent = TRUE) + modelc<- model + newCol <- modelc[,1] + modelc<- cbind.data.frame(modelc,newCol) + modelc[,"newCol"]<- model[,5]+3*model[,7] + expect_equal(calibMuso(skipSpinup = FALSE,silent = TRUE, postProcString = "newCol <- @5 + 3* @7"), modelc) +}) + diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/alignData.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/alignData.Rd new file mode 100644 index 0000000..0200b96 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/alignData.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/musoTime.R +\name{alignData} +\alias{alignData} +\title{alignData} +\usage{ +alignData( + mdata, + dataCol, + modellSettings = NULL, + startDate = NULL, + endDate = NULL, + formatString = "\%Y-\%m-\%d", + leapYear = TRUE, + continious = FALSE +) +} +\description{ +This function align the data to the model and the model to the data +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/calibMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/calibMuso.Rd new file mode 100644 index 0000000..99d96cb --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/calibMuso.Rd @@ -0,0 +1,49 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/calibMuso.R +\name{calibMuso} +\alias{calibMuso} +\title{calibMuso} +\usage{ +calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, +keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +} +\arguments{ +\item{settings}{You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment} + +\item{parameters}{In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4)} + +\item{timee}{The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet.} + +\item{debugging}{If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles} + +\item{logfilename}{If you want to set a specific name for your logfiles you can set this via logfile parameter} + +\item{keepEpc}{If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.} + +\item{export}{if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.} + +\item{silent}{If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.} + +\item{aggressive}{It deletes every possible modell-outputs from the previous modell runs.} + +\item{keepBinary}{In default RBBGCMuso to keep working area as clean as possible, deletes all the regular output files. The results are directly printed to the standard output, but you can redirect it, and save it to a variable, or you can export your results to the desired destination in a desired format. Whith this variable you can enable to keep the binary output files. If you want to set the location of the binary output, please take a look at the binaryPlace argument.} + +\item{binaryPlace}{The place of the binary output files.} + +\item{fileToChange}{You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini"} + +\item{skipSpinup}{If TRUE, calibMuso wont do spinup simulation} + +\item{prettyOut}{date ad Date type, separate year, month, day vectors} + +\item{leapYear}{Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.} +} +\value{ +No return, outputs are written to file +} +\description{ +This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a well-structured way. +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/calibrateMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/calibrateMuso.Rd new file mode 100644 index 0000000..b352155 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/calibrateMuso.Rd @@ -0,0 +1,43 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/calibrateMuso.R +\name{calibrateMuso} +\alias{calibrateMuso} +\title{calibrateMuso} +\usage{ +calibrateMuso( + measuredData, + parameters = read.csv("parameters.csv", stringsAsFactor = FALSE), + startDate = NULL, + endDate = NULL, + formatString = "\%Y-\%m-\%d", + dataVar, + outLoc = "./calib", + preTag = "cal-", + settings = setupMuso(), + outVars = NULL, + iterations = 100, + skipSpinup = TRUE, + plotName = "calib.jpg", + modifyOriginal = TRUE, + likelihood, + uncertainity = NULL, + naVal = NULL, + postProcString = NULL, + thread_prefix = "thread", + numCores = (parallel::detectCores() - 1), + pb = txtProgressBar(min = 0, max = iterations, style = 3), + maxLikelihoodEpc = TRUE, + pbUpdate = setTxtProgressBar, + outputLoc = "./", + method = "GLUE", + lg = FALSE, + w = NULL, + ... +) +} +\description{ +This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/changemulline.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/changemulline.Rd new file mode 100644 index 0000000..3676348 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/changemulline.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/changeMuso.R +\name{changemulline} +\alias{changemulline} +\title{changemulline} +\usage{ +changemulline(filePaths, calibrationPar, contents, src, outFiles = filePaths) +} +\description{ +The function uses the previous changspecline function to operate. +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/checkFileSystem.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/checkFileSystem.Rd new file mode 100644 index 0000000..ab4f105 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/checkFileSystem.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/flat.R +\name{checkFileSystem} +\alias{checkFileSystem} +\title{checkFileSystem} +\usage{ +checkFileSystem(iniName, root = ".", depTree = options("RMuso_depTree")[[1]]) +} +\arguments{ +\item{iniName}{The name of the ini file} + +\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]} +} +\description{ +This function checks the MuSo file system, if it is correct +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/checkMeteoBGC.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/checkMeteoBGC.Rd new file mode 100644 index 0000000..02bdcfa --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/checkMeteoBGC.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/checkMeteoBGC.R +\name{checkMeteoBGC} +\alias{checkMeteoBGC} +\title{checkMeteoBGC} +\usage{ +checkMeteoBGC( + settings = NULL, + skip = 4, + numericReport = FALSE, + type = "normal" +) +} +\arguments{ +\item{settings}{The output of setupMuso} + +\item{skip}{Number of header lines in meteorology file.} + +\item{numericReport}{If numericReport is set to FALSE, the function returns with a text report. If numericReport is set to TRUE, the function returns with a numeric report.} + +\item{type}{meteorology for spinup or normal run} + +\item{metFileName}{The name of the meteorology file (mtc43).} +} +\value{ +It depends on the numericReport parameter. The function returns with a text report, or with a numeric report. +} +\description{ +This function calculates the daily and yearly statistics for a given meteorology file (mtc43). +} +\author{ +Erzsebet Kristof +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/cleanupMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/cleanupMuso.Rd new file mode 100644 index 0000000..7f830d6 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/cleanupMuso.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/cleanup.R +\name{cleanupMuso} +\alias{cleanupMuso} +\title{cleanupMuso} +\usage{ +cleanupMuso(location=NULL, simplicity=TRUE,deep=FALSE) +} +\arguments{ +\item{location}{This is the place (directory) where your output files are located.} + +\item{simplicity}{TRUE or FALSE. If TRUE cleanupMuso will erase only the log files from the location} + +\item{deep}{If it is TRUE, it will delete every files from the subdirectories also} +} +\description{ +cleanupMuso can erase all of the unnecessary log and output files. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/compareCalibratedWithOriginal.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/compareCalibratedWithOriginal.Rd new file mode 100644 index 0000000..1b46fc9 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/compareCalibratedWithOriginal.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/multiSite.R +\name{compareCalibratedWithOriginal} +\alias{compareCalibratedWithOriginal} +\title{compareCalibratedWithOriginal} +\usage{ +compareCalibratedWithOriginal( + key, + modOld, + modNew, + mes, + likelihoods, + alignIndexes, + musoCodeToIndex, + nameGroupTable, + groupFun +) +} +\description{ +This functions compareses the likelihood and the RMSE values of the simulations and the measurements +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/compareMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/compareMuso.Rd new file mode 100644 index 0000000..b4c6380 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/compareMuso.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/plotMuso.R +\name{compareMuso} +\alias{compareMuso} +\title{compareMuso} +\usage{ +compareMuso( + settings = NULL, + parameters, + variable = 1, + calibrationPar = NULL, + fileToChange = "epc", + skipSpinup = TRUE, + timeFrame = "day" +) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{parameters}{Using this function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).} + +\item{variable}{The name of the output variable to plot} + +\item{calibrationPar}{You might want to change some parameters in your EPC file before running the model. This function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)} + +\item{fileToChange}{You can change any line of the EPC or the INI file. Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user.} +} +\description{ +This function runs the model, then changes one of its input data, runs it again, and plots both results in one graph. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/copyMusoExampleTo.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/copyMusoExampleTo.Rd new file mode 100644 index 0000000..be32c7d --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/copyMusoExampleTo.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/musoExample.R +\name{copyMusoExampleTo} +\alias{copyMusoExampleTo} +\title{copyMusoExampleTo} +\usage{ +copyMusoExampleTo(example = NULL, destination = NULL) +} +\arguments{ +\item{example}{This is the name of the example file. If it is not set then a simple graphical user interface (tcl/tk menu) will open to select the target dataset (which is typically an experimental site). In the list hhs means the Hegyhatsal eddy covariance site in Hungary.} + +\item{destination}{The destination where the example files will be copied.} +} +\description{ +This function enables the user to download a complete, working file set to quickly start using Biome-BGCMuSo through RBBGCMuso (or in standalone mode). The user has to specify the target directory for the files. The file set contains the model executable (muso.exe in Windows), the INI files that drive the model, and other files like meteorology input, ecophysiological constants file (EPC), and other ancillary files (CO2 concentration, parameter range definition file called parameters.csv). Note that we strongly recommend to read the User's Guide of Biome-BGCMuSo to clarify the meaning of the input files. The input files (s.ini, n.ini, maize.epc, meteorology files) are simple text files, so the user can read (and modify) them with his/her favourite text editor (like Editpad Lite, vim, emacs). Note that some files use UNIX/Linux style text which means that the text will not be readable using the Windows Notepad. +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/corrigMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/corrigMuso.Rd new file mode 100644 index 0000000..97387b2 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/corrigMuso.Rd @@ -0,0 +1,22 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{corrigMuso} +\alias{corrigMuso} +\title{corrigMuso} +\usage{ +corrigMuso(settings, data) +} +\arguments{ +\item{settings}{This is the output of the setupMuso() function. It contains all of the RBBGCMuso settings} + +\item{data}{the models outputdata} +} +\value{ +It returns the modells leapyear-corrigated output data. +} +\description{ +This function leapyear-corrigate the output of the modell +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/createSoilFile.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/createSoilFile.Rd new file mode 100644 index 0000000..5eb6bac --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/createSoilFile.Rd @@ -0,0 +1,11 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/soilQuery.R +\name{createSoilFile} +\alias{createSoilFile} +\title{createSoilFile} +\description{ +This function collects soil data from a given restapi, de default is soilGrid +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/dynRound.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/dynRound.Rd new file mode 100644 index 0000000..6c5c541 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/dynRound.Rd @@ -0,0 +1,22 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{dynRound} +\alias{dynRound} +\title{dynRound} +\usage{ +dynRound(x, y, seqLen) +} +\arguments{ +\item{x}{The lower end of the sequence} + +\item{y}{The higher end of the sequence} + +\item{seqLen}{The length of the sequence} +} +\value{ +rounded sequence +} +\description{ +This function rounds a sequence (definded by its endpoints and the length) optimally +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/fextension.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/fextension.Rd new file mode 100644 index 0000000..45075f8 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/fextension.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{fextension} +\alias{fextension} +\title{fextension} +\usage{ +fextension(filename) +} +\arguments{ +\item{filename}{The string of the filenam} +} +\value{ +the extension of the given file +} +\description{ +A function for extracting the extension name from the filename string +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/flatMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/flatMuso.Rd new file mode 100644 index 0000000..4fd2907 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/flatMuso.Rd @@ -0,0 +1,25 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/flat.R +\name{flatMuso} +\alias{flatMuso} +\title{flatMuso} +\usage{ +flatMuso( + iniName, + execPath = "./", + depTree = options("RMuso_depTree")[[1]], + directory = "flatdir", + d = TRUE, + outE = TRUE +) +} +\arguments{ +\item{iniName}{The name of the ini file} + +\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]} + +\item{directory}{The destination directory for flattening. At default it will be flatdir} +} +\description{ +This function reads the ini file and creates a directory (named after the directory argument) with all the files the modell uses with this file. the directory will be flat. +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getAnnualOutputList.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getAnnualOutputList.Rd new file mode 100644 index 0000000..ac956c8 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getAnnualOutputList.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/getOutPutList.R +\name{getAnnualOutputList} +\alias{getAnnualOutputList} +\title{getAnnualOutputList} +\usage{ +getAnnualOutputList(settings = NULL) +} +\arguments{ +\item{settings}{bla} +} +\description{ +bla bla +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getConstMatrix.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getConstMatrix.Rd new file mode 100644 index 0000000..8563459 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getConstMatrix.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{getConstMatrix} +\alias{getConstMatrix} +\title{getConstMatrix} +\usage{ +getConstMatrix( + filetype = "epc", + version = as.character(getOption("RMuso_version")) +) +} +\arguments{ +\item{filetype}{It can be "epc" or "soil".} + +\item{version}{The version of the MuSo environment} +} +\description{ +getConstMatrix is a function whith wich you can get the default constrain matrix for your choosen type and version. +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getDailyOutputList.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getDailyOutputList.Rd new file mode 100644 index 0000000..f02058b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getDailyOutputList.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/getOutPutList.R +\name{getDailyOutputList} +\alias{getDailyOutputList} +\title{getDailyOutputList} +\usage{ +getDailyOutputList(settings = NULL) +} +\arguments{ +\item{settings}{bla} +} +\description{ +bla bla +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getFilePath.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getFilePath.Rd new file mode 100644 index 0000000..3855cd5 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getFilePath.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/flat.R +\name{getFilePath} +\alias{getFilePath} +\title{getFilePath} +\usage{ +getFilePath( + iniName, + fileType, + execPath = "./", + depTree = options("RMuso_depTree")[[1]] +) +} +\arguments{ +\item{iniName}{The name of the ini file} + +\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]} + +\item{filetype}{The type of the choosen file. For options see options("RMuso_depTree")[[1]]$name} +} +\description{ +This function reads the ini file and for a chosen fileType it gives you the filePath +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getFilesFromIni.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getFilesFromIni.Rd new file mode 100644 index 0000000..8124081 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getFilesFromIni.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/flat.R +\name{getFilesFromIni} +\alias{getFilesFromIni} +\title{getFilesFromIni} +\usage{ +getFilesFromIni( + iniName, + execPath = "./", + depTree = options("RMuso_depTree")[[1]] +) +} +\arguments{ +\item{iniName}{The name of the ini file} + +\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]} +} +\description{ +This function reads the ini file and gives yout back the path of all file involved in model run +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getLogs.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getLogs.Rd new file mode 100644 index 0000000..8b0057b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getLogs.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{getLogs} +\alias{getLogs} +\title{getLogs} +\usage{ +getLogs(outputLoc, outputNames, type = "spinup") +} +\arguments{ +\item{outputLoc}{This is the location of the output files.} + +\item{outputNames}{These are the prefixes of the logfiles} +} +\value{ +Logfiles with paths +} +\description{ +This function gives us the muso logfiles with their path +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getOutFiles.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getOutFiles.Rd new file mode 100644 index 0000000..2183a46 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getOutFiles.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{getOutFiles} +\alias{getOutFiles} +\title{getOutFiles} +\usage{ +getOutFiles(outputLoc, outputNames) +} +\arguments{ +\item{outputLoc}{This is the location of the output files.} + +\item{outputNames}{These are the prefixes of the logfiles.} +} +\value{ +Output files with their paths. +} +\description{ +This function gives us the muso output files with their paths +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getSoilDataFull.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getSoilDataFull.Rd new file mode 100644 index 0000000..4442e72 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getSoilDataFull.Rd @@ -0,0 +1,11 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/soilQuery.R +\name{getSoilDataFull} +\alias{getSoilDataFull} +\title{getSoilDataFull} +\description{ +This function collects soil data from a given restapi, de default is soilGrid +} +\author{ +Roland HOLLÓS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getyearlycum.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getyearlycum.Rd new file mode 100644 index 0000000..70cce89 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getyearlycum.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{getyearlycum} +\alias{getyearlycum} +\title{getyearlycum} +\usage{ +getyearlycum(daily_observations) +} +\arguments{ +\item{daily_observations}{vector of the daily observations.} +} +\value{ +A vector of yearly data +} +\description{ +Funtion for getting cumulative yearly data from observations +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getyearlymax.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getyearlymax.Rd new file mode 100644 index 0000000..c3c5785 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/getyearlymax.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{getyearlymax} +\alias{getyearlymax} +\title{getyearlymax} +\usage{ +getyearlymax(daily_observations) +} +\arguments{ +\item{daily_observations}{vector of the daily observations} +} +\value{ +A vector of yearly data +} +\description{ +Function for getting the maximum values of the years, from daily data +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/multiSiteCalib.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/multiSiteCalib.Rd new file mode 100644 index 0000000..5074820 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/multiSiteCalib.Rd @@ -0,0 +1,64 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/multiSite.R +\name{multiSiteCalib} +\alias{multiSiteCalib} +\title{multiSiteCalib} +\usage{ +multiSiteCalib( + measurements, + calTable, + parameters, + dataVar, + iterations = 100, + burnin = ifelse(iterations < 3000, 3000, NULL), + likelihood, + execPath, + thread_prefix = "thread", + numCores = (parallel::detectCores() - 1), + pb = txtProgressBar(min = 0, max = iterations, style = 3), + pbUpdate = setTxtProgressBar, + copyThread = TRUE, + constraints = NULL, + th = 10, + treeControl = rpart.control() +) +} +\arguments{ +\item{calTable}{A dataframe which contantains the ini file locations and the domains they belongs to} + +\item{parameters}{A dataframe with the name, the minimum, and the maximum value for the parameters used in MonteCarlo experiment} + +\item{dataVar}{A named vector where the elements are the MuSo variable codes and the names are the same as provided in measurements and likelihood} + +\item{iterations}{The number of MonteCarlo experiments to be executed} + +\item{burnin}{Currently not used, altought it is the length of burnin period of the MCMC sampling used to generate random parameters} + +\item{likelihood}{A list of likelihood functions which names are linked to dataVar} + +\item{execPath}{If you are running the calibration from different location than the MuSo executable, you have to provide the path} + +\item{thread_prefix}{The prefix of thread directory names in the tmp directory created during the calibrational process} + +\item{numCores}{The number of processes used during the calibration. At default it uses one less than the number of threads available} + +\item{pb}{The progress bar function. If you use (web-)GUI you can provide a different function} + +\item{pbUpdate}{The update function for pb (progress bar)} + +\item{copyThread}{A boolean, recreate tmp directory for calibration or not (case of repeating the calibration)} + +\item{th}{A trashold value for multisite calibration. What percentage of the site should satisfy the constraints.} + +\item{treeControl}{A list which controls (maximal complexity, maximal depth) the details of the decession tree making.} + +\item{measuremets}{The table which contains the measurements} + +\item{contsraints}{A dataframe containing the constraints logic the minimum and a maximum value for the calibration.} +} +\description{ +This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution of the random parameters on convex polytopes. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/multiSiteThread.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/multiSiteThread.Rd new file mode 100644 index 0000000..7e1073b --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/multiSiteThread.Rd @@ -0,0 +1,36 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/multiSite.R +\name{multiSiteThread} +\alias{multiSiteThread} +\title{multiSiteThread} +\usage{ +multiSiteThread( + measuredData, + parameters = NULL, + startDate = NULL, + endDate = NULL, + formatString = "\%Y-\%m-\%d", + calTable, + dataVar, + outLoc = "./calib", + outVars = NULL, + iterations = 300, + skipSpinup = TRUE, + plotName = "calib.jpg", + modifyOriginal = TRUE, + likelihood, + uncertainity = NULL, + burnin = NULL, + naVal = NULL, + postProcString = NULL, + threadNumber, + constraints = NULL, + th = 10 +) +} +\description{ +This is an +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoDate.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoDate.Rd new file mode 100644 index 0000000..d2d47f6 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoDate.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/musoTime.R +\name{musoDate} +\alias{musoDate} +\title{musoDate} +\usage{ +musoDate( + startYear, + endYears = NULL, + numYears, + combined = TRUE, + leapYearHandling = FALSE, + prettyOut = FALSE +) +} +\description{ +This function generates MuSo compatibla dates for the data +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoGlue.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoGlue.Rd new file mode 100644 index 0000000..c3b878c --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoGlue.Rd @@ -0,0 +1,24 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/calibration.R +\name{musoGlue} +\alias{musoGlue} +\title{musoGlue} +\usage{ +musoGlue( + presCalFile, + w, + delta = 0.17, + settings = setupMuso(), + parameters = read.csv("parameters.csv", stringsAsFactors = FALSE), + lg = FALSE +) +} +\arguments{ +\item{plotName}{u} +} +\description{ +This function calculates the -users specified- likelihood for random model input. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMapping.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMapping.Rd new file mode 100644 index 0000000..d8e2b9f --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMapping.Rd @@ -0,0 +1,22 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/outputMapping.R +\name{musoMapping} +\alias{musoMapping} +\title{musoMapping} +\usage{ +musoMapping(code, mapData=NULL) +} +\arguments{ +\item{code}{the MuSo outputcode} + +\item{mapData}{updateMusomapping generated matrix} +} +\value{ +The name of the Biome-BGCMuSo output code (e.g. if code is 3009 this function should return GPP to the user) +} +\description{ +musoMapping can provide the user the name of a Biome-BGCMuSo output code. Within Biome-BGCMuSo the state variables and fluxes are marked by integer numbers. In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is utilized by this function. This function converts variable codes into names musoMappingFind does the opposite. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMappingFind.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMappingFind.Rd new file mode 100644 index 0000000..22710a6 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMappingFind.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/outputMapping.R +\name{musoMappingFind} +\alias{musoMappingFind} +\title{musoMappingFind} +\usage{ +musoMapping(code, mapData=NULL) +} +\arguments{ +\item{variable}{If this is null, return the whole mapping table. In other cases search for the variable code} +} +\value{ +The code of the specific output variable name +} +\description{ +musoMappingFind can provide us the code of the Biome-BGCMuSo output variable name. Within Biome-BGCMuSo the state variables and fluxes are marked by integer numbers. In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is utilized by this function. This function converts variable names into codes. musoMapping does the opposite. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMonte.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMonte.Rd new file mode 100644 index 0000000..04732a4 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoMonte.Rd @@ -0,0 +1,57 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/musoMonte.R +\name{musoMonte} +\alias{musoMonte} +\title{musoMonte} +\usage{ +musoMonte( + settings = NULL, + parameters = NULL, + inputDir = "./", + outLoc = "./calib", + iterations = 10, + preTag = "mont-", + outputType = "moreCsv", + fun = mean, + varIndex = 1, + outVars = NULL, + silent = TRUE, + skipSpinup = TRUE, + debugging = FALSE, + keepEpc = FALSE, + constrains = NULL, + skipZero = TRUE, + postProcString = NULL, + modifyOut = TRUE, + ... +) +} +\arguments{ +\item{settings}{A list of environmental variables for the Monte Carlo experiment. These settings are generated by the setupMuso function. By default the settings parameter is generated automatically.} + +\item{parameters}{This is a dataframe (heterogeneous data-matrix), where the first column is the name of the parameter, the second is a numeric vector of the rownumbers of the given variable in the input EPC file, and the last two columns describe the minimum and the maximum of the parameter (i.e. the parameter ranges), defining the interval for the randomization.} + +\item{inputDir}{The location of the input directory for the Biome-BGCMuSo model. This directory must contain a viable pack of all input files and the model executable file.} + +\item{iterations}{Number of the Monte Carlo simulations.} + +\item{preTag}{This defines the name of the output files. This tag will be re-used so that the results will be like preTag-1.csv, preTag-2csv...} + +\item{outputType}{This parameter can be "oneCsv", "moreCsv", and "netCDF". If "oneCsv" is chosen the function creates one large csv file for all of the runs. If "moreCsv" is chosen, every model output goes to separate files. If netCDF is selected the output will be stored in a netCDF file. The default value of the outputTypes is "moreCsv". Note that netCDF is not implemented yet.} + +\item{fun}{If you select a variable from the possible outputs (by using the varIndex parameter), you have to provide a function which maps to a subset of real numbers. The most frequent possibilities are: mean, min, max, var, but you can define any function for your needs.} + +\item{varIndex}{This parameter specifies which parameter will be used for the Monte Carlo experiment from the output list of Biome-BGCMuSo (defined by the INI file). You can extract this information from the INI files. At the output parameter specifications, the parameter order will determine this number. For example, if you have set these output parameters: 412, 874, 926, 888, and you want to use 926 for the experiment, you should specify varIndex as 3.} + +\item{debugging}{If you set this parameter, you can save every logfile, and RBBGCMuso will select those which contains errors. This is useful to study why the model crashes with a given parameter set.} + +\item{keepEpc}{If you set keepEpc as TRUE, it will save every selected EPC file, and move the wrong ones into the WRONGEPC directory.} + +\item{calibrationPar}{You might want to change some parameters in your EPC file before you run the modell. You have to select the appropirate model parameters here. You can refer to the parameters by the number of the line in the EPC file where the variables are defined. The indexing of the lines starts at 1, and each line matters (like in any simple text file). You should use a vector for this selection like c(1,5,8)} +} +\description{ +This function executes the Monte Carlo experiment with Biome-BGCMuSo (musoRand is called by this function). It samples the selected model parameters within user defined ranges from conditional multivariate uniform distribution, and then runs the model for each run. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoQuickEffect.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoQuickEffect.Rd new file mode 100644 index 0000000..57879e4 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoQuickEffect.Rd @@ -0,0 +1,40 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/quickeffect.R +\name{musoQuickEffect} +\alias{musoQuickEffect} +\title{musoQuickEffect} +\usage{ +musoQuickEffect( + settings = setupMuso(), + calibrationPar = NULL, + startVal, + endVal, + nSteps = 1, + fileToChange = "epc", + modifyOriginal = TRUE, + outVar, + parName = "parVal", + yearNum = 1, + year = (settings$startYear + yearNum - 1) +) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{startVal}{The initial value of the given parameter.} + +\item{endVal}{The maximum of the given parameter.} + +\item{nSteps}{Number of steps from startVal to endVal. It equals the number of simulations, and number of curves on the final plot.} + +\item{fileTochange}{Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user.} +} +\value{ +Graph showing the runs with the selected parameters with color coding. The graph will show data from the last simulation year. +} +\description{ +This function changes a chosen parameter from the INI or from the ecophysiological constants file (EPC) within a predefined range (defined by the user), and visualizes the effect of the change on the selected output variable. The user has to specify the parameter, the interval for the parameter effect test, and the number of steps. This function focuses only on one parameter. The so-called paramSweep function can manipulate multiple INI/EPC parameters and visualize the results. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoRand.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoRand.Rd new file mode 100644 index 0000000..33b91e6 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoRand.Rd @@ -0,0 +1,27 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/musoRand.R +\name{musoRand} +\alias{musoRand} +\title{musoRand} +\usage{ +musoRand( + parameters, + iterations = 3000, + fileType = "epc", + constrains = NULL, + burnin = NULL +) +} +\arguments{ +\item{parameters}{This is a dataframe (heterogeneous data-matrix), where the first column is the name of the parameter, the second is a numeric vector of the rownumbers of the given variable in the input EPC file, and the last two columns describe the minimum and the maximum of the parameter (i.e. the parameter ranges), defining the interval for the randomization.} + +\item{constrains}{This is a matrix wich specify the constrain rules for the sampling. Parameter dependencies are described in the Biome-BGCMuSo User's Guide. Further informations is coming soon.} + +\item{iteration}{The number of samples for the Monte-Carlo experiment. We propose to use at least 3000 iteration because it is generally fast and it can be subsampled later at any time.} +} +\description{ +This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoSensi.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoSensi.Rd new file mode 100644 index 0000000..13afa5e --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/musoSensi.Rd @@ -0,0 +1,52 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/musoSensi.R +\name{musoSensi} +\alias{musoSensi} +\title{musoSensi} +\usage{ +musoSensi( + monteCarloFile = NULL, + parameters = NULL, + settings = NULL, + inputDir = "./", + outLoc = "./calib", + outVars = NULL, + iterations = 30, + preTag = "mont-", + outputType = "moreCsv", + fun = mean, + varIndex = 1, + outputFile = "sensitivity.csv", + plotName = "sensitivity.png", + plotTitle = "Sensitivity", + skipSpinup = TRUE, + skipZero = TRUE, + postProcString = NULL, + modifyOut = TRUE, + dpi = 300 +) +} +\arguments{ +\item{parameters}{This is a dataframe (heterogen data-matrix), which first column is the name of the parameters, the second is a numeric vector of the rownumbers of the given variable in the epc-fie, the last two column consist the endpont of the parameter-ranges, where the parameters will be randomized.} + +\item{settings}{A list of montecarlos environmental variables. It is generated by the setupMuso() function. In default the settings parameter is generated automatically.} + +\item{inputDir}{The location of the input directory, this directory must content a viable pack of all inputfiles and the executable file.} + +\item{iterations}{number of the monteCarlo run.} + +\item{preTag}{It will be the name of the output files. For example preTag-1.csv, pretag-2csv...} + +\item{outputType}{This parameter can be "oneCsv", "moreCsv", and "netCDF". If "oneCsv" is choosen the function create 1 big csv file for all of the runs, if "moreCsv" is choosen, every modell output goes to separate files, if netCDF is selected the outputs will be put in a netCDF file. The default value of the outputTypes is "moreCsv". netCDF is not implemented yet.} + +\item{fun}{If you select a variable from the possible outputs (with specify the varIndex parameter), you have to provide a function which maps to a subset of real numbers. The most frequent possibilities are: mean, min, max, var, but you can define any function for your need.} + +\item{varIndex}{This parameter specify which parameter of the output will be used. You can extract this information from the ini-files. At the output parameter specifications, the parameters order will determine this number. For example, if you have set these output parameters: 412, 874, 926, 888, and you want to use 926, you should address varIndex with 3.} + +\item{skipSpinup}{With this parameter, you can turn of the spinup phase after the first spinup. I will decrease the time significantly.} + +\item{calibrationPar}{You may want to change some parameters in your epc file, before you run the modell. You have to select the appropirate modell parameters. You can refence to these with the number of the line in the epc file where the variables are. It indexes from one. You should use a vector for this, like: c(1,5,8)} +} +\description{ +This function does regression based sensitivity analysis based on the output of musoMonte. +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/normalMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/normalMuso.Rd new file mode 100644 index 0000000..972f667 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/normalMuso.Rd @@ -0,0 +1,45 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/normalMuso.R +\name{normalMuso} +\alias{normalMuso} +\title{normalMuso} +\usage{ +normalMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, +keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{parameters}{Using normalMuso it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).} + +\item{timee}{The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet.} + +\item{debugging}{If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory and stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.} + +\item{logfilename}{If you would like to set a specific name for your logfiles you can set this via the logfile parameter.} + +\item{keepEpc}{If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.} + +\item{export}{If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv.} + +\item{silent}{If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.} + +\item{aggressive}{It deletes all previous model-outputs from previous model runs.} + +\item{leapYear}{Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years.} + +\item{binaryPlace}{The directory for the binary output files (see the keepBinary parameter).} + +\item{fileToChange}{You can change any line of the EPC or the INI file prior to model execution. All you need to do is to specify with this variable which file you want to change. Two options possible: "EPC" or "INI"} + +\item{keepBinary}{By default RBBGCMuso keeps the working environment as clean as possible, thus deletes all the regular output files. The results are directly written to the standard output (e.g. to the screen), but you can redirect it and save them to a variable. Alternatively, you can export your results to the desired destination in a desired format. Through the keepBinary parameter you can set RBBGCMuso to keep the binary output files. If you would like to set the location of the binary output, please take a look at the binaryPlace argument.} +} +\value{ +The simulation output matrix, where the columns are the chosen variables and each row is a daily/monthly/annual data. +} +\description{ +This function optionally changes the EPC file and runs the Biome-BGCMuSo model in normal phase and reads its output file in a well-structured way with debugging features. (Execution of spinup phase is possible with spinupMuso.) Prerequisite of normalMuso is the existence of the endpoint file (which is the result of the spinup phase and contains initial conditions for the simulation). +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/numcut.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/numcut.Rd new file mode 100644 index 0000000..61994a1 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/numcut.Rd @@ -0,0 +1,15 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/stamplog.R +\name{numcut} +\alias{numcut} +\title{This function returns only the starting numbers of a string} +\usage{ +numcut(string) +} +\description{ +This function returns only the starting numbers of a string +} +\author{ +Roland Hollos +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/numcutall.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/numcutall.Rd new file mode 100644 index 0000000..e15b30d --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/numcutall.Rd @@ -0,0 +1,15 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/stamplog.R +\name{numcutall} +\alias{numcutall} +\title{numcutall} +\usage{ +numcutall(vector) +} +\description{ +apply numcut for all elements of a string vector +} +\author{ +Roland Hollos +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/optiMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/optiMuso.Rd new file mode 100644 index 0000000..6543dc9 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/optiMuso.Rd @@ -0,0 +1,75 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/calibration.R +\name{optiMuso} +\alias{optiMuso} +\title{optiMuso} +\usage{ +optiMuso( + measuredData, + parameters = NULL, + startDate = NULL, + endDate = NULL, + formatString = "\%Y-\%m-\%d", + dataVar, + outLoc = "./calib", + preTag = "cal-", + settings = setupMuso(), + outVars = NULL, + iterations = 30, + skipSpinup = TRUE, + plotName = "calib.jpg", + modifyOriginal = TRUE, + likelihood, + uncertainity = NULL, + naVal = NULL, + postProcString = NULL, + w = NULL, + lg = FALSE, + parallel = TRUE +) +} +\arguments{ +\item{parameters}{b} + +\item{startDate}{d} + +\item{endDate}{e} + +\item{formatString}{a} + +\item{outLoc}{c} + +\item{settings}{e} + +\item{iterations}{c} + +\item{skipSpinup}{a} + +\item{plotName}{u} + +\item{likelihood}{d} + +\item{measuredDataFile}{a} + +\item{sep}{c} + +\item{filterCol}{a} + +\item{filterVal}{b} + +\item{selVar}{c} + +\item{pretag}{a} + +\item{calPar}{a} + +\item{constrains}{d} + +\item{leapYear}{b} +} +\description{ +This function calculates the -users specified- likelihood for random model input. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/paramSweep.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/paramSweep.Rd new file mode 100644 index 0000000..8933dce --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/paramSweep.Rd @@ -0,0 +1,34 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/parametersweep.R +\name{paramSweep} +\alias{paramSweep} +\title{paramSweep} +\usage{ +paramSweep( + inputDir = "./", + parameters = NULL, + outputDir = NULL, + iterations = 10, + outVar = "daily_gpp", + htmlOutName = "paramsweep.html" +) +} +\arguments{ +\item{inputDir}{The directory which contains the MuSo model's ini files} + +\item{parameters}{A csv file's path which contains the input parameters. The first row must be the name of the parameters, the second is the index of the parameters(row index in the input file), the third is the minimum value of the parameters, the forth is the maximum value of the parameters. If it is not privided, a filebrowser will pop up.} + +\item{outputDir}{The path of the directory where the html file will be generated.} + +\item{iterations}{The number of changes in the parameter} + +\item{outVar}{The name of the output variable to plot, of the MuSo code of it.} + +\item{htmlOutName}{The name of the rendered html file} +} +\description{ +This function is for testing the modell response to change a set of input variables. It generates an html file which contains a set of graphics of the ... +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/plotMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/plotMuso.Rd new file mode 100644 index 0000000..0e33757 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/plotMuso.Rd @@ -0,0 +1,46 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/plotMuso.R +\name{plotMuso} +\alias{plotMuso} +\title{plot the Biome-BGCMuSo output} +\usage{ +plotMuso(settings, variable, +timee="d", silent=TRUE, +debugging=FALSE, keepEpc=FALSE, +logfilename=NULL, aggressive=FALSE, +leapYear=FALSE, export=FALSE) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{variable}{Column number of the output variable which should be plotted, or "all" if you have less than 10 variables. In this case the function will plot everything in a matrix layout.} + +\item{timee}{The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet.} + +\item{silent}{If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.} + +\item{debugging}{If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory and stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.} + +\item{keepEpc}{If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.} + +\item{logfilename}{If you would like to set a specific name for your logfiles you can set this via the logfile parameter.} + +\item{aggressive}{It deletes all previous model-outputs from previous model runs.} + +\item{leapYear}{Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years.} + +\item{plotType}{There are two options implemented by now: continuous time series ("cts") or disctrete time series ("dts")} + +\item{skipSpinup}{If TRUE, the function won't perform the spinup simulation. In this case the endpoint file must exist that provides initial conditions for the run.} + +\item{export}{If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv.} +} +\value{ +It depends on the export parameter. The function returns with a matrix with the model output, or writes this into a file, which is defined previously +} +\description{ +This function runs the Biome-BGCMuSo model and reads its output file in a well structured way, and after that it plots the results automatically. plotMuso is a convenient and quick method to create nice graphs from Biome-BGCMuSo output which is quite painful in other environments. +} +\author{ +Roland HOLLOS, Dora HIDY +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/plotMusoWithData.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/plotMusoWithData.Rd new file mode 100644 index 0000000..d7b8b3d --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/plotMusoWithData.Rd @@ -0,0 +1,35 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/plotMuso.R +\name{plotMusoWithData} +\alias{plotMusoWithData} +\title{plot the Biome-BGCMuSo model output with observation data} +\usage{ +plotMuso(settings, variable, +timee="d", silent=TRUE, +debugging=FALSE, keepEpc=FALSE, +logfilename=NULL, aggressive=FALSE, +leapYear=FALSE, export=FALSE) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{sep}{This is the separator symbol used in the measurement file (that is supposed to be a delimited text file)} + +\item{savePlot}{It it is specified, the plot will be saved in a graphical format specified by the immanent extension. For example, it the savePlot is set to image01.png then a PNG graphics file will be created.} + +\item{variable}{The name of the output variable to plot} + +\item{NACHAR}{This is not implemented yet} + +\item{csvFile}{This specifies the filename of the measurements. It must contain a header. Typically this is a CSV file.} + +\item{calibrationPar}{You might want to change some parameters in your EPC file before running the model. The function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)} + +\item{parameters}{Using the function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).} +} +\description{ +This function runs the Biome-BGCMuSo model and reads its output file in a well structured way, and after that it plots the results automatically along with a given measurement dataset provided by the user. plotMusoWithData is a convenient and quick method to create nice graphs from Biome-BGCMuSo output which is quite painful in other environments. +} +\author{ +Roland HOLLOS, Dora HIDY +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/postProcMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/postProcMuso.Rd new file mode 100644 index 0000000..c5a17c2 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/postProcMuso.Rd @@ -0,0 +1,12 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/postProcString.R +\name{postProcMuso} +\alias{postProcMuso} +\title{postProcMuso} +\usage{ +postProcMuso(modelData, procString) +} +\description{ +This is a function wich provides some minimal post processing capabilities +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/putOutVars.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/putOutVars.Rd new file mode 100644 index 0000000..297f474 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/putOutVars.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/putOutVars.R +\name{putOutVars} +\alias{putOutVars} +\title{putOutVars} +\usage{ +putOutVars(iniFile, outputVars, modifyOriginal = FALSE) +} +\arguments{ +\item{outputVars}{List of the output codes} + +\item{IniFile}{The name of the normal ini file.} +} +\description{ +This function is for adding variables in the inifiles. +} +\author{ +Roland Hollos +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/randEpc.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/randEpc.Rd new file mode 100644 index 0000000..4a83540 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/randEpc.Rd @@ -0,0 +1,29 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/genEpc.R +\name{randEpc} +\alias{randEpc} +\title{randEpc} +\usage{ +randEpc( + parameterFile = "parameters.csv", + location = "./epcDir", + sourceEpc = "maize.epc", + iterations = 1000, + constrains = NULL +) +} +\arguments{ +\item{parameterFile}{parameters.csv file location} + +\item{location}{output location directory} + +\item{sourceEpc}{the original epc file-the template} + +\item{iteration}{the number of iterations} +} +\description{ +randEpc is a random epc creator based on musoMonte +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/readErrors.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/readErrors.Rd new file mode 100644 index 0000000..a5723da --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/readErrors.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{readErrors} +\alias{readErrors} +\title{readErrors} +\usage{ +readErrors(outputLoc, logfiles, type = "both") +} +\arguments{ +\item{outputLoc}{This is the location of the output file.} + +\item{logfiles}{These are the names of the logfiles.} +} +\value{ +vector with 0 and 1 values, 1, if succed, 0 if not. The first is the spinup run, the second is the normal. +} +\description{ +This function reads the spinup and the normal logfiles and gives back the last line which indicates weather there are any errors during the model execution or not. +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/readObservedData.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/readObservedData.Rd new file mode 100644 index 0000000..e079014 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/readObservedData.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{readObservedData} +\alias{readObservedData} +\title{readMeasuredMuso} +\usage{ +readObservedData( + inFile, + naString = NULL, + sep = ",", + leapYearHandling = TRUE, + convert.var = NULL, + convert.scalar = 1, + convert.fun = (function(x) { x * convert.scalar }), + convert.file = NULL, + filterCol = NULL, + filterVal = 1, + selVar = NULL +) +} +\description{ +MuSo data reader +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/runMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/runMuso.Rd new file mode 100644 index 0000000..dba37f0 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/runMuso.Rd @@ -0,0 +1,49 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/runMuso.R +\name{runMuso} +\alias{runMuso} +\title{runMuso} +\usage{ +calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, +keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{timee}{The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet.} + +\item{debugging}{If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory to stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.} + +\item{keepEpc}{If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.} + +\item{export}{If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv.} + +\item{silent}{IIf you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.} + +\item{aggressive}{It deletes all previous model-outputs from previous model runs.} + +\item{parameters}{Using normalMuso it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).} + +\item{logfilename}{If you would like to set a specific name for your logfiles you can set this via the logfile parameter.} + +\item{leapYear}{Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years.} + +\item{keepBinary}{By default RBBGCMuso keeps the working environment as clean as possible, thus deletes all the regular output files. The results are directly written to the standard output (e.g. to the screen), but you can redirect it and save them to a variable. Alternatively, you can export your results to the desired destination in a desired format. Through the keepBinary parameter you can set RBBGCMuso to keep the binary output files. If you would like to set the location of the binary output, please take a look at the binaryPlace argument.} + +\item{binaryPlace}{The directory for the binary output files (see the keepBinary parameter).} + +\item{fileToChange}{You can change any line of the EPC or the INI file prior to model execution. All you need to do is to specify with this variable which file you want to change. Two options possible: "EPC" or "INI"} + +\item{skipSpinup}{If this is set to TRUE, runMuso will not perform the spinup simulation. This is of course means that the endpoint file (initial conditions) must be available for the normal INI file. This option might be extremely useful to speed up multiple model execution. In cropland related simulations due to site history the EPC file used in the normal phase might differ from the one used in the spinup phase, which means that the spinup is the same even if we change the parameterization for the normal phase. In this situation skipSpinup is really useful.} + +\item{prettyOut}{If this parameter is to TRUE then date will provided as the R-style Date type, and separate year, month and day vectors. In typical cases the user should use this option.} +} +\value{ +No return, outputs are written to file +} +\description{ +This function runs the Biome-BGCMuSo model (with option to change the EPC file), then it reads its output file in a well-structured way. As the result is passed to R, the results can be easily post-processed in R environment. +} +\author{ +Roland HOLL\'{O}S +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/rungetMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/rungetMuso.Rd new file mode 100644 index 0000000..5f44c48 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/rungetMuso.Rd @@ -0,0 +1,37 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/rungetMuso.R +\name{rungetMuso} +\alias{rungetMuso} +\title{rungetMuso} +\usage{ +rungetMuso(settings, timee="d", debugging=FALSE, logfilename=NULL, +keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) +} +\arguments{ +\item{settings}{You have to run the setupMuso function before rungetMuso. It is its output which contains all of the necessary system variables. It sets the whole environment} + +\item{timee}{The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly} + +\item{debugging}{If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles} + +\item{logfilename}{If you want to set a specific name for your logfiles you can set this via logfile parameter} + +\item{keepEpc}{If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.} + +\item{export}{if it is yes or you give a filename here, it converts the output to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.} + +\item{silent}{If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.} + +\item{aggressive}{It deletes every possible modell-outputs from the previous modell runs.} + +\item{leapYear}{Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.} +} +\value{ +It depends on the export parameter. The function returns with a matrix with the modell output, or writes this in a file, which is given previously +} +\description{ +This function runs the BBGC-MuSo model and reads in its outputfile in a very structured way. +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/saveAllMusoPlots.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/saveAllMusoPlots.Rd new file mode 100644 index 0000000..4f07af1 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/saveAllMusoPlots.Rd @@ -0,0 +1,31 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/plotMuso.R +\name{saveAllMusoPlots} +\alias{saveAllMusoPlots} +\title{saveAllMusoPlots} +\usage{ +saveAllMusoPlots( + settings = NULL, + plotName = ".png", + silent = TRUE, + type = "line", + outFile = "annual.csv", + colour = "blue", + skipSpinup = FALSE +) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{plotName}{The basename for the output plots} + +\item{silent}{if true do not suspect for printfs...} + +\item{destination}{The destination for the output plots, it not exits the function will create it.} +} +\description{ +This simple function takes the parameters from the ini files and generates graphics for all output variable. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/setupMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/setupMuso.Rd new file mode 100644 index 0000000..e2d9502 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/setupMuso.Rd @@ -0,0 +1,64 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/setupMuso.R +\name{setupMuso} +\alias{setupMuso} +\title{setupMuso} +\usage{ +setupMuso(executable=NULL, parallel = F, calibrationPar =c(1), +outputLoc=NULL, inputLoc=NULL, +metInput=NULL, CO2Input=NULL, +plantInput=NULL, thinInput=NULL, +mowInput=NULL, grazInput=NULL, +harvInput=NULL, plougInput=NULL, +fertInput=NULL, irrInput=NULL, +nitInput=NULL, iniInput=NULL, epcInput=NULL) +} +\arguments{ +\item{executable}{This parameter stores the location (directory) of the model-executable file. In normal usage, you don't have to set this parameter, because the RBBGCMuso package always contains the latest model executable. In spite of this, if you would like to use this package for model development or just want to use different model version (for example for comparison), you will find this option useful} + +\item{parallel}{Set this variable to TRUE if you would like to implement parallel execution of the model} + +\item{calibrationPar}{You might want to change some parameters in your EPC file before running the model. setupMuso offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)} + +\item{outputLoc}{With this parameter the user can specify the directory for the model output. The syntax is simple, for example: outputLoc="/place/of/the/outputs/" or outputLoc="C:/my_model_directory/". Note that this output directory is specified by the user within the INI file, which means that the outputLoc parameter overrides the INI settings if specified.} + +\item{modelOutputs}{This parameter contains the list of the codes that defines the required model output variables. Check the Biome-BGCMuS website for the complete list of possible output variables at http://agromo.agrar.mta.hu/bbgc/download.html} + +\item{inputLoc}{Usually this is the root (or base) directory where the user stores the INI files for the model. If the working directory is set by the user, this parameter can be skipped.} + +\item{metInput}{Via the metInput parameter the user can specify the location of the input meteorological files. By default the package reads this information from the INI files.} + +\item{CO2Input}{Via the CO2Input parameter the user can specify the location of the CO2 data file. By default the package reads this information from the INI files.} + +\item{plantInput}{Via the plantInput parameter, the user can specify the location of the the file that contains the planting information. By default the package reads this information from the INI files.} + +\item{thinInput}{Via the thinInput parameter,the user can specify the location of the file that contains the thinning information. By default the package reads this information from the INI files.} + +\item{mowInput}{Via the mowInput parameter, the user can specify the location of the file that contains the mowing (i.e. grass cutting) information. By default the package reads this information from the INI files.} + +\item{grazInput}{Via the grazInput parameter, the user can specify the location of the file that contains the grazing information. By default the package reads this information from the INI files.} + +\item{harvInput}{Via the harvInput parameter, the user can specify the location of the file that contains the harvesting information. By default the package reads this information from the INI files.} + +\item{plougInput}{Via the plougInput parameter, the user can specify the location of the file that contains the ploughing information. By default the package reads this information from the INI files.} + +\item{fertInput}{Via the fertInput parameter, ythe user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files.} + +\item{irrInput}{Via the irrInput parameter, the user can specify the location of the file that contains the irrigation information. By default the package reads this information from the INI files.} + +\item{nitInput}{Via the nitInput parameter, the user can specify the location of the file that contains the nitrogen deposition data. By default the package reads this information from the INI files.} + +\item{iniInput}{Via the iniInput parameter, the user can specify the location of the INI files. By default the package reads the INI files from the working directory.} + +\item{epcInput}{Via the epcInput parameter, the user can specify the location of the EPC data file. By default the package reads this information from the INI files.} +} +\value{ +The output is a the model settings list wich contains the following elements: +executable, calibrationPar, outputLoc, outputName, inputLoc, iniInput, metInput, epcInput,thinInput,CO2Input, mowInput, grazInput, harvInput, plougInput, fertInput,rrInput, nitInput, inputFiles, numData, startyear, numYears, outputVars +} +\description{ +The setupMuso is fundamental for the Biome-BGCMuSo model related other functions like runMuso, spinupMuso, normalMuso, rungetMuso, as it sets the model's environment. The function reads the INI files from a given directory, analyzes them with error checking, and creates a data structure in R that contains the complete information content for the simulation. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/spinupMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/spinupMuso.Rd new file mode 100644 index 0000000..6f31f41 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/spinupMuso.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/spinupMuso.R +\name{spinupMuso} +\alias{spinupMuso} +\title{Runs the Biome-BGCMuSo model in spinup phase (execution of normal phase is possible with normalMuso) with debugging features.} +\usage{ +spinupMuso(settings, parameters=NULL, debugging=FALSE, +logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE) +} +\arguments{ +\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.} + +\item{parameters}{|||| In the parameters variable you have set the row indices of the variables that you wish to change. In this parameter you can provide an exact value for them in a vector form like c(1,2,3,4)} + +\item{debugging}{If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory to stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.} + +\item{logfilename}{If you would like to set a specific name for the logfiles you can set this via the logfilename parameter} + +\item{keepEpc}{If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.} + +\item{silent}{If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.} + +\item{aggressive}{It deletes all previous model-outputs from previous model runs.} +} +\value{ +No return, outputs are written to file +} +\description{ +This function runs the Biome-BGCMuSo model in spinup phase. +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/stamp.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/stamp.Rd new file mode 100644 index 0000000..13f6b1c --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/stamp.Rd @@ -0,0 +1,15 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/stamplog.R +\name{stamp} +\alias{stamp} +\title{It gives back a stamp wich is the maximum number of the output numcall} +\usage{ +stamp(path = "./") +} +\description{ +It gives back a stamp wich is the maximum number of the output numcall +} +\author{ +Roland Hollos +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/stampAndDir.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/stampAndDir.Rd new file mode 100644 index 0000000..c30516e --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/stampAndDir.Rd @@ -0,0 +1,28 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{stampAndDir} +\alias{stampAndDir} +\title{stampAndCopy} +\usage{ +stampAndDir( + outputLoc, + names, + stampDir, + wrongDir, + type = "output", + errorsign, + logfiles +) +} +\arguments{ +\item{outputLoc}{This is the location of the output files.} + +\item{outputNames}{These are the prefixes of the logfiles} +} +\value{ +Output files with their paths +} +\description{ +This function gives us the model output files with their paths +} +\keyword{internal} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/supportedMuso.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/supportedMuso.Rd new file mode 100644 index 0000000..84681d0 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/supportedMuso.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{supportedMuso} +\alias{supportedMuso} +\title{supportedMuso} +\usage{ +supportedMuso(type="outputs") +} +\arguments{ +\item{type}{"outputs" or "message", if you choose "outputs", it gives you a simple vector of the formats, if you choose "message", it gives you a full sentence which contains the same information.} +} +\value{ +if you choose "outputs", it gives you a simple vector of the formats, if you choose "message", it gives you a full sentence which contains the same information. +} +\description{ +A function for getting the list of the output formats which is supported by RBBGCMuso +} +\author{ +Roland Hollos +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/updateMusoMapping.Rd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/updateMusoMapping.Rd new file mode 100644 index 0000000..ecdffc0 --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/man/updateMusoMapping.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/outputMapping.R +\name{updateMusoMapping} +\alias{updateMusoMapping} +\title{updateMusoMapping} +\usage{ +updateMusoMapping(excelName, dest = "./", version = getOption("RMuso_version")) +} +\arguments{ +\item{excelName}{Name of the excelfile which contains the parameters} +} +\value{ +The output code-variable matrix, and also the function changes the global variable +} +\description{ +This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variablesare marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order! +} +\author{ +Roland HOLLOS +} diff --git a/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/vignettes/my-vignette.Rmd b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/vignettes/my-vignette.Rmd new file mode 100644 index 0000000..aace6af --- /dev/null +++ b/RBBGCMuso.Rcheck/00_pkg_src/RBBGCMuso/vignettes/my-vignette.Rmd @@ -0,0 +1,58 @@ +--- +title: "Vignette Title" +author: "Vignette Author" +date: "`r Sys.Date()`" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{Vignette Title} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + +Vignettes are long form documentation commonly included in packages. Because they are part of the distribution of the package, they need to be as compact as possible. The `html_vignette` output type provides a custom style sheet (and tweaks some options) to ensure that the resulting html is as small as possible. The `html_vignette` format: + +- Never uses retina figures +- Has a smaller default figure size +- Uses a custom CSS stylesheet instead of the default Twitter Bootstrap style + +## Vignette Info + +Note the various macros within the `vignette` section of the metadata block above. These are required in order to instruct R how to build the vignette. Note that you should change the `title` field and the `\VignetteIndexEntry` to match the title of your vignette. + +## Styles + +The `html_vignette` template includes a basic CSS theme. To override this theme you can specify your own CSS in the document metadata as follows: + + output: + rmarkdown::html_vignette: + css: mystyles.css + +## Figures + +The figure sizes have been customised so that you can easily put two images side-by-side. + +```{r, fig.show='hold'} +plot(1:10) +plot(10:1) +``` + +You can enable figure captions by `fig_caption: yes` in YAML: + + output: + rmarkdown::html_vignette: + fig_caption: yes + +Then you can use the chunk option `fig.cap = "Your figure caption."` in **knitr**. + +## More Examples + +You can write math expressions, e.g. $Y = X\beta + \epsilon$, footnotes^[A footnote here.], and tables, e.g. using `knitr::kable()`. + +```{r, echo=FALSE, results='asis'} +knitr::kable(head(mtcars, 10)) +``` + +Also a quote using `>`: + +> "He who gives up [code] safety for [code] speed deserves neither." +([via](https://twitter.com/hadleywickham/status/504368538874703872)) diff --git a/RBBGCMuso.Rcheck/00check.log b/RBBGCMuso.Rcheck/00check.log new file mode 100644 index 0000000..1f97dbc --- /dev/null +++ b/RBBGCMuso.Rcheck/00check.log @@ -0,0 +1,548 @@ +* using log directory 'E:/GIT/RBBGCMuso/RBBGCMuso.Rcheck' +* using R version 4.2.2 (2022-10-31 ucrt) +* using platform: x86_64-w64-mingw32 (64-bit) +* using session charset: UTF-8 +* using options '--no-manual --as-cran' +* checking for file 'RBBGCMuso/DESCRIPTION' ... OK +* this is package 'RBBGCMuso' version '0.7.1' +* checking package namespace information ... OK +* checking package dependencies ... NOTE +Imports includes 22 non-default packages. +Importing from so many packages makes the package vulnerable to any of +them becoming unavailable. Move as many as possible to Suggests and +use conditionally. +* checking if this is a source package ... NOTE +Found the following apparent object files/libraries: + inst/examples/hhs/cygwin1.dll +Object files/libraries should not be included in a source package. +* checking if there is a namespace ... OK +* checking for executable files ... WARNING +Found the following executable files: + inst/examples/hhs/cygwin1.dll + inst/examples/hhs/muso + inst/examples/hhs/muso.exe + inst/examples/hhs/muso7.0b7.exe + inst/mtclim43 + inst/mtclim43.exe +Source packages should not contain undeclared executable files. +See section 'Package structure' in the 'Writing R Extensions' manual. +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking serialization versions ... OK +* checking whether package 'RBBGCMuso' can be installed ... WARNING +Found the following significant warnings: + Note: possible error in 'changemulline(filename = epc[1], ': unused argument (filename = epc[1]) + Note: possible error in 'changemulline(filename = iniInput[1], ': unused argument (filename = iniInput[1]) + Note: possible error in 'musoDate(startYear = startYear, ': unused argument (corrigated = FALSE) + Note: possible error in 'changemulline(filePaths = basename(sourceEpc), ': unused arguments (fileOut = epcOut, fileToChange = "epc") + Note: possible error in 'musoDate(settings$startYear, ': unused argument (corrigated = FALSE) +See 'E:/GIT/RBBGCMuso/RBBGCMuso.Rcheck/00install.out' for details. +Information on the location(s) of code generating the 'Note's can be +obtained by re-running with environment variable R_KEEP_PKG_SOURCE set +to 'yes'. +* checking installed package size ... NOTE + installed size is 13.4Mb + sub-directories of 1Mb or more: + examples 12.2Mb +* checking package directory ... OK +* checking for future file timestamps ... OK +* checking 'build' directory ... OK +* checking DESCRIPTION meta-information ... NOTE +Packages listed in more than one of Depends, Imports, Suggests, Enhances: + 'tcltk' 'rmarkdown' +A package should be listed in only one of these fields. +* checking top-level files ... OK +* checking for left-over files ... OK +* checking index information ... OK +* checking package subdirectories ... WARNING +Found the following non-empty subdirectories of 'inst' also used by R: + inst/data +It is recommended not to interfere with package subdirectories used by +R. +* checking R files for non-ASCII characters ... OK +* checking R files for syntax errors ... OK +* checking whether the package can be loaded ... OK +* checking whether the package can be loaded with stated dependencies ... OK +* checking whether the package can be unloaded cleanly ... OK +* checking whether the namespace can be loaded with stated dependencies ... OK +* checking whether the namespace can be unloaded cleanly ... OK +* checking loading without being on the library search path ... OK +* checking dependencies in R code ... NOTE +Namespaces in Imports field not imported from: + 'Boruta' 'Rcpp' 'grDevices' 'graphics' 'ncdf4' + All declared Imports should be used. +* checking S3 generic/method consistency ... OK +* checking replacement functions ... OK +* checking foreign function calls ... OK +* checking R code for possible problems ... [14s] NOTE +File 'RBBGCMuso/R/atStart.R': + .onLoad calls: + cat(sprintf("This is RBBGCMuso version 1.0\nDefault Biome-BGCMuSo version: %d", RMuso_version)) + +Package startup functions should use 'packageStartupMessage' to + generate messages. +See section 'Good practice' in '?.onAttach'. + +This is RBBGCMuso version 1.0 +Default Biome-BGCMuSo version: 7agroLikelihood : : no visible global function definition for + 'dnorm' +calibrateMuso: no visible global function definition for 'lines' +calibrateMuso: no visible global function definition for 'polygon' +calibrateMuso: no visible global function definition for 'points' +checkMeteoBGC : sradAvgShortestDay: no visible global function + definition for 'na.omit' +checkMeteoBGC : sradAvgLongestDay: no visible global function + definition for 'na.omit' +corrigMuso: no visible global function definition for 'musoLeapYears' +createSoilFile : createMusoLayers: no visible binding for global + variable '.' +multiSiteCalib : : no visible global function definition for + 'sd' +multiSiteCalib: no visible global function definition for 'svg' +multiSiteCalib: no visible global function definition for 'dev.off' +multiSiteCalib: no visible global function definition for 'lm' +multiSiteCalib: no visible global function definition for 'png' +multiSiteCalib: no visible global function definition for 'par' +musoGlue: no visible global function definition for 'quantile' +musoGlue : : no visible global function definition for + 'quantile' +musoGlue: no visible global function definition for 'pdf' +musoGlue: no visible global function definition for 'par' +musoGlue: no visible global function definition for 'abline' +musoGlue: no visible global function definition for 'dev.off' +musoMapping: no visible binding for global variable 'mMapping' +musoMonte: no visible binding for global variable 'procString' +musoQuickEffect: no visible binding for global variable 'parVal' +musoSensi : doSensi: no visible global function definition for 'lm' +musoSensi : doSensi: no visible binding for global variable 'var' +musoSensi : doSensi: no visible binding for global variable 'name' +normalMuso: possible error in changemulline(filename = epc[1], + calibrationPar, parameters): unused argument (filename = epc[1]) +normalMuso: possible error in changemulline(filename = iniInput[1], + calibrationPar, parameters): unused argument (filename = iniInput[1]) +plotMuso : : no visible binding for global variable + 'whereAmI' +plotMuso: possible error in musoDate(startYear = startYear, numYears = + numberOfYears, combined = TRUE, corrigated = FALSE): unused argument + (corrigated = FALSE) +plotMuso: possible error in musoDate(startYear = startYear, numYears = + numberOfYears, combined = FALSE, corrigated = FALSE): unused argument + (corrigated = FALSE) +plotMuso: no visible binding for global variable 'year' +plotMuso: no visible binding for global variable 'cum_yieldC_HRV' +plotMuso: no visible binding for global variable 'date2' +plotMuso : pointOrLineOrPlot: no visible binding for global variable + '.' +plotMuso : pointOrLineOrPlot: no visible binding for global variable + 'outputs' +plotMuso : pointOrLineOrPlot: no visible binding for global variable + 'bla' +plotMusoWithData: no visible binding for global variable 'modIndex' +plotMusoWithData: no visible binding for global variable 'measuredData' +plotMusoWithData: no visible binding for global variable 'measured' +prepareFromAgroMo: no visible global function definition for 'reshape' +randEpc: possible error in changemulline(filePaths = + basename(sourceEpc), calibrationPar = randVals[[1]], contents = + randVals[[2]][i, ], fileOut = epcOut, fileToChange = "epc"): unused + arguments (fileOut = epcOut, fileToChange = "epc") +rungetMuso: possible error in musoDate(settings$startYear, + settings$numYears, corrigated = FALSE): unused argument (corrigated = + FALSE) +setupMuso: no visible binding for global variable 'numDate' +spinupMuso: possible error in changemulline(filename = epc[1], + calibrationPar, parameters): unused argument (filename = epc[1]) +spinupMuso: possible error in changemulline(filename = iniInput[1], + calibrationPar, parameters): unused argument (filename = iniInput[1]) +spinupMuso: no visible binding for global variable 'EPCS' +spinupMuso : : no visible binding for global variable 'EPCS' +spinupMuso : : no visible binding for global variable + 'WRONGEPC' +truncNorm: no visible global function definition for 'rnorm' +Undefined global functions or variables: + . EPCS WRONGEPC abline bla cum_yieldC_HRV date2 dev.off dnorm lines + lm mMapping measured measuredData modIndex musoLeapYears na.omit name + numDate outputs par parVal pdf png points polygon procString quantile + reshape rnorm sd svg var whereAmI year +Consider adding + importFrom("grDevices", "dev.off", "pdf", "png", "svg") + importFrom("graphics", "abline", "lines", "par", "points", "polygon") + importFrom("stats", "dnorm", "lm", "na.omit", "quantile", "reshape", + "rnorm", "sd", "var") +to your NAMESPACE file. +* checking Rd files ... WARNING +./man/getSoilDataFull.Rd: non-ASCII input and no declared encoding +problem found in 'getSoilDataFull.Rd' +* checking Rd metadata ... OK +* checking Rd line widths ... OK +* checking Rd cross-references ... OK +* checking for missing documentation entries ... WARNING +Undocumented data sets: + 'depTree' +All user-level objects in a package should have documentation entries. +See chapter 'Writing R documentation files' in the 'Writing R +Extensions' manual. +* checking for code/documentation mismatches ... WARNING +Codoc mismatches from documentation object 'calibMuso': +calibMuso + Code: function(settings = setupMuso(), calibrationPar = NULL, + parameters = NULL, outVars = NULL, timee = "d", + debugging = FALSE, logfilename = NULL, keepEpc = + FALSE, export = FALSE, silent = FALSE, aggressive = + FALSE, keepBinary = FALSE, binaryPlace = "./", + fileToChange = "epc", skipSpinup = TRUE, + modifyOriginal = FALSE, prettyOut = FALSE, + postProcString = NULL, doBackup = TRUE) + Docs: function(settings, parameters = NULL, timee = "d", debugging = + FALSE, logfilename = NULL, keepEpc = FALSE, export = + FALSE, silent = FALSE, aggressive = FALSE, leapYear = + FALSE) + Argument names in code not in docs: + calibrationPar outVars keepBinary binaryPlace fileToChange + skipSpinup modifyOriginal prettyOut postProcString doBackup + Argument names in docs not in code: + leapYear + Mismatches in argument names (first 3): + Position: 2 Code: calibrationPar Docs: parameters + Position: 3 Code: parameters Docs: timee + Position: 4 Code: outVars Docs: debugging + Mismatches in argument default values: + Name: 'settings' Code: setupMuso() Docs: + +Codoc mismatches from documentation object 'calibrateMuso': +calibrateMuso + Code: function(measuredData, parameters = read.csv("parameters.csv", + stringsAsFactor = FALSE), startDate = NULL, endDate = + NULL, formatString = "%Y-%m-%d", dataVar, outLoc = + "./calib", preTag = "cal-", settings = setupMuso(), + outVars = NULL, iterations = 100, skipSpinup = TRUE, + plotName = "calib.jpg", modifyOriginal = TRUE, + likelihood, uncertainity = NULL, naVal = NULL, + postProcString = NULL, thread_prefix = "thread", + numCores = max(c(parallel::detectCores() - 1, 1)), pb + = txtProgressBar(min = 0, max = iterations, style = + 3), maxLikelihoodEpc = TRUE, pbUpdate = + setTxtProgressBar, outputLoc = "./", method = "GLUE", + lg = FALSE, w = NULL, ...) + Docs: function(measuredData, parameters = read.csv("parameters.csv", + stringsAsFactor = FALSE), startDate = NULL, endDate = + NULL, formatString = "%Y-%m-%d", dataVar, outLoc = + "./calib", preTag = "cal-", settings = setupMuso(), + outVars = NULL, iterations = 100, skipSpinup = TRUE, + plotName = "calib.jpg", modifyOriginal = TRUE, + likelihood, uncertainity = NULL, naVal = NULL, + postProcString = NULL, thread_prefix = "thread", + numCores = (parallel::detectCores() - 1), pb = + txtProgressBar(min = 0, max = iterations, style = 3), + maxLikelihoodEpc = TRUE, pbUpdate = setTxtProgressBar, + outputLoc = "./", method = "GLUE", lg = FALSE, w = + NULL, ...) + Mismatches in argument default values: + Name: 'numCores' Code: max(c(parallel::detectCores() - 1, 1)) Docs: (parallel::detectCores() - 1) + +Codoc mismatches from documentation object 'musoMapping': +musoMapping + Code: function(code, mapData = + getOption("RMuso_varTable")[[as.character(getOption("RMuso_version"))]]) + Docs: function(code, mapData = NULL) + Mismatches in argument default values: + Name: 'mapData' Code: getOption("RMuso_varTable")[[as.character(getOption("RMuso_version"))]] Docs: NULL + +Codoc mismatches from documentation object 'musoMappingFind': +musoMapping + Code: function(code, mapData = + getOption("RMuso_varTable")[[as.character(getOption("RMuso_version"))]]) + Docs: function(code, mapData = NULL) + Mismatches in argument default values: + Name: 'mapData' Code: getOption("RMuso_varTable")[[as.character(getOption("RMuso_version"))]] Docs: NULL + +Codoc mismatches from documentation object 'normalMuso': +normalMuso + Code: function(settings = NULL, parameters = NULL, timee = "d", + debugging = FALSE, logfilename = NULL, keepEpc = + FALSE, export = FALSE, silent = FALSE, aggressive = + FALSE, leapYear = FALSE, binaryPlace = NULL, + fileToChange = "epc", keepBinary = FALSE) + Docs: function(settings, parameters = NULL, timee = "d", debugging = + FALSE, logfilename = NULL, keepEpc = FALSE, export = + FALSE, silent = FALSE, aggressive = FALSE, leapYear = + FALSE) + Argument names in code not in docs: + binaryPlace fileToChange keepBinary + Mismatches in argument default values: + Name: 'settings' Code: NULL Docs: + +Codoc mismatches from documentation object 'plotMuso': +plotMuso + Code: function(settings = NULL, variable = "all", timee = "d", silent + = TRUE, calibrationPar = NULL, parameters = NULL, + debugging = FALSE, keepEpc = FALSE, fileToChange = + "epc", logfilename = NULL, aggressive = FALSE, + leapYear = FALSE, plotName = NULL, plotType = "cts", + layerPlot = FALSE, colour = "blue", skipSpinup = TRUE, + fromData = FALSE, timeFrame = "day", selectYear = + NULL, groupFun = mean, separateFile = FALSE, dpi = + 300, postProcString = NULL) + Docs: function(settings, variable, timee = "d", silent = TRUE, + debugging = FALSE, keepEpc = FALSE, logfilename = + NULL, aggressive = FALSE, leapYear = FALSE, export = + FALSE) + Argument names in code not in docs: + calibrationPar parameters fileToChange plotName plotType layerPlot + colour skipSpinup fromData timeFrame selectYear groupFun + separateFile dpi postProcString + Argument names in docs not in code: + export + Mismatches in argument names (first 3): + Position: 5 Code: calibrationPar Docs: debugging + Position: 6 Code: parameters Docs: keepEpc + Position: 7 Code: debugging Docs: logfilename + Mismatches in argument default values: + Name: 'settings' Code: NULL Docs: + Name: 'variable' Code: "all" Docs: + +Codoc mismatches from documentation object 'plotMusoWithData': +plotMuso + Code: function(settings = NULL, variable = "all", timee = "d", silent + = TRUE, calibrationPar = NULL, parameters = NULL, + debugging = FALSE, keepEpc = FALSE, fileToChange = + "epc", logfilename = NULL, aggressive = FALSE, + leapYear = FALSE, plotName = NULL, plotType = "cts", + layerPlot = FALSE, colour = "blue", skipSpinup = TRUE, + fromData = FALSE, timeFrame = "day", selectYear = + NULL, groupFun = mean, separateFile = FALSE, dpi = + 300, postProcString = NULL) + Docs: function(settings, variable, timee = "d", silent = TRUE, + debugging = FALSE, keepEpc = FALSE, logfilename = + NULL, aggressive = FALSE, leapYear = FALSE, export = + FALSE) + Argument names in code not in docs: + calibrationPar parameters fileToChange plotName plotType layerPlot + colour skipSpinup fromData timeFrame selectYear groupFun + separateFile dpi postProcString + Argument names in docs not in code: + export + Mismatches in argument names (first 3): + Position: 5 Code: calibrationPar Docs: debugging + Position: 6 Code: parameters Docs: keepEpc + Position: 7 Code: debugging Docs: logfilename + Mismatches in argument default values: + Name: 'settings' Code: NULL Docs: + Name: 'variable' Code: "all" Docs: + +Codoc mismatches from documentation object 'runMuso': +calibMuso + Code: function(settings = setupMuso(), calibrationPar = NULL, + parameters = NULL, outVars = NULL, timee = "d", + debugging = FALSE, logfilename = NULL, keepEpc = + FALSE, export = FALSE, silent = FALSE, aggressive = + FALSE, keepBinary = FALSE, binaryPlace = "./", + fileToChange = "epc", skipSpinup = TRUE, + modifyOriginal = FALSE, prettyOut = FALSE, + postProcString = NULL, doBackup = TRUE) + Docs: function(settings, parameters = NULL, timee = "d", debugging = + FALSE, logfilename = NULL, keepEpc = FALSE, export = + FALSE, silent = FALSE, aggressive = FALSE, leapYear = + FALSE) + Argument names in code not in docs: + calibrationPar outVars keepBinary binaryPlace fileToChange + skipSpinup modifyOriginal prettyOut postProcString doBackup + Argument names in docs not in code: + leapYear + Mismatches in argument names (first 3): + Position: 2 Code: calibrationPar Docs: parameters + Position: 3 Code: parameters Docs: timee + Position: 4 Code: outVars Docs: debugging + Mismatches in argument default values: + Name: 'settings' Code: setupMuso() Docs: + +Codoc mismatches from documentation object 'setupMuso': +setupMuso + Code: function(executable = NULL, parallel = F, calibrationPar = + c(1), outputLoc = NULL, modelOutputs = NULL, inputLoc + = NULL, metInput = NULL, CO2Input = NULL, plantInput = + NULL, thinInput = NULL, mowInput = NULL, grazInput = + NULL, harvInput = NULL, plougInput = NULL, fertInput = + NULL, irrInput = NULL, nitInput = NULL, iniInput = + NULL, epcInput = NULL, mapData = NULL, leapYear = + FALSE, version = 6, doCopy = TRUE) + Docs: function(executable = NULL, parallel = F, calibrationPar = + c(1), outputLoc = NULL, inputLoc = NULL, metInput = + NULL, CO2Input = NULL, plantInput = NULL, thinInput = + NULL, mowInput = NULL, grazInput = NULL, harvInput = + NULL, plougInput = NULL, fertInput = NULL, irrInput = + NULL, nitInput = NULL, iniInput = NULL, epcInput = + NULL) + Argument names in code not in docs: + modelOutputs mapData leapYear version doCopy + Mismatches in argument names (first 3): + Position: 5 Code: modelOutputs Docs: inputLoc + Position: 6 Code: inputLoc Docs: metInput + Position: 7 Code: metInput Docs: CO2Input + +Codoc mismatches from documentation object 'spinupMuso': +spinupMuso + Code: function(settings = NULL, parameters = NULL, debugging = FALSE, + logfilename = NULL, keepEpc = FALSE, silent = FALSE, + aggressive = FALSE, fileToChange = "epc") + Docs: function(settings, parameters = NULL, debugging = FALSE, + logfilename = NULL, keepEpc = FALSE, silent = FALSE, + aggressive = FALSE) + Argument names in code not in docs: + fileToChange + Mismatches in argument default values: + Name: 'settings' Code: NULL Docs: + +* checking Rd \usage sections ... WARNING +Documented arguments not in \usage in documentation object 'calibMuso': + 'keepBinary' 'binaryPlace' 'fileToChange' 'skipSpinup' 'prettyOut' + +Undocumented arguments in documentation object 'calibrateMuso' + 'measuredData' 'parameters' 'startDate' 'endDate' 'formatString' + 'dataVar' 'outLoc' 'preTag' 'settings' 'outVars' 'iterations' + 'skipSpinup' 'plotName' 'modifyOriginal' 'likelihood' 'uncertainity' + 'naVal' 'postProcString' 'thread_prefix' 'numCores' 'pb' + 'maxLikelihoodEpc' 'pbUpdate' 'outputLoc' 'method' 'lg' 'w' '...' + +Undocumented arguments in documentation object 'changemulline' + 'filePaths' 'calibrationPar' 'contents' 'src' 'outFiles' + +Undocumented arguments in documentation object 'checkFileSystem' + 'root' + +Documented arguments not in \usage in documentation object 'checkMeteoBGC': + 'metFileName' + +Undocumented arguments in documentation object 'compareCalibratedWithOriginal' + 'key' 'modOld' 'modNew' 'mes' 'likelihoods' 'alignIndexes' + 'musoCodeToIndex' 'nameGroupTable' 'groupFun' + +Undocumented arguments in documentation object 'compareMuso' + 'skipSpinup' 'timeFrame' + +Undocumented arguments in documentation object 'flatMuso' + 'execPath' 'd' 'outE' + +Undocumented arguments in documentation object 'getFilePath' + 'fileType' 'execPath' +Documented arguments not in \usage in documentation object 'getFilePath': + 'filetype' + +Undocumented arguments in documentation object 'getFilesFromIni' + 'execPath' + +Undocumented arguments in documentation object 'multiSiteCalib' + 'measurements' 'constraints' +Documented arguments not in \usage in documentation object 'multiSiteCalib': + 'measuremets' 'contsraints' + +Undocumented arguments in documentation object 'multiSiteThread' + 'measuredData' 'parameters' 'startDate' 'endDate' 'formatString' + 'calTable' 'dataVar' 'outLoc' 'outVars' 'iterations' 'skipSpinup' + 'plotName' 'modifyOriginal' 'likelihood' 'uncertainity' 'burnin' + 'naVal' 'postProcString' 'threadNumber' 'constraints' 'th' + +Undocumented arguments in documentation object 'musoDate' + 'startYear' 'endYears' 'numYears' 'combined' 'leapYearHandling' + 'prettyOut' + +Undocumented arguments in documentation object 'musoGlue' + 'presCalFile' 'w' 'delta' 'settings' 'parameters' 'lg' +Documented arguments not in \usage in documentation object 'musoGlue': + 'plotName' + +Undocumented arguments in documentation object 'musoMappingFind' + 'code' 'mapData' +Documented arguments not in \usage in documentation object 'musoMappingFind': + 'variable' +Objects in \usage without \alias in documentation object 'musoMappingFind': + 'musoMapping' + +Undocumented arguments in documentation object 'musoMonte' + 'outLoc' 'outVars' 'silent' 'skipSpinup' 'constrains' 'skipZero' + 'postProcString' 'modifyOut' '...' +Documented arguments not in \usage in documentation object 'musoMonte': + 'calibrationPar' + +Undocumented arguments in documentation object 'musoQuickEffect' + 'calibrationPar' 'fileToChange' 'modifyOriginal' 'outVar' 'parName' + 'yearNum' 'year' +Documented arguments not in \usage in documentation object 'musoQuickEffect': + 'fileTochange' + +Undocumented arguments in documentation object 'musoRand' + 'iterations' 'fileType' 'burnin' +Documented arguments not in \usage in documentation object 'musoRand': + 'iteration' + +Undocumented arguments in documentation object 'musoSensi' + 'monteCarloFile' 'outLoc' 'outVars' 'outputFile' 'plotName' + 'plotTitle' 'skipZero' 'postProcString' 'modifyOut' 'dpi' +Documented arguments not in \usage in documentation object 'musoSensi': + 'calibrationPar' + +Documented arguments not in \usage in documentation object 'normalMuso': + 'binaryPlace' 'fileToChange' 'keepBinary' + +Undocumented arguments in documentation object 'optiMuso' + 'measuredData' 'dataVar' 'preTag' 'outVars' 'modifyOriginal' + 'uncertainity' 'naVal' 'postProcString' 'w' 'lg' 'parallel' +Documented arguments not in \usage in documentation object 'optiMuso': + 'measuredDataFile' 'sep' 'filterCol' 'filterVal' 'selVar' 'pretag' + 'calPar' 'constrains' 'leapYear' + +Documented arguments not in \usage in documentation object 'plotMuso': + 'plotType' 'skipSpinup' + +Undocumented arguments in documentation object 'plotMusoWithData' + 'timee' 'silent' 'debugging' 'keepEpc' 'logfilename' 'aggressive' + 'leapYear' 'export' +Documented arguments not in \usage in documentation object 'plotMusoWithData': + 'sep' 'savePlot' 'NACHAR' 'csvFile' 'calibrationPar' 'parameters' +Objects in \usage without \alias in documentation object 'plotMusoWithData': + 'plotMuso' + +Undocumented arguments in documentation object 'randEpc' + 'iterations' 'constrains' +Documented arguments not in \usage in documentation object 'randEpc': + 'iteration' + +Undocumented arguments in documentation object 'readObservedData' + 'inFile' 'naString' 'sep' 'leapYearHandling' 'convert.var' + 'convert.scalar' 'convert.fun' 'convert.file' 'filterCol' 'filterVal' + 'selVar' + +Documented arguments not in \usage in documentation object 'runMuso': + 'keepBinary' 'binaryPlace' 'fileToChange' 'skipSpinup' 'prettyOut' +Objects in \usage without \alias in documentation object 'runMuso': + 'calibMuso' + +Undocumented arguments in documentation object 'saveAllMusoPlots' + 'type' 'outFile' 'colour' 'skipSpinup' +Documented arguments not in \usage in documentation object 'saveAllMusoPlots': + 'destination' + +Documented arguments not in \usage in documentation object 'setupMuso': + 'modelOutputs' + +Undocumented arguments in documentation object 'updateMusoMapping' + 'dest' 'version' + +Functions with \usage entries need to have the appropriate \alias +entries, and all their arguments documented. +The \usage entries must correspond to syntactically valid R code. +See chapter 'Writing R documentation files' in the 'Writing R +Extensions' manual. +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking installed files from 'inst/doc' ... OK +* checking files in 'vignettes' ... OK +* checking examples ... NONE +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in 'inst/doc' ... NOTE +Package vignette with placeholder title 'Vignette Title': + 'my-vignette.Rmd' +* checking re-building of vignette outputs ... OK +* checking for non-standard things in the check directory ... OK +* checking for detritus in the temp directory ... OK +* DONE +Status: 7 WARNINGs, 7 NOTEs diff --git a/RBBGCMuso.Rcheck/00install.out b/RBBGCMuso.Rcheck/00install.out new file mode 100644 index 0000000..bdb5da0 --- /dev/null +++ b/RBBGCMuso.Rcheck/00install.out @@ -0,0 +1,25 @@ +* installing *source* package 'RBBGCMuso' ... +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Note: possible error in 'changemulline(filename = epc[1], ': unused argument (filename = epc[1]) +Note: possible error in 'changemulline(filename = iniInput[1], ': unused argument (filename = iniInput[1]) +Note: possible error in 'musoDate(startYear = startYear, ': unused argument (corrigated = FALSE) +Note: possible error in 'musoDate(startYear = startYear, ': unused argument (corrigated = FALSE) +Note: possible error in 'changemulline(filePaths = basename(sourceEpc), ': unused arguments (fileOut = epcOut, fileToChange = "epc") +Note: possible error in 'musoDate(settings$startYear, ': unused argument (corrigated = FALSE) +Note: possible error in 'changemulline(filename = epc[1], ': unused argument (filename = epc[1]) +Note: possible error in 'changemulline(filename = iniInput[1], ': unused argument (filename = iniInput[1]) +** help +*** installing help indices +** building package indices +** installing vignettes +** testing if installed package can be loaded from temporary location +This is RBBGCMuso version 1.0 +Default Biome-BGCMuSo version: 7 +** testing if installed package can be loaded from final location +This is RBBGCMuso version 1.0 +Default Biome-BGCMuSo version: 7 +** testing if installed package keeps a record of temporary installation path +* DONE (RBBGCMuso) diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/DESCRIPTION b/RBBGCMuso.Rcheck/RBBGCMuso/DESCRIPTION new file mode 100644 index 0000000..be9e1c6 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/DESCRIPTION @@ -0,0 +1,19 @@ +Package: RBBGCMuso +Title: An R package for BiomeBGC-MuSo ecosystem modelling +Version: 0.7.1 +Authors@R: person("Roland", "Hollo's", , "hollorol@gmail.com", role = c("aut", "cre")) +Description: What the package does (one paragraph). +Depends: R (>= 3.3.2) +License: GPL-2 +NeedsCompilation: no +Packaged: 2023-02-06 09:42:51 UTC; user +Author: Roland Hollo's [aut, cre] +Imports: grDevices, limSolve, stats, utils, graphics, Rcpp, magrittr, + dplyr, ggplot2, rmarkdown, tibble, tidyr, glue, scales, tcltk, + digest, jsonlite, data.table, gridExtra, lubridate, openxlsx, + ncdf4, future, httr, tcltk, Boruta, rpart, rpart.plot +Maintainer: Roland Hollo's +Suggests: knitr, rmarkdown, +VignetteBuilder: knitr +ByteCompile: true +Built: R 4.2.2; ; 2023-02-06 09:42:58 UTC; windows diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/INDEX b/RBBGCMuso.Rcheck/RBBGCMuso/INDEX new file mode 100644 index 0000000..90abec2 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/INDEX @@ -0,0 +1,49 @@ +calibMuso calibMuso +calibrateMuso calibrateMuso +changemulline changemulline +checkFileSystem checkFileSystem +checkMeteoBGC checkMeteoBGC +cleanupMuso cleanupMuso +compareCalibratedWithOriginal + compareCalibratedWithOriginal +compareMuso compareMuso +copyMusoExampleTo copyMusoExampleTo +corrigMuso corrigMuso +createSoilFile createSoilFile +fextension fextension +flatMuso flatMuso +getAnnualOutputList getAnnualOutputList +getConstMatrix getConstMatrix +getDailyOutputList getDailyOutputList +getFilePath getFilePath +getFilesFromIni getFilesFromIni +getSoilDataFull getSoilDataFull +getyearlycum getyearlycum +getyearlymax getyearlymax +multiSiteCalib multiSiteCalib +multiSiteThread multiSiteThread +musoDate musoDate +musoGlue musoGlue +musoMapping musoMapping +musoMappingFind musoMappingFind +musoMonte musoMonte +musoQuickEffect musoQuickEffect +musoRand musoRand +musoSensi musoSensi +normalMuso normalMuso +optiMuso optiMuso +paramSweep paramSweep +plotMuso plot the Biome-BGCMuSo output +plotMusoWithData plot the Biome-BGCMuSo model output with + observation data +randEpc randEpc +readObservedData readMeasuredMuso +runMuso runMuso +rungetMuso rungetMuso +saveAllMusoPlots saveAllMusoPlots +setupMuso setupMuso +spinupMuso Runs the Biome-BGCMuSo model in spinup phase + (execution of normal phase is possible with + normalMuso) with debugging features. +supportedMuso supportedMuso +updateMusoMapping updateMusoMapping diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/Rd.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/Rd.rds new file mode 100644 index 0000000..e9508cc Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/Rd.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/data.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/data.rds new file mode 100644 index 0000000..f90d4ec Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/data.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/features.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/features.rds new file mode 100644 index 0000000..848ce62 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/features.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/hsearch.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/hsearch.rds new file mode 100644 index 0000000..d2ba8e1 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/hsearch.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/links.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/links.rds new file mode 100644 index 0000000..38977ec Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/links.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/nsInfo.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/nsInfo.rds new file mode 100644 index 0000000..2de3df3 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/nsInfo.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/package.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/package.rds new file mode 100644 index 0000000..4c596b7 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/package.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/Meta/vignette.rds b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/vignette.rds new file mode 100644 index 0000000..1ca0eff Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/Meta/vignette.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/NAMESPACE b/RBBGCMuso.Rcheck/RBBGCMuso/NAMESPACE new file mode 100644 index 0000000..448280f --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/NAMESPACE @@ -0,0 +1,97 @@ +# Generated by roxygen2: do not edit by hand + +export(calibMuso) +export(calibrateMuso) +export(changemulline) +export(checkFileSystem) +export(checkMeteoBGC) +export(cleanupMuso) +export(compareMuso) +export(copyMusoExampleTo) +export(corrigMuso) +export(createSoilFile) +export(flatMuso) +export(getAnnualOutputList) +export(getConstMatrix) +export(getDailyOutputList) +export(getFilePath) +export(getFilesFromIni) +export(getyearlycum) +export(getyearlymax) +export(multiSiteCalib) +export(musoDate) +export(musoGlue) +export(musoMapping) +export(musoMappingFind) +export(musoMonte) +export(musoQuickEffect) +export(musoRand) +export(musoSensi) +export(normalMuso) +export(optiMuso) +export(paramSweep) +export(plotMuso) +export(plotMusoWithData) +export(randEpc) +export(readObservedData) +export(runMuso) +export(rungetMuso) +export(saveAllMusoPlots) +export(setupMuso) +export(spinupMuso) +export(supportedMuso) +export(updateMusoMapping) +import(ggplot2) +import(utils) +importFrom(data.table,':=') +importFrom(data.table,data.table) +importFrom(data.table,fread) +importFrom(digest,digest) +importFrom(dplyr,'%>%') +importFrom(dplyr,filter) +importFrom(dplyr,group_by) +importFrom(dplyr,mutate) +importFrom(dplyr,select) +importFrom(dplyr,summarize) +importFrom(dplyr,tbl_df) +importFrom(future,future) +importFrom(ggplot2,aes) +importFrom(ggplot2,aes_string) +importFrom(ggplot2,element_blank) +importFrom(ggplot2,element_text) +importFrom(ggplot2,facet_wrap) +importFrom(ggplot2,geom_bar) +importFrom(ggplot2,geom_line) +importFrom(ggplot2,geom_point) +importFrom(ggplot2,ggplot) +importFrom(ggplot2,ggsave) +importFrom(ggplot2,ggtitle) +importFrom(ggplot2,labs) +importFrom(ggplot2,scale_y_continuous) +importFrom(ggplot2,theme) +importFrom(ggplot2,theme_classic) +importFrom(ggplot2,xlab) +importFrom(ggplot2,ylab) +importFrom(glue,glue) +importFrom(gridExtra,grid.arrange) +importFrom(httr,GET) +importFrom(httr,config) +importFrom(httr,content) +importFrom(httr,with_config) +importFrom(jsonlite,write_json) +importFrom(limSolve,xsample) +importFrom(lubridate,leap_year) +importFrom(magrittr,'%<>%') +importFrom(magrittr,'%>%') +importFrom(openxlsx,read.xlsx) +importFrom(rmarkdown,pandoc_version) +importFrom(rmarkdown,render) +importFrom(rpart,rpart) +importFrom(rpart,rpart.control) +importFrom(rpart.plot,rpart.plot) +importFrom(scales,percent) +importFrom(stats,approx) +importFrom(tcltk,tk_choose.files) +importFrom(tibble,rownames_to_column) +importFrom(tidyr,gather) +importFrom(tidyr,separate) diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso b/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso new file mode 100644 index 0000000..6686156 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso @@ -0,0 +1,27 @@ +# File share/R/nspackloader.R +# Part of the R package, https://www.R-project.org +# +# Copyright (C) 1995-2012 The R Core Team +# +# This program is free software; you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation; either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# A copy of the GNU General Public License is available at +# https://www.r-project.org/Licenses/ + +local({ + info <- loadingNamespaceInfo() + pkg <- info$pkgname + ns <- .getNamespace(as.name(pkg)) + if (is.null(ns)) + stop("cannot find namespace environment for ", pkg, domain = NA); + dbbase <- file.path(info$libname, pkg, "R", pkg) + lazyLoad(dbbase, ns, filter = function(n) n != ".__NAMESPACE__.") +}) diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso.rdb b/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso.rdb new file mode 100644 index 0000000..3b11105 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso.rdb differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso.rdx b/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso.rdx new file mode 100644 index 0000000..3ee719a Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/R/RBBGCMuso.rdx differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/constMatrix5.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/constMatrix5.json new file mode 100644 index 0000000..d691e1b --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/constMatrix5.json @@ -0,0 +1 @@ +[{"X":1,"NAME":"yearday to start new growth","INDEX":9,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":2,"NAME":"yearday to end new growth","INDEX":10,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":3,"NAME":"transfer growth period as fraction of growing season","INDEX":11,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":4,"NAME":"litterfall as fraction of growing season","INDEX":12,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":5,"NAME":"base temperature","INDEX":13,"UNIT":"Celsius","MIN":0,"MAX":12,"GROUP":0,"TYPE":0},{"X":6,"NAME":"minimum temperature for growth displayed on current day","INDEX":14,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":1,"TYPE":1},{"X":7,"NAME":"optimal1 temperature for growth displayed on current day","INDEX":15,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":1,"TYPE":1},{"X":8,"NAME":"optimal2 temperature for growth displayed on current day","INDEX":16,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":1,"TYPE":1},{"X":9,"NAME":"maxmimum temperature for growth displayed on current day","INDEX":17,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":1,"TYPE":1},{"X":10,"NAME":"minimum temperature for carbon assimilation displayed on current day","INDEX":18,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":2,"TYPE":1},{"X":11,"NAME":"optimal1 temperature for carbon assimilation displayed on current day","INDEX":19,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":2,"TYPE":1},{"X":12,"NAME":"optimal2 temperature for carbon assimilation displayed on current day","INDEX":20,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":2,"TYPE":1},{"X":13,"NAME":"maxmimum temperature for carbon assimilation displayed on current day","INDEX":21,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":2,"TYPE":1},{"X":14,"NAME":"annual leaf and fine root turnover fraction","INDEX":22,"UNIT":"1/yr","MIN":0.1,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":15,"NAME":"annual live wood turnover fraction","INDEX":23,"UNIT":"1/yr","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":16,"NAME":"annual fire mortality fraction","INDEX":24,"UNIT":"1/yr","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":17,"NAME":"whole-plant mortality paramter for vegetation period","INDEX":25,"UNIT":"1/vegper","MIN":0,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":18,"NAME":"C:N of leaves","INDEX":26,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":10,"MAX":100,"GROUP":0,"TYPE":0},{"X":19,"NAME":"C:N of leaf litter","INDEX":27,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":20,"NAME":"C:N of fine roots","INDEX":28,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":21,"NAME":"C:N of fruit","INDEX":29,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":22,"NAME":"C:N of softstem","INDEX":30,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":23,"NAME":"C:N of live wood","INDEX":31,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":50,"MAX":100,"GROUP":4,"TYPE":1},{"X":24,"NAME":"C:N of dead wood","INDEX":32,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":300,"MAX":800,"GROUP":4,"TYPE":1},{"X":25,"NAME":"dry matter content of leaves","INDEX":33,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":26,"NAME":"dry matter content of leaf litter","INDEX":34,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":27,"NAME":"dry matter content of fine roots","INDEX":35,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":28,"NAME":"dry matter content of fruit","INDEX":36,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":29,"NAME":"dry matter content of softstem","INDEX":37,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":30,"NAME":"dry matter content of live wood","INDEX":38,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":31,"NAME":"dry matter content of dead wood","INDEX":39,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":32,"NAME":"leaf litter labile proportion","INDEX":40,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":33,"NAME":"leaf litter cellulose proportion","INDEX":41,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":34,"NAME":"fine root labile proportion","INDEX":42,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":35,"NAME":"fine root cellulose proportion","INDEX":43,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":36,"NAME":"fruit labile proportion","INDEX":44,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":37,"NAME":"fruit cellulose proportion","INDEX":45,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":38,"NAME":"softstem labile proportion","INDEX":46,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":39,"NAME":"softstem cellulose proportion","INDEX":47,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":40,"NAME":"dead wood cellulose proportion","INDEX":48,"UNIT":"prop","MIN":0.5,"MAX":0.9,"GROUP":0,"TYPE":0},{"X":41,"NAME":"canopy water interception coefficient","INDEX":49,"UNIT":"1/LAI/d","MIN":0.01,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":42,"NAME":"canopy light extinction coefficient","INDEX":50,"UNIT":"dimless","MIN":0.2,"MAX":0.8,"GROUP":0,"TYPE":0},{"X":43,"NAME":"potential radiation use efficiency","INDEX":51,"UNIT":"g/MJ","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":44,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":52,"UNIT":"dimless","MIN":0.781,"MAX":0.781,"GROUP":0,"TYPE":0},{"X":45,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":53,"UNIT":"dimless","MIN":-13.596,"MAX":-13.596,"GROUP":0,"TYPE":0},{"X":46,"NAME":"all-sided to projected leaf area ratio","INDEX":54,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":47,"NAME":"ratio of shaded SLA:sunlit SLA","INDEX":55,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":48,"NAME":"fraction of leaf N in Rubisco","INDEX":56,"UNIT":"dimless","MIN":0.01,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":49,"NAME":"fraction of leaf N in PeP","INDEX":57,"UNIT":"dimless","MIN":0.0424,"MAX":0.0424,"GROUP":0,"TYPE":0},{"X":50,"NAME":"maximum stomatal conductance ","INDEX":58,"UNIT":"m/s","MIN":0.001,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":51,"NAME":"cuticular conductance ","INDEX":59,"UNIT":"m/s","MIN":1e-05,"MAX":0.0001,"GROUP":0,"TYPE":0},{"X":52,"NAME":"boundary layer conductance","INDEX":60,"UNIT":"m/s","MIN":0.01,"MAX":0.09,"GROUP":0,"TYPE":0},{"X":53,"NAME":"maximum height of plant","INDEX":61,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":54,"NAME":"stem weight corresponding to maximum height","INDEX":62,"UNIT":"kgC","MIN":0.1,"MAX":100,"GROUP":0,"TYPE":0},{"X":55,"NAME":"plant height function shape parameter (slope)","INDEX":63,"UNIT":"dimless","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":56,"NAME":"maximum depth of rooting zone","INDEX":64,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":57,"NAME":"root distribution parameter","INDEX":65,"UNIT":"prop","MIN":3.67,"MAX":3.67,"GROUP":0,"TYPE":0},{"X":58,"NAME":"root weight corresponding to max root depth","INDEX":66,"UNIT":"kgC/m2","MIN":0.4,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":59,"NAME":"root depth function shape parameter (slope)","INDEX":67,"UNIT":"prop","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":60,"NAME":"root weight to rooth length conversion factor","INDEX":68,"UNIT":"m/kg","MIN":1000,"MAX":1000,"GROUP":0,"TYPE":0},{"X":61,"NAME":"growth resp per unit of C grown","INDEX":69,"UNIT":"prop","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":62,"NAME":"maintenance respiration in kgC/day per kg of tissue N ","INDEX":70,"UNIT":"kgC/kgN/d","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":63,"NAME":"theoretical maximum prop. of non-structural and structural carbohydrates","INDEX":71,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":64,"NAME":"prop. of non-structural carbohydrates available for maintanance resp","INDEX":72,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":65,"NAME":"symbiotic+asymbiotic fixation of N","INDEX":73,"UNIT":"kgN/m2/yr","MIN":0,"MAX":0.001,"GROUP":0,"TYPE":0},{"X":66,"NAME":"time delay for temperature in photosynthesis acclimation","INDEX":74,"UNIT":"day","MIN":0,"MAX":50,"GROUP":0,"TYPE":0},{"X":67,"NAME":"critical VWCratio (prop. to FC-WP) in germination","INDEX":79,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":68,"NAME":"critical photoslow daylength","INDEX":81,"UNIT":"hour","MIN":14,"MAX":18,"GROUP":0,"TYPE":0},{"X":69,"NAME":"slope of relative photoslow development rate ","INDEX":82,"UNIT":"dimless","MIN":0.005,"MAX":0.005,"GROUP":0,"TYPE":0},{"X":70,"NAME":"critical vernalization temperature 1","INDEX":84,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":9,"TYPE":1},{"X":71,"NAME":"critical vernalization temperature 2","INDEX":85,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":9,"TYPE":1},{"X":72,"NAME":"critical vernalization temperature 3","INDEX":86,"UNIT":"Celsius","DEPENDENCE":2,"MIN":5,"MAX":15,"GROUP":9,"TYPE":1},{"X":73,"NAME":"critical vernalization temperature 4","INDEX":87,"UNIT":"Celsius","DEPENDENCE":3,"MIN":10,"MAX":20,"GROUP":9,"TYPE":1},{"X":74,"NAME":"slope of relative vernalization development rate ","INDEX":88,"UNIT":"dimless","MIN":0.04,"MAX":0.04,"GROUP":0,"TYPE":0},{"X":75,"NAME":"required vernalization days (in vernalization development rate)","INDEX":89,"UNIT":"dimless","MIN":30,"MAX":70,"GROUP":0,"TYPE":0},{"X":76,"NAME":"critical flowering heat stress temperature 1","INDEX":91,"UNIT":"Celsius","DEPENDENCE":0,"MIN":30,"MAX":40,"GROUP":10,"TYPE":1},{"X":77,"NAME":"critical flowering heat stress temperature 2","INDEX":92,"UNIT":"Celsius","DEPENDENCE":1,"MIN":30,"MAX":50,"GROUP":10,"TYPE":1},{"X":78,"NAME":"theoretical maximum of flowering thermal stress mortality","INDEX":93,"UNIT":"prop","MIN":0,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":79,"NAME":"VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)","INDEX":96,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":80,"NAME":"VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)","INDEX":97,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":81,"NAME":"minimum of soil moisture limit2 multiplicator (full anoxic stress value)","INDEX":98,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":82,"NAME":"vapor pressure deficit: start of conductance reduction","INDEX":99,"UNIT":"Pa","MIN":500,"MAX":1500,"GROUP":0,"TYPE":0},{"X":83,"NAME":"vapor pressure deficit: complete conductance reduction","INDEX":100,"UNIT":"Pa","MIN":1500,"MAX":3500,"GROUP":0,"TYPE":0},{"X":84,"NAME":"maximum senescence mortality coefficient of aboveground plant material","INDEX":101,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":85,"NAME":"maximum senescence mortality coefficient of belowground plant material","INDEX":102,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":86,"NAME":"maximum senescence mortality coefficient of non-structured plant material","INDEX":103,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":87,"NAME":"lower limit extreme high temperature effect on senescence mortality","INDEX":104,"UNIT":"Celsius","MIN":30,"MAX":40,"GROUP":0,"TYPE":0},{"X":88,"NAME":"upper limit extreme high temperature effect on senescence mortality","INDEX":105,"UNIT":"Celsius","MIN":30,"MAX":50,"GROUP":0,"TYPE":0},{"X":89,"NAME":"turnover rate of wilted standing biomass to litter","INDEX":106,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":90,"NAME":"turnover rate of cut-down non-woody biomass to litter","INDEX":107,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":91,"NAME":"turnover rate of cut-down woody biomass to litter","INDEX":108,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":92,"NAME":"drought tolerance parameter (critical value of day since water stress)","INDEX":109,"UNIT":"n_day","MIN":0,"MAX":100,"GROUP":0,"TYPE":0},{"X":93,"NAME":"crit. amount of snow limiting photosyn.","INDEX":112,"UNIT":"kg/m2","MIN":0,"MAX":20,"GROUP":0,"TYPE":0},{"X":94,"NAME":"limit1 (under:full constrained) of HEATSUM index","INDEX":113,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":50,"GROUP":11,"TYPE":1},{"X":95,"NAME":"limit2 (above:unconstrained) of HEATSUM index","INDEX":114,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":100,"GROUP":11,"TYPE":1},{"X":96,"NAME":"limit1 (under:full constrained) of TMIN index","INDEX":115,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":12,"TYPE":1},{"X":97,"NAME":"limit2 (above:unconstrained) of TMIN index","INDEX":116,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":12,"TYPE":1},{"X":98,"NAME":"limit1 (above:full constrained) of VPD index","INDEX":117,"UNIT":"Pa","DEPENDENCE":0,"MIN":2000,"MAX":600,"GROUP":13,"TYPE":1},{"X":99,"NAME":"limit2 (under:unconstrained) of VPD index","INDEX":118,"UNIT":"Pa","DEPENDENCE":1,"MIN":500,"MAX":1500,"GROUP":13,"TYPE":1},{"X":100,"NAME":"limit1 (under:full constrained) of DAYLENGTH index","INDEX":119,"UNIT":"s","DEPENDENCE":0,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":101,"NAME":"limit2 (above:unconstrained) of DAYLENGTH index","INDEX":120,"UNIT":"s","DEPENDENCE":1,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":102,"NAME":"moving average (to avoid the effects of extreme events)","INDEX":121,"UNIT":"n_day","MIN":2,"MAX":20,"GROUP":0,"TYPE":0},{"X":103,"NAME":"GSI limit1 (greater that limit -> start of vegper)","INDEX":122,"UNIT":"dimless","MIN":0,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":104,"NAME":"GSI limit2 (less that limit -> end of vegper)","INDEX":123,"UNIT":"dimless","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":105,"NAME":"length of phenophase (GDD)","INDEX":127,"UNIT":"Celsius","MIN":0,"MAX":10000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -0","INDEX":128.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-0","INDEX":129.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -0","INDEX":130.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-0","INDEX":131.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -0","INDEX":132.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -0","INDEX":133.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-0","INDEX":134.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -0","INDEX":135.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-0","INDEX":136.6,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-0","INDEX":137.6,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-0","INDEX":138.6,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -1","INDEX":128.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-1","INDEX":129.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -1","INDEX":130.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-1","INDEX":131.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -1","INDEX":132.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -1","INDEX":133.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-1","INDEX":134.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -1","INDEX":135.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-1","INDEX":136.61,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-1","INDEX":137.61,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-1","INDEX":138.61,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -2","INDEX":128.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-2","INDEX":129.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -2","INDEX":130.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-2","INDEX":131.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -2","INDEX":132.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -2","INDEX":133.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-2","INDEX":134.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -2","INDEX":135.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-2","INDEX":136.62,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-2","INDEX":137.62,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-2","INDEX":138.62,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -3","INDEX":128.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-3","INDEX":129.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -3","INDEX":130.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-3","INDEX":131.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -3","INDEX":132.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -3","INDEX":133.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-3","INDEX":134.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -3","INDEX":135.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-3","INDEX":136.63,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-3","INDEX":137.63,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-3","INDEX":138.63,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -4","INDEX":128.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-4","INDEX":129.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -4","INDEX":130.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-4","INDEX":131.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -4","INDEX":132.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -4","INDEX":133.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-4","INDEX":134.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -4","INDEX":135.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-4","INDEX":136.64,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-4","INDEX":137.64,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-4","INDEX":138.64,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -5","INDEX":128.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-5","INDEX":129.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -5","INDEX":130.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-5","INDEX":131.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -5","INDEX":132.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -5","INDEX":133.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-5","INDEX":134.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -5","INDEX":135.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-5","INDEX":136.65,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-5","INDEX":137.65,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-5","INDEX":138.65,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -6","INDEX":128.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-6","INDEX":129.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -6","INDEX":130.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-6","INDEX":131.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -6","INDEX":132.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -6","INDEX":133.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-6","INDEX":134.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -6","INDEX":135.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-6","INDEX":136.66,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-6","INDEX":137.66,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-6","INDEX":138.66,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0}] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/constMatrix6.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/constMatrix6.json new file mode 100644 index 0000000..6fcfe03 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/constMatrix6.json @@ -0,0 +1,190 @@ +[ + {"X": "1", "NAME": "yearday to start new growth", "INDEX": "9", "UNIT": "yday", "MIN": "0", "MAX": "364", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "2", "NAME": "yearday to end new growth", "INDEX": "10", "UNIT": "yday", "MIN": "0", "MAX": "364", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "3", "NAME": "transfer growth period as fraction of growing season", "INDEX": "11", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "4", "NAME": "litterfall as fraction of growing season", "INDEX": "12", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "5", "NAME": "base temperature", "INDEX": "13", "UNIT": "Celsius", "MIN": "0", "MAX": "12", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "6", "NAME": "minimum temperature for growth displayed on current day", "INDEX": "14", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "0", "GROUP": "1", "TYPE": "1"}, + {"X": "7", "NAME": "optimal1 temperature for growth displayed on current day", "INDEX": "15", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "1", "GROUP": "1", "TYPE": "1"}, + {"X": "8", "NAME": "optimal2 temperature for growth displayed on current day", "INDEX": "16", "UNIT": "Celsius", "MIN": "20", "MAX": "40", "DEPENDENCE": "2", "GROUP": "1", "TYPE": "1"}, + {"X": "9", "NAME": "maxmimum temperature for growth displayed on current day", "INDEX": "17", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "3", "GROUP": "1", "TYPE": "1"}, + {"X": "10", "NAME": "minimum temperature for carbon assimilation displayed on current day", "INDEX": "18", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "0", "GROUP": "2", "TYPE": "1"}, + {"X": "11", "NAME": "optimal1 temperature for carbon assimilation displayed on current day", "INDEX": "19", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "1", "GROUP": "2", "TYPE": "1"}, + {"X": "12", "NAME": "optimal2 temperature for carbon assimilation displayed on current day", "INDEX": "20", "UNIT": "Celsius", "MIN": "20", "MAX": "40", "DEPENDENCE": "2", "GROUP": "2", "TYPE": "1"}, + {"X": "13", "NAME": "maxmimum temperature for carbon assimilation displayed on current day", "INDEX": "21", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "3", "GROUP": "2", "TYPE": "1"}, + {"X": "14", "NAME": "annual leaf and fine root turnover fraction", "INDEX": "22", "UNIT": "1/yr", "MIN": "0.1", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "15", "NAME": "annual live wood turnover fraction", "INDEX": "23", "UNIT": "1/yr", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "16", "NAME": "annual fire mortality fraction", "INDEX": "24", "UNIT": "1/yr", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "17", "NAME": "whole-plant mortality paramter for vegetation period", "INDEX": "25", "UNIT": "1/vegper", "MIN": "0", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "18", "NAME": "C:N of leaves", "INDEX": "26", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "100", "DEPENDENCE": "0", "GROUP": "3", "TYPE": "1"}, + {"X": "19", "NAME": "C:N of leaf litter", "INDEX": "27", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "20", "NAME": "C:N of fine roots", "INDEX": "28", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "21", "NAME": "C:N of fruit", "INDEX": "29", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "22", "NAME": "C:N of softstem", "INDEX": "30", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"}, + {"X": "23", "NAME": "C:N of live wood", "INDEX": "31", "UNIT": "kgC/kgN", "MIN": "50", "MAX": "100", "DEPENDENCE": "0", "GROUP": "4", "TYPE": "1"}, + {"X": "24", "NAME": "C:N of dead wood", "INDEX": "32", "UNIT": "kgC/kgN", "MIN": "300", "MAX": "800", "DEPENDENCE": "1", "GROUP": "4", "TYPE": "1"}, + {"X": "25", "NAME": "dry matter content of leaves", "INDEX": "33", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "26", "NAME": "dry matter content of leaf litter", "INDEX": "34", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "27", "NAME": "dry matter content of fine roots", "INDEX": "35", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "28", "NAME": "dry matter content of fruit", "INDEX": "36", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "29", "NAME": "dry matter content of softstem", "INDEX": "37", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "30", "NAME": "dry matter content of live wood", "INDEX": "38", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "31", "NAME": "dry matter content of dead wood", "INDEX": "39", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "32", "NAME": "leaf litter labile proportion", "INDEX": "40", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "5", "TYPE": "2"}, + {"X": "33", "NAME": "leaf litter cellulose proportion", "INDEX": "41", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "5", "TYPE": "2"}, + {"X": "34", "NAME": "fine root labile proportion", "INDEX": "42", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "6", "TYPE": "2"}, + {"X": "35", "NAME": "fine root cellulose proportion", "INDEX": "43", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "6", "TYPE": "2"}, + {"X": "36", "NAME": "fruit labile proportion", "INDEX": "44", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "7", "TYPE": "2"}, + {"X": "37", "NAME": "fruit cellulose proportion", "INDEX": "45", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "7", "TYPE": "2"}, + {"X": "38", "NAME": "softstem labile proportion", "INDEX": "46", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "8", "TYPE": "2"}, + {"X": "39", "NAME": "softstem cellulose proportion", "INDEX": "47", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "8", "TYPE": "2"}, + {"X": "40", "NAME": "dead wood cellulose proportion", "INDEX": "48", "UNIT": "prop", "MIN": "0.5", "MAX": "0.9", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "41", "NAME": "canopy water interception coefficient", "INDEX": "49", "UNIT": "1/LAI/d", "MIN": "0.01", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "42", "NAME": "canopy light extinction coefficient", "INDEX": "50", "UNIT": "dimless", "MIN": "0.2", "MAX": "0.8", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "43", "NAME": "potential radiation use efficiency", "INDEX": "51", "UNIT": "g/MJ", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "44", "NAME": "radiation parameter1 (Jiang et al.2015)", "INDEX": "52", "UNIT": "dimless", "MIN": "0.781", "MAX": "0.781", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "45", "NAME": "radiation parameter1 (Jiang et al.2015)", "INDEX": "53", "UNIT": "dimless", "MIN": "-13.596", "MAX": "-13.596", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "46", "NAME": "all-sided to projected leaf area ratio", "INDEX": "54", "UNIT": "dimless", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "47", "NAME": "ratio of shaded SLA:sunlit SLA", "INDEX": "55", "UNIT": "dimless", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "48", "NAME": "fraction of leaf N in Rubisco", "INDEX": "56", "UNIT": "dimless", "MIN": "0.01", "MAX": "0.2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "49", "NAME": "fraction of leaf N in PeP", "INDEX": "57", "UNIT": "dimless", "MIN": "0.0424", "MAX": "0.0424", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "50", "NAME": "maximum stomatal conductance", "INDEX": "58", "UNIT": "m/s", "MIN": "0.001", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "51", "NAME": "cuticular conductance", "INDEX": "59", "UNIT": "m/s", "MIN": "1E-05", "MAX": "0.0001", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "52", "NAME": "boundary layer conductance", "INDEX": "60", "UNIT": "m/s", "MIN": "0.01", "MAX": "0.09", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "53", "NAME": "maximum height of plant", "INDEX": "61", "UNIT": "m", "MIN": "0.1", "MAX": "10", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "54", "NAME": "stem weight corresponding to maximum height", "INDEX": "62", "UNIT": "kgC", "MIN": "0.1", "MAX": "100", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "55", "NAME": "plant height function shape parameter (slope)", "INDEX": "63", "UNIT": "dimless", "MIN": "0.5", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "56", "NAME": "maximum depth of rooting zone", "INDEX": "64", "UNIT": "m", "MIN": "0.1", "MAX": "10", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "57", "NAME": "root distribution parameter", "INDEX": "65", "UNIT": "prop", "MIN": "3.67", "MAX": "3.67", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "58", "NAME": "root weight corresponding to max root depth", "INDEX": "66", "UNIT": "kgC/m2", "MIN": "0.4", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "59", "NAME": "root depth function shape parameter (slope)", "INDEX": "67", "UNIT": "prop", "MIN": "0.5", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "60", "NAME": "root weight to rooth length conversion factor", "INDEX": "68", "UNIT": "m/kg", "MIN": "1000", "MAX": "1000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "61", "NAME": "growth resp per unit of C grown", "INDEX": "69", "UNIT": "prop", "MIN": "0.1", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "62", "NAME": "maintenance respiration in kgC/day per kg of tissue N", "INDEX": "70", "UNIT": "kgC/kgN/d", "MIN": "0.1", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "63", "NAME": "theoretical maximum prop. of non-structural and structural carbohydrates", "INDEX": "71", "UNIT": "dimless", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "64", "NAME": "prop. of non-structural carbohydrates available for maintanance resp", "INDEX": "72", "UNIT": "dimless", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "65", "NAME": "symbiotic+asymbiotic fixation of N", "INDEX": "73", "UNIT": "kgN/m2/yr", "MIN": "0", "MAX": "0.001", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "66", "NAME": "time delay for temperature in photosynthesis acclimation", "INDEX": "74", "UNIT": "day", "MIN": "0", "MAX": "50", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "67", "NAME": "critical VWCratio (prop. to FC-WP) in germination", "INDEX": "79", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "68", "NAME": "critical photoslow daylength", "INDEX": "81", "UNIT": "hour", "MIN": "14", "MAX": "18", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "69", "NAME": "slope of relative photoslow development rate", "INDEX": "82", "UNIT": "dimless", "MIN": "0.005", "MAX": "0.005", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "70", "NAME": "critical vernalization temperature 1", "INDEX": "84", "UNIT": "Celsius", "MIN": "-5", "MAX": "5", "DEPENDENCE": "0", "GROUP": "9", "TYPE": "1"}, + {"X": "71", "NAME": "critical vernalization temperature 2", "INDEX": "85", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "1", "GROUP": "9", "TYPE": "1"}, + {"X": "72", "NAME": "critical vernalization temperature 3", "INDEX": "86", "UNIT": "Celsius", "MIN": "5", "MAX": "15", "DEPENDENCE": "2", "GROUP": "9", "TYPE": "1"}, + {"X": "73", "NAME": "critical vernalization temperature 4", "INDEX": "87", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "3", "GROUP": "9", "TYPE": "1"}, + {"X": "74", "NAME": "slope of relative vernalization development rate", "INDEX": "88", "UNIT": "dimless", "MIN": "0.04", "MAX": "0.04", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "75", "NAME": "required vernalization days (in vernalization development rate)", "INDEX": "89", "UNIT": "dimless", "MIN": "30", "MAX": "70", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "76", "NAME": "critical flowering heat stress temperature 1", "INDEX": "91", "UNIT": "Celsius", "MIN": "30", "MAX": "40", "DEPENDENCE": "0", "GROUP": "10", "TYPE": "1"}, + {"X": "77", "NAME": "critical flowering heat stress temperature 2", "INDEX": "92", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "1", "GROUP": "10", "TYPE": "1"}, + {"X": "78", "NAME": "theoretical maximum of flowering thermal stress mortality", "INDEX": "93", "UNIT": "prop", "MIN": "0", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "79", "NAME": "VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)", "INDEX": "96", "UNIT": "prop", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "80", "NAME": "VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)", "INDEX": "97", "UNIT": "prop", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "81", "NAME": "minimum of soil moisture limit2 multiplicator (full anoxic stress value)", "INDEX": "98", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "82", "NAME": "vapor pressure deficit: start of conductance reduction", "INDEX": "99", "UNIT": "Pa", "MIN": "500", "MAX": "1500", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "83", "NAME": "vapor pressure deficit: complete conductance reduction", "INDEX": "100", "UNIT": "Pa", "MIN": "1500", "MAX": "3500", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "84", "NAME": "maximum senescence mortality coefficient of aboveground plant material", "INDEX": "101", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "85", "NAME": "maximum senescence mortality coefficient of belowground plant material", "INDEX": "102", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "86", "NAME": "maximum senescence mortality coefficient of non-structured plant material", "INDEX": "103", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "87", "NAME": "lower limit extreme high temperature effect on senescence mortality", "INDEX": "104", "UNIT": "Celsius", "MIN": "30", "MAX": "40", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "88", "NAME": "upper limit extreme high temperature effect on senescence mortality", "INDEX": "105", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "89", "NAME": "turnover rate of wilted standing biomass to litter", "INDEX": "106", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "90", "NAME": "turnover rate of cut-down non-woody biomass to litter", "INDEX": "107", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "91", "NAME": "turnover rate of cut-down woody biomass to litter", "INDEX": "108", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "92", "NAME": "drought tolerance parameter (critical value of day since water stress)", "INDEX": "109", "UNIT": "n_day", "MIN": "0", "MAX": "100", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "93", "NAME": "crit. amount of snow limiting photosyn.", "INDEX": "112", "UNIT": "kg/m2", "MIN": "0", "MAX": "20", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "94", "NAME": "limit1 (under:full constrained) of HEATSUM index", "INDEX": "113", "UNIT": "Celsius", "MIN": "0", "MAX": "50", "DEPENDENCE": "0", "GROUP": "11", "TYPE": "1"}, + {"X": "95", "NAME": "limit2 (above:unconstrained) of HEATSUM index", "INDEX": "114", "UNIT": "Celsius", "MIN": "0", "MAX": "100", "DEPENDENCE": "1", "GROUP": "11", "TYPE": "1"}, + {"X": "96", "NAME": "limit1 (under:full constrained) of TMIN index", "INDEX": "115", "UNIT": "Celsius", "MIN": "-5", "MAX": "5", "DEPENDENCE": "0", "GROUP": "12", "TYPE": "1"}, + {"X": "97", "NAME": "limit2 (above:unconstrained) of TMIN index", "INDEX": "116", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "1", "GROUP": "12", "TYPE": "1"}, + {"X": "98", "NAME": "limit1 (above:full constrained) of VPD index", "INDEX": "117", "UNIT": "Pa", "MIN": "2000", "MAX": "600", "DEPENDENCE": "0", "GROUP": "13", "TYPE": "1"}, + {"X": "99", "NAME": "limit2 (under:unconstrained) of VPD index", "INDEX": "118", "UNIT": "Pa", "MIN": "500", "MAX": "1500", "DEPENDENCE": "1", "GROUP": "13", "TYPE": "1"}, + {"X": "100", "NAME": "limit1 (under:full constrained) of DAYLENGTH index", "INDEX": "119", "UNIT": "s", "MIN": "0", "MAX": "0", "DEPENDENCE": "0", "GROUP": "14", "TYPE": "1"}, + {"X": "101", "NAME": "limit2 (above:unconstrained) of DAYLENGTH index", "INDEX": "120", "UNIT": "s", "MIN": "0", "MAX": "0", "DEPENDENCE": "1", "GROUP": "14", "TYPE": "1"}, + {"X": "102", "NAME": "moving average (to avoid the effects of extreme events)", "INDEX": "121", "UNIT": "n_day", "MIN": "2", "MAX": "20", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "103", "NAME": "GSI limit1 (greater that limit -> start of vegper)", "INDEX": "122", "UNIT": "dimless", "MIN": "0", "MAX": "0.2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "104", "NAME": "GSI limit2 (less that limit -> end of vegper)", "INDEX": "123", "UNIT": "dimless", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-0", "INDEX": "127.6", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -0", "INDEX": "128.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-0", "INDEX": "129.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -0", "INDEX": "130.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-0", "INDEX": "131.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -0", "INDEX": "132.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -0", "INDEX": "133.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-0", "INDEX": "134.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -0", "INDEX": "135.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-0", "INDEX": "136.6", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-0", "INDEX": "137.6", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-0", "INDEX": "138.6", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-1", "INDEX": "127.61", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -1", "INDEX": "128.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-1", "INDEX": "129.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -1", "INDEX": "130.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-1", "INDEX": "131.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -1", "INDEX": "132.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -1", "INDEX": "133.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-1", "INDEX": "134.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -1", "INDEX": "135.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-1", "INDEX": "136.61", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-1", "INDEX": "137.61", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-1", "INDEX": "138.61", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-2", "INDEX": "127.62", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -2", "INDEX": "128.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-2", "INDEX": "129.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -2", "INDEX": "130.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-2", "INDEX": "131.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -2", "INDEX": "132.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -2", "INDEX": "133.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-2", "INDEX": "134.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -2", "INDEX": "135.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-2", "INDEX": "136.62", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-2", "INDEX": "137.62", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-2", "INDEX": "138.62", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-3", "INDEX": "127.63", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -3", "INDEX": "128.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-3", "INDEX": "129.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -3", "INDEX": "130.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-3", "INDEX": "131.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -3", "INDEX": "132.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -3", "INDEX": "133.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-3", "INDEX": "134.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -3", "INDEX": "135.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-3", "INDEX": "136.63", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-3", "INDEX": "137.63", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-3", "INDEX": "138.63", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-4", "INDEX": "127.64", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -4", "INDEX": "128.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-4", "INDEX": "129.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -4", "INDEX": "130.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-4", "INDEX": "131.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -4", "INDEX": "132.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -4", "INDEX": "133.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-4", "INDEX": "134.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -4", "INDEX": "135.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-4", "INDEX": "136.64", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-4", "INDEX": "137.64", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-4", "INDEX": "138.64", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-5", "INDEX": "127.65", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -5", "INDEX": "128.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-5", "INDEX": "129.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -5", "INDEX": "130.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-5", "INDEX": "131.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -5", "INDEX": "132.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -5", "INDEX": "133.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-5", "INDEX": "134.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -5", "INDEX": "135.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-5", "INDEX": "136.65", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-5", "INDEX": "137.65", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-5", "INDEX": "138.65", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "105", "NAME": "length of phenophase (GDD)-6", "INDEX": "127.6", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "106", "NAME": "leaf ALLOCATION -6", "INDEX": "128.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "107", "NAME": "fine root ALLOCATION-6", "INDEX": "129.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "108", "NAME": "fruit ALLOCATION -6", "INDEX": "130.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "109", "NAME": "soft stem ALLOCATION-6", "INDEX": "131.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "110", "NAME": "live woody stem ALLOCATION -6", "INDEX": "132.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "111", "NAME": "dead woody stem ALLOCATION -6", "INDEX": "133.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "112", "NAME": "live coarse root ALLOCATION-6", "INDEX": "134.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "113", "NAME": "dead coarse root ALLOCATION -6", "INDEX": "135.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"}, + {"X": "114", "NAME": "canopy average specific leaf area-6", "INDEX": "136.66", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "115", "NAME": "current growth proportion-6", "INDEX": "137.66", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}, + {"X": "116", "NAME": "maximal lifetime of plant tissue-6", "INDEX": "138.66", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"} +] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/depTree.csv b/RBBGCMuso.Rcheck/RBBGCMuso/data/depTree.csv new file mode 100644 index 0000000..afa513a --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/depTree.csv @@ -0,0 +1,18 @@ +"child","parent","mod","name" +"wth","ini",1,"weather" +"endpoint","ini",1,"endpointIn" +"endpoint","ini",2,"endpointOut" +"txt","ini",1,"co2" +"txt","ini",2,"nitrogen" +"soi","ini",1,"soil" +"epc","ini",1,"startEpc" +"mgm","ini",1,"management" +"plt","mgm",1,"planting" +"thn","mgm",1,"thining" +"mow","mgm",1,"mowing" +"grz","mgm",1,"grazing" +"hrv","mgm",1,"harvest" +"cul","mgm",1,"cultivation" +"frz","mgm",1,"fertilization" +"irr","mgm",1,"irrigation" +"epc","plt",0,"plantEpc" diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/epcConstMatrix5.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/epcConstMatrix5.json new file mode 100644 index 0000000..d691e1b --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/epcConstMatrix5.json @@ -0,0 +1 @@ +[{"X":1,"NAME":"yearday to start new growth","INDEX":9,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":2,"NAME":"yearday to end new growth","INDEX":10,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":3,"NAME":"transfer growth period as fraction of growing season","INDEX":11,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":4,"NAME":"litterfall as fraction of growing season","INDEX":12,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":5,"NAME":"base temperature","INDEX":13,"UNIT":"Celsius","MIN":0,"MAX":12,"GROUP":0,"TYPE":0},{"X":6,"NAME":"minimum temperature for growth displayed on current day","INDEX":14,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":1,"TYPE":1},{"X":7,"NAME":"optimal1 temperature for growth displayed on current day","INDEX":15,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":1,"TYPE":1},{"X":8,"NAME":"optimal2 temperature for growth displayed on current day","INDEX":16,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":1,"TYPE":1},{"X":9,"NAME":"maxmimum temperature for growth displayed on current day","INDEX":17,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":1,"TYPE":1},{"X":10,"NAME":"minimum temperature for carbon assimilation displayed on current day","INDEX":18,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":2,"TYPE":1},{"X":11,"NAME":"optimal1 temperature for carbon assimilation displayed on current day","INDEX":19,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":2,"TYPE":1},{"X":12,"NAME":"optimal2 temperature for carbon assimilation displayed on current day","INDEX":20,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":2,"TYPE":1},{"X":13,"NAME":"maxmimum temperature for carbon assimilation displayed on current day","INDEX":21,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":2,"TYPE":1},{"X":14,"NAME":"annual leaf and fine root turnover fraction","INDEX":22,"UNIT":"1/yr","MIN":0.1,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":15,"NAME":"annual live wood turnover fraction","INDEX":23,"UNIT":"1/yr","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":16,"NAME":"annual fire mortality fraction","INDEX":24,"UNIT":"1/yr","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":17,"NAME":"whole-plant mortality paramter for vegetation period","INDEX":25,"UNIT":"1/vegper","MIN":0,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":18,"NAME":"C:N of leaves","INDEX":26,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":10,"MAX":100,"GROUP":0,"TYPE":0},{"X":19,"NAME":"C:N of leaf litter","INDEX":27,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":20,"NAME":"C:N of fine roots","INDEX":28,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":21,"NAME":"C:N of fruit","INDEX":29,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":22,"NAME":"C:N of softstem","INDEX":30,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":23,"NAME":"C:N of live wood","INDEX":31,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":50,"MAX":100,"GROUP":4,"TYPE":1},{"X":24,"NAME":"C:N of dead wood","INDEX":32,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":300,"MAX":800,"GROUP":4,"TYPE":1},{"X":25,"NAME":"dry matter content of leaves","INDEX":33,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":26,"NAME":"dry matter content of leaf litter","INDEX":34,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":27,"NAME":"dry matter content of fine roots","INDEX":35,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":28,"NAME":"dry matter content of fruit","INDEX":36,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":29,"NAME":"dry matter content of softstem","INDEX":37,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":30,"NAME":"dry matter content of live wood","INDEX":38,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":31,"NAME":"dry matter content of dead wood","INDEX":39,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":32,"NAME":"leaf litter labile proportion","INDEX":40,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":33,"NAME":"leaf litter cellulose proportion","INDEX":41,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":34,"NAME":"fine root labile proportion","INDEX":42,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":35,"NAME":"fine root cellulose proportion","INDEX":43,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":36,"NAME":"fruit labile proportion","INDEX":44,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":37,"NAME":"fruit cellulose proportion","INDEX":45,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":38,"NAME":"softstem labile proportion","INDEX":46,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":39,"NAME":"softstem cellulose proportion","INDEX":47,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":40,"NAME":"dead wood cellulose proportion","INDEX":48,"UNIT":"prop","MIN":0.5,"MAX":0.9,"GROUP":0,"TYPE":0},{"X":41,"NAME":"canopy water interception coefficient","INDEX":49,"UNIT":"1/LAI/d","MIN":0.01,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":42,"NAME":"canopy light extinction coefficient","INDEX":50,"UNIT":"dimless","MIN":0.2,"MAX":0.8,"GROUP":0,"TYPE":0},{"X":43,"NAME":"potential radiation use efficiency","INDEX":51,"UNIT":"g/MJ","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":44,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":52,"UNIT":"dimless","MIN":0.781,"MAX":0.781,"GROUP":0,"TYPE":0},{"X":45,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":53,"UNIT":"dimless","MIN":-13.596,"MAX":-13.596,"GROUP":0,"TYPE":0},{"X":46,"NAME":"all-sided to projected leaf area ratio","INDEX":54,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":47,"NAME":"ratio of shaded SLA:sunlit SLA","INDEX":55,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":48,"NAME":"fraction of leaf N in Rubisco","INDEX":56,"UNIT":"dimless","MIN":0.01,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":49,"NAME":"fraction of leaf N in PeP","INDEX":57,"UNIT":"dimless","MIN":0.0424,"MAX":0.0424,"GROUP":0,"TYPE":0},{"X":50,"NAME":"maximum stomatal conductance ","INDEX":58,"UNIT":"m/s","MIN":0.001,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":51,"NAME":"cuticular conductance ","INDEX":59,"UNIT":"m/s","MIN":1e-05,"MAX":0.0001,"GROUP":0,"TYPE":0},{"X":52,"NAME":"boundary layer conductance","INDEX":60,"UNIT":"m/s","MIN":0.01,"MAX":0.09,"GROUP":0,"TYPE":0},{"X":53,"NAME":"maximum height of plant","INDEX":61,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":54,"NAME":"stem weight corresponding to maximum height","INDEX":62,"UNIT":"kgC","MIN":0.1,"MAX":100,"GROUP":0,"TYPE":0},{"X":55,"NAME":"plant height function shape parameter (slope)","INDEX":63,"UNIT":"dimless","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":56,"NAME":"maximum depth of rooting zone","INDEX":64,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":57,"NAME":"root distribution parameter","INDEX":65,"UNIT":"prop","MIN":3.67,"MAX":3.67,"GROUP":0,"TYPE":0},{"X":58,"NAME":"root weight corresponding to max root depth","INDEX":66,"UNIT":"kgC/m2","MIN":0.4,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":59,"NAME":"root depth function shape parameter (slope)","INDEX":67,"UNIT":"prop","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":60,"NAME":"root weight to rooth length conversion factor","INDEX":68,"UNIT":"m/kg","MIN":1000,"MAX":1000,"GROUP":0,"TYPE":0},{"X":61,"NAME":"growth resp per unit of C grown","INDEX":69,"UNIT":"prop","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":62,"NAME":"maintenance respiration in kgC/day per kg of tissue N ","INDEX":70,"UNIT":"kgC/kgN/d","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":63,"NAME":"theoretical maximum prop. of non-structural and structural carbohydrates","INDEX":71,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":64,"NAME":"prop. of non-structural carbohydrates available for maintanance resp","INDEX":72,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":65,"NAME":"symbiotic+asymbiotic fixation of N","INDEX":73,"UNIT":"kgN/m2/yr","MIN":0,"MAX":0.001,"GROUP":0,"TYPE":0},{"X":66,"NAME":"time delay for temperature in photosynthesis acclimation","INDEX":74,"UNIT":"day","MIN":0,"MAX":50,"GROUP":0,"TYPE":0},{"X":67,"NAME":"critical VWCratio (prop. to FC-WP) in germination","INDEX":79,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":68,"NAME":"critical photoslow daylength","INDEX":81,"UNIT":"hour","MIN":14,"MAX":18,"GROUP":0,"TYPE":0},{"X":69,"NAME":"slope of relative photoslow development rate ","INDEX":82,"UNIT":"dimless","MIN":0.005,"MAX":0.005,"GROUP":0,"TYPE":0},{"X":70,"NAME":"critical vernalization temperature 1","INDEX":84,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":9,"TYPE":1},{"X":71,"NAME":"critical vernalization temperature 2","INDEX":85,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":9,"TYPE":1},{"X":72,"NAME":"critical vernalization temperature 3","INDEX":86,"UNIT":"Celsius","DEPENDENCE":2,"MIN":5,"MAX":15,"GROUP":9,"TYPE":1},{"X":73,"NAME":"critical vernalization temperature 4","INDEX":87,"UNIT":"Celsius","DEPENDENCE":3,"MIN":10,"MAX":20,"GROUP":9,"TYPE":1},{"X":74,"NAME":"slope of relative vernalization development rate ","INDEX":88,"UNIT":"dimless","MIN":0.04,"MAX":0.04,"GROUP":0,"TYPE":0},{"X":75,"NAME":"required vernalization days (in vernalization development rate)","INDEX":89,"UNIT":"dimless","MIN":30,"MAX":70,"GROUP":0,"TYPE":0},{"X":76,"NAME":"critical flowering heat stress temperature 1","INDEX":91,"UNIT":"Celsius","DEPENDENCE":0,"MIN":30,"MAX":40,"GROUP":10,"TYPE":1},{"X":77,"NAME":"critical flowering heat stress temperature 2","INDEX":92,"UNIT":"Celsius","DEPENDENCE":1,"MIN":30,"MAX":50,"GROUP":10,"TYPE":1},{"X":78,"NAME":"theoretical maximum of flowering thermal stress mortality","INDEX":93,"UNIT":"prop","MIN":0,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":79,"NAME":"VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)","INDEX":96,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":80,"NAME":"VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)","INDEX":97,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":81,"NAME":"minimum of soil moisture limit2 multiplicator (full anoxic stress value)","INDEX":98,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":82,"NAME":"vapor pressure deficit: start of conductance reduction","INDEX":99,"UNIT":"Pa","MIN":500,"MAX":1500,"GROUP":0,"TYPE":0},{"X":83,"NAME":"vapor pressure deficit: complete conductance reduction","INDEX":100,"UNIT":"Pa","MIN":1500,"MAX":3500,"GROUP":0,"TYPE":0},{"X":84,"NAME":"maximum senescence mortality coefficient of aboveground plant material","INDEX":101,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":85,"NAME":"maximum senescence mortality coefficient of belowground plant material","INDEX":102,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":86,"NAME":"maximum senescence mortality coefficient of non-structured plant material","INDEX":103,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":87,"NAME":"lower limit extreme high temperature effect on senescence mortality","INDEX":104,"UNIT":"Celsius","MIN":30,"MAX":40,"GROUP":0,"TYPE":0},{"X":88,"NAME":"upper limit extreme high temperature effect on senescence mortality","INDEX":105,"UNIT":"Celsius","MIN":30,"MAX":50,"GROUP":0,"TYPE":0},{"X":89,"NAME":"turnover rate of wilted standing biomass to litter","INDEX":106,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":90,"NAME":"turnover rate of cut-down non-woody biomass to litter","INDEX":107,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":91,"NAME":"turnover rate of cut-down woody biomass to litter","INDEX":108,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":92,"NAME":"drought tolerance parameter (critical value of day since water stress)","INDEX":109,"UNIT":"n_day","MIN":0,"MAX":100,"GROUP":0,"TYPE":0},{"X":93,"NAME":"crit. amount of snow limiting photosyn.","INDEX":112,"UNIT":"kg/m2","MIN":0,"MAX":20,"GROUP":0,"TYPE":0},{"X":94,"NAME":"limit1 (under:full constrained) of HEATSUM index","INDEX":113,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":50,"GROUP":11,"TYPE":1},{"X":95,"NAME":"limit2 (above:unconstrained) of HEATSUM index","INDEX":114,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":100,"GROUP":11,"TYPE":1},{"X":96,"NAME":"limit1 (under:full constrained) of TMIN index","INDEX":115,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":12,"TYPE":1},{"X":97,"NAME":"limit2 (above:unconstrained) of TMIN index","INDEX":116,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":12,"TYPE":1},{"X":98,"NAME":"limit1 (above:full constrained) of VPD index","INDEX":117,"UNIT":"Pa","DEPENDENCE":0,"MIN":2000,"MAX":600,"GROUP":13,"TYPE":1},{"X":99,"NAME":"limit2 (under:unconstrained) of VPD index","INDEX":118,"UNIT":"Pa","DEPENDENCE":1,"MIN":500,"MAX":1500,"GROUP":13,"TYPE":1},{"X":100,"NAME":"limit1 (under:full constrained) of DAYLENGTH index","INDEX":119,"UNIT":"s","DEPENDENCE":0,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":101,"NAME":"limit2 (above:unconstrained) of DAYLENGTH index","INDEX":120,"UNIT":"s","DEPENDENCE":1,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":102,"NAME":"moving average (to avoid the effects of extreme events)","INDEX":121,"UNIT":"n_day","MIN":2,"MAX":20,"GROUP":0,"TYPE":0},{"X":103,"NAME":"GSI limit1 (greater that limit -> start of vegper)","INDEX":122,"UNIT":"dimless","MIN":0,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":104,"NAME":"GSI limit2 (less that limit -> end of vegper)","INDEX":123,"UNIT":"dimless","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":105,"NAME":"length of phenophase (GDD)","INDEX":127,"UNIT":"Celsius","MIN":0,"MAX":10000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -0","INDEX":128.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-0","INDEX":129.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -0","INDEX":130.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-0","INDEX":131.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -0","INDEX":132.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -0","INDEX":133.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-0","INDEX":134.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -0","INDEX":135.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-0","INDEX":136.6,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-0","INDEX":137.6,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-0","INDEX":138.6,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -1","INDEX":128.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-1","INDEX":129.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -1","INDEX":130.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-1","INDEX":131.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -1","INDEX":132.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -1","INDEX":133.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-1","INDEX":134.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -1","INDEX":135.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-1","INDEX":136.61,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-1","INDEX":137.61,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-1","INDEX":138.61,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -2","INDEX":128.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-2","INDEX":129.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -2","INDEX":130.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-2","INDEX":131.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -2","INDEX":132.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -2","INDEX":133.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-2","INDEX":134.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -2","INDEX":135.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-2","INDEX":136.62,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-2","INDEX":137.62,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-2","INDEX":138.62,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -3","INDEX":128.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-3","INDEX":129.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -3","INDEX":130.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-3","INDEX":131.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -3","INDEX":132.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -3","INDEX":133.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-3","INDEX":134.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -3","INDEX":135.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-3","INDEX":136.63,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-3","INDEX":137.63,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-3","INDEX":138.63,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -4","INDEX":128.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-4","INDEX":129.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -4","INDEX":130.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-4","INDEX":131.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -4","INDEX":132.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -4","INDEX":133.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-4","INDEX":134.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -4","INDEX":135.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-4","INDEX":136.64,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-4","INDEX":137.64,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-4","INDEX":138.64,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -5","INDEX":128.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-5","INDEX":129.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -5","INDEX":130.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-5","INDEX":131.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -5","INDEX":132.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -5","INDEX":133.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-5","INDEX":134.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -5","INDEX":135.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-5","INDEX":136.65,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-5","INDEX":137.65,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-5","INDEX":138.65,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -6","INDEX":128.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-6","INDEX":129.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -6","INDEX":130.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-6","INDEX":131.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -6","INDEX":132.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -6","INDEX":133.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-6","INDEX":134.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -6","INDEX":135.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-6","INDEX":136.66,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-6","INDEX":137.66,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-6","INDEX":138.66,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0}] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/epcConstMatrix6.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/epcConstMatrix6.json new file mode 100644 index 0000000..337faac --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/epcConstMatrix6.json @@ -0,0 +1,1987 @@ +[ + { + "X": 1, + "NAME": "yearday to start new growth", + "INDEX": 9, + "UNIT": "yday", + "MIN": 0, + "MAX": 364, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 2, + "NAME": "yearday to end new growth", + "INDEX": 10, + "UNIT": "yday", + "MIN": 0, + "MAX": 364, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 3, + "NAME": "transfer growth period as fraction of growing season", + "INDEX": 11, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 4, + "NAME": "litterfall as fraction of growing season", + "INDEX": 12, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 5, + "NAME": "base temperature", + "INDEX": 13, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 12, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 6, + "NAME": "minimum temperature for growth displayed on current day", + "INDEX": 14, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 0, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 7, + "NAME": "optimal1 temperature for growth displayed on current day", + "INDEX": 15, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 1, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 8, + "NAME": "optimal2 temperature for growth displayed on current day", + "INDEX": 16, + "UNIT": "Celsius", + "MIN": 20, + "MAX": 40, + "DEPENDENCE": 2, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 9, + "NAME": "maxmimum temperature for growth displayed on current day", + "INDEX": 17, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 3, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 10, + "NAME": "minimum temperature for carbon assimilation displayed on current day", + "INDEX": 18, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 0, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 11, + "NAME": "optimal1 temperature for carbon assimilation displayed on current day", + "INDEX": 19, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 1, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 12, + "NAME": "optimal2 temperature for carbon assimilation displayed on current day", + "INDEX": 20, + "UNIT": "Celsius", + "MIN": 20, + "MAX": 40, + "DEPENDENCE": 2, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 13, + "NAME": "maxmimum temperature for carbon assimilation displayed on current day", + "INDEX": 21, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 3, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 14, + "NAME": "annual leaf and fine root turnover fraction", + "INDEX": 22, + "UNIT": "1/yr", + "MIN": 0.1, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 15, + "NAME": "annual live wood turnover fraction", + "INDEX": 23, + "UNIT": "1/yr", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 16, + "NAME": "annual fire mortality fraction", + "INDEX": 24, + "UNIT": "1/yr", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 17, + "NAME": "whole-plant mortality paramter for vegetation period", + "INDEX": 25, + "UNIT": "1/vegper", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 18, + "NAME": "C:N of leaves", + "INDEX": 26, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 100, + "DEPENDENCE": 0, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 19, + "NAME": "C:N of leaf litter", + "INDEX": 27, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 20, + "NAME": "C:N of fine roots", + "INDEX": 28, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 21, + "NAME": "C:N of fruit", + "INDEX": 29, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 22, + "NAME": "C:N of softstem", + "INDEX": 30, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 23, + "NAME": "C:N of live wood", + "INDEX": 31, + "UNIT": "kgC/kgN", + "MIN": 50, + "MAX": 100, + "DEPENDENCE": 0, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 24, + "NAME": "C:N of dead wood", + "INDEX": 32, + "UNIT": "kgC/kgN", + "MIN": 300, + "MAX": 800, + "DEPENDENCE": 1, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 25, + "NAME": "dry matter content of leaves", + "INDEX": 33, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 26, + "NAME": "dry matter content of leaf litter", + "INDEX": 34, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 27, + "NAME": "dry matter content of fine roots", + "INDEX": 35, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 28, + "NAME": "dry matter content of fruit", + "INDEX": 36, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 29, + "NAME": "dry matter content of softstem", + "INDEX": 37, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 30, + "NAME": "dry matter content of live wood", + "INDEX": 38, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 31, + "NAME": "dry matter content of dead wood", + "INDEX": 39, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 32, + "NAME": "leaf litter labile proportion", + "INDEX": 40, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 33, + "NAME": "leaf litter cellulose proportion", + "INDEX": 41, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 34, + "NAME": "fine root labile proportion", + "INDEX": 42, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 6, + "TYPE": 2 + }, + { + "X": 35, + "NAME": "fine root cellulose proportion", + "INDEX": 43, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 6, + "TYPE": 2 + }, + { + "X": 36, + "NAME": "fruit labile proportion", + "INDEX": 44, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 37, + "NAME": "fruit cellulose proportion", + "INDEX": 45, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 38, + "NAME": "softstem labile proportion", + "INDEX": 46, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 8, + "TYPE": 2 + }, + { + "X": 39, + "NAME": "softstem cellulose proportion", + "INDEX": 47, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 8, + "TYPE": 2 + }, + { + "X": 40, + "NAME": "dead wood cellulose proportion", + "INDEX": 48, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 0.9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 41, + "NAME": "canopy water interception coefficient", + "INDEX": 49, + "UNIT": "1/LAI/d", + "MIN": 0.01, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 42, + "NAME": "canopy light extinction coefficient", + "INDEX": 50, + "UNIT": "dimless", + "MIN": 0.2, + "MAX": 0.8, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 43, + "NAME": "potential radiation use efficiency", + "INDEX": 51, + "UNIT": "g/MJ", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "radiation parameter1 (Jiang et al.2015)", + "INDEX": 52, + "UNIT": "dimless", + "MIN": 0.781, + "MAX": 0.781, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 45, + "NAME": "radiation parameter1 (Jiang et al.2015)", + "INDEX": 53, + "UNIT": "dimless", + "MIN": -13.596, + "MAX": -13.596, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 46, + "NAME": "all-sided to projected leaf area ratio", + "INDEX": 54, + "UNIT": "dimless", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "ratio of shaded SLA:sunlit SLA", + "INDEX": 55, + "UNIT": "dimless", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "fraction of leaf N in Rubisco", + "INDEX": 56, + "UNIT": "dimless", + "MIN": 0.01, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 49, + "NAME": "fraction of leaf N in PeP", + "INDEX": 57, + "UNIT": "dimless", + "MIN": 0.0424, + "MAX": 0.0424, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 50, + "NAME": "maximum stomatal conductance", + "INDEX": 58, + "UNIT": "m/s", + "MIN": 0.001, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 51, + "NAME": "cuticular conductance", + "INDEX": 59, + "UNIT": "m/s", + "MIN": 1e-05, + "MAX": 0.0001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 52, + "NAME": "boundary layer conductance", + "INDEX": 60, + "UNIT": "m/s", + "MIN": 0.01, + "MAX": 0.09, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "maximum height of plant", + "INDEX": 61, + "UNIT": "m", + "MIN": 0.1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 54, + "NAME": "stem weight corresponding to maximum height", + "INDEX": 62, + "UNIT": "kgC", + "MIN": 0.1, + "MAX": 100, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 55, + "NAME": "plant height function shape parameter (slope)", + "INDEX": 63, + "UNIT": "dimless", + "MIN": 0.5, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 56, + "NAME": "maximum depth of rooting zone", + "INDEX": 64, + "UNIT": "m", + "MIN": 0.1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 57, + "NAME": "root distribution parameter", + "INDEX": 65, + "UNIT": "prop", + "MIN": 3.67, + "MAX": 3.67, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 58, + "NAME": "root weight corresponding to max root depth", + "INDEX": 66, + "UNIT": "kgC/m2", + "MIN": 0.4, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 59, + "NAME": "root depth function shape parameter (slope)", + "INDEX": 67, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 60, + "NAME": "root weight to rooth length conversion factor", + "INDEX": 68, + "UNIT": "m/kg", + "MIN": 1000, + "MAX": 1000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 61, + "NAME": "growth resp per unit of C grown", + "INDEX": 69, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 62, + "NAME": "maintenance respiration in kgC/day per kg of tissue N", + "INDEX": 70, + "UNIT": "kgC/kgN/d", + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 63, + "NAME": "theoretical maximum prop. of non-structural and structural carbohydrates", + "INDEX": 71, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 64, + "NAME": "prop. of non-structural carbohydrates available for maintanance resp", + "INDEX": 72, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 65, + "NAME": "symbiotic+asymbiotic fixation of N", + "INDEX": 73, + "UNIT": "kgN/m2/yr", + "MIN": 0, + "MAX": 0.001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 66, + "NAME": "time delay for temperature in photosynthesis acclimation", + "INDEX": 74, + "UNIT": "day", + "MIN": 0, + "MAX": 50, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 67, + "NAME": "critical VWCratio (prop. to FC-WP) in germination", + "INDEX": 79, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 68, + "NAME": "critical photoslow daylength", + "INDEX": 81, + "UNIT": "hour", + "MIN": 14, + "MAX": 18, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 69, + "NAME": "slope of relative photoslow development rate", + "INDEX": 82, + "UNIT": "dimless", + "MIN": 0.005, + "MAX": 0.005, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 70, + "NAME": "critical vernalization temperature 1", + "INDEX": 84, + "UNIT": "Celsius", + "MIN": -5, + "MAX": 5, + "DEPENDENCE": 0, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 71, + "NAME": "critical vernalization temperature 2", + "INDEX": 85, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 1, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 72, + "NAME": "critical vernalization temperature 3", + "INDEX": 86, + "UNIT": "Celsius", + "MIN": 5, + "MAX": 15, + "DEPENDENCE": 2, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 73, + "NAME": "critical vernalization temperature 4", + "INDEX": 87, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 3, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 74, + "NAME": "slope of relative vernalization development rate", + "INDEX": 88, + "UNIT": "dimless", + "MIN": 0.04, + "MAX": 0.04, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 75, + "NAME": "required vernalization days (in vernalization development rate)", + "INDEX": 89, + "UNIT": "dimless", + "MIN": 30, + "MAX": 70, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 76, + "NAME": "critical flowering heat stress temperature 1", + "INDEX": 91, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 40, + "DEPENDENCE": 0, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 77, + "NAME": "critical flowering heat stress temperature 2", + "INDEX": 92, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 1, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 78, + "NAME": "theoretical maximum of flowering thermal stress mortality", + "INDEX": 93, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 79, + "NAME": "VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)", + "INDEX": 96, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 80, + "NAME": "VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)", + "INDEX": 97, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 81, + "NAME": "minimum of soil moisture limit2 multiplicator (full anoxic stress value)", + "INDEX": 98, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 82, + "NAME": "vapor pressure deficit: start of conductance reduction", + "INDEX": 99, + "UNIT": "Pa", + "MIN": 500, + "MAX": 1500, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 83, + "NAME": "vapor pressure deficit: complete conductance reduction", + "INDEX": 100, + "UNIT": "Pa", + "MIN": 1500, + "MAX": 3500, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 84, + "NAME": "maximum senescence mortality coefficient of aboveground plant material", + "INDEX": 101, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "DEPENDENCE": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 85, + "NAME": "maximum senescence mortality coefficient of belowground plant material", + "INDEX": 102, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "DEPENDENCE": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 86, + "NAME": "maximum senescence mortality coefficient of non-structured plant material", + "INDEX": 103, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 87, + "NAME": "lower limit extreme high temperature effect on senescence mortality", + "INDEX": 104, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 88, + "NAME": "upper limit extreme high temperature effect on senescence mortality", + "INDEX": 105, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 89, + "NAME": "turnover rate of wilted standing biomass to litter", + "INDEX": 106, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 90, + "NAME": "turnover rate of cut-down non-woody biomass to litter", + "INDEX": 107, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 91, + "NAME": "turnover rate of cut-down woody biomass to litter", + "INDEX": 108, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 92, + "NAME": "drought tolerance parameter (critical value of day since water stress)", + "INDEX": 109, + "UNIT": "n_day", + "MIN": 0, + "MAX": 100, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 93, + "NAME": "effect of soilstress factor on photosynthesis", + "INDEX": 110, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 94, + "NAME": "crit. amount of snow limiting photosyn.", + "INDEX": 113, + "UNIT": "kg/m2", + "MIN": 0, + "MAX": 20, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 95, + "NAME": "limit1 (under:full constrained) of HEATSUM index", + "INDEX": 114, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 50, + "DEPENDENCE": 0, + "GROUP": 11, + "TYPE": 1 + }, + { + "X": 96, + "NAME": "limit2 (above:unconstrained) of HEATSUM index", + "INDEX": 115, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 100, + "DEPENDENCE": 1, + "GROUP": 11, + "TYPE": 1 + }, + { + "X": 97, + "NAME": "limit1 (under:full constrained) of TMIN index", + "INDEX": 116, + "UNIT": "Celsius", + "MIN": -5, + "MAX": 5, + "DEPENDENCE": 0, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 98, + "NAME": "limit2 (above:unconstrained) of TMIN index", + "INDEX": 117, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 1, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 99, + "NAME": "limit1 (above:full constrained) of VPD index", + "INDEX": 118, + "UNIT": "Pa", + "MIN": 2000, + "MAX": 600, + "DEPENDENCE": 0, + "GROUP": 13, + "TYPE": 1 + }, + { + "X": 100, + "NAME": "limit2 (under:unconstrained) of VPD index", + "INDEX": 119, + "UNIT": "Pa", + "MIN": 500, + "MAX": 1500, + "DEPENDENCE": 1, + "GROUP": 13, + "TYPE": 1 + }, + { + "X": 101, + "NAME": "limit1 (under:full constrained) of DAYLENGTH index", + "INDEX": 120, + "UNIT": "s", + "MIN": 0, + "MAX": 0, + "DEPENDENCE": 0, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 102, + "NAME": "limit2 (above:unconstrained) of DAYLENGTH index", + "INDEX": 121, + "UNIT": "s", + "MIN": 0, + "MAX": 0, + "DEPENDENCE": 1, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 103, + "NAME": "moving average (to avoid the effects of extreme events)", + "INDEX": 122, + "UNIT": "n_day", + "MIN": 2, + "MAX": 20, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 104, + "NAME": "GSI limit1 (greater that limit -> start of vegper)", + "INDEX": 123, + "UNIT": "dimless", + "MIN": 0, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 105, + "NAME": "GSI limit2 (less that limit -> end of vegper)", + "INDEX": 124, + "UNIT": "dimless", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-0", + "INDEX": 128.6, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -0", + "INDEX": 129.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-0", + "INDEX": 130.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -0", + "INDEX": 131.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-0", + "INDEX": 132.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -0", + "INDEX": 133.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -0", + "INDEX": 134.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-0", + "INDEX": 135.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -0", + "INDEX": 136.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-0", + "INDEX": 137.6, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-0", + "INDEX": 138.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-0", + "INDEX": 139.6, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-1", + "INDEX": 128.61, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -1", + "INDEX": 129.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-1", + "INDEX": 130.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -1", + "INDEX": 131.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-1", + "INDEX": 132.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -1", + "INDEX": 133.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -1", + "INDEX": 134.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-1", + "INDEX": 135.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -1", + "INDEX": 136.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-1", + "INDEX": 137.61, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-1", + "INDEX": 138.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-1", + "INDEX": 139.61, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-2", + "INDEX": 128.62, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -2", + "INDEX": 129.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-2", + "INDEX": 130.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -2", + "INDEX": 131.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-2", + "INDEX": 132.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -2", + "INDEX": 133.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -2", + "INDEX": 134.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-2", + "INDEX": 135.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -2", + "INDEX": 136.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-2", + "INDEX": 137.62, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-2", + "INDEX": 138.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-2", + "INDEX": 139.62, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-3", + "INDEX": 128.63, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -3", + "INDEX": 129.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-3", + "INDEX": 130.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -3", + "INDEX": 131.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-3", + "INDEX": 132.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -3", + "INDEX": 133.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -3", + "INDEX": 134.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-3", + "INDEX": 135.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -3", + "INDEX": 136.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-3", + "INDEX": 137.63, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-3", + "INDEX": 138.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-3", + "INDEX": 139.63, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-4", + "INDEX": 128.64, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -4", + "INDEX": 129.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-4", + "INDEX": 130.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -4", + "INDEX": 131.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-4", + "INDEX": 132.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -4", + "INDEX": 133.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -4", + "INDEX": 134.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-4", + "INDEX": 135.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -4", + "INDEX": 136.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-4", + "INDEX": 137.64, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-4", + "INDEX": 138.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-4", + "INDEX": 139.64, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-5", + "INDEX": 128.65, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -5", + "INDEX": 129.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-5", + "INDEX": 130.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -5", + "INDEX": 131.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-5", + "INDEX": 132.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -5", + "INDEX": 133.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -5", + "INDEX": 134.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-5", + "INDEX": 135.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -5", + "INDEX": 136.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-5", + "INDEX": 137.65, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-5", + "INDEX": 138.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-5", + "INDEX": 139.65, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 106, + "NAME": "length of phenophase (GDD)-6", + "INDEX": 128.66, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "leaf ALLOCATION -6", + "INDEX": 129.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 108, + "NAME": "fine root ALLOCATION-6", + "INDEX": 130.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 109, + "NAME": "fruit ALLOCATION -6", + "INDEX": 131.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 110, + "NAME": "soft stem ALLOCATION-6", + "INDEX": 132.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "live woody stem ALLOCATION -6", + "INDEX": 133.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "dead woody stem ALLOCATION -6", + "INDEX": 134.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "live coarse root ALLOCATION-6", + "INDEX": 135.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "dead coarse root ALLOCATION -6", + "INDEX": 136.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "canopy average specific leaf area-6", + "INDEX": 137.66, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 116, + "NAME": "current growth proportion-6", + "INDEX": 138.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 117, + "NAME": "maximal lifetime of plant tissue-6", + "INDEX": 139.66, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + } +] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/soilConstMatrix5.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/soilConstMatrix5.json new file mode 100644 index 0000000..d691e1b --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/soilConstMatrix5.json @@ -0,0 +1 @@ +[{"X":1,"NAME":"yearday to start new growth","INDEX":9,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":2,"NAME":"yearday to end new growth","INDEX":10,"UNIT":"yday","MIN":0,"MAX":364,"GROUP":0,"TYPE":0},{"X":3,"NAME":"transfer growth period as fraction of growing season","INDEX":11,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":4,"NAME":"litterfall as fraction of growing season","INDEX":12,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":5,"NAME":"base temperature","INDEX":13,"UNIT":"Celsius","MIN":0,"MAX":12,"GROUP":0,"TYPE":0},{"X":6,"NAME":"minimum temperature for growth displayed on current day","INDEX":14,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":1,"TYPE":1},{"X":7,"NAME":"optimal1 temperature for growth displayed on current day","INDEX":15,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":1,"TYPE":1},{"X":8,"NAME":"optimal2 temperature for growth displayed on current day","INDEX":16,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":1,"TYPE":1},{"X":9,"NAME":"maxmimum temperature for growth displayed on current day","INDEX":17,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":1,"TYPE":1},{"X":10,"NAME":"minimum temperature for carbon assimilation displayed on current day","INDEX":18,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":10,"GROUP":2,"TYPE":1},{"X":11,"NAME":"optimal1 temperature for carbon assimilation displayed on current day","INDEX":19,"UNIT":"Celsius","DEPENDENCE":1,"MIN":10,"MAX":20,"GROUP":2,"TYPE":1},{"X":12,"NAME":"optimal2 temperature for carbon assimilation displayed on current day","INDEX":20,"UNIT":"Celsius","DEPENDENCE":2,"MIN":20,"MAX":40,"GROUP":2,"TYPE":1},{"X":13,"NAME":"maxmimum temperature for carbon assimilation displayed on current day","INDEX":21,"UNIT":"Celsius","DEPENDENCE":3,"MIN":30,"MAX":50,"GROUP":2,"TYPE":1},{"X":14,"NAME":"annual leaf and fine root turnover fraction","INDEX":22,"UNIT":"1/yr","MIN":0.1,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":15,"NAME":"annual live wood turnover fraction","INDEX":23,"UNIT":"1/yr","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":16,"NAME":"annual fire mortality fraction","INDEX":24,"UNIT":"1/yr","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":17,"NAME":"whole-plant mortality paramter for vegetation period","INDEX":25,"UNIT":"1/vegper","MIN":0,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":18,"NAME":"C:N of leaves","INDEX":26,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":10,"MAX":100,"GROUP":0,"TYPE":0},{"X":19,"NAME":"C:N of leaf litter","INDEX":27,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":20,"NAME":"C:N of fine roots","INDEX":28,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":21,"NAME":"C:N of fruit","INDEX":29,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":22,"NAME":"C:N of softstem","INDEX":30,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":10,"MAX":60,"GROUP":3,"TYPE":1},{"X":23,"NAME":"C:N of live wood","INDEX":31,"UNIT":"kgC/kgN","DEPENDENCE":0,"MIN":50,"MAX":100,"GROUP":4,"TYPE":1},{"X":24,"NAME":"C:N of dead wood","INDEX":32,"UNIT":"kgC/kgN","DEPENDENCE":1,"MIN":300,"MAX":800,"GROUP":4,"TYPE":1},{"X":25,"NAME":"dry matter content of leaves","INDEX":33,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":26,"NAME":"dry matter content of leaf litter","INDEX":34,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":27,"NAME":"dry matter content of fine roots","INDEX":35,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":28,"NAME":"dry matter content of fruit","INDEX":36,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":29,"NAME":"dry matter content of softstem","INDEX":37,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":30,"NAME":"dry matter content of live wood","INDEX":38,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":31,"NAME":"dry matter content of dead wood","INDEX":39,"UNIT":"kgC/kgDM","MIN":0.2,"MAX":0.6,"GROUP":0,"TYPE":0},{"X":32,"NAME":"leaf litter labile proportion","INDEX":40,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":33,"NAME":"leaf litter cellulose proportion","INDEX":41,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":5,"TYPE":2},{"X":34,"NAME":"fine root labile proportion","INDEX":42,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":35,"NAME":"fine root cellulose proportion","INDEX":43,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":6,"TYPE":2},{"X":36,"NAME":"fruit labile proportion","INDEX":44,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":37,"NAME":"fruit cellulose proportion","INDEX":45,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":7,"TYPE":2},{"X":38,"NAME":"softstem labile proportion","INDEX":46,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":39,"NAME":"softstem cellulose proportion","INDEX":47,"UNIT":"prop","DEPENDENCE":1,"MIN":0.1,"MAX":0.6,"GROUP":8,"TYPE":2},{"X":40,"NAME":"dead wood cellulose proportion","INDEX":48,"UNIT":"prop","MIN":0.5,"MAX":0.9,"GROUP":0,"TYPE":0},{"X":41,"NAME":"canopy water interception coefficient","INDEX":49,"UNIT":"1/LAI/d","MIN":0.01,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":42,"NAME":"canopy light extinction coefficient","INDEX":50,"UNIT":"dimless","MIN":0.2,"MAX":0.8,"GROUP":0,"TYPE":0},{"X":43,"NAME":"potential radiation use efficiency","INDEX":51,"UNIT":"g/MJ","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":44,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":52,"UNIT":"dimless","MIN":0.781,"MAX":0.781,"GROUP":0,"TYPE":0},{"X":45,"NAME":"radiation parameter1 (Jiang et al.2015)","INDEX":53,"UNIT":"dimless","MIN":-13.596,"MAX":-13.596,"GROUP":0,"TYPE":0},{"X":46,"NAME":"all-sided to projected leaf area ratio","INDEX":54,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":47,"NAME":"ratio of shaded SLA:sunlit SLA","INDEX":55,"UNIT":"dimless","MIN":2,"MAX":2,"GROUP":0,"TYPE":0},{"X":48,"NAME":"fraction of leaf N in Rubisco","INDEX":56,"UNIT":"dimless","MIN":0.01,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":49,"NAME":"fraction of leaf N in PeP","INDEX":57,"UNIT":"dimless","MIN":0.0424,"MAX":0.0424,"GROUP":0,"TYPE":0},{"X":50,"NAME":"maximum stomatal conductance ","INDEX":58,"UNIT":"m/s","MIN":0.001,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":51,"NAME":"cuticular conductance ","INDEX":59,"UNIT":"m/s","MIN":1e-05,"MAX":0.0001,"GROUP":0,"TYPE":0},{"X":52,"NAME":"boundary layer conductance","INDEX":60,"UNIT":"m/s","MIN":0.01,"MAX":0.09,"GROUP":0,"TYPE":0},{"X":53,"NAME":"maximum height of plant","INDEX":61,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":54,"NAME":"stem weight corresponding to maximum height","INDEX":62,"UNIT":"kgC","MIN":0.1,"MAX":100,"GROUP":0,"TYPE":0},{"X":55,"NAME":"plant height function shape parameter (slope)","INDEX":63,"UNIT":"dimless","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":56,"NAME":"maximum depth of rooting zone","INDEX":64,"UNIT":"m","MIN":0.1,"MAX":10,"GROUP":0,"TYPE":0},{"X":57,"NAME":"root distribution parameter","INDEX":65,"UNIT":"prop","MIN":3.67,"MAX":3.67,"GROUP":0,"TYPE":0},{"X":58,"NAME":"root weight corresponding to max root depth","INDEX":66,"UNIT":"kgC/m2","MIN":0.4,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":59,"NAME":"root depth function shape parameter (slope)","INDEX":67,"UNIT":"prop","MIN":0.5,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":60,"NAME":"root weight to rooth length conversion factor","INDEX":68,"UNIT":"m/kg","MIN":1000,"MAX":1000,"GROUP":0,"TYPE":0},{"X":61,"NAME":"growth resp per unit of C grown","INDEX":69,"UNIT":"prop","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":62,"NAME":"maintenance respiration in kgC/day per kg of tissue N ","INDEX":70,"UNIT":"kgC/kgN/d","MIN":0.1,"MAX":0.5,"GROUP":0,"TYPE":0},{"X":63,"NAME":"theoretical maximum prop. of non-structural and structural carbohydrates","INDEX":71,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":64,"NAME":"prop. of non-structural carbohydrates available for maintanance resp","INDEX":72,"UNIT":"dimless","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":65,"NAME":"symbiotic+asymbiotic fixation of N","INDEX":73,"UNIT":"kgN/m2/yr","MIN":0,"MAX":0.001,"GROUP":0,"TYPE":0},{"X":66,"NAME":"time delay for temperature in photosynthesis acclimation","INDEX":74,"UNIT":"day","MIN":0,"MAX":50,"GROUP":0,"TYPE":0},{"X":67,"NAME":"critical VWCratio (prop. to FC-WP) in germination","INDEX":79,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":68,"NAME":"critical photoslow daylength","INDEX":81,"UNIT":"hour","MIN":14,"MAX":18,"GROUP":0,"TYPE":0},{"X":69,"NAME":"slope of relative photoslow development rate ","INDEX":82,"UNIT":"dimless","MIN":0.005,"MAX":0.005,"GROUP":0,"TYPE":0},{"X":70,"NAME":"critical vernalization temperature 1","INDEX":84,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":9,"TYPE":1},{"X":71,"NAME":"critical vernalization temperature 2","INDEX":85,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":9,"TYPE":1},{"X":72,"NAME":"critical vernalization temperature 3","INDEX":86,"UNIT":"Celsius","DEPENDENCE":2,"MIN":5,"MAX":15,"GROUP":9,"TYPE":1},{"X":73,"NAME":"critical vernalization temperature 4","INDEX":87,"UNIT":"Celsius","DEPENDENCE":3,"MIN":10,"MAX":20,"GROUP":9,"TYPE":1},{"X":74,"NAME":"slope of relative vernalization development rate ","INDEX":88,"UNIT":"dimless","MIN":0.04,"MAX":0.04,"GROUP":0,"TYPE":0},{"X":75,"NAME":"required vernalization days (in vernalization development rate)","INDEX":89,"UNIT":"dimless","MIN":30,"MAX":70,"GROUP":0,"TYPE":0},{"X":76,"NAME":"critical flowering heat stress temperature 1","INDEX":91,"UNIT":"Celsius","DEPENDENCE":0,"MIN":30,"MAX":40,"GROUP":10,"TYPE":1},{"X":77,"NAME":"critical flowering heat stress temperature 2","INDEX":92,"UNIT":"Celsius","DEPENDENCE":1,"MIN":30,"MAX":50,"GROUP":10,"TYPE":1},{"X":78,"NAME":"theoretical maximum of flowering thermal stress mortality","INDEX":93,"UNIT":"prop","MIN":0,"MAX":0.4,"GROUP":0,"TYPE":0},{"X":79,"NAME":"VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)","INDEX":96,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":80,"NAME":"VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)","INDEX":97,"UNIT":"prop","MIN":0.5,"MAX":1,"GROUP":0,"TYPE":0},{"X":81,"NAME":"minimum of soil moisture limit2 multiplicator (full anoxic stress value)","INDEX":98,"UNIT":"prop","MIN":0,"MAX":1,"GROUP":0,"TYPE":0},{"X":82,"NAME":"vapor pressure deficit: start of conductance reduction","INDEX":99,"UNIT":"Pa","MIN":500,"MAX":1500,"GROUP":0,"TYPE":0},{"X":83,"NAME":"vapor pressure deficit: complete conductance reduction","INDEX":100,"UNIT":"Pa","MIN":1500,"MAX":3500,"GROUP":0,"TYPE":0},{"X":84,"NAME":"maximum senescence mortality coefficient of aboveground plant material","INDEX":101,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":85,"NAME":"maximum senescence mortality coefficient of belowground plant material","INDEX":102,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":86,"NAME":"maximum senescence mortality coefficient of non-structured plant material","INDEX":103,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":87,"NAME":"lower limit extreme high temperature effect on senescence mortality","INDEX":104,"UNIT":"Celsius","MIN":30,"MAX":40,"GROUP":0,"TYPE":0},{"X":88,"NAME":"upper limit extreme high temperature effect on senescence mortality","INDEX":105,"UNIT":"Celsius","MIN":30,"MAX":50,"GROUP":0,"TYPE":0},{"X":89,"NAME":"turnover rate of wilted standing biomass to litter","INDEX":106,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":90,"NAME":"turnover rate of cut-down non-woody biomass to litter","INDEX":107,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":91,"NAME":"turnover rate of cut-down woody biomass to litter","INDEX":108,"UNIT":"prop","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":92,"NAME":"drought tolerance parameter (critical value of day since water stress)","INDEX":109,"UNIT":"n_day","MIN":0,"MAX":100,"GROUP":0,"TYPE":0},{"X":93,"NAME":"crit. amount of snow limiting photosyn.","INDEX":112,"UNIT":"kg/m2","MIN":0,"MAX":20,"GROUP":0,"TYPE":0},{"X":94,"NAME":"limit1 (under:full constrained) of HEATSUM index","INDEX":113,"UNIT":"Celsius","DEPENDENCE":0,"MIN":0,"MAX":50,"GROUP":11,"TYPE":1},{"X":95,"NAME":"limit2 (above:unconstrained) of HEATSUM index","INDEX":114,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":100,"GROUP":11,"TYPE":1},{"X":96,"NAME":"limit1 (under:full constrained) of TMIN index","INDEX":115,"UNIT":"Celsius","DEPENDENCE":0,"MIN":-5,"MAX":5,"GROUP":12,"TYPE":1},{"X":97,"NAME":"limit2 (above:unconstrained) of TMIN index","INDEX":116,"UNIT":"Celsius","DEPENDENCE":1,"MIN":0,"MAX":10,"GROUP":12,"TYPE":1},{"X":98,"NAME":"limit1 (above:full constrained) of VPD index","INDEX":117,"UNIT":"Pa","DEPENDENCE":0,"MIN":2000,"MAX":600,"GROUP":13,"TYPE":1},{"X":99,"NAME":"limit2 (under:unconstrained) of VPD index","INDEX":118,"UNIT":"Pa","DEPENDENCE":1,"MIN":500,"MAX":1500,"GROUP":13,"TYPE":1},{"X":100,"NAME":"limit1 (under:full constrained) of DAYLENGTH index","INDEX":119,"UNIT":"s","DEPENDENCE":0,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":101,"NAME":"limit2 (above:unconstrained) of DAYLENGTH index","INDEX":120,"UNIT":"s","DEPENDENCE":1,"MIN":0,"MAX":0,"GROUP":14,"TYPE":1},{"X":102,"NAME":"moving average (to avoid the effects of extreme events)","INDEX":121,"UNIT":"n_day","MIN":2,"MAX":20,"GROUP":0,"TYPE":0},{"X":103,"NAME":"GSI limit1 (greater that limit -> start of vegper)","INDEX":122,"UNIT":"dimless","MIN":0,"MAX":0.2,"GROUP":0,"TYPE":0},{"X":104,"NAME":"GSI limit2 (less that limit -> end of vegper)","INDEX":123,"UNIT":"dimless","MIN":0,"MAX":0.1,"GROUP":0,"TYPE":0},{"X":105,"NAME":"length of phenophase (GDD)","INDEX":127,"UNIT":"Celsius","MIN":0,"MAX":10000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -0","INDEX":128.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-0","INDEX":129.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -0","INDEX":130.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-0","INDEX":131.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -0","INDEX":132.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -0","INDEX":133.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-0","INDEX":134.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -0","INDEX":135.6,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":15,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-0","INDEX":136.6,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-0","INDEX":137.6,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-0","INDEX":138.6,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -1","INDEX":128.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-1","INDEX":129.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -1","INDEX":130.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-1","INDEX":131.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -1","INDEX":132.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -1","INDEX":133.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-1","INDEX":134.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -1","INDEX":135.61,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":16,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-1","INDEX":136.61,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-1","INDEX":137.61,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-1","INDEX":138.61,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -2","INDEX":128.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-2","INDEX":129.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -2","INDEX":130.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-2","INDEX":131.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -2","INDEX":132.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -2","INDEX":133.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-2","INDEX":134.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -2","INDEX":135.62,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":17,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-2","INDEX":136.62,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-2","INDEX":137.62,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-2","INDEX":138.62,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -3","INDEX":128.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-3","INDEX":129.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -3","INDEX":130.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-3","INDEX":131.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -3","INDEX":132.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -3","INDEX":133.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-3","INDEX":134.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -3","INDEX":135.63,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":18,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-3","INDEX":136.63,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-3","INDEX":137.63,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-3","INDEX":138.63,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -4","INDEX":128.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-4","INDEX":129.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -4","INDEX":130.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-4","INDEX":131.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -4","INDEX":132.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -4","INDEX":133.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-4","INDEX":134.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -4","INDEX":135.64,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":19,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-4","INDEX":136.64,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-4","INDEX":137.64,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-4","INDEX":138.64,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -5","INDEX":128.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-5","INDEX":129.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -5","INDEX":130.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-5","INDEX":131.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -5","INDEX":132.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -5","INDEX":133.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-5","INDEX":134.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -5","INDEX":135.65,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":20,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-5","INDEX":136.65,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-5","INDEX":137.65,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-5","INDEX":138.65,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0},{"X":106,"NAME":"leaf ALLOCATION -6","INDEX":128.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":107,"NAME":"fine root ALLOCATION-6","INDEX":129.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":108,"NAME":"fruit ALLOCATION -6","INDEX":130.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":109,"NAME":"soft stem ALLOCATION-6","INDEX":131.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":110,"NAME":"live woody stem ALLOCATION -6","INDEX":132.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":111,"NAME":"dead woody stem ALLOCATION -6","INDEX":133.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":112,"NAME":"live coarse root ALLOCATION-6","INDEX":134.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":113,"NAME":"dead coarse root ALLOCATION -6","INDEX":135.66,"UNIT":"prop","DEPENDENCE":1,"MIN":0,"MAX":1,"GROUP":21,"TYPE":-3},{"X":114,"NAME":"canopy average specific leaf area-6","INDEX":136.66,"UNIT":"m2/kg","MIN":0,"MAX":2,"GROUP":0,"TYPE":0},{"X":115,"NAME":"current growth proportion-6","INDEX":137.66,"UNIT":"prop","MIN":0,"MAX":0,"GROUP":0,"TYPE":0},{"X":116,"NAME":"maximal lifetime of plant tissue-6","INDEX":138.66,"UNIT":"Celsius","MIN":1,"MAX":20000,"GROUP":0,"TYPE":0}] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/soilConstMatrix6.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/soilConstMatrix6.json new file mode 100644 index 0000000..891f0f1 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/soilConstMatrix6.json @@ -0,0 +1,1495 @@ +[ + { + "X": 1, + "NAME": "denitrification rate per g of CO2 respiration of SOM", + "INDEX": 4, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 2, + "NAME": "nitrification coefficient 1 ", + "INDEX": 5, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 3, + "NAME": "nitrification coefficient 2", + "INDEX": 6, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 4, + "NAME": "coefficient of N2O emission of nitrification", + "INDEX": 7, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 5, + "NAME": "NH4 mobilen proportion", + "INDEX": 8, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 6, + "NAME": "NO3 mobilen proportion", + "INDEX": 9, + "UNIT": "prop", + "MIN": 0.8, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 7, + "NAME": "e-folding depth of decomposition rate's depth scalar", + "INDEX": 10, + "UNIT": "m", + "MIN": 6, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 8, + "NAME": "fraction of dissolved part of SOIL1 organic matter", + "INDEX": 11, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 9, + "NAME": "fraction of dissolved part of SOIL2 organic matter", + "INDEX": 12, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 10, + "NAME": "fraction of dissolved part of SOIL3organic matter", + "INDEX": 13, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 11, + "NAME": "fraction of dissolved part of SOIL4 organic matter", + "INDEX": 14, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 12, + "NAME": "minimum WFPS for scalar of nitrification calculation", + "INDEX": 15, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 0, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 13, + "NAME": "lower optimum WFPS for scalar of nitrification calculation", + "INDEX": 16, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 14, + "NAME": "higher optimum WFPS for scalar of nitrification calculation", + "INDEX": 17, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 2, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 15, + "NAME": "minimum value for saturated WFPS scalar of nitrification calculation", + "INDEX": 18, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 16, + "NAME": "critical value of dissolved N and C in bottom (inactive layer)", + "INDEX": 19, + "UNIT": "ppm", + "MIN": 0, + "MAX": 1000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 17, + "NAME": "respiration fractions for fluxes between compartments (l1s1)", + "INDEX": 22, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 18, + "NAME": "respiration fractions for fluxes between compartments (l2s2)", + "INDEX": 23, + "UNIT": "prop", + "MIN": 0.55, + "MAX": 0.55, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 19, + "NAME": "respiration fractions for fluxes between compartments (l4s3)", + "INDEX": 24, + "UNIT": "prop", + "MIN": 0.29, + "MAX": 0.29, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 20, + "NAME": "respiration fractions for fluxes between compartments (s1s2)", + "INDEX": 25, + "UNIT": "prop", + "MIN": 0.28, + "MAX": 0.28, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 21, + "NAME": "respiration fractions for fluxes between compartments (s2s3)", + "INDEX": 26, + "UNIT": "prop", + "MIN": 0.46, + "MAX": 0.46, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 22, + "NAME": "respiration fractions for fluxes between compartments (s3s4)", + "INDEX": 27, + "UNIT": "prop", + "MIN": 0.55, + "MAX": 0.55, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 23, + "NAME": "rate constant scalar of labile litter pool", + "INDEX": 28, + "UNIT": "1/day", + "MIN": 0.7, + "MAX": 0.7, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 24, + "NAME": "rate constant scalar of cellulose litter pool", + "INDEX": 29, + "UNIT": "1/day", + "MIN": 0.07, + "MAX": 0.07, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 25, + "NAME": "rate constant scalar of lignin litter pool", + "INDEX": 30, + "UNIT": "1/day", + "MIN": 0.014, + "MAX": 0.014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 26, + "NAME": "rate constant scalar of fast microbial recycling pool", + "INDEX": 31, + "UNIT": "1/day", + "MIN": 0.07, + "MAX": 0.07, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 27, + "NAME": "rate constant scalar of medium microbial recycling pool", + "INDEX": 32, + "UNIT": "1/day", + "MIN": 0.014, + "MAX": 0.014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 28, + "NAME": "rate constant scalar of slow microbial recycling pool", + "INDEX": 33, + "UNIT": "1/day", + "MIN": 0.0014, + "MAX": 0.0014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 29, + "NAME": "rate constant scalar of recalcitrant SOM (humus) pool", + "INDEX": 34, + "UNIT": "1/day", + "MIN": 0.0001, + "MAX": 0.0001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 30, + "NAME": "rate constant scalar of physical fragmentation of coarse woody debris", + "INDEX": 35, + "UNIT": "1/day", + "MIN": 0.001, + "MAX": 0.001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 31, + "NAME": "param1 for CH4 calculations (empirical function of BD)", + "INDEX": 38, + "UNIT": "dimless", + "MIN": 212.5, + "MAX": 212.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 32, + "NAME": "param2 for CH4 calculations (empirical function of BD)", + "INDEX": 39, + "UNIT": "dimless", + "MIN": 1.81, + "MAX": 1.81, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 33, + "NAME": "param1 for CH4 calculations (empirical function of VWC)", + "INDEX": 40, + "UNIT": "dimless", + "MIN": -1.353, + "MAX": -1.353, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 34, + "NAME": "param2 for CH4 calculations (empirical function of VWC)", + "INDEX": 41, + "UNIT": "dimless", + "MIN": 0.2, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 35, + "NAME": "param3 for CH4 calculations (empirical function of VWC)", + "INDEX": 42, + "UNIT": "dimless", + "MIN": 1.781, + "MAX": 1.781, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 36, + "NAME": "param4 for CH4 calculations (empirical function of VWC)", + "INDEX": 43, + "UNIT": "dimless", + "MIN": 6.786, + "MAX": 6.786, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 37, + "NAME": "param1 for CH4 calculations (empirical function of Tsoil)", + "INDEX": 44, + "UNIT": "dimless", + "MIN": 0.01, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 38, + "NAME": "depth of soil", + "INDEX": 47, + "UNIT": "m", + "MIN": 1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 39, + "NAME": "limit of first stage evaporation", + "INDEX": 48, + "UNIT": "prop", + "MIN": 1, + "MAX": 9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 40, + "NAME": "maximum height of pond water", + "INDEX": 49, + "UNIT": "mm", + "MIN": 0, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 41, + "NAME": "curvature of soil stress functionr", + "INDEX": 50, + "UNIT": "dimless", + "MIN": 0.1, + "MAX": 5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 42, + "NAME": "runoff curve parameter", + "INDEX": 51, + "UNIT": "dimless", + "MIN": 10, + "MAX": 90, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 43, + "NAME": "aerodynamic resistance", + "INDEX": 52, + "UNIT": "s/m", + "MIN": 60, + "MAX": 200, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-0", + "INDEX": 55.9, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 1, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-0", + "INDEX": 56.9, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 1, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-0", + "INDEX": 57.9, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-0", + "INDEX": 58.9, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-0", + "INDEX": 59.9, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-0", + "INDEX": 60.9, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-0", + "INDEX": 61.9, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-0", + "INDEX": 62.9, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-0", + "INDEX": 63.9, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-0", + "INDEX": 64.9, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-1", + "INDEX": 55.91, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 3, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-1", + "INDEX": 56.91, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 3, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-1", + "INDEX": 57.91, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-1", + "INDEX": 58.91, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-1", + "INDEX": 59.91, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-1", + "INDEX": 60.91, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-1", + "INDEX": 61.91, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-1", + "INDEX": 62.91, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-1", + "INDEX": 63.91, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-1", + "INDEX": 64.91, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-2", + "INDEX": 55.92, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-2", + "INDEX": 56.92, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-2", + "INDEX": 57.92, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-2", + "INDEX": 58.92, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-2", + "INDEX": 59.92, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-2", + "INDEX": 60.92, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-2", + "INDEX": 61.92, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-2", + "INDEX": 62.92, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-2", + "INDEX": 63.92, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-2", + "INDEX": 64.92, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-3", + "INDEX": 55.93, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-3", + "INDEX": 56.93, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-3", + "INDEX": 57.93, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-3", + "INDEX": 58.93, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-3", + "INDEX": 59.93, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-3", + "INDEX": 60.93, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-3", + "INDEX": 61.93, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-3", + "INDEX": 62.93, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-3", + "INDEX": 63.93, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-3", + "INDEX": 64.93, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-4", + "INDEX": 55.94, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 9, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-4", + "INDEX": 56.94, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 9, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-4", + "INDEX": 57.94, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-4", + "INDEX": 58.94, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-4", + "INDEX": 59.94, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-4", + "INDEX": 60.94, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-4", + "INDEX": 61.94, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-4", + "INDEX": 62.94, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-4", + "INDEX": 63.94, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-4", + "INDEX": 64.94, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-5", + "INDEX": 55.95, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 11, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-5", + "INDEX": 56.95, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 11, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-5", + "INDEX": 57.95, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-5", + "INDEX": 58.95, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-5", + "INDEX": 59.95, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-5", + "INDEX": 60.95, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-5", + "INDEX": 61.95, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-5", + "INDEX": 62.95, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-5", + "INDEX": 63.95, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-5", + "INDEX": 64.95, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-6", + "INDEX": 55.96, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 13, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-6", + "INDEX": 56.96, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 13, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-6", + "INDEX": 57.96, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-6", + "INDEX": 58.96, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-6", + "INDEX": 59.96, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-6", + "INDEX": 60.96, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-6", + "INDEX": 61.96, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-6", + "INDEX": 62.96, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-6", + "INDEX": 63.96, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-6", + "INDEX": 64.96, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-7", + "INDEX": 55.97, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 15, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-7", + "INDEX": 56.97, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 15, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-7", + "INDEX": 57.97, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-7", + "INDEX": 58.97, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-7", + "INDEX": 59.97, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-7", + "INDEX": 60.97, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-7", + "INDEX": 61.97, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-7", + "INDEX": 62.97, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-7", + "INDEX": 63.97, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-7", + "INDEX": 64.97, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-8", + "INDEX": 55.98, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 17, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-8", + "INDEX": 56.98, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 17, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-8", + "INDEX": 57.98, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-8", + "INDEX": 58.98, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-8", + "INDEX": 59.98, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-8", + "INDEX": 60.98, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-8", + "INDEX": 61.98, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-8", + "INDEX": 62.98, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-8", + "INDEX": 63.98, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-8", + "INDEX": 64.98, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-9", + "INDEX": 55.99, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 19, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-9", + "INDEX": 56.99, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 19, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-9", + "INDEX": 57.99, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-9", + "INDEX": 58.99, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-9", + "INDEX": 59.99, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-9", + "INDEX": 60.99, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-9", + "INDEX": 61.99, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-9", + "INDEX": 62.99, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-9", + "INDEX": 63.99, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-9", + "INDEX": 64.99, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + } +] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/data/varTable6.json b/RBBGCMuso.Rcheck/RBBGCMuso/data/varTable6.json new file mode 100644 index 0000000..1900b6f --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/data/varTable6.json @@ -0,0 +1,15770 @@ +[ + { + "codes": 0, + "names": "remdays_curgrowth", + "units": "n", + "descriptions": "Remaining days current growth season" + }, + { + "codes": 1, + "names": "remdays_transfer", + "units": "n", + "descriptions": "Remaining days transfer period" + }, + { + "codes": 2, + "names": "remdays_litfall", + "units": "n", + "descriptions": "Remaining days litterfall" + }, + { + "codes": 3, + "names": "predays_transfer", + "units": "n", + "descriptions": "Previous days transfer period" + }, + { + "codes": 4, + "names": "predays_litfall", + "units": "n", + "descriptions": "Previous days litterfall" + }, + { + "codes": 5, + "names": "n_growthday", + "units": "n", + "descriptions": "Number of growing days" + }, + { + "codes": 6, + "names": "n_transferday", + "units": "n", + "descriptions": "Number of transfer days" + }, + { + "codes": 7, + "names": "n_litfallday", + "units": "n", + "descriptions": "Number of litterfall days" + }, + { + "codes": 8, + "names": "yday_total", + "units": "dimless", + "descriptions": "Counter for simdays of the whole simulation" + }, + { + "codes": 9, + "names": "phpsl_dev_rate", + "units": "dimless", + "descriptions": "Photoslowing effect rel. development" + }, + { + "codes": 10, + "names": "vern_dev_rate", + "units": "dimless", + "descriptions": "Vernalization rel. development" + }, + { + "codes": 11, + "names": "vern_days", + "units": "n", + "descriptions": "Vernalization days" + }, + { + "codes": 12, + "names": "GDD_limit", + "units": "degree", + "descriptions": "Lower limit of GDD in given phen.phase" + }, + { + "codes": 13, + "names": "GDD_crit[0]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 1" + }, + { + "codes": 14, + "names": "GDD_crit[1]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 2" + }, + { + "codes": 15, + "names": "GDD_crit[2]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 3" + }, + { + "codes": 16, + "names": "GDD_crit[3]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 4" + }, + { + "codes": 17, + "names": "GDD_crit[4]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 5" + }, + { + "codes": 18, + "names": "GDD_crit[5]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 6" + }, + { + "codes": 19, + "names": "GDD_crit[6]", + "units": "degree", + "descriptions": "Critical GDD phen.phase 7" + }, + { + "codes": 20, + "names": "GDD_emergSTART", + "units": "degree", + "descriptions": "GDD at start of emergence period" + }, + { + "codes": 21, + "names": "GDD_emergEND", + "units": "degree", + "descriptions": "GDD at end of emergence period" + }, + { + "codes": 22, + "names": "onday", + "units": "dimless", + "descriptions": "Actual onday value" + }, + { + "codes": 23, + "names": "offday", + "units": "dimless", + "descriptions": "Actual offday value" + }, + { + "codes": 24, + "names": "planttype", + "units": "dimless", + "descriptions": "Plant type (maize:1,wheat:2,barley:3,...)" + }, + { + "codes": 40, + "names": "tACCLIM", + "units": "degree", + "descriptions": "Acclimation temperature" + }, + { + "codes": 41, + "names": "tnight", + "units": "degree", + "descriptions": "Nighttime temperature" + }, + { + "codes": 42, + "names": "tavg11_ra", + "units": "degree", + "descriptions": "11-day running average temperature" + }, + { + "codes": 43, + "names": "tavg10_ra", + "units": "degree", + "descriptions": "10-day running average temperature" + }, + { + "codes": 44, + "names": "tavg30_ra", + "units": "degree", + "descriptions": "30-day running average temperature" + }, + { + "codes": 45, + "names": "F_temprad", + "units": "dimless", + "descriptions": "Soil temperature factor (air temperature and radiation)" + }, + { + "codes": 46, + "names": "F_temprad_ra", + "units": "dimless", + "descriptions": "5-day running average soil temperature factor" + }, + { + "codes": 47, + "names": "tsoil_surface", + "units": "degree", + "descriptions": "Soil surface temperature" + }, + { + "codes": 48, + "names": "tsoil_surface_pre", + "units": "degree", + "descriptions": "Soil surface temperature of previous day" + }, + { + "codes": 49, + "names": "tsoil_avg", + "units": "degree", + "descriptions": "Average soil temperature" + }, + { + "codes": 50, + "names": "tsoil[0]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 1 (0 - 2 cm)" + }, + { + "codes": 51, + "names": "tsoil[1]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 2 (3 - 10 cm)" + }, + { + "codes": 52, + "names": "tsoil[2]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 3 (10 - 30 cm)" + }, + { + "codes": 53, + "names": "tsoil[3]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 4 (30 - 60 cm)" + }, + { + "codes": 54, + "names": "tsoil[4]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 5 (60 - 90 cm)" + }, + { + "codes": 55, + "names": "tsoil[5]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 6 (90 - 120 cm)" + }, + { + "codes": 56, + "names": "tsoil[6]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 7 (120 - 150 cm)" + }, + { + "codes": 57, + "names": "tsoil[7]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 8 (150 - 200 cm)" + }, + { + "codes": 58, + "names": "tsoil[8]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 9 (200 - 400 cm)" + }, + { + "codes": 59, + "names": "tsoil[9]", + "units": "degree", + "descriptions": "Daily temperature of soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 60, + "names": "swRADnet", + "units": "Wm-2", + "descriptions": "Net shortwave radiation" + }, + { + "codes": 61, + "names": "lwRADnet", + "units": "Wm-2", + "descriptions": "Net outgoing longwave radiation" + }, + { + "codes": 62, + "names": "RADnet", + "units": "Wm-2", + "descriptions": "Daylight average net radiation flux" + }, + { + "codes": 63, + "names": "RADnet_per_plaisun", + "units": "Wm-2", + "descriptions": "Daylight avg. net radiation flux sunshade proj. leaf area index" + }, + { + "codes": 64, + "names": "RADnet_per_plaishade", + "units": "Wm-2", + "descriptions": "Daylight avg. net radiation flux sunlit proj. leaf area index" + }, + { + "codes": 65, + "names": "swavgfd", + "units": "Wm-2", + "descriptions": "Daylight average shortwave flux" + }, + { + "codes": 66, + "names": "swabs", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux" + }, + { + "codes": 67, + "names": "swtrans", + "units": "Wm-2", + "descriptions": "Transmitted shortwave flux" + }, + { + "codes": 68, + "names": "swabs_per_plaisun", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux sunlit prof. leaf area index" + }, + { + "codes": 69, + "names": "swabs_per_plaishade", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux sunshade prof. leaf area index" + }, + { + "codes": 70, + "names": "ppfd_per_plaisun", + "units": "µmolm-2s-1", + "descriptions": "PPFD sunlit proj. leaf area index" + }, + { + "codes": 71, + "names": "ppfd_per_plaishade", + "units": "µmolm-2s-1", + "descriptions": "PPFD sunshade proj. leaf area index" + }, + { + "codes": 72, + "names": "parabs", + "units": "Wm-2", + "descriptions": "Canopy absorbed PAR" + }, + { + "codes": 73, + "names": "parabs_plaisun", + "units": "Wm-2", + "descriptions": "PAR absorbed by sunlit canopy fraction" + }, + { + "codes": 74, + "names": "parabs_plaishade", + "units": "Wm-2", + "descriptions": "PAR absorbed by sunshade canopy fraction" + }, + { + "codes": 75, + "names": "GDD", + "units": "degree", + "descriptions": "GDD" + }, + { + "codes": 76, + "names": "GDD_wMOD", + "units": "degree", + "descriptions": "GDD modified by vern. and photop. effect" + }, + { + "codes": 77, + "names": "GDDpre", + "units": "degree", + "descriptions": "GDD previous day" + }, + { + "codes": 78, + "names": "pa", + "units": "Pa", + "descriptions": "Atmospheric pressure" + }, + { + "codes": 80, + "names": "soilw[0]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 1 (0 - 2 cm)" + }, + { + "codes": 81, + "names": "soilw[1]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 2 (3 - 10 cm)" + }, + { + "codes": 82, + "names": "soilw[2]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 3 (10 - 30 cm)" + }, + { + "codes": 83, + "names": "soilw[3]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 4 (30 - 60 cm)" + }, + { + "codes": 84, + "names": "soilw[4]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 5 (60 - 90 cm)" + }, + { + "codes": 85, + "names": "soilw[5]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 6 (90 - 120 cm)" + }, + { + "codes": 86, + "names": "soilw[6]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 7 (120 - 150 cm)" + }, + { + "codes": 87, + "names": "soilw[7]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 8 (150 - 200 cm)" + }, + { + "codes": 88, + "names": "soilw[8]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 9 (200 - 400 cm)" + }, + { + "codes": 89, + "names": "soilw[9]", + "units": "kgH2O m-2", + "descriptions": "SWC of soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 90, + "names": "soilw_SUM", + "units": "kgH2O m-2", + "descriptions": "SWC" + }, + { + "codes": 91, + "names": "pond_water", + "units": "kgH2O m-2", + "descriptions": "Pond water" + }, + { + "codes": 92, + "names": "snoww", + "units": "kgH2O m-2", + "descriptions": "Snow water" + }, + { + "codes": 93, + "names": "canopyw", + "units": "kgH2O m-2", + "descriptions": "Canopy water" + }, + { + "codes": 94, + "names": "prcp_src", + "units": "kgH2O m-2", + "descriptions": "Precipitation" + }, + { + "codes": 95, + "names": "soilevap_snk", + "units": "kgH2O m-2", + "descriptions": "Soil water evaporation" + }, + { + "codes": 96, + "names": "snowsubl_snk", + "units": "kgH2O m-2", + "descriptions": "Snow sublimation" + }, + { + "codes": 97, + "names": "canopyevap_snk", + "units": "kgH2O m-2", + "descriptions": "Canopy evaporation" + }, + { + "codes": 98, + "names": "pondwevap_snk", + "units": "kgH2O m-2", + "descriptions": "Pond water evaporation" + }, + { + "codes": 99, + "names": "trans_snk", + "units": "kgH2O m-2", + "descriptions": "Transpiration" + }, + { + "codes": 100, + "names": "runoff_snk", + "units": "kgH2O m-2", + "descriptions": "Runoff" + }, + { + "codes": 101, + "names": "deeppercolation_snk", + "units": "kgH2O m-2", + "descriptions": "Deep percolation" + }, + { + "codes": 102, + "names": "groundwater_src", + "units": "kgH2O m-2", + "descriptions": "Water plus from groundwater" + }, + { + "codes": 103, + "names": "canopyw_THNsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss thinning" + }, + { + "codes": 104, + "names": "canopyw_MOWsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss mowing" + }, + { + "codes": 105, + "names": "canopyw_HRVsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss harvesting" + }, + { + "codes": 106, + "names": "canopyw_PLGsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss ploughing" + }, + { + "codes": 107, + "names": "canopyw_GRZsnk", + "units": "kgH2O m-2", + "descriptions": "Canopy water loss grazing" + }, + { + "codes": 108, + "names": "IRGsrc_W", + "units": "kgH2O m-2", + "descriptions": "Water income from irrigation" + }, + { + "codes": 109, + "names": "FRZsrc_W", + "units": "kgH2O m-2", + "descriptions": "Water income from fertilizers" + }, + { + "codes": 110, + "names": "WbalanceERR", + "units": "kgH2O m-2", + "descriptions": "Water balance error" + }, + { + "codes": 111, + "names": "inW", + "units": "kgH2O m-2", + "descriptions": "SUM of water input" + }, + { + "codes": 112, + "names": "outW", + "units": "kgH2O m-2", + "descriptions": "SUM of water output" + }, + { + "codes": 113, + "names": "storeW", + "units": "kgH2O m-2", + "descriptions": "SUM of water storage" + }, + { + "codes": 114, + "names": "soil_evapCUM1", + "units": "kgH2O m-2", + "descriptions": "Cumulated soil evaporation in first evaporation phase (no limit)" + }, + { + "codes": 115, + "names": "soil_evapCUM2", + "units": "kgH2O m-2", + "descriptions": "Cumulated soil evaporation in second evaporation phase (dsr limit)" + }, + { + "codes": 116, + "names": "soilw_2 m", + "units": "kgH2O m-2", + "descriptions": "SWC in 0-2 m" + }, + { + "codes": 117, + "names": "soilw_RZ", + "units": "kgH2O m-2", + "descriptions": "SWC in rootzone" + }, + { + "codes": 118, + "names": "soilw_RZ_avail", + "units": "kgH2O m-2", + "descriptions": "SWC in rootzone available for plants" + }, + { + "codes": 119, + "names": "soilw_avail[0]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 2 (0 - 3 cm)" + }, + { + "codes": 120, + "names": "soilw_avail[1]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 2 (3 - 10 cm)" + }, + { + "codes": 121, + "names": "soilw_avail[2]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 3 (10 - 30 cm)" + }, + { + "codes": 122, + "names": "soilw_avail[3]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 4 (30 - 60 cm)" + }, + { + "codes": 123, + "names": "soilw_avail[4]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 5 (60 - 90 cm)" + }, + { + "codes": 124, + "names": "soilw_avail[5]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 6 (90 - 120 cm)" + }, + { + "codes": 125, + "names": "soilw_avail[6]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 7 (120 - 150 cm)" + }, + { + "codes": 126, + "names": "soilw_avail[7]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 8 (150 - 200 cm)" + }, + { + "codes": 127, + "names": "soilw_avail[8]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 9 (200 - 400 cm)" + }, + { + "codes": 128, + "names": "soilw_avail[9]", + "units": "kgH2O m-2", + "descriptions": "Available soil water 10 (400 - 1000 cm)" + }, + { + "codes": 150, + "names": "prcp_to_canopyw", + "units": "kgH2O m-2 day-1", + "descriptions": "Interception on canopy" + }, + { + "codes": 151, + "names": "prcp_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Precipitation entering soilwater pool" + }, + { + "codes": 152, + "names": "prcp_to_snoww", + "units": "kgH2O m-2 day-1", + "descriptions": "Snowpack accumulation" + }, + { + "codes": 153, + "names": "prcp_to_runoff", + "units": "kgH2O m-2 day-1", + "descriptions": "Runoff flux" + }, + { + "codes": 154, + "names": "canopyw_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Evaporation from canopy" + }, + { + "codes": 155, + "names": "canopyw_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy drip and stemflow" + }, + { + "codes": 156, + "names": "pondw_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Pond water evaporation" + }, + { + "codes": 157, + "names": "snoww_subl", + "units": "kgH2O m-2 day-1", + "descriptions": "Sublimation from snowpack" + }, + { + "codes": 158, + "names": "snoww_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Melt from snowpack" + }, + { + "codes": 159, + "names": "soilw_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Evaporation from soil" + }, + { + "codes": 160, + "names": "soilw_trans[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 1 (0 - 2 cm)" + }, + { + "codes": 161, + "names": "soilw_trans[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 2 (3 - 10 cm)" + }, + { + "codes": 162, + "names": "soilw_trans[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 3 (10 - 30 cm)" + }, + { + "codes": 163, + "names": "soilw_trans[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 4 (30 - 60 cm)" + }, + { + "codes": 164, + "names": "soilw_trans[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 5 (60 - 90 cm)" + }, + { + "codes": 165, + "names": "soilw_trans[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 6 (90 - 120 cm)" + }, + { + "codes": 166, + "names": "soilw_trans[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 7 (120 - 150 cm)" + }, + { + "codes": 167, + "names": "soilw_trans[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 8 (150 - 200 cm)" + }, + { + "codes": 168, + "names": "soilw_trans[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 9 (200 - 400 cm)" + }, + { + "codes": 169, + "names": "soilw_trans[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration from soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 170, + "names": "soilw_trans_SUM", + "units": "kgH2O m-2 day-1", + "descriptions": "SUM of transpiration from the soil layers" + }, + { + "codes": 171, + "names": "evapotransp", + "units": "kgH2O m-2 day-1", + "descriptions": "Evapotranspiration (evap+transp+subl)" + }, + { + "codes": 172, + "names": "pondw_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Water flux from pond to soil" + }, + { + "codes": 173, + "names": "soilw_to_pondw", + "units": "kgH2O m-2 day-1", + "descriptions": "Water flux from soil to pond" + }, + { + "codes": 174, + "names": "soilw_percolated[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 1 (0-3 cm)" + }, + { + "codes": 175, + "names": "soilw_percolated[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 2 (3-10 cm)" + }, + { + "codes": 176, + "names": "soilw_percolated[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 3 (10-30 cm)" + }, + { + "codes": 177, + "names": "soilw_percolated[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 4 (30-60 cm)" + }, + { + "codes": 178, + "names": "soilw_percolated[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 5 (60-90 cm)" + }, + { + "codes": 179, + "names": "soilw_percolated[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 6 (90-120 cm)" + }, + { + "codes": 180, + "names": "soilw_percolated[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 7 (120-150 cm)" + }, + { + "codes": 181, + "names": "soilw_percolated[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 8 (150-200 cm)" + }, + { + "codes": 182, + "names": "soilw_percolated[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 9 (200-400 cm)" + }, + { + "codes": 183, + "names": "soilw_percolated[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water percolation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 184, + "names": "soilw_diffused[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 1 (0-3 cm)" + }, + { + "codes": 185, + "names": "soilw_diffused[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 2 (3-10 cm)" + }, + { + "codes": 186, + "names": "soilw_diffused[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 3 (10-30 cm)" + }, + { + "codes": 187, + "names": "soilw_diffused[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 4 (30-60 cm)" + }, + { + "codes": 188, + "names": "soilw_diffused[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 5 (60-90 cm)" + }, + { + "codes": 189, + "names": "soilw_diffused[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 6 (90-120 cm)" + }, + { + "codes": 190, + "names": "soilw_diffused[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 7 (120-150 cm)" + }, + { + "codes": 191, + "names": "soilw_diffused[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 8 (150-200 cm)" + }, + { + "codes": 192, + "names": "soilw_diffused[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 9 (200-400 cm)" + }, + { + "codes": 193, + "names": "soilw_diffused[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water diffusion in soil layer 10 (400-1000 cm)" + }, + { + "codes": 194, + "names": "soilw_from_GW[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 1 (0-3 cm)" + }, + { + "codes": 195, + "names": "soilw_from_GW[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 2 (3-10 cm)" + }, + { + "codes": 196, + "names": "soilw_from_GW[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 3 (10-30 cm)" + }, + { + "codes": 197, + "names": "soilw_from_GW[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 4 (30-60 cm)" + }, + { + "codes": 198, + "names": "soilw_from_GW[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 5 (60-90 cm)" + }, + { + "codes": 199, + "names": "soilw_from_GW[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 6 (90-120 cm)" + }, + { + "codes": 200, + "names": "soilw_from_GW[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 7 (120-150 cm)" + }, + { + "codes": 201, + "names": "soilw_from_GW[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 8 (150-200 cm)" + }, + { + "codes": 202, + "names": "soilw_from_GW[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 9 (200-400 cm)" + }, + { + "codes": 203, + "names": "soilw_from_GW[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water from groundwater in soil layer 10 (400-1000 cm)" + }, + { + "codes": 204, + "names": "soilw_leached_RZ", + "units": "kgH2O m-2 day-1", + "descriptions": "Soil water leached from rootzone (perc+diff)" + }, + { + "codes": 205, + "names": "canopyw_to_THN", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss thinning" + }, + { + "codes": 206, + "names": "canopyw_to_MOW", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss mowing" + }, + { + "codes": 207, + "names": "canopyw_to_HRV", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss harvesting" + }, + { + "codes": 208, + "names": "canopyw_to_PLG", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss ploughing" + }, + { + "codes": 209, + "names": "canopyw_to_GRZ", + "units": "kgH2O m-2 day-1", + "descriptions": "Canopy water loss grazing" + }, + { + "codes": 210, + "names": "IRG_to_prcp", + "units": "kgH2O m-2 day-1", + "descriptions": "Irrigated water amount" + }, + { + "codes": 211, + "names": "FRZ_to_soilw", + "units": "kgH2O m-2 day-1", + "descriptions": "Water flux from fertilization" + }, + { + "codes": 212, + "names": "pot_evap", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential evaporation" + }, + { + "codes": 213, + "names": "pot_infilt", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential infiltration" + }, + { + "codes": 214, + "names": "soilw_transDEMAND[0]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 1 (0 - 2 cm)" + }, + { + "codes": 215, + "names": "soilw_transDEMAND[1]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 2 (3 - 10 cm)" + }, + { + "codes": 216, + "names": "soilw_transDEMAND[2]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 3 (10 - 30 cm)" + }, + { + "codes": 217, + "names": "soilw_transDEMAND[3]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 4 (30 - 60 cm)" + }, + { + "codes": 218, + "names": "soilw_transDEMAND[4]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 5 (60 - 90 cm)" + }, + { + "codes": 219, + "names": "soilw_transDEMAND[5]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 6 (90 - 120 cm)" + }, + { + "codes": 220, + "names": "soilw_transDEMAND[6]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 7 (120 - 150 cm)" + }, + { + "codes": 221, + "names": "soilw_transDEMAND[7]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 8 (150 - 200 cm)" + }, + { + "codes": 222, + "names": "soilw_transDEMAND[8]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 9 (200 - 400 cm)" + }, + { + "codes": 223, + "names": "soilw_transDEMAND[9]", + "units": "kgH2O m-2 day-1", + "descriptions": "Transpiration demand from soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 224, + "names": "soilw_transDEMAND_SUM", + "units": "kgH2O m-2 day-1", + "descriptions": "Sum of transpiration demand" + }, + { + "codes": 225, + "names": "soilw_transPOT", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential transpiration (no SWC limit)" + }, + { + "codes": 226, + "names": "PET", + "units": "kgH2O m-2 day-1", + "descriptions": "Potential evapotranspiration" + }, + { + "codes": 300, + "names": "leafcSUM_phenphase[0]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 1" + }, + { + "codes": 301, + "names": "leafcSUM_phenphase[1]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 2" + }, + { + "codes": 302, + "names": "leafcSUM_phenphase[2]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 3" + }, + { + "codes": 303, + "names": "leafcSUM_phenphase[3]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 4" + }, + { + "codes": 304, + "names": "leafcSUM_phenphase[4]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 5" + }, + { + "codes": 305, + "names": "leafcSUM_phenphase[5]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 6" + }, + { + "codes": 306, + "names": "leafcSUM_phenphase[6]", + "units": "kgC m-2", + "descriptions": "SUM of leaf carbon content in phen.phase 7" + }, + { + "codes": 307, + "names": "leafc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of leaf pool" + }, + { + "codes": 308, + "names": "leafc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of leaf storage pool" + }, + { + "codes": 309, + "names": "leafc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of leaf transfer pool" + }, + { + "codes": 310, + "names": "frootc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of fine root pool" + }, + { + "codes": 311, + "names": "frootc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of fine root storage pool" + }, + { + "codes": 312, + "names": "frootc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of fine root storage pool" + }, + { + "codes": 313, + "names": "fruitc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of fruit pool" + }, + { + "codes": 314, + "names": "fruitc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of fruit storage pool" + }, + { + "codes": 315, + "names": "fruitc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of fruit transfer pool" + }, + { + "codes": 316, + "names": "softstemc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of softstem pool" + }, + { + "codes": 317, + "names": "softstemc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of softstem storage pool" + }, + { + "codes": 318, + "names": "softstemc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of softstem transfer pool" + }, + { + "codes": 319, + "names": "livestemc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of live stem pool" + }, + { + "codes": 320, + "names": "livestemc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of live stem storage pool" + }, + { + "codes": 321, + "names": "livestemc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of live stem transfer pool" + }, + { + "codes": 322, + "names": "deadstemc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of dead stem pool" + }, + { + "codes": 323, + "names": "deadstemc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of dead stem storage pool" + }, + { + "codes": 324, + "names": "deadstemc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of dead stem transfer pool" + }, + { + "codes": 325, + "names": "livecrootc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of live coarse root pool" + }, + { + "codes": 326, + "names": "livecrootc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of live coarse root storge pool" + }, + { + "codes": 327, + "names": "livecrootc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of live coarse root transfer pool" + }, + { + "codes": 328, + "names": "deadcrootc", + "units": "kgC m-2", + "descriptions": "Actual carbon content of dead coarse root pool" + }, + { + "codes": 329, + "names": "deadcrootc_storage", + "units": "kgC m-2", + "descriptions": "Carbon content of dead coarse root storage pool" + }, + { + "codes": 330, + "names": "deadcrootc_transfer", + "units": "kgC m-2", + "descriptions": "Carbon content of dead coarse root transfer pool" + }, + { + "codes": 331, + "names": "gresp_storage", + "units": "kgC m-2", + "descriptions": "Growth respiration storage pool" + }, + { + "codes": 332, + "names": "gresp_transfer", + "units": "kgC m-2", + "descriptions": "Growth respiration transfer pool" + }, + { + "codes": 333, + "names": "nsc_w", + "units": "kgC m-2", + "descriptions": "Non-structured woody carbohydrate pool" + }, + { + "codes": 334, + "names": "nsc_nw", + "units": "kgC m-2", + "descriptions": "Non-structured non-woody carbohydrate pool" + }, + { + "codes": 335, + "names": "sc_w", + "units": "kgC m-2", + "descriptions": "Structured woody carbohydrate pool" + }, + { + "codes": 336, + "names": "sc_nw", + "units": "kgC m-2", + "descriptions": "Structured non-woody carbohydrate pool" + }, + { + "codes": 337, + "names": "cwdc[0]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 1 (0-3 cm)" + }, + { + "codes": 338, + "names": "cwdc[1]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 2 (3-10 cm)" + }, + { + "codes": 339, + "names": "cwdc[2]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 3 (10-30 cm)" + }, + { + "codes": 340, + "names": "cwdc[3]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 4 (30-60 cm)" + }, + { + "codes": 341, + "names": "cwdc[4]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 5 (60-90 cm)" + }, + { + "codes": 342, + "names": "cwdc[5]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 6 (90-120 cm)" + }, + { + "codes": 343, + "names": "cwdc[6]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 7 (120-150 cm)" + }, + { + "codes": 344, + "names": "cwdc[7]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 8 (150-200 cm)" + }, + { + "codes": 345, + "names": "cwdc[8]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 9 (200-400 cm)" + }, + { + "codes": 346, + "names": "cwdc[9]", + "units": "kgC m-2", + "descriptions": "Coarse woody debris in soil layer 10 (400-1000 cm)" + }, + { + "codes": 347, + "names": "litr1c[0]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 348, + "names": "litr1c[1]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 349, + "names": "litr1c[2]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 350, + "names": "litr1c[3]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 351, + "names": "litr1c[4]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 352, + "names": "litr1c[5]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 353, + "names": "litr1c[6]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 354, + "names": "litr1c[7]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 355, + "names": "litr1c[8]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 356, + "names": "litr1c[9]", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 357, + "names": "litr2c[0]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 358, + "names": "litr2c[1]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 359, + "names": "litr2c[2]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 360, + "names": "litr2c[3]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 361, + "names": "litr2c[4]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 362, + "names": "litr2c[5]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 363, + "names": "litr2c[6]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 364, + "names": "litr2c[7]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 365, + "names": "litr2c[8]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 366, + "names": "litr2c[9]", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 367, + "names": "litr3c[0]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 368, + "names": "litr3c[1]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 369, + "names": "litr3c[2]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 370, + "names": "litr3c[3]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 371, + "names": "litr3c[4]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 372, + "names": "litr3c[5]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 373, + "names": "litr3c[6]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 374, + "names": "litr3c[7]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 375, + "names": "litr3c[8]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 376, + "names": "litr3c[9]", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 377, + "names": "litr4c[0]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 378, + "names": "litr4c[1]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 379, + "names": "litr4c[2]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 380, + "names": "litr4c[3]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 381, + "names": "litr4c[4]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 382, + "names": "litr4c[5]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 383, + "names": "litr4c[6]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 384, + "names": "litr4c[7]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 385, + "names": "litr4c[8]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 386, + "names": "litr4c[9]", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 387, + "names": "litrC[0]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 1 (0-3 cm)" + }, + { + "codes": 388, + "names": "litrC[1]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 2 (3-10 cm)" + }, + { + "codes": 389, + "names": "litrC[2]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 3 (10-30 cm)" + }, + { + "codes": 390, + "names": "litrC[3]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 4 (30-60 cm)" + }, + { + "codes": 391, + "names": "litrC[4]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 5 (60-90 cm)" + }, + { + "codes": 392, + "names": "litrC[5]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 6 (90-120 cm)" + }, + { + "codes": 393, + "names": "litrC[6]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 7 (120-150 cm)" + }, + { + "codes": 394, + "names": "litrC[7]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 8 (150-200 cm)" + }, + { + "codes": 395, + "names": "litrC[8]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 9 (200-400 cm)" + }, + { + "codes": 396, + "names": "litrC[9]", + "units": "kgC m-2", + "descriptions": "Total litter content in soil layer 10 (400-1000 cm)" + }, + { + "codes": 397, + "names": "litr1c_total", + "units": "kgC m-2", + "descriptions": "Labile C proportion of litter" + }, + { + "codes": 398, + "names": "litr2c_total", + "units": "kgC m-2", + "descriptions": "Unshielded cellulose proportion of litter" + }, + { + "codes": 399, + "names": "litr3c_total", + "units": "kgC m-2", + "descriptions": "Shielded cellulose proportion of litter" + }, + { + "codes": 400, + "names": "litr4c_total", + "units": "kgC m-2", + "descriptions": "Lignin proportion of litter" + }, + { + "codes": 401, + "names": "cwdc_total", + "units": "kgC m-2", + "descriptions": "Total carbon content of coarse woody debris" + }, + { + "codes": 402, + "names": "STDBc_leaf", + "units": "kgC m-2", + "descriptions": "Wilted leaf biomass" + }, + { + "codes": 403, + "names": "STDBc_froot", + "units": "kgC m-2", + "descriptions": "Wilted fine root biomass" + }, + { + "codes": 404, + "names": "STDBc_fruit", + "units": "kgC m-2", + "descriptions": "Wilted fruit biomass" + }, + { + "codes": 405, + "names": "STDBc_softstem", + "units": "kgC m-2", + "descriptions": "Wilted softstem biomass" + }, + { + "codes": 406, + "names": "STDBc_nsc", + "units": "kgC m-2", + "descriptions": "Wilted non-stuctured carbohydrate biomass" + }, + { + "codes": 407, + "names": "STDBc_above", + "units": "kgC m-2", + "descriptions": "Wilted aboveground plant biomass" + }, + { + "codes": 408, + "names": "STDBc_below", + "units": "kgC m-2", + "descriptions": "Wilted belowground plant biomass" + }, + { + "codes": 409, + "names": "CTDBc_leaf", + "units": "kgC m-2", + "descriptions": "Cut-down leaf biomass" + }, + { + "codes": 410, + "names": "CTDBc_froot", + "units": "kgC m-2", + "descriptions": "Cut-down fineroot biomass" + }, + { + "codes": 411, + "names": "CTDBc_fruit", + "units": "kgC m-2", + "descriptions": "Cut-down fruit biomass" + }, + { + "codes": 412, + "names": "CTDBc_softstem", + "units": "kgC m-2", + "descriptions": "Cut-down softstem biomass" + }, + { + "codes": 413, + "names": "CTDBc_nsc", + "units": "kgC m-2", + "descriptions": "Cut-down non-structured biomass" + }, + { + "codes": 414, + "names": "CTDBc_cstem", + "units": "kgC m-2", + "descriptions": "Cut-down coarse stem biomass" + }, + { + "codes": 415, + "names": "CTDBc_croot", + "units": "kgC m-2", + "descriptions": "Cut-down coarse root biomass" + }, + { + "codes": 416, + "names": "CTDBc_above", + "units": "kgC m-2", + "descriptions": "Cut-down aboveground plant biomass" + }, + { + "codes": 417, + "names": "CTDBc_below", + "units": "kgC m-2", + "descriptions": "Cut-down belowground plant biomass" + }, + { + "codes": 418, + "names": "soil1c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 419, + "names": "soil1c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 420, + "names": "soil1c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 421, + "names": "soil1c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 422, + "names": "soil1c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 423, + "names": "soil1c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 424, + "names": "soil1c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 425, + "names": "soil1c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 426, + "names": "soil1c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 427, + "names": "soil1c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 428, + "names": "soil2c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 429, + "names": "soil2c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 430, + "names": "soil2c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 431, + "names": "soil2c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 432, + "names": "soil2c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 433, + "names": "soil2c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 434, + "names": "soil2c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 435, + "names": "soil2c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 436, + "names": "soil2c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 437, + "names": "soil2c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 438, + "names": "soil3c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 439, + "names": "soil3c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 440, + "names": "soil3c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 441, + "names": "soil3c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 442, + "names": "soil3c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 443, + "names": "soil3c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 444, + "names": "soil3c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 445, + "names": "soil3c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 446, + "names": "soil3c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 447, + "names": "soil3c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 448, + "names": "soil4c[0]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 449, + "names": "soil4c[1]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 450, + "names": "soil4c[2]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 451, + "names": "soil4c[3]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 452, + "names": "soil4c[4]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 453, + "names": "soil4c[5]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 454, + "names": "soil4c[6]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 455, + "names": "soil4c[7]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 456, + "names": "soil4c[8]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 457, + "names": "soil4c[9]", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM pool in soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 458, + "names": "soilC[0]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 1 (0-3 cm)" + }, + { + "codes": 459, + "names": "soilC[1]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 2 (3-10 cm)" + }, + { + "codes": 460, + "names": "soilC[2]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 3 (10-30 cm)" + }, + { + "codes": 461, + "names": "soilC[3]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 4 (30-60 cm)" + }, + { + "codes": 462, + "names": "soilC[4]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 5 (60-90 cm)" + }, + { + "codes": 463, + "names": "soilC[5]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 6 (90-120 cm)" + }, + { + "codes": 464, + "names": "soilC[6]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 7 (120-150 cm)" + }, + { + "codes": 465, + "names": "soilC[7]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 8 (150-200 cm)" + }, + { + "codes": 466, + "names": "soilC[8]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 9 (200-400 cm)" + }, + { + "codes": 467, + "names": "soilC[9]", + "units": "kgC m-2", + "descriptions": "Total C content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 468, + "names": "soil1_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 469, + "names": "soil1_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 470, + "names": "soil1_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 471, + "names": "soil1_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 472, + "names": "soil1_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 473, + "names": "soil1_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 474, + "names": "soil1_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 475, + "names": "soil1_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 476, + "names": "soil1_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 477, + "names": "soil1_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of labile SOM pool in soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 478, + "names": "soil2_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 479, + "names": "soil2_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 480, + "names": "soil2_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 481, + "names": "soil2_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 482, + "names": "soil2_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 483, + "names": "soil2_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 484, + "names": "soil2_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 485, + "names": "soil2_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 486, + "names": "soil2_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 487, + "names": "soil2_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of fast SOM pool in soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 488, + "names": "soil3_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 489, + "names": "soil3_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 490, + "names": "soil3_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 491, + "names": "soil3_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 492, + "names": "soil3_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 493, + "names": "soil3_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 494, + "names": "soil3_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 495, + "names": "soil3_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 496, + "names": "soil3_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 497, + "names": "soil3_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of slow SOM pool in soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 498, + "names": "soil4_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 499, + "names": "soil4_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 500, + "names": "soil4_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 501, + "names": "soil4_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 502, + "names": "soil4_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 503, + "names": "soil4_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 504, + "names": "soil4_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 505, + "names": "soil4_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 506, + "names": "soil4_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 507, + "names": "soil4_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of stable SOM pool in soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 508, + "names": "soil_DOC[0]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 509, + "names": "soil_DOC[1]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 510, + "names": "soil_DOC[2]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 511, + "names": "soil_DOC[3]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 512, + "names": "soil_DOC[4]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 513, + "names": "soil_DOC[5]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 514, + "names": "soil_DOC[6]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 515, + "names": "soil_DOC[7]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 516, + "names": "soil_DOC[8]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 517, + "names": "soil_DOC[9]", + "units": "kgC m-2", + "descriptions": "Dissolved Carbon content of total SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 518, + "names": "soil1c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (labile)" + }, + { + "codes": 519, + "names": "soil2c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (fast)" + }, + { + "codes": 520, + "names": "soil3c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (slow)" + }, + { + "codes": 521, + "names": "soil4c_total", + "units": "kgC m-2", + "descriptions": "Carbon content of SOM (stable)" + }, + { + "codes": 522, + "names": "cpool", + "units": "kgC m-2", + "descriptions": "Temporary photosynthate C pool" + }, + { + "codes": 523, + "names": "psnsun_src", + "units": "kgC m-2", + "descriptions": "Gross photosynthesis from sunlit canopy" + }, + { + "codes": 524, + "names": "psnshade_src", + "units": "kgC m-2", + "descriptions": "Gross photosynthesis from shaded canopy" + }, + { + "codes": 525, + "names": "NSC_mr_snk", + "units": "kgC m-2", + "descriptions": "Non-structured carbohydrate MR loss" + }, + { + "codes": 526, + "names": "actC_mr_snk", + "units": "kgC m-2", + "descriptions": "MR loss from actual carbon pool" + }, + { + "codes": 527, + "names": "leaf_mr_snk", + "units": "kgC m-2", + "descriptions": "Leaf maintenance respiration" + }, + { + "codes": 528, + "names": "froot_mr_snk", + "units": "kgC m-2", + "descriptions": "Fine root maintenance respiration" + }, + { + "codes": 529, + "names": "fruit_mr_snk", + "units": "kgC m-2", + "descriptions": "Fruit maintenance respiration" + }, + { + "codes": 530, + "names": "softstem_mr_snk", + "units": "kgC m-2", + "descriptions": "Softstem maintenance respiration" + }, + { + "codes": 531, + "names": "livestem_mr_snk", + "units": "kgC m-2", + "descriptions": "Live stem maintenance respiration" + }, + { + "codes": 532, + "names": "livecroot_mr_snk", + "units": "kgC m-2", + "descriptions": "Live coarse root maintenance respiration" + }, + { + "codes": 533, + "names": "leaf_gr_snk", + "units": "kgC m-2", + "descriptions": "Leaf growth respiration" + }, + { + "codes": 534, + "names": "froot_gr_snk", + "units": "kgC m-2", + "descriptions": "Fine root growth respiration" + }, + { + "codes": 535, + "names": "fruit_gr_snk", + "units": "kgC m-2", + "descriptions": "Fruit growth respiration" + }, + { + "codes": 536, + "names": "softstem_gr_snk", + "units": "kgC m-2", + "descriptions": "Softstem growth respiration" + }, + { + "codes": 537, + "names": "livestem_gr_snk", + "units": "kgC m-2", + "descriptions": "Live stem growth respiration" + }, + { + "codes": 538, + "names": "livecroot_gr_snk", + "units": "kgC m-2", + "descriptions": "Live coarse root growth respiration" + }, + { + "codes": 539, + "names": "deadstem_gr_snk", + "units": "kgC m-2", + "descriptions": "Dead stem growth respiration" + }, + { + "codes": 540, + "names": "deadcroot_gr_snk", + "units": "kgC m-2", + "descriptions": "Dead coarse root growth respiration" + }, + { + "codes": 541, + "names": "litr1_hr_snk", + "units": "kgC m-2", + "descriptions": "Labile litter microbial respiration" + }, + { + "codes": 542, + "names": "litr2_hr_snk", + "units": "kgC m-2", + "descriptions": "Cellulose litter microbial respiration" + }, + { + "codes": 543, + "names": "litr4_hr_snk", + "units": "kgC m-2", + "descriptions": "Lignin litter microbial respiration" + }, + { + "codes": 544, + "names": "soil1_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of labile SOM" + }, + { + "codes": 545, + "names": "soil2_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of fast SOM" + }, + { + "codes": 546, + "names": "soil3_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of slow SOM" + }, + { + "codes": 547, + "names": "soil4_hr_snk", + "units": "kgC m-2", + "descriptions": "Respiration of stable SOM" + }, + { + "codes": 548, + "names": "FIREsnk_C", + "units": "kgC m-2", + "descriptions": "Fire C losses" + }, + { + "codes": 549, + "names": "SNSCsnk_C", + "units": "kgC m-2", + "descriptions": "Senescence C losses" + }, + { + "codes": 550, + "names": "PLTsrc_C", + "units": "kgC m-2", + "descriptions": "C content of planted plant material" + }, + { + "codes": 551, + "names": "THN_transportC", + "units": "kgC m-2", + "descriptions": "C content of thinned and transported plant material" + }, + { + "codes": 552, + "names": "HRV_transportC", + "units": "kgC m-2", + "descriptions": "C content of harvested and transported plant material" + }, + { + "codes": 553, + "names": "MOW_transportC", + "units": "kgC m-2", + "descriptions": "C content of mowed and transported plant material" + }, + { + "codes": 554, + "names": "GRZsnk_C", + "units": "kgC m-2", + "descriptions": "C content of grazed leaf" + }, + { + "codes": 555, + "names": "GRZsrc_C", + "units": "kgC m-2", + "descriptions": "Added C from fertilizer" + }, + { + "codes": 556, + "names": "FRZsrc_C", + "units": "kgC m-2", + "descriptions": "C content of fertilizer return to the litter pool" + }, + { + "codes": 557, + "names": "fruitC_HRV", + "units": "kgC m-2", + "descriptions": "C content of havested fruit in a year" + }, + { + "codes": 558, + "names": "vegC_HRV", + "units": "kgC m-2", + "descriptions": "C content of havested plant (leaf+stem+fruit) in a year" + }, + { + "codes": 559, + "names": "CbalanceERR", + "units": "kgC m-2", + "descriptions": "Carbon balance error" + }, + { + "codes": 560, + "names": "inC", + "units": "kgC m-2", + "descriptions": "Carbon input" + }, + { + "codes": 561, + "names": "outC", + "units": "kgC m-2", + "descriptions": "Carbon output" + }, + { + "codes": 562, + "names": "storeC", + "units": "kgC m-2", + "descriptions": "Carbon store" + }, + { + "codes": 563, + "names": "Cdeepleach_snk", + "units": "kgC m-2", + "descriptions": "SUM of C deep leaching" + }, + { + "codes": 564, + "names": "cwdc_above", + "units": "kgC m-2", + "descriptions": "Aboveground cwdc" + }, + { + "codes": 565, + "names": "litrc_above", + "units": "kgC m-2", + "descriptions": "Aboveground litrc" + }, + { + "codes": 566, + "names": "CNratioERR", + "units": "kgC m-2", + "descriptions": "CN ratio error" + }, + { + "codes": 567, + "names": "flowHSsnk_C", + "units": "kgC m-2", + "descriptions": "C loss due to flower heat stress" + }, + { + "codes": 600, + "names": "m_leafc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to labile C portion of litter" + }, + { + "codes": 601, + "names": "m_leafc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to unshielded cellulose portion of litter" + }, + { + "codes": 602, + "names": "m_leafc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to shielded cellulose portion of litter" + }, + { + "codes": 603, + "names": "m_leafc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf to lignin portion of litter" + }, + { + "codes": 604, + "names": "m_frootc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to labile litter" + }, + { + "codes": 605, + "names": "m_frootc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 606, + "names": "m_frootc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 607, + "names": "m_frootc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root to lignin portion of litter" + }, + { + "codes": 608, + "names": "m_fruitc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to labile litter" + }, + { + "codes": 609, + "names": "m_fruitc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to unshielded cellulose portion of litter" + }, + { + "codes": 610, + "names": "m_fruitc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to shielded cellulose portion of litter" + }, + { + "codes": 611, + "names": "m_fruitc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit to lignin portion of litter" + }, + { + "codes": 612, + "names": "m_softstemc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to labile litter" + }, + { + "codes": 613, + "names": "m_softstemc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 614, + "names": "m_softstemc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 615, + "names": "m_softstemc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem to lignin portion of litter" + }, + { + "codes": 616, + "names": "m_leafc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf storage pool to labile litter" + }, + { + "codes": 617, + "names": "m_frootc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root storage pool to labile litter" + }, + { + "codes": 618, + "names": "m_softstemc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem storage pool to labile litter" + }, + { + "codes": 619, + "names": "m_fruitc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit storage pool to labile litter" + }, + { + "codes": 620, + "names": "m_livestemc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live stem storage pool to labile litter" + }, + { + "codes": 621, + "names": "m_deadstemc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead stem storage pool to labile litter" + }, + { + "codes": 622, + "names": "m_livecrootc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live coarse root storage pool to labile litter" + }, + { + "codes": 623, + "names": "m_deadcrootc_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead coarse root storage pool to labile litter" + }, + { + "codes": 624, + "names": "m_leafc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from leaf transfer pool to labile litter" + }, + { + "codes": 625, + "names": "m_frootc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fine root transfer pool to labile litter" + }, + { + "codes": 626, + "names": "m_fruitc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from fruit transfer pool to labile litter" + }, + { + "codes": 627, + "names": "m_softstemc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from softstem transfer pool to labile litter" + }, + { + "codes": 628, + "names": "m_livestemc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live stem transfer pool to labile litter" + }, + { + "codes": 629, + "names": "m_deadstemc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead stem transfer pool to labile litter" + }, + { + "codes": 630, + "names": "m_livecrootc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live coarse root transfer pool to labile litter" + }, + { + "codes": 631, + "names": "m_deadcrootc_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead coarse root transfer pool to labile litter" + }, + { + "codes": 632, + "names": "m_livestemc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Moartality C flux from live stem to coarse woody debris" + }, + { + "codes": 633, + "names": "m_deadstemc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from dead stem to coarse woody debris" + }, + { + "codes": 634, + "names": "m_livecrootc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from live coarse root to coarse woody debris" + }, + { + "codes": 635, + "names": "m_deadcrootc_to_cwdc", + "units": "kgC m-2 day-1", + "descriptions": "Moartality C flux from dead coarse root to coarse woody debris" + }, + { + "codes": 636, + "names": "m_gresp_storage_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from growth respiration storage pool to labile litter" + }, + { + "codes": 637, + "names": "m_gresp_transfer_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Mortality C flux from growth respiration transfer pool to labile litter" + }, + { + "codes": 638, + "names": "m_leafc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Leaf fire C flux" + }, + { + "codes": 639, + "names": "m_frootc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fine root fire C flux" + }, + { + "codes": 640, + "names": "m_fruitc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fruit fire C flux" + }, + { + "codes": 641, + "names": "m_softstemc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Softstem fire C flux" + }, + { + "codes": 642, + "names": "m_STDBc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Wilted plant biomass fire C flux" + }, + { + "codes": 643, + "names": "m_CTDBc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down plant biomass fire C flux" + }, + { + "codes": 644, + "names": "m_leafc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Leaf storage pool fire C flux" + }, + { + "codes": 645, + "names": "m_frootc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fine root storage pool fire C flux" + }, + { + "codes": 646, + "names": "m_fruitc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fruit storage pool fire C flux" + }, + { + "codes": 647, + "names": "m_softstemc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Softstem storage pool fire C flux" + }, + { + "codes": 648, + "names": "m_livestemc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live stem storage pool fire C flux" + }, + { + "codes": 649, + "names": "m_deadstemc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead stem storage pool fire C flux" + }, + { + "codes": 650, + "names": "m_livecrootc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root storage pool fire C flux" + }, + { + "codes": 651, + "names": "m_deadcrootc_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead coarse root storage pool fire C flux" + }, + { + "codes": 652, + "names": "m_leafc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Leaf transfer pool fire C flux" + }, + { + "codes": 653, + "names": "m_frootc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fine root transfer pool fire C flux" + }, + { + "codes": 654, + "names": "m_fruitc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fruit transfer pool fire C flux" + }, + { + "codes": 655, + "names": "m_softstemc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Softstem transfer pool fire C flux" + }, + { + "codes": 656, + "names": "m_livestemc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live stem transfer pool fire C flux" + }, + { + "codes": 657, + "names": "m_deadstemc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead stem transfer pool fire C flux" + }, + { + "codes": 658, + "names": "m_livecrootc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root transfer pool fire C flux" + }, + { + "codes": 659, + "names": "m_deadcrootc_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead coarse root transfer pool fire C flux" + }, + { + "codes": 660, + "names": "m_livestemc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live stem fire C flux" + }, + { + "codes": 661, + "names": "m_deadstemc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead stem fire C flux" + }, + { + "codes": 662, + "names": "m_livecrootc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root fire C flux" + }, + { + "codes": 663, + "names": "m_deadcrootc_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Dead coarse root fire C flux" + }, + { + "codes": 664, + "names": "m_gresp_storage_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration storage pool fire C flux" + }, + { + "codes": 665, + "names": "m_gresp_transfer_to_fire", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration transfer pool fire C flux" + }, + { + "codes": 666, + "names": "m_litr1c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "labile litter fire C flux" + }, + { + "codes": 667, + "names": "m_litr2c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Unshielded cellulose portion of litter fire C flux" + }, + { + "codes": 668, + "names": "m_litr3c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Shielded cellulose portion of litter fire C flux" + }, + { + "codes": 669, + "names": "m_litr4c_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Lignin portion of litter fire C flux" + }, + { + "codes": 670, + "names": "m_cwdc_to_fireTOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Coarse woody debris fire C flux" + }, + { + "codes": 671, + "names": "m_vegc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Total vegetation senescence C flux" + }, + { + "codes": 672, + "names": "m_leafc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Leaf senescence C flux" + }, + { + "codes": 673, + "names": "m_leafc_to_SNSCgenprog", + "units": "kgC m-2 day-1", + "descriptions": "Leaf gen. prog. scenescene C flux" + }, + { + "codes": 674, + "names": "m_frootc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fine root senescene C flux" + }, + { + "codes": 675, + "names": "m_fruitc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fruit senescence C flux" + }, + { + "codes": 676, + "names": "m_softstemc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Softstem senescence C flux" + }, + { + "codes": 677, + "names": "m_leafc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Leaf storage pool senescence C flux" + }, + { + "codes": 678, + "names": "m_frootc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fine root storage pool senescence C flux" + }, + { + "codes": 679, + "names": "m_leafc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Leaf transfer pool senescence C flux" + }, + { + "codes": 680, + "names": "m_frootc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fine root transfer pool senescence C flux" + }, + { + "codes": 681, + "names": "m_fruitc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fruit storage pool senescence C flux" + }, + { + "codes": 682, + "names": "m_fruitc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Fruit transfer pool senescence C flux" + }, + { + "codes": 683, + "names": "m_softstemc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Softstem storage pool senescence C flux" + }, + { + "codes": 684, + "names": "m_softstemc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Softstem transfer pool senescence C flux" + }, + { + "codes": 685, + "names": "m_gresp_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration storage pool senescence C flux" + }, + { + "codes": 686, + "names": "m_gresp_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration transfer pool senescence C flux" + }, + { + "codes": 687, + "names": "HRV_leafc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested leaf storage pool senescence C flux" + }, + { + "codes": 688, + "names": "HRV_leafc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested leaf transfer pool senescence C flux" + }, + { + "codes": 689, + "names": "HRV_fruitc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fruit storage pool senescence C flux" + }, + { + "codes": 690, + "names": "HRV_fruitc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fruit transfer pool senescence C flux" + }, + { + "codes": 691, + "names": "HRV_frootc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fine root senescence C flux" + }, + { + "codes": 692, + "names": "HRV_softstemc_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested softstem senscence C flux" + }, + { + "codes": 693, + "names": "HRV_frootc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fine root storage senescence C flux" + }, + { + "codes": 694, + "names": "HRV_frootc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested fine root transfer senescence C flux" + }, + { + "codes": 695, + "names": "HRV_softstemc_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested softstem storage senescence C flux" + }, + { + "codes": 696, + "names": "HRV_softstemc_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested softstem transfer senescence C flux" + }, + { + "codes": 697, + "names": "HRV_gresp_storage_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested growth respiration storage pool senescence C flux" + }, + { + "codes": 698, + "names": "HRV_gresp_transfer_to_SNSC", + "units": "kgC m-2 day-1", + "descriptions": "Harvested growth respiration transfer pool senescence C flux" + }, + { + "codes": 699, + "names": "fruitc_to_flowHS", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit flowering heat stress" + }, + { + "codes": 700, + "names": "STDBc_leaf_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Leaf standing dead biomass C flux to litter" + }, + { + "codes": 701, + "names": "STDBc_froot_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Fine root standing dead biomass C flux to litter" + }, + { + "codes": 702, + "names": "STDBc_fruit_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Fruit standing dead biomass C flux to litter" + }, + { + "codes": 703, + "names": "STDBc_softstem_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Softstem standing dead biomass C flux to litter" + }, + { + "codes": 704, + "names": "STDBc_nsc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Standing dead biomass non-structured pool C flux to litter" + }, + { + "codes": 705, + "names": "STDBc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Standing dead biomass C flux to litter" + }, + { + "codes": 706, + "names": "CTDBc_leaf_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down leaf dead biomass C flux to litter" + }, + { + "codes": 707, + "names": "CTDBc_froot_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down fine root dead biomass C flux to litter" + }, + { + "codes": 708, + "names": "CTDBc_fruit_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down fruit dead biomass C flux to litter" + }, + { + "codes": 709, + "names": "CTDBc_softstem_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down softstem dead biomass C flux to litter" + }, + { + "codes": 710, + "names": "CTDBc_nsc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down dead biomass non-structured pool C flux to litter" + }, + { + "codes": 711, + "names": "CTDBc_cstem_to_cwd", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down coarse stem dead biomass C flux to coarse woody debris" + }, + { + "codes": 712, + "names": "CTDBc_croot_to_cwd", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down coarse root dead biomass C flux to coarse woody debris" + }, + { + "codes": 713, + "names": "CTDBc_to_litr", + "units": "kgC m-2 day-1", + "descriptions": "Cut-down dead biomass C flux to litter" + }, + { + "codes": 714, + "names": "leafc_transfer_to_leafc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from leaf transfer pool to leaf" + }, + { + "codes": 715, + "names": "frootc_transfer_to_frootc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from fine root transfer pool to fine root" + }, + { + "codes": 716, + "names": "fruitc_transfer_to_fruitc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from fruit transfer pool to fruit" + }, + { + "codes": 717, + "names": "softstemc_transfer_to_softstemc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from softstem transfer pool to softstem" + }, + { + "codes": 718, + "names": "livestemc_transfer_to_livestemc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from live stem transfer pool to live stem" + }, + { + "codes": 719, + "names": "deadstemc_transfer_to_deadstemc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from dead stem transfer to dead stem" + }, + { + "codes": 720, + "names": "livecrootc_transfer_to_livecrootc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from live coarse root transfer pool to live coarse root" + }, + { + "codes": 721, + "names": "deadcrootc_transfer_to_deadcrootc", + "units": "kgC m-2 day-1", + "descriptions": "Phenology C flux from dead coarse root transfer pool to dead coarse root" + }, + { + "codes": 722, + "names": "leafc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to labile litter" + }, + { + "codes": 723, + "names": "leafc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to unshielded cellulose portion of litter" + }, + { + "codes": 724, + "names": "leafc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to shielded cellulose portion of litter" + }, + { + "codes": 725, + "names": "leafc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from leaf to lignin portion of litter" + }, + { + "codes": 726, + "names": "frootc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to labile litter" + }, + { + "codes": 727, + "names": "frootc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 728, + "names": "frootc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 729, + "names": "frootc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fine root to lignin portion of litter" + }, + { + "codes": 730, + "names": "fruitc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to labile litter" + }, + { + "codes": 731, + "names": "fruitc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to unshielded cellulose portion of litter" + }, + { + "codes": 732, + "names": "fruitc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to shielded cellulose portion of litter" + }, + { + "codes": 733, + "names": "fruitc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fruit to lignin portion of litter" + }, + { + "codes": 734, + "names": "softstemc_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to labile litter" + }, + { + "codes": 735, + "names": "softstemc_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 736, + "names": "softstemc_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 737, + "names": "softstemc_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "C flux from softstem to lignin portion of litter" + }, + { + "codes": 738, + "names": "leaf_day_mr", + "units": "kgC m-2 day-1", + "descriptions": "Leaf daylight maintenance respiration" + }, + { + "codes": 739, + "names": "leaf_night_mr", + "units": "kgC m-2 day-1", + "descriptions": "Leaf night maintenance respiration" + }, + { + "codes": 740, + "names": "froot_mr", + "units": "kgC m-2 day-1", + "descriptions": "Fine root maintenance respiration" + }, + { + "codes": 741, + "names": "fruit_mr", + "units": "kgC m-2 day-1", + "descriptions": "Fruit maintenance repsiration" + }, + { + "codes": 742, + "names": "softstem_mr", + "units": "kgC m-2 day-1", + "descriptions": "Softstem maintenance respiration" + }, + { + "codes": 743, + "names": "livestem_mr", + "units": "kgC m-2 day-1", + "descriptions": "Live stem maintenance respiration" + }, + { + "codes": 744, + "names": "livecroot_mr", + "units": "kgC m-2 day-1", + "descriptions": "Live coarse root maintenance respiration" + }, + { + "codes": 745, + "names": "psnsun_to_cpool", + "units": "kgC m-2 day-1", + "descriptions": "C flux to temporary photosynthate C pool by sunlight" + }, + { + "codes": 746, + "names": "psnshade_to_cpool", + "units": "kgC m-2 day-1", + "descriptions": "C flux to temporary photosynthate C pool by sunshade" + }, + { + "codes": 747, + "names": "cwdc_to_litr2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose part of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 748, + "names": "cwdc_to_litr2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 749, + "names": "cwdc_to_litr2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 750, + "names": "cwdc_to_litr2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 751, + "names": "cwdc_to_litr2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 752, + "names": "cwdc_to_litr2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 753, + "names": "cwdc_to_litr2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 754, + "names": "cwdc_to_litr2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 755, + "names": "cwdc_to_litr2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 756, + "names": "cwdc_to_litr2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 757, + "names": "cwdc_to_litr3c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 758, + "names": "cwdc_to_litr3c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 759, + "names": "cwdc_to_litr3c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 760, + "names": "cwdc_to_litr3c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 761, + "names": "cwdc_to_litr3c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 762, + "names": "cwdc_to_litr3c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 763, + "names": "cwdc_to_litr3c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 764, + "names": "cwdc_to_litr3c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 765, + "names": "cwdc_to_litr3c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 766, + "names": "cwdc_to_litr3c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 767, + "names": "cwdc_to_litr4c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 768, + "names": "cwdc_to_litr4c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 769, + "names": "cwdc_to_litr4c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 770, + "names": "cwdc_to_litr4c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 771, + "names": "cwdc_to_litr4c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 772, + "names": "cwdc_to_litr4c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 773, + "names": "cwdc_to_litr4c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 774, + "names": "cwdc_to_litr4c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 775, + "names": "cwdc_to_litr4c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 776, + "names": "cwdc_to_litr4c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 777, + "names": "litr1_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 778, + "names": "litr1_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 779, + "names": "litr1_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 780, + "names": "litr1_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 781, + "names": "litr1_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 782, + "names": "litr1_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 783, + "names": "litr1_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 784, + "names": "litr1_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 785, + "names": "litr1_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 786, + "names": "litr1_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 787, + "names": "litr1c_to_soil1c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 788, + "names": "litr1c_to_soil1c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 789, + "names": "litr1c_to_soil1c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 790, + "names": "litr1c_to_soil1c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 791, + "names": "litr1c_to_soil1c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 792, + "names": "litr1c_to_soil1c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 793, + "names": "litr1c_to_soil1c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 794, + "names": "litr1c_to_soil1c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 795, + "names": "litr1c_to_soil1c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 796, + "names": "litr1c_to_soil1c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 797, + "names": "litr2_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose soil layer 1 (0-3 cm)" + }, + { + "codes": 798, + "names": "litr2_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 2 (3-10 cm)" + }, + { + "codes": 799, + "names": "litr2_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 3 (10-30 cm)" + }, + { + "codes": 800, + "names": "litr2_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 4 (30-60 cm)" + }, + { + "codes": 801, + "names": "litr2_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 5 (60-90 cm)" + }, + { + "codes": 802, + "names": "litr2_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 6 (90-120 cm)" + }, + { + "codes": 803, + "names": "litr2_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 7 (120-150 cm)" + }, + { + "codes": 804, + "names": "litr2_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 8 (150-200 cm)" + }, + { + "codes": 805, + "names": "litr2_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 9 (200-400 cm)" + }, + { + "codes": 806, + "names": "litr2_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 10 (400-1000 cm)" + }, + { + "codes": 807, + "names": "litr2c_to_soil2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 808, + "names": "litr2c_to_soil2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 809, + "names": "litr2c_to_soil2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 810, + "names": "litr2c_to_soil2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 811, + "names": "litr2c_to_soil2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 812, + "names": "litr2c_to_soil2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 813, + "names": "litr2c_to_soil2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 814, + "names": "litr2c_to_soil2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 815, + "names": "litr2c_to_soil2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 816, + "names": "litr2c_to_soil2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 817, + "names": "litr3c_to_litr2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 818, + "names": "litr3c_to_litr2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 819, + "names": "litr3c_to_litr2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 820, + "names": "litr3c_to_litr2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 821, + "names": "litr3c_to_litr2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 822, + "names": "litr3c_to_litr2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 823, + "names": "litr3c_to_litr2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 824, + "names": "litr3c_to_litr2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 825, + "names": "litr3c_to_litr2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 826, + "names": "litr3c_to_litr2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 827, + "names": "litr4_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 828, + "names": "litr4_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 828, + "names": "litr4_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 830, + "names": "litr4_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 831, + "names": "litr4_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 832, + "names": "litr4_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 833, + "names": "litr4_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 834, + "names": "litr4_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 835, + "names": "litr4_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 836, + "names": "litr4_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 837, + "names": "litr4c_to_soil3c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 838, + "names": "litr4c_to_soil3c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 839, + "names": "litr4c_to_soil3c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 840, + "names": "litr4c_to_soil3c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 841, + "names": "litr4c_to_soil3c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 842, + "names": "litr4c_to_soil3c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 843, + "names": "litr4c_to_soil3c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 844, + "names": "litr4c_to_soil3c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 845, + "names": "litr4c_to_soil3c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 846, + "names": "litr4c_to_soil3c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 847, + "names": "soil1_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 848, + "names": "soil1_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 849, + "names": "soil1_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 850, + "names": "soil1_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 851, + "names": "soil1_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 852, + "names": "soil1_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 853, + "names": "soil1_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 854, + "names": "soil1_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 855, + "names": "soil1_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 856, + "names": "soil1_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 857, + "names": "soil1c_to_soil2c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 858, + "names": "soil1c_to_soil2c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 859, + "names": "soil1c_to_soil2c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 860, + "names": "soil1c_to_soil2c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 861, + "names": "soil1c_to_soil2c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 862, + "names": "soil1c_to_soil2c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 863, + "names": "soil1c_to_soil2c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 864, + "names": "soil1c_to_soil2c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 865, + "names": "soil1c_to_soil2c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 866, + "names": "soil1c_to_soil2c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 867, + "names": "soil2_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 868, + "names": "soil2_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer (3-10 cm)" + }, + { + "codes": 869, + "names": "soil2_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 870, + "names": "soil2_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 871, + "names": "soil2_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 872, + "names": "soil2_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 873, + "names": "soil2_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 874, + "names": "soil2_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 875, + "names": "soil2_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 876, + "names": "soil2_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 1 (400-1000 cm)" + }, + { + "codes": 877, + "names": "soil2c_to_soil3c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 878, + "names": "soil2c_to_soil3c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 879, + "names": "soil2c_to_soil3c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 880, + "names": "soil2c_to_soil3c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 881, + "names": "soil2c_to_soil3c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 882, + "names": "soil2c_to_soil3c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 883, + "names": "soil2c_to_soil3c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 884, + "names": "soil2c_to_soil3c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 885, + "names": "soil2c_to_soil3c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 886, + "names": "soil2c_to_soil3c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 887, + "names": "soil3_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 888, + "names": "soil3_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer (3-10 cm)" + }, + { + "codes": 889, + "names": "soil3_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 890, + "names": "soil3_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 891, + "names": "soil3_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 892, + "names": "soil3_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 893, + "names": "soil3_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 894, + "names": "soil3_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 895, + "names": "soil3_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 896, + "names": "soil3_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 897, + "names": "soil3c_to_soil4c[0]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 898, + "names": "soil3c_to_soil4c[1]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 2 (3-10 cm)" + }, + { + "codes": 899, + "names": "soil3c_to_soil4c[2]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 3 (10-30 cm)" + }, + { + "codes": 900, + "names": "soil3c_to_soil4c[3]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 4 (30-60 cm)" + }, + { + "codes": 901, + "names": "soil3c_to_soil4c[4]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 5 (60-90 cm)" + }, + { + "codes": 902, + "names": "soil3c_to_soil4c[5]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 6 (90-120 cm)" + }, + { + "codes": 903, + "names": "soil3c_to_soil4c[6]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 7 (120-150 cm)" + }, + { + "codes": 904, + "names": "soil3c_to_soil4c[7]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 8 (150-200 cm)" + }, + { + "codes": 905, + "names": "soil3c_to_soil4c[8]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 9 (200-400 cm)" + }, + { + "codes": 906, + "names": "soil3c_to_soil4c[9]", + "units": "kgC m-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 10 (400-1000 cm)" + }, + { + "codes": 907, + "names": "soil4_hr[0]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 1 (0-3 cm)" + }, + { + "codes": 908, + "names": "soil4_hr[1]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 2 (3-10 cm)" + }, + { + "codes": 909, + "names": "soil4_hr[2]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 3 (10-30 cm)" + }, + { + "codes": 910, + "names": "soil4_hr[3]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 4 (30-60 cm)" + }, + { + "codes": 911, + "names": "soil4_hr[4]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 5 (60-90 cm)" + }, + { + "codes": 912, + "names": "soil4_hr[5]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 6 (90-120 cm)" + }, + { + "codes": 913, + "names": "soil4_hr[6]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 7 (120-150 cm)" + }, + { + "codes": 914, + "names": "soil4_hr[7]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 8 (150-200 cm)" + }, + { + "codes": 915, + "names": "soil4_hr[8]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 9 (200-400 cm)" + }, + { + "codes": 916, + "names": "soil4_hr[9]", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 917, + "names": "soil1_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 918, + "names": "soil1_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 919, + "names": "soil1_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 920, + "names": "soil1_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 921, + "names": "soil1_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 922, + "names": "soil1_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 923, + "names": "soil1_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 924, + "names": "soil1_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 925, + "names": "soil1_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 926, + "names": "soil1_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 927, + "names": "soil2_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 928, + "names": "soil2_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 929, + "names": "soil2_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 930, + "names": "soil2_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 931, + "names": "soil2_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 932, + "names": "soil2_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 933, + "names": "soil2_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 934, + "names": "soil2_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 935, + "names": "soil2_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 936, + "names": "soil2_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 937, + "names": "soil3_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 938, + "names": "soil3_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 939, + "names": "soil3_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 940, + "names": "soil3_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 941, + "names": "soil3_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 942, + "names": "soil3_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 943, + "names": "soil3_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 944, + "names": "soil3_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 945, + "names": "soil3_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 946, + "names": "soil3_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 947, + "names": "soil4_DOC_percol[0]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 948, + "names": "soil4_DOC_percol[1]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 949, + "names": "soil4_DOC_percol[2]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 950, + "names": "soil4_DOC_percol[3]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 951, + "names": "soil4_DOC_percol[4]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 952, + "names": "soil4_DOC_percol[5]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 953, + "names": "soil4_DOC_percol[6]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 954, + "names": "soil4_DOC_percol[7]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 955, + "names": "soil4_DOC_percol[8]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 956, + "names": "soil4_DOC_percol[9]", + "units": "kgC m-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 957, + "names": "soil1_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 958, + "names": "soil1_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 959, + "names": "soil1_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 960, + "names": "soil1_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 961, + "names": "soil1_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 962, + "names": "soil1_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 963, + "names": "soil1_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 964, + "names": "soil1_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 965, + "names": "soil1_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 966, + "names": "soil1_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 967, + "names": "soil2_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 968, + "names": "soil2_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 969, + "names": "soil2_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 970, + "names": "soil2_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 971, + "names": "soil2_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 972, + "names": "soil2_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 973, + "names": "soil2_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 974, + "names": "soil2_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 975, + "names": "soil2_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 976, + "names": "soil2_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 977, + "names": "soil3_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 978, + "names": "soil3_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 979, + "names": "soil3_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 980, + "names": "soil3_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 981, + "names": "soil3_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 982, + "names": "soil3_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 983, + "names": "soil3_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 984, + "names": "soil3_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 985, + "names": "soil3_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 986, + "names": "soil3_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 987, + "names": "soil4_DOC_diffus[0]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 988, + "names": "soil4_DOC_diffus[1]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 989, + "names": "soil4_DOC_diffus[2]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 990, + "names": "soil4_DOC_diffus[3]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 991, + "names": "soil4_DOC_diffus[4]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 992, + "names": "soil4_DOC_diffus[5]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 993, + "names": "soil4_DOC_diffus[6]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 994, + "names": "soil4_DOC_diffus[7]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 995, + "names": "soil4_DOC_diffus[8]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 996, + "names": "soil4_DOC_diffus[9]", + "units": "kgC m-2 day-1", + "descriptions": "Diffused C flux from DOC of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 997, + "names": "DOC_leached_RZ", + "units": "kgC m-2 day-1", + "descriptions": "Leached DOC from rootzone" + }, + { + "codes": 998, + "names": "cpool_to_leafc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to leaf" + }, + { + "codes": 999, + "names": "cpool_to_leafc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Dail allocation C flux from current GPP to leaf storage pool" + }, + { + "codes": 1000, + "names": "cpool_to_frootc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fine root" + }, + { + "codes": 1001, + "names": "cpool_to_frootc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fine root storage pool" + }, + { + "codes": 1002, + "names": "cpool_to_fruitc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fruit" + }, + { + "codes": 1003, + "names": "cpool_to_fruitc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fruit storage pool" + }, + { + "codes": 1004, + "names": "cpool_to_softstemc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to softstem" + }, + { + "codes": 1005, + "names": "cpool_to_softstemc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to softstem storage pool" + }, + { + "codes": 1006, + "names": "cpool_to_livestemc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live stem" + }, + { + "codes": 1007, + "names": "cpool_to_livestemc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily alloaction C flux from current GPP to live stem storage pool" + }, + { + "codes": 1008, + "names": "cpool_to_deadstemc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead stem" + }, + { + "codes": 1009, + "names": "cpool_to_deadstemc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead stem storage pool" + }, + { + "codes": 1010, + "names": "cpool_to_livecrootc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live coarse root" + }, + { + "codes": 1011, + "names": "cpool_to_livecrootc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live coarse root storage pool" + }, + { + "codes": 1012, + "names": "cpool_to_deadcrootc", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead coarse root" + }, + { + "codes": 1013, + "names": "cpool_to_deadcrootc_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead coarse root storage pool" + }, + { + "codes": 1014, + "names": "cpool_to_gresp_storage", + "units": "kgC m-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to growth respiration storage pool" + }, + { + "codes": 1015, + "names": "cpool_leaf_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily leaf growth respiration flux" + }, + { + "codes": 1016, + "names": "cpool_leaf_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily leaf storage pool growth respiration flux" + }, + { + "codes": 1017, + "names": "transfer_leaf_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily leaf transfer pool respiration flux" + }, + { + "codes": 1018, + "names": "cpool_froot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fine root growth respiration flux" + }, + { + "codes": 1019, + "names": "cpool_froot_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fine root storage pool growth respiration flux" + }, + { + "codes": 1020, + "names": "transfer_froot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fine root transfer pool growth respiration flux" + }, + { + "codes": 1021, + "names": "cpool_fruit_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fruit growth respiration flux" + }, + { + "codes": 1022, + "names": "cpool_fruit_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fruit storage pool growth respiration flux" + }, + { + "codes": 1023, + "names": "transfer_fruit_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily fruit transfer pool gowth respiration flux" + }, + { + "codes": 1024, + "names": "cpool_softstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily softstem growth respiration flux" + }, + { + "codes": 1025, + "names": "cpool_softstem_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily softstem storage pool growth respiration flux" + }, + { + "codes": 1026, + "names": "transfer_softstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily softstem transfer pool growth respiration flux" + }, + { + "codes": 1027, + "names": "cpool_livestem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live stem growth respiration flux" + }, + { + "codes": 1028, + "names": "cpool_livestem_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live stem storage pool growth respiration flux" + }, + { + "codes": 1029, + "names": "transfer_livestem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live stem transfer pool growth respiration flux" + }, + { + "codes": 1030, + "names": "cpool_deadstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead stem growth respiration flux" + }, + { + "codes": 1031, + "names": "cpool_deadstem_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead stem storage pool growth respiration flux" + }, + { + "codes": 1032, + "names": "transfer_deadstem_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead stem transfer pool growth respiration flux" + }, + { + "codes": 1033, + "names": "cpool_livecroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live coarse root growth respiration flux" + }, + { + "codes": 1034, + "names": "cpool_livecroot_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live coarse root storage pool growth respiration flux" + }, + { + "codes": 1035, + "names": "transfer_livecroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily live coarse root transfer pool growth respiration flux" + }, + { + "codes": 1036, + "names": "cpool_deadcroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead coarse root growth respiration flux" + }, + { + "codes": 1037, + "names": "cpool_deadcroot_storage_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead coarse root storage pool respiration flux" + }, + { + "codes": 1038, + "names": "transfer_deadcroot_gr", + "units": "kgC m-2 day-1", + "descriptions": "Daily dead coarse root transfer pool respiration flux" + }, + { + "codes": 1039, + "names": "leafc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf storage pool" + }, + { + "codes": 1040, + "names": "frootc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root storage pool" + }, + { + "codes": 1041, + "names": "fruitc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fruit storage pool" + }, + { + "codes": 1042, + "names": "softstemc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem storage pool" + }, + { + "codes": 1043, + "names": "livestemc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem storage pool" + }, + { + "codes": 1044, + "names": "livecrootc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root storage pool" + }, + { + "codes": 1045, + "names": "deadstemc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead stem storage pool" + }, + { + "codes": 1046, + "names": "deadcrootc_storage_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead coarse root storage pool" + }, + { + "codes": 1047, + "names": "leafc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf transfer pool" + }, + { + "codes": 1048, + "names": "frootc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root transfer pool" + }, + { + "codes": 1049, + "names": "fruitc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fruit transfer pool" + }, + { + "codes": 1050, + "names": "softstemc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem transfer pool" + }, + { + "codes": 1051, + "names": "livestemc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem transfer pool" + }, + { + "codes": 1052, + "names": "livecrootc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root transfer pool" + }, + { + "codes": 1053, + "names": "deadstemc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead stem transfer pool" + }, + { + "codes": 1054, + "names": "deadcrootc_transfer_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead coarse root transfer pool" + }, + { + "codes": 1055, + "names": "leafc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf" + }, + { + "codes": 1056, + "names": "frootc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root" + }, + { + "codes": 1057, + "names": "fruitc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fruit" + }, + { + "codes": 1058, + "names": "softstemc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem" + }, + { + "codes": 1059, + "names": "livestemc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem" + }, + { + "codes": 1060, + "names": "livecrootc_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root" + }, + { + "codes": 1061, + "names": "NSC_nw_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-structured non-woody carbohydrates" + }, + { + "codes": 1062, + "names": "actC_nw_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-woody portion ofactual C pool" + }, + { + "codes": 1063, + "names": "NSC_w_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-structured woody carbohydrates" + }, + { + "codes": 1064, + "names": "actC_w_to_maintresp", + "units": "kgC m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from woody portion ofactual C pool" + }, + { + "codes": 1065, + "names": "leafc_storage_to_leafc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of leaf storage to transfer pool" + }, + { + "codes": 1066, + "names": "frootc_storage_to_frootc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of fine root storage to transfer pool" + }, + { + "codes": 1067, + "names": "fruitc_storage_to_fruitc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of fruit storage to transfer pool" + }, + { + "codes": 1068, + "names": "softstemc_storage_to_softstemc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of softstem storage to transfer pool" + }, + { + "codes": 1069, + "names": "livestemc_storage_to_livestemc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live stem storage to transfer pool" + }, + { + "codes": 1070, + "names": "deadstemc_storage_to_deadstemc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of dead stem storage to transfer pool" + }, + { + "codes": 1071, + "names": "livecrootc_storage_to_livecrootc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live coarse root storage to transfer pool" + }, + { + "codes": 1072, + "names": "deadcrootc_storage_to_deadcrootc_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of dead coarse root storage to transfer pool" + }, + { + "codes": 1073, + "names": "gresp_storage_to_gresp_transfer", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of growth respiration storage to transfer pool" + }, + { + "codes": 1074, + "names": "livestemc_to_deadstemc", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live stem to dead stem" + }, + { + "codes": 1075, + "names": "livecrootc_to_deadcrootc", + "units": "kgC m-2 day-1", + "descriptions": "Annual turnover of live coarse root to dead coarse root" + }, + { + "codes": 1076, + "names": "leafc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Leaf transfer pool C flux from planting" + }, + { + "codes": 1077, + "names": "frootc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Fine root transfer pool C flux from planting" + }, + { + "codes": 1078, + "names": "fruitc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Fruit transfer pool C flux from planting" + }, + { + "codes": 1079, + "names": "softstemc_transfer_from_PLT", + "units": "kgC m-2 day-1", + "descriptions": "Softstem transfer pool C flux from planting" + }, + { + "codes": 1080, + "names": "leafc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from leaf" + }, + { + "codes": 1081, + "names": "leafc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from leaf storage pool" + }, + { + "codes": 1082, + "names": "leafc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from leaf transfer pool" + }, + { + "codes": 1083, + "names": "fruitc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from fruit" + }, + { + "codes": 1084, + "names": "fruitc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from fruit storage pool" + }, + { + "codes": 1085, + "names": "fruitc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from fruit transfer pool" + }, + { + "codes": 1086, + "names": "livestemc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from live stem" + }, + { + "codes": 1087, + "names": "livestemc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from live stem storage pool" + }, + { + "codes": 1088, + "names": "livestemc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from live stem transfer pool" + }, + { + "codes": 1089, + "names": "deadstemc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from dead stem" + }, + { + "codes": 1090, + "names": "deadstemc_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from dead stem storage pool" + }, + { + "codes": 1091, + "names": "deadstemc_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from dead stem transfer pool" + }, + { + "codes": 1092, + "names": "gresp_storage_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from growth respiration storage pool" + }, + { + "codes": 1093, + "names": "gresp_transfer_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from growth respiration transfer pool" + }, + { + "codes": 1094, + "names": "THN_to_CTDBc_leaf", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down leaf biomass" + }, + { + "codes": 1095, + "names": "THN_to_CTDBc_fruit", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down fruit biomass" + }, + { + "codes": 1096, + "names": "THN_to_CTDBc_nsc", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down plant biomass non-structured pool" + }, + { + "codes": 1097, + "names": "THN_to_CTDBc_cstem", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux to cut-down coarse stem biomass" + }, + { + "codes": 1098, + "names": "STDBc_leaf_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from wilted leaf biomass" + }, + { + "codes": 1099, + "names": "STDBc_fruit_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from wilted fruit biomass" + }, + { + "codes": 1100, + "names": "STDBc_nsc_to_THN", + "units": "kgC m-2 day-1", + "descriptions": "Thinning C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1101, + "names": "leafc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from leaf" + }, + { + "codes": 1102, + "names": "leafc_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from leaf storage pool" + }, + { + "codes": 1103, + "names": "leafc_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from leaf transfer pool" + }, + { + "codes": 1104, + "names": "fruitc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from fruit" + }, + { + "codes": 1105, + "names": "fruitc_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from fruit storage pool" + }, + { + "codes": 1106, + "names": "fruitc_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from fruit transfer pool" + }, + { + "codes": 1107, + "names": "softstemc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from softstem" + }, + { + "codes": 1108, + "names": "softstemc_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from softstem storage pool" + }, + { + "codes": 1109, + "names": "softstemc_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from softstem transfer pool" + }, + { + "codes": 1110, + "names": "gresp_storage_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from growth respiration storage pool" + }, + { + "codes": 1111, + "names": "gresp_transfer_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from growth respiration transfer pool" + }, + { + "codes": 1112, + "names": "MOW_to_CTDBc_leaf", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down leaf biomass" + }, + { + "codes": 1113, + "names": "MOW_to_CTDBc_fruit", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down fruit biomass" + }, + { + "codes": 1114, + "names": "MOW_to_CTDBc_softstem", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down softstem biomass" + }, + { + "codes": 1115, + "names": "MOW_to_CTDBc_nsc", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux to cut-down biomass non-structured pool" + }, + { + "codes": 1116, + "names": "STDBc_leaf_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted leaf biomass" + }, + { + "codes": 1117, + "names": "STDBc_fruit_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted fruit biomass" + }, + { + "codes": 1118, + "names": "STDBc_softstem_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted softstem biomass" + }, + { + "codes": 1119, + "names": "STDBc_nsc_to_MOW", + "units": "kgC m-2 day-1", + "descriptions": "Mowing C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1120, + "names": "leafc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from leaf" + }, + { + "codes": 1121, + "names": "leafc_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from leaf storage pool" + }, + { + "codes": 1122, + "names": "leafc_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from leaf transfer pool" + }, + { + "codes": 1123, + "names": "fruitc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from fruit" + }, + { + "codes": 1124, + "names": "fruitc_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from fruit storage pool" + }, + { + "codes": 1125, + "names": "fruitc_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from fruit transfer pool" + }, + { + "codes": 1126, + "names": "softstemc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from softstem" + }, + { + "codes": 1127, + "names": "softstemc_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from softstem storage pool" + }, + { + "codes": 1128, + "names": "softstemc_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from softstem transfer pool" + }, + { + "codes": 1129, + "names": "gresp_storage_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from growth respiration storage pool" + }, + { + "codes": 1130, + "names": "gresp_transfer_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from growth respiration transfer pool" + }, + { + "codes": 1131, + "names": "HRV_to_CTDBc_leaf", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down leaf biomass" + }, + { + "codes": 1132, + "names": "HRV_to_CTDBc_fruit", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down fruit biomass" + }, + { + "codes": 1133, + "names": "HRV_to_CTDBc_softstem", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down softstem biomass" + }, + { + "codes": 1134, + "names": "HRV_to_CTDBc_nsc", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux to cut-down biomass non-structured pool" + }, + { + "codes": 1135, + "names": "STDBc_leaf_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted leaf biomass" + }, + { + "codes": 1136, + "names": "STDBc_fruit_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted fruit biomass" + }, + { + "codes": 1137, + "names": "STDBc_softstem_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted softstem biomass" + }, + { + "codes": 1138, + "names": "STDBc_nsc_to_HRV", + "units": "kgC m-2 day-1", + "descriptions": "Harvesting C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1139, + "names": "leafc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from leaf" + }, + { + "codes": 1140, + "names": "leafc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from leaf storage pool" + }, + { + "codes": 1141, + "names": "leafc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from leaf transfer pool" + }, + { + "codes": 1142, + "names": "frootc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fine root" + }, + { + "codes": 1143, + "names": "frootc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fine root storage pool" + }, + { + "codes": 1144, + "names": "frootc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fine root transfer pool" + }, + { + "codes": 1145, + "names": "fruitc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fruit" + }, + { + "codes": 1146, + "names": "fruitc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fruit storage pool" + }, + { + "codes": 1147, + "names": "fruitc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from fruit transfer pool" + }, + { + "codes": 1148, + "names": "softstemc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from softstem" + }, + { + "codes": 1149, + "names": "softstemc_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from softstem storage pool" + }, + { + "codes": 1150, + "names": "softstemc_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from softstem transfer pool" + }, + { + "codes": 1151, + "names": "gresp_storage_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from growth respiration storage pool" + }, + { + "codes": 1152, + "names": "gresp_transfer_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from growth respiration transfer pool" + }, + { + "codes": 1153, + "names": "STDBc_leaf_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted leaf biomass" + }, + { + "codes": 1154, + "names": "STDBc_froot_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted fine root biomass" + }, + { + "codes": 1155, + "names": "STDBc_fruit_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted fruit biomass" + }, + { + "codes": 1156, + "names": "STDBc_softstem_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted softstem biomass" + }, + { + "codes": 1157, + "names": "STDBc_nsc_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1158, + "names": "CTDBc_leaf_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from cut-down leaf biomass" + }, + { + "codes": 1159, + "names": "CTDBc_fruit_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from cut-down fruit biomass" + }, + { + "codes": 1160, + "names": "CTDBc_softstem_to_PLG", + "units": "kgC m-2 day-1", + "descriptions": "Ploughing C flux from cut-down softstem biomass" + }, + { + "codes": 1161, + "names": "leafc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from leaf" + }, + { + "codes": 1162, + "names": "leafc_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazig C flux from leaf storage pool" + }, + { + "codes": 1163, + "names": "leafc_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux fromleaf transfer pool" + }, + { + "codes": 1164, + "names": "fruitc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from fruit" + }, + { + "codes": 1165, + "names": "fruitc_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from fruit storage pool" + }, + { + "codes": 1166, + "names": "fruitc_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from fruit transfer pool" + }, + { + "codes": 1167, + "names": "softstemc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from softstem" + }, + { + "codes": 1168, + "names": "softstemc_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from softstem storage pool" + }, + { + "codes": 1169, + "names": "softstemc_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from softstem transfer pool" + }, + { + "codes": 1170, + "names": "gresp_storage_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from growth respiration storage pool" + }, + { + "codes": 1171, + "names": "gresp_transfer_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from growth respiration transfer pool" + }, + { + "codes": 1172, + "names": "STDBc_leaf_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from wilted leaf biomass" + }, + { + "codes": 1173, + "names": "STDBc_fruit_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux from wilted fruit biomass" + }, + { + "codes": 1174, + "names": "STDBc_softstem_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing flux from wilted softstem biomass" + }, + { + "codes": 1175, + "names": "STDBc_nsc_to_GRZ", + "units": "kgC m-2 day-1", + "descriptions": "Grazing flux from wilted plant biomass non-structured pool" + }, + { + "codes": 1176, + "names": "GRZ_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to labile litter" + }, + { + "codes": 1177, + "names": "GRZ_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to unshielded cellulose portion of litter" + }, + { + "codes": 1178, + "names": "GRZ_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to shielded cellulose portion of litter" + }, + { + "codes": 1179, + "names": "GRZ_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Grazing C flux to lignin portion of litter" + }, + { + "codes": 1180, + "names": "FRZ_to_litr1c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to labile litter" + }, + { + "codes": 1181, + "names": "FRZ_to_litr2c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to unshielded cellulose portion of litter" + }, + { + "codes": 1182, + "names": "FRZ_to_litr3c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to shielded cellulose portion of litter" + }, + { + "codes": 1183, + "names": "FRZ_to_litr4c", + "units": "kgC m-2 day-1", + "descriptions": "Fertilizing C flux to lignin portion of litter" + }, + { + "codes": 1184, + "names": "CH4_flux_soil", + "units": "kgC m-2 day-1", + "descriptions": "Estimated CH4 flux from soil" + }, + { + "codes": 1185, + "names": "CH4_flux_MANURE", + "units": "kgC m-2 day-1", + "descriptions": "Estimated CH4 flux from manure" + }, + { + "codes": 1186, + "names": "CH4_flux_ANIMAL", + "units": "kgC m-2 day-1", + "descriptions": "Estimated CH4 flux from animals" + }, + { + "codes": 1300, + "names": "leafn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of leaf pool" + }, + { + "codes": 1301, + "names": "leafn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of leaf storage pool" + }, + { + "codes": 1302, + "names": "leafn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of leaf transfer pool" + }, + { + "codes": 1303, + "names": "frootn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of fine root pool" + }, + { + "codes": 1304, + "names": "frootn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fine root storage pool" + }, + { + "codes": 1305, + "names": "frootn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fine root storage pool" + }, + { + "codes": 1306, + "names": "fruitn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of fruit pool" + }, + { + "codes": 1307, + "names": "fruitn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fruit storage pool" + }, + { + "codes": 1308, + "names": "fruitn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of fruit transfer pool" + }, + { + "codes": 1309, + "names": "softstemn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of softstem pool" + }, + { + "codes": 1310, + "names": "softstemn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of softstem storage pool" + }, + { + "codes": 1311, + "names": "softstemn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of softstem transfer pool" + }, + { + "codes": 1312, + "names": "livestemn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of live stem pool" + }, + { + "codes": 1313, + "names": "livestemn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live stem storage pool" + }, + { + "codes": 1314, + "names": "livestemn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live stem transfer pool" + }, + { + "codes": 1315, + "names": "deadstemn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of dead stem pool" + }, + { + "codes": 1316, + "names": "deadstemn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead stem storage pool" + }, + { + "codes": 1317, + "names": "deadstemn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead stem transfer pool" + }, + { + "codes": 1318, + "names": "livecrootn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of live coarse root pool" + }, + { + "codes": 1319, + "names": "livecrootn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live coarse root storage pool" + }, + { + "codes": 1320, + "names": "livecrootn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of live coarse root transfer pool" + }, + { + "codes": 1321, + "names": "deadcrootn", + "units": "kgN m-2", + "descriptions": "Actual nitrogen content of dead coarse root pool" + }, + { + "codes": 1322, + "names": "deadcrootn_storage", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead coarse root storage pool" + }, + { + "codes": 1323, + "names": "deadcrootn_transfer", + "units": "kgN m-2", + "descriptions": "Nitrogen content of dead coarse root transfer pool" + }, + { + "codes": 1324, + "names": "npool", + "units": "kgN m-2", + "descriptions": "Temporary plant N pool" + }, + { + "codes": 1325, + "names": "cwdn[0]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 1 (0-3 cm)" + }, + { + "codes": 1326, + "names": "cwdn[1]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 2 (3-10 cm)" + }, + { + "codes": 1327, + "names": "cwdn[2]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 3 (10-30 cm)" + }, + { + "codes": 1328, + "names": "cwdn[3]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 4 (30-60 cm)" + }, + { + "codes": 1329, + "names": "cwdn[4]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 5 (60-90 cm)" + }, + { + "codes": 1330, + "names": "cwdn[5]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 6 (90-120 cm)" + }, + { + "codes": 1331, + "names": "cwdn[6]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 7 (120-150 cm)" + }, + { + "codes": 1332, + "names": "cwdn[7]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 8 (150-200 cm)" + }, + { + "codes": 1333, + "names": "cwdn[8]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 9 (200-400 cm)" + }, + { + "codes": 1334, + "names": "cwdn[9]", + "units": "kgN m-2", + "descriptions": "Coarse woody debris N content in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1335, + "names": "litr1n[0]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1336, + "names": "litr1n[1]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1337, + "names": "litr1n[2]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1338, + "names": "litr1n[3]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1339, + "names": "litr1n[4]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1340, + "names": "litr1n[5]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1341, + "names": "litr1n[6]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1342, + "names": "litr1n[7]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1343, + "names": "litr1n[8]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1344, + "names": "litr1n[9]", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1345, + "names": "litr2n[0]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1346, + "names": "litr2n[1]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1347, + "names": "litr2n[2]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1348, + "names": "litr2n[3]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1349, + "names": "litr2n[4]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1350, + "names": "litr2n[5]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1351, + "names": "litr2n[6]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1352, + "names": "litr2n[7]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1353, + "names": "litr2n[8]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1354, + "names": "litr2n[9]", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1355, + "names": "litr3n[0]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1356, + "names": "litr3n[1]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1357, + "names": "litr3n[2]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1358, + "names": "litr3n[3]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1359, + "names": "litr3n[4]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1360, + "names": "litr3n[5]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1361, + "names": "litr3n[6]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1362, + "names": "litr3n[7]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1363, + "names": "litr3n[8]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1364, + "names": "litr3n[9]", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1365, + "names": "litr4n[0]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1366, + "names": "litr4n[1]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1367, + "names": "litr4n[2]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1368, + "names": "litr4n[3]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1369, + "names": "litr4n[4]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1370, + "names": "litr4n[5]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1371, + "names": "litr4n[6]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1372, + "names": "litr4n[7]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1373, + "names": "litr4n[8]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1374, + "names": "litr4n[9]", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1375, + "names": "litrN[0]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1376, + "names": "litrN[1]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1377, + "names": "litrN[2]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1378, + "names": "litrN[3]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1379, + "names": "litrN[4]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1380, + "names": "litrN[5]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1381, + "names": "litrN[6]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1382, + "names": "litrN[7]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1383, + "names": "litrN[8]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1384, + "names": "litrN[9]", + "units": "kgN m-2", + "descriptions": "Total N content of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1385, + "names": "litr1n_total", + "units": "kgN m-2", + "descriptions": "Labile N proportion of litter" + }, + { + "codes": 1386, + "names": "litr2n_total", + "units": "kgN m-2", + "descriptions": "N content of unshielded cellulose proportion of litter" + }, + { + "codes": 1387, + "names": "litr3n_total", + "units": "kgN m-2", + "descriptions": "N content of shielded cellulose proportion of litter" + }, + { + "codes": 1388, + "names": "litr4n_total", + "units": "kgN m-2", + "descriptions": "N content of lignin proportion of litter" + }, + { + "codes": 1389, + "names": "cwdn_total", + "units": "kgN m-2", + "descriptions": "Total nitrogen content of coarse woody debris" + }, + { + "codes": 1390, + "names": "STDBn_leaf", + "units": "kgN m-2", + "descriptions": "N content of wilted leaf biomass" + }, + { + "codes": 1391, + "names": "STDBn_froot", + "units": "kgN m-2", + "descriptions": "N content of wilted fine root biomass" + }, + { + "codes": 1392, + "names": "STDBn_fruit", + "units": "kgN m-2", + "descriptions": "N content of wilted fruit biomass" + }, + { + "codes": 1393, + "names": "STDBn_softstem", + "units": "kgN m-2", + "descriptions": "N content of wilted softstem biomass" + }, + { + "codes": 1394, + "names": "STDBn_nsc", + "units": "kgN m-2", + "descriptions": "N content of wilted non-structured biomass" + }, + { + "codes": 1395, + "names": "STDBn_above", + "units": "kgN m-2", + "descriptions": "N content of wilted aboveground plant biomass" + }, + { + "codes": 1396, + "names": "STDBn_below", + "units": "kgN m-2", + "descriptions": "N content of wilted belowground plant biomass" + }, + { + "codes": 1397, + "names": "CTDBn_leaf", + "units": "kgN m-2", + "descriptions": "N content of cut-down leaf biomass" + }, + { + "codes": 1398, + "names": "CTDBn_froot", + "units": "kgN m-2", + "descriptions": "N content of cut-down fineroot biomass" + }, + { + "codes": 1399, + "names": "CTDBn_fruit", + "units": "kgN m-2", + "descriptions": "N content of cut-down fruit biomass" + }, + { + "codes": 1400, + "names": "CTDBn_softstem", + "units": "kgN m-2", + "descriptions": "N content of cut-down softstem biomass" + }, + { + "codes": 1401, + "names": "CTDBn_nsc", + "units": "kgN m-2", + "descriptions": "N content of cut-down non-structured biomass" + }, + { + "codes": 1402, + "names": "CTDBn_cstem", + "units": "kgN m-2", + "descriptions": "N content of cut-down coarse stem biomass" + }, + { + "codes": 1403, + "names": "CTDBn_croot", + "units": "kgN m-2", + "descriptions": "N content of cut-down coarse root biomass" + }, + { + "codes": 1404, + "names": "CTDBn_above", + "units": "kgN m-2", + "descriptions": "N content of cut-down aboveground plant biomass" + }, + { + "codes": 1405, + "names": "CTDBn_below", + "units": "kgN m-2", + "descriptions": "N content of cut-down belowground plant biomass" + }, + { + "codes": 1406, + "names": "soil1n[0]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 1407, + "names": "soil1n[1]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 1408, + "names": "soil1n[2]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 1409, + "names": "soil1n[3]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 1410, + "names": "soil1n[4]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 1411, + "names": "soil1n[5]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 1412, + "names": "soil1n[6]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 1413, + "names": "soil1n[7]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 1414, + "names": "soil1n[8]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 1415, + "names": "soil1n[9]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 1416, + "names": "soil2n[0]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 1417, + "names": "soil2n[1]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 1418, + "names": "soil2n[2]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 1419, + "names": "soil2n[3]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 1420, + "names": "soil2n[4]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 1421, + "names": "soil2n[5]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 1422, + "names": "soil2n[6]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 1423, + "names": "soil2n[7]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 1424, + "names": "soil2n[8]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 1425, + "names": "soil2n[9]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 1426, + "names": "soil3n[0]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 1427, + "names": "soil3n[1]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 1428, + "names": "soil3n[2]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 1429, + "names": "soil3n[3]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 1430, + "names": "soil3n[4]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 1431, + "names": "soil3n[5]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 1432, + "names": "soil3n[6]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 1433, + "names": "soil3n[7]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 1434, + "names": "soil3n[8]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 1435, + "names": "soil3n[9]", + "units": "kgN m-2", + "descriptions": "Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 1436, + "names": "soil4n[0]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 1437, + "names": "soil4n[1]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 1438, + "names": "soil4n[2]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 1439, + "names": "soil4n[3]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 1440, + "names": "soil4n[4]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 1441, + "names": "soil4n[5]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 1442, + "names": "soil4n[6]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 1443, + "names": "soil4n[7]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 1444, + "names": "soil4n[8]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 1445, + "names": "soil4n[9]", + "units": "kgN m-2", + "descriptions": "stable soil organic matter N content of soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 1446, + "names": "soilN[0]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1447, + "names": "soilN[1]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1448, + "names": "soilN[2]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1449, + "names": "soilN[3]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1450, + "names": "soilN[4]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1451, + "names": "soilN[5]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1452, + "names": "soilN[6]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1453, + "names": "soilN[7]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1454, + "names": "soilN[8]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1455, + "names": "soilN[9]", + "units": "kgN m-2", + "descriptions": "Total N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1456, + "names": "soil1_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 1457, + "names": "soil1_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 1458, + "names": "soil1_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 1459, + "names": "soil1_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 1460, + "names": "soil1_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 1461, + "names": "soil1_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 1462, + "names": "soil1_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 1463, + "names": "soil1_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 1464, + "names": "soil1_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 1465, + "names": "soil1_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 1466, + "names": "soil2_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 1467, + "names": "soil2_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 1468, + "names": "soil2_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 1469, + "names": "soil2_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 1470, + "names": "soil2_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 1471, + "names": "soil2_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 1472, + "names": "soil2_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 1473, + "names": "soil2_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 1474, + "names": "soil2_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 1475, + "names": "soil2_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 1476, + "names": "soil3_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 1477, + "names": "soil3_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 1478, + "names": "soil3_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 1479, + "names": "soil3_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 1480, + "names": "soil3_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 1481, + "names": "soil3_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 1482, + "names": "soil3_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 1483, + "names": "soil3_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 1484, + "names": "soil3_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 1485, + "names": "soil3_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved Carbon content of SOM pool N content of soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 1486, + "names": "soil4_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 1487, + "names": "soil4_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 1488, + "names": "soil4_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 1489, + "names": "soil4_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 1490, + "names": "soil4_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 1491, + "names": "soil4_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 1492, + "names": "soil4_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 1493, + "names": "soil4_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 1494, + "names": "soil4_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 1495, + "names": "soil4_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 1496, + "names": "soil_DON[0]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1497, + "names": "soil_DON[1]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1498, + "names": "soil_DON[2]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1499, + "names": "soil_DON[3]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1500, + "names": "soil_DON[4]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1501, + "names": "soil_DON[5]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1502, + "names": "soil_DON[6]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1503, + "names": "soil_DON[7]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1504, + "names": "soil_DON[8]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1505, + "names": "soil_DON[9]", + "units": "kgN m-2", + "descriptions": "Dissolved part of total soil N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1506, + "names": "soil1n_total", + "units": "kgN m-2", + "descriptions": "Labile SOM nitrogen pool" + }, + { + "codes": 1507, + "names": "soil2n_total", + "units": "kgN m-2", + "descriptions": "Fast decomposing SOM nitrogen pool (fast)" + }, + { + "codes": 1508, + "names": "soil3n_total", + "units": "kgN m-2", + "descriptions": "Slow decomposing SOM nitrogen pool" + }, + { + "codes": 1509, + "names": "soil4n_total", + "units": "kgN m-2", + "descriptions": "Stable SOM nitrogen pool" + }, + { + "codes": 1510, + "names": "retransn", + "units": "kgN m-2", + "descriptions": "Plant pool of retranslocated N" + }, + { + "codes": 1511, + "names": "sminNH4[0]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1512, + "names": "sminNH4[1]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1513, + "names": "sminNH4[2]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1514, + "names": "sminNH4[3]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1515, + "names": "sminNH4[4]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1516, + "names": "sminNH4[5]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1517, + "names": "sminNH4[6]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1518, + "names": "sminNH4[7]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1519, + "names": "sminNH4[8]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1520, + "names": "sminNH4[9]", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1521, + "names": "sminNO3[0]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1522, + "names": "sminNO3[1]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1523, + "names": "sminNO3[2]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1524, + "names": "sminNO3[3]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1525, + "names": "sminNO3[4]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1526, + "names": "sminNO3[5]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1527, + "names": "sminNO3[6]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1528, + "names": "sminNO3[7]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1529, + "names": "sminNO3[8]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1530, + "names": "sminNO3[9]", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1531, + "names": "sminNH4_total", + "units": "kgN m-2", + "descriptions": "Mineral NH4 content of soil" + }, + { + "codes": 1532, + "names": "sminNO3_total", + "units": "kgN m-2", + "descriptions": "Mineral NO3 content of soil" + }, + { + "codes": 1533, + "names": "Nfix_src", + "units": "kgN m-2", + "descriptions": "SUM of biological N fixation" + }, + { + "codes": 1534, + "names": "Ndep_src", + "units": "kgN m-2", + "descriptions": "SUM of N deposition inputs" + }, + { + "codes": 1535, + "names": "Ndeepleach_snk", + "units": "kgN m-2", + "descriptions": "SUM of N deep leaching" + }, + { + "codes": 1536, + "names": "Nvol_snk", + "units": "kgN m-2", + "descriptions": "SUM of N lost to volatilization" + }, + { + "codes": 1537, + "names": "FIREsnk_N", + "units": "kgN m-2", + "descriptions": "SUM of N lost to fire" + }, + { + "codes": 1538, + "names": "Nprec_snk", + "units": "kgN m-2", + "descriptions": "SUM of N lost to precision control" + }, + { + "codes": 1539, + "names": "SNSCsnk_N", + "units": "kgN m-2", + "descriptions": "SUM of senescence N losses" + }, + { + "codes": 1540, + "names": "FRZsrc_N", + "units": "kgN m-2", + "descriptions": "SUM of N fertilization inputs" + }, + { + "codes": 1541, + "names": "PLTsrc_N", + "units": "kgN m-2", + "descriptions": "SUM of planted leaf N" + }, + { + "codes": 1542, + "names": "THN_transportN", + "units": "kgN m-2", + "descriptions": "SUM N content of thinned and transported plant material" + }, + { + "codes": 1543, + "names": "HRV_transportN", + "units": "kgN m-2", + "descriptions": "SUM of N content of harvested and transported plant material" + }, + { + "codes": 1544, + "names": "MOW_transportN", + "units": "kgN m-2", + "descriptions": "SUM of N content of mowed and transported plant material" + }, + { + "codes": 1545, + "names": "GRZsnk_N", + "units": "kgN m-2", + "descriptions": "SUM of grazed leaf N content" + }, + { + "codes": 1546, + "names": "GRZsrc_N", + "units": "kgN m-2", + "descriptions": "SUM of leaf N from grazing" + }, + { + "codes": 1548, + "names": "SPINUPsrc", + "units": "kgN m-2", + "descriptions": "SUM of leaf N from spinup" + }, + { + "codes": 1550, + "names": "NbalanceERR", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen balance error" + }, + { + "codes": 1551, + "names": "inN", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen input" + }, + { + "codes": 1552, + "names": "outN", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen output" + }, + { + "codes": 1553, + "names": "storeN", + "units": "kgN m-2", + "descriptions": "SUM of nitrogen store" + }, + { + "codes": 1700, + "names": "m_leafn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to labile N portion of litter" + }, + { + "codes": 1701, + "names": "m_leafn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to unshielded cellulose N portion of litter" + }, + { + "codes": 1702, + "names": "m_leafn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to shielded cellulose N portion of litter" + }, + { + "codes": 1703, + "names": "m_leafn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf to lignin N portion of litter" + }, + { + "codes": 1704, + "names": "m_frootn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to labile N portion of litter" + }, + { + "codes": 1705, + "names": "m_frootn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to unshielded cellulose N portion of litter" + }, + { + "codes": 1706, + "names": "m_frootn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to shielded cellulose portion N of litter" + }, + { + "codes": 1707, + "names": "m_frootn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root to lignin N portion of litter" + }, + { + "codes": 1708, + "names": "m_fruitn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to labile N portion of litter" + }, + { + "codes": 1709, + "names": "m_fruitn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to unshielded cellulose N portion of litter" + }, + { + "codes": 1710, + "names": "m_fruitn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to shielded cellulose N portion of litter" + }, + { + "codes": 1711, + "names": "m_fruitn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit to lignin N portion of litter" + }, + { + "codes": 1712, + "names": "m_softstemn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to labile N portion of litter" + }, + { + "codes": 1713, + "names": "m_softstemn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to unshielded cellulose N portion of litter" + }, + { + "codes": 1714, + "names": "m_softstemn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to shielded cellulose N portion of litter" + }, + { + "codes": 1715, + "names": "m_softstemn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem to lignin N portion of litter" + }, + { + "codes": 1716, + "names": "m_leafn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf storage pool to labile N portion of litter" + }, + { + "codes": 1717, + "names": "m_frootn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root storage pool to labile N portion of litter" + }, + { + "codes": 1718, + "names": "m_fruitn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit storage pool to labile N portion of litter" + }, + { + "codes": 1719, + "names": "m_fruitn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fruit transfer pool to labile N portion of litter" + }, + { + "codes": 1720, + "names": "m_softstemn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem storage pool to labile N portion of litter" + }, + { + "codes": 1721, + "names": "m_softstemn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from softstem transfer pool to labile N portion of litter" + }, + { + "codes": 1722, + "names": "m_livestemn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem storage pool to labile N portion of litter" + }, + { + "codes": 1723, + "names": "m_deadstemn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead stem storage pool to labile N portion of litter" + }, + { + "codes": 1724, + "names": "m_livecrootn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root storage pool to labile N portion of litter" + }, + { + "codes": 1725, + "names": "m_deadcrootn_storage_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead coarse root storage pool to labile N portion of litter" + }, + { + "codes": 1726, + "names": "m_leafn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from leaf transfer pool to labile N portion of litter" + }, + { + "codes": 1727, + "names": "m_frootn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from fine root transfer pool to labile N portion of litter" + }, + { + "codes": 1728, + "names": "m_livestemn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem transfer pool to labile N portion of litter" + }, + { + "codes": 1729, + "names": "m_deadstemn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead stem transfer pool to labile N portion of litter" + }, + { + "codes": 1730, + "names": "m_livecrootn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root transfer pool to labile N portion of litter" + }, + { + "codes": 1731, + "names": "m_deadcrootn_transfer_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead coarse root transfer pool to labile N portion of litter" + }, + { + "codes": 1732, + "names": "m_livestemn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem to labile N portion of litter" + }, + { + "codes": 1733, + "names": "m_livestemn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live stem to coarse woody debris" + }, + { + "codes": 1734, + "names": "m_deadstemn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead stem to coarse woody debris" + }, + { + "codes": 1735, + "names": "m_livecrootn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root ro labile N portion of litter" + }, + { + "codes": 1736, + "names": "m_livecrootn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from live coarse root to coarse woody debris" + }, + { + "codes": 1737, + "names": "m_deadcrootn_to_cwdn", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from dead coarse root to coarse woody debris" + }, + { + "codes": 1738, + "names": "m_retransn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Mortality N flux from retranslocated N to labile N portion of litter" + }, + { + "codes": 1739, + "names": "m_vegn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Total vegetation senescence N flux" + }, + { + "codes": 1740, + "names": "m_leafn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Leaf senescence N flux" + }, + { + "codes": 1741, + "names": "m_leafn_to_SNSCgenprog", + "units": "kgN m-2 day-1", + "descriptions": "Leaf gen. prog. scenescene N flux" + }, + { + "codes": 1742, + "names": "m_frootn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fine root senescene N flux" + }, + { + "codes": 1743, + "names": "m_leafn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Leaf storage pool senescence N flux" + }, + { + "codes": 1744, + "names": "m_frootn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fine root storage pool senescence N flux" + }, + { + "codes": 1745, + "names": "m_leafn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Leaf transfer pool senescence N flux" + }, + { + "codes": 1746, + "names": "m_frootn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fine root transfer pool senescence N flux" + }, + { + "codes": 1747, + "names": "m_fruitn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fruit senescence N flux" + }, + { + "codes": 1748, + "names": "m_fruitn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fruit storage pool senescence N flux" + }, + { + "codes": 1749, + "names": "m_fruitn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Fruit transfer pool senescence N flux" + }, + { + "codes": 1750, + "names": "m_softstemn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Softstem senescence N flux" + }, + { + "codes": 1751, + "names": "m_softstemn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Softstem storage pool senescence N flux" + }, + { + "codes": 1752, + "names": "m_softstemn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Softstem transfer pool senescence N flux" + }, + { + "codes": 1753, + "names": "m_retransn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Retranslocated N senescene N flux" + }, + { + "codes": 1754, + "names": "HRV_leafn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested leaf storage pool senescence N flux" + }, + { + "codes": 1755, + "names": "HRV_leafn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested leaf transfer pool senescence N flux" + }, + { + "codes": 1756, + "names": "HRV_fruitn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fruit storage pool senescence N flux" + }, + { + "codes": 1757, + "names": "HRV_fruitn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fruit transfer pool senescence N flux" + }, + { + "codes": 1758, + "names": "HRV_frootn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fine root senescence N flux" + }, + { + "codes": 1759, + "names": "HRV_softstemn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested softstem senscence N flux" + }, + { + "codes": 1760, + "names": "HRV_frootn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fine root storage senescence N flux" + }, + { + "codes": 1761, + "names": "HRV_frootn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested fine root transfer senescence N flux" + }, + { + "codes": 1762, + "names": "HRV_softstemn_storage_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested softstem storage senescence N flux" + }, + { + "codes": 1763, + "names": "HRV_softstemn_transfer_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested softstem transfer senescence N flux" + }, + { + "codes": 1764, + "names": "HRV_retransn_to_SNSC", + "units": "kgN m-2 day-1", + "descriptions": "Harvested retranslocated N senescence N flux" + }, + { + "codes": 1765, + "names": "fruitn_to_flowHS", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit flowering heat stress" + }, + { + "codes": 1766, + "names": "STDBn_leaf_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Leaf standing dead biomass N flux to litter" + }, + { + "codes": 1767, + "names": "STDBn_froot_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Fine root standing dead biomass N flux to litter" + }, + { + "codes": 1768, + "names": "STDBn_fruit_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Fruit standing dead biomass N flux to litter" + }, + { + "codes": 1769, + "names": "STDBn_softstem_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Softstem standing dead biomass N flux to litter" + }, + { + "codes": 1770, + "names": "STDBn_nsc_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Standing dead biomass non-structured pool N flux to litter" + }, + { + "codes": 1771, + "names": "STDBn_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Standing dead biomass N flux to litter" + }, + { + "codes": 1772, + "names": "CTDBn_leaf_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down leaf dead biomass N flux to litter" + }, + { + "codes": 1773, + "names": "CTDBn_froot_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down fine root dead biomass N flux to litter" + }, + { + "codes": 1774, + "names": "CTDBn_fruit_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down fruit dead biomass N flux to litter" + }, + { + "codes": 1775, + "names": "CTDBn_softstem_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down softstem dead biomass N flux to litter" + }, + { + "codes": 1776, + "names": "CTDBn_nsc_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down dead biomass non-structured pool N flux to litter" + }, + { + "codes": 1777, + "names": "CTDBn_cstem_to_cwd", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down coarse stem dead biomass N flux to coarse woody debris" + }, + { + "codes": 1778, + "names": "CTDBn_croot_to_cwd", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down coarse root dead biomass N flux to coarse woody debris" + }, + { + "codes": 1779, + "names": "CTDBn_to_litr", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down dead biomass N flux to litter" + }, + { + "codes": 1780, + "names": "m_leafn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Leaf fire N flux" + }, + { + "codes": 1781, + "names": "m_frootn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fine root fire N flux" + }, + { + "codes": 1782, + "names": "m_fruitn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fruit fire N flux" + }, + { + "codes": 1783, + "names": "m_softstemn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Softstem fire N flux" + }, + { + "codes": 1784, + "names": "m_STDBn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Wilted plant biomass fire N flux" + }, + { + "codes": 1785, + "names": "m_CTDBn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Cut-down plant biomass fire N flux" + }, + { + "codes": 1786, + "names": "m_leafn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Leaf storage pool fire N flux" + }, + { + "codes": 1787, + "names": "m_frootn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fine root storage pool fire N flux" + }, + { + "codes": 1788, + "names": "m_fruitn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fruit storage pool fire N flux" + }, + { + "codes": 1789, + "names": "m_fruitn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fruit transfer pool fire N flux" + }, + { + "codes": 1790, + "names": "m_softstemn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Softstem storage pool fire N flux" + }, + { + "codes": 1791, + "names": "m_softstemn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Softstem transfer pool fire N flux" + }, + { + "codes": 1792, + "names": "m_livestemn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live stem storage pool fire N flux" + }, + { + "codes": 1793, + "names": "m_deadstemn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead stem storage pool fire N flux" + }, + { + "codes": 1794, + "names": "m_livecrootn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live coarse root storage pool fire N flux" + }, + { + "codes": 1795, + "names": "m_deadcrootn_storage_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead coarse root storage pool fire N flux" + }, + { + "codes": 1796, + "names": "m_leafn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Leaf transfer pool fire N flux" + }, + { + "codes": 1797, + "names": "m_frootn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Fine root transfer pool fire N flux" + }, + { + "codes": 1798, + "names": "m_livestemn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live stem transfer pool fire N flux" + }, + { + "codes": 1799, + "names": "m_deadstemn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead stem transfer pool fire N flux" + }, + { + "codes": 1800, + "names": "m_livecrootn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live coarse root transfer pool fire N flux" + }, + { + "codes": 1801, + "names": "m_deadcrootn_transfer_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead coarse root transfer pool fire N flux" + }, + { + "codes": 1802, + "names": "m_livestemn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live stem fire N flux" + }, + { + "codes": 1803, + "names": "m_deadstemn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead stem fire N flux" + }, + { + "codes": 1804, + "names": "m_livecrootn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Live coarse root fire N flux" + }, + { + "codes": 1805, + "names": "m_deadcrootn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Dead coarse root fire N flux" + }, + { + "codes": 1806, + "names": "m_retransn_to_fire", + "units": "kgN m-2 day-1", + "descriptions": "Retranslocated N fire N flux" + }, + { + "codes": 1807, + "names": "m_litr1n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Labile N portion of litter fire N flux" + }, + { + "codes": 1808, + "names": "m_litr2n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Unshielded cellulose portion N of litter fire N flux" + }, + { + "codes": 1809, + "names": "m_litr3n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Shielded cellulose portion N of litter fire N flux" + }, + { + "codes": 1810, + "names": "m_litr4n_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Lignin N portion of litter fire N flux" + }, + { + "codes": 1811, + "names": "m_cwdn_to_fireTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Coarse woody debris fire N flux" + }, + { + "codes": 1812, + "names": "leafn_transfer_to_leafn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from leaf transfer pool to leaf" + }, + { + "codes": 1813, + "names": "frootn_transfer_to_frootn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from fine root transfer pool to fine root" + }, + { + "codes": 1814, + "names": "fruitn_transfer_to_fruitn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from fruit transfer pool to fruit" + }, + { + "codes": 1815, + "names": "softstemn_transfer_to_softstemn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from softstem transfer pool to softstem" + }, + { + "codes": 1816, + "names": "livestemn_transfer_to_livestemn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from live stem transfer pool to live stem" + }, + { + "codes": 1817, + "names": "deadstemn_transfer_to_deadstemn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from dead stem transfer to dead stem" + }, + { + "codes": 1818, + "names": "livecrootn_transfer_to_livecrootn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from live coarse root transfer pool to live coarse root" + }, + { + "codes": 1819, + "names": "deadcrootn_transfer_to_deadcrootn", + "units": "kgN m-2 day-1", + "descriptions": "Phenology N flux from dead coarse root transfer pool to dead coarse root" + }, + { + "codes": 1820, + "names": "leafn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to labile N portion of litter" + }, + { + "codes": 1821, + "names": "leafn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to unshielded cellulose N portion of litter" + }, + { + "codes": 1822, + "names": "leafn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to shielded cellulose N portion of litter" + }, + { + "codes": 1823, + "names": "leafn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to lignin N portion of litter" + }, + { + "codes": 1824, + "names": "leafn_to_retransn", + "units": "kgN m-2 day-1", + "descriptions": "N flux from leaf to retranslocated N" + }, + { + "codes": 1825, + "names": "frootn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to labile N portion of litter" + }, + { + "codes": 1826, + "names": "frootn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 1827, + "names": "frootn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 1828, + "names": "frootn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fine root to lignin N portion of litter" + }, + { + "codes": 1829, + "names": "fruitn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to labile N portion of litter" + }, + { + "codes": 1830, + "names": "fruitn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to unshielded cellulose portion of litter" + }, + { + "codes": 1831, + "names": "fruitn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to shielded cellulose portion of litter" + }, + { + "codes": 1832, + "names": "fruitn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fruit to lignin N portion of litter" + }, + { + "codes": 1833, + "names": "softstemn_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to labile N portion of litter" + }, + { + "codes": 1834, + "names": "softstemn_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 1835, + "names": "softstemn_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 1836, + "names": "softstemn_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "N flux from softstem to lignin N portion of litter" + }, + { + "codes": 1837, + "names": "ndep_to_sminnTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from N deposition to soil mineral N" + }, + { + "codes": 1838, + "names": "nfix_to_sminnTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from N fixation to soil mineral N" + }, + { + "codes": 1839, + "names": "cwdn_to_litr2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1840, + "names": "cwdn_to_litr2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1841, + "names": "cwdn_to_litr2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1842, + "names": "cwdn_to_litr2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1843, + "names": "cwdn_to_litr2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1844, + "names": "cwdn_to_litr2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1845, + "names": "cwdn_to_litr2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1846, + "names": "cwdn_to_litr2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1847, + "names": "cwdn_to_litr2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1848, + "names": "cwdn_to_litr2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1849, + "names": "cwdn_to_litr3n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1850, + "names": "cwdn_to_litr3n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1851, + "names": "cwdn_to_litr3n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1852, + "names": "cwdn_to_litr3n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1853, + "names": "cwdn_to_litr3n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1854, + "names": "cwdn_to_litr3n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1855, + "names": "cwdn_to_litr3n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1856, + "names": "cwdn_to_litr3n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1857, + "names": "cwdn_to_litr3n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1858, + "names": "cwdn_to_litr3n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1859, + "names": "cwdn_to_litr4n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1860, + "names": "cwdn_to_litr4n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1861, + "names": "cwdn_to_litr4n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1862, + "names": "cwdn_to_litr4n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1863, + "names": "cwdn_to_litr4n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1864, + "names": "cwdn_to_litr4n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1865, + "names": "cwdn_to_litr4n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1866, + "names": "cwdn_to_litr4n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1867, + "names": "cwdn_to_litr4n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1868, + "names": "cwdn_to_litr4n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1869, + "names": "litr1n_to_soil1n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1870, + "names": "litr1n_to_soil1n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1871, + "names": "litr1n_to_soil1n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1872, + "names": "litr1n_to_soil1n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1873, + "names": "litr1n_to_soil1n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1874, + "names": "litr1n_to_soil1n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1875, + "names": "litr1n_to_soil1n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1876, + "names": "litr1n_to_soil1n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1877, + "names": "litr1n_to_soil1n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1878, + "names": "litr1n_to_soil1n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1879, + "names": "litr2n_to_soil2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1880, + "names": "litr2n_to_soil2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1881, + "names": "litr2n_to_soil2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1882, + "names": "litr2n_to_soil2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1883, + "names": "litr2n_to_soil2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1884, + "names": "litr2n_to_soil2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1885, + "names": "litr2n_to_soil2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1886, + "names": "litr2n_to_soil2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1887, + "names": "litr2n_to_soil2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1888, + "names": "litr2n_to_soil2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1889, + "names": "litr3n_to_litr2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1890, + "names": "litr3n_to_litr2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1891, + "names": "litr3n_to_litr2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1892, + "names": "litr3n_to_litr2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1893, + "names": "litr3n_to_litr2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1894, + "names": "litr3n_to_litr2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1895, + "names": "litr3n_to_litr2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1896, + "names": "litr3n_to_litr2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1897, + "names": "litr3n_to_litr2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1898, + "names": "litr3n_to_litr2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1899, + "names": "litr4n_to_soil3n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1900, + "names": "litr4n_to_soil3n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1901, + "names": "litr4n_to_soil3n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1902, + "names": "litr4n_to_soil3n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1903, + "names": "litr4n_to_soil3n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1904, + "names": "litr4n_to_soil3n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1905, + "names": "litr4n_to_soil3n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1906, + "names": "litr4n_to_soil3n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1907, + "names": "litr4n_to_soil3n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1908, + "names": "litr4n_to_soil3n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1909, + "names": "soil1n_to_soil2n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1910, + "names": "soil1n_to_soil2n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1911, + "names": "soil1n_to_soil2n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1912, + "names": "soil1n_to_soil2n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1913, + "names": "soil1n_to_soil2n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1914, + "names": "soil1n_to_soil2n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1915, + "names": "soil1n_to_soil2n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1916, + "names": "soil1n_to_soil2n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1917, + "names": "soil1n_to_soil2n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1918, + "names": "soil1n_to_soil2n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1919, + "names": "soil2n_to_soil3n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1920, + "names": "soil2n_to_soil3n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1921, + "names": "soil2n_to_soil3n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1922, + "names": "soil2n_to_soil3n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1923, + "names": "soil2n_to_soil3n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1924, + "names": "soil2n_to_soil3n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1925, + "names": "soil2n_to_soil3n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1926, + "names": "soil2n_to_soil3n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1927, + "names": "soil2n_to_soil3n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1928, + "names": "soil2n_to_soil3n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1929, + "names": "soil3n_to_soil4n[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 1 (0-3 cm)" + }, + { + "codes": 1930, + "names": "soil3n_to_soil4n[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 2 (3-10 cm)" + }, + { + "codes": 1931, + "names": "soil3n_to_soil4n[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 3 (10-30 cm)" + }, + { + "codes": 1932, + "names": "soil3n_to_soil4n[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 4 (30-60 cm)" + }, + { + "codes": 1933, + "names": "soil3n_to_soil4n[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 5 (60-90 cm)" + }, + { + "codes": 1934, + "names": "soil3n_to_soil4n[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 6 (90-120 cm)" + }, + { + "codes": 1935, + "names": "soil3n_to_soil4n[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 7 (120-150 cm)" + }, + { + "codes": 1936, + "names": "soil3n_to_soil4n[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 8 (150-200 cm)" + }, + { + "codes": 1937, + "names": "soil3n_to_soil4n[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 9 (200-400 cm)" + }, + { + "codes": 1938, + "names": "soil3n_to_soil4n[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1939, + "names": "soil4n_to_sminNH4[0]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 1 (0-3 cm)" + }, + { + "codes": 1940, + "names": "soil4n_to_sminNH4[1]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer (3-10 cm)" + }, + { + "codes": 1941, + "names": "soil4n_to_sminNH4[2]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 3 (10-30 cm)" + }, + { + "codes": 1942, + "names": "soil4n_to_sminNH4[3]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 4 (30-60 cm)" + }, + { + "codes": 1943, + "names": "soil4n_to_sminNH4[4]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 5 (60-90 cm)" + }, + { + "codes": 1944, + "names": "soil4n_to_sminNH4[5]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 6 (90-120 cm)" + }, + { + "codes": 1945, + "names": "soil4n_to_sminNH4[6]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 7 (120-150 cm)" + }, + { + "codes": 1946, + "names": "soil4n_to_sminNH4[7]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 8 (150-200 cm)" + }, + { + "codes": 1947, + "names": "soil4n_to_sminNH4[8]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 9 (200-400 cm)" + }, + { + "codes": 1948, + "names": "soil4n_to_sminNH4[9]", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 1 (400-1000 cm)" + }, + { + "codes": 1949, + "names": "soil4n_to_sminNH4_total", + "units": "kgN m-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4" + }, + { + "codes": 1950, + "names": "sminn_to_soil_SUM[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 1 (0-3 cm)" + }, + { + "codes": 1951, + "names": "sminn_to_soil_SUM[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 2 (3-10 cm)" + }, + { + "codes": 1952, + "names": "sminn_to_soil_SUM[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 3 (10-30 cm)" + }, + { + "codes": 1953, + "names": "sminn_to_soil_SUM[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 4 (30-60 cm)" + }, + { + "codes": 1954, + "names": "sminn_to_soil_SUM[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 5 (60-90 cm)" + }, + { + "codes": 1955, + "names": "sminn_to_soil_SUM[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 6 (90-120 cm)" + }, + { + "codes": 1956, + "names": "sminn_to_soil_SUM[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 7 (120-150 cm)" + }, + { + "codes": 1957, + "names": "sminn_to_soil_SUM[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 8 (150-200 cm)" + }, + { + "codes": 1958, + "names": "sminn_to_soil_SUM[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 9 (200-400 cm)" + }, + { + "codes": 1959, + "names": "sminn_to_soil_SUM[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1960, + "names": "sminNH4_to_soil_SUM[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 1 (0-3 cm)" + }, + { + "codes": 1961, + "names": "sminNH4_to_soil_SUM[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 2 (3-10 cm)" + }, + { + "codes": 1962, + "names": "sminNH4_to_soil_SUM[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 3 (10-30 cm)" + }, + { + "codes": 1963, + "names": "sminNH4_to_soil_SUM[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 4 (30-60 cm)" + }, + { + "codes": 1964, + "names": "sminNH4_to_soil_SUM[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 5 (60-90 cm)" + }, + { + "codes": 1965, + "names": "sminNH4_to_soil_SUM[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 6 (90-120 cm)" + }, + { + "codes": 1966, + "names": "sminNH4_to_soil_SUM[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 7 (120-150 cm)" + }, + { + "codes": 1967, + "names": "sminNH4_to_soil_SUM[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 8 (150-200 cm)" + }, + { + "codes": 1968, + "names": "sminNH4_to_soil_SUM[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 9 (200-400 cm)" + }, + { + "codes": 1969, + "names": "sminNH4_to_soil_SUM[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1970, + "names": "sminNO3_to_soil_SUM[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 1 (0-3 cm)" + }, + { + "codes": 1971, + "names": "sminNO3_to_soil_SUM[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 2 (3-10 cm)" + }, + { + "codes": 1972, + "names": "sminNO3_to_soil_SUM[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 3 (10-30 cm)" + }, + { + "codes": 1973, + "names": "sminNO3_to_soil_SUM[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 4 (30-60 cm)" + }, + { + "codes": 1974, + "names": "sminNO3_to_soil_SUM[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 5 (60-90 cm)" + }, + { + "codes": 1975, + "names": "sminNO3_to_soil_SUM[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 6 (90-120 cm)" + }, + { + "codes": 1976, + "names": "sminNO3_to_soil_SUM[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 7 (120-150 cm)" + }, + { + "codes": 1977, + "names": "sminNO3_to_soil_SUM[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 8 (150-200 cm)" + }, + { + "codes": 1978, + "names": "sminNO3_to_soil_SUM[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 9 (200-400 cm)" + }, + { + "codes": 1979, + "names": "sminNO3_to_soil_SUM[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1980, + "names": "sminn_to_soil1n_l1[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1981, + "names": "sminn_to_soil1n_l1[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1982, + "names": "sminn_to_soil1n_l1[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1983, + "names": "sminn_to_soil1n_l1[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1984, + "names": "sminn_to_soil1n_l1[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1985, + "names": "sminn_to_soil1n_l1[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1986, + "names": "sminn_to_soil1n_l1[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1987, + "names": "sminn_to_soil1n_l1[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1988, + "names": "sminn_to_soil1n_l1[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1989, + "names": "sminn_to_soil1n_l1[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1990, + "names": "sminn_to_soil2n_l2[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1991, + "names": "sminn_to_soil2n_l2[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1992, + "names": "sminn_to_soil2n_l2[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1993, + "names": "sminn_to_soil2n_l2[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1994, + "names": "sminn_to_soil2n_l2[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1995, + "names": "sminn_to_soil2n_l2[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1996, + "names": "sminn_to_soil2n_l2[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1997, + "names": "sminn_to_soil2n_l2[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1998, + "names": "sminn_to_soil2n_l2[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1999, + "names": "sminn_to_soil2n_l2[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2000, + "names": "sminn_to_soil3n_l4[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2001, + "names": "sminn_to_soil3n_l4[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2002, + "names": "sminn_to_soil3n_l4[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2003, + "names": "sminn_to_soil3n_l4[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2004, + "names": "sminn_to_soil3n_l4[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2005, + "names": "sminn_to_soil3n_l4[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2006, + "names": "sminn_to_soil3n_l4[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2007, + "names": "sminn_to_soil3n_l4[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2008, + "names": "sminn_to_soil3n_l4[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2009, + "names": "sminn_to_soil3n_l4[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2010, + "names": "sminn_to_soil2n_s1[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2011, + "names": "sminn_to_soil2n_s1[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2012, + "names": "sminn_to_soil2n_s1[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2013, + "names": "sminn_to_soil2n_s1[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2014, + "names": "sminn_to_soil2n_s1[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2015, + "names": "sminn_to_soil2n_s1[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2016, + "names": "sminn_to_soil2n_s1[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2017, + "names": "sminn_to_soil2n_s1[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2018, + "names": "sminn_to_soil2n_s1[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2019, + "names": "sminn_to_soil2n_s1[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2020, + "names": "sminn_to_soil3n_s2[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2021, + "names": "sminn_to_soil3n_s2[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2022, + "names": "sminn_to_soil3n_s2[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2023, + "names": "sminn_to_soil3n_s2[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2024, + "names": "sminn_to_soil3n_s2[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2025, + "names": "sminn_to_soil3n_s2[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2026, + "names": "sminn_to_soil3n_s2[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2027, + "names": "sminn_to_soil3n_s2[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2028, + "names": "sminn_to_soil3n_s2[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2029, + "names": "sminn_to_soil3n_s2[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2030, + "names": "sminn_to_soil4n_s3[0]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2031, + "names": "sminn_to_soil4n_s3[1]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2032, + "names": "sminn_to_soil4n_s3[2]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2033, + "names": "sminn_to_soil4n_s3[3]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2034, + "names": "sminn_to_soil4n_s3[4]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2035, + "names": "sminn_to_soil4n_s3[5]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2036, + "names": "sminn_to_soil4n_s3[6]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2037, + "names": "sminn_to_soil4n_s3[7]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2038, + "names": "sminn_to_soil4n_s3[8]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2039, + "names": "sminn_to_soil4n_s3[9]", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2040, + "names": "sminn_to_soil_SUM_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil" + }, + { + "codes": 2041, + "names": "sminNH4_to_soil_SUM_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux srom soil mineral NH4 to soil" + }, + { + "codes": 2042, + "names": "sminNO3_to_soil_SUM_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral NO3 to soil" + }, + { + "codes": 2043, + "names": "sminNO3_to_denitr[0]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2044, + "names": "sminNO3_to_denitr[1]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2045, + "names": "sminNO3_to_denitr[2]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2045, + "names": "cwdn_to_litr2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in total soil" + }, + { + "codes": 2046, + "names": "sminNO3_to_denitr[3]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2046, + "names": "cwdn_to_litr3n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in total soil" + }, + { + "codes": 2047, + "names": "sminNO3_to_denitr[4]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2047, + "names": "cwdn_to_litr4n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in total soil" + }, + { + "codes": 2048, + "names": "sminNO3_to_denitr[5]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2048, + "names": "litr1n_to_soil1n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in total soil" + }, + { + "codes": 2049, + "names": "sminNO3_to_denitr[6]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2049, + "names": "litr2n_to_soil2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in total soil" + }, + { + "codes": 2050, + "names": "sminNO3_to_denitr[7]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2050, + "names": "litr3n_to_litr2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in total soil" + }, + { + "codes": 2051, + "names": "sminNO3_to_denitr[8]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2051, + "names": "litr4n_to_soil3n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in total soil" + }, + { + "codes": 2052, + "names": "sminNO3_to_denitr[9]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2052, + "names": "soil1n_to_soil2n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from labile to fast decomposing SOM pool in total soil" + }, + { + "codes": 2053, + "names": "sminNH4_to_nitrif[0]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2053, + "names": "soil2n_to_soil3n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from fast to slow decomposing SOM pool in total soil" + }, + { + "codes": 2054, + "names": "sminNH4_to_nitrif[1]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2054, + "names": "soil3n_to_soil4n_total", + "units": "kgN m-2 day-1", + "descriptions": "N flux from slow to stable SOM Carbon content of SOM pool in total soil" + }, + { + "codes": 2055, + "names": "sminNH4_to_nitrif[2]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2055, + "names": "sminn_to_soil1n_l1_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2056, + "names": "sminNH4_to_nitrif[3]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2056, + "names": "sminn_to_soil2n_l2_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2057, + "names": "sminNH4_to_nitrif[4]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2057, + "names": "sminn_to_soil3n_l4_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2058, + "names": "sminNH4_to_nitrif[5]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2058, + "names": "sminn_to_soil2n_s1_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2059, + "names": "sminNH4_to_nitrif[6]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2059, + "names": "sminn_to_soil3n_s2_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2060, + "names": "sminNH4_to_nitrif[7]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2060, + "names": "sminn_to_soil4n_s3_total", + "units": "kgN m-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2061, + "names": "sminNH4_to_nitrif[8]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2062, + "names": "sminNH4_to_nitrif[9]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2063, + "names": "N2_flux_DENITR[0]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2064, + "names": "N2_flux_DENITR[1]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2065, + "names": "N2_flux_DENITR[2]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2066, + "names": "N2_flux_DENITR[3]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2067, + "names": "N2_flux_DENITR[4]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2068, + "names": "N2_flux_DENITR[5]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2069, + "names": "N2_flux_DENITR[6]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2070, + "names": "N2_flux_DENITR[7]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2071, + "names": "N2_flux_DENITR[8]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2072, + "names": "N2_flux_DENITR[9]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2073, + "names": "N2O_flux_NITRIF[0]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 1 (1-2 cm)" + }, + { + "codes": 2074, + "names": "N2O_flux_NITRIF[1]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 2 (3-10 cm)" + }, + { + "codes": 2075, + "names": "N2O_flux_NITRIF[2]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 3 (10-30 cm)" + }, + { + "codes": 2076, + "names": "N2O_flux_NITRIF[3]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 4 (30-60 cm)" + }, + { + "codes": 2077, + "names": "N2O_flux_NITRIF[4]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 5 (60-90 cm)" + }, + { + "codes": 2078, + "names": "N2O_flux_NITRIF[5]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 6 (90-120 cm)" + }, + { + "codes": 2079, + "names": "N2O_flux_NITRIF[6]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 7 (120-150 cm)" + }, + { + "codes": 2080, + "names": "N2O_flux_NITRIF[7]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 8 (150-200 cm)" + }, + { + "codes": 2081, + "names": "N2O_flux_NITRIF[8]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 9 (200-400 cm)" + }, + { + "codes": 2082, + "names": "N2O_flux_NITRIF[9]", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2083, + "names": "N2O_flux_DENITR[0]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 1 (1-2 cm)" + }, + { + "codes": 2084, + "names": "N2O_flux_DENITR[1]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 2 (3-10 cm)" + }, + { + "codes": 2085, + "names": "N2O_flux_DENITR[2]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 3 (10-30 cm)" + }, + { + "codes": 2086, + "names": "N2O_flux_DENITR[3]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 4 (30-60 cm)" + }, + { + "codes": 2087, + "names": "N2O_flux_DENITR[4]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 5 (60-90 cm)" + }, + { + "codes": 2088, + "names": "N2O_flux_DENITR[5]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 6 (90-120 cm)" + }, + { + "codes": 2089, + "names": "N2O_flux_DENITR[6]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 7 (120-150 cm)" + }, + { + "codes": 2090, + "names": "N2O_flux_DENITR[7]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 8 (150-200 cm)" + }, + { + "codes": 2091, + "names": "N2O_flux_DENITR[8]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 9 (200-400 cm)" + }, + { + "codes": 2092, + "names": "N2O_flux_DENITR[9]", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2093, + "names": "sminNO3_to_denitr_total", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3" + }, + { + "codes": 2094, + "names": "sminNH4_to_nitrif_total", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4" + }, + { + "codes": 2095, + "names": "N2_flux_DENITR_total", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2" + }, + { + "codes": 2096, + "names": "N2O_flux_NITRIF_total", + "units": "kgN m-2 day-1", + "descriptions": "Nitrification flux of N2O" + }, + { + "codes": 2097, + "names": "N2O_flux_DENITR_total", + "units": "kgN m-2 day-1", + "descriptions": "Denitrification flux of N2O" + }, + { + "codes": 2098, + "names": "sminNH4_to_npool[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 1 (1-2 cm)" + }, + { + "codes": 2099, + "names": "sminNH4_to_npool[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2100, + "names": "sminNH4_to_npool[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2101, + "names": "sminNH4_to_npool[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2102, + "names": "sminNH4_to_npool[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2103, + "names": "sminNH4_to_npool[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2104, + "names": "sminNH4_to_npool[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2105, + "names": "sminNH4_to_npool[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2106, + "names": "sminNH4_to_npool[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2107, + "names": "sminNH4_to_npool[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2108, + "names": "sminNO3_to_npool[0]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 1 (1-2 cm)" + }, + { + "codes": 2109, + "names": "sminNO3_to_npool[1]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2110, + "names": "sminNO3_to_npool[2]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2111, + "names": "sminNO3_to_npool[3]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2112, + "names": "sminNO3_to_npool[4]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2113, + "names": "sminNO3_to_npool[5]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2114, + "names": "sminNO3_to_npool[6]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2115, + "names": "sminNO3_to_npool[7]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2116, + "names": "sminNO3_to_npool[8]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2117, + "names": "sminNO3_to_npool[9]", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2118, + "names": "sminNH4_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool" + }, + { + "codes": 2119, + "names": "sminNO3_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool" + }, + { + "codes": 2120, + "names": "sminn_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "N flux from soil mineral N to temporary plant N pool" + }, + { + "codes": 2121, + "names": "sminNH4_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2122, + "names": "sminNH4_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2123, + "names": "sminNH4_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2124, + "names": "sminNH4_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2125, + "names": "sminNH4_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2126, + "names": "sminNH4_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2127, + "names": "sminNH4_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2128, + "names": "sminNH4_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2129, + "names": "sminNH4_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2130, + "names": "sminNH4_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NH4 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2131, + "names": "sminNH4_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2132, + "names": "sminNH4_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2133, + "names": "sminNH4_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2134, + "names": "sminNH4_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2135, + "names": "sminNH4_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2136, + "names": "sminNH4_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2137, + "names": "sminNH4_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2138, + "names": "sminNH4_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2139, + "names": "sminNH4_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2140, + "names": "sminNH4_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NH4 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2141, + "names": "sminNO3_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2142, + "names": "sminNO3_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2143, + "names": "sminNO3_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2144, + "names": "sminNO3_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2145, + "names": "sminNO3_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2146, + "names": "sminNO3_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2147, + "names": "sminNO3_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2148, + "names": "sminNO3_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2149, + "names": "sminNO3_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2150, + "names": "sminNO3_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral NO3 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2151, + "names": "sminNO3_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2152, + "names": "sminNO3_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2153, + "names": "sminNO3_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2154, + "names": "sminNO3_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2155, + "names": "sminNO3_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2156, + "names": "sminNO3_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2157, + "names": "sminNO3_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2158, + "names": "sminNO3_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2159, + "names": "sminNO3_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2160, + "names": "sminNO3_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused soil mineral NO3 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2161, + "names": "sminN_leached_RZ", + "units": "kgN m-2 day-1", + "descriptions": "Percolated soil mineral N from rootzone" + }, + { + "codes": 2162, + "names": "soil1_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2163, + "names": "soil1_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2164, + "names": "soil1_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2165, + "names": "soil1_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2166, + "names": "soil1_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2167, + "names": "soil1_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2168, + "names": "soil1_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2169, + "names": "soil1_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2170, + "names": "soil1_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2171, + "names": "soil1_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2172, + "names": "soil2_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2173, + "names": "soil2_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2174, + "names": "soil2_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2175, + "names": "soil2_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2176, + "names": "soil2_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2177, + "names": "soil2_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2178, + "names": "soil2_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2179, + "names": "soil2_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2180, + "names": "soil2_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2181, + "names": "soil2_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2182, + "names": "soil3_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2183, + "names": "soil3_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2184, + "names": "soil3_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2185, + "names": "soil3_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2186, + "names": "soil3_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2187, + "names": "soil3_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2188, + "names": "soil3_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2189, + "names": "soil3_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2190, + "names": "soil3_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2191, + "names": "soil3_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2192, + "names": "soil4_DON_percol[0]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 2193, + "names": "soil4_DON_percol[1]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 2194, + "names": "soil4_DON_percol[2]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 2195, + "names": "soil4_DON_percol[3]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 2196, + "names": "soil4_DON_percol[4]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 2197, + "names": "soil4_DON_percol[5]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 2198, + "names": "soil4_DON_percol[6]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 2199, + "names": "soil4_DON_percol[7]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 2200, + "names": "soil4_DON_percol[8]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 2201, + "names": "soil4_DON_percol[9]", + "units": "kgN m-2 day-1", + "descriptions": "Percolated N flux from DON of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2202, + "names": "soil1_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2203, + "names": "soil1_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2204, + "names": "soil1_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2205, + "names": "soil1_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2206, + "names": "soil1_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2207, + "names": "soil1_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2208, + "names": "soil1_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2209, + "names": "soil1_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2210, + "names": "soil1_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2211, + "names": "soil1_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2212, + "names": "soil2_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2213, + "names": "soil2_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2214, + "names": "soil2_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2215, + "names": "soil2_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2216, + "names": "soil2_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2217, + "names": "soil2_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2218, + "names": "soil2_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2219, + "names": "soil2_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2220, + "names": "soil2_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2221, + "names": "soil2_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2222, + "names": "soil3_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2223, + "names": "soil3_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2224, + "names": "soil3_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2225, + "names": "soil3_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2226, + "names": "soil3_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2227, + "names": "soil3_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2228, + "names": "soil3_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2229, + "names": "soil3_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2230, + "names": "soil3_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2231, + "names": "soil3_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2232, + "names": "soil4_DON_diffus[0]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 2233, + "names": "soil4_DON_diffus[1]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 2234, + "names": "soil4_DON_diffus[2]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 2235, + "names": "soil4_DON_diffus[3]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 2236, + "names": "soil4_DON_diffus[4]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 2237, + "names": "soil4_DON_diffus[5]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 2238, + "names": "soil4_DON_diffus[6]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 2239, + "names": "soil4_DON_diffus[7]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 2240, + "names": "soil4_DON_diffus[8]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 2241, + "names": "soil4_DON_diffus[9]", + "units": "kgN m-2 day-1", + "descriptions": "Diffused N flux from DON of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2242, + "names": "DON_leached_RZ", + "units": "kgN m-2 day-1", + "descriptions": "Leached DON from rootzone" + }, + { + "codes": 2243, + "names": "retransn_to_npoolTOTAL", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from retransclocated N to temporary plant N pool" + }, + { + "codes": 2244, + "names": "npool_to_leafn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to leaf" + }, + { + "codes": 2245, + "names": "npool_to_leafn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Dail allocation N flux from temporary plant N pool to leaf storage pool" + }, + { + "codes": 2246, + "names": "npool_to_frootn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fine root" + }, + { + "codes": 2247, + "names": "npool_to_frootn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fine root storage pool" + }, + { + "codes": 2248, + "names": "npool_to_fruitn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fruit" + }, + { + "codes": 2249, + "names": "npool_to_fruitn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fruit storage pool" + }, + { + "codes": 2250, + "names": "npool_to_softstemn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to softstem" + }, + { + "codes": 2251, + "names": "npool_to_softstemn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to softstem storage pool" + }, + { + "codes": 2252, + "names": "npool_to_livestemn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live stem" + }, + { + "codes": 2253, + "names": "npool_to_livestemn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily alloaction N flux from temporary plant N pool to live stem storage pool" + }, + { + "codes": 2254, + "names": "npool_to_deadstemn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead stem" + }, + { + "codes": 2255, + "names": "npool_to_deadstemn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead stem storage pool" + }, + { + "codes": 2256, + "names": "npool_to_livecrootn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live coarse root" + }, + { + "codes": 2257, + "names": "npool_to_livecrootn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live coarse root storage pool" + }, + { + "codes": 2258, + "names": "npool_to_deadcrootn", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead coarse root" + }, + { + "codes": 2259, + "names": "npool_to_deadcrootn_storage", + "units": "kgN m-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead coarse root storage pool" + }, + { + "codes": 2260, + "names": "leafn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf storage pool" + }, + { + "codes": 2261, + "names": "frootn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root storage pool" + }, + { + "codes": 2262, + "names": "fruitn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fruit storage pool" + }, + { + "codes": 2263, + "names": "softstemn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem storage pool" + }, + { + "codes": 2264, + "names": "livestemn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem storage pool" + }, + { + "codes": 2265, + "names": "livecrootn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root storage pool" + }, + { + "codes": 2266, + "names": "deadstemn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead stem storage pool" + }, + { + "codes": 2267, + "names": "deadcrootn_storage_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead coarse root storage pool" + }, + { + "codes": 2268, + "names": "leafn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf transfer pool" + }, + { + "codes": 2269, + "names": "frootn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root transfer pool" + }, + { + "codes": 2270, + "names": "fruitn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fruit transfer pool" + }, + { + "codes": 2271, + "names": "softstemn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem transfer pool" + }, + { + "codes": 2272, + "names": "livestemn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem transfer pool" + }, + { + "codes": 2273, + "names": "livecrootn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root transfer pool" + }, + { + "codes": 2274, + "names": "deadstemn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead stem transfer pool" + }, + { + "codes": 2275, + "names": "deadcrootn_transfer_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead coarse root transfer pool" + }, + { + "codes": 2276, + "names": "leafn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf" + }, + { + "codes": 2277, + "names": "frootn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root" + }, + { + "codes": 2278, + "names": "fruitn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fruit" + }, + { + "codes": 2279, + "names": "softstemn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem" + }, + { + "codes": 2280, + "names": "livestemn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem" + }, + { + "codes": 2281, + "names": "livecrootn_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root" + }, + { + "codes": 2282, + "names": "NSN_nw_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-structured non-woody nitrogen" + }, + { + "codes": 2283, + "names": "actN_nw_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-woody portion of actual N pool" + }, + { + "codes": 2284, + "names": "NSN_w_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-structured woody nitrogen" + }, + { + "codes": 2285, + "names": "actN_w_to_maintresp", + "units": "kgN m-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from woody portion ofactual N pool" + }, + { + "codes": 2286, + "names": "leafn_storage_to_leafn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of leaf storage to transfer pool" + }, + { + "codes": 2287, + "names": "frootn_storage_to_frootn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of fine root storage to transfer pool" + }, + { + "codes": 2288, + "names": "livestemn_storage_to_livestemn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live stem storage to transfer pool" + }, + { + "codes": 2289, + "names": "deadstemn_storage_to_deadstemn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of dead stem storage to transfer pool" + }, + { + "codes": 2290, + "names": "livecrootn_storage_to_livecrootn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live coarse root storage to transfer pool" + }, + { + "codes": 2291, + "names": "deadcrootn_storage_to_deadcrootn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of dead coarse root storage to transfer pool" + }, + { + "codes": 2292, + "names": "fruitn_storage_to_fruitn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of fruit storage to transfer pool" + }, + { + "codes": 2293, + "names": "softstemn_storage_to_softstemn_transfer", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of softstem storage to transfer pool" + }, + { + "codes": 2294, + "names": "livestemn_to_deadstemn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live stem to dead stem" + }, + { + "codes": 2295, + "names": "livestemn_to_retransn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N trunover of live stem to retranslocated N" + }, + { + "codes": 2296, + "names": "livecrootn_to_deadcrootn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live coarse root to dead coarse root" + }, + { + "codes": 2297, + "names": "livecrootn_to_retransn", + "units": "kgN m-2 day-1", + "descriptions": "Annual N turnover of live coarse root to retranslocated N" + }, + { + "codes": 2298, + "names": "leafn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Leaf transfer pool N flux from planting" + }, + { + "codes": 2299, + "names": "frootn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Fine root transfer pool N flux from planting" + }, + { + "codes": 2300, + "names": "fruitn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Fruit transfer pool N flux from planting" + }, + { + "codes": 2301, + "names": "softstemn_transfer_from_PLT", + "units": "kgN m-2 day-1", + "descriptions": "Softstem transfer pool N flux from planting" + }, + { + "codes": 2302, + "names": "leafn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from leaf" + }, + { + "codes": 2303, + "names": "leafn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from leaf storage pool" + }, + { + "codes": 2304, + "names": "leafn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from leaf transfer pool" + }, + { + "codes": 2305, + "names": "fruitn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from fruit" + }, + { + "codes": 2306, + "names": "fruitn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from fruit storage pool" + }, + { + "codes": 2307, + "names": "fruitn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from fruit transfer pool" + }, + { + "codes": 2308, + "names": "livestemn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from live stem" + }, + { + "codes": 2309, + "names": "livestemn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from live stem storage pool" + }, + { + "codes": 2310, + "names": "livestemn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from live stem transfer pool" + }, + { + "codes": 2311, + "names": "deadstemn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from dead stem" + }, + { + "codes": 2312, + "names": "deadstemn_storage_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from dead stem storage pool" + }, + { + "codes": 2313, + "names": "deadstemn_transfer_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from dead stem transfer pool" + }, + { + "codes": 2314, + "names": "retransn_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from retranslocated N" + }, + { + "codes": 2315, + "names": "THN_to_CTDBn_leaf", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down leaf biomass" + }, + { + "codes": 2316, + "names": "THN_to_CTDBn_fruit", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down fruit biomass" + }, + { + "codes": 2317, + "names": "THN_to_CTDBn_nsc", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down plant biomass non-structured pool" + }, + { + "codes": 2318, + "names": "THN_to_CTDBn_cstem", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux to cut-down coarse stem biomass" + }, + { + "codes": 2319, + "names": "STDBn_leaf_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from wilted leaf biomass" + }, + { + "codes": 2320, + "names": "STDBn_fruit_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from wilted fruit biomass" + }, + { + "codes": 2321, + "names": "STDBn_nsc_to_THN", + "units": "kgN m-2 day-1", + "descriptions": "Thinning N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2322, + "names": "leafn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from leaf" + }, + { + "codes": 2323, + "names": "leafn_storage_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from leaf storage pool" + }, + { + "codes": 2324, + "names": "leafn_transfer_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from leaf transfer pool" + }, + { + "codes": 2325, + "names": "fruitn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from fruit" + }, + { + "codes": 2326, + "names": "fruitn_storage_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from fruit storage pool" + }, + { + "codes": 2327, + "names": "fruitn_transfer_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from fruit transfer pool" + }, + { + "codes": 2328, + "names": "softstemn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from softstem" + }, + { + "codes": 2329, + "names": "softstemn_storage_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from softstem storage pool" + }, + { + "codes": 2330, + "names": "softstemn_transfer_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from softstem transfer pool" + }, + { + "codes": 2331, + "names": "retransn_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from retranslocated N" + }, + { + "codes": 2332, + "names": "MOW_to_CTDBn_leaf", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down leaf biomass" + }, + { + "codes": 2333, + "names": "MOW_to_CTDBn_fruit", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down fruit biomass" + }, + { + "codes": 2334, + "names": "MOW_to_CTDBn_softstem", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down softstem biomass" + }, + { + "codes": 2335, + "names": "MOW_to_CTDBn_nsc", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux to cut-down biomass non-structured pool" + }, + { + "codes": 2336, + "names": "STDBn_leaf_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted leaf biomass" + }, + { + "codes": 2337, + "names": "STDBn_fruit_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted fruit biomass" + }, + { + "codes": 2338, + "names": "STDBn_softstem_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted softstem biomass" + }, + { + "codes": 2339, + "names": "STDBn_nsc_to_MOW", + "units": "kgN m-2 day-1", + "descriptions": "Mowing N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2340, + "names": "leafn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from leaf" + }, + { + "codes": 2341, + "names": "leafn_storage_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from leaf storage pool" + }, + { + "codes": 2342, + "names": "leafn_transfer_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from leaf transfer pool" + }, + { + "codes": 2343, + "names": "fruitn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from fruit" + }, + { + "codes": 2344, + "names": "fruitn_storage_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from fruit storage pool" + }, + { + "codes": 2345, + "names": "fruitn_transfer_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from fruit transfer pool" + }, + { + "codes": 2346, + "names": "softstemn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from softstem" + }, + { + "codes": 2347, + "names": "softstemn_storage_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from softstem storage pool" + }, + { + "codes": 2348, + "names": "softstemn_transfer_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from softstem transfer pool" + }, + { + "codes": 2349, + "names": "retransn_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from retranslocated N" + }, + { + "codes": 2350, + "names": "HRV_to_CTDBn_leaf", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down leaf biomass" + }, + { + "codes": 2351, + "names": "HRV_to_CTDBn_fruit", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down fruit biomass" + }, + { + "codes": 2352, + "names": "HRV_to_CTDBn_softstem", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down softstem biomass" + }, + { + "codes": 2353, + "names": "HRV_to_CTDBn_nsc", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux to cut-down biomass non-structured pool" + }, + { + "codes": 2354, + "names": "STDBn_leaf_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted leaf biomass" + }, + { + "codes": 2355, + "names": "STDBn_fruit_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted fruit biomass" + }, + { + "codes": 2356, + "names": "STDBn_softstem_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted softstem biomass" + }, + { + "codes": 2357, + "names": "STDBn_nsc_to_HRV", + "units": "kgN m-2 day-1", + "descriptions": "Harvesting N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2358, + "names": "leafn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from leaf" + }, + { + "codes": 2359, + "names": "leafn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from leaf storage pool" + }, + { + "codes": 2360, + "names": "leafn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from leaf transfer pool" + }, + { + "codes": 2361, + "names": "frootn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fine root" + }, + { + "codes": 2362, + "names": "frootn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fine root storage pool" + }, + { + "codes": 2363, + "names": "frootn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fine root transfer pool" + }, + { + "codes": 2364, + "names": "fruitn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fruit" + }, + { + "codes": 2365, + "names": "fruitn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fruit storage pool" + }, + { + "codes": 2366, + "names": "fruitn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from fruit transfer pool" + }, + { + "codes": 2367, + "names": "softstemn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from softstem" + }, + { + "codes": 2368, + "names": "softstemn_storage_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from softstem storage pool" + }, + { + "codes": 2369, + "names": "softstemn_transfer_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from softstem transfer pool" + }, + { + "codes": 2370, + "names": "retransn_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from retranslocated N" + }, + { + "codes": 2371, + "names": "STDBn_leaf_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted leaf biomass" + }, + { + "codes": 2372, + "names": "STDBn_froot_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted fine root biomass" + }, + { + "codes": 2373, + "names": "STDBn_fruit_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted fruit biomass" + }, + { + "codes": 2374, + "names": "STDBn_softstem_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted softstem biomass" + }, + { + "codes": 2375, + "names": "STDBn_nsc_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2376, + "names": "CTDBn_leaf_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from cut-down leaf biomass" + }, + { + "codes": 2377, + "names": "CTDBn_fruit_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from cut-down fruit biomass" + }, + { + "codes": 2378, + "names": "CTDBn_softstem_to_PLG", + "units": "kgN m-2 day-1", + "descriptions": "Ploughing N flux from cut-down softstem biomass" + }, + { + "codes": 2379, + "names": "leafn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from leaf" + }, + { + "codes": 2380, + "names": "leafn_storage_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazig N flux from leaf storage pool" + }, + { + "codes": 2381, + "names": "leafn_transfer_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux fromleaf transfer pool" + }, + { + "codes": 2382, + "names": "fruitn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from fruit" + }, + { + "codes": 2383, + "names": "fruitn_storage_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from fruit storage pool" + }, + { + "codes": 2384, + "names": "fruitn_transfer_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from fruit transfer pool" + }, + { + "codes": 2385, + "names": "softstemn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from softstem" + }, + { + "codes": 2386, + "names": "softstemn_storage_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from softstem storage pool" + }, + { + "codes": 2387, + "names": "softstemn_transfer_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from softstem transfer pool" + }, + { + "codes": 2388, + "names": "STDBn_leaf_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from wilted leaf biomass" + }, + { + "codes": 2389, + "names": "STDBn_fruit_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux from wilted fruit biomass" + }, + { + "codes": 2390, + "names": "STDBn_softstem_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing flux from wilted softstem biomass" + }, + { + "codes": 2391, + "names": "STDBn_nsc_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing flux from wilted plant biomass non-structured pool" + }, + { + "codes": 2392, + "names": "retransn_to_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Grazing flux from retranslocated N" + }, + { + "codes": 2393, + "names": "GRZ_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to labile N portion of litter" + }, + { + "codes": 2394, + "names": "GRZ_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to unshielded cellulose N portion of litter" + }, + { + "codes": 2395, + "names": "GRZ_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to shielded cellulose N portion of litter" + }, + { + "codes": 2396, + "names": "GRZ_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Grazing N flux to lignin N portion of litter" + }, + { + "codes": 2397, + "names": "FRZ_to_sminNH4", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to soil mineral NH4" + }, + { + "codes": 2398, + "names": "FRZ_to_sminNO3", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to soil mineral NO3" + }, + { + "codes": 2399, + "names": "FRZ_to_litr1n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to labile N portion of litter" + }, + { + "codes": 2400, + "names": "FRZ_to_litr2n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to unshielded cellulose N portion of litter" + }, + { + "codes": 2401, + "names": "FRZ_to_litr3n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to shielded cellulose N portion of litter" + }, + { + "codes": 2402, + "names": "FRZ_to_litr4n", + "units": "kgN m-2 day-1", + "descriptions": "Fertilizing N flux to lignin N portion of litter" + }, + { + "codes": 2403, + "names": "N2O_flux_GRZ", + "units": "kgN m-2 day-1", + "descriptions": "Estimated N2O flux from grazing" + }, + { + "codes": 2404, + "names": "N2O_flux_FRZ", + "units": "kgN m-2 day-1", + "descriptions": "Estimated N2O flux from fertilizing" + }, + { + "codes": 2500, + "names": "thermal_time", + "units": "degree(Celsius)", + "descriptions": "Difference between avg. temp. and base temperature" + }, + { + "codes": 2501, + "names": "leafday", + "units": "n", + "descriptions": "Counter for days when leaves are on" + }, + { + "codes": 2502, + "names": "n_actphen", + "units": "n", + "descriptions": "Number of the actual phenophase" + }, + { + "codes": 2503, + "names": "leafday_lastmort", + "units": "degree(Celsius)", + "descriptions": "Last genetical mortality day" + }, + { + "codes": 2504, + "names": "flowHS_mort", + "units": "prop", + "descriptions": "Mortality coefficient of flowering heat stress" + }, + { + "codes": 2505, + "names": "transfer_ratio", + "units": "prop", + "descriptions": "Transfer proportion on actual day" + }, + { + "codes": 2506, + "names": "day_leafc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of leaf litterfall" + }, + { + "codes": 2507, + "names": "day_fruitc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of fruit litterfall" + }, + { + "codes": 2508, + "names": "day_softstemc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of softstem litterfall" + }, + { + "codes": 2509, + "names": "day_frootc_litfall_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of fineroot litterfall" + }, + { + "codes": 2510, + "names": "day_livestemc_turnover_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of livestem turnover" + }, + { + "codes": 2511, + "names": "day_livecrootc_turnover_increment", + "units": "kgC m-2 day-1", + "descriptions": "Daily rate of live coarse root turnover" + }, + { + "codes": 2512, + "names": "annmax_leafc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily leaf C content" + }, + { + "codes": 2513, + "names": "annmax_fruitc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily fruit C content" + }, + { + "codes": 2514, + "names": "annmax_softstemc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily softstem C content" + }, + { + "codes": 2515, + "names": "annmax_frootc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily fine root C content" + }, + { + "codes": 2516, + "names": "annmax_livestemc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily livestem C content" + }, + { + "codes": 2517, + "names": "annmax_livecrootc", + "units": "kgC m-2", + "descriptions": "Annual maximum daily live coarse root C content" + }, + { + "codes": 2518, + "names": "dsr", + "units": "n", + "descriptions": "Number of days since rain" + }, + { + "codes": 2519, + "names": "cumSWCstress", + "units": "n", + "descriptions": "Cumulative soil water stress" + }, + { + "codes": 2520, + "names": "proj_lai", + "units": "m^2 m-2", + "descriptions": "Live projected leaf area index" + }, + { + "codes": 2521, + "names": "all_lai", + "units": "m^2 m-2", + "descriptions": "Live all-sided leaf area index" + }, + { + "codes": 2522, + "names": "sla_avg", + "units": "m^2 m-2", + "descriptions": "Canopy average proj. SLA" + }, + { + "codes": 2523, + "names": "plaisun", + "units": "m^2 m-2", + "descriptions": "Sunlit projected leaf area index" + }, + { + "codes": 2524, + "names": "plaishade", + "units": "m^2 m-2", + "descriptions": "Shaded projected leaf area index" + }, + { + "codes": 2525, + "names": "sun_proj_sla", + "units": "m2 kgC-1", + "descriptions": "Sunlit projected SLA" + }, + { + "codes": 2526, + "names": "shade_proj_sla", + "units": "m2 kgC-1", + "descriptions": "Shaded projected SLA" + }, + { + "codes": 2527, + "names": "plant_height", + "units": "m", + "descriptions": "Height of plant (based on stemw and" + }, + { + "codes": 2528, + "names": "NDVI", + "units": "ratio", + "descriptions": "Normalized difference vegetation index" + }, + { + "codes": 2529, + "names": "rootlength_prop[0]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 1 (0-3 cm)" + }, + { + "codes": 2530, + "names": "rootlength_prop[1]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 2 (3-10 cm)" + }, + { + "codes": 2531, + "names": "rootlength_prop[2]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 3 (10-30 cm)" + }, + { + "codes": 2532, + "names": "rootlength_prop[3]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 4 (30-60 cm)" + }, + { + "codes": 2533, + "names": "rootlength_prop[4]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 5 (60-90 cm)" + }, + { + "codes": 2534, + "names": "rootlength_prop[5]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 6 (90-120 cm)" + }, + { + "codes": 2535, + "names": "rootlength_prop[6]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 7 (120-150 cm)" + }, + { + "codes": 2536, + "names": "rootlength_prop[7]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 8 (150-200 cm)" + }, + { + "codes": 2537, + "names": "rootlength_prop[8]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 9 (200-400 cm)" + }, + { + "codes": 2538, + "names": "rootlength_prop[9]", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2539, + "names": "psi[0]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 1 (0-3 cm)" + }, + { + "codes": 2540, + "names": "psi[1]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 2 (3-10 cm)" + }, + { + "codes": 2541, + "names": "psi[2]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 3 (10-30 cm)" + }, + { + "codes": 2542, + "names": "psi[3]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 4 (30-60 cm)" + }, + { + "codes": 2543, + "names": "psi[4]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 5 (60-90 cm)" + }, + { + "codes": 2544, + "names": "psi[5]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 6 (90-120 cm)" + }, + { + "codes": 2545, + "names": "psi[6]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 7 (120-150 cm)" + }, + { + "codes": 2546, + "names": "psi[7]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 8 (150-200 cm)" + }, + { + "codes": 2547, + "names": "psi[8]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 9 (200-400 cm)" + }, + { + "codes": 2548, + "names": "psi[9]", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2549, + "names": "pF[0]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 1 (0-3 cm)" + }, + { + "codes": 2550, + "names": "pF[1]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 2 (3-10 cm)" + }, + { + "codes": 2551, + "names": "pF[2]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 3 (10-30 cm)" + }, + { + "codes": 2552, + "names": "pF[3]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 4 (30-60 cm)" + }, + { + "codes": 2553, + "names": "pF[4]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 5 (60-90 cm)" + }, + { + "codes": 2554, + "names": "pF[5]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 6 (90-120 cm)" + }, + { + "codes": 2555, + "names": "pF[6]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 7 (120-150 cm)" + }, + { + "codes": 2556, + "names": "pF[7]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 8 (150-200 cm)" + }, + { + "codes": 2557, + "names": "pF[8]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 9 (200-400 cm)" + }, + { + "codes": 2558, + "names": "pF[9]", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2559, + "names": "hydr_conductSTART[0]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2560, + "names": "hydr_conductSTART[1]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2561, + "names": "hydr_conductSTART[2]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2562, + "names": "hydr_conductSTART[3]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2563, + "names": "hydr_conductSTART[4]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2564, + "names": "hydr_conductSTART[5]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2565, + "names": "hydr_conductSTART[6]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2566, + "names": "hydr_conductSTART[7]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2567, + "names": "hydr_conductSTART[8]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2568, + "names": "hydr_conductSTART[9]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the beginning of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2569, + "names": "hydr_diffusSTART[0]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2570, + "names": "hydr_diffusSTART[1]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2571, + "names": "hydr_diffusSTART[2]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2572, + "names": "hydr_diffusSTART[3]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2573, + "names": "hydr_diffusSTART[4]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2574, + "names": "hydr_diffusSTART[5]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2575, + "names": "hydr_diffusSTART[6]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2576, + "names": "hydr_diffusSTART[7]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2577, + "names": "hydr_diffusSTART[8]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2578, + "names": "hydr_diffusSTART[9]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the beginning of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2579, + "names": "hydr_conductEND[0]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2580, + "names": "hydr_conductEND[1]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2581, + "names": "hydr_conductEND[2]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2582, + "names": "hydr_conductEND[3]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2583, + "names": "hydr_conductEND[4]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2584, + "names": "hydr_conductEND[5]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2585, + "names": "rootdepth5", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2586, + "names": "hydr_conductEND[7]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2587, + "names": "hydr_conductEND[8]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2588, + "names": "hydr_conductEND[9]", + "units": "ms-1", + "descriptions": "Hydraulic conductivity at the end of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2589, + "names": "hydr_diffusEND[0]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2590, + "names": "hydr_diffusEND[1]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2591, + "names": "hydr_diffusEND[2]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2592, + "names": "hydr_diffusEND[3]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2593, + "names": "hydr_diffusEND[4]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2594, + "names": "hydr_diffusEND[5]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2595, + "names": "hydr_diffusEND[6]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2596, + "names": "hydr_diffusEND[7]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2597, + "names": "hydr_diffusEND[8]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2598, + "names": "hydr_diffusEND[9]", + "units": "m2 s-1", + "descriptions": "Hydraulic diffusivity at the end of the day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2599, + "names": "vwcSAT_RZ", + "units": "m3 m-3", + "descriptions": "Average value of VWC saturation (max.soil.depth)" + }, + { + "codes": 2600, + "names": "vwcFC_RZ", + "units": "m3 m-3", + "descriptions": "Average value of VWC field capacity (max.soil.depth)" + }, + { + "codes": 2601, + "names": "vwcWP_RZ", + "units": "m3 m-3", + "descriptions": "Average value of VWC wilting point (max.soil.depth)" + }, + { + "codes": 2602, + "names": "vwcHW_RZ", + "units": "m3 m-3", + "descriptions": "Average value of hygroscopic VWC (max.soil.depth)" + }, + { + "codes": 2603, + "names": "vwc[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 1 (0-3 cm)" + }, + { + "codes": 2604, + "names": "vwc[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 2 (3-10 cm)" + }, + { + "codes": 2605, + "names": "vwc[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 3 (10-30 cm)" + }, + { + "codes": 2606, + "names": "vwc[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 4 (30-60 cm)" + }, + { + "codes": 2607, + "names": "vwc[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 5 (60-90 cm)" + }, + { + "codes": 2608, + "names": "vwc[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 6 (90-120 cm)" + }, + { + "codes": 2609, + "names": "vwc[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 7 (120-150 cm)" + }, + { + "codes": 2610, + "names": "vwc[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 8 (150-200 cm)" + }, + { + "codes": 2611, + "names": "vwc[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 9 (200-400 cm)" + }, + { + "codes": 2612, + "names": "vwc[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2613, + "names": "vwc_crit1[0]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 1 (0-3 cm)" + }, + { + "codes": 2614, + "names": "vwc_crit1[1]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 2 (3-10 cm)" + }, + { + "codes": 2615, + "names": "vwc_crit1[2]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 3 (10-30 cm)" + }, + { + "codes": 2616, + "names": "vwc_crit1[3]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 4 (30-60 cm)" + }, + { + "codes": 2617, + "names": "vwc_crit1[4]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 5 (60-90 cm)" + }, + { + "codes": 2618, + "names": "vwc_crit1[5]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 6 (90-120 cm)" + }, + { + "codes": 2619, + "names": "vwc_crit1[6]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 7 (120-150 cm)" + }, + { + "codes": 2620, + "names": "vwc_crit1[7]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 8 (150-200 cm)" + }, + { + "codes": 2621, + "names": "vwc_crit1[8]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 9 (200-400 cm)" + }, + { + "codes": 2622, + "names": "vwc_crit1[9]", + "units": "ratio", + "descriptions": "Volumetric water content at start of conductance reduction of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2623, + "names": "vwc_crit2[0]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 1 (0-3 cm)" + }, + { + "codes": 2624, + "names": "vwc_crit2[1]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 2 (3-10 cm)" + }, + { + "codes": 2625, + "names": "vwc_crit2[2]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 3 (10-30 cm)" + }, + { + "codes": 2626, + "names": "vwc_crit2[3]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 4 (30-60 cm)" + }, + { + "codes": 2627, + "names": "vwc_crit2[4]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 5 (60-90 cm)" + }, + { + "codes": 2628, + "names": "vwc_crit2[5]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 6 (90-120 cm)" + }, + { + "codes": 2629, + "names": "vwc_crit2[6]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 7 (120-150 cm)" + }, + { + "codes": 2630, + "names": "vwc_crit2[7]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 8 (150-200 cm)" + }, + { + "codes": 2631, + "names": "vwc_crit2[8]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 9 (200-400 cm)" + }, + { + "codes": 2632, + "names": "vwc_crit2[9]", + "units": "ratio", + "descriptions": "Volumetric water content at stomatal closure of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2633, + "names": "vwc_avg", + "units": "m3 m-3", + "descriptions": "Average volumetric water content in active layers" + }, + { + "codes": 2634, + "names": "vwc_RZ", + "units": "m3 m-3", + "descriptions": "Average volumetric water content in rootzone (max.soil.depth)" + }, + { + "codes": 2635, + "names": "psi_RZ", + "units": "MPa", + "descriptions": "Average water potential of soil and leaves" + }, + { + "codes": 2636, + "names": "rootdepth", + "units": "m", + "descriptions": "Actual depth of the rooting zone" + }, + { + "codes": 2637, + "names": "dlmr_area_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit leaf MR" + }, + { + "codes": 2638, + "names": "dlmr_area_shade", + "units": "umol/m2/s", + "descriptions": "Shaded leaf MR" + }, + { + "codes": 2639, + "names": "gl_t_wv_sun", + "units": "m s-1", + "descriptions": "Sunlit leaf-scale conductance to transpired water" + }, + { + "codes": 2640, + "names": "gl_t_wv_shade", + "units": "m s-1", + "descriptions": "Shaded leaf-scale conductance to transpired water" + }, + { + "codes": 2641, + "names": "assim_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit assimilation per unit pleaf area index" + }, + { + "codes": 2642, + "names": "assim_shade", + "units": "umol/m2/s", + "descriptions": "Shaded assimilation per unit pleaf area index" + }, + { + "codes": 2643, + "names": "t_scalar[0]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2644, + "names": "t_scalar[1]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2645, + "names": "t_scalar[2]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2646, + "names": "t_scalar[3]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2647, + "names": "t_scalar[4]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2648, + "names": "t_scalar[5]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2649, + "names": "t_scalar[6]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2650, + "names": "t_scalar[7]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2651, + "names": "t_scalar[8]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2652, + "names": "t_scalar[9]", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2653, + "names": "w_scalar[0]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2654, + "names": "w_scalar[1]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2655, + "names": "w_scalar[2]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2656, + "names": "w_scalar[3]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2657, + "names": "w_scalar[4]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2658, + "names": "w_scalar[5]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2659, + "names": "w_scalar[6]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2660, + "names": "w_scalar[7]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2661, + "names": "w_scalar[8]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2662, + "names": "w_scalar[9]", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2663, + "names": "rate_scalar[0]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2664, + "names": "rate_scalar[1]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2665, + "names": "rate_scalar[2]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2666, + "names": "rate_scalar[3]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2667, + "names": "rate_scalar[4]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2668, + "names": "rate_scalar[5]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2669, + "names": "rate_scalar[6]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2670, + "names": "rate_scalar[7]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2671, + "names": "rate_scalar[8]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2672, + "names": "rate_scalar[9]", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2673, + "names": "rate_scalar_avg", + "units": "dimless", + "descriptions": "Decomposition combined and averaged scalar" + }, + { + "codes": 2674, + "names": "annmax_rootDepth", + "units": "m", + "descriptions": "Year-to-date maximum rooting depth" + }, + { + "codes": 2675, + "names": "annmax_plantHeight", + "units": "m", + "descriptions": "Year-to-date maximum plant height" + }, + { + "codes": 2676, + "names": "grossMINER[0]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2677, + "names": "grossMINER[1]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2678, + "names": "grossMINER[2]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2679, + "names": "grossMINER[3]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2680, + "names": "grossMINER[4]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2681, + "names": "grossMINER[5]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2682, + "names": "grossMINER[6]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2683, + "names": "grossMINER[7]", + "units": "kgN/m2/day", + "descriptions": "Gross N mineralization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2684, + "names": "potIMMOB[0]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2685, + "names": "potIMMOB[1]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2686, + "names": "potIMMOB[2]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2687, + "names": "potIMMOB[3]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2688, + "names": "potIMMOB[4]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2689, + "names": "potIMMOB[5]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2690, + "names": "potIMMOB[6]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2691, + "names": "potIMMOB[7]", + "units": "kgN/m2/day", + "descriptions": "Potential N immobilization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2692, + "names": "netMINER[0]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2693, + "names": "netMINER[1]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2694, + "names": "netMINER[2]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2695, + "names": "netMINER[3]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2696, + "names": "netMINER[4]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2697, + "names": "netMINER[5]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2698, + "names": "netMINER[6]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2699, + "names": "netMINER[7]", + "units": "kgN/m2/day", + "descriptions": "Net N mineralization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2700, + "names": "grossMINER_tot", + "units": "kgN/m2/day", + "descriptions": "Total gross N mineralization" + }, + { + "codes": 2701, + "names": "potIMMOB_total", + "units": "kgN/m2/day", + "descriptions": "Total potential N immobilization" + }, + { + "codes": 2702, + "names": "netMINER_total", + "units": "kgN/m2/day", + "descriptions": "Total net N mineralization" + }, + { + "codes": 2703, + "names": "actIMMOB_total", + "units": "kgN/m2/day", + "descriptions": "Total actual N immobilization" + }, + { + "codes": 2704, + "names": "stomaCONDUCT_max", + "units": "m/s", + "descriptions": "Maximal stomatal conductance with temperature-pressure correction" + }, + { + "codes": 2705, + "names": "m_tmin", + "units": "dimless", + "descriptions": "Freezing night temperature multiplier" + }, + { + "codes": 2706, + "names": "m_SWCstress_layer[0]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 1 (0-3 cm)" + }, + { + "codes": 2707, + "names": "m_SWCstress_layer[1]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 2 (3-10 cm)" + }, + { + "codes": 2708, + "names": "m_SWCstress_layer[2]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 3 (10-30 cm)" + }, + { + "codes": 2709, + "names": "m_SWCstress_layer[3]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 4 (30-60 cm)" + }, + { + "codes": 2710, + "names": "m_SWCstress_layer[4]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 5 (60-90 cm)" + }, + { + "codes": 2711, + "names": "m_SWCstress_layer[5]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 6 (90-120 cm)" + }, + { + "codes": 2712, + "names": "m_SWCstress_layer[6]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 7 (120-150 cm)" + }, + { + "codes": 2713, + "names": "m_SWCstress_layer[7]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 8 (150-200 cm)" + }, + { + "codes": 2714, + "names": "m_SWCstress_layer[8]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 9 (200-400 cm)" + }, + { + "codes": 2715, + "names": "m_SWCstress_layer[9]", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2716, + "names": "m_SWCstress", + "units": "dimless", + "descriptions": "Soil water properties multiplier" + }, + { + "codes": 2717, + "names": "m_ppfd_sun", + "units": "dimless", + "descriptions": "Sunlit PAR flux density multiplier" + }, + { + "codes": 2718, + "names": "m_ppfd_shade", + "units": "dimless", + "descriptions": "Sunshade PAR flux density multiplier" + }, + { + "codes": 2719, + "names": "m_vpd", + "units": "dimless", + "descriptions": "Vapor pressure deficit multiplier" + }, + { + "codes": 2720, + "names": "m_final_sun", + "units": "dimless", + "descriptions": "Sunlit product of all other multipliers" + }, + { + "codes": 2721, + "names": "m_final_shade", + "units": "dimless", + "descriptions": "Sunshade product of all other multipliers" + }, + { + "codes": 2722, + "names": "m_SWCstressLENGTH", + "units": "dimless", + "descriptions": "Soil water stress length multiplier" + }, + { + "codes": 2723, + "names": "m_extremT", + "units": "dimless", + "descriptions": "Extrem temperature multiplier" + }, + { + "codes": 2724, + "names": "SMSI", + "units": "prop", + "descriptions": "Soil moisture stress index" + }, + { + "codes": 2725, + "names": "gcorr", + "units": "dimless", + "descriptions": "Temperature and pressure correction factor for conductances" + }, + { + "codes": 2726, + "names": "gl_bl", + "units": "ms-1", + "descriptions": "Leaf boundary layer conductance" + }, + { + "codes": 2727, + "names": "gl_c", + "units": "ms-1", + "descriptions": "Leaf cuticular conductance" + }, + { + "codes": 2728, + "names": "gl_s_sun", + "units": "ms-1", + "descriptions": "Sunlit leaf-scale stomatal conductance" + }, + { + "codes": 2729, + "names": "gl_s_shade", + "units": "ms-1", + "descriptions": "Sunshade leaf-scale stomatal conductance" + }, + { + "codes": 2730, + "names": "gl_e_wv", + "units": "ms-1", + "descriptions": "Leaf conductance to evaporated water" + }, + { + "codes": 2731, + "names": "gl_sh", + "units": "ms-1", + "descriptions": "Leaf conductance to sensible heat" + }, + { + "codes": 2732, + "names": "gc_e_wv", + "units": "ms-1", + "descriptions": "Canopy conductance to evaporated water" + }, + { + "codes": 2733, + "names": "gc_sh", + "units": "ms-1", + "descriptions": "Canopy conductance to sensible heat" + }, + { + "codes": 2734, + "names": "annmax_lai", + "units": "m^{2 m-2", + "descriptions": "Year-to-date maximum projected leaf area index" + }, + { + "codes": 2735, + "names": "IMMOBratio[0]", + "units": "dimless", + "descriptions": "Immobilization ratio (act:pot) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2736, + "names": "IMMOBratio[1]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 2 (3-10 cm)" + }, + { + "codes": 2737, + "names": "IMMOBratio[2]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 3 (10-30 cm)" + }, + { + "codes": 2738, + "names": "IMMOBratio[3]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 4 (30-60 cm)" + }, + { + "codes": 2739, + "names": "IMMOBratio[4]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 5 (60-90 cm)" + }, + { + "codes": 2740, + "names": "IMMOBratio[5]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 6 (90-120 cm)" + }, + { + "codes": 2741, + "names": "IMMOBratio[6]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 7 (120-150 cm)" + }, + { + "codes": 2742, + "names": "IMMOBratio[7]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 8 (150-200 cm)" + }, + { + "codes": 2743, + "names": "IMMOBratio[8]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 9 (200-400 cm)" + }, + { + "codes": 2744, + "names": "IMMOBratio[9]", + "units": "dimless", + "descriptions": "Immobilization ratio in soil layer 9 (400-1000 cm)" + }, + { + "codes": 2745, + "names": "plant_calloc", + "units": "kgC m-2", + "descriptions": "Amount of allocated C" + }, + { + "codes": 2746, + "names": "plant_nalloc", + "units": "kgN m-2", + "descriptions": "Amount of allocated N" + }, + { + "codes": 2747, + "names": "excess_c", + "units": "kgC m-2", + "descriptions": "Difference between available and allocated carbon" + }, + { + "codes": 2748, + "names": "pnow", + "units": "prop", + "descriptions": "Proportion of growth displayed on current day" + }, + { + "codes": 2749, + "names": "NSC_limit_nw", + "units": "flag", + "descriptions": "For NSC-limitation in maint.resp.calculation for nw-biomass" + }, + { + "codes": 2750, + "names": "NSC_limit_w", + "units": "flag", + "descriptions": "For NSC-limitation in maint.resp.calculation for w-biomass" + }, + { + "codes": 2751, + "names": "plantNdemand", + "units": "kgN m-2", + "descriptions": "Plant N demand" + }, + { + "codes": 2752, + "names": "assim_Tcoeff", + "units": "dimless", + "descriptions": "Maximum temperature limitation factor of photosynthesis" + }, + { + "codes": 2753, + "names": "assim_SScoeff", + "units": "dimless", + "descriptions": "Soil moisture stress limitation factor of photosynthesis" + }, + { + "codes": 2754, + "names": "cumNstress", + "units": "dimless", + "descriptions": "Cumulative soil N stress" + }, + { + "codes": 2755, + "names": "SWCstressLENGTH", + "units": "dimless", + "descriptions": "Limitiation factor of SWC-stress length" + }, + { + "codes": 2756, + "names": "WFPS[1]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 1 (0-3 cm)" + }, + { + "codes": 2757, + "names": "WFPS[1]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 2 (3-10 cm)" + }, + { + "codes": 2758, + "names": "WFPS[2]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 3 (10-30 cm)" + }, + { + "codes": 2759, + "names": "WFPS[3]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 4 (30-60 cm)" + }, + { + "codes": 2760, + "names": "WFPS[4]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 5 (60-90 cm)" + }, + { + "codes": 2761, + "names": "WFPS[5]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 6 (90-120 cm)" + }, + { + "codes": 2762, + "names": "WFPS[6]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 7 (120-150 cm)" + }, + { + "codes": 2763, + "names": "WFPS[7]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 8 (150-200 cm)" + }, + { + "codes": 2764, + "names": "WFPS[8]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 9 (200-400 cm)" + }, + { + "codes": 2765, + "names": "WFPS[9]", + "units": "m3 m-3", + "descriptions": "Water filled pore spaceof soil layer 10 (400-1000 cm)" + }, + { + "codes": 2766, + "names": "wfps_scalar[1]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 2 (0-3 cm)" + }, + { + "codes": 2767, + "names": "wfps_scalar[1]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2768, + "names": "wfps_scalar[2]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2769, + "names": "wfps_scalar[3]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2770, + "names": "wfps_scalar[4]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2771, + "names": "wfps_scalar[5]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2772, + "names": "wfps_scalar[6]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2773, + "names": "wfps_scalar[7]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2774, + "names": "wfps_scalar[8]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2775, + "names": "wfps_scalar[9]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2776, + "names": "wfps_scalar[10]", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2777, + "names": "pH_scalar[1]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2778, + "names": "pH_scalar[2]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2779, + "names": "pH_scalar[3]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2780, + "names": "pH_scalar[4]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2781, + "names": "pH_scalar[5]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2782, + "names": "pH_scalar[6]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2783, + "names": "pH_scalar[7]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2784, + "names": "pH_scalar[8]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2785, + "names": "pH_scalar[9]", + "units": "dimless", + "descriptions": "Nitrification pH scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2786, + "names": "phenphase_date[0]", + "units": "dimless", + "descriptions": "First day of the phenphase1" + }, + { + "codes": 2787, + "names": "phenphase_date[1]", + "units": "dimless", + "descriptions": "First day of the phenphase2" + }, + { + "codes": 2788, + "names": "phenphase_date[2]", + "units": "dimless", + "descriptions": "First day of the phenphase3" + }, + { + "codes": 2789, + "names": "phenphase_date[3]", + "units": "dimless", + "descriptions": "First day of the phenphase4" + }, + { + "codes": 2790, + "names": "phenphase_date[4]", + "units": "dimless", + "descriptions": "First day of the phenphase5" + }, + { + "codes": 2791, + "names": "phenphase_date[5]", + "units": "dimless", + "descriptions": "First day of the phenphase6" + }, + { + "codes": 2792, + "names": "phenphase_date[6]", + "units": "dimless", + "descriptions": "First day of the phenphase7" + }, + { + "codes": 2793, + "names": "wpm_act", + "units": "dimless", + "descriptions": "Whole plant mortality value on actual day" + }, + { + "codes": 2794, + "names": "flower_date", + "units": "day of year", + "descriptions": "Start of flowering phenophase" + }, + { + "codes": 2795, + "names": "mulch_coverage", + "units": "%", + "descriptions": "Percent of mulch coverage" + }, + { + "codes": 2796, + "names": "evapREDmulch", + "units": "prop", + "descriptions": "Evaporation reduction of mulch" + }, + { + "codes": 2800, + "names": "RCN", + "units": "dimless", + "descriptions": "Runoff curve number" + }, + { + "codes": 2801, + "names": "soil_b[0]", + "units": "dimless", + "descriptions": "Clapp-Hornberger parameter in soil layer 1 (0-3 cm)" + }, + { + "codes": 2802, + "names": "soil_b[1]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 2 (3-10 cm)" + }, + { + "codes": 2803, + "names": "soil_b[2]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 3 (10-30 cm)" + }, + { + "codes": 2804, + "names": "soil_b[3]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 4 (30-60 cm)" + }, + { + "codes": 2805, + "names": "soil_b[4]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 5 (60-90 cm)" + }, + { + "codes": 2806, + "names": "soil_b[5]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 6 (90-120 cm)" + }, + { + "codes": 2807, + "names": "soil_b[6]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 7 (120-150 cm)" + }, + { + "codes": 2808, + "names": "soil_b[7]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 8 (150-200 cm)" + }, + { + "codes": 2809, + "names": "soil_b[8]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 9 (200-400 cm)" + }, + { + "codes": 2810, + "names": "soil_b[9]", + "units": "dimless", + "descriptions": "Clapp-Hornberger b parameter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2811, + "names": "BD[0]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 1 (0-3 cm)" + }, + { + "codes": 2812, + "names": "BD[1]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 2 (3-10 cm)" + }, + { + "codes": 2813, + "names": "BD[2]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 3 (10-30 cm)" + }, + { + "codes": 2814, + "names": "BD[3]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 4 (30-60 cm)" + }, + { + "codes": 2815, + "names": "BD[4]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 5 (60-90 cm)" + }, + { + "codes": 2816, + "names": "BD[5]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 6 (90-120 cm)" + }, + { + "codes": 2817, + "names": "BD[6]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 7 (120-150 cm)" + }, + { + "codes": 2818, + "names": "BD[7]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 8 (150-200 cm)" + }, + { + "codes": 2819, + "names": "BD[8]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 9 (200-400 cm)" + }, + { + "codes": 2820, + "names": "BD[9]", + "units": "gm^-3", + "descriptions": "Bulk density in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2821, + "names": "vwc_sat[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2822, + "names": "vwc_sat[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2823, + "names": "vwc_sat[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2824, + "names": "vwc_sat[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2825, + "names": "vwc_sat[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2826, + "names": "vwc_sat[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2827, + "names": "vwc_sat[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2828, + "names": "vwc_sat[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2829, + "names": "vwc_sat[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2830, + "names": "vwc_sat[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2831, + "names": "vwc_fc[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2832, + "names": "vwc_fc[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2833, + "names": "vwc_fc[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2834, + "names": "vwc_fc[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2835, + "names": "vwc_fc[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2836, + "names": "vwc_fc[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2837, + "names": "vwc_fc[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2838, + "names": "vwc_fc[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2839, + "names": "vwc_fc[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2840, + "names": "vwc_fc[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2841, + "names": "vwc_wp[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 1 (0-3 cm)" + }, + { + "codes": 2842, + "names": "vwc_wp[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 2 (3-10 cm)" + }, + { + "codes": 2843, + "names": "vwc_wp[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 3 (10-30 cm)" + }, + { + "codes": 2844, + "names": "vwc_wp[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 4 (30-60 cm)" + }, + { + "codes": 2845, + "names": "vwc_wp[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 5 (60-90 cm)" + }, + { + "codes": 2846, + "names": "vwc_wp[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 6 (90-120 cm)" + }, + { + "codes": 2847, + "names": "vwc_wp[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 7 (120-150 cm)" + }, + { + "codes": 2848, + "names": "vwc_wp[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 8 (150-200 cm)" + }, + { + "codes": 2849, + "names": "vwc_wp[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 9 (200-400 cm)" + }, + { + "codes": 2850, + "names": "vwc_wp[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at wilting point in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2851, + "names": "vwc_hw[0]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 1 (0-3 cm)" + }, + { + "codes": 2852, + "names": "vwc_hw[1]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 2 (3-10 cm)" + }, + { + "codes": 2853, + "names": "vwc_hw[2]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 3 (10-30 cm)" + }, + { + "codes": 2854, + "names": "vwc_hw[3]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 4 (30-60 cm)" + }, + { + "codes": 2855, + "names": "vwc_hw[4]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 5 (60-90 cm)" + }, + { + "codes": 2856, + "names": "vwc_hw[5]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 6 (90-120 cm)" + }, + { + "codes": 2857, + "names": "vwc_hw[6]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 7 (120-150 cm)" + }, + { + "codes": 2858, + "names": "vwc_hw[7]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 8 (150-200 cm)" + }, + { + "codes": 2859, + "names": "vwc_hw[8]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 9 (200-400 cm)" + }, + { + "codes": 2860, + "names": "vwc_hw[9]", + "units": "m3 m-3", + "descriptions": "Volumetric water content at hygroscopic water in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2861, + "names": "psi_sat[0]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2862, + "names": "psi_sat[1]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2863, + "names": "psi_sat[2]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2864, + "names": "psi_sat[3]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2865, + "names": "psi_sat[4]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2866, + "names": "psi_sat[5]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2867, + "names": "psi_sat[6]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2868, + "names": "psi_sat[7]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2869, + "names": "psi_sat[8]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2870, + "names": "psi_sat[9]", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2871, + "names": "psi_fc[0]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2872, + "names": "psi_fc[1]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2873, + "names": "psi_fc[2]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2874, + "names": "psi_fc[3]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2875, + "names": "psi_fc[4]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2876, + "names": "psi_fc[5]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2877, + "names": "psi_fc[6]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2878, + "names": "psi_fc[7]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2879, + "names": "psi_fc[8]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2880, + "names": "psi_fc[9]", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2881, + "names": "psi_wp[0]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 1 (0-3 cm)" + }, + { + "codes": 2882, + "names": "psi_wp[1]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 2 (3-10 cm)" + }, + { + "codes": 2883, + "names": "psi_wp[2]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 3 (10-30 cm)" + }, + { + "codes": 2884, + "names": "psi_wp[3]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 4 (30-60 cm)" + }, + { + "codes": 2885, + "names": "psi_wp[4]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 5 (60-90 cm)" + }, + { + "codes": 2886, + "names": "psi_wp[5]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 6 (90-120 cm)" + }, + { + "codes": 2887, + "names": "psi_wp[6]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 7 (120-150 cm)" + }, + { + "codes": 2888, + "names": "psi_wp[7]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 8 (150-200 cm)" + }, + { + "codes": 2889, + "names": "psi_wp[8]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 9 (200-400 cm)" + }, + { + "codes": 2890, + "names": "psi_wp[9]", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2891, + "names": "hydr_conduct_sat[0]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2892, + "names": "hydr_conduct_sat[1]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2893, + "names": "hydr_conduct_sat[2]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2894, + "names": "hydr_conduct_sat[3]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2895, + "names": "hydr_conduct_sat[4]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2896, + "names": "hydr_conduct_sat[5]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2897, + "names": "hydr_conduct_sat[6]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2898, + "names": "hydr_conduct_sat[7]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2899, + "names": "hydr_conduct_sat[8]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2900, + "names": "hydr_conduct_sat[9]", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2901, + "names": "hydr_diffus_sat[0]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2902, + "names": "hydr_diffus_sat[1]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2903, + "names": "hydr_diffus_sat[2]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2904, + "names": "hydr_diffus_sat[3]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2905, + "names": "hydr_diffus_sat[4]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2906, + "names": "hydr_diffus_sat[5]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2907, + "names": "hydr_diffus_sat[6]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2908, + "names": "hydr_diffus_sat[7]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2909, + "names": "hydr_diffus_sat[8]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2910, + "names": "hydr_diffus_sat[9]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2911, + "names": "hydr_conduct_fc[0]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2912, + "names": "hydr_conduct_fc[1]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2913, + "names": "hydr_conduct_fc[2]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2914, + "names": "hydr_conduct_fc[3]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2915, + "names": "hydr_conduct_fc[4]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2916, + "names": "hydr_conduct_fc[5]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2917, + "names": "hydr_conduct_fc[6]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2918, + "names": "hydr_conduct_fc[7]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2919, + "names": "hydr_conduct_fc[8]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2920, + "names": "hydr_conduct_fc[9]", + "units": "m s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2921, + "names": "hydr_diffus_fc[0]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2922, + "names": "hydr_diffus_fc[1]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2923, + "names": "hydr_diffus_fc[2]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2924, + "names": "hydr_diffus_fc[3]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2925, + "names": "hydr_diffus_fc[4]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2926, + "names": "hydr_diffus_fc[5]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2927, + "names": "hydr_diffus_fc[6]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2928, + "names": "hydr_diffus_fc[7]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2929, + "names": "hydr_diffus_fc[8]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2930, + "names": "hydr_diffus_fc[9]", + "units": "m2 s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2950, + "names": "pa_sun", + "units": "Pa", + "descriptions": "Sunlit atmospheric pressure" + }, + { + "codes": 2951, + "names": "pa_shade", + "units": "Pa", + "descriptions": "Sunshade atmospheric pressure" + }, + { + "codes": 2952, + "names": "co2_sun", + "units": "ppm", + "descriptions": "Sunlit atmospheric CO2 conc." + }, + { + "codes": 2953, + "names": "co2_shade", + "units": "ppm", + "descriptions": "Sunshade atmospheric CO2 conc." + }, + { + "codes": 2954, + "names": "t_sun", + "units": "degree(Celsius)", + "descriptions": "Sunlit temperature" + }, + { + "codes": 2955, + "names": "t_shade", + "units": "degree(Celsius)", + "descriptions": "Sunshade temperature" + }, + { + "codes": 2956, + "names": "lnc_sun", + "units": "kgN/(leaf)m2", + "descriptions": "Leaf N per unit sunlit leaf area" + }, + { + "codes": 2957, + "names": "lnc_shade", + "units": "kgN/(leaf)m2", + "descriptions": "Leaf N per unit sunshade area" + }, + { + "codes": 2958, + "names": "flnr_sun", + "units": "kgN Rubisco/kgN (leaf)", + "descriptions": "Sunlit fraction of leaf N in Rubisco" + }, + { + "codes": 2959, + "names": "flnr_shade", + "units": "kgN Rubisco/kgN (leaf)", + "descriptions": "Sunshade fraction of leaf N in Rubisco" + }, + { + "codes": 2960, + "names": "flnp_sun", + "units": "kgN PEP/kgN (leaf)", + "descriptions": "Sunlit fraction of leaf N in PEP Carboxylase" + }, + { + "codes": 2961, + "names": "flnp_shade", + "units": "kgN PEP/kgN (leaf)", + "descriptions": "Sunshade fraction of leaf N in PEP Carboxylase" + }, + { + "codes": 2962, + "names": "ppfd_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit PAR flux per unit sunlit leaf area" + }, + { + "codes": 2963, + "names": "ppfd_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade PAR flux per unit sunlit leaf area" + }, + { + "codes": 2964, + "names": "g_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit conductance to CO2" + }, + { + "codes": 2965, + "names": "g_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade conductance to CO2" + }, + { + "codes": 2966, + "names": "dlmr_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit day leaf maintenance respiration" + }, + { + "codes": 2967, + "names": "dlmr_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade day leaf maintenance respiration" + }, + { + "codes": 2968, + "names": "Ci_sun", + "units": "Pa", + "descriptions": "Sunlit intercellular CO2 concentration" + }, + { + "codes": 2969, + "names": "Ci_shade", + "units": "Pa", + "descriptions": "Sunshade intercellular CO2 concentration" + }, + { + "codes": 2970, + "names": "O2_sun", + "units": "Pa", + "descriptions": "Sunlit atmospheric O2 concentration" + }, + { + "codes": 2971, + "names": "O2_shade", + "units": "Pa", + "descriptions": "Sunshade atmospheric O2 concentration" + }, + { + "codes": 2972, + "names": "Ca_sun", + "units": "Pa", + "descriptions": "Sunlit atmospheric CO2 concentration" + }, + { + "codes": 2973, + "names": "Ca_shade", + "units": "Pa", + "descriptions": "Sunshade atmospheric CO2 concentration" + }, + { + "codes": 2974, + "names": "gamma_sun", + "units": "Pa", + "descriptions": "Sunlit CO2 compensation point" + }, + { + "codes": 2975, + "names": "gamma_shade", + "units": "Pa", + "descriptions": "Sunshade CO2 compensation point" + }, + { + "codes": 2976, + "names": "Kc_sun", + "units": "Pa", + "descriptions": "Sunlit MM constant carboxylation" + }, + { + "codes": 2977, + "names": "Kc_shade", + "units": "Pa", + "descriptions": "Sunshade MM constant carboxylation" + }, + { + "codes": 2978, + "names": "Ko_sun", + "units": "Pa", + "descriptions": "Sunlit MM constant oxygenation" + }, + { + "codes": 2979, + "names": "Ko_shade", + "units": "Pa", + "descriptions": "Sunshade MM constant oxygenation" + }, + { + "codes": 2980, + "names": "Vmax_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit max. rate of carboxylation" + }, + { + "codes": 2981, + "names": "Vmax_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade max. rate of carboxylation" + }, + { + "codes": 2982, + "names": "Jmax_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit max. rate of electron transport" + }, + { + "codes": 2983, + "names": "Jmax_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade max. rate of electron transport" + }, + { + "codes": 2984, + "names": "J_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit rate of RuBP regeneration" + }, + { + "codes": 2985, + "names": "J_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade rate of RuBP regeneration" + }, + { + "codes": 2986, + "names": "Av_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit carboxylation limited assimilation" + }, + { + "codes": 2987, + "names": "Av_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade carboxylation limited assimilation" + }, + { + "codes": 2988, + "names": "Aj_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit RuBP regeneration limited assimilation" + }, + { + "codes": 2989, + "names": "Aj_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade RuBP regeneration limited assimilation" + }, + { + "codes": 2990, + "names": "A_sun", + "units": "umol/m2/s", + "descriptions": "Sunlit final assimilation rate" + }, + { + "codes": 2991, + "names": "A_shade", + "units": "umol/m2/s", + "descriptions": "Sunshade final assimilation rate" + }, + { + "codes": 3000, + "names": "annprcp", + "units": "mm year-1", + "descriptions": "Annual precipitation" + }, + { + "codes": 3001, + "names": "anntavg", + "units": "degree", + "descriptions": "Annual average air temperature" + }, + { + "codes": 3002, + "names": "cum_runoff", + "units": "kgH2O m-2 year-1", + "descriptions": "Cumulated SUM of runoff" + }, + { + "codes": 3003, + "names": "cum_WleachRZ", + "units": "kgH2O m-2 year-1", + "descriptions": "Cumulated SUM of water leaching from rootzone" + }, + { + "codes": 3004, + "names": "daily_n2o", + "units": "kgN m-2 day-1", + "descriptions": "Daily N2O flux" + }, + { + "codes": 3005, + "names": "daily_nep", + "units": "kgC m-2 day-1", + "descriptions": "Net ecosystem production" + }, + { + "codes": 3006, + "names": "daily_npp", + "units": "kgC m-2 day-1", + "descriptions": "Net primary production" + }, + { + "codes": 3007, + "names": "daily_nee", + "units": "kgC m-2 day-1", + "descriptions": "Net ecosystem exchange" + }, + { + "codes": 3008, + "names": "daily_nbp", + "units": "kgC m-2 day-1", + "descriptions": "Net biom production" + }, + { + "codes": 3009, + "names": "daily_gpp", + "units": "kgC m-2 day-1", + "descriptions": "Gross primary production" + }, + { + "codes": 3010, + "names": "daily_mr", + "units": "kgC m-2 day-1", + "descriptions": "Maintenance respiration" + }, + { + "codes": 3011, + "names": "daily_gr", + "units": "kgC m-2 day-1", + "descriptions": "Growth respiration" + }, + { + "codes": 3012, + "names": "daily_hr", + "units": "kgC m-2 day-1", + "descriptions": "Heterotroph respiration" + }, + { + "codes": 3013, + "names": "daily_sr", + "units": "kgC m-2 day-1", + "descriptions": "Soil respiration" + }, + { + "codes": 3014, + "names": "daily_tr", + "units": "kgC m-2 day-1", + "descriptions": "Total respiration" + }, + { + "codes": 3015, + "names": "daily_fire", + "units": "kgC m-2 day-1", + "descriptions": "Fire losses" + }, + { + "codes": 3016, + "names": "daily_litfallc", + "units": "kgC m-2 day-1", + "descriptions": "Total litterfall" + }, + { + "codes": 3017, + "names": "daily_litfallc_above", + "units": "kgC m-2 day-1", + "descriptions": "Total litterfall aboveground" + }, + { + "codes": 3018, + "names": "daily_litfallc_below", + "units": "kgC m-2 day-1", + "descriptions": "Total litterfall belowground" + }, + { + "codes": 3019, + "names": "daily_litdecomp", + "units": "kgC m-2 day-1", + "descriptions": "Total litter decomposition" + }, + { + "codes": 3020, + "names": "daily_litfire", + "units": "kgC m-2 day-1", + "descriptions": "Total litter fire mortality" + }, + { + "codes": 3021, + "names": "daily_litter", + "units": "kgC m-2", + "descriptions": "Total amount of litter" + }, + { + "codes": 3022, + "names": "cum_npp", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NPP" + }, + { + "codes": 3023, + "names": "cum_nep", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NEP" + }, + { + "codes": 3024, + "names": "cum_nee", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NEE" + }, + { + "codes": 3025, + "names": "cum_gpp", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of GPP" + }, + { + "codes": 3026, + "names": "cum_mr", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of MR" + }, + { + "codes": 3027, + "names": "cum_gr", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of GR" + }, + { + "codes": 3028, + "names": "cum_hr", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of HR" + }, + { + "codes": 3029, + "names": "cum_tr", + "units": "kgC m-2", + "descriptions": "Cumulative SUM of total ecosystem respiration" + }, + { + "codes": 3030, + "names": "cum_n2o", + "units": "kgN m-2", + "descriptions": "Cumulative annual SUM N2O flux" + }, + { + "codes": 3031, + "names": "cum_Closs_MGM", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of management C loss" + }, + { + "codes": 3032, + "names": "cum_Cplus_MGM", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of management C plus" + }, + { + "codes": 3033, + "names": "cum_Closs_THN_w", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of thinning woody C loss" + }, + { + "codes": 3034, + "names": "cum_Closs_THN_nw", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of thinning non-woody C loss" + }, + { + "codes": 3035, + "names": "cum_Closs_MOW", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of mowing C loss" + }, + { + "codes": 3036, + "names": "cum_Closs_HRV", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of harvesting C loss" + }, + { + "codes": 3037, + "names": "cum_yieldC_HRV", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of harvested yield" + }, + { + "codes": 3038, + "names": "cum_Closs_PLG", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of ploughing C loss" + }, + { + "codes": 3039, + "names": "cum_Closs_GRZ", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of grazing C loss" + }, + { + "codes": 3040, + "names": "cum_Cplus_GRZ", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of grazing C plus" + }, + { + "codes": 3041, + "names": "cum_Cplus_FRZ", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of fertilizing C plus" + }, + { + "codes": 3042, + "names": "cum_Cplus_PLT", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of planting C change" + }, + { + "codes": 3043, + "names": "cum_Nplus_GRZ", + "units": "kgN m-2", + "descriptions": "Cumulative annual SUM of grazing N plus" + }, + { + "codes": 3044, + "names": "cum_Nplus_FRZ", + "units": "kgN m-2", + "descriptions": "Cumulative annual SUM of fertilizing N plus" + }, + { + "codes": 3045, + "names": "cum_Closs_SNSC", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of senescence C loss" + }, + { + "codes": 3046, + "names": "cum_Cplus_STDB", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of standing dead biome C plus" + }, + { + "codes": 3047, + "names": "cum_Cplus_CTDB", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of cut-down dead biome C plus" + }, + { + "codes": 3048, + "names": "cum_evap", + "units": "kgH2O m-2", + "descriptions": "Cumulative SUM of evaporation" + }, + { + "codes": 3049, + "names": "cum_transp", + "units": "kgH2O m-2", + "descriptions": "Cumulative SUM of transpiration" + }, + { + "codes": 3050, + "names": "cum_ET", + "units": "kgH2O m-2", + "descriptions": "Cumulative SUM of evapotranspiration" + }, + { + "codes": 3051, + "names": "leaf_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of leaves" + }, + { + "codes": 3052, + "names": "leaflitr_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of leaf litter" + }, + { + "codes": 3053, + "names": "froot_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of fine roots" + }, + { + "codes": 3054, + "names": "fruit_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of fruits" + }, + { + "codes": 3055, + "names": "softstem_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of softstems" + }, + { + "codes": 3056, + "names": "livewood_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of live wood" + }, + { + "codes": 3057, + "names": "deadwood_DM", + "units": "kgDM m-2", + "descriptions": "Dry matter C content of dead wood" + }, + { + "codes": 3058, + "names": "vegC", + "units": "kgC m-2", + "descriptions": "Total vegetation C content" + }, + { + "codes": 3059, + "names": "litrN_total", + "units": "kgN m-2", + "descriptions": "Total litter N content" + }, + { + "codes": 3060, + "names": "litrC_total", + "units": "kgC m-2", + "descriptions": "Total litter C content" + }, + { + "codes": 3061, + "names": "soilC_total", + "units": "kgC m-2", + "descriptions": "Total soil C content" + }, + { + "codes": 3062, + "names": "soilN_total", + "units": "kgN m-2", + "descriptions": "Total soil N content" + }, + { + "codes": 3063, + "names": "sminN_total", + "units": "kgN m-2", + "descriptions": "Total soil mineralized N content" + }, + { + "codes": 3064, + "names": "totalC", + "units": "kgC m-2", + "descriptions": "Total C content" + }, + { + "codes": 3065, + "names": "stableSOC_top30", + "units": "%", + "descriptions": "C content of stable SOM in soil top 0-30 cm" + }, + { + "codes": 3066, + "names": "SOC_top30", + "units": "%", + "descriptions": "Soil organic matter C content in soil top 0-30 cm" + }, + { + "codes": 3067, + "names": "SOM_N_top30", + "units": "%", + "descriptions": "Soil organic matter N content in soil top 0-30 cm" + }, + { + "codes": 3068, + "names": "NH4_top30avail", + "units": "ppm", + "descriptions": "Available soil NH4-content in soil top 0-30 cm" + }, + { + "codes": 3069, + "names": "NO3_top30avail", + "units": "ppm", + "descriptions": "Available soil NO3-content in soil top 0-30 cm" + }, + { + "codes": 3070, + "names": "SOC_30to60", + "units": "%", + "descriptions": "Soil organic matter C content in 30-60 cm" + }, + { + "codes": 3071, + "names": "SOC_60to90", + "units": "%", + "descriptions": "Soil organic matter C content in 60-90 cm" + }, + { + "codes": 3072, + "names": "litrCwdC_total", + "units": "kgN m-2", + "descriptions": "Total Litter and cwdc carbon content" + }, + { + "codes": 3073, + "names": "litrCwdN_total", + "units": "kgC m-2", + "descriptions": "Total litter and cwdc nitrogen content" + }, + { + "codes": 3074, + "names": "sminNavail_top30", + "units": "ppm", + "descriptions": "Available mineralized N in soil top 0-30 cm" + }, + { + "codes": 3075, + "names": "leafc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead leaf C content" + }, + { + "codes": 3076, + "names": "frootc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead fine root C content" + }, + { + "codes": 3077, + "names": "fruitc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead fruit C content" + }, + { + "codes": 3078, + "names": "softstemc_LandD", + "units": "kgC m-2", + "descriptions": "Live and dead sofstem C content" + }, + { + "codes": 3079, + "names": "sminNH4_ppm[0]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 1 (0-3 cm)" + }, + { + "codes": 3080, + "names": "sminNH4_ppm[1]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 2 (3-10 cm)" + }, + { + "codes": 3081, + "names": "sminNH4_ppm[2]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 3 (10-30 cm)" + }, + { + "codes": 3082, + "names": "sminNH4_ppm[3]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 4 (30-60 cm)" + }, + { + "codes": 3083, + "names": "sminNH4_ppm[4]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 5 (60-90 cm)" + }, + { + "codes": 3084, + "names": "sminNH4_ppm[5]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 6 (90-120 cm)" + }, + { + "codes": 3085, + "names": "sminNH4_ppm[6]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 7 (120-150 cm)" + }, + { + "codes": 3086, + "names": "sminNH4_ppm[7]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 8 (150-200 cm)" + }, + { + "codes": 3087, + "names": "sminNH4_ppm[8]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 9 (200-400 cm)" + }, + { + "codes": 3088, + "names": "sminNH4_ppm[9]", + "units": "ppm", + "descriptions": "Soil NH4 content in ppm of soil layer 10 (400-1000 cm)" + }, + { + "codes": 3089, + "names": "sminNO3_ppm[0]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 1 (0-3 cm)" + }, + { + "codes": 3090, + "names": "sminNO3_ppm[1]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 2 (3-10 cm)" + }, + { + "codes": 3091, + "names": "sminNO3_ppm[2]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 3 (10-30 cm)" + }, + { + "codes": 3092, + "names": "sminNO3_ppm[3]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 4 (30-60 cm)" + }, + { + "codes": 3093, + "names": "sminNO3_ppm[4]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 5 (60-90 cm)" + }, + { + "codes": 3094, + "names": "sminNO3_ppm[5]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 6 (90-120 cm)" + }, + { + "codes": 3095, + "names": "sminNO3_ppm[6]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 7 (120-150 cm)" + }, + { + "codes": 3096, + "names": "sminNO3_ppm[7]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 8 (150-200 cm)" + }, + { + "codes": 3097, + "names": "sminNO3_ppm[8]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 9 (200-400 cm)" + }, + { + "codes": 3098, + "names": "sminNO3_ppm[9]", + "units": "ppm", + "descriptions": "Soil NO3 content in ppm of soil layer 10 (400-1000 cm)" + }, + { + "codes": 3099, + "names": "CH4_flux_TOTAL", + "units": "kgC m-2 day-1", + "descriptions": "Estimated total CH4 flux of ecosystem" + }, + { + "codes": 3100, + "names": "daily_ngb", + "units": "kgC m-2 m-2", + "descriptions": "Net greenhouse gas balance" + }, + { + "codes": 3101, + "names": "cum_ngb", + "units": "kgC m-2", + "descriptions": "Cumulative annual SUM of NGB" + }, + { + "codes": 3102, + "names": "lateral_Cflux", + "units": "kgC m-2 day-1", + "descriptions": "Lateral carbon flux" + }, + { + "codes": 3103, + "names": "harvest_index", + "units": "dimless", + "descriptions": "Harvest index" + }, + { + "codes": 3104, + "names": "sminNavail_total", + "units": "kgN m-2", + "descriptions": "Total available soil mineralized N content" + }, + { + "codes": 3105, + "names": "cum_NleachRZ", + "units": "kgN m-2", + "descriptions": "Cumulated SUM of N leaching from rootzone" + }, + { + "codes": 3106, + "names": "cum_sr", + "units": "kgC m-2", + "descriptions": "Cumulated SUM of soil respiration" + }, + { + "codes": 3107, + "names": "CNlitr_total", + "units": "ppm", + "descriptions": "C:N ratio of litter pool" + }, + { + "codes": 3108, + "names": "CNsoil_total", + "units": "ppm", + "descriptions": "C:N ratio of soil pool" + }, + { + "codes": 3109, + "names": "litr1HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of labile litter in soil" + }, + { + "codes": 3110, + "names": "litr2HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of unshielded cellulose soil" + }, + { + "codes": 3111, + "names": "litr4HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil" + }, + { + "codes": 3112, + "names": "soil1HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil" + }, + { + "codes": 3113, + "names": "soil2HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil" + }, + { + "codes": 3114, + "names": "soil3HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil" + }, + { + "codes": 3115, + "names": "soil4HR_total", + "units": "kgC m-2", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil" + }, + { + "codes": 3116, + "names": "grainDM_HRV", + "units": "kgDM m-2", + "descriptions": "dry matter carbon content of grain at harvest - annual variable" + }, + { + "codes": 3157, + "names": "LDaboveC_nw", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound non-woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3158, + "names": "LDaboveC_w", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3159, + "names": "LDaboveCnsc_nw", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3160, + "names": "LDaboveCnsc_w", + "units": "kgC m-2", + "descriptions": "Living+dead abovegound woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3161, + "names": "LaboveC_nw", + "units": "kgC m-2", + "descriptions": "Living abovegound non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3162, + "names": "LaboveC_w", + "units": "kgC m-2", + "descriptions": "Living abovegound woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3163, + "names": "LaboveCnsc_nw", + "units": "kgC m-2", + "descriptions": "Living abovegound non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3164, + "names": "LaboveCnsc_w", + "units": "kgC m-2", + "descriptions": "Living abovegound woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3165, + "names": "DaboveC_nw", + "units": "kgC m-2", + "descriptions": "Dead abovegound non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3166, + "names": "DaboveC_w", + "units": "kgC m-2", + "descriptions": "Dead abovegound woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3167, + "names": "DaboveCnsc_nw", + "units": "kgC m-2", + "descriptions": "Dead abovegound non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3168, + "names": "DaboveCnsc_w", + "units": "kgC m-2", + "descriptions": "Dead abovegound woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3169, + "names": "sminN_maxRZ", + "units": "kgN m-2", + "descriptions": "Soil mineralized N content in maximal rooting zone" + }, + { + "codes": 3170, + "names": "soilC_maxRZ", + "units": "kgC m-2", + "descriptions": "Soil carbon content in maximal rooting zone" + }, + { + "codes": 3171, + "names": "soilN_maxRZ", + "units": "kgN m-2", + "descriptions": "Soil nitrogen content in maximal rooting zone" + }, + { + "codes": 3172, + "names": "litrC_maxRZ", + "units": "kgC m-2", + "descriptions": "Litter carbon content in maximal rooting zone" + }, + { + "codes": 3173, + "names": "litrN_maxRZ", + "units": "kgN m-2", + "descriptions": "Litter nitrogen content in maximal rooting zone" + }, + { + "codes": 3174, + "names": "sminNavail_maxRZ", + "units": "kgN m-2", + "descriptions": "Available soil mineralized N content in maximal rooting zone" + }, + { + "codes": 3175, + "names": "tally1", + "units": "kgC m-2", + "descriptions": "Tally of total soil C during successive met cycles (metcyle=1) for comparison" + }, + { + "codes": 3176, + "names": "tally2", + "units": "kgC m-2", + "descriptions": "Tally of total soil C during successive met cycles (metcyle=2) for comparison" + }, + { + "codes": 3177, + "names": "steady1", + "units": "flag", + "descriptions": "Marker for comparison of soilC change and spinup tolerance in metcyle=1" + }, + { + "codes": 3178, + "names": "steady2", + "units": "flag", + "descriptions": "Marker for comparison of soilC change and spinup tolerance in metcyle=2" + }, + { + "codes": 3179, + "names": "metcycle", + "units": "flag", + "descriptions": "Counter for metcyles (0,1 or 2)" + } +] diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/doc/index.html b/RBBGCMuso.Rcheck/RBBGCMuso/doc/index.html new file mode 100644 index 0000000..9c81e1a --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/doc/index.html @@ -0,0 +1,29 @@ + + +R: Vignettes and other documentation + + + +
+

Vignettes and other documentation + +

+
+
+[Top] +
+

Vignettes from package 'RBBGCMuso'

+ +++++++ + + + + +
RBBGCMuso::my-vignetteVignette TitleHTMLsourceR code
+
diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.R b/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.R new file mode 100644 index 0000000..0497c85 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.R @@ -0,0 +1,7 @@ +## ---- fig.show='hold'--------------------------------------------------------- +plot(1:10) +plot(10:1) + +## ---- echo=FALSE, results='asis'---------------------------------------------- +knitr::kable(head(mtcars, 10)) + diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.Rmd b/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.Rmd new file mode 100644 index 0000000..aace6af --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.Rmd @@ -0,0 +1,58 @@ +--- +title: "Vignette Title" +author: "Vignette Author" +date: "`r Sys.Date()`" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{Vignette Title} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + +Vignettes are long form documentation commonly included in packages. Because they are part of the distribution of the package, they need to be as compact as possible. The `html_vignette` output type provides a custom style sheet (and tweaks some options) to ensure that the resulting html is as small as possible. The `html_vignette` format: + +- Never uses retina figures +- Has a smaller default figure size +- Uses a custom CSS stylesheet instead of the default Twitter Bootstrap style + +## Vignette Info + +Note the various macros within the `vignette` section of the metadata block above. These are required in order to instruct R how to build the vignette. Note that you should change the `title` field and the `\VignetteIndexEntry` to match the title of your vignette. + +## Styles + +The `html_vignette` template includes a basic CSS theme. To override this theme you can specify your own CSS in the document metadata as follows: + + output: + rmarkdown::html_vignette: + css: mystyles.css + +## Figures + +The figure sizes have been customised so that you can easily put two images side-by-side. + +```{r, fig.show='hold'} +plot(1:10) +plot(10:1) +``` + +You can enable figure captions by `fig_caption: yes` in YAML: + + output: + rmarkdown::html_vignette: + fig_caption: yes + +Then you can use the chunk option `fig.cap = "Your figure caption."` in **knitr**. + +## More Examples + +You can write math expressions, e.g. $Y = X\beta + \epsilon$, footnotes^[A footnote here.], and tables, e.g. using `knitr::kable()`. + +```{r, echo=FALSE, results='asis'} +knitr::kable(head(mtcars, 10)) +``` + +Also a quote using `>`: + +> "He who gives up [code] safety for [code] speed deserves neither." +([via](https://twitter.com/hadleywickham/status/504368538874703872)) diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.html b/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.html new file mode 100644 index 0000000..b0ff013 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/doc/my-vignette.html @@ -0,0 +1,600 @@ + + + + + + + + + + + + + + + + +Vignette Title + + + + + + + + + + + + + + + + + + + + + + + + + + +

Vignette Title

+

Vignette Author

+

2023-02-06

+ + + +

Vignettes are long form documentation commonly included in packages. +Because they are part of the distribution of the package, they need to +be as compact as possible. The html_vignette output type +provides a custom style sheet (and tweaks some options) to ensure that +the resulting html is as small as possible. The +html_vignette format:

+
    +
  • Never uses retina figures
  • +
  • Has a smaller default figure size
  • +
  • Uses a custom CSS stylesheet instead of the default Twitter +Bootstrap style
  • +
+
+

Vignette Info

+

Note the various macros within the vignette section of +the metadata block above. These are required in order to instruct R how +to build the vignette. Note that you should change the +title field and the \VignetteIndexEntry to +match the title of your vignette.

+
+
+

Styles

+

The html_vignette template includes a basic CSS theme. +To override this theme you can specify your own CSS in the document +metadata as follows:

+
output: 
+  rmarkdown::html_vignette:
+    css: mystyles.css
+
+
+

Figures

+

The figure sizes have been customised so that you can easily put two +images side-by-side.

+
plot(1:10)
+plot(10:1)
+

+

You can enable figure captions by fig_caption: yes in +YAML:

+
output:
+  rmarkdown::html_vignette:
+    fig_caption: yes
+

Then you can use the chunk option +fig.cap = "Your figure caption." in +knitr.

+
+
+

More Examples

+

You can write math expressions, e.g. \(Y = +X\beta + \epsilon\), footnotes1, and tables, e.g. using +knitr::kable().

+ ++++++++++++++ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
mpgcyldisphpdratwtqsecvsamgearcarb
Mazda RX421.06160.01103.902.62016.460144
Mazda RX4 Wag21.06160.01103.902.87517.020144
Datsun 71022.84108.0933.852.32018.611141
Hornet 4 Drive21.46258.01103.083.21519.441031
Hornet Sportabout18.78360.01753.153.44017.020032
Valiant18.16225.01052.763.46020.221031
Duster 36014.38360.02453.213.57015.840034
Merc 240D24.44146.7623.693.19020.001042
Merc 23022.84140.8953.923.15022.901042
Merc 28019.26167.61233.923.44018.301044
+

Also a quote using >:

+
+

“He who gives up [code] safety for [code] speed deserves neither.” +(via)

+
+
+
+
+
    +
  1. A footnote here.↩︎

  2. +
+
+ + + + + + + + + + + diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/CO2.txt b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/CO2.txt new file mode 100644 index 0000000..b710046 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/CO2.txt @@ -0,0 +1,119 @@ + 1900 296.10 + 1901 296.10 + 1902 296.50 + 1903 296.80 + 1904 297.20 + 1905 297.60 + 1906 298.10 + 1907 298.50 + 1908 298.90 + 1909 299.30 + 1910 299.70 + 1911 300.10 + 1912 300.40 + 1913 300.80 + 1914 301.10 + 1915 301.40 + 1916 301.70 + 1917 302.10 + 1918 302.40 + 1919 302.70 + 1920 303.00 + 1921 303.40 + 1922 303.80 + 1923 304.10 + 1924 304.50 + 1925 305.00 + 1926 305.40 + 1927 305.80 + 1928 306.30 + 1929 306.80 + 1930 307.20 + 1931 307.70 + 1932 308.20 + 1933 308.60 + 1934 309.00 + 1935 309.40 + 1936 309.80 + 1937 310.00 + 1938 310.20 + 1939 310.30 + 1940 310.40 + 1941 310.40 + 1942 310.30 + 1943 310.20 + 1944 310.10 + 1945 310.10 + 1946 310.10 + 1947 310.20 + 1948 310.30 + 1949 310.50 + 1950 310.70 + 1951 311.10 + 1952 311.50 + 1953 311.90 + 1954 312.40 + 1955 313.00 + 1956 313.60 + 1957 314.20 + 1958 314.90 + 1959 315.79 + 1960 316.61 + 1961 317.33 + 1962 318.08 + 1963 318.70 + 1964 319.36 + 1965 320.02 + 1966 321.09 + 1967 321.99 + 1968 322.93 + 1969 324.21 + 1970 325.24 + 1971 326.06 + 1972 327.18 + 1973 328.84 + 1974 329.73 + 1975 330.73 + 1976 331.83 + 1977 333.25 + 1978 334.60 + 1979 336.85 + 1980 338.69 + 1981 339.93 + 1982 341.13 + 1983 342.78 + 1984 344.42 + 1985 345.90 + 1986 347.15 + 1987 348.93 + 1988 351.48 + 1989 352.91 + 1990 354.19 + 1991 355.59 + 1992 356.37 + 1993 357.04 + 1994 358.88 + 1995 360.88 + 1996 362.64 + 1997 363.76 + 1998 366.63 + 1999 368.31 + 2000 369.48 + 2001 372.59 + 2002 374.37 + 2003 378.04 + 2004 380.88 + 2005 383.88 + 2006 385.64 + 2007 385.76 + 2008 386.13 + 2009 387.37 + 2010 389.85 + 2011 391.62 + 2012 393.82 + 2013 396.48 + 2014 398.61 + 2015 400.00 + 2016 401.00 + 2017 402.00 + 2018 404.00 diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/HU-He2_2012_MEASURED.txt b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/HU-He2_2012_MEASURED.txt new file mode 100644 index 0000000..63696cb --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/HU-He2_2012_MEASURED.txt @@ -0,0 +1,367 @@ + yyyy mm dd NEE GPP TER LE flag + 2012 1 1 0.440 0.284 0.724 0.030 0 + 2012 1 2 0.540 0.486 1.026 0.222 0 + 2012 1 3 0.716 0.313 1.030 0.002 0 + 2012 1 4 0.627 0.468 1.095 0.055 0 + 2012 1 5 0.868 0.080 0.948 0.061 0 + 2012 1 6 0.077 0.751 0.828 0.372 0 + 2012 1 7 0.396 0.394 0.791 0.219 0 + 2012 1 8 0.110 0.767 0.877 0.125 0 + 2012 1 9 0.239 0.771 1.010 0.182 0 + 2012 1 10 0.207 0.732 0.938 0.271 0 + 2012 1 11 0.115 1.043 1.158 0.173 0 + 2012 1 12 0.509 0.443 0.952 0.351 0 + 2012 1 13 0.245 0.694 0.940 0.294 0 + 2012 1 14 0.509 0.521 1.030 0.192 0 + 2012 1 15 0.516 0.521 1.037 0.120 0 + 2012 1 16 0.142 0.630 0.772 0.195 0 + 2012 1 17 0.423 0.333 0.756 0.172 0 + 2012 1 18 0.277 0.586 0.863 0.256 0 + 2012 1 19 0.609 0.264 0.873 0.179 0 + 2012 1 20 0.853 0.191 1.043 0.028 0 + 2012 1 21 1.004 0.345 1.349 0.240 0 + 2012 1 22 0.658 0.828 1.486 0.313 0 + 2012 1 23 0.339 0.739 1.078 0.153 0 + 2012 1 24 0.281 0.752 1.032 0.045 0 + 2012 1 25 0.275 0.612 0.886 0.234 0 + 2012 1 26 0.098 0.614 0.712 0.189 0 + 2012 1 27 0.065 0.526 0.591 0.198 0 + 2012 1 28 0.270 0.307 0.577 0.101 0 + 2012 1 29 0.180 0.327 0.507 0.062 0 + 2012 1 30 0.916 0.371 1.287 0.086 0 + 2012 1 31 0.462 0.159 0.621 0.119 0 + 2012 2 1 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 2 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 3 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 4 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 5 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 6 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 7 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 8 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 9 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 10 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 11 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 12 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 13 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 14 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 15 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 16 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 17 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 18 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 19 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 2 20 0.263 0.396 0.660 0.255 0 + 2012 2 21 0.517 0.294 0.811 0.450 0 + 2012 2 22 0.497 0.381 0.878 0.340 0 + 2012 2 23 0.593 0.362 0.955 0.254 0 + 2012 2 24 0.361 0.510 0.872 0.491 0 + 2012 2 25 1.043 0.667 1.710 0.435 0 + 2012 2 26 0.471 0.545 1.016 0.287 0 + 2012 2 27 0.208 0.616 0.825 0.416 0 + 2012 2 28 0.421 0.399 0.820 0.092 0 + 2012 2 29 1.095 0.905 2.000 0.336 0 + 2012 3 1 0.458 1.085 1.542 0.146 0 + 2012 3 2 1.019 1.193 2.212 0.515 0 + 2012 3 3 0.848 1.016 1.865 0.681 0 + 2012 3 4 0.043 1.019 1.063 0.478 0 + 2012 3 5 0.326 0.870 1.196 0.502 0 + 2012 3 6 0.478 0.837 1.315 0.495 0 + 2012 3 7 0.206 0.470 0.675 0.332 0 + 2012 3 8 0.117 0.888 1.005 0.400 0 + 2012 3 9 -0.025 1.098 1.074 0.476 0 + 2012 3 10 0.449 1.011 1.460 0.587 0 + 2012 3 11 1.073 0.594 1.667 0.219 0 + 2012 3 12 1.044 0.590 1.634 0.047 0 + 2012 3 13 0.517 1.387 1.904 0.408 0 + 2012 3 14 0.166 1.769 1.935 0.505 0 + 2012 3 15 0.412 1.703 2.115 0.599 0 + 2012 3 16 0.244 1.535 1.779 0.483 0 + 2012 3 17 0.908 1.756 2.664 0.687 0 + 2012 3 18 0.885 1.659 2.544 0.539 0 + 2012 3 19 -0.386 2.395 2.009 0.502 0 + 2012 3 20 -0.606 2.823 2.217 0.859 0 + 2012 3 21 0.268 2.692 2.960 0.995 0 + 2012 3 22 -0.066 2.926 2.861 0.886 0 + 2012 3 23 0.009 3.536 3.545 0.854 0 + 2012 3 24 0.148 3.509 3.658 0.906 0 + 2012 3 25 -0.373 4.010 3.638 1.150 0 + 2012 3 26 -0.715 3.039 2.325 0.854 0 + 2012 3 27 -1.472 4.040 2.568 1.404 0 + 2012 3 28 -1.693 4.342 2.649 1.060 0 + 2012 3 29 0.028 3.126 3.155 0.736 0 + 2012 3 30 0.353 2.246 2.598 0.348 0 + 2012 3 31 -1.879 5.469 3.589 1.439 0 + 2012 4 1 -2.075 3.925 1.849 0.868 0 + 2012 4 2 -1.823 3.726 1.903 0.912 0 + 2012 4 3 -1.644 4.712 3.068 1.198 0 + 2012 4 4 -1.513 5.074 3.562 1.154 0 + 2012 4 5 -1.560 5.514 3.954 1.246 0 + 2012 4 6 1.817 1.514 3.331 0.048 0 + 2012 4 7 2.102 1.280 3.382 1.149 0 + 2012 4 8 -1.261 4.121 2.861 1.043 0 + 2012 4 9 -0.849 3.436 2.586 1.254 0 + 2012 4 10 -1.403 4.031 2.628 1.119 0 + 2012 4 11 -2.714 5.045 2.331 0.973 0 + 2012 4 12 -0.814 3.435 2.621 0.371 0 + 2012 4 13 -1.430 5.563 4.133 1.196 0 + 2012 4 14 0.886 3.198 4.085 0.124 0 + 2012 4 15 -1.468 5.235 3.767 0.354 0 + 2012 4 16 -0.391 3.663 3.272 0.408 0 + 2012 4 17 -2.404 5.576 3.172 0.967 0 + 2012 4 18 -2.231 5.599 3.368 0.857 0 + 2012 4 19 -4.172 7.629 3.457 1.407 0 + 2012 4 20 -3.302 7.423 4.121 1.344 0 + 2012 4 21 -2.392 6.356 3.965 0.839 0 + 2012 4 22 -1.016 4.731 3.715 0.532 0 + 2012 4 23 -3.809 7.395 3.586 0.974 0 + 2012 4 24 -2.960 6.773 3.813 0.612 0 + 2012 4 25 -4.338 8.789 4.451 2.042 0 + 2012 4 26 -5.087 10.121 5.034 2.478 0 + 2012 4 27 -4.817 8.607 3.790 2.461 0 + 2012 4 28 -4.396 8.659 4.263 2.372 0 + 2012 4 29 -6.780 10.393 3.613 2.607 0 + 2012 4 30 -6.309 9.668 3.358 2.703 0 + 2012 5 1 -3.619 8.815 5.196 2.805 0 + 2012 5 2 -4.568 10.142 5.574 2.899 0 + 2012 5 3 -3.377 7.731 4.355 1.086 0 + 2012 5 4 -0.910 5.555 4.645 0.711 0 + 2012 5 5 -5.536 11.269 5.733 2.516 0 + 2012 5 6 -6.022 11.611 5.589 2.154 0 + 2012 5 7 -1.552 6.454 4.903 0.780 0 + 2012 5 8 -4.539 11.023 6.485 2.654 0 + 2012 5 9 -6.838 12.291 5.453 2.248 0 + 2012 5 10 -6.109 13.095 6.986 2.653 0 + 2012 5 11 -6.404 13.728 7.324 2.453 0 + 2012 5 12 -3.041 11.038 7.998 1.494 0 + 2012 5 13 -2.685 8.466 5.781 1.701 0 + 2012 5 14 -1.911 7.159 5.247 0.614 0 + 2012 5 15 -4.420 10.143 5.723 1.881 0 + 2012 5 16 -2.677 7.455 4.778 0.899 0 + 2012 5 17 -4.086 8.456 4.370 1.535 0 + 2012 5 18 -2.892 8.133 5.241 1.827 0 + 2012 5 19 -3.103 9.789 6.686 2.036 0 + 2012 5 20 -3.446 10.774 7.328 1.722 0 + 2012 5 21 -1.290 8.958 7.668 0.755 0 + 2012 5 22 2.787 3.587 6.373 1.697 0 + 2012 5 23 -0.447 9.872 9.425 1.763 0 + 2012 5 24 0.187 10.434 10.622 2.221 0 + 2012 5 25 -1.949 10.115 8.166 2.603 0 + 2012 5 26 0.660 5.055 5.715 1.618 0 + 2012 5 27 2.652 3.893 6.545 1.588 0 + 2012 5 28 1.376 4.117 5.492 0.978 0 + 2012 5 29 1.416 4.619 6.035 1.400 0 + 2012 5 30 2.294 4.686 6.981 1.480 0 + 2012 5 31 4.244 2.414 6.659 1.549 0 + 2012 6 1 5.654 1.717 7.371 1.859 0 + 2012 6 2 -0.535 6.426 5.891 0.618 0 + 2012 6 3 -2.344 10.030 7.686 2.302 0 + 2012 6 4 1.526 5.390 6.916 1.171 0 + 2012 6 5 3.911 2.762 6.673 1.908 0 + 2012 6 6 -2.767 7.480 4.713 1.747 0 + 2012 6 7 -0.002 5.994 5.993 2.189 0 + 2012 6 8 -1.293 8.200 6.907 2.516 0 + 2012 6 9 2.902 3.437 6.339 0.607 0 + 2012 6 10 1.859 5.307 7.167 1.120 0 + 2012 6 11 2.909 4.120 7.030 0.814 0 + 2012 6 12 1.635 7.776 9.411 0.162 0 + 2012 6 13 3.300 9.112 12.413 1.079 0 + 2012 6 14 -0.500 13.424 12.924 2.230 0 + 2012 6 15 -0.555 13.719 13.164 2.650 0 + 2012 6 16 -2.240 15.315 13.075 2.788 0 + 2012 6 17 -3.710 15.421 11.711 3.815 0 + 2012 6 18 -1.316 13.615 12.299 3.467 0 + 2012 6 19 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 6 20 0.835 9.146 9.981 2.682 0 + 2012 6 21 -3.757 11.764 8.007 2.801 0 + 2012 6 22 -3.178 9.991 6.813 1.756 0 + 2012 6 23 -2.973 11.667 8.695 2.479 0 + 2012 6 24 -1.681 8.276 6.595 2.378 0 + 2012 6 25 1.698 4.862 6.559 0.469 0 + 2012 6 26 -0.333 8.257 7.924 2.947 0 + 2012 6 27 -1.240 9.078 7.839 2.568 0 + 2012 6 28 -2.438 8.591 6.153 2.323 0 + 2012 6 29 -0.041 6.786 6.745 2.320 0 + 2012 6 30 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 1 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 2 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 3 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 4 -1.694 7.565 5.871 2.055 0 + 2012 7 5 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 6 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 7 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 8 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 7 9 0.081 8.633 8.714 1.883 0 + 2012 7 10 5.480 4.571 10.050 2.978 0 + 2012 7 11 3.540 6.345 9.885 2.251 0 + 2012 7 12 3.573 6.518 10.092 2.055 0 + 2012 7 13 0.738 6.337 7.074 0.663 0 + 2012 7 14 2.392 5.352 7.744 1.730 0 + 2012 7 15 2.621 3.246 5.867 0.517 0 + 2012 7 16 0.002 5.766 5.768 2.395 0 + 2012 7 17 2.181 4.233 6.414 2.290 0 + 2012 7 18 0.333 5.522 5.855 2.121 0 + 2012 7 19 2.896 4.745 7.641 1.881 0 + 2012 7 20 -4.409 12.188 7.779 2.913 0 + 2012 7 21 2.161 4.473 6.635 0.085 0 + 2012 7 22 -1.966 9.473 7.507 1.158 0 + 2012 7 23 -3.943 12.987 9.044 2.395 0 + 2012 7 24 -1.126 11.111 9.984 1.840 0 + 2012 7 25 0.630 9.271 9.901 1.197 0 + 2012 7 26 0.641 10.025 10.666 2.289 0 + 2012 7 27 -3.677 14.036 10.359 3.401 0 + 2012 7 28 4.881 6.944 11.825 2.951 0 + 2012 7 29 -0.567 10.221 9.654 2.393 0 + 2012 7 30 -5.159 13.376 8.217 2.932 0 + 2012 7 31 -1.854 11.970 10.116 2.514 0 + 2012 8 1 -2.916 12.214 9.298 3.764 0 + 2012 8 2 0.390 8.301 8.691 2.852 0 + 2012 8 3 -3.120 12.612 9.492 2.479 0 + 2012 8 4 -0.243 9.906 9.662 3.369 0 + 2012 8 5 0.921 7.809 8.730 2.621 0 + 2012 8 6 1.958 7.150 9.108 2.832 0 + 2012 8 7 -3.802 12.456 8.654 2.834 0 + 2012 8 8 -3.271 10.859 7.588 1.917 0 + 2012 8 9 -2.539 10.918 8.379 1.708 0 + 2012 8 10 -4.573 13.220 8.647 2.166 0 + 2012 8 11 -1.417 7.881 6.464 0.969 0 + 2012 8 12 -5.064 11.249 6.185 2.064 0 + 2012 8 13 -3.401 10.948 7.547 1.999 0 + 2012 8 14 -4.735 11.421 6.685 2.658 0 + 2012 8 15 -1.630 9.253 7.623 2.609 0 + 2012 8 16 -0.523 9.221 8.698 2.449 0 + 2012 8 17 1.732 5.620 7.352 1.526 0 + 2012 8 18 1.792 5.627 7.419 1.600 0 + 2012 8 19 1.106 5.309 6.415 1.804 0 + 2012 8 20 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 8 21 -1.427 6.966 5.539 1.564 0 + 2012 8 22 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 8 23 1.842 3.369 5.211 1.107 0 + 2012 8 24 -9999.000 -9999.000 -9999.000 -9999.000 1 + 2012 8 25 0.752 4.044 4.796 1.564 0 + 2012 8 26 3.442 2.638 6.080 0.522 0 + 2012 8 27 4.227 2.070 6.297 1.209 0 + 2012 8 28 2.774 2.543 5.317 0.935 0 + 2012 8 29 0.889 6.332 7.221 1.144 0 + 2012 8 30 1.106 5.600 6.705 0.831 0 + 2012 8 31 1.499 4.726 6.225 0.397 0 + 2012 9 1 5.480 0.607 6.087 0.086 0 + 2012 9 2 4.770 3.085 7.854 1.212 0 + 2012 9 3 1.925 4.683 6.608 1.032 0 + 2012 9 4 1.147 4.621 5.768 0.847 0 + 2012 9 5 0.741 4.361 5.102 1.092 0 + 2012 9 6 0.236 3.269 3.505 0.792 0 + 2012 9 7 0.763 2.721 3.484 0.940 0 + 2012 9 8 1.173 3.364 4.537 1.023 0 + 2012 9 9 0.653 4.112 4.765 1.027 0 + 2012 9 10 0.912 4.461 5.373 0.874 0 + 2012 9 11 1.132 4.765 5.898 0.767 0 + 2012 9 12 1.016 5.574 6.589 0.666 0 + 2012 9 13 4.085 0.392 4.477 0.011 0 + 2012 9 14 3.004 2.271 5.276 0.517 0 + 2012 9 15 2.511 3.204 5.715 0.893 0 + 2012 9 16 1.539 4.356 5.896 0.949 0 + 2012 9 17 1.364 4.156 5.520 1.255 0 + 2012 9 18 2.299 4.659 6.957 0.954 0 + 2012 9 19 0.491 5.345 5.836 0.542 0 + 2012 9 20 1.374 4.325 5.699 1.097 0 + 2012 9 21 0.522 3.115 3.637 0.972 0 + 2012 9 22 0.051 3.473 3.524 1.001 0 + 2012 9 23 -0.100 2.702 2.602 0.878 0 + 2012 9 24 0.966 2.419 3.385 0.719 0 + 2012 9 25 1.793 2.237 4.030 1.720 0 + 2012 9 26 1.756 2.586 4.342 1.772 0 + 2012 9 27 0.954 3.168 4.122 0.882 0 + 2012 9 28 0.857 3.393 4.250 1.065 0 + 2012 9 29 1.165 3.372 4.537 0.451 0 + 2012 9 30 -0.759 5.569 4.811 0.830 0 + 2012 10 1 0.207 4.616 4.823 0.919 0 + 2012 10 2 2.516 1.735 4.251 0.041 0 + 2012 10 3 -1.047 4.089 3.042 0.614 0 + 2012 10 4 -1.631 4.975 3.343 0.784 0 + 2012 10 5 -1.277 4.647 3.369 0.901 0 + 2012 10 6 -1.711 5.633 3.922 0.899 0 + 2012 10 7 -1.559 5.570 4.011 0.717 0 + 2012 10 8 -2.029 5.085 3.056 0.904 0 + 2012 10 9 -1.604 5.274 3.671 0.692 0 + 2012 10 10 0.803 1.903 2.705 0.122 0 + 2012 10 11 -2.131 4.498 2.367 0.456 0 + 2012 10 12 0.644 2.323 2.966 0.063 0 + 2012 10 13 0.037 2.745 2.783 0.162 0 + 2012 10 14 -1.170 4.054 2.884 0.115 0 + 2012 10 15 -2.453 5.964 3.511 0.608 0 + 2012 10 16 0.666 1.569 2.235 0.361 0 + 2012 10 17 -2.423 5.213 2.790 0.140 0 + 2012 10 18 -2.999 7.236 4.237 0.575 0 + 2012 10 19 -2.974 6.842 3.869 0.509 0 + 2012 10 20 -0.961 6.009 5.047 0.313 0 + 2012 10 21 -1.929 6.137 4.208 0.308 0 + 2012 10 22 -1.843 7.383 5.540 0.478 0 + 2012 10 23 0.129 4.387 4.516 0.030 0 + 2012 10 24 1.710 3.265 4.975 0.073 0 + 2012 10 25 1.606 3.260 4.866 0.060 0 + 2012 10 26 0.887 2.925 3.811 0.051 0 + 2012 10 27 -1.423 4.769 3.346 0.060 0 + 2012 10 28 0.073 2.014 2.088 0.099 0 + 2012 10 29 0.697 0.838 1.535 0.002 0 + 2012 10 30 -0.362 1.947 1.585 0.214 0 + 2012 10 31 -0.675 2.402 1.727 0.288 0 + 2012 11 1 0.985 0.571 1.556 0.159 0 + 2012 11 2 0.282 1.449 1.731 0.123 0 + 2012 11 3 -1.547 3.771 2.224 0.479 0 + 2012 11 4 -1.364 4.402 3.038 0.569 0 + 2012 11 5 1.604 0.670 2.273 0.159 0 + 2012 11 6 0.679 2.410 3.089 0.170 0 + 2012 11 7 -0.727 2.904 2.176 0.374 0 + 2012 11 8 -0.928 3.313 2.385 0.377 0 + 2012 11 9 -0.790 2.533 1.743 0.293 0 + 2012 11 10 -0.660 2.691 2.031 0.184 0 + 2012 11 11 -0.739 2.588 1.850 0.136 0 + 2012 11 12 2.039 0.224 2.263 0.002 0 + 2012 11 13 1.237 2.104 3.341 0.052 0 + 2012 11 14 0.073 2.379 2.452 0.243 0 + 2012 11 15 -1.381 3.138 1.757 0.207 0 + 2012 11 16 0.103 1.772 1.875 0.067 0 + 2012 11 17 -0.843 2.621 1.778 0.094 0 + 2012 11 18 0.383 1.353 1.736 0.017 0 + 2012 11 19 1.891 0.365 2.256 0.007 0 + 2012 11 20 0.456 1.504 1.960 0.027 0 + 2012 11 21 0.973 1.028 2.002 0.011 0 + 2012 11 22 1.407 0.499 1.905 0.014 0 + 2012 11 23 0.676 1.122 1.798 0.011 0 + 2012 11 24 -0.320 2.203 1.883 0.023 0 + 2012 11 25 0.519 1.067 1.586 0.024 0 + 2012 11 26 0.191 1.449 1.640 0.067 0 + 2012 11 27 -0.142 2.655 2.512 0.536 0 + 2012 11 28 -0.100 2.787 2.686 0.361 0 + 2012 11 29 -0.291 2.827 2.536 0.099 0 + 2012 11 30 1.480 0.791 2.271 0.216 0 + 2012 12 1 -0.573 1.355 0.782 0.104 0 + 2012 12 2 1.006 0.284 1.290 0.009 0 + 2012 12 3 0.518 1.285 1.803 0.211 0 + 2012 12 4 0.150 1.210 1.360 0.035 0 + 2012 12 5 0.435 1.623 2.058 0.033 0 + 2012 12 6 0.319 0.842 1.161 0.022 0 + 2012 12 7 0.430 0.904 1.334 0.080 0 + 2012 12 8 1.286 0.000 1.286 0.012 0 + 2012 12 9 0.610 0.205 0.815 0.104 0 + 2012 12 10 0.676 0.293 0.969 0.087 0 + 2012 12 11 0.656 0.223 0.878 0.034 0 + 2012 12 12 0.418 0.242 0.660 0.101 0 + 2012 12 13 0.494 0.000 0.494 0.042 0 + 2012 12 14 0.662 0.316 0.978 0.005 0 + 2012 12 15 0.458 0.707 1.164 0.006 0 + 2012 12 16 0.185 0.889 1.073 0.005 0 + 2012 12 17 0.743 0.345 1.088 0.044 0 + 2012 12 18 0.764 0.111 0.875 0.009 0 + 2012 12 19 0.554 0.677 1.231 0.044 0 + 2012 12 20 0.308 0.775 1.083 0.028 0 + 2012 12 21 0.439 0.496 0.934 0.044 0 + 2012 12 22 0.141 0.800 0.941 0.005 0 + 2012 12 23 0.146 0.846 0.992 0.044 0 + 2012 12 24 -0.763 1.761 0.999 0.066 0 + 2012 12 25 0.390 1.345 1.735 0.131 0 + 2012 12 26 1.101 0.369 1.470 0.015 0 + 2012 12 27 -0.462 1.742 1.280 0.048 0 + 2012 12 28 0.525 0.520 1.045 0.044 0 + 2012 12 29 -0.086 0.827 0.740 0.060 0 + 2012 12 30 -0.044 0.648 0.604 0.056 0 + 2012 12 31 -0.040 0.731 0.692 0.092 0 diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/Ndep.txt b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/Ndep.txt new file mode 100644 index 0000000..fe6c63d --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/Ndep.txt @@ -0,0 +1,119 @@ +1900 0.0003911 +1901 0.0003922 +1902 0.0003952 +1903 0.0003982 +1904 0.0004012 +1905 0.0004043 +1906 0.0004073 +1907 0.0004103 +1908 0.0004133 +1909 0.0004164 +1910 0.0004224 +1911 0.0004267 +1912 0.0004310 +1913 0.0004353 +1914 0.0004396 +1915 0.0004439 +1916 0.0004482 +1917 0.0004525 +1918 0.0004568 +1919 0.0004611 +1920 0.0004697 +1921 0.0004741 +1922 0.0004786 +1923 0.0004830 +1924 0.0004875 +1925 0.0004919 +1926 0.0004964 +1927 0.0005008 +1928 0.0005053 +1929 0.0005097 +1930 0.0005186 +1931 0.0005214 +1932 0.0005243 +1933 0.0005271 +1934 0.0005299 +1935 0.0005327 +1936 0.0005356 +1937 0.0005384 +1938 0.0005412 +1939 0.0005440 +1940 0.0005497 +1941 0.0005600 +1942 0.0005703 +1943 0.0005806 +1944 0.0005909 +1945 0.0006013 +1946 0.0006116 +1947 0.0006219 +1948 0.0006322 +1949 0.0006425 +1950 0.0006632 +1951 0.0006775 +1952 0.0006919 +1953 0.0007063 +1954 0.0007207 +1955 0.0007350 +1956 0.0007494 +1957 0.0007638 +1958 0.0007782 +1959 0.0007925 +1960 0.0008213 +1961 0.0008407 +1962 0.0008601 +1963 0.0008795 +1964 0.0008989 +1965 0.0009183 +1966 0.0009378 +1967 0.0009572 +1968 0.0009766 +1969 0.0009960 +1970 0.0010348 +1971 0.0010591 +1972 0.0010465 +1973 0.0010524 +1974 0.0010582 +1975 0.0010641 +1976 0.0010699 +1977 0.0010758 +1978 0.0010816 +1979 0.0010875 +1980 0.0010933 +1981 0.0010992 +1982 0.0011050 +1983 0.0011109 +1984 0.0011167 +1985 0.0011226 +1986 0.0011284 +1987 0.0011343 +1988 0.0011401 +1989 0.0011460 +1990 0.0011519 +1991 0.0011577 +1992 0.0011636 +1993 0.0011694 +1994 0.0011753 +1995 0.0011811 +1996 0.0011870 +1997 0.0011928 +1998 0.0011987 +1999 0.0012045 +2000 0.0012104 +2001 0.0012239 +2002 0.0012347 +2003 0.0012654 +2004 0.0012762 +2005 0.0012870 +2006 0.0012977 +2007 0.0013085 +2008 0.0013192 +2009 0.0013200 +2010 0.0013407 +2011 0.0013515 +2012 0.0013722 +2013 0.0013830 +2014 0.0013938 +2015 0.0014010 +2016 0.0014020 +2017 0.0014040 +2018 0.0014050 diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/c3grass_muso6.epc b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/c3grass_muso6.epc new file mode 100644 index 0000000..7ca48f3 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/c3grass_muso6.epc @@ -0,0 +1,139 @@ +ECOPHYS FILE - C3 grass muso6 +---------------------------------------------------------------------------------------- +FLAGS +0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY) +0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS) +1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN) +---------------------------------------------------------------------------------------- +PLANT FUNCTIONING PARAMETERS +0 (yday) yearday to start new growth (when phenology flag = 0) +364 (yday) yearday to end litterfall (when phenology flag = 0) +0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0) +0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0) +0 (Celsius) base temperature +-9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +1.0 (1/yr) annual leaf and fine root turnover fraction +0.00 (1/yr) annual live wood turnover fraction +0.03 (1/yr) annual fire mortality fraction +0.01 (1/vegper) whole-plant mortality fraction in vegetation period +36.6 (kgC/kgN) C:N of leaves +45.0 (kgC/kgN) C:N of leaf litter, after retranslocation +50.0 (kgC/kgN) C:N of fine roots +36.6 *(kgC/kgN) C:N of fruit +36.6 (kgC/kgN) C:N of soft stem +0.0 *(kgC/kgN) C:N of live wood +0.0 *(kgC/kgN) C:N of dead wood +0.4 (kgC/kgDM) dry matter carbon content of leaves +0.4 (kgC/kgDM) dry matter carbon content of leaf litter +0.4 (kgC/kgDM) dry matter carbon content of fine roots +0.4 *(kgC/kgDM) dry matter carbon content of fruit +0.4 (kgC/kgDM) dry matter carbon content of soft stem +0.4 *(kgC/kgDM) dry matter carbon content of live wood +0.4 *(kgC/kgDM) dry matter carbon content of dead wood +0.68 (DIM) leaf litter labile proportion +0.23 (DIM) leaf litter cellulose proportion +0.34 (DIM) fine root labile proportion +0.44 (DIM) fine root cellulose proportion +0.68 *(DIM) fruit litter labile proportion +0.23 *(DIM) fruit litter cellulose proportion +0.68 (DIM) soft stem litter labile proportion +0.23 (DIM) soft stem litter cellulose proportion +0.00 *(DIM) dead wood cellulose proportion +0.01 (1/LAI/d) canopy water interception coefficient +0.63 (DIM) canopy light extinction coefficient +2.0 (g/MJ) potential radiation use efficiency +0.781 (DIM) radiation parameter1 (Jiang et al.2015) +-13.596 (DIM) radiation parameter2 (Jiang et al.2015) +2.0 (DIM) all-sided to projected leaf area ratio +2.0 (DIM) ratio of shaded SLA:sunlit SLA +0.14 (DIM) fraction of leaf N in Rubisco +0.03 (DIM) fraction of leaf N in PEP Carboxylase +0.004 (m/s) maximum stomatal conductance (projected area basis) +0.00006 (m/s) cuticular conductance (projected area basis) +0.04 (m/s) boundary layer conductance (projected area basis) +1.5 (m) maximum height of plant +0.8 (kgC) stem weight corresponding to maximum height +0.5 (dimless) plant height function shape parameter (slope) +4.0 (m) maximum depth of rooting zone +3.67 (DIM) root distribution parameter +0.4 (kgC) root weight corresponding to max root depth +0.5 (dimless) root depth function shape parameter (slope) +1000 (m/kg) root weight to root length conversion factor +0.3 (prop.) growth resp per unit of C grown +0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N +0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates +0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration +0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N +0 (day) time delay for temperature in photosynthesis acclimation +---------------------------------------------------------------------------------------- +CROP SPECIFIC PARAMETERS +0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific) +0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific) +0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination +0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect) +20 (hour) critical photoslow daylength +0.005 (DIM) slope of relative photoslow development rate +0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect) +0 (Celsius) critical vernalization temperature 1 +5 (Celsius) critical vernalization temperature 2 +8 (Celsius) critical vernalization temperature 3 +15 (Celsius) critical vernalization temperature 4 +0.04 (DIM) slope of relative vernalization development rate +50 (n) required vernalization days (in vernalization development rate) +0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect) +35 (Celsius) critical flowering heat stress temperature 1 +40 (Celsius) critical flowering heat stress temperature 2 +0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter +---------------------------------------------------------------------------------------- +STRESS AND SENESCENCE PARAMETERS +0.98 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP) +0.7 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC) +0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value) +1000 (Pa) vapor pressure deficit: start of conductance reduction +4000 (Pa) vapor pressure deficit: complete conductance reduction +0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material +0.001 (prop.) maximum senescence mortality coefficient of belowground plant material +0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material +35 (Celsius) lower limit extreme high temperature effect on senescence mortality +40 (Celsius) upper limit extreme high temperature effect on senescence mortality +0.01 (prop.) turnover rate of wilted standing biomass to litter +0.047 (prop.) turnover rate of non-woody cut-down biomass to litter +0.01 (prop.) turnover rate of woody cut-down biomass to litter +17 (nday) drought tolerance parameter (critical value of DSWS) +0.3 (prop) soil water deficit effect on photosynthesis downregulation +---------------------------------------------------------------------------------------- +GROWING SEASON PARAMETERS +5 (kg/m2) crit. amount of snow limiting photosyn. +20 (Celsius) limit1 (under:full constrained) of HEATSUM index +60 (Celsius) limit2 (above:unconstrained) of HEATSUM index +0 (Celsius) limit1 (under:full constrained) of TMIN index +5 (Celsius) limit2 (above:unconstrained) of TMIN index +4000 (Pa) limit1 (above:full constrained) of VPD index +1000 (Pa) limit2 (under:unconstrained) of VPD index +0 (s) limit1 (under:full constrained) of DAYLENGTH index +0 (s) limit2 (above:unconstrained) of DAYLENGTH index +10 (day) moving average (to avoid the effects of extreme events) +0.10 (dimless) GSI limit1 (greater that limit -> start of vegper) +0.01 (dimless) GSI limit2 (less that limit -> end of vegper) +---------------------------------------------------------------------------------------- +PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases) +phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase +5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD) +0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION +0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION +0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION +0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION +0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION +49 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis) +0.37 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion +10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/compile_log_linux.txt b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/compile_log_linux.txt new file mode 100644 index 0000000..9b3fdc7 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/compile_log_linux.txt @@ -0,0 +1,6 @@ +System: Linux meteor30 4.19.0-6-amd64 #1 SMP Debian 4.19.67-2+deb10u2 (2019-11-11) x86_64 GNU/Linux +Compilation time: Mon 02 Dec 2019 02:03:10 PM CET +Compiler: gcc (Debian 8.3.0-6) 8.3.0 +Compiler flags: +Model version: 6.0.3 + diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mgm b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mgm new file mode 100644 index 0000000..c2ab5e8 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mgm @@ -0,0 +1,33 @@ +MANAGEMENT_INFORMATION MuSo6 +------------------------------------------------------------------------------------------------------------------- +PLANTING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +THINNING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +MOWING +1 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +hhs.mow +------------------------------------------------------------------------------------------------------------------- +GRAZING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +HARVESTING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +PLOUGHING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +FERTILIZING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +IRRIGATING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mow b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mow new file mode 100644 index 0000000..9144646 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mow @@ -0,0 +1,23 @@ +DATE afterLAI(m2/m2) transPART(%) +2006.08.09 1 90 +2007.06.18 1 90 +2008.05.30 1 90 +2008.08.18 1 90 +2009.06.08 1 90 +2009.08.07 1 90 +2010.06.12 1 90 +2010.09.26 1 90 +2011.06.01 1 90 +2011.08.21 1 90 +2012.05.24 1 90 +2012.08.17 1 90 +2013.06.16 1 90 +2013.09.29 1 90 +2014.06.09 1 90 +2015.06.13 1 90 +2015.09.30 1 90 +2016.06.22 1 90 +2016.08.14 1 90 +2017.06.18 1 90 +2018.06.03 1 90 +2018.07.30 1 90 diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mtc43 b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mtc43 new file mode 100644 index 0000000..1c71d0b --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.mtc43 @@ -0,0 +1,42344 @@ +Hegyhatsal, 1901-2016, input for BBGCMuSo6 +MTCLIM v4.3 OUTPUT FILE +year yday Tmax Tmin Tday prcp VPD srad daylen + (degC) (degC) (degC) (cm) (Pa) (Wm-2) (s) +1901 1 -1.28 -7.28 -2.93 0 138.46 175.61 30438 +1901 2 -4.34 -10.34 -5.99 0 112.36 177.35 30492 +1901 3 -2.56 -8.56 -4.21 0 126.96 177.62 30551 +1901 4 -0.5 -6.5 -2.15 0 145.9 177.66 30614 +1901 5 -0.25 -6.25 -1.9 0 148.35 178.12 30681 +1901 6 1.43 -4.57 -0.22 0 165.8 177.97 30752 +1901 7 1.23 -4.77 -0.42 0 163.64 178.59 30828 +1901 8 -0.27 -6.27 -1.92 0 148.15 180.65 30907 +1901 9 -3.52 -9.52 -5.17 0.13 118.89 148.54 30991 +1901 10 -1.86 -7.86 -3.51 0 133.14 184.05 31079 +1901 11 0.57 -5.43 -1.08 0.1 156.66 148.72 31171 +1901 12 1.39 -4.61 -0.26 0.03 165.37 148.88 31266 +1901 13 2.51 -3.49 0.86 0 177.93 184.73 31366 +1901 14 0.65 -5.35 -1 0 157.49 186.92 31469 +1901 15 0.71 -5.29 -0.94 0.89 158.12 151.64 31575 +1901 16 -3.05 -9.05 -4.7 1.16 122.79 157.18 31686 +1901 17 -5.78 -11.78 -7.43 0.62 101.63 160.86 31800 +1901 18 -0.57 -6.57 -2.22 0.13 145.22 161.06 31917 +1901 19 -3.52 -9.52 -5.17 0.05 118.89 163.39 32038 +1901 20 0.82 -5.18 -0.83 0 159.27 201.48 32161 +1901 21 -0.39 -6.39 -2.04 0 146.97 203.9 32289 +1901 22 -0.86 -6.86 -2.51 0 142.42 205.7 32419 +1901 23 -2.91 -8.91 -4.56 0 123.97 208.17 32552 +1901 24 -7.01 -13.01 -8.66 0 93.18 211.49 32688 +1901 25 -7.25 -13.25 -8.9 0 91.61 213.29 32827 +1901 26 -5.69 -11.69 -7.34 0 102.27 214.57 32969 +1901 27 -6.63 -12.63 -8.28 0 95.72 216.74 33114 +1901 28 -11.28 -17.28 -12.93 0 68.4 220.04 33261 +1901 29 -13.02 -19.02 -14.67 0 60.09 222.64 33411 +1901 30 -13.82 -19.82 -15.47 0 56.57 224.89 33564 +1901 31 -6.81 -12.81 -8.46 0 94.51 225.36 33718 +1901 32 0.2 -5.8 -1.45 0 152.86 224.34 33875 +1901 33 -2.69 -8.69 -4.34 0.01 125.84 182.31 34035 +1901 34 0.94 -5.06 -0.71 0.62 160.54 182.3 34196 +1901 35 -3.32 -9.32 -4.97 0 120.54 232.38 34360 +1901 36 -5.62 -11.62 -7.27 0 102.78 235.64 34526 +1901 37 -3.7 -9.7 -5.35 0.37 117.43 189.79 34694 +1901 38 -5.97 -11.97 -7.62 0 100.28 241.63 34863 +1901 39 -5.69 -11.69 -7.34 0 102.27 243.97 35035 +1901 40 -3.3 -9.3 -4.95 0.02 120.7 195.13 35208 +1901 41 -4.39 -10.39 -6.04 0 111.97 248.4 35383 +1901 42 -5.89 -11.89 -7.54 0.01 100.85 199.48 35560 +1901 43 -5.03 -11.03 -6.68 0 107.1 253.62 35738 +1901 44 -2.09 -8.09 -3.74 0 131.09 254.68 35918 +1901 45 -4.86 -10.86 -6.51 0 108.37 258.41 36099 +1901 46 -4.6 -10.6 -6.25 0 110.35 260.83 36282 +1901 47 -3.64 -9.64 -5.29 0 117.92 263.05 36466 +1901 48 -0.3 -6.3 -1.95 0 147.86 263.93 36652 +1901 49 1.47 -4.53 -0.18 1.24 166.24 209.42 36838 +1901 50 3.44 -2.56 1.79 0.02 188.98 209.78 37026 +1901 51 6 0 4.35 0 222.51 265.85 37215 +1901 52 5.04 -0.96 3.39 0.02 209.38 211.54 37405 +1901 53 4.67 -1.33 3.02 0.04 204.5 213.3 37596 +1901 54 5.46 -0.54 3.81 0 215.04 272.65 37788 +1901 55 5.63 -0.37 3.98 0 217.37 274.7 37981 +1901 56 2.85 -3.15 1.2 0 181.9 279.3 38175 +1901 57 -0.37 -6.37 -2.02 0.26 147.17 223.1 38370 +1901 58 0.8 -5.2 -0.85 0 159.06 286.89 38565 +1901 59 -5.47 -11.47 -7.12 0.05 103.86 229.15 38761 +1901 60 7.62 1.62 5.97 1.5 246.26 223.09 38958 +1901 61 9.72 3.72 8.07 0.02 280.28 222.21 39156 +1901 62 5.31 -0.69 3.66 0 213 291.62 39355 +1901 63 5.46 -0.54 3.81 0.16 215.04 228.7 39553 +1901 64 7.53 1.53 5.88 0.08 244.89 195.7 39753 +1901 65 6.32 0.32 4.67 0 227.04 265.15 39953 +1901 66 7.67 1.67 6.02 0 247.03 266.38 40154 +1901 67 5.89 -0.11 4.24 0 220.97 271.26 40355 +1901 68 5.33 -0.67 3.68 0.96 213.27 206.05 40556 +1901 69 9.09 3.09 7.44 0 269.68 272.99 40758 +1901 70 9.36 3.36 7.71 0 274.18 275.46 40960 +1901 71 10.93 4.93 9.28 0 301.65 276.12 41163 +1901 72 10.65 4.65 9 0.05 296.59 209.5 41366 +1901 73 7.07 1.07 5.42 1 237.97 215.05 41569 +1901 74 8.9 2.9 7.25 0.31 266.55 215.38 41772 +1901 75 7.99 1.99 6.34 0 251.99 291.08 41976 +1901 76 2.87 -3.13 1.22 0 182.14 299.33 42179 +1901 77 5.22 -0.78 3.57 0.61 211.79 224.71 42383 +1901 78 5.76 -0.24 4.11 0.15 219.16 226.28 42587 +1901 79 7.18 1.18 5.53 0.01 239.61 227.07 42791 +1901 80 6.6 0.6 4.95 0.24 231.07 229.51 42996 +1901 81 6.8 0.8 5.15 0.21 233.98 231.28 43200 +1901 82 7.29 1.29 5.64 0.33 241.26 232.82 43404 +1901 83 8.5 2.5 6.85 0.04 260.06 233.48 43608 +1901 84 5.69 -0.31 4.04 1.54 218.19 238.08 43812 +1901 85 5.72 -0.28 4.07 0 218.61 319.94 44016 +1901 86 3.88 -2.12 2.23 0.43 194.41 243.32 44220 +1901 87 4.82 -1.18 3.17 0.38 206.47 244.48 44424 +1901 88 3.89 -2.11 2.24 0 194.54 329.38 44627 +1901 89 7.86 1.86 6.21 0.04 249.96 245.14 44831 +1901 90 6.24 0.24 4.59 0 225.9 331.37 45034 +1901 91 14.78 8.78 13.13 0.11 379.19 239.58 45237 +1901 92 14.59 8.59 12.94 0.02 375 241.53 45439 +1901 93 11.68 5.68 10.03 0.1 315.59 247.43 45642 +1901 94 12.65 6.65 11 0.01 334.42 247.69 45843 +1901 95 13.04 7.04 11.39 0.34 342.26 248.72 46045 +1901 96 10.45 4.45 8.8 0 293.01 338.44 46246 +1901 97 14.6 8.6 12.95 0 375.22 332.51 46446 +1901 98 13.7 7.7 12.05 0.22 355.89 252.27 46647 +1901 99 10.61 4.61 8.96 0 295.87 344.21 46846 +1901 100 12.31 6.31 10.66 0 327.71 343.06 47045 +1901 101 13.43 7.43 11.78 0 350.26 342.75 47243 +1901 102 15.52 9.52 13.87 0 395.89 340.02 47441 +1901 103 12.69 6.69 11.04 0.29 335.22 260.98 47638 +1901 104 12.21 6.21 10.56 0.04 325.76 263.05 47834 +1901 105 11.46 5.46 9.81 1.09 311.44 265.47 48030 +1901 106 12.1 6.1 10.45 0.34 323.63 265.79 48225 +1901 107 16.52 10.52 14.87 0 419.46 346.19 48419 +1901 108 15.18 9.18 13.53 0 388.14 351.18 48612 +1901 109 18.4 12.4 16.75 0.44 467.02 258.29 48804 +1901 110 19.42 13.42 17.77 0 494.69 342.74 48995 +1901 111 17.6 11.6 15.95 0 446.25 349.51 49185 +1901 112 17.67 11.67 16.02 0 448.04 350.8 49374 +1901 113 14.7 8.7 13.05 0.47 377.42 269.75 49561 +1901 114 11.01 5.01 9.36 0 303.11 368.87 49748 +1901 115 13.23 7.23 11.58 0 346.14 365.86 49933 +1901 116 10.86 4.86 9.21 0 300.38 371.82 50117 +1901 117 7.64 1.64 5.99 0 246.57 378.59 50300 +1901 118 13.04 7.04 11.39 0.51 342.26 277.59 50481 +1901 119 10.35 4.35 8.7 0 291.24 376.63 50661 +1901 120 5.66 -0.34 4.01 0.23 217.78 288.91 50840 +1901 121 9.06 3.06 7.41 0.55 269.18 285.92 51016 +1901 122 12.78 6.78 11.13 0.61 337.02 281.54 51191 +1901 123 12.28 6.28 10.63 0.53 327.13 283.1 51365 +1901 124 12.67 6.67 11.02 0 334.82 377.75 51536 +1901 125 13.41 7.41 11.76 0 349.85 377.14 51706 +1901 126 15.37 9.37 13.72 0.07 392.46 280.13 51874 +1901 127 14.6 8.6 12.95 0 375.22 376.29 52039 +1901 128 18.66 12.66 17.01 0 473.94 366.29 52203 +1901 129 16.2 10.2 14.55 0 411.79 374.11 52365 +1901 130 16.71 10.71 15.06 0 424.07 373.53 52524 +1901 131 15.25 9.25 13.6 0 389.73 378.14 52681 +1901 132 18.64 12.64 16.99 0 473.41 369.55 52836 +1901 133 16.91 10.91 15.26 0 428.97 375.29 52989 +1901 134 20.91 14.91 19.26 0.05 537.61 272.63 53138 +1901 135 22.61 16.61 20.96 0 590.41 357.95 53286 +1901 136 22.81 16.81 21.16 0.04 596.9 268.34 53430 +1901 137 21.6 15.6 19.95 0.07 558.54 272.27 53572 +1901 138 17.92 11.92 16.27 0 454.46 375.73 53711 +1901 139 17.35 11.35 15.7 0 439.92 378.07 53848 +1901 140 17.28 11.28 15.63 0.11 438.16 284.07 53981 +1901 141 17.55 11.55 15.9 0 444.98 378.41 54111 +1901 142 16.93 10.93 15.28 0 429.47 380.68 54238 +1901 143 18.4 12.4 16.75 0.67 467.02 282.68 54362 +1901 144 20.19 14.19 18.54 0.09 516.49 278.71 54483 +1901 145 23.85 17.85 22.2 0 631.63 358.29 54600 +1901 146 20.92 14.92 19.27 0.58 537.91 277.44 54714 +1901 147 22.38 16.38 20.73 1.43 583.02 273.75 54824 +1901 148 22.29 16.29 20.64 0.59 580.15 274.28 54931 +1901 149 19.18 13.18 17.53 0.78 488.06 282.71 55034 +1901 150 19.6 13.6 17.95 0.04 499.72 281.93 55134 +1901 151 17.82 11.82 16.17 0.02 451.88 286.4 55229 +1901 152 19.94 13.94 18.29 0.65 509.33 281.45 55321 +1901 153 16.41 10.41 14.76 0 416.81 386.25 55409 +1901 154 18.16 12.16 16.51 0 460.7 381.52 55492 +1901 155 21.58 15.58 19.93 0 557.92 370.23 55572 +1901 156 22 16 20.35 0 570.98 368.98 55648 +1901 157 25.86 19.86 24.21 0.02 703.64 264.64 55719 +1901 158 25.42 19.42 23.77 0.21 687.31 266.29 55786 +1901 159 27.27 21.27 25.62 0.01 758.19 259.79 55849 +1901 160 27.06 21.06 25.41 0.36 749.85 260.71 55908 +1901 161 24.97 18.97 23.32 0.5 670.94 268.17 55962 +1901 162 22.97 16.97 21.32 0.02 602.13 274.56 56011 +1901 163 26.21 20.21 24.56 0 716.86 352.09 56056 +1901 164 27.32 21.32 25.67 0.37 760.19 260 56097 +1901 165 26.4 20.4 24.75 0.17 724.13 263.48 56133 +1901 166 22.73 16.73 21.08 1.73 594.29 275.59 56165 +1901 167 21.16 15.16 19.51 0.03 545.11 280 56192 +1901 168 19.25 13.25 17.6 0.08 489.98 284.97 56214 +1901 169 20.35 14.35 18.7 0 521.12 376.29 56231 +1901 170 20.31 14.31 18.66 0.61 519.96 282.32 56244 +1901 171 21.77 15.77 20.12 0.86 563.79 278.43 56252 +1901 172 23.45 17.45 21.8 2.46 618.08 273.47 56256 +1901 173 20.31 14.31 18.66 0.62 519.96 282.35 56255 +1901 174 15.08 9.08 13.43 0.01 385.89 293.96 56249 +1901 175 13.24 7.24 11.59 0 346.35 396.35 56238 +1901 176 17.25 11.25 15.6 0 437.41 385.99 56223 +1901 177 23.25 17.25 21.6 0 611.39 365.19 56203 +1901 178 22.55 16.55 20.9 0 588.47 368.01 56179 +1901 179 21.05 15.05 19.4 0.01 541.8 280.15 56150 +1901 180 19.1 13.1 17.45 0.49 485.86 285.03 56116 +1901 181 20.86 14.86 19.21 0.87 536.12 280.51 56078 +1901 182 21.47 15.47 19.82 0.41 554.54 278.75 56035 +1901 183 22.53 16.53 20.88 0 587.83 367.48 55987 +1901 184 21.65 15.65 20 0 560.08 370.67 55935 +1901 185 25.43 19.43 23.78 0.02 687.68 266.24 55879 +1901 186 29.49 23.49 27.84 0.2 851.31 250.49 55818 +1901 187 28.05 22.05 26.4 0 789.88 341.69 55753 +1901 188 26.3 20.3 24.65 0.35 720.29 262.67 55684 +1901 189 27.46 21.46 25.81 0.07 765.81 258.25 55611 +1901 190 24.03 18.03 22.38 0.03 637.82 269.94 55533 +1901 191 21.22 15.22 19.57 0.01 546.93 277.99 55451 +1901 192 26.43 20.43 24.78 0.31 725.28 261.4 55366 +1901 193 24.25 18.25 22.6 0.35 645.44 268.63 55276 +1901 194 21.02 15.02 19.37 0.41 540.9 277.93 55182 +1901 195 19.92 13.92 18.27 0 508.76 374.1 55085 +1901 196 18.33 12.33 16.68 0.01 465.17 284.08 54984 +1901 197 20.98 14.98 19.33 0.09 539.7 277.19 54879 +1901 198 23.28 17.28 21.63 0.22 612.39 270.34 54770 +1901 199 24.75 18.75 23.1 0 663.06 353.94 54658 +1901 200 24.48 18.48 22.83 0 653.5 354.72 54542 +1901 201 24.67 18.67 23.02 0 660.22 353.45 54423 +1901 202 28.17 22.17 26.52 0.02 794.85 252.13 54301 +1901 203 27.7 21.7 26.05 0 775.52 338.14 54176 +1901 204 25.28 19.28 23.63 0 682.18 349.24 54047 +1901 205 22.19 16.19 20.54 0 576.97 361.45 53915 +1901 206 21.29 15.29 19.64 0 549.05 364.2 53780 +1901 207 23.56 17.56 21.91 0.54 621.78 266.17 53643 +1901 208 20.75 14.75 19.1 0 532.86 364.79 53502 +1901 209 19.15 13.15 17.5 0 487.23 369.43 53359 +1901 210 19.87 13.87 18.22 0.94 507.33 274.86 53213 +1901 211 20.42 14.42 18.77 0.02 523.16 272.91 53064 +1901 212 24.21 18.21 22.56 0.17 644.05 261.61 52913 +1901 213 21.53 15.53 19.88 0 556.38 358.46 52760 +1901 214 21.05 15.05 19.4 0.19 541.8 269.56 52604 +1901 215 20.77 14.77 19.12 0 533.45 359.71 52445 +1901 216 22.64 16.64 20.99 0.4 591.38 263.96 52285 +1901 217 24.74 18.74 23.09 0.81 662.71 256.96 52122 +1901 218 26.07 20.07 24.42 0 711.55 335.96 51958 +1901 219 27.76 21.76 26.11 0 777.97 326.88 51791 +1901 220 28.08 22.08 26.43 0 791.12 324.4 51622 +1901 221 25.37 19.37 23.72 0 685.47 336.24 51451 +1901 222 21.67 15.67 20.02 0.19 560.7 262.4 51279 +1901 223 20.64 14.64 18.99 0 529.61 352.29 51105 +1901 224 21.39 15.39 19.74 0.61 552.1 261.51 50929 +1901 225 22.56 16.56 20.91 0.17 588.79 257.5 50751 +1901 226 20.54 14.54 18.89 0 526.67 349.29 50572 +1901 227 19.67 13.67 18.02 0 501.68 350.82 50392 +1901 228 21.07 15.07 19.42 0.03 542.4 258.78 50210 +1901 229 23.25 17.25 21.6 1.07 611.39 251.98 50026 +1901 230 25.35 19.35 23.7 0.38 684.74 244.7 49842 +1901 231 22.81 16.81 21.16 0.05 596.9 251.22 49656 +1901 232 20.34 14.34 18.69 0.62 520.83 256.62 49469 +1901 233 23.11 17.11 21.46 0 606.75 331.14 49280 +1901 234 23.02 17.02 21.37 0.76 603.78 247.57 49091 +1901 235 18.99 12.99 17.34 0.29 482.86 256.5 48900 +1901 236 19.76 13.76 18.11 0 504.22 338.25 48709 +1901 237 19.7 13.7 18.05 0 502.53 336.8 48516 +1901 238 19.21 13.21 17.56 0 488.88 336.6 48323 +1901 239 20.61 14.61 18.96 0.16 528.72 248.1 48128 +1901 240 20.7 14.7 19.05 0 531.38 328.78 47933 +1901 241 20.61 14.61 18.96 0 528.72 327.36 47737 +1901 242 22.55 16.55 20.9 0 588.47 319.19 47541 +1901 243 22.65 16.65 21 0.06 591.7 237.77 47343 +1901 244 14.51 8.51 12.86 0.02 373.25 253.56 47145 +1901 245 13.49 7.49 11.84 0 351.51 338.35 46947 +1901 246 15.61 9.61 13.96 0 397.97 331.72 46747 +1901 247 18.16 12.16 16.51 1.51 460.7 242.62 46547 +1901 248 17.46 11.46 15.81 0.28 442.7 242.53 46347 +1901 249 15.68 9.68 14.03 2.56 399.59 244.21 46146 +1901 250 15.34 9.34 13.69 1.98 391.77 243.31 45945 +1901 251 15.81 9.81 14.16 0.64 402.61 240.9 45743 +1901 252 15.99 9.99 14.34 0.78 406.83 238.96 45541 +1901 253 16.4 10.4 14.75 0.43 416.57 236.64 45339 +1901 254 17.49 11.49 15.84 1.11 443.46 233.06 45136 +1901 255 21.55 15.55 19.9 0.39 557 222.88 44933 +1901 256 20.83 14.83 19.18 0.01 535.23 222.87 44730 +1901 257 21.48 15.48 19.83 0 554.85 293.09 44527 +1901 258 25.43 19.43 23.78 0 687.68 277.31 44323 +1901 259 30.62 24.62 28.97 0 902.3 252.38 44119 +1901 260 21.4 15.4 19.75 0.09 552.4 214.8 43915 +1901 261 21.25 15.25 19.6 1.05 547.84 213.36 43711 +1901 262 18.13 12.13 16.48 0.02 459.92 217.96 43507 +1901 263 17.87 11.87 16.22 0 453.17 288.8 43303 +1901 264 18.57 12.57 16.92 0.55 471.54 213.41 43099 +1901 265 15.6 9.6 13.95 0.02 397.74 216.74 42894 +1901 266 16.96 10.96 15.31 0 430.2 283.57 42690 +1901 267 16.74 10.74 15.09 0 424.8 281.4 42486 +1901 268 15.63 9.63 13.98 0 398.43 281.2 42282 +1901 269 14.33 8.33 12.68 0 369.33 281.23 42078 +1901 270 15.09 9.09 13.44 0 386.11 277.13 41875 +1901 271 13.33 7.33 11.68 0 348.2 277.76 41671 +1901 272 17.87 11.87 16.22 0.03 453.17 199.47 41468 +1901 273 18.1 12.1 16.45 0.09 459.14 197.21 41265 +1901 274 11.69 5.69 10.04 0.05 315.78 204.33 41062 +1901 275 13.28 7.28 11.63 0 347.17 267.07 40860 +1901 276 13.63 7.63 11.98 0 354.42 263.77 40658 +1901 277 15.91 9.91 14.26 0 404.95 256.94 40456 +1901 278 15.49 9.49 13.84 0.11 395.2 191.18 40255 +1901 279 16.77 10.77 15.12 0 425.54 249.63 40054 +1901 280 16.58 10.58 14.93 0 420.91 247.4 39854 +1901 281 17.4 11.4 15.75 0 441.18 243.08 39654 +1901 282 20.43 14.43 18.78 0 523.45 233.62 39455 +1901 283 16.87 10.87 15.22 0 427.99 238.7 39256 +1901 284 16.53 10.53 14.88 0.59 419.7 177.29 39058 +1901 285 17.7 11.7 16.05 0.82 448.8 173.63 38861 +1901 286 18.84 12.84 17.19 0 478.79 226.44 38664 +1901 287 16.61 10.61 14.96 0 421.64 228.06 38468 +1901 288 17.1 11.1 15.45 0 433.67 224.42 38273 +1901 289 16.38 10.38 14.73 0.09 416.09 167.39 38079 +1901 290 8.69 2.69 7.04 0.09 263.12 173.6 37885 +1901 291 9.54 3.54 7.89 1.03 277.21 170.82 37693 +1901 292 13.66 7.66 12.01 0 355.05 219.56 37501 +1901 293 10.06 4.06 8.41 0.42 286.15 166.26 37311 +1901 294 11.14 5.14 9.49 0.61 305.5 163.08 37121 +1901 295 12.42 6.42 10.77 0 329.87 212.93 36933 +1901 296 14.6 8.6 12.95 0 375.22 207.22 36745 +1901 297 15.08 9.08 13.43 0 385.89 203.8 36560 +1901 298 14.86 8.86 13.21 0 380.96 201.58 36375 +1901 299 13.77 7.77 12.12 0 357.36 200.45 36191 +1901 300 12.41 6.41 10.76 0 329.68 199.66 36009 +1901 301 12.69 6.69 11.04 0 335.22 196.8 35829 +1901 302 9.58 3.58 7.93 0 277.89 197.88 35650 +1901 303 10.75 4.75 9.1 0.13 298.39 145.51 35472 +1901 304 12.73 6.73 11.08 0 336.02 189.18 35296 +1901 305 8.48 2.48 6.83 0 259.74 191.2 35122 +1901 306 10.81 4.81 9.16 0 299.47 186.52 34950 +1901 307 8.67 2.67 7.02 0 262.8 186.24 34779 +1901 308 7.94 1.94 6.29 0.28 251.21 138.23 34610 +1901 309 6.12 0.12 4.47 0.15 224.2 137.66 34444 +1901 310 2.48 -3.52 0.83 1.21 177.58 137.75 34279 +1901 311 5.5 -0.5 3.85 0 215.58 179.36 34116 +1901 312 4.42 -1.58 2.77 0 201.26 177.48 33956 +1901 313 3.37 -2.63 1.72 0 188.13 176.05 33797 +1901 314 3.7 -2.3 2.05 0 192.17 173.84 33641 +1901 315 7.4 1.4 5.75 0 242.92 168.55 33488 +1901 316 11.5 5.5 9.85 0.15 312.19 121.89 33337 +1901 317 10.6 4.6 8.95 0 295.69 161.28 33188 +1901 318 5.79 -0.21 4.14 0 219.58 163.07 33042 +1901 319 13.77 7.77 12.12 0 357.36 153.87 32899 +1901 320 14.31 8.31 12.66 0.16 368.89 113.56 32758 +1901 321 12.28 6.28 10.63 0 327.13 151.67 32620 +1901 322 12.58 6.58 10.93 0 333.03 149.56 32486 +1901 323 8.91 2.91 7.26 0 266.71 151.5 32354 +1901 324 5.25 -0.75 3.6 1.34 212.19 114.17 32225 +1901 325 1.49 -4.51 -0.16 0 166.46 152.72 32100 +1901 326 1.57 -4.43 -0.08 0 167.33 151.2 31977 +1901 327 -4.03 -10.03 -5.68 0 114.79 151.73 31858 +1901 328 -1.09 -7.09 -2.74 1.1 140.24 156.35 31743 +1901 329 0.78 -5.22 -0.87 0 158.85 191.19 31631 +1901 330 1.19 -4.81 -0.46 0 163.21 189.53 31522 +1901 331 0.26 -5.74 -1.39 0 153.47 188.75 31417 +1901 332 7.33 1.33 5.68 0 241.86 182.19 31316 +1901 333 3.83 -2.17 2.18 0.07 193.79 148.24 31218 +1901 334 1.63 -4.37 -0.02 0.21 167.99 148.21 31125 +1901 335 1.53 -4.47 -0.12 0 166.89 181.78 31035 +1901 336 3.14 -2.86 1.49 0 185.35 179.59 30949 +1901 337 3.93 -2.07 2.28 0.07 195.04 143.59 30867 +1901 338 5.65 -0.35 4 0.04 217.64 99.02 30790 +1901 339 4.13 -1.87 2.48 0 197.56 132.14 30716 +1901 340 6.29 0.29 4.64 0 226.61 130.1 30647 +1901 341 5.55 -0.45 3.9 0 216.27 129.65 30582 +1901 342 8.8 2.8 7.15 0.02 264.91 95.01 30521 +1901 343 8.87 2.87 7.22 0 266.06 125.81 30465 +1901 344 12.15 6.15 10.5 0.08 324.6 91.46 30413 +1901 345 8.8 2.8 7.15 0.86 264.91 93.24 30366 +1901 346 7.66 1.66 6.01 0 246.88 124.6 30323 +1901 347 7.1 1.1 5.45 0.01 238.41 93.29 30284 +1901 348 6.97 0.97 5.32 0.11 236.48 93.1 30251 +1901 349 6.84 0.84 5.19 0 234.57 123.84 30221 +1901 350 5.01 -0.99 3.36 0.52 208.98 93.47 30197 +1901 351 4.72 -1.28 3.07 0 205.16 124.58 30177 +1901 352 5.64 -0.36 3.99 0 217.5 123.95 30162 +1901 353 5.34 -0.66 3.69 0 213.41 124.06 30151 +1901 354 5.59 -0.41 3.94 0 216.82 123.88 30145 +1901 355 5.66 -0.34 4.01 0 217.78 123.84 30144 +1901 356 6.77 0.77 5.12 0.06 233.54 92.38 30147 +1901 357 2.12 -3.88 0.47 0.14 173.47 94.37 30156 +1901 358 2.51 -3.49 0.86 0.14 177.93 94.3 30169 +1901 359 5.08 -0.92 3.43 0.69 209.91 93.35 30186 +1901 360 4.82 -1.18 3.17 2.14 206.47 93.74 30208 +1901 361 3.25 -2.75 1.6 0.01 186.68 94.63 30235 +1901 362 3.49 -2.51 1.84 0 189.59 126.49 30267 +1901 363 4.68 -1.32 3.03 0 204.63 126.42 30303 +1901 364 5.8 -0.2 4.15 0 219.72 126.15 30343 +1901 365 2.12 -3.88 0.47 0 173.47 128.74 30388 +1902 1 0.23 -5.77 -1.42 0.97 153.17 97.87 30438 +1902 2 -0.88 -6.88 -2.53 0.28 142.23 142.94 30492 +1902 3 0.28 -5.72 -1.37 0.33 153.68 143.17 30551 +1902 4 1.61 -4.39 -0.04 1.01 167.77 143.1 30614 +1902 5 3.63 -2.37 1.98 0.19 191.31 142.24 30681 +1902 6 6.06 0.06 4.41 0 223.35 131.53 30752 +1902 7 6.04 0.04 4.39 0.37 223.07 99.25 30828 +1902 8 5.02 -0.98 3.37 0.31 209.11 100.84 30907 +1902 9 7.12 1.12 5.47 0.06 238.71 100.75 30991 +1902 10 2.64 -3.36 0.99 0.03 179.44 103.77 31079 +1902 11 2.12 -3.88 0.47 0 173.47 139.62 31171 +1902 12 4.33 -1.67 2.68 0 200.11 139.41 31266 +1902 13 3.46 -2.54 1.81 0 189.23 141.54 31366 +1902 14 5.14 -0.86 3.49 0 210.72 142 31469 +1902 15 6.59 0.59 4.94 0 230.92 142.47 31575 +1902 16 12.54 6.54 10.89 0 332.24 138.63 31686 +1902 17 8.6 2.6 6.95 0 261.67 143.88 31800 +1902 18 11.86 5.86 10.21 0.01 319.01 107.1 31917 +1902 19 12.19 6.19 10.54 0 325.37 144.35 32038 +1902 20 6.89 0.89 5.24 0 235.3 150.56 32161 +1902 21 6.68 0.68 5.03 0 232.23 152.71 32289 +1902 22 4.83 -1.17 3.18 0 206.6 155.74 32419 +1902 23 4.51 -1.49 2.86 0 202.42 157.72 32552 +1902 24 2.93 -3.07 1.28 0 182.85 160.77 32688 +1902 25 0.67 -5.33 -0.98 0 157.7 163.92 32827 +1902 26 4.88 -1.12 3.23 0.05 207.26 122.51 32969 +1902 27 5.6 -0.4 3.95 0 216.95 164.85 33114 +1902 28 7.91 1.91 6.26 0 250.74 165.23 33261 +1902 29 8.51 2.51 6.86 0 260.22 167.06 33411 +1902 30 7.79 1.79 6.14 0 248.88 169.9 33564 +1902 31 1.88 -4.12 0.23 0.08 170.77 132.37 33718 +1902 32 -3.16 -9.16 -4.81 2.66 121.87 182.37 33875 +1902 33 -3.37 -9.37 -5.02 1.59 120.12 188.7 34035 +1902 34 -4.19 -10.19 -5.84 2.1 113.53 196.29 34196 +1902 35 -0.81 -6.81 -2.46 0.01 142.9 196.54 34360 +1902 36 5.26 -0.74 3.61 0.51 212.33 194.68 34526 +1902 37 6.14 0.14 4.49 0.86 224.48 194.99 34694 +1902 38 3.89 -2.11 2.24 1.65 194.54 197.62 34863 +1902 39 0.75 -5.25 -0.9 0.18 158.54 200.77 35035 +1902 40 2.96 -3.04 1.31 0.9 183.21 201.09 35208 +1902 41 6.17 0.17 4.52 0 224.9 249.76 35383 +1902 42 6.18 0.18 4.53 0 225.05 251.34 35560 +1902 43 7.21 1.21 5.56 0.02 240.06 201.45 35738 +1902 44 3.66 -2.34 2.01 0 191.68 256.91 35918 +1902 45 0.91 -5.09 -0.74 0.13 160.22 207.98 36099 +1902 46 4.62 -1.38 2.97 0.18 203.85 207.26 36282 +1902 47 9.12 3.12 7.47 0.85 270.17 204.93 36466 +1902 48 0.93 -5.07 -0.72 0.23 160.43 211.92 36652 +1902 49 -1.84 -7.84 -3.49 0.05 133.32 215.15 36838 +1902 50 2.02 -3.98 0.37 0 172.34 271.32 37026 +1902 51 3.62 -2.38 1.97 0.17 191.19 215.65 37215 +1902 52 4.64 -1.36 2.99 0 204.11 273.76 37405 +1902 53 8.12 2.12 6.47 0.01 254.02 215.02 37596 +1902 54 8.27 2.27 6.62 0 256.39 273.73 37788 +1902 55 5.49 -0.51 3.84 0 215.45 278.72 37981 +1902 56 6.89 0.89 5.24 0 235.3 279.11 38175 +1902 57 6.54 0.54 4.89 0.12 230.2 220.98 38370 +1902 58 7.34 1.34 5.69 0 242.01 282.57 38565 +1902 59 9.73 3.73 8.08 0.25 280.45 220.3 38761 +1902 60 14.67 8.67 13.02 0 376.76 275.1 38958 +1902 61 13.39 7.39 11.74 0 349.43 278.51 39156 +1902 62 12.51 6.51 10.86 0 331.65 248.48 39355 +1902 63 11.02 5.02 9.37 0 303.3 253.62 39553 +1902 64 10.92 4.92 9.27 0.06 301.47 192.47 39753 +1902 65 7.75 1.75 6.1 0.15 248.26 197.67 39953 +1902 66 6.95 0.95 5.3 0 236.19 267.21 40154 +1902 67 8.67 2.67 7.02 0 262.8 268.06 40355 +1902 68 6.84 0.84 5.19 0 234.57 273.11 40556 +1902 69 5.99 -0.01 4.34 0 222.37 276.67 40758 +1902 70 5.43 -0.57 3.78 0 214.63 280.13 40960 +1902 71 5.86 -0.14 4.21 0 220.55 282.6 41163 +1902 72 5.59 -0.41 3.94 0.01 216.82 214.3 41366 +1902 73 6.2 0.2 4.55 0 225.33 287.74 41569 +1902 74 5.99 -0.01 4.34 0 222.37 290.74 41772 +1902 75 7.36 1.36 5.71 0.11 242.31 218.9 41976 +1902 76 5.21 -0.79 3.56 0.12 211.65 222.75 42179 +1902 77 5.93 -0.07 4.28 0.11 221.53 224.12 42383 +1902 78 9.76 3.76 8.11 0.07 280.97 222.41 42587 +1902 79 8.12 2.12 6.47 0.38 254.02 226.16 42791 +1902 80 5.87 -0.13 4.22 0 220.69 306.88 42996 +1902 81 5.77 -0.23 4.12 0.14 219.3 232.2 43200 +1902 82 5.18 -0.82 3.53 0.1 211.25 234.71 43404 +1902 83 5.77 -0.23 4.12 1.03 219.3 236.09 43608 +1902 84 4.08 -1.92 2.43 1.16 196.93 239.42 43812 +1902 85 4.38 -1.62 2.73 0 200.75 321.45 44016 +1902 86 8.73 2.73 7.08 0 263.77 318.44 44220 +1902 87 8.8 2.8 7.15 0 264.91 320.87 44424 +1902 88 6.24 0.24 4.59 0 225.9 326.68 44627 +1902 89 3.49 -2.51 1.84 0 189.59 332.12 44831 +1902 90 1.93 -4.07 0.28 0 171.33 336.08 45034 +1902 91 4.87 -1.13 3.22 0 207.13 335.31 45237 +1902 92 8.31 2.31 6.66 0 257.03 333.13 45439 +1902 93 12.29 6.29 10.64 0 327.32 328.8 45642 +1902 94 11.47 5.47 9.82 0 311.63 332.43 45843 +1902 95 13.75 7.75 12.1 0 356.94 330.2 46045 +1902 96 10.52 4.52 8.87 0.15 294.26 253.74 46246 +1902 97 8.81 2.81 7.16 0.77 265.08 257.35 46446 +1902 98 10.1 4.1 8.45 0.16 286.85 257.29 46647 +1902 99 6.75 0.75 5.1 0.09 233.25 262.59 46846 +1902 100 6.8 0.8 5.15 0.79 233.98 264.03 47045 +1902 101 12.52 6.52 10.87 0.13 331.84 258.43 47243 +1902 102 14.25 8.25 12.6 0.58 367.6 257.17 47441 +1902 103 14.62 8.62 12.97 0.13 375.66 257.92 47638 +1902 104 13.98 7.98 12.33 0.81 361.81 260.33 47834 +1902 105 15.07 9.07 13.42 0.71 385.66 259.83 48030 +1902 106 11.94 5.94 10.29 0.05 320.54 266.02 48225 +1902 107 13.88 7.88 12.23 0 359.69 352.4 48419 +1902 108 16.37 10.37 14.72 0.04 415.85 261.21 48612 +1902 109 15.26 9.26 13.61 0 389.95 352.58 48804 +1902 110 15.57 9.57 13.92 0.22 397.04 264.92 48995 +1902 111 17.38 11.38 15.73 0 440.68 350.11 49185 +1902 112 16.53 10.53 14.88 0 419.7 353.85 49374 +1902 113 12.77 6.77 11.12 0 336.82 363.9 49561 +1902 114 13 7 11.35 0 341.45 364.92 49748 +1902 115 15.67 9.67 14.02 0 399.35 360.23 49933 +1902 116 12.39 6.39 10.74 0 329.28 368.84 50117 +1902 117 12.66 6.66 11.01 0 334.62 369.6 50300 +1902 118 11.78 5.78 10.13 0.41 317.49 279.53 50481 +1902 119 12.69 6.69 11.04 0 335.22 372.06 50661 +1902 120 13.61 7.61 11.96 0.3 354.01 278.44 50840 +1902 121 11.83 5.83 10.18 1.19 318.44 282.1 51016 +1902 122 12.12 6.12 10.47 1.78 324.02 282.57 51191 +1902 123 13.92 7.92 12.27 0 360.53 373.91 51365 +1902 124 16.4 10.4 14.75 0.99 416.57 276.67 51536 +1902 125 11.98 5.98 10.33 0.26 321.31 285.13 51706 +1902 126 10.43 4.43 8.78 0 292.66 384.2 51874 +1902 127 11.83 5.83 10.18 0.29 318.44 286.79 52039 +1902 128 13.18 7.18 11.53 0.01 345.12 285.41 52203 +1902 129 16.11 10.11 14.46 0.13 409.66 280.76 52365 +1902 130 16.4 10.4 14.75 0.14 416.57 280.77 52524 +1902 131 15.37 9.37 13.72 1.07 392.46 283.38 52681 +1902 132 18.68 12.68 17.03 0.12 474.48 277.07 52836 +1902 133 16.18 10.18 14.53 0.03 411.32 282.95 52989 +1902 134 15.1 9.1 13.45 0.49 386.34 285.57 53138 +1902 135 14.2 8.2 12.55 0 366.52 383.65 53286 +1902 136 11.81 5.81 10.16 0 318.06 389.57 53430 +1902 137 13.45 7.45 11.8 0.05 350.68 290.06 53572 +1902 138 17.03 11.03 15.38 0.28 431.94 283.72 53711 +1902 139 15.42 9.42 13.77 0.55 393.6 287.48 53848 +1902 140 8.31 2.31 6.66 0.67 257.03 298.94 53981 +1902 141 11.52 5.52 9.87 1.56 312.57 294.86 54111 +1902 142 12.5 6.5 10.85 0.01 331.45 293.71 54238 +1902 143 12.58 6.58 10.93 0.75 333.03 293.99 54362 +1902 144 9.07 3.07 7.42 0 269.35 399.31 54483 +1902 145 10.27 4.27 8.62 0.11 289.83 298.22 54600 +1902 146 7 1 5.35 0.24 236.93 302.69 54714 +1902 147 13.38 7.38 11.73 0 349.23 392.04 54824 +1902 148 13.54 7.54 11.89 0 352.55 392.06 54931 +1902 149 18.77 12.77 17.12 0 476.9 378.24 55034 +1902 150 18.92 12.92 17.27 0.16 480.96 283.58 55134 +1902 151 16.3 10.3 14.65 0.6 414.18 289.65 55229 +1902 152 19.51 13.51 17.86 1.47 497.2 282.52 55321 +1902 153 17.66 11.66 16.01 0.38 447.78 287.02 55409 +1902 154 16.98 10.98 15.33 0.13 430.7 288.74 55492 +1902 155 14.35 8.35 12.7 0 369.76 392.09 55572 +1902 156 18.84 12.84 17.19 0.06 478.79 284.94 55648 +1902 157 19.66 13.66 18.01 0 501.4 377.44 55719 +1902 158 20.27 14.27 18.62 0.29 518.8 281.66 55786 +1902 159 21.51 15.51 19.86 0.78 555.77 278.53 55849 +1902 160 20.46 14.46 18.81 0.05 524.33 281.49 55908 +1902 161 21.15 15.15 19.5 2.09 544.81 279.7 55962 +1902 162 21.21 15.21 19.56 1.3 546.63 279.59 56011 +1902 163 17.85 11.85 16.2 0 452.65 384.08 56056 +1902 164 17.64 11.64 15.99 0 447.27 384.75 56097 +1902 165 24.53 18.53 22.88 0 655.26 359.9 56133 +1902 166 19.4 13.4 17.75 0.03 494.14 284.59 56165 +1902 167 19.63 13.63 17.98 0 500.56 378.64 56192 +1902 168 22.37 16.37 20.72 0.04 582.7 276.66 56214 +1902 169 17.31 11.31 15.66 0 438.92 385.93 56231 +1902 170 11.84 5.84 10.19 0.49 318.63 299.62 56244 +1902 171 15.43 9.43 13.78 0.64 393.83 293.37 56252 +1902 172 15.43 9.43 13.78 0.16 393.83 293.36 56256 +1902 173 20.87 14.87 19.22 0 536.42 374.5 56255 +1902 174 21.66 15.66 20.01 0.22 560.39 278.66 56249 +1902 175 18.18 12.18 16.53 0.2 461.23 287.45 56238 +1902 176 17.61 11.61 15.96 0.74 446.5 288.7 56223 +1902 177 22.85 16.85 21.2 0 598.2 366.79 56203 +1902 178 21.56 15.56 19.91 0 557.3 371.77 56179 +1902 179 24.67 18.67 23.02 0 660.22 359.11 56150 +1902 180 20.5 14.5 18.85 0 525.5 375.35 56116 +1902 181 18.16 12.16 16.51 2.16 460.7 287.18 56078 +1902 182 21.09 15.09 19.44 0.12 543 279.79 56035 +1902 183 18.38 12.38 16.73 0.68 466.49 286.43 55987 +1902 184 17.12 11.12 15.47 0.7 434.17 289.12 55935 +1902 185 17.7 11.7 16.05 1.72 448.8 287.79 55879 +1902 186 14.98 8.98 13.33 0 383.64 390.9 55818 +1902 187 19.12 13.12 17.47 0 486.41 378.89 55753 +1902 188 22.02 16.02 20.37 0 571.61 368.5 55684 +1902 189 19.18 13.18 17.53 0.32 488.06 283.69 55611 +1902 190 18.76 12.76 17.11 0.15 476.63 284.41 55533 +1902 191 21.35 15.35 19.7 0.22 550.88 277.63 55451 +1902 192 22.66 16.66 21.01 0.3 592.02 273.7 55366 +1902 193 23.95 17.95 22.3 0.07 635.06 269.58 55276 +1902 194 23.61 17.61 21.96 1.18 623.47 270.48 55182 +1902 195 25.99 19.99 24.34 1.86 708.52 262.43 55085 +1902 196 26.06 20.06 24.41 0.26 711.17 261.89 54984 +1902 197 22.47 16.47 20.82 0.05 585.9 273.05 54879 +1902 198 23.08 17.08 21.43 1.01 605.76 270.94 54770 +1902 199 22.29 16.29 20.64 0.24 580.15 272.99 54658 +1902 200 20.38 14.38 18.73 0.12 522 277.87 54542 +1902 201 21.85 15.85 20.2 0 566.28 364.79 54423 +1902 202 24.78 18.78 23.13 0.16 664.13 264.32 54301 +1902 203 26.37 20.37 24.72 0 722.97 344.69 54176 +1902 204 22.1 16.1 20.45 0.58 574.13 271.72 54047 +1902 205 19.36 13.36 17.71 0 493.03 371.31 53915 +1902 206 20.26 14.26 18.61 0 518.51 367.78 53780 +1902 207 23.89 17.89 22.24 0 633 353.54 53643 +1902 208 22.11 16.11 20.46 0 574.44 359.89 53502 +1902 209 21.32 15.32 19.67 0.3 549.96 271.6 53359 +1902 210 21.55 15.55 19.9 0 557 360.69 53213 +1902 211 23.9 17.9 22.25 0 633.35 350.86 53064 +1902 212 20.32 14.32 18.67 0.36 520.25 272.57 52913 +1902 213 18.49 12.49 16.84 0.28 469.41 276.37 52760 +1902 214 17.4 11.4 15.75 0 441.18 370.92 52604 +1902 215 14.56 8.56 12.91 0 374.34 377.62 52445 +1902 216 16.94 10.94 15.29 0 429.71 370.48 52285 +1902 217 20.01 14.01 18.36 0 511.32 360.36 52122 +1902 218 21.09 15.09 19.44 0 543 355.9 51958 +1902 219 22.92 16.92 21.27 0 600.49 348.18 51791 +1902 220 22.13 16.13 20.48 0 575.07 350.22 51622 +1902 221 20.53 14.53 18.88 0.08 526.38 266.13 51451 +1902 222 18.87 12.87 17.22 0 479.6 359.08 51279 +1902 223 22.12 16.12 20.47 0.03 574.76 260.34 51105 +1902 224 20.97 14.97 19.32 0 539.4 350.12 50929 +1902 225 25.06 19.06 23.41 0 674.19 333.38 50751 +1902 226 21.4 15.4 19.75 0 552.4 346.38 50572 +1902 227 25.88 19.88 24.23 0 704.39 327.5 50392 +1902 228 25.54 19.54 23.89 0 691.73 327.83 50210 +1902 229 25.32 19.32 23.67 0 683.64 327.6 50026 +1902 230 25.41 19.41 23.76 0 686.94 326.01 49842 +1902 231 24.31 18.31 22.66 0 647.54 329.16 49656 +1902 232 21.43 15.43 19.78 0 553.32 338.55 49469 +1902 233 24.28 18.28 22.63 0.02 646.49 244.96 49280 +1902 234 21.36 15.36 19.71 0.07 551.18 251.99 49091 +1902 235 27.53 21.53 25.88 1.05 768.63 232.28 48900 +1902 236 25.61 19.61 23.96 0.97 694.32 237.75 48709 +1902 237 21.76 15.76 20.11 0.05 563.48 247.6 48516 +1902 238 21.76 15.76 20.11 0.06 563.48 246.37 48323 +1902 239 21.37 15.37 19.72 0.12 551.49 246.25 48128 +1902 240 19.49 13.49 17.84 0.15 496.64 249.38 47933 +1902 241 21.35 15.35 19.7 0.08 550.88 243.73 47737 +1902 242 18.15 12.15 16.5 0 460.44 332.87 47541 +1902 243 20.8 14.8 19.15 0.03 534.34 242.41 47343 +1902 244 19.92 13.92 18.27 0 508.76 324.12 47145 +1902 245 21.6 15.6 19.95 1.19 558.54 237.77 46947 +1902 246 17.51 11.51 15.86 0 443.96 327.06 46747 +1902 247 18.11 12.11 16.46 0 459.4 323.62 46547 +1902 248 23.23 17.23 21.58 0 610.73 305.87 46347 +1902 249 21.79 15.79 20.14 0.47 564.42 231.58 46146 +1902 250 18.61 12.61 16.96 0.12 472.61 237.25 45945 +1902 251 19.54 13.54 17.89 0 498.04 311.66 45743 +1902 252 17.97 11.97 16.32 0.14 455.76 235.33 45541 +1902 253 19.28 13.28 17.63 0 490.81 308.16 45339 +1902 254 17.41 11.41 15.76 0.24 441.43 233.21 45136 +1902 255 17.07 11.07 15.42 0.21 432.93 232.14 44933 +1902 256 14.63 8.63 12.98 0 375.88 312.71 44730 +1902 257 17.65 11.65 16 0 447.52 303.68 44527 +1902 258 16.28 10.28 14.63 0 413.7 304.58 44323 +1902 259 14.45 8.45 12.8 0 371.94 306.06 44119 +1902 260 12.54 6.54 10.89 0 332.24 307.27 43915 +1902 261 17.42 11.42 15.77 0 441.69 294.68 43711 +1902 262 15.82 9.82 14.17 0.28 402.84 221.95 43507 +1902 263 16.71 10.71 15.06 0.11 424.07 218.63 43303 +1902 264 15.81 9.81 14.16 0 402.61 290.92 43099 +1902 265 16.93 10.93 15.28 0 429.47 286.1 42894 +1902 266 12.18 6.18 10.53 0 325.18 292.92 42690 +1902 267 15.38 9.38 13.73 0 392.69 284.28 42486 +1902 268 18.68 12.68 17.03 0 474.48 274.36 42282 +1902 269 18.76 12.76 17.11 0 476.63 271.7 42078 +1902 270 22.13 16.13 20.48 0 575.07 260.1 41875 +1902 271 23.04 17.04 21.39 0.78 604.44 191.16 41671 +1902 272 24.91 18.91 23.26 0.02 668.79 184.72 41468 +1902 273 23.35 17.35 21.7 0.15 614.73 186.72 41265 +1902 274 14.64 8.64 12.99 0 376.1 267.44 41062 +1902 275 18.69 12.69 17.04 0 474.75 256.27 40860 +1902 276 19.81 13.81 18.16 0.04 505.63 188.22 40658 +1902 277 17.6 11.6 15.95 0.16 446.25 190.11 40456 +1902 278 16.81 10.81 15.16 0.88 426.52 189.23 40255 +1902 279 16.96 10.96 15.31 0 430.2 249.24 40054 +1902 280 17.61 11.61 15.96 0.36 446.5 183.97 39854 +1902 281 13.71 7.71 12.06 0 356.1 249.92 39654 +1902 282 9.45 3.45 7.8 0.11 275.69 190.01 39455 +1902 283 9.83 3.83 8.18 0.02 282.17 187.5 39256 +1902 284 10.42 4.42 8.77 0.86 292.48 184.63 39058 +1902 285 13.95 7.95 12.3 0 361.17 238.34 38861 +1902 286 9.29 3.29 7.64 0.07 273.01 181.6 38664 +1902 287 9.56 3.56 7.91 0.14 277.55 179.13 38468 +1902 288 12.15 6.15 10.5 0.37 324.6 174.46 38273 +1902 289 11.88 5.88 10.23 0.26 319.39 172.77 38079 +1902 290 8.17 2.17 6.52 0.98 254.81 174.04 37885 +1902 291 12.58 6.58 10.93 0.72 333.03 167.86 37693 +1902 292 11.92 5.92 10.27 0.11 320.16 166.53 37501 +1902 293 9.92 3.92 8.27 0.07 283.72 166.38 37311 +1902 294 10.95 4.95 9.3 0.04 302.02 163.26 37121 +1902 295 12.95 6.95 11.3 0.3 340.44 159.15 36933 +1902 296 8.77 2.77 7.12 1.23 264.42 161.07 36745 +1902 297 8.29 2.29 6.64 0.08 256.71 159.39 36560 +1902 298 10.42 4.42 8.77 0 292.48 207.55 36375 +1902 299 12.54 6.54 10.89 2.35 332.24 151.6 36191 +1902 300 10.98 4.98 9.33 0.81 302.56 151.08 36009 +1902 301 11.45 5.45 9.8 0.31 311.26 148.77 35829 +1902 302 10.57 4.57 8.92 0 295.15 196.79 35650 +1902 303 14.85 8.85 13.2 0.8 380.74 141.53 35472 +1902 304 18.81 12.81 17.16 0 477.98 179.83 35296 +1902 305 7.55 1.55 5.9 0 245.19 192.07 35122 +1902 306 8.86 2.86 7.21 0 265.89 188.56 34950 +1902 307 10.02 4.02 8.37 0.46 285.45 138.66 34779 +1902 308 5.87 -0.13 4.22 0 220.69 186.08 34610 +1902 309 6.48 0.48 4.83 0 229.33 183.25 34444 +1902 310 6.11 0.11 4.46 0 224.06 181.09 34279 +1902 311 9.13 3.13 7.48 0 270.34 176.25 34116 +1902 312 7.31 1.31 5.66 0 241.56 175.25 33956 +1902 313 6.53 0.53 4.88 0 230.05 173.76 33797 +1902 314 3.5 -2.5 1.85 0 189.71 173.98 33641 +1902 315 4.32 -1.68 2.67 0 199.98 170.87 33488 +1902 316 5.08 -0.92 3.43 0 209.91 168.14 33337 +1902 317 3.81 -2.19 2.16 0.47 193.54 125.09 33188 +1902 318 2.92 -3.08 1.27 0 182.73 164.98 33042 +1902 319 -2.9 -8.9 -4.55 0 124.05 166.14 32899 +1902 320 -3.28 -9.28 -4.93 0 120.87 164.37 32758 +1902 321 1.42 -4.58 -0.23 0 165.69 160.07 32620 +1902 322 7.81 1.81 6.16 0 249.19 154.02 32486 +1902 323 8.54 2.54 6.89 0 260.7 151.82 32354 +1902 324 8.83 2.83 7.18 0 265.4 149.53 32225 +1902 325 8.57 2.57 6.92 0.01 261.19 111.03 32100 +1902 326 2.83 -3.17 1.18 0.19 181.67 112.89 31977 +1902 327 0.85 -5.15 -0.8 0 159.59 149.69 31858 +1902 328 -2.12 -8.12 -3.77 0 130.82 149.01 31743 +1902 329 -3.18 -9.18 -4.83 0 121.7 147.89 31631 +1902 330 -1.3 -7.3 -2.95 0 138.27 145.68 31522 +1902 331 1.11 -4.89 -0.54 0 162.35 143.26 31417 +1902 332 1.41 -4.59 -0.24 0 165.58 141.46 31316 +1902 333 1.23 -4.77 -0.42 0.27 163.64 105.33 31218 +1902 334 2.42 -3.58 0.77 0.2 176.89 104.05 31125 +1902 335 0.87 -5.13 -0.78 0.04 159.8 103.74 31035 +1902 336 -2.16 -8.16 -3.81 0 130.46 138.5 30949 +1902 337 -1.03 -7.03 -2.68 0 140.81 136.38 30867 +1902 338 1.03 -4.97 -0.62 0 161.49 134.53 30790 +1902 339 -1.57 -7.57 -3.22 0.06 135.78 144.28 30716 +1902 340 0.22 -5.78 -1.43 0 153.07 176.58 30647 +1902 341 -0.41 -6.41 -2.06 0 146.78 176.01 30582 +1902 342 1.29 -4.71 -0.36 0 164.28 131.17 30521 +1902 343 -1.77 -7.77 -3.42 0.09 133.96 142.33 30465 +1902 344 -5.11 -11.11 -6.76 0.16 106.5 142.89 30413 +1902 345 -1.25 -7.25 -2.9 0 138.74 174.1 30366 +1902 346 0.25 -5.75 -1.4 0 153.37 172.97 30323 +1902 347 3.67 -2.33 2.02 0 191.8 170.3 30284 +1902 348 2.01 -3.99 0.36 0 172.22 170.57 30251 +1902 349 -1.44 -7.44 -3.09 0.27 136.97 140.55 30221 +1902 350 -1.69 -7.69 -3.34 0 134.68 172.34 30197 +1902 351 1.43 -4.57 -0.22 0 165.8 170.68 30177 +1902 352 -2.23 -8.23 -3.88 0 129.85 172.08 30162 +1902 353 2.56 -3.44 0.91 0 178.51 169.67 30151 +1902 354 2.67 -3.33 1.02 0 179.79 125.48 30145 +1902 355 3.41 -2.59 1.76 0 188.62 125.1 30144 +1902 356 1.57 -4.43 -0.08 0 167.33 126.03 30147 +1902 357 0.02 -5.98 -1.63 0 151.05 126.77 30156 +1902 358 -1.64 -7.64 -3.29 0 135.14 127.51 30169 +1902 359 -0.32 -6.32 -1.97 0.22 147.66 139.77 30186 +1902 360 -2.29 -8.29 -3.94 0.23 129.32 141.3 30208 +1902 361 -5.15 -11.15 -6.8 0 106.21 174.58 30235 +1902 362 -2.86 -8.86 -4.51 0 124.39 174.26 30267 +1902 363 -0.41 -6.41 -2.06 0 146.78 173.88 30303 +1902 364 -1.46 -7.46 -3.11 0 136.79 174.63 30343 +1902 365 1.32 -4.68 -0.33 0 164.61 173.8 30388 +1903 1 -1.34 -7.34 -2.99 0 137.9 175.75 30438 +1903 2 -1.37 -7.37 -3.02 0.1 137.62 143.76 30492 +1903 3 -5.93 -11.93 -7.58 0.12 100.56 145.9 30551 +1903 4 -6.95 -12.95 -8.6 0 93.58 180.61 30614 +1903 5 -4.09 -10.09 -5.74 0 114.32 180.34 30681 +1903 6 -2.92 -8.92 -4.57 0 123.88 180.74 30752 +1903 7 -1.61 -7.61 -3.26 0 135.41 180.95 30828 +1903 8 2.26 -3.74 0.61 0.23 175.06 146.32 30907 +1903 9 -0.69 -6.69 -2.34 1.02 144.05 151.32 30991 +1903 10 1.94 -4.06 0.29 0.58 171.44 151.02 31079 +1903 11 4.81 -1.19 3.16 0 206.34 184.33 31171 +1903 12 7.79 1.79 6.14 0 248.88 182.17 31266 +1903 13 6.28 0.28 4.63 0 226.47 183.9 31366 +1903 14 1.38 -4.62 -0.27 0 165.26 187.92 31469 +1903 15 3.14 -2.86 1.49 0 185.35 187.89 31575 +1903 16 4.51 -1.49 2.86 0 202.42 187.64 31686 +1903 17 0.03 -5.97 -1.62 0 151.15 191.58 31800 +1903 18 1.41 -4.59 -0.24 0.14 165.58 154.88 31917 +1903 19 5.29 -0.71 3.64 0.07 212.73 153.8 32038 +1903 20 4.44 -1.56 2.79 0.18 201.52 114.19 32161 +1903 21 3.29 -2.71 1.64 0.46 187.16 116.22 32289 +1903 22 0.84 -5.16 -0.81 0 159.48 158.06 32419 +1903 23 -2.68 -8.68 -4.33 0 125.93 161.45 32552 +1903 24 -0.8 -6.8 -2.45 0.69 143 164.46 32688 +1903 25 -0.56 -6.56 -2.21 0.18 145.31 166.15 32827 +1903 26 0.81 -5.19 -0.84 0.82 159.17 166.81 32969 +1903 27 -0.4 -6.4 -2.05 0 146.88 210.73 33114 +1903 28 -0.9 -6.9 -2.55 0.01 142.04 170.31 33261 +1903 29 -1.69 -7.69 -3.34 0 134.68 215.62 33411 +1903 30 1.53 -4.47 -0.12 0 166.89 215.87 33564 +1903 31 1.99 -4.01 0.34 0 172 217.56 33718 +1903 32 5.38 -0.62 3.73 0 213.95 216.59 33875 +1903 33 3.59 -2.41 1.94 0 190.82 219.87 34035 +1903 34 4.83 -1.17 3.18 0 206.6 220.45 34196 +1903 35 4.55 -1.45 2.9 0 202.94 183.86 34360 +1903 36 3.27 -2.73 1.62 0.37 186.92 140.46 34526 +1903 37 7.21 1.21 5.56 0.95 240.06 139.99 34694 +1903 38 3.38 -2.62 1.73 0 188.25 192.38 34863 +1903 39 1.29 -4.71 -0.36 0 164.28 196.36 35035 +1903 40 8.93 2.93 7.28 0 267.04 192.91 35208 +1903 41 7.81 1.81 6.16 0 249.19 196.6 35383 +1903 42 8.87 2.87 7.22 0 266.06 198.08 35560 +1903 43 5.83 -0.17 4.18 0 220.13 203.6 35738 +1903 44 9.52 3.52 7.87 0 276.88 202.59 35918 +1903 45 9.33 3.33 7.68 0 273.67 205.38 36099 +1903 46 12.09 6.09 10.44 0 323.43 204.74 36282 +1903 47 14.35 8.35 12.7 0 369.76 204.33 36466 +1903 48 12.88 6.88 11.23 0.11 339.03 156.87 36652 +1903 49 15.3 9.3 13.65 0 390.86 208.23 36838 +1903 50 11.18 5.18 9.53 0 306.24 216.73 37026 +1903 51 11.58 5.58 9.93 0.02 313.7 164.34 37215 +1903 52 7.75 1.75 6.1 0.02 248.26 169.81 37405 +1903 53 5.46 -0.54 3.81 0 215.04 231.59 37596 +1903 54 3.02 -2.98 1.37 0.11 183.92 177.32 37788 +1903 55 2.77 -3.23 1.12 0 180.96 239.63 37981 +1903 56 2.84 -3.16 1.19 0 181.79 242.29 38175 +1903 57 4.54 -1.46 2.89 0 202.81 243.77 38370 +1903 58 5.43 -0.57 3.78 0 214.63 245.89 38565 +1903 59 1.43 -4.57 -0.22 0 165.8 251.97 38761 +1903 60 8.26 2.26 6.61 0 256.23 248.5 38958 +1903 61 13.74 7.74 12.09 0.76 356.73 182.86 39156 +1903 62 13.92 7.92 12.27 0.18 360.53 184.67 39355 +1903 63 11.62 5.62 9.97 0 314.45 252.76 39553 +1903 64 12.27 6.27 10.62 0 326.93 254.64 39753 +1903 65 13.31 7.31 11.66 0 347.78 255.81 39953 +1903 66 13.54 7.54 11.89 0 352.55 258.09 40154 +1903 67 11.14 5.14 9.49 0 305.5 264.71 40355 +1903 68 11.53 5.53 9.88 0 312.76 266.96 40556 +1903 69 13.06 7.06 11.41 0 342.67 267.1 40758 +1903 70 11.08 5.08 9.43 0.02 304.4 204.77 40960 +1903 71 9.36 3.36 7.71 0 274.18 278.35 41163 +1903 72 9.8 3.8 8.15 0.28 281.65 210.41 41366 +1903 73 9.37 3.37 7.72 0.13 274.35 212.85 41569 +1903 74 7.42 1.42 5.77 0.08 243.22 216.8 41772 +1903 75 9.88 3.88 8.23 0.28 283.03 216.39 41976 +1903 76 11.25 5.25 9.6 1.28 307.53 216.8 42179 +1903 77 10.37 4.37 8.72 0.14 291.59 219.75 42383 +1903 78 12.21 6.21 10.56 0 325.76 292.7 42587 +1903 79 16.27 10.27 14.62 0.18 413.46 215.66 42791 +1903 80 15.16 9.16 13.51 0.06 387.69 219.26 42996 +1903 81 14.85 8.85 13.2 0 380.74 295.49 43200 +1903 82 10.97 4.97 9.32 0 302.38 305.13 43404 +1903 83 7.73 1.73 6.08 0 247.95 312.35 43608 +1903 84 7.01 1.01 5.36 0 237.08 315.84 43812 +1903 85 6.57 0.57 4.92 0 230.63 318.91 44016 +1903 86 3.4 -2.6 1.75 0 188.49 324.92 44220 +1903 87 4.16 -1.84 2.51 0 197.94 326.7 44424 +1903 88 8.34 2.34 6.69 0 257.5 323.89 44627 +1903 89 3.74 -2.26 2.09 0 192.67 331.86 44831 +1903 90 6.89 0.89 5.24 0 235.3 330.54 45034 +1903 91 3.88 -2.12 2.23 0.37 194.41 252.31 45237 +1903 92 6.51 0.51 4.86 0 229.76 335.58 45439 +1903 93 7.02 1.02 5.37 0 237.22 337.15 45642 +1903 94 5.8 -0.2 4.15 0 219.72 340.91 45843 +1903 95 7.07 1.07 5.42 0.5 237.97 256.08 46045 +1903 96 6.59 0.59 4.94 0.13 230.92 258.16 46246 +1903 97 11.25 5.25 9.6 0.18 307.53 254.33 46446 +1903 98 11.55 5.55 9.9 0.04 313.13 255.4 46647 +1903 99 12.25 6.25 10.6 0 326.54 341.24 46846 +1903 100 11.63 5.63 9.98 1.99 314.64 258.26 47045 +1903 101 14.11 8.11 12.46 3.9 364.59 255.99 47243 +1903 102 11.92 5.92 10.27 0.39 320.16 260.72 47441 +1903 103 10.9 4.9 9.25 0.14 301.11 263.51 47638 +1903 104 12.31 6.31 10.66 0.17 327.71 262.91 47834 +1903 105 12.81 6.81 11.16 0.23 337.62 263.5 48030 +1903 106 10.56 4.56 8.91 0.01 294.97 267.93 48225 +1903 107 10.52 4.52 8.87 0.16 294.26 269.25 48419 +1903 108 11.06 5.06 9.41 0.01 304.03 269.84 48612 +1903 109 9.22 3.22 7.57 0 271.84 364.61 48804 +1903 110 9.26 3.26 7.61 0 272.5 365.97 48995 +1903 111 8.81 2.81 7.16 0.19 265.08 276.21 49185 +1903 112 5.52 -0.48 3.87 1.71 215.86 280.97 49374 +1903 113 6.51 0.51 4.86 0.18 229.76 281 49561 +1903 114 8.36 2.36 6.71 0.03 257.82 280.07 49748 +1903 115 9.54 3.54 7.89 1.22 277.21 279.71 49933 +1903 116 12.31 6.31 10.66 0.19 327.71 276.75 50117 +1903 117 15.78 9.78 14.13 0.12 401.91 271.84 50300 +1903 118 14.3 8.3 12.65 0.58 368.68 275.49 50481 +1903 119 9.74 3.74 8.09 0 280.62 377.72 50661 +1903 120 9.77 3.77 8.12 0 281.14 378.86 50840 +1903 121 17 11 15.35 0 431.19 364.01 51016 +1903 122 19.41 13.41 17.76 0 494.41 358.13 51191 +1903 123 18.14 12.14 16.49 0 460.18 362.98 51365 +1903 124 18.23 12.23 16.58 0 462.54 363.78 51536 +1903 125 15.63 9.63 13.98 0.02 398.43 278.9 51706 +1903 126 13.11 7.11 11.46 0.19 343.69 284.1 51874 +1903 127 16.05 10.05 14.4 0.31 408.24 279.5 52039 +1903 128 14.98 8.98 13.33 0.86 383.64 282.27 52203 +1903 129 15.13 9.13 13.48 0 387.01 376.84 52365 +1903 130 20.04 14.04 18.39 0.02 512.18 272.64 52524 +1903 131 21.86 15.86 20.21 0 566.6 357.95 52681 +1903 132 21.5 15.5 19.85 0.1 555.46 270.04 52836 +1903 133 24.52 18.52 22.87 0 654.91 348.87 52989 +1903 134 18.74 12.74 17.09 0.05 476.09 277.98 53138 +1903 135 18.22 12.22 16.57 0.19 462.28 279.68 53286 +1903 136 13.28 7.28 11.63 0.01 347.17 289.81 53430 +1903 137 10.71 4.71 9.06 0.51 297.67 294.35 53572 +1903 138 14.85 8.85 13.2 0 380.74 384.04 53711 +1903 139 13.72 7.72 12.07 0.13 356.31 290.58 53848 +1903 140 11.63 5.63 9.98 0 314.64 392.47 53981 +1903 141 15.68 9.68 14.03 0 399.59 383.56 54111 +1903 142 18.44 12.44 16.79 0 468.08 376.26 54238 +1903 143 18.14 12.14 16.49 0.09 460.18 283.27 54362 +1903 144 17.32 11.32 15.67 0 439.17 380.59 54483 +1903 145 16.44 10.44 14.79 0.07 417.53 287.64 54600 +1903 146 19.5 13.5 17.85 0.87 496.92 281.06 54714 +1903 147 20.38 14.38 18.73 0.21 522 279.2 54824 +1903 148 16.72 10.72 15.07 0.47 424.32 288 54931 +1903 149 20.51 14.51 18.86 0 525.79 372.5 55034 +1903 150 18.72 12.72 17.07 0.04 475.56 284.05 55134 +1903 151 20.85 14.85 19.2 0 535.82 372.03 55229 +1903 152 22 16 20.35 0 570.98 367.93 55321 +1903 153 21.13 15.13 19.48 0 544.21 371.37 55409 +1903 154 21.72 15.72 20.07 0 562.24 369.52 55492 +1903 155 21.5 15.5 19.85 1.72 555.46 277.89 55572 +1903 156 18.5 12.5 16.85 0.58 469.67 285.74 55648 +1903 157 17.79 11.79 16.14 0 451.11 383.31 55719 +1903 158 17.65 11.65 16 0.18 447.52 287.93 55786 +1903 159 16.71 10.71 15.06 0 424.07 386.85 55849 +1903 160 16.29 10.29 14.64 0 413.94 388.2 55908 +1903 161 14.94 8.94 13.29 0 382.75 391.81 55962 +1903 162 18.11 12.11 16.46 0.1 459.4 287.31 56011 +1903 163 18.38 12.38 16.73 0.09 466.49 286.85 56056 +1903 164 20.97 14.97 19.32 0 539.4 373.9 56097 +1903 165 27.37 21.37 25.72 0 762.19 346.5 56133 +1903 166 25.49 19.49 23.84 0 689.89 355.67 56165 +1903 167 23.86 17.86 22.21 0.02 631.98 272.09 56192 +1903 168 20.33 14.33 18.68 0 520.54 376.35 56214 +1903 169 20.61 14.61 18.96 1.37 528.72 281.54 56231 +1903 170 20.84 14.84 19.19 0.56 535.53 280.93 56244 +1903 171 18.78 12.78 17.13 0 477.17 381.54 56252 +1903 172 19.43 13.43 17.78 0 494.97 379.44 56256 +1903 173 23.91 17.91 22.26 0 633.69 362.7 56255 +1903 174 21.05 15.05 19.4 0.13 541.8 280.33 56249 +1903 175 18 12 16.35 0.08 456.53 287.86 56238 +1903 176 13.45 7.45 11.8 0 350.68 395.83 56223 +1903 177 19.77 13.77 18.12 0.03 504.5 283.53 56203 +1903 178 18.17 12.17 16.52 0.02 460.97 287.38 56179 +1903 179 17.79 11.79 16.14 0.53 451.11 288.16 56150 +1903 180 17.95 11.95 16.3 0.07 455.24 287.71 56116 +1903 181 19.27 13.27 17.62 0.55 490.54 284.56 56078 +1903 182 23.88 17.88 22.23 0.36 632.66 271.64 56035 +1903 183 24.74 18.74 23.09 0.14 662.71 268.73 55987 +1903 184 27.11 21.11 25.46 0.29 751.83 260.26 55935 +1903 185 27.2 21.2 25.55 0 755.4 346.48 55879 +1903 186 22.62 16.62 20.97 0 590.73 366.64 55818 +1903 187 26.1 20.1 24.45 0 712.68 351.44 55753 +1903 188 24.66 18.66 23.01 0.02 659.86 268.31 55684 +1903 189 22.41 16.41 20.76 1.33 583.98 275.12 55611 +1903 190 17.5 11.5 15.85 0.74 443.71 287.27 55533 +1903 191 19.74 13.74 18.09 2.98 503.65 281.83 55451 +1903 192 18.71 12.71 17.06 0.44 475.29 284.1 55366 +1903 193 20.56 14.56 18.91 0.11 527.26 279.31 55276 +1903 194 22.96 16.96 21.31 0.01 601.8 272.45 55182 +1903 195 23.79 17.79 22.14 0.71 629.58 269.72 55085 +1903 196 24.18 18.18 22.53 0.93 643.01 268.19 54984 +1903 197 18.67 12.67 17.02 0.21 474.21 282.95 54879 +1903 198 15.96 9.96 14.31 0.14 406.12 288.47 54770 +1903 199 21.44 15.44 19.79 0.57 553.62 275.37 54658 +1903 200 19.21 13.21 17.56 0.19 488.88 280.78 54542 +1903 201 17.29 11.29 15.64 0.08 438.42 284.78 54423 +1903 202 18.51 12.51 16.86 0.97 469.94 281.64 54301 +1903 203 20.05 14.05 18.4 0.05 512.47 277.56 54176 +1903 204 19.55 13.55 17.9 0.76 498.32 278.41 54047 +1903 205 18.35 12.35 16.7 0.18 465.7 280.84 53915 +1903 206 19.63 13.63 17.98 0.09 500.56 277.4 53780 +1903 207 21.61 15.61 19.96 0.1 558.84 271.79 53643 +1903 208 22.02 16.02 20.37 1.28 571.61 270.17 53502 +1903 209 21.06 15.06 19.41 1.14 542.1 272.3 53359 +1903 210 25.47 19.47 23.82 0 689.15 344.87 53213 +1903 211 27.8 21.8 26.15 0 779.6 332.99 53064 +1903 212 28.29 22.29 26.64 0.18 799.85 247.29 52913 +1903 213 27.77 21.77 26.12 0.06 778.38 248.76 52760 +1903 214 27.64 21.64 25.99 0.44 773.09 248.73 52604 +1903 215 25.5 19.5 23.85 0.18 690.25 255.85 52445 +1903 216 26.49 20.49 24.84 1.41 727.59 251.72 52285 +1903 217 23.02 17.02 21.37 0.61 603.78 262.21 52122 +1903 218 23.36 17.36 21.71 0.06 615.06 260.62 51958 +1903 219 25.34 19.34 23.69 0 684.38 338.23 51791 +1903 220 21.88 15.88 20.23 0 567.22 351.13 51622 +1903 221 23.12 17.12 21.47 0.03 607.08 259.13 51451 +1903 222 22.93 16.93 21.28 0.93 600.82 258.91 51279 +1903 223 19.17 13.17 17.52 0.04 487.78 267.76 51105 +1903 224 17.88 11.88 16.23 0.07 453.43 269.83 50929 +1903 225 15.78 9.78 14.13 0 401.91 364.24 50751 +1903 226 16.82 10.82 15.17 0.39 426.76 270.28 50572 +1903 227 18.03 12.03 16.38 0.35 457.31 266.8 50392 +1903 228 19.31 13.31 17.66 0.08 491.64 263.04 50210 +1903 229 17.4 11.4 15.75 0 441.18 355.01 50026 +1903 230 22.07 16.07 20.42 0 573.18 339.09 49842 +1903 231 20.63 14.63 18.98 0.05 529.31 256.92 49656 +1903 232 19.08 13.08 17.43 0.54 485.32 259.55 49469 +1903 233 22.74 16.74 21.09 0 594.62 332.51 49280 +1903 234 22.86 16.86 21.21 0 598.53 330.69 49091 +1903 235 24.23 18.23 22.58 0 644.75 324.02 48900 +1903 236 21.38 15.38 19.73 0.97 551.79 249.78 48709 +1903 237 20.63 14.63 18.98 1 529.31 250.42 48516 +1903 238 21.8 15.8 20.15 0 564.73 328.36 48323 +1903 239 21.81 15.81 20.16 0 565.04 326.85 48128 +1903 240 20.29 14.29 18.64 0 519.38 330.07 47933 +1903 241 22.32 16.32 20.67 0 581.1 321.69 47737 +1903 242 25.03 19.03 23.38 0 673.11 309.85 47541 +1903 243 20.93 14.93 19.28 0.12 538.21 242.1 47343 +1903 244 19.53 13.53 17.88 0.17 497.76 243.96 47145 +1903 245 22.72 16.72 21.07 0 593.97 313.23 46947 +1903 246 23.55 17.55 21.9 0 621.44 308.36 46747 +1903 247 21.21 15.21 19.56 0.37 546.63 235.92 46547 +1903 248 19.62 13.62 17.97 0.45 500.28 238.11 46347 +1903 249 18.93 12.93 17.28 0 481.23 317.4 46146 +1903 250 19.64 13.64 17.99 0.08 500.84 235.09 45945 +1903 251 14.99 8.99 13.34 0.02 383.87 242.28 45743 +1903 252 17.37 11.37 15.72 0 440.43 315.3 45541 +1903 253 18.84 12.84 17.19 0 478.79 309.37 45339 +1903 254 17.89 11.89 16.24 0 453.69 309.74 45136 +1903 255 15.3 9.3 13.65 0 390.86 313.58 44933 +1903 256 14.93 8.93 13.28 0.07 382.52 234.06 44730 +1903 257 14.13 8.13 12.48 0 365.02 311.54 44527 +1903 258 19.46 13.46 17.81 0 495.8 296.66 44323 +1903 259 19.44 13.44 17.79 0 495.25 294.32 44119 +1903 260 18.86 12.86 17.21 0 479.33 293.52 43915 +1903 261 22.2 16.2 20.55 0.83 577.29 211.19 43711 +1903 262 20.29 14.29 18.64 0.05 519.38 213.7 43507 +1903 263 18.24 12.24 16.59 0.33 462.8 215.93 43303 +1903 264 19.98 13.98 18.33 0.43 510.47 210.66 43099 +1903 265 20.51 14.51 18.86 0.65 525.79 207.84 42894 +1903 266 22.53 16.53 20.88 0.04 587.83 201.62 42690 +1903 267 19.97 13.97 18.32 0.7 510.18 205.18 42486 +1903 268 19.41 13.41 17.76 0 494.41 272.53 42282 +1903 269 19.48 13.48 17.83 0.28 496.36 202.43 42078 +1903 270 17.56 11.56 15.91 0.61 445.23 203.95 41875 +1903 271 10.92 4.92 9.27 0 301.47 281.68 41671 +1903 272 13.03 7.03 11.38 0 342.06 275.52 41468 +1903 273 12.19 6.19 10.54 0 325.37 274.36 41265 +1903 274 11.37 5.37 9.72 0.87 309.76 204.7 41062 +1903 275 12.47 6.47 10.82 0 330.86 268.41 40860 +1903 276 11.95 5.95 10.3 0.27 320.74 199.88 40658 +1903 277 12.32 6.32 10.67 0 327.91 263.24 40456 +1903 278 10.56 4.56 8.91 0 294.97 262.96 40255 +1903 279 13.28 7.28 11.63 0 347.17 256 40054 +1903 280 12.14 6.14 10.49 0 324.4 255.13 39854 +1903 281 13.42 7.42 11.77 0 350.05 250.39 39654 +1903 282 17.26 11.26 15.61 0 437.66 240.68 39455 +1903 283 21.46 15.46 19.81 0 554.23 228.36 39256 +1903 284 25.15 19.15 23.5 0 677.45 215.08 39058 +1903 285 19.62 13.62 17.97 0 500.28 227.38 38861 +1903 286 17.36 11.36 15.71 0 440.17 229.49 38664 +1903 287 15.56 9.56 13.91 0.35 396.81 172.48 38468 +1903 288 12.63 6.63 10.98 0 334.03 231.92 38273 +1903 289 16.37 10.37 14.72 0.28 415.85 167.4 38079 +1903 290 11.21 5.21 9.56 0.4 306.79 171.29 37885 +1903 291 8.68 2.68 7.03 0 262.96 228.74 37693 +1903 292 7.33 1.33 5.68 0.01 241.86 170.59 37501 +1903 293 8 2 6.35 0 252.14 223.99 37311 +1903 294 10.48 4.48 8.83 0.17 293.55 163.7 37121 +1903 295 12.83 6.83 11.18 0.82 338.02 159.28 36933 +1903 296 14.9 8.9 13.25 0 381.86 206.76 36745 +1903 297 17.52 11.52 15.87 0.03 444.22 149.77 36560 +1903 298 18.05 12.05 16.4 0.53 457.83 147.15 36375 +1903 299 14.13 8.13 12.48 0.18 365.02 149.95 36191 +1903 300 14.8 8.8 13.15 0.78 379.63 147.24 36009 +1903 301 16.44 10.44 14.79 0.92 417.53 143.48 35829 +1903 302 11.46 5.46 9.81 1.14 311.44 146.81 35650 +1903 303 11.72 5.72 10.07 0.39 316.34 144.65 35472 +1903 304 12.52 6.52 10.87 0.02 331.84 142.08 35296 +1903 305 6.81 0.81 5.16 0.15 234.13 144.55 35122 +1903 306 4.96 -1.04 3.31 0 208.32 191.97 34950 +1903 307 5.03 -0.97 3.38 0 209.25 189.37 34779 +1903 308 10.22 4.22 8.57 0 288.95 182.07 34610 +1903 309 10.43 4.43 8.78 0 292.66 179.54 34444 +1903 310 12.3 6.3 10.65 0 327.52 175.04 34279 +1903 311 13.32 7.32 11.67 0 347.99 171.67 34116 +1903 312 12.37 6.37 10.72 0.02 328.89 127.66 33956 +1903 313 8.8 2.8 7.15 0 264.91 171.81 33797 +1903 314 7.59 1.59 5.94 0 245.81 170.93 33641 +1903 315 7.57 1.57 5.92 2.06 245.5 126.31 33488 +1903 316 8.53 2.53 6.88 0 260.54 165.4 33337 +1903 317 10.9 4.9 9.25 0 301.11 160.98 33188 +1903 318 16.26 10.26 14.61 0.06 413.22 114.22 33042 +1903 319 10.41 4.41 8.76 0.86 292.3 118.11 32899 +1903 320 11.11 5.11 9.46 0.07 304.95 116.21 32758 +1903 321 10.75 4.75 9.1 0.07 298.39 114.92 32620 +1903 322 8.87 2.87 7.22 0.84 266.06 114.86 32486 +1903 323 9.51 3.51 7.86 0 276.71 150.98 32354 +1903 324 11.81 5.81 10.16 0.58 318.06 110.08 32225 +1903 325 11.48 5.48 9.83 0.03 311.82 109.06 32100 +1903 326 10.64 4.64 8.99 0.41 296.41 108.6 31977 +1903 327 10.63 4.63 8.98 0.32 296.23 107.24 31858 +1903 328 8.16 2.16 6.51 0.08 254.65 107.35 31743 +1903 329 2.07 -3.93 0.42 0.31 172.9 109.18 31631 +1903 330 -0.11 -6.11 -1.76 0.46 149.74 152.15 31522 +1903 331 1.37 -4.63 -0.28 0.02 165.15 150.6 31417 +1903 332 3.63 -2.37 1.98 0 191.31 183.2 31316 +1903 333 3.81 -2.19 2.16 0.62 193.54 146.87 31218 +1903 334 7.91 1.91 6.26 0 250.74 135.3 31125 +1903 335 6.73 0.73 5.08 0 232.96 134.98 31035 +1903 336 6.55 0.55 4.9 0 230.34 134.03 30949 +1903 337 2.54 -3.46 0.89 0.04 178.28 101.06 30867 +1903 338 4.55 -1.45 2.9 0 202.94 132.69 30790 +1903 339 6.29 0.29 4.64 0 226.61 130.83 30716 +1903 340 9.47 3.47 7.82 0.03 276.03 95.86 30647 +1903 341 9.12 3.12 7.47 0.91 270.17 95.39 30582 +1903 342 9.77 3.77 8.12 0 281.14 125.92 30521 +1903 343 9.74 3.74 8.09 0 280.62 125.14 30465 +1903 344 6.58 0.58 4.93 0 230.78 126.29 30413 +1903 345 5.03 -0.97 3.38 0.25 209.25 95.12 30366 +1903 346 -1.91 -7.91 -3.56 0.06 132.69 140.87 30323 +1903 347 2.22 -3.78 0.57 0.45 174.6 95.39 30284 +1903 348 -0.27 -6.27 -1.92 0 148.15 127.94 30251 +1903 349 -0.14 -6.14 -1.79 0.68 149.44 141.47 30221 +1903 350 -1.83 -7.83 -3.48 0 133.41 173.7 30197 +1903 351 2.27 -3.73 0.62 0.15 175.17 140 30177 +1903 352 5.64 -0.36 3.99 2.18 217.5 137.83 30162 +1903 353 4.44 -1.56 2.79 1.98 201.52 137.73 30151 +1903 354 3.31 -2.69 1.66 0.23 187.4 137.72 30145 +1903 355 1.07 -4.93 -0.58 0.06 161.92 94.67 30144 +1903 356 0.16 -5.84 -1.49 1.11 152.46 94.99 30147 +1903 357 -0.09 -6.09 -1.74 1.37 149.94 143.24 30156 +1903 358 4.47 -1.53 2.82 0.31 201.91 141.04 30169 +1903 359 2.01 -3.99 0.36 0.99 172.22 141.79 30186 +1903 360 -2.56 -8.56 -4.21 0.01 126.96 143.46 30208 +1903 361 0.18 -5.82 -1.47 0.68 152.66 142.86 30235 +1903 362 3.92 -2.08 2.27 0.04 194.91 141.27 30267 +1903 363 0.17 -5.83 -1.48 0 152.56 175.15 30303 +1903 364 5.23 -0.77 3.58 0.01 211.92 140.61 30343 +1903 365 3.33 -2.67 1.68 0 187.64 173.36 30388 +1904 1 -1.4 -7.4 -3.05 0 137.34 176.32 30438 +1904 2 3.57 -2.43 1.92 0 190.57 174.23 30492 +1904 3 1.82 -4.18 0.17 0.29 170.1 142.88 30551 +1904 4 3.21 -2.79 1.56 0 186.2 175.44 30614 +1904 5 5.2 -0.8 3.55 0 211.52 131.19 30681 +1904 6 1.54 -4.46 -0.11 0 167 134.05 30752 +1904 7 -1.17 -7.17 -2.82 0 139.49 136.05 30828 +1904 8 1.2 -4.8 -0.45 0 163.31 136.51 30907 +1904 9 9.34 3.34 7.69 0 273.84 132.66 30991 +1904 10 8.26 2.26 6.61 0 256.23 134.79 31079 +1904 11 3.15 -2.85 1.5 0.59 185.47 104.31 31171 +1904 12 2.33 -3.67 0.68 0.27 175.86 105.39 31266 +1904 13 -0.29 -6.29 -1.94 0.04 147.96 149.77 31366 +1904 14 -0.25 -6.25 -1.9 0.07 148.35 150.95 31469 +1904 15 3.85 -2.15 2.2 0 194.04 144.23 31575 +1904 16 2.16 -3.84 0.51 0.05 173.92 109.85 31686 +1904 17 -0.57 -6.57 -2.22 0.44 145.22 154.95 31800 +1904 18 -5.28 -11.28 -6.93 0 105.25 195.88 31917 +1904 19 -2.69 -8.69 -4.34 0 125.84 196.76 32038 +1904 20 -1.59 -7.59 -3.24 0.03 135.6 159 32161 +1904 21 0.69 -5.31 -0.96 0 157.91 198.57 32289 +1904 22 1.2 -4.8 -0.45 0 163.31 199.75 32419 +1904 23 1.9 -4.1 0.25 0 170.99 200.75 32552 +1904 24 -1.44 -7.44 -3.09 0 136.97 204.32 32688 +1904 25 -3.69 -9.69 -5.34 0 117.51 206.98 32827 +1904 26 -0.24 -6.24 -1.89 0 148.45 207.26 32969 +1904 27 -1.98 -7.98 -3.63 0 132.07 209.93 33114 +1904 28 -2.98 -8.98 -4.63 0 123.38 212.42 33261 +1904 29 -3.9 -9.9 -5.55 0 115.82 215.02 33411 +1904 30 -2.22 -8.22 -3.87 0 129.93 216.41 33564 +1904 31 -1.17 -7.17 -2.82 0.65 139.49 175.47 33718 +1904 32 6.22 0.22 4.57 1.1 225.61 172.68 33875 +1904 33 6.77 0.77 5.12 1.15 233.54 173.31 34035 +1904 34 5.26 -0.74 3.61 0.1 212.33 175.04 34196 +1904 35 4.23 -1.77 2.58 0 198.83 222.56 34360 +1904 36 6.19 0.19 4.54 0 225.19 185.11 34526 +1904 37 7.53 1.53 5.88 0 244.89 186.37 34694 +1904 38 8.67 2.67 7.02 0.05 262.8 141.01 34863 +1904 39 9.01 3.01 7.36 0 268.36 190.25 35035 +1904 40 6.38 0.38 4.73 0.05 227.89 146.46 35208 +1904 41 7.96 1.96 6.31 0.23 251.52 147.34 35383 +1904 42 6.72 0.72 5.07 0 232.81 200.13 35560 +1904 43 5.17 -0.83 3.52 0 211.12 204.15 35738 +1904 44 4.33 -1.67 2.68 0 200.11 207.39 35918 +1904 45 6.91 0.91 5.26 0.51 235.6 155.86 36099 +1904 46 7.07 1.07 5.42 0 237.97 210.33 36282 +1904 47 3.96 -2.04 2.31 0 195.41 215.83 36466 +1904 48 6.08 0.08 4.43 0.06 223.63 162.64 36652 +1904 49 4.22 -1.78 2.57 0.83 198.7 165.91 36838 +1904 50 7.58 1.58 5.93 0.15 245.65 165.62 37026 +1904 51 9.75 3.75 8.1 1.16 280.79 166.05 37215 +1904 52 4.27 -1.73 2.62 1.23 199.34 172.25 37405 +1904 53 -0.59 -6.59 -2.24 0.08 145.02 212.41 37596 +1904 54 2.47 -3.53 0.82 0 177.47 236.84 37788 +1904 55 3.49 -2.51 1.84 0 189.59 239.06 37981 +1904 56 4.83 -1.17 3.18 0 206.6 240.62 38175 +1904 57 4.55 -1.45 2.9 0.46 202.94 182.82 38370 +1904 58 5.7 -0.3 4.05 0.9 218.33 184.23 38565 +1904 59 7.46 1.46 5.81 0.99 243.83 184.9 38761 +1904 60 7.79 1.79 6.14 0 248.88 249.04 38958 +1904 61 8.85 2.85 7.2 0 265.73 250.72 39156 +1904 62 11.59 5.59 9.94 0.22 313.89 187.38 39355 +1904 63 15.14 9.14 13.49 0 387.24 247.03 39553 +1904 64 16.57 10.57 14.92 0 420.67 247.12 39753 +1904 65 14.51 8.51 12.86 0.19 373.25 190.32 39953 +1904 66 18.53 12.53 16.88 0.35 470.47 186.25 40154 +1904 67 16.85 10.85 15.2 0 427.5 254.72 40355 +1904 68 17.65 11.65 16 0 447.52 255.78 40556 +1904 69 11.51 5.51 9.86 0 312.38 269.57 40758 +1904 70 8.94 2.94 7.29 0.66 267.2 207.01 40960 +1904 71 5.99 -0.01 4.34 0.75 222.37 211.84 41163 +1904 72 10.08 4.08 8.43 0 286.5 280.16 41366 +1904 73 9.07 3.07 7.42 0.07 269.35 213.15 41569 +1904 74 7.31 1.31 5.66 0 241.56 289.2 41772 +1904 75 5.16 -0.84 3.51 0 210.98 294.39 41976 +1904 76 4.4 -1.6 2.75 0 201 297.85 42179 +1904 77 3.25 -2.75 1.6 0.06 186.68 226.21 42383 +1904 78 2.49 -3.51 0.84 0 177.7 305.03 42587 +1904 79 3.47 -2.53 1.82 1.12 189.35 230.15 42791 +1904 80 0.81 -5.19 -0.84 0.29 159.17 233.89 42996 +1904 81 -0.35 -6.35 -2 1.89 147.37 271.31 43200 +1904 82 2.17 -3.83 0.52 1.24 174.03 271.39 43404 +1904 83 3.11 -2.89 1.46 0.16 184.99 272.17 43608 +1904 84 2.78 -3.22 1.13 0 181.08 354.07 43812 +1904 85 -0.06 -6.06 -1.71 0 150.24 358.98 44016 +1904 86 3.93 -2.07 2.28 0.01 195.04 276.14 44220 +1904 87 5.16 -0.84 3.51 0.26 210.98 276.43 44424 +1904 88 6.62 0.62 4.97 0.12 231.36 276.15 44627 +1904 89 8.95 2.95 7.3 0.23 267.37 274.52 44831 +1904 90 13.09 7.09 11.44 0.21 343.28 240.48 45034 +1904 91 17.15 11.15 15.5 1.47 434.92 235.5 45237 +1904 92 11.21 5.21 9.56 0 306.79 328.53 45439 +1904 93 10.86 4.86 9.21 0 300.38 331.34 45642 +1904 94 10.57 4.57 8.92 0 295.15 333.98 45843 +1904 95 8.5 2.5 6.85 0.03 260.06 254.55 46045 +1904 96 12.52 6.52 10.87 0 331.84 334.73 46246 +1904 97 15.58 9.58 13.93 0 397.27 330.31 46446 +1904 98 16.19 10.19 14.54 0 411.56 330.79 46647 +1904 99 15.05 9.05 13.4 0.95 385.21 251.56 46846 +1904 100 14.51 8.51 12.86 0 373.25 338.54 47045 +1904 101 15.17 9.17 13.52 0.18 387.92 254.22 47243 +1904 102 12.89 6.89 11.24 0.2 339.23 259.31 47441 +1904 103 13.89 7.89 12.24 0 359.9 345.49 47638 +1904 104 14.82 8.82 13.17 0 380.08 345.25 47834 +1904 105 17.24 11.24 15.59 0.62 437.16 255.81 48030 +1904 106 17.79 11.79 16.14 0 451.11 341.21 48225 +1904 107 19.34 13.34 17.69 0 492.47 338.4 48419 +1904 108 14.64 8.64 12.99 0 376.1 352.43 48612 +1904 109 17.61 11.61 15.96 0.35 446.5 259.95 48804 +1904 110 14.26 8.26 12.61 0.17 367.81 267.22 48995 +1904 111 14.66 8.66 13.01 0 376.54 356.92 49185 +1904 112 11.47 5.47 9.82 0.52 311.63 273.86 49374 +1904 113 10.23 4.23 8.58 0.15 289.12 276.59 49561 +1904 114 11.27 5.27 9.62 0 307.9 368.38 49748 +1904 115 10.55 4.55 8.9 0 294.79 371.16 49933 +1904 116 11.98 5.98 10.33 0 321.31 369.67 50117 +1904 117 13.23 7.23 11.58 0.16 346.14 276.29 50300 +1904 118 9.11 3.11 7.46 0.86 270.01 283.19 50481 +1904 119 9.57 3.57 7.92 0.15 277.72 283.51 50661 +1904 120 7.54 1.54 5.89 0 245.04 382.51 50840 +1904 121 9 3 7.35 0.23 268.19 286 51016 +1904 122 7.61 1.61 5.96 0.2 246.11 288.59 51191 +1904 123 4.6 -1.4 2.95 0 203.59 390.07 51365 +1904 124 11.06 5.06 9.41 0 304.03 380.99 51536 +1904 125 13.05 7.05 11.4 0.14 342.47 283.44 51706 +1904 126 17.49 11.49 15.84 0 443.46 367.86 51874 +1904 127 16.63 10.63 14.98 0.57 422.13 278.34 52039 +1904 128 17.9 11.9 16.25 0 453.94 368.55 52203 +1904 129 15.63 9.63 13.98 0.08 398.43 281.69 52365 +1904 130 14.03 8.03 12.38 0 362.88 380.28 52524 +1904 131 13.99 7.99 12.34 0.27 362.02 285.88 52681 +1904 132 11.4 5.4 9.75 0 310.32 387.59 52836 +1904 133 14.08 8.08 12.43 0 363.94 382.51 52989 +1904 134 21.04 15.04 19.39 0 541.5 363.05 53138 +1904 135 17.71 11.71 16.06 1.43 449.06 280.81 53286 +1904 136 22.71 16.71 21.06 1.27 593.64 268.63 53430 +1904 137 19.26 13.26 17.61 1.62 490.26 278.26 53572 +1904 138 20.27 14.27 18.62 0 518.8 368.28 53711 +1904 139 16.41 10.41 14.76 2.34 416.81 285.52 53848 +1904 140 16.32 10.32 14.67 0.46 414.65 286.07 53981 +1904 141 16.54 10.54 14.89 0.27 419.95 285.95 54111 +1904 142 23.37 17.37 21.72 0 615.39 358.83 54238 +1904 143 22.85 16.85 21.2 0 598.2 361.42 54362 +1904 144 21.77 15.77 20.12 0 563.79 366.01 54483 +1904 145 20.26 14.26 18.61 0 518.51 371.84 54600 +1904 146 24.03 18.03 22.38 0 637.82 357.89 54714 +1904 147 21.35 15.35 19.7 0 550.88 368.84 54824 +1904 148 23.3 17.3 21.65 0.25 613.06 271.3 54931 +1904 149 19.18 13.18 17.53 0.1 488.06 282.71 55034 +1904 150 17.83 11.83 16.18 0 452.14 381.45 55134 +1904 151 21.65 15.65 20 0 560.08 369.13 55229 +1904 152 26.24 20.24 24.59 2.06 718 262.41 55321 +1904 153 25.65 19.65 24 0.09 695.8 264.66 55409 +1904 154 23.89 17.89 22.24 0.1 633 270.7 55492 +1904 155 19.18 13.18 17.53 0.57 488.06 283.89 55572 +1904 156 15.86 9.86 14.21 1.27 403.78 291.43 55648 +1904 157 16.21 10.21 14.56 0.54 412.03 290.86 55719 +1904 158 13.38 7.38 11.73 0 349.23 395.06 55786 +1904 159 14.06 8.06 12.41 0 363.52 393.71 55849 +1904 160 18.52 12.52 16.87 0 470.21 381.7 55908 +1904 161 17.24 11.24 15.59 0.03 437.16 289.2 55962 +1904 162 21.02 15.02 19.37 0 540.9 373.47 56011 +1904 163 17.12 11.12 15.47 0 434.17 386.22 56056 +1904 164 18.41 12.41 16.76 0 467.28 382.43 56097 +1904 165 21.16 15.16 19.51 0.07 545.11 279.98 56133 +1904 166 21.99 15.99 20.34 1.31 570.66 277.74 56165 +1904 167 24.16 18.16 22.51 0.04 642.31 271.14 56192 +1904 168 24.24 18.24 22.59 0.65 645.09 270.94 56214 +1904 169 27.95 21.95 26.3 0.23 785.75 257.7 56231 +1904 170 25.61 19.61 23.96 0.11 694.32 266.36 56244 +1904 171 26.91 20.91 25.26 0.08 743.94 261.73 56252 +1904 172 25.89 19.89 24.24 0.24 704.76 265.42 56256 +1904 173 24.87 18.87 23.22 0.52 667.35 268.91 56255 +1904 174 21.5 15.5 19.85 0 555.46 372.13 56249 +1904 175 24.08 18.08 22.43 0 639.54 361.87 56238 +1904 176 20.73 14.73 19.08 0 532.26 374.85 56223 +1904 177 23.37 17.37 21.72 0.09 615.39 273.52 56203 +1904 178 20.33 14.33 18.68 0.09 520.54 282.12 56179 +1904 179 20.47 14.47 18.82 0 524.62 375.58 56150 +1904 180 16.69 10.69 15.04 0.01 423.59 290.45 56116 +1904 181 16.49 10.49 14.84 0 418.74 387.75 56078 +1904 182 20.11 14.11 18.46 0 514.19 376.48 56035 +1904 183 25.05 19.05 23.4 0 673.83 356.93 55987 +1904 184 24.18 18.18 22.53 0 643.01 360.59 55935 +1904 185 28.59 22.59 26.94 0 812.46 339.22 55879 +1904 186 26.24 20.24 24.59 0 718 350.95 55818 +1904 187 25.02 19.02 23.37 0.01 672.74 267.31 55753 +1904 188 22.29 16.29 20.64 0 580.15 367.47 55684 +1904 189 21.36 15.36 19.71 0 551.18 370.77 55611 +1904 190 21.73 15.73 20.08 0 562.55 369.04 55533 +1904 191 24.62 18.62 22.97 0 658.44 357.12 55451 +1904 192 28.46 22.46 26.81 0 806.98 338.21 55366 +1904 193 29.69 23.69 28.04 0.12 860.16 248.36 55276 +1904 194 27.79 21.79 26.14 0.02 779.19 255.97 55182 +1904 195 24.86 18.86 23.21 0 666.99 355.04 55085 +1904 196 22.46 16.46 20.81 0 585.58 364.56 54984 +1904 197 23.12 17.12 21.47 0.65 607.08 271.13 54879 +1904 198 23.37 17.37 21.72 0.11 615.39 270.07 54770 +1904 199 25.71 19.71 24.06 0.29 698.04 262.22 54658 +1904 200 22.47 16.47 20.82 0.13 585.9 272.18 54542 +1904 201 20.66 14.66 19.01 0.32 530.2 276.8 54423 +1904 202 24.63 18.63 22.98 0.62 658.8 264.8 54301 +1904 203 25.89 19.89 24.24 0.31 704.76 260.21 54176 +1904 204 23.1 17.1 21.45 0.32 606.42 268.83 54047 +1904 205 26.02 20.02 24.37 0 709.66 345.36 53915 +1904 206 28.19 22.19 26.54 0 795.68 334.12 53780 +1904 207 26.63 20.63 24.98 0.03 733 255.99 53643 +1904 208 26.19 20.19 24.54 0 716.1 342.78 53502 +1904 209 25.97 19.97 24.32 0.09 707.77 257.39 53359 +1904 210 24.9 18.9 23.25 0 668.43 347.39 53213 +1904 211 22.61 16.61 20.96 0 590.41 355.98 53064 +1904 212 23.06 17.06 21.41 0.08 605.1 265.1 52913 +1904 213 24.7 18.7 23.05 0.19 661.28 259.5 52760 +1904 214 30.68 24.68 29.03 0.01 905.08 236.32 52604 +1904 215 30.49 24.49 28.84 0.45 896.31 236.71 52445 +1904 216 20.16 14.16 18.51 0.58 515.63 270.56 52285 +1904 217 21.37 15.37 19.72 0.02 551.49 266.8 52122 +1904 218 20.5 14.5 18.85 0 525.5 357.91 51958 +1904 219 24.11 18.11 22.46 0.42 640.58 257.59 51791 +1904 220 23.51 17.51 21.86 1.46 620.09 258.72 51622 +1904 221 19.43 13.43 17.78 0.7 494.97 268.8 51451 +1904 222 19.84 13.84 18.19 0.14 506.48 267.04 51279 +1904 223 18.39 12.39 16.74 0 466.76 359.36 51105 +1904 224 19.21 13.21 17.56 0 488.88 355.83 50929 +1904 225 22.81 16.81 21.16 0.07 596.9 256.8 50751 +1904 226 18.33 12.33 16.68 0.59 465.17 267.12 50572 +1904 227 21.75 15.75 20.1 0.48 563.17 257.92 50392 +1904 228 21.46 15.46 19.81 0.37 554.23 257.78 50210 +1904 229 18.65 12.65 17 0.26 473.68 263.59 50026 +1904 230 20.91 14.91 19.26 1.04 537.61 257.32 49842 +1904 231 22.98 16.98 21.33 0 602.46 334.33 49656 +1904 232 22.96 16.96 21.31 0 601.8 333.08 49469 +1904 233 23.62 17.62 21.97 0 623.81 329.2 49280 +1904 234 26.27 20.27 24.62 0 719.15 316.88 49091 +1904 235 28.75 22.75 27.1 0 819.26 303.75 48900 +1904 236 27.87 21.87 26.22 0.19 782.47 230.08 48709 +1904 237 25.99 19.99 24.34 0.15 708.52 235.35 48516 +1904 238 28.05 22.05 26.4 0.3 789.88 227.12 48323 +1904 239 22.76 16.76 21.11 3.25 595.27 242.64 48128 +1904 240 21.28 15.28 19.63 1.03 548.75 245.17 47933 +1904 241 23.31 17.31 21.66 0.14 613.39 238.61 47737 +1904 242 22.24 16.24 20.59 0 578.56 320.27 47541 +1904 243 23.79 17.79 22.14 0 629.58 312.89 47343 +1904 244 18 12 16.35 0.04 456.53 247.19 47145 +1904 245 17.38 11.38 15.73 0.22 440.68 247.03 46947 +1904 246 23.09 17.09 21.44 1.47 606.09 232.52 46747 +1904 247 19.83 13.83 18.18 0.25 506.2 239.09 46547 +1904 248 22 16 20.35 1.73 570.98 232.57 46347 +1904 249 19.78 13.78 18.13 1.33 504.78 236.24 46146 +1904 250 15.24 9.24 13.59 0.01 389.5 243.47 45945 +1904 251 14.63 8.63 12.98 0.06 375.88 242.86 45743 +1904 252 16.98 10.98 15.33 0 430.7 316.26 45541 +1904 253 17.86 11.86 16.21 0.02 452.91 233.96 45339 +1904 254 19.94 13.94 18.29 0.36 509.33 228.15 45136 +1904 255 19.58 13.58 17.93 0 499.16 302.99 44933 +1904 256 16.78 10.78 15.13 1.5 425.78 230.96 44730 +1904 257 15.43 9.43 13.78 0.33 393.83 231.62 44527 +1904 258 16.38 10.38 14.73 0.93 416.09 228.27 44323 +1904 259 17.01 11.01 15.36 0.1 431.44 225.35 44119 +1904 260 14.47 8.47 12.82 0.55 372.37 227.7 43915 +1904 261 15.29 9.29 13.64 0.3 390.64 224.59 43711 +1904 262 17.77 11.77 16.12 0.47 450.6 218.61 43507 +1904 263 17.42 11.42 15.77 0.47 441.69 217.41 43303 +1904 264 11.97 5.97 10.32 0.86 321.12 223.66 43099 +1904 265 12.94 6.94 11.29 0 340.24 294.12 42894 +1904 266 13.74 7.74 12.09 0.7 356.73 217.61 42690 +1904 267 13.5 7.5 11.85 0.05 351.71 215.92 42486 +1904 268 13.07 7.07 11.42 0 342.87 286.07 42282 +1904 269 11.7 5.7 10.05 0.15 315.97 214.36 42078 +1904 270 14.5 8.5 12.85 0 373.03 278.27 41875 +1904 271 22.12 16.12 20.47 0.08 574.76 193.22 41671 +1904 272 23.87 17.87 22.22 0 632.32 249.71 41468 +1904 273 22.01 16.01 20.36 0 571.29 252.94 41265 +1904 274 20.77 14.77 19.12 0 533.45 253.78 41062 +1904 275 19.91 13.91 18.26 0 508.47 253.33 40860 +1904 276 18.23 12.23 16.58 0.72 462.54 191.02 40658 +1904 277 18.51 12.51 16.86 1.58 469.94 188.6 40456 +1904 278 12.78 6.78 11.13 0.55 337.02 194.72 40255 +1904 279 11.44 5.44 9.79 0 311.07 258.85 40054 +1904 280 12.01 6.01 10.36 0.01 321.89 191.5 39854 +1904 281 15.61 9.61 13.96 0 397.97 246.58 39654 +1904 282 13.06 7.06 11.41 1.19 342.67 186.17 39455 +1904 283 13.26 7.26 11.61 0.06 346.76 183.82 39256 +1904 284 13.85 7.85 12.2 0.14 359.05 180.85 39058 +1904 285 14.31 8.31 12.66 0.11 368.89 178.31 38861 +1904 286 14.6 8.6 12.95 0 375.22 234.52 38664 +1904 287 15.56 9.56 13.91 0.94 396.81 172.48 38468 +1904 288 7.59 1.59 5.94 0.46 245.81 178.7 38273 +1904 289 10.21 4.21 8.56 1.36 288.77 174.42 38079 +1904 290 8.3 2.3 6.65 0 256.87 231.91 37885 +1904 291 7.09 1.09 5.44 0 238.26 230.44 37693 +1904 292 9.49 3.49 7.84 0.48 276.37 168.83 37501 +1904 293 16.14 10.14 14.49 0.45 410.37 159.65 37311 +1904 294 14.18 8.18 12.53 0.47 366.09 159.91 37121 +1904 295 11.64 5.64 9.99 0 314.83 213.97 36933 +1904 296 13.56 7.56 11.91 0 352.96 208.77 36745 +1904 297 13.14 7.14 11.49 0 344.3 206.67 36560 +1904 298 13.41 7.41 11.76 0.07 349.85 152.78 36375 +1904 299 12.7 6.7 11.05 0.37 335.42 151.44 36191 +1904 300 10.01 4.01 8.36 0.33 285.28 151.92 36009 +1904 301 12.11 6.11 10.46 0.24 323.82 148.16 35829 +1904 302 12.92 6.92 11.27 0.01 339.83 145.44 35650 +1904 303 13.09 7.09 11.44 0.45 343.28 143.36 35472 +1904 304 13.97 7.97 12.32 0.24 361.6 140.65 35296 +1904 305 4.64 -1.36 2.99 0 204.11 194.51 35122 +1904 306 2.32 -3.68 0.67 0 175.74 193.84 34950 +1904 307 1.87 -4.13 0.22 0 170.65 191.56 34779 +1904 308 3.02 -2.98 1.37 0 183.92 188.16 34610 +1904 309 8.07 2.07 6.42 0 253.24 181.87 34444 +1904 310 11.89 5.89 10.24 0.04 319.59 131.64 34279 +1904 311 7.93 1.93 6.28 0 251.05 177.36 34116 +1904 312 4.97 -1.03 3.32 0 208.45 177.09 33956 +1904 313 2.3 -3.7 0.65 0 175.51 176.72 33797 +1904 314 3.72 -2.28 2.07 0 192.42 173.83 33641 +1904 315 3.7 -2.3 2.05 0 192.17 171.28 33488 +1904 316 3.77 -2.23 2.12 0 193.04 169.03 33337 +1904 317 -0.77 -6.77 -2.42 0.29 143.28 167.61 33188 +1904 318 3.3 -2.7 1.65 0.43 187.28 163.95 33042 +1904 319 3.74 -2.26 2.09 0 192.67 162.75 32899 +1904 320 5.39 -0.61 3.74 0 214.09 159.77 32758 +1904 321 8.55 2.55 6.9 0 260.86 155.22 32620 +1904 322 9.62 3.62 7.97 0.04 278.57 114.36 32486 +1904 323 8.56 2.56 6.91 0 261.02 151.8 32354 +1904 324 12.49 6.49 10.84 0 331.25 146.07 32225 +1904 325 11.17 5.17 9.52 0 306.05 145.72 32100 +1904 326 11.98 5.98 10.33 0.61 321.31 107.62 31977 +1904 327 10.27 4.27 8.62 1.93 289.83 107.48 31858 +1904 328 8.15 2.15 6.5 0 254.5 143.14 31743 +1904 329 7.35 1.35 5.7 0.17 242.16 106.7 31631 +1904 330 8.56 2.56 6.91 0.01 261.02 104.93 31522 +1904 331 9.79 3.79 8.14 0.01 281.48 103.19 31417 +1904 332 5.18 -0.82 3.53 0 211.25 139.35 31316 +1904 333 3.27 -2.73 1.62 0 186.92 139.39 31218 +1904 334 -0.7 -6.7 -2.35 0 143.96 140.2 31125 +1904 335 -3.23 -9.23 -4.88 0.01 121.28 147.55 31035 +1904 336 -1.72 -7.72 -3.37 0.23 134.41 147.14 30949 +1904 337 1.02 -4.98 -0.63 0 161.39 178.86 30867 +1904 338 0.85 -5.15 -0.8 0 159.59 177.99 30790 +1904 339 1.29 -4.71 -0.36 0 164.28 176.92 30716 +1904 340 2.75 -3.25 1.1 0.17 180.73 99.11 30647 +1904 341 1.44 -4.56 -0.21 0 165.91 131.87 30582 +1904 342 -1.7 -7.7 -3.35 0 134.59 132.43 30521 +1904 343 0.39 -5.61 -1.26 0.16 154.8 98.06 30465 +1904 344 -0.02 -6.02 -1.67 0.09 150.64 141.02 30413 +1904 345 0.83 -5.17 -0.82 0 159.38 172.62 30366 +1904 346 1.18 -4.82 -0.47 0 163.1 171.82 30323 +1904 347 -0.65 -6.65 -2.3 0 144.44 172.05 30284 +1904 348 5.1 -0.9 3.45 0 210.18 125.29 30251 +1904 349 6.65 0.65 5 1.2 231.79 92.97 30221 +1904 350 7.26 1.26 5.61 0.19 240.81 92.42 30197 +1904 351 3.63 -2.37 1.98 0 191.31 125.18 30177 +1904 352 9.03 3.03 7.38 0 268.69 121.67 30162 +1904 353 11.22 5.22 9.57 0 306.98 119.85 30151 +1904 354 11.91 5.91 10.26 0 319.97 119.22 30145 +1904 355 10.85 4.85 9.2 0 300.2 120.13 30144 +1904 356 9.38 3.38 7.73 0.18 274.51 91 30147 +1904 357 10.12 4.12 8.47 0.42 287.2 90.61 30156 +1904 358 10.53 4.53 8.88 0.21 294.44 90.42 30169 +1904 359 8.09 2.09 6.44 0.39 253.55 91.9 30186 +1904 360 7.89 1.89 6.24 0.1 250.43 92.28 30208 +1904 361 6.9 0.9 5.25 0 235.45 124.04 30235 +1904 362 6.39 0.39 4.74 0.45 228.04 93.6 30267 +1904 363 3.18 -2.82 1.53 0.15 185.83 95.43 30303 +1904 364 7.5 1.5 5.85 0.03 244.43 93.78 30343 +1904 365 4.16 -1.84 2.51 0 197.94 127.67 30388 +1905 1 0.77 -5.23 -0.88 0 158.75 130.26 30438 +1905 2 -4.68 -10.68 -6.33 0 109.74 133.03 30492 +1905 3 -1.38 -7.38 -3.03 0 137.53 132.84 30551 +1905 4 1.89 -4.11 0.24 0 170.88 132.34 30614 +1905 5 -0.05 -6.05 -1.7 0 150.34 133.88 30681 +1905 6 -0.93 -6.93 -2.58 0 141.76 135.14 30752 +1905 7 -1.47 -7.47 -3.12 0 136.7 136.16 30828 +1905 8 -2.19 -8.19 -3.84 0 130.2 137.94 30907 +1905 9 -3.14 -9.14 -4.79 0 122.03 139.56 30991 +1905 10 -4.15 -10.15 -5.8 0 113.84 141.22 31079 +1905 11 -4.55 -10.55 -6.2 0 110.73 142.36 31171 +1905 12 -2.81 -8.81 -4.46 0 124.82 142.79 31266 +1905 13 1.43 -4.57 -0.22 0 165.8 142.61 31366 +1905 14 -1.89 -7.89 -3.54 0 132.87 145.58 31469 +1905 15 1.74 -4.26 0.09 0 169.21 145.39 31575 +1905 16 -0.04 -6.04 -1.69 0 150.44 147.55 31686 +1905 17 0.09 -5.91 -1.56 0.46 151.75 111.89 31800 +1905 18 1.36 -4.64 -0.29 0.45 165.04 112.86 31917 +1905 19 -0.28 -6.28 -1.93 0.22 148.06 156.77 32038 +1905 20 -1.16 -7.16 -2.81 0 139.58 196.92 32161 +1905 21 -2.44 -8.44 -4.09 0 128.01 199.32 32289 +1905 22 -0.22 -6.22 -1.87 0.23 148.65 160.99 32419 +1905 23 -1.33 -7.33 -2.98 0 137.99 202.76 32552 +1905 24 -0.13 -6.13 -1.78 0 149.54 204.12 32688 +1905 25 -1.14 -7.14 -2.79 0 139.77 206.32 32827 +1905 26 -2.5 -8.5 -4.15 0 127.48 208.69 32969 +1905 27 -2.01 -8.01 -3.66 0 131.8 210.35 33114 +1905 28 -1.69 -7.69 -3.34 0.09 134.68 169.7 33261 +1905 29 -2.16 -8.16 -3.81 0.01 130.46 171.51 33411 +1905 30 -1.89 -7.89 -3.54 0 132.87 216.95 33564 +1905 31 -5.58 -11.58 -7.23 0.44 103.06 176.92 33718 +1905 32 1.15 -4.85 -0.5 0 162.78 220.68 33875 +1905 33 -1.22 -7.22 -2.87 0.13 139.02 179.01 34035 +1905 34 -0.18 -6.18 -1.83 0 149.05 226.25 34196 +1905 35 1.06 -4.94 -0.59 0 161.81 227.42 34360 +1905 36 1.83 -4.17 0.18 0 170.21 229.08 34526 +1905 37 6.34 0.34 4.69 0 227.32 227.33 34694 +1905 38 4.53 -1.47 2.88 0.62 202.68 182.89 34863 +1905 39 6.41 0.41 4.76 0 228.32 230.95 35035 +1905 40 3.93 -2.07 2.28 0.06 195.04 185.57 35208 +1905 41 0.21 -5.79 -1.44 0.92 152.96 189.16 35383 +1905 42 -0.49 -6.49 -2.14 0 145.99 242.52 35560 +1905 43 -0.24 -6.24 -1.89 0.18 148.45 193.45 35738 +1905 44 -1.15 -7.15 -2.8 0.29 139.68 196.37 35918 +1905 45 1.37 -4.63 -0.28 0 165.15 249.93 36099 +1905 46 4.06 -1.94 2.41 0.66 196.67 196.85 36282 +1905 47 4.13 -1.87 2.48 0 197.56 252.21 36466 +1905 48 3.52 -2.48 1.87 0 189.96 218.98 36652 +1905 49 3.56 -2.44 1.91 0 190.45 221.74 36838 +1905 50 4.9 -1.1 3.25 0 207.52 223.33 37026 +1905 51 0.96 -5.04 -0.69 0.22 160.75 171.96 37215 +1905 52 3.4 -2.6 1.75 0.01 188.49 172.78 37405 +1905 53 4.06 -1.94 2.41 0 196.67 232.81 37596 +1905 54 5.08 -0.92 3.43 0.04 209.91 176.02 37788 +1905 55 5.47 -0.53 3.82 0 215.17 237.34 37981 +1905 56 9.49 3.49 7.84 0 276.37 235.75 38175 +1905 57 8.22 2.22 6.57 0 255.6 240.08 38370 +1905 58 4.3 -1.7 2.65 0 199.72 246.93 38565 +1905 59 7.31 1.31 5.66 0 241.56 246.69 38761 +1905 60 12.47 6.47 10.82 0 330.86 242.94 38958 +1905 61 12.51 6.51 10.86 0 331.65 245.75 39156 +1905 62 11.64 5.64 9.99 0 314.83 249.77 39355 +1905 63 10.16 4.16 8.51 0 287.9 254.8 39553 +1905 64 4.5 -1.5 2.85 0.22 202.29 198.05 39753 +1905 65 3.22 -2.78 1.57 0.43 186.32 201.11 39953 +1905 66 4.07 -1.93 2.42 0 196.8 270.14 40154 +1905 67 6.23 0.23 4.58 0 225.75 270.9 40355 +1905 68 8.94 2.94 7.29 0 267.2 270.57 40556 +1905 69 8.11 2.11 6.46 0 253.87 274.23 40758 +1905 70 7.21 1.21 5.56 0.03 240.06 208.62 40960 +1905 71 9.59 3.59 7.94 0 278.06 278.04 41163 +1905 72 8.21 2.21 6.56 0 255.44 282.67 41366 +1905 73 7.27 1.27 5.62 0 240.96 286.5 41569 +1905 74 9.85 3.85 8.2 0 282.51 285.86 41772 +1905 75 14.12 8.12 12.47 0.21 364.8 211.17 41976 +1905 76 17.46 11.46 15.81 0.35 442.7 207.91 42179 +1905 77 18.87 12.87 17.22 0 479.6 276.32 42383 +1905 78 11.86 5.86 10.21 0.29 319.01 219.97 42587 +1905 79 10.58 4.58 8.93 1.36 295.33 223.52 42791 +1905 80 8.29 2.29 6.64 0.12 256.71 227.9 42996 +1905 81 6.74 0.74 5.09 0 233.1 308.44 43200 +1905 82 6.19 0.19 4.54 0 225.19 311.78 43404 +1905 83 5.37 -0.63 3.72 0 213.82 315.25 43608 +1905 84 6.27 0.27 4.62 0 226.32 316.75 43812 +1905 85 7.05 1.05 5.4 0.37 237.67 238.72 44016 +1905 86 5.75 -0.25 4.1 0.12 219.02 241.75 44220 +1905 87 5.58 -0.42 3.93 0.35 216.68 243.82 44424 +1905 88 5.32 -0.68 3.67 0.7 213.14 245.84 44627 +1905 89 9.49 3.49 7.84 0.01 276.37 243.36 44831 +1905 90 10.1 4.1 8.45 0 286.85 325.89 45034 +1905 91 14.14 8.14 12.49 0 365.23 320.78 45237 +1905 92 7.86 1.86 6.21 0 249.96 333.77 45439 +1905 93 8.23 2.23 6.58 0.02 255.76 251.6 45642 +1905 94 10.76 4.76 9.11 1.34 298.57 250.25 45843 +1905 95 15.01 9.01 13.36 1.16 384.31 245.64 46045 +1905 96 13.72 7.72 12.07 0.39 356.31 249.26 46246 +1905 97 10.49 4.49 8.84 0 293.72 340.43 46446 +1905 98 8.48 2.48 6.83 0 259.74 345.62 46647 +1905 99 12.52 6.52 10.87 0 331.84 340.72 46846 +1905 100 16.69 10.69 15.04 0 423.59 333.43 47045 +1905 101 15.11 9.11 13.46 0.19 386.56 254.32 47243 +1905 102 15.89 9.89 14.24 0.01 404.48 254.36 47441 +1905 103 13.53 7.53 11.88 0.16 352.34 259.69 47638 +1905 104 11.22 5.22 9.57 0.03 306.98 264.45 47834 +1905 105 12.77 6.77 11.12 1.01 336.82 263.56 48030 +1905 106 9.17 3.17 7.52 0.01 271 269.7 48225 +1905 107 10.73 4.73 9.08 0.47 298.03 268.97 48419 +1905 108 15.15 9.15 13.5 0 387.46 351.25 48612 +1905 109 14.23 8.23 12.58 0 367.17 354.96 48804 +1905 110 11.11 5.11 9.46 0 304.95 362.73 48995 +1905 111 8.97 2.97 7.32 0.47 267.7 276.02 49185 +1905 112 6.51 0.51 4.86 1.46 229.76 279.97 49374 +1905 113 4.78 -1.22 3.13 0.14 205.94 282.72 49561 +1905 114 5.8 -0.2 4.15 0 219.72 377.17 49748 +1905 115 9.11 3.11 7.46 0 270.01 373.67 49933 +1905 116 10.53 4.53 8.88 0 294.44 372.43 50117 +1905 117 11.91 5.91 10.26 0 319.97 371.13 50300 +1905 118 8.83 2.83 7.18 0 265.4 378.05 50481 +1905 119 13.06 7.06 11.41 0 342.67 371.27 50661 +1905 120 10.6 4.6 8.95 0.01 295.69 283.02 50840 +1905 121 10.22 4.22 8.57 0 288.95 379.2 51016 +1905 122 12.62 6.62 10.97 0 333.83 375.72 51191 +1905 123 14.13 8.13 12.48 0 365.02 373.43 51365 +1905 124 13.98 7.98 12.33 0 361.81 374.86 51536 +1905 125 17.06 11.06 15.41 0 432.68 368.08 51706 +1905 126 14.84 8.84 13.19 0.1 380.52 281.11 51874 +1905 127 18.74 12.74 17.09 0 476.09 365.06 52039 +1905 128 17.52 11.52 15.87 0.35 444.22 277.23 52203 +1905 129 16.3 10.3 14.65 0.03 414.18 280.38 52365 +1905 130 16.88 10.88 15.23 0 428.23 373.06 52524 +1905 131 16.19 10.19 14.54 0.11 411.56 281.79 52681 +1905 132 16.05 10.05 14.4 1.27 408.24 282.68 52836 +1905 133 12.76 6.76 11.11 0 336.62 385.48 52989 +1905 134 15.01 9.01 13.36 0.43 384.31 285.74 53138 +1905 135 19.32 13.32 17.67 0.01 491.92 277.13 53286 +1905 136 20.2 14.2 18.55 0.79 516.78 275.43 53430 +1905 137 18.65 12.65 17 1.2 473.68 279.69 53572 +1905 138 19.01 13.01 17.36 1.48 483.41 279.3 53711 +1905 139 18.67 12.67 17.02 1.62 474.21 280.61 53848 +1905 140 13.35 7.35 11.7 0.45 348.61 291.58 53981 +1905 141 17.46 11.46 15.81 0.49 442.7 284.01 54111 +1905 142 19.69 13.69 18.04 0.01 502.24 279.22 54238 +1905 143 14.71 8.71 13.06 0.48 377.64 290.29 54362 +1905 144 14.24 8.24 12.59 0 367.38 388.68 54483 +1905 145 17.71 11.71 16.06 0 449.06 379.92 54600 +1905 146 18.9 12.9 17.25 0 480.41 376.67 54714 +1905 147 19.45 13.45 17.8 0.05 495.53 281.53 54824 +1905 148 20.14 14.14 18.49 0 515.05 373.46 54931 +1905 149 21.58 15.58 19.93 0.12 557.92 276.51 55034 +1905 150 20.22 14.22 18.57 0.82 517.36 280.37 55134 +1905 151 21.46 15.46 19.81 0.82 554.23 277.37 55229 +1905 152 26.17 20.17 24.52 0 715.34 350.21 55321 +1905 153 25.61 19.61 23.96 0 694.32 353.06 55409 +1905 154 26.4 20.4 24.75 0 724.13 349.64 55492 +1905 155 26.15 20.15 24.5 0 714.58 351.01 55572 +1905 156 24.6 18.6 22.95 0.6 657.73 268.79 55648 +1905 157 25.54 19.54 23.89 1.34 691.73 265.75 55719 +1905 158 23.1 17.1 21.45 0.07 606.42 273.76 55786 +1905 159 20.92 14.92 19.27 0.15 537.91 280.14 55849 +1905 160 22.5 16.5 20.85 0 586.86 367.81 55908 +1905 161 22.24 16.24 20.59 0 578.56 368.88 55962 +1905 162 15.64 9.64 13.99 0 398.66 390.07 56011 +1905 163 15.66 9.66 14.01 0.05 399.12 292.68 56056 +1905 164 15.37 9.37 13.72 0.04 392.46 293.28 56097 +1905 165 16.19 10.19 14.54 0 411.56 388.96 56133 +1905 166 15.91 9.91 14.26 0 404.95 389.8 56165 +1905 167 20.19 14.19 18.54 0 516.49 376.75 56192 +1905 168 20.72 14.72 19.07 0 531.97 374.99 56214 +1905 169 20.37 14.37 18.72 0 521.7 376.22 56231 +1905 170 19.95 13.95 18.3 0.06 509.61 283.24 56244 +1905 171 22.11 16.11 20.46 0.41 574.44 277.47 56252 +1905 172 22.16 16.16 20.51 0 576.02 369.75 56256 +1905 173 22.09 16.09 20.44 1.27 573.81 277.5 56255 +1905 174 17.1 11.1 15.45 0.11 433.67 289.87 56249 +1905 175 20.02 14.02 18.37 0.62 511.61 283.01 56238 +1905 176 21.43 15.43 19.78 0.08 553.32 279.24 56223 +1905 177 23.44 17.44 21.79 0 617.74 364.41 56203 +1905 178 25.09 19.09 23.44 0.03 675.27 268.01 56179 +1905 179 23.1 17.1 21.45 0.17 606.42 274.29 56150 +1905 180 19.1 13.1 17.45 0 485.86 380.04 56116 +1905 181 21.18 15.18 19.53 0 545.72 372.87 56078 +1905 182 22.34 16.34 20.69 0.12 581.74 276.29 56035 +1905 183 22.59 16.59 20.94 0 589.76 367.24 55987 +1905 184 26.55 20.55 24.9 0.51 729.9 262.33 55935 +1905 185 27.47 21.47 25.82 0.33 766.21 258.84 55879 +1905 186 24.2 18.2 22.55 0.11 643.7 270.13 55818 +1905 187 23.87 17.87 22.22 0.3 632.32 271.04 55753 +1905 188 23.29 17.29 21.64 0.14 612.72 272.64 55684 +1905 189 27.17 21.17 25.52 0 754.21 345.79 55611 +1905 190 30.66 24.66 29.01 0 904.15 326.21 55533 +1905 191 30.93 24.93 29.28 0 916.73 324.33 55451 +1905 192 25.28 19.28 23.63 0.7 682.18 265.43 55366 +1905 193 25.84 19.84 24.19 0 702.89 351.07 55276 +1905 194 26.93 20.93 25.28 0 744.72 345.63 55182 +1905 195 30.96 24.96 29.31 0 918.14 323.2 55085 +1905 196 30.47 24.47 28.82 0.09 895.39 244.34 54984 +1905 197 29.52 23.52 27.87 0.04 852.64 248.15 54879 +1905 198 29.82 23.82 28.17 0.09 865.95 246.58 54770 +1905 199 28.87 22.87 27.22 0.02 824.39 250.33 54658 +1905 200 24.15 18.15 22.5 0.01 641.97 267.1 54542 +1905 201 22.39 16.39 20.74 0.41 583.34 272.06 54423 +1905 202 23.39 17.39 21.74 0.26 616.06 268.7 54301 +1905 203 22.07 16.07 20.42 0.12 573.18 272.18 54176 +1905 204 23.21 17.21 21.56 0 610.06 358 54047 +1905 205 22.88 16.88 21.23 0.72 599.18 269.1 53915 +1905 206 20.6 14.6 18.95 0.38 528.43 274.96 53780 +1905 207 20.95 14.95 19.3 0.68 538.81 273.56 53643 +1905 208 18.18 12.18 16.53 2.07 461.23 279.8 53502 +1905 209 18.47 12.47 16.82 0.03 468.88 278.65 53359 +1905 210 19.25 13.25 17.6 0 489.98 368.49 53213 +1905 211 19.88 13.88 18.23 0 507.62 365.67 53064 +1905 212 20.45 14.45 18.8 0.66 524.04 272.24 52913 +1905 213 16.87 10.87 15.22 0.02 427.99 279.87 52760 +1905 214 14.13 8.13 12.48 0 365.02 379.34 52604 +1905 215 14.55 8.55 12.9 0.55 374.12 283.23 52445 +1905 216 18.05 12.05 16.4 0 457.83 367.33 52285 +1905 217 17.73 11.73 16.08 0 449.57 367.35 52122 +1905 218 20.43 14.43 18.78 0 523.45 358.15 51958 +1905 219 19.6 13.6 17.95 0.15 499.72 269.86 51791 +1905 220 15.99 9.99 14.34 0.96 406.83 276.92 51622 +1905 221 22.82 16.82 21.17 0.01 597.22 260 51451 +1905 222 19.43 13.43 17.78 0.39 494.97 268.02 51279 +1905 223 19.48 13.48 17.83 0.53 496.36 267.04 51105 +1905 224 20.42 14.42 18.77 0.22 523.16 263.98 50929 +1905 225 21.06 15.06 19.41 0.02 542.1 261.51 50751 +1905 226 24.07 18.07 22.42 0.02 639.2 252.29 50572 +1905 227 27.04 21.04 25.39 0 749.06 322.19 50392 +1905 228 25.27 19.27 23.62 0.01 681.82 246.75 50210 +1905 229 23.38 17.38 21.73 0.2 615.73 251.61 50026 +1905 230 24.53 18.53 22.88 1.11 655.26 247.27 49842 +1905 231 23.2 17.2 21.55 0.32 609.73 250.12 49656 +1905 232 25.57 19.57 23.92 0 692.84 322.63 49469 +1905 233 28.43 22.43 26.78 0 805.71 308.02 49280 +1905 234 27.23 21.23 25.58 2.04 756.6 234.38 49091 +1905 235 29.68 23.68 28.03 0 859.71 298.93 48900 +1905 236 33.48 27.48 31.83 0.01 1042.97 206.58 48709 +1905 237 29.39 23.39 27.74 0.05 846.92 223.25 48516 +1905 238 28.17 22.17 26.52 0.06 794.85 226.69 48323 +1905 239 28.81 22.81 27.16 0 821.82 297.73 48128 +1905 240 28.51 22.51 26.86 1.41 809.08 223.2 47933 +1905 241 28.55 22.55 26.9 0.16 810.77 221.87 47737 +1905 242 25.84 19.84 24.19 0 702.89 306.51 47541 +1905 243 25.33 19.33 23.68 0 684.01 306.87 47343 +1905 244 21.73 15.73 20.08 0 562.55 318.4 47145 +1905 245 23.58 17.58 21.93 0 622.45 310.14 46947 +1905 246 20.84 14.84 19.19 0 535.53 317.55 46747 +1905 247 20.04 14.04 18.39 1.51 512.18 238.63 46547 +1905 248 22.05 16.05 20.4 0.53 572.55 232.45 46347 +1905 249 22.93 16.93 21.28 0.03 600.82 228.7 46146 +1905 250 21.65 15.65 20 0 560.08 307.34 45945 +1905 251 23.47 17.47 21.82 0 618.75 299.14 45743 +1905 252 19.37 13.37 17.72 0.08 493.3 232.5 45541 +1905 253 19.14 13.14 17.49 0 486.96 308.55 45339 +1905 254 17.97 11.97 16.32 0.01 455.76 232.15 45136 +1905 255 24.53 18.53 22.88 0.01 655.26 215.29 44933 +1905 256 21.41 15.41 19.76 0.01 552.71 221.55 44730 +1905 257 21.19 15.19 19.54 0 546.02 293.98 44527 +1905 258 20.02 14.02 18.37 0.6 511.61 221.33 44323 +1905 259 18.16 12.16 16.51 1.46 460.7 223.25 44119 +1905 260 19.42 13.42 17.77 0 494.69 292.04 43915 +1905 261 21.19 15.19 19.54 0.8 546.02 213.49 43711 +1905 262 20.72 14.72 19.07 1.33 531.97 212.79 43507 +1905 263 15.16 9.16 13.51 0.29 387.69 221.14 43303 +1905 264 17.31 11.31 15.66 0 438.92 287.58 43099 +1905 265 21.53 15.53 19.88 0 556.38 274.21 42894 +1905 266 17.88 11.88 16.23 0.1 453.43 211.08 42690 +1905 267 19.77 13.77 18.12 0 504.5 274.1 42486 +1905 268 17.48 11.48 15.83 0 443.2 277.2 42282 +1905 269 14.67 8.67 13.02 0.05 376.76 210.44 42078 +1905 270 15.13 9.13 13.48 0 387.01 277.05 41875 +1905 271 19.87 13.87 18.22 0 507.33 263.79 41671 +1905 272 20.47 14.47 18.82 0 524.62 259.59 41468 +1905 273 21.56 15.56 19.91 0.16 557.3 190.65 41265 +1905 274 8.46 2.46 6.81 0.81 259.42 207.73 41062 +1905 275 7.42 1.42 5.77 0.02 243.22 206.55 40860 +1905 276 9.49 3.49 7.84 0 276.37 270.05 40658 +1905 277 8.81 2.81 7.16 0 265.08 268.21 40456 +1905 278 10.66 4.66 9.01 0.16 296.77 197.12 40255 +1905 279 9.07 3.07 7.42 0.4 269.35 196.57 40054 +1905 280 9.05 3.05 7.4 0.42 269.02 194.56 39854 +1905 281 8.23 2.23 6.58 1.63 255.76 193.23 39654 +1905 282 14.25 8.25 12.6 0.76 367.6 184.71 39455 +1905 283 17.35 11.35 15.7 0.92 439.92 178.3 39256 +1905 284 16.54 10.54 14.89 0.21 419.95 177.28 39058 +1905 285 13.06 7.06 11.41 0 342.67 239.75 38861 +1905 286 12.86 6.86 11.21 0.75 338.63 177.97 38664 +1905 287 10.61 4.61 8.96 0.26 295.87 178.13 38468 +1905 288 10.14 4.14 8.49 0.23 287.55 176.48 38273 +1905 289 11.35 5.35 9.7 0 309.39 231.08 38079 +1905 290 10.98 4.98 9.33 0.04 302.56 171.52 37885 +1905 291 10.99 4.99 9.34 1.02 302.75 169.48 37693 +1905 292 7.83 1.83 6.18 0.28 249.5 170.2 37501 +1905 293 5.97 -0.03 4.32 2.07 222.09 169.49 37311 +1905 294 5.66 -0.34 4.01 1.59 217.78 167.5 37121 +1905 295 6.22 0.22 4.57 0 225.61 219.93 36933 +1905 296 5.05 -0.95 3.4 0.09 209.51 163.74 36745 +1905 297 2.61 -3.39 0.96 0.05 179.09 163.08 36560 +1905 298 4.22 -1.78 2.57 0.15 198.7 160.16 36375 +1905 299 7.86 1.86 6.21 0.11 249.96 155.63 36191 +1905 300 6.91 0.91 5.26 0.31 235.6 154.28 36009 +1905 301 4.51 -1.49 2.86 0 202.42 205.19 35829 +1905 302 7.49 1.49 5.84 0 244.28 199.98 35650 +1905 303 6.24 0.24 4.59 0.41 225.9 148.87 35472 +1905 304 3.92 -2.08 2.27 2.05 194.91 148.37 35296 +1905 305 5.38 -0.62 3.73 0.77 213.95 145.45 35122 +1905 306 7.64 1.64 5.99 0.59 246.57 142.29 34950 +1905 307 8.25 2.25 6.6 1.02 256.08 139.98 34779 +1905 308 7.49 1.49 5.84 1.31 244.28 138.54 34610 +1905 309 12.01 6.01 10.36 0.54 321.89 133.34 34444 +1905 310 13.47 7.47 11.82 0.27 351.09 130.21 34279 +1905 311 11.69 5.69 10.04 0.12 315.78 130.2 34116 +1905 312 9.82 3.82 8.17 0.08 282 129.71 33956 +1905 313 9.54 3.54 7.89 0 277.21 171.11 33797 +1905 314 8.2 2.2 6.55 0.09 255.28 127.8 33641 +1905 315 6.06 0.06 4.41 1.61 223.35 127.21 33488 +1905 316 5.47 -0.53 3.82 1.06 215.17 125.89 33337 +1905 317 8.32 2.32 6.67 0.02 257.19 122.55 33188 +1905 318 8.98 2.98 7.33 0.16 267.86 120.37 33042 +1905 319 9.01 3.01 7.36 0.1 268.36 119.08 32899 +1905 320 8.92 2.92 7.27 1.1 266.88 117.75 32758 +1905 321 5.97 -0.03 4.32 0 222.09 157.24 32620 +1905 322 8.8 2.8 7.15 0.07 264.91 114.9 32486 +1905 323 9.79 3.79 8.14 0.65 281.48 113.05 32354 +1905 324 7.36 1.36 5.71 0.48 242.31 113.04 32225 +1905 325 7.98 1.98 6.33 0.04 251.83 111.39 32100 +1905 326 7.44 1.44 5.79 0.51 243.52 110.62 31977 +1905 327 9.81 3.81 8.16 1.4 281.82 107.79 31858 +1905 328 9.06 3.06 7.41 1.05 269.18 106.81 31743 +1905 329 8.57 2.57 6.92 0.87 261.19 105.99 31631 +1905 330 6.88 0.88 5.23 0.22 235.16 105.87 31522 +1905 331 6.77 0.77 5.12 0.02 233.54 104.95 31417 +1905 332 7.01 1.01 5.36 0.14 237.08 103.6 31316 +1905 333 8.39 2.39 6.74 0.72 258.3 102.02 31218 +1905 334 6.99 0.99 5.34 0 236.78 135.97 31125 +1905 335 1.4 -4.6 -0.25 0 165.48 138.06 31035 +1905 336 2.51 -3.49 0.86 0 177.93 136.43 30949 +1905 337 6.83 0.83 5.18 0 234.42 132.19 30867 +1905 338 6.14 0.14 4.49 0 224.48 131.71 30790 +1905 339 5.63 -0.37 3.98 0 217.37 131.25 30716 +1905 340 1.16 -4.84 -0.49 0 162.88 132.93 30647 +1905 341 3.19 -2.81 1.54 0 185.95 131 30582 +1905 342 2.36 -3.64 0.71 0.03 176.2 98 30521 +1905 343 2.65 -3.35 1 0 179.56 129.69 30465 +1905 344 2.33 -3.67 0.68 0 175.86 128.71 30413 +1905 345 5.17 -0.83 3.52 0.05 211.12 95.06 30366 +1905 346 3.73 -2.27 2.08 0 192.55 127.01 30323 +1905 347 3.33 -2.67 1.68 0 187.64 126.62 30284 +1905 348 1.07 -4.93 -0.58 0 161.92 127.37 30251 +1905 349 3.65 -2.35 2 0 191.56 125.72 30221 +1905 350 1.55 -4.45 -0.1 0 167.11 126.43 30197 +1905 351 4.8 -1.2 3.15 0 206.2 124.54 30177 +1905 352 6.65 0.65 5 0 231.79 123.32 30162 +1905 353 7.51 1.51 5.86 0 244.59 122.69 30151 +1905 354 5.13 -0.87 3.48 0 210.58 124.15 30145 +1905 355 4.52 -1.48 2.87 0 202.55 124.5 30144 +1905 356 3.91 -2.09 2.26 0 194.79 124.86 30147 +1905 357 0.68 -5.32 -0.97 0 157.8 126.49 30156 +1905 358 2.49 -3.51 0.84 0.09 177.7 94.3 30169 +1905 359 4.89 -1.11 3.24 0 207.39 124.58 30186 +1905 360 5.46 -0.54 3.81 0 215.04 124.61 30208 +1905 361 5.27 -0.73 3.62 0 212.46 125.05 30235 +1905 362 4.71 -1.29 3.06 0 205.02 125.82 30267 +1905 363 7.89 1.89 6.24 0 250.43 124.38 30303 +1905 364 11.32 5.32 9.67 0 308.83 122.07 30343 +1905 365 7.05 1.05 5.4 0.04 237.67 94.43 30388 +1906 1 4.29 -1.71 2.64 0 199.59 128.49 30438 +1906 2 3.02 -2.98 1.37 0 183.92 129.91 30492 +1906 3 2.15 -3.85 0.5 0 173.81 131.3 30551 +1906 4 2.22 -3.78 0.57 0 174.6 132.18 30614 +1906 5 4.43 -1.57 2.78 1.16 201.39 98.73 30681 +1906 6 5.62 -0.38 3.97 0.43 217.23 98.86 30752 +1906 7 5.43 -0.57 3.78 0.04 214.63 99.54 30828 +1906 8 3.38 -2.62 1.73 0 188.25 135.4 30907 +1906 9 2.62 -3.38 0.97 0 179.21 137.06 30991 +1906 10 3.56 -2.44 1.91 0.01 190.45 103.39 31079 +1906 11 1.2 -4.8 -0.45 0 163.31 140.08 31171 +1906 12 -0.82 -6.82 -2.47 0 142.8 142.01 31266 +1906 13 5.68 -0.32 4.03 0 218.05 140.18 31366 +1906 14 0.11 -5.89 -1.54 0.06 151.95 108.54 31469 +1906 15 -2.08 -8.08 -3.73 0.13 131.17 152.54 31575 +1906 16 -1.31 -7.31 -2.96 0.01 138.18 153.16 31686 +1906 17 -0.59 -6.59 -2.24 0 145.02 191.43 31800 +1906 18 -0.82 -6.82 -2.47 0.05 142.8 155.56 31917 +1906 19 -0.61 -6.61 -2.26 0.18 144.83 157.34 32038 +1906 20 -0.29 -6.29 -1.94 0.52 147.96 159.82 32161 +1906 21 0.82 -5.18 -0.83 0.09 159.27 160.66 32289 +1906 22 -1.19 -7.19 -2.84 0 139.3 202.28 32419 +1906 23 -4.12 -10.12 -5.77 0 114.08 205.08 32552 +1906 24 0.41 -5.59 -1.24 0.46 155.01 164.46 32688 +1906 25 -1.29 -7.29 -2.94 0.84 138.37 168.77 32827 +1906 26 1.93 -4.07 0.28 0.33 171.33 168.57 32969 +1906 27 6.38 0.38 4.73 0 227.89 207.98 33114 +1906 28 5.6 -0.4 3.95 0 216.95 209.89 33261 +1906 29 4.56 -1.44 2.91 0 203.07 212.26 33411 +1906 30 4.96 -1.04 3.31 0.07 208.32 170.4 33564 +1906 31 3.7 -2.3 2.05 0 192.17 216.04 33718 +1906 32 1.95 -4.05 0.3 0 171.55 218.84 33875 +1906 33 2.97 -3.03 1.32 0 183.33 220.31 34035 +1906 34 7.36 1.36 5.71 0 242.31 218.16 34196 +1906 35 5.12 -0.88 3.47 0 210.45 183.44 34360 +1906 36 5.9 -0.1 4.25 0 221.11 185.34 34526 +1906 37 3.13 -2.87 1.48 0 185.23 189.8 34694 +1906 38 5.35 -0.65 3.7 0 213.54 190.93 34863 +1906 39 6.39 0.39 4.74 1.7 228.04 144.51 35035 +1906 40 5.53 -0.47 3.88 1.94 215.99 147 35208 +1906 41 2.38 -3.62 0.73 0.09 176.43 150.7 35383 +1906 42 2.7 -3.3 1.05 0 180.14 203.29 35560 +1906 43 0.77 -5.23 -0.88 0.03 158.75 155.45 35738 +1906 44 -0.46 -6.46 -2.11 0 146.29 210.59 35918 +1906 45 1.84 -4.16 0.19 0 170.32 211.82 36099 +1906 46 1.32 -4.68 -0.33 0.07 164.61 161.15 36282 +1906 47 5.2 -0.8 3.55 0.45 211.52 161.11 36466 +1906 48 2.27 -3.73 0.62 0.24 175.17 164.93 36652 +1906 49 3.57 -2.43 1.92 0 190.57 221.73 36838 +1906 50 5.82 -0.18 4.17 0.11 219.99 166.89 37026 +1906 51 8.45 2.45 6.8 0 259.26 222.86 37215 +1906 52 9.81 3.81 8.16 0 281.82 224.11 37405 +1906 53 10.33 4.33 8.68 0.21 290.89 169.8 37596 +1906 54 1.88 -4.12 0.23 0.01 170.77 177.96 37788 +1906 55 0.28 -5.72 -1.37 0.27 153.68 181.06 37981 +1906 56 1.83 -4.17 0.18 0 170.21 243.06 38175 +1906 57 0.46 -5.54 -1.19 0.05 155.52 185.21 38370 +1906 58 1.86 -4.14 0.21 0 170.54 248.91 38565 +1906 59 0.84 -5.16 -0.81 0.03 159.48 189.3 38761 +1906 60 5.89 -0.11 4.24 0 220.97 251.05 38958 +1906 61 10.17 4.17 8.52 0.08 288.07 186.79 39156 +1906 62 11.14 5.14 9.49 0.13 305.5 187.86 39355 +1906 63 12.42 6.42 10.77 1.29 329.87 188.67 39553 +1906 64 11.21 5.21 9.56 0.19 306.79 192.16 39753 +1906 65 10.4 4.4 8.75 0.01 292.12 195.15 39953 +1906 66 4.89 -1.11 3.24 1.19 207.39 202.02 40154 +1906 67 7.49 1.49 5.84 0.1 244.28 202.12 40355 +1906 68 5.63 -0.37 3.98 0 217.37 274.42 40556 +1906 69 11.66 5.66 10.01 0 315.21 269.34 40758 +1906 70 10.12 4.12 8.47 0 287.2 274.41 40960 +1906 71 9.82 3.82 8.17 0 282 277.72 41163 +1906 72 13 7 11.35 0 341.45 275.6 41366 +1906 73 7.47 1.47 5.82 0.36 243.98 214.69 41569 +1906 74 7.46 1.46 5.81 0 243.83 289.02 41772 +1906 75 6.29 0.29 4.64 0 226.61 293.14 41976 +1906 76 6.8 0.8 5.15 0.03 233.98 221.4 42179 +1906 77 4.28 -1.72 2.63 0 199.47 300.6 42383 +1906 78 4.22 -1.78 2.57 0.31 198.7 227.52 42587 +1906 79 -2.58 -8.58 -4.23 0.09 126.79 264.86 42791 +1906 80 -1.2 -7.2 -2.85 0 139.21 344.3 42996 +1906 81 2.05 -3.95 0.4 0.29 172.67 265.62 43200 +1906 82 6.55 0.55 4.9 0.01 230.34 233.51 43404 +1906 83 9.4 3.4 7.75 0 274.85 310.02 43608 +1906 84 7.85 1.85 6.2 0.63 249.81 236.05 43812 +1906 85 9.81 3.81 8.16 0 281.82 314.43 44016 +1906 86 12.94 6.94 11.29 0.03 340.24 233.65 44220 +1906 87 12.6 6.6 10.95 0 333.43 314.66 44424 +1906 88 10.84 4.84 9.19 0 300.02 320.06 44627 +1906 89 7.78 1.78 6.13 0.57 248.73 245.22 44831 +1906 90 5.65 -0.35 4 0.62 217.64 249.07 45034 +1906 91 10.47 4.47 8.82 0.24 293.37 245.66 45237 +1906 92 12.51 6.51 10.86 0 331.65 326.19 45439 +1906 93 14.71 8.71 13.06 0 377.64 323.95 45642 +1906 94 17.65 11.65 16 0 447.52 319.13 45843 +1906 95 17.26 11.26 15.61 0.01 437.66 241.65 46045 +1906 96 12.43 6.43 10.78 0.2 330.07 251.17 46246 +1906 97 12.63 6.63 10.98 0.24 334.03 252.41 46446 +1906 98 12.81 6.81 11.16 0.37 337.62 253.61 46647 +1906 99 17.9 11.9 16.25 0 453.94 328.42 46846 +1906 100 15.75 9.75 14.1 0.04 401.21 251.79 47045 +1906 101 15.56 9.56 13.91 0 396.81 338.06 47243 +1906 102 17.3 11.3 15.65 0.02 438.67 251.71 47441 +1906 103 16.59 10.59 14.94 0.03 421.16 254.42 47638 +1906 104 17.67 11.67 16.02 0.12 448.04 253.64 47834 +1906 105 14.52 8.52 12.87 0.04 373.46 260.77 48030 +1906 106 12.15 6.15 10.5 0.18 324.6 265.72 48225 +1906 107 11.18 5.18 9.53 0.79 306.24 268.36 48419 +1906 108 13.12 7.12 11.47 0.06 343.89 266.81 48612 +1906 109 14.3 8.3 12.65 0 368.68 354.8 48804 +1906 110 13.12 7.12 11.47 0.11 343.89 269.07 48995 +1906 111 12.5 6.5 10.85 0 331.45 361.59 49185 +1906 112 13.08 7.08 11.43 0 343.08 361.91 49374 +1906 113 11.3 5.3 9.65 0 308.46 366.82 49561 +1906 114 10.99 4.99 9.34 0 302.75 368.9 49748 +1906 115 11.36 5.36 9.71 0 309.57 369.65 49933 +1906 116 10.07 4.07 8.42 0.02 286.32 279.94 50117 +1906 117 8.56 2.56 6.91 0 261.02 377.15 50300 +1906 118 11.41 5.41 9.76 0.3 310.51 280.07 50481 +1906 119 12.67 6.67 11.02 0 334.82 372.1 50661 +1906 120 16.41 10.41 14.76 0 416.81 364.48 50840 +1906 121 23.8 17.8 22.15 0 629.93 341.37 51016 +1906 122 22.04 16.04 20.39 0.17 572.24 261.92 51191 +1906 123 21.62 15.62 19.97 0.5 559.15 263.79 51365 +1906 124 15.57 9.57 13.92 0 397.04 371.03 51536 +1906 125 17.05 11.05 15.4 0.63 432.43 276.08 51706 +1906 126 16.56 10.56 14.91 0.99 420.43 277.82 51874 +1906 127 16.52 10.52 14.87 0.01 419.46 278.56 52039 +1906 128 17.22 11.22 15.57 1.45 436.66 277.87 52203 +1906 129 17.15 11.15 15.5 0.04 434.92 278.65 52365 +1906 130 17.16 11.16 15.51 0 435.17 372.29 52524 +1906 131 18.47 12.47 16.82 0 468.88 369.26 52681 +1906 132 16.84 10.84 15.19 0 427.25 374.78 52836 +1906 133 13.73 7.73 12.08 0.3 356.52 287.49 52989 +1906 134 17.92 11.92 16.27 0.24 454.46 279.83 53138 +1906 135 21.63 15.63 19.98 0 559.46 361.62 53286 +1906 136 17.67 11.67 16.02 0.39 448.04 281.37 53430 +1906 137 17.85 11.85 16.2 0.64 452.65 281.5 53572 +1906 138 18.75 12.75 17.1 0.06 476.36 279.91 53711 +1906 139 17.66 11.66 16.01 0 447.78 377.18 53848 +1906 140 21.67 15.67 20.02 0 560.7 364.49 53981 +1906 141 16.02 10.02 14.37 0 407.53 382.66 54111 +1906 142 15.12 9.12 13.47 0.02 386.79 289.12 54238 +1906 143 14.2 8.2 12.55 0 366.52 388.29 54362 +1906 144 15.89 9.89 14.24 0.26 404.48 288.4 54483 +1906 145 15.88 9.88 14.23 0.22 404.24 288.77 54600 +1906 146 18.15 12.15 16.5 0.94 460.44 284.24 54714 +1906 147 20.29 14.29 18.64 0 519.38 372.58 54824 +1906 148 19.87 13.87 18.22 0.24 507.33 280.78 54931 +1906 149 18.07 12.07 16.42 0.82 458.35 285.3 55034 +1906 150 17.61 11.61 15.96 0.09 446.5 286.57 55134 +1906 151 19.59 13.59 17.94 0 499.44 376.33 55229 +1906 152 20.35 14.35 18.7 0 521.12 373.88 55321 +1906 153 22.52 16.52 20.87 0.01 587.51 274.63 55409 +1906 154 25.26 19.26 23.61 0.6 681.45 266.22 55492 +1906 155 24.29 18.29 22.64 0.76 646.84 269.57 55572 +1906 156 20.93 14.93 19.28 0.47 538.21 279.68 55648 +1906 157 20.55 14.55 18.9 0.04 526.96 280.81 55719 +1906 158 20.72 14.72 19.07 0.04 531.97 280.49 55786 +1906 159 20.39 14.39 18.74 0.01 522.29 281.53 55849 +1906 160 16.47 10.47 14.82 0.27 418.26 290.78 55908 +1906 161 18.01 12.01 16.36 0.74 456.79 287.49 55962 +1906 162 16.56 10.56 14.91 0.14 420.43 290.69 56011 +1906 163 15.55 9.55 13.9 0.36 396.58 292.89 56056 +1906 164 21.88 15.88 20.23 0 567.22 370.56 56097 +1906 165 24.31 18.31 22.66 0.55 647.54 270.64 56133 +1906 166 26.42 20.42 24.77 0.26 724.89 263.46 56165 +1906 167 24.51 18.51 22.86 0.15 654.55 270.01 56192 +1906 168 20.94 14.94 19.29 0.24 538.51 280.65 56214 +1906 169 18.92 12.92 17.27 0.23 480.96 285.78 56231 +1906 170 15.97 9.97 14.32 1.39 406.36 292.26 56244 +1906 171 17.38 11.38 15.73 0.74 440.68 289.34 56252 +1906 172 20.56 14.56 18.91 0 527.26 375.61 56256 +1906 173 22.7 16.7 21.05 0 593.32 367.64 56255 +1906 174 24.84 18.84 23.19 0 666.28 358.59 56249 +1906 175 21.35 15.35 19.7 0.03 550.88 279.49 56238 +1906 176 15.46 9.46 13.81 2.21 394.52 293.18 56223 +1906 177 14.78 8.78 13.13 0.41 379.19 294.4 56203 +1906 178 15.68 9.68 14.03 0.05 399.59 292.68 56179 +1906 179 15.26 9.26 13.61 0.01 389.95 293.42 56150 +1906 180 18.54 12.54 16.89 0 470.74 381.81 56116 +1906 181 23.23 17.23 21.58 0 610.73 365.01 56078 +1906 182 24.47 18.47 22.82 0.08 653.15 269.74 56035 +1906 183 22.37 16.37 20.72 0.06 582.7 276.07 55987 +1906 184 22.8 16.8 21.15 0 596.57 366.26 55935 +1906 185 24.55 18.55 22.9 0 655.97 358.91 55879 +1906 186 18.87 12.87 17.22 0.14 479.6 284.91 55818 +1906 187 18.6 12.6 16.95 1.01 472.34 285.4 55753 +1906 188 18.78 12.78 17.13 2.95 477.17 284.78 55684 +1906 189 17.85 11.85 16.2 0.84 452.65 286.78 55611 +1906 190 20.5 14.5 18.85 0.18 525.5 280.1 55533 +1906 191 19.02 13.02 17.37 0 483.68 378.12 55451 +1906 192 18.01 12.01 16.36 0.27 456.79 285.7 55366 +1906 193 16.72 10.72 15.07 0.27 424.32 288.3 55276 +1906 194 19.57 13.57 17.92 0.47 498.88 281.65 55182 +1906 195 22.48 16.48 20.83 0 586.22 364.88 55085 +1906 196 23.29 17.29 21.64 0 612.72 361.28 54984 +1906 197 23.61 17.61 21.96 0.04 623.47 269.64 54879 +1906 198 21.59 15.59 19.94 0 558.23 366.96 54770 +1906 199 24.27 18.27 22.62 0 646.14 356.01 54658 +1906 200 23.35 17.35 21.7 0.37 614.73 269.58 54542 +1906 201 28.19 22.19 26.54 0 795.68 336.6 54423 +1906 202 27.86 21.86 26.21 0.11 782.06 253.34 54301 +1906 203 26.34 20.34 24.69 1.56 721.82 258.62 54176 +1906 204 24.09 18.09 22.44 0.44 639.89 265.8 54047 +1906 205 25.49 19.49 23.84 0 689.89 347.79 53915 +1906 206 23.01 17.01 21.36 0 603.45 357.73 53780 +1906 207 24.06 18.06 22.41 0 638.85 352.83 53643 +1906 208 21.71 15.71 20.06 0 561.93 361.37 53502 +1906 209 22.22 16.22 20.57 0 577.92 358.84 53359 +1906 210 23.02 17.02 21.37 0 603.78 355.16 53213 +1906 211 21.73 15.73 20.08 0.55 562.55 269.45 53064 +1906 212 21.15 15.15 19.5 1.25 544.81 270.42 52913 +1906 213 21.64 15.64 19.99 0 559.77 358.06 52760 +1906 214 23.76 17.76 22.11 0.75 628.56 261.9 52604 +1906 215 18.75 12.75 17.1 0.36 476.36 274.69 52445 +1906 216 24.09 18.09 22.44 0.15 639.89 259.65 52285 +1906 217 19.96 13.96 18.31 0.13 509.9 270.39 52122 +1906 218 17.02 11.02 15.37 0 431.69 368.51 51958 +1906 219 14.41 8.41 12.76 0.21 371.06 280.57 51791 +1906 220 19.04 13.04 17.39 0 484.22 360.62 51622 +1906 221 18.48 12.48 16.83 0 469.14 361.31 51451 +1906 222 23.96 17.96 22.31 0 635.41 341.17 51279 +1906 223 25.73 19.73 24.08 0 698.78 332.56 51105 +1906 224 29.19 23.19 27.54 0 838.19 314.7 50929 +1906 225 24.52 18.52 22.87 0.58 654.91 251.74 50751 +1906 226 26.93 20.93 25.28 0.37 744.72 242.93 50572 +1906 227 22.74 16.74 21.09 0 594.62 340.3 50392 +1906 228 25.4 19.4 23.75 1.41 686.58 246.33 50210 +1906 229 20.76 14.76 19.11 0.18 533.15 258.64 50026 +1906 230 25.08 19.08 23.43 0 674.91 327.41 49842 +1906 231 28.92 22.92 27.27 0 826.53 308.08 49656 +1906 232 27.44 21.44 25.79 0 765.01 314.17 49469 +1906 233 27.67 21.67 26.02 0.09 774.3 233.81 49280 +1906 234 24.24 18.24 22.59 0.23 645.09 244.06 49091 +1906 235 18.82 12.82 17.17 1.53 478.25 256.87 48900 +1906 236 22.21 16.21 20.56 0 577.6 330.19 48709 +1906 237 17.32 11.32 15.67 0.54 439.17 257.68 48516 +1906 238 18.04 12.04 16.39 0.16 457.57 254.96 48323 +1906 239 20.18 14.18 18.53 0 516.2 332.16 48128 +1906 240 18.91 12.91 17.26 0 480.69 334.21 47933 +1906 241 17.65 11.65 16 0.15 447.52 251.98 47737 +1906 242 18.7 12.7 17.05 0 475.02 331.35 47541 +1906 243 19.85 13.85 18.2 0.43 506.77 244.61 47343 +1906 244 18.42 12.42 16.77 0 467.55 328.44 47145 +1906 245 21.33 15.33 19.68 0 550.27 317.91 46947 +1906 246 20.53 14.53 18.88 0.21 526.38 238.88 46747 +1906 247 18.69 12.69 17.04 0.38 474.75 241.53 46547 +1906 248 19.99 13.99 18.34 2.06 510.75 237.3 46347 +1906 249 16.21 10.21 14.56 0.55 412.03 243.28 46146 +1906 250 16.84 10.84 15.19 0 427.25 320.9 45945 +1906 251 17.21 11.21 15.56 0.03 436.41 238.4 45743 +1906 252 13.61 7.61 11.96 1.41 354.01 242.79 45541 +1906 253 18.91 12.91 17.26 0 480.69 309.18 45339 +1906 254 20.63 14.63 18.98 0.01 529.31 226.63 45136 +1906 255 16.96 10.96 15.31 0.36 430.2 232.34 44933 +1906 256 15.61 9.61 13.96 0 397.97 310.61 44730 +1906 257 15.59 9.59 13.94 0 397.51 308.48 44527 +1906 258 18.69 12.69 17.04 0.04 474.75 224.04 44323 +1906 259 20.07 14.07 18.42 0 513.04 292.59 44119 +1906 260 20.91 14.91 19.26 0 537.61 287.85 43915 +1906 261 19.55 13.55 17.9 0.04 498.32 216.96 43711 +1906 262 15.78 9.78 14.13 0.17 401.91 222.02 43507 +1906 263 13.87 7.87 12.22 0.61 359.47 223.06 43303 +1906 264 15.46 9.46 13.81 0 394.52 291.65 43099 +1906 265 17.03 11.03 15.38 0 431.94 285.87 42894 +1906 266 16.33 10.33 14.68 0.22 414.89 213.72 42690 +1906 267 18.27 12.27 16.62 0.8 463.59 208.4 42486 +1906 268 16.43 10.43 14.78 0.52 417.29 209.64 42282 +1906 269 15.22 9.22 13.57 0 389.05 279.51 42078 +1906 270 15.69 9.69 14.04 1.91 399.82 206.95 41875 +1906 271 16.16 10.16 14.51 0.35 410.84 204.27 41671 +1906 272 15.76 9.76 14.11 0.33 401.44 202.85 41468 +1906 273 14.71 8.71 13.06 0.1 377.64 202.48 41265 +1906 274 12.49 6.49 10.84 0 331.25 271.17 41062 +1906 275 13.35 7.35 11.7 0.13 348.61 200.21 40860 +1906 276 12.88 6.88 11.23 0 339.03 265.02 40658 +1906 277 14.92 8.92 13.27 0 382.3 258.82 40456 +1906 278 12.32 6.32 10.67 0 327.91 260.36 40255 +1906 279 10.75 4.75 9.1 0 298.39 259.84 40054 +1906 280 11.88 5.88 10.23 0 319.39 255.53 39854 +1906 281 14.6 8.6 12.95 0 375.22 248.4 39654 +1906 282 11.76 5.76 10.11 0.88 317.1 187.65 39455 +1906 283 10.04 4.04 8.39 0.12 285.8 187.3 39256 +1906 284 13.28 7.28 11.63 0 347.17 242.04 39058 +1906 285 11.58 5.58 9.93 0.05 313.7 181.45 38861 +1906 286 10.99 4.99 9.34 0.15 302.75 179.97 38664 +1906 287 12.49 6.49 10.84 0 331.25 234.91 38468 +1906 288 15.37 9.37 13.72 0 392.46 227.56 38273 +1906 289 15.72 9.72 14.07 0 400.51 224.36 38079 +1906 290 15.7 9.7 14.05 0.03 400.05 166.19 37885 +1906 291 15.21 9.21 13.56 0 388.82 219.76 37693 +1906 292 15.63 9.63 13.98 0 398.43 216.41 37501 +1906 293 10.99 4.99 9.34 0.07 302.75 165.4 37311 +1906 294 12.34 6.34 10.69 0 328.3 215.87 37121 +1906 295 10.84 4.84 9.19 0.51 300.02 161.24 36933 +1906 296 10.71 4.71 9.06 0 297.67 212.55 36745 +1906 297 14.39 8.39 12.74 0.07 370.63 153.64 36560 +1906 298 9.5 3.5 7.85 0 276.54 208.59 36375 +1906 299 13.1 7.1 11.45 0.34 343.48 151.04 36191 +1906 300 15.02 9.02 13.37 0 384.54 195.99 36009 +1906 301 16.29 10.29 14.64 0.05 413.94 143.66 35829 +1906 302 14.55 8.55 12.9 0.46 374.12 143.75 35650 +1906 303 17.54 11.54 15.89 0.07 444.72 138.33 35472 +1906 304 14.42 8.42 12.77 0 371.28 186.91 35296 +1906 305 6.95 0.95 5.3 0.96 236.19 144.46 35122 +1906 306 8.63 2.63 6.98 0.37 262.15 141.59 34950 +1906 307 7.5 1.5 5.85 0 244.43 187.32 34779 +1906 308 6.42 0.42 4.77 0.32 228.47 139.22 34610 +1906 309 3.93 -2.07 2.28 0 195.04 185.19 34444 +1906 310 5.94 -0.06 4.29 0 221.67 181.22 34279 +1906 311 13.24 7.24 11.59 0.1 346.35 128.83 34116 +1906 312 13.53 7.53 11.88 0.11 352.34 126.61 33956 +1906 313 15.91 9.91 14.26 0.43 404.95 122.69 33797 +1906 314 11.62 5.62 9.97 0.77 314.45 125.29 33641 +1906 315 12.9 6.9 11.25 0.1 339.43 122.33 33488 +1906 316 13.68 7.68 12.03 0.07 355.47 120.04 33337 +1906 317 12.78 6.78 11.13 0.51 337.02 119.22 33188 +1906 318 15.8 9.8 14.15 0.14 402.38 114.7 33042 +1906 319 15.45 9.45 13.8 0 394.29 151.77 32899 +1906 320 15.08 9.08 13.43 0 385.89 150.45 32758 +1906 321 10.52 4.52 8.87 0 294.26 153.45 32620 +1906 322 9.11 3.11 7.46 0 270.01 152.93 32486 +1906 323 9.73 3.73 8.08 0 280.45 150.79 32354 +1906 324 12.7 6.7 11.05 0 335.42 145.85 32225 +1906 325 7.63 1.63 5.98 0.09 246.42 111.59 32100 +1906 326 8.56 2.56 6.91 0 261.02 146.61 31977 +1906 327 10.7 4.7 9.05 0.37 297.48 107.19 31858 +1906 328 12.18 6.18 10.53 0.05 325.18 104.67 31743 +1906 329 13.05 7.05 11.4 0 342.47 137.2 31631 +1906 330 9.27 3.27 7.62 0.09 272.67 104.5 31522 +1906 331 5.59 -0.41 3.94 0.37 216.82 105.55 31417 +1906 332 5.51 -0.49 3.86 0 215.72 139.14 31316 +1906 333 4.61 -1.39 2.96 0.28 203.72 103.96 31218 +1906 334 6.19 0.19 4.54 0.79 225.19 102.38 31125 +1906 335 -4.5 -10.5 -6.15 0 111.12 140.41 31035 +1906 336 -0.75 -6.75 -2.4 0.01 143.48 146.14 30949 +1906 337 -0.76 -6.76 -2.41 0 143.38 179.06 30867 +1906 338 1.86 -4.14 0.21 0 170.54 134.13 30790 +1906 339 3.2 -2.8 1.55 0.22 186.07 99.49 30716 +1906 340 0.9 -5.1 -0.75 0 160.12 133.05 30647 +1906 341 0.13 -5.87 -1.52 1.21 152.15 99.35 30582 +1906 342 1.6 -4.4 -0.05 0.3 167.66 98.27 30521 +1906 343 0.84 -5.16 -0.81 0 159.48 130.55 30465 +1906 344 2 -4 0.35 0.02 172.11 96.65 30413 +1906 345 0.08 -5.92 -1.57 0 151.65 129.31 30366 +1906 346 -0.17 -6.17 -1.82 0 149.15 128.85 30323 +1906 347 0.85 -5.15 -0.8 0 159.59 127.82 30284 +1906 348 3.09 -2.91 1.44 0 184.76 126.4 30251 +1906 349 1.01 -4.99 -0.64 0 161.28 127.01 30221 +1906 350 1.64 -4.36 -0.01 0 168.1 126.39 30197 +1906 351 1.29 -4.71 -0.36 0.37 164.28 94.74 30177 +1906 352 0.25 -5.75 -1.4 0.49 153.37 95.01 30162 +1906 353 2.64 -3.36 0.99 0.03 179.44 94.15 30151 +1906 354 1.49 -4.51 -0.16 0.49 166.46 94.53 30145 +1906 355 -0.06 -6.06 -1.71 1.63 150.24 144.01 30144 +1906 356 1.62 -4.38 -0.03 0 167.88 174.76 30147 +1906 357 5.77 -0.23 4.12 0 219.3 171.83 30156 +1906 358 6 0 4.35 0.04 222.51 140 30169 +1906 359 2.46 -3.54 0.81 0.46 177.35 141.2 30186 +1906 360 0.89 -5.11 -0.76 0 160.01 173.61 30208 +1906 361 2.68 -3.32 1.03 0 179.91 172.71 30235 +1906 362 3.65 -2.35 2 0 191.56 172.11 30267 +1906 363 1.94 -4.06 0.29 1.23 171.44 141.29 30303 +1906 364 -5.64 -11.64 -7.29 0.56 102.63 145.42 30343 +1906 365 -3.12 -9.12 -4.77 0.14 122.2 145.64 30388 +1907 1 -1.7 -7.7 -3.35 0.07 134.59 146.08 30438 +1907 2 3.26 -2.74 1.61 0.19 186.8 144.45 30492 +1907 3 -0.03 -6.03 -1.68 0.49 150.54 147.78 30551 +1907 4 1.66 -4.34 0.01 0.7 168.32 147.58 30614 +1907 5 2.08 -3.92 0.43 0.47 173.01 147.53 30681 +1907 6 0.05 -5.95 -1.6 0.74 151.35 148.79 30752 +1907 7 0.3 -5.7 -1.35 0.53 153.88 149.16 30828 +1907 8 2 -4 0.35 0.57 172.11 149.29 30907 +1907 9 2.15 -3.85 0.5 0 173.81 184.1 30991 +1907 10 3.13 -2.87 1.48 0.88 185.23 149.83 31079 +1907 11 -1.07 -7.07 -2.72 0.04 140.43 152.06 31171 +1907 12 -2.07 -8.07 -3.72 0.33 131.26 154 31266 +1907 13 -2.34 -8.34 -3.99 0 128.88 191.22 31366 +1907 14 0.78 -5.22 -0.87 0 158.85 191.13 31469 +1907 15 3.99 -2.01 2.34 0 195.79 190.19 31575 +1907 16 1.88 -4.12 0.23 0.25 170.77 155.61 31686 +1907 17 2.4 -3.6 0.75 0 176.66 193.2 31800 +1907 18 1.53 -4.47 -0.12 0 166.89 195.21 31917 +1907 19 0.8 -5.2 -0.85 0 159.06 197.25 32038 +1907 20 1.86 -4.14 0.21 0.15 170.54 159.46 32161 +1907 21 2.54 -3.46 0.89 0.47 178.28 160.2 32289 +1907 22 4.86 -1.14 3.21 0.42 206.99 159.67 32419 +1907 23 -1.62 -7.62 -3.27 0 135.32 203.71 32552 +1907 24 -4.31 -10.31 -5.96 0 112.59 206.69 32688 +1907 25 -6.19 -12.19 -7.84 0 98.74 209.07 32827 +1907 26 -3.36 -9.36 -5.01 0 120.21 209.85 32969 +1907 27 -2.09 -8.09 -3.74 0 131.09 211.19 33114 +1907 28 0.36 -5.64 -1.29 0 154.5 212.03 33261 +1907 29 4.78 -1.22 3.13 0 205.94 210.99 33411 +1907 30 5.91 -0.09 4.26 0 221.25 211.5 33564 +1907 31 2.52 -3.48 0.87 0 178.05 215.71 33718 +1907 32 8.96 2.96 7.31 0 267.53 173.28 33875 +1907 33 9.53 3.53 7.88 0 277.05 175.32 34035 +1907 34 10 4 8.35 0.18 285.11 132.76 34196 +1907 35 7.05 1.05 5.4 0.01 237.67 136.42 34360 +1907 36 2.51 -3.49 0.86 0 177.93 187.78 34526 +1907 37 3 -3 1.35 0 183.68 189.89 34694 +1907 38 1.31 -4.69 -0.34 0.26 164.5 145.29 34863 +1907 39 1.12 -4.88 -0.53 0.33 162.45 147.35 35035 +1907 40 0.26 -5.74 -1.39 0.3 153.47 149.71 35208 +1907 41 3.61 -2.39 1.96 0 191.06 200.09 35383 +1907 42 -0.6 -6.6 -2.25 0 144.92 205.33 35560 +1907 43 -0.73 -6.73 -2.38 0 143.67 208.14 35738 +1907 44 0.19 -5.81 -1.46 0.35 152.76 157.66 35918 +1907 45 -1.16 -7.16 -2.81 0 139.58 213.63 36099 +1907 46 0.62 -5.38 -1.03 0 157.18 215.32 36282 +1907 47 0.39 -5.61 -1.26 0 154.8 218.31 36466 +1907 48 -0.49 -6.49 -2.14 0.37 145.99 203.24 36652 +1907 49 -1.73 -7.73 -3.38 0 134.32 261.99 36838 +1907 50 -5.13 -11.13 -6.78 0 106.36 266.18 37026 +1907 51 1.16 -4.84 -0.49 0 162.88 265.45 37215 +1907 52 -0.39 -6.39 -2.04 0 146.97 269.13 37405 +1907 53 -2.19 -8.19 -3.84 0.1 130.2 213.98 37596 +1907 54 1.9 -4.1 0.25 0 170.99 273.06 37788 +1907 55 1.79 -4.21 0.14 0 169.76 275.79 37981 +1907 56 -4.19 -10.19 -5.84 0 113.53 281.94 38175 +1907 57 -0.76 -6.76 -2.41 0 143.38 282.81 38370 +1907 58 2.01 -3.99 0.36 0 172.22 283.48 38565 +1907 59 2.42 -3.58 0.77 0 176.89 285.47 38761 +1907 60 3.4 -2.6 1.75 0.4 188.49 190 38958 +1907 61 4.82 -1.18 3.17 0 206.47 255.02 39156 +1907 62 -1.05 -7.05 -2.7 0 140.62 262.41 39355 +1907 63 6.73 0.73 5.08 0.02 232.96 194.19 39553 +1907 64 7.89 1.89 6.24 0.01 250.43 195.39 39753 +1907 65 7.97 1.97 6.32 0 251.67 263.3 39953 +1907 66 5.02 -0.98 3.37 0 209.11 269.23 40154 +1907 67 5.43 -0.57 3.78 0 214.63 271.74 40355 +1907 68 6.75 0.75 5.1 0 233.25 273.21 40556 +1907 69 8.93 2.93 7.28 0 267.04 273.2 40758 +1907 70 8.04 2.04 6.39 0 252.77 277.16 40960 +1907 71 8.31 2.31 6.66 0 257.03 279.73 41163 +1907 72 1.24 -4.76 -0.41 0 163.74 289.78 41366 +1907 73 5.34 -0.66 3.69 0 213.41 288.68 41569 +1907 74 6.34 0.34 4.69 0 227.32 290.34 41772 +1907 75 6.11 0.11 4.46 0 224.06 293.34 41976 +1907 76 0.48 -5.52 -1.17 0 155.73 301.37 42179 +1907 77 -1.33 -7.33 -2.98 0 137.99 305.37 42383 +1907 78 -0.65 -6.65 -2.3 0 144.44 307.61 42587 +1907 79 0.85 -5.15 -0.8 0 159.59 309.23 42791 +1907 80 1.43 -4.57 -0.22 0.03 165.8 233.49 42996 +1907 81 2.28 -3.72 0.63 0 175.29 313.2 43200 +1907 82 9.7 3.7 8.05 0.05 279.94 230.32 43404 +1907 83 8.12 2.12 6.47 0.05 254.02 233.87 43608 +1907 84 10.19 4.19 8.54 0 288.42 311.36 43812 +1907 85 9.8 3.8 8.15 0 281.65 314.45 44016 +1907 86 9.19 3.19 7.54 0.06 271.34 238.33 44220 +1907 87 8.66 2.66 7.01 0.19 262.64 240.81 44424 +1907 88 6.49 0.49 4.84 0.54 229.48 244.77 44627 +1907 89 9.96 3.96 8.31 0.14 284.41 242.81 44831 +1907 90 9.18 3.18 7.53 0.47 271.17 245.49 45034 +1907 91 11.02 5.02 9.37 1.81 303.3 244.97 45237 +1907 92 9.63 3.63 7.98 1.25 278.74 248.35 45439 +1907 93 11.22 5.22 9.57 0 306.98 330.72 45642 +1907 94 7.07 1.07 5.42 0.31 237.97 254.45 45843 +1907 95 6.29 0.29 4.64 0.73 226.61 256.85 46045 +1907 96 4.1 -1.9 2.45 0.39 197.18 260.44 46246 +1907 97 3.84 -2.16 2.19 0.19 193.91 262.24 46446 +1907 98 2.53 -3.47 0.88 0 178.16 353.06 46647 +1907 99 6.1 0.1 4.45 0 223.91 350.99 46846 +1907 100 5.88 -0.12 4.23 0 220.83 353.25 47045 +1907 101 11.95 5.95 10.3 0 320.74 345.67 47243 +1907 102 10.43 4.43 8.78 0.5 292.66 262.74 47441 +1907 103 15.35 9.35 13.7 2.68 392 256.67 47638 +1907 104 17.58 11.58 15.93 0.89 445.74 253.83 47834 +1907 105 18.53 12.53 16.88 0.54 470.47 253.17 48030 +1907 106 14.9 8.9 13.25 0.08 381.86 261.34 48225 +1907 107 12.34 6.34 10.69 0 328.3 355.59 48419 +1907 108 10.25 4.25 8.6 0.81 289.48 270.92 48612 +1907 109 9.32 3.32 7.67 0.47 273.51 273.33 48804 +1907 110 11.04 5.04 9.39 0.57 303.66 272.15 48995 +1907 111 13.65 7.65 12 0.16 354.84 269.38 49185 +1907 112 11.33 5.33 9.68 0.78 309.02 274.06 49374 +1907 113 11.97 5.97 10.32 0.32 321.12 274.14 49561 +1907 114 11.67 5.67 10.02 0 315.4 367.61 49748 +1907 115 11.55 5.55 9.9 0 313.13 369.28 49933 +1907 116 10.73 4.73 9.08 0 298.03 372.07 50117 +1907 117 10.73 4.73 9.08 0.01 298.03 280.04 50300 +1907 118 4.37 -1.63 2.72 0.57 200.62 288.33 50481 +1907 119 9.96 3.96 8.31 0.21 284.41 283 50661 +1907 120 11.35 5.35 9.7 0 309.39 375.94 50840 +1907 121 24.2 18.2 22.55 0 643.7 339.75 51016 +1907 122 21.21 15.21 19.56 0 546.63 352.18 51191 +1907 123 22.41 16.41 20.76 0 583.98 348.84 51365 +1907 124 19.28 13.28 17.63 0 490.81 360.59 51536 +1907 125 15.78 9.78 14.13 0 401.91 371.48 51706 +1907 126 15.71 9.71 14.06 0 400.28 372.65 51874 +1907 127 16.87 10.87 15.22 0.34 427.99 277.85 52039 +1907 128 18.07 12.07 16.42 0 458.35 368.05 52203 +1907 129 18.03 12.03 16.38 0.41 457.31 276.75 52365 +1907 130 14.95 8.95 13.3 0.07 382.97 283.56 52524 +1907 131 14.3 8.3 12.65 0.03 368.68 285.34 52681 +1907 132 14.48 8.48 12.83 0 372.59 380.85 52836 +1907 133 20.02 14.02 18.37 0 511.61 365.85 52989 +1907 134 21.51 15.51 19.86 0 555.77 361.38 53138 +1907 135 20.14 14.14 18.49 0 515.05 366.82 53286 +1907 136 23.08 17.08 21.43 0 605.76 356.72 53430 +1907 137 20.29 14.29 18.64 0.19 519.38 275.72 53572 +1907 138 21.03 15.03 19.38 0.62 541.2 274.24 53711 +1907 139 22.42 16.42 20.77 0 584.3 361.21 53848 +1907 140 20.01 14.01 18.36 0.01 511.32 277.73 53981 +1907 141 19.62 13.62 17.97 1.71 500.28 279.02 54111 +1907 142 17.41 11.41 15.76 0 441.43 379.32 54238 +1907 143 15.32 9.32 13.67 0 391.32 385.53 54362 +1907 144 14.1 8.1 12.45 0 364.37 389.02 54483 +1907 145 18.12 12.12 16.47 0.76 459.66 284.03 54600 +1907 146 16.26 10.26 14.61 0.09 413.22 288.29 54714 +1907 147 17.67 11.67 16.02 0.02 448.04 285.67 54824 +1907 148 25.48 19.48 23.83 0.01 689.52 264.26 54931 +1907 149 24.26 18.26 22.61 0 645.79 358.04 55034 +1907 150 24.34 18.34 22.69 0.42 648.58 268.51 55134 +1907 151 22.36 16.36 20.71 0.91 582.38 274.84 55229 +1907 152 26.27 20.27 24.62 0 719.15 349.74 55321 +1907 153 21.57 15.57 19.92 0 557.61 369.77 55409 +1907 154 21.86 15.86 20.21 0 566.6 369 55492 +1907 155 20.89 14.89 19.24 0.15 537.02 279.55 55572 +1907 156 20.11 14.11 18.46 0.39 514.19 281.82 55648 +1907 157 20.95 14.95 19.3 0.08 538.81 279.75 55719 +1907 158 22 16 20.35 0.05 570.98 276.98 55786 +1907 159 23.39 17.39 21.74 0 616.06 364.07 55849 +1907 160 18.72 12.72 17.07 0.52 475.56 285.8 55908 +1907 161 21.96 15.96 20.31 0 569.72 369.95 55962 +1907 162 23.88 17.88 22.23 0 632.66 362.34 56011 +1907 163 20.43 14.43 18.78 0 523.45 375.76 56056 +1907 164 16.87 10.87 15.22 0 427.99 386.98 56097 +1907 165 15.04 9.04 13.39 0.19 384.99 293.99 56133 +1907 166 17.5 11.5 15.85 0 443.71 385.34 56165 +1907 167 19.17 13.17 17.52 0.11 487.78 285.11 56192 +1907 168 22.62 16.62 20.97 0 590.73 367.91 56214 +1907 169 24.49 18.49 22.84 0 653.85 360.18 56231 +1907 170 23.42 17.42 21.77 0.15 617.07 273.53 56244 +1907 171 18.57 12.57 16.92 0.01 471.54 286.65 56252 +1907 172 20.54 14.54 18.89 0 526.67 375.68 56256 +1907 173 23.19 17.19 21.54 0.32 609.4 274.26 56255 +1907 174 22.19 16.19 20.54 0.85 576.97 277.15 56249 +1907 175 21.91 15.91 20.26 0 568.16 370.58 56238 +1907 176 21.28 15.28 19.63 0 548.75 372.87 56223 +1907 177 21.44 15.44 19.79 0.52 553.62 279.14 56203 +1907 178 20.06 14.06 18.41 0 512.76 377.09 56179 +1907 179 23.47 17.47 21.82 0 618.75 364.21 56150 +1907 180 24.8 18.8 23.15 0 664.85 358.42 56116 +1907 181 28.11 22.11 26.46 0 792.36 342.31 56078 +1907 182 25.42 19.42 23.77 0 687.31 355.42 56035 +1907 183 25.05 19.05 23.4 0.38 673.83 267.7 55987 +1907 184 22.47 16.47 20.82 0.66 585.9 275.67 55935 +1907 185 22.94 16.94 21.29 0.08 601.15 274.22 55879 +1907 186 21 15 19.35 0 540.3 372.7 55818 +1907 187 23.2 17.2 21.55 0.16 609.73 273.11 55753 +1907 188 21.02 15.02 19.37 2.21 540.9 279.14 55684 +1907 189 19.97 13.97 18.32 1.63 510.18 281.73 55611 +1907 190 17.33 11.33 15.68 0 439.42 383.52 55533 +1907 191 18 12 16.35 0.06 456.53 285.96 55451 +1907 192 20.81 14.81 19.16 1.45 534.64 278.86 55366 +1907 193 19.23 13.23 17.58 0.67 489.43 282.65 55276 +1907 194 23.36 17.36 21.71 0.07 615.06 271.24 55182 +1907 195 19.06 13.06 17.41 0.01 484.77 282.68 55085 +1907 196 18.39 12.39 16.74 0.02 466.76 283.94 54984 +1907 197 24.02 18.02 22.37 0.09 637.47 268.36 54879 +1907 198 27.54 21.54 25.89 0 769.04 341.1 54770 +1907 199 24.32 18.32 22.67 0 647.88 355.8 54658 +1907 200 26.9 20.9 25.25 0.02 743.54 257.69 54542 +1907 201 25.72 19.72 24.07 0 698.41 348.75 54423 +1907 202 24.66 18.66 23.01 0 659.86 352.94 54301 +1907 203 21.62 15.62 19.97 0.42 559.15 273.43 54176 +1907 204 23.52 17.52 21.87 0.62 620.43 267.56 54047 +1907 205 17.69 11.69 16.04 0.16 448.55 282.32 53915 +1907 206 20.02 14.02 18.37 0.46 511.61 276.44 53780 +1907 207 16.22 10.22 14.57 0.56 412.27 284.46 53643 +1907 208 14.15 8.15 12.5 0.07 365.44 287.85 53502 +1907 209 12.41 6.41 10.76 0 329.68 387.02 53359 +1907 210 17.42 11.42 15.77 0 441.69 374 53213 +1907 211 20.59 14.59 18.94 0.05 528.14 272.47 53064 +1907 212 22.52 16.52 20.87 0.61 587.51 266.66 52913 +1907 213 26.53 20.53 24.88 0.17 729.13 253.32 52760 +1907 214 28.96 22.96 27.31 0 828.25 324.79 52604 +1907 215 25.99 19.99 24.34 0 708.52 338.92 52445 +1907 216 23.52 17.52 21.87 0.09 620.43 261.39 52285 +1907 217 26.24 20.24 24.59 0 718 335.95 52122 +1907 218 27.33 21.33 25.68 0 760.59 330 51958 +1907 219 26.4 20.4 24.75 0.12 724.13 250.08 51791 +1907 220 28.8 22.8 27.15 0 821.39 320.68 51622 +1907 221 30.29 24.29 28.64 0.05 887.15 233.69 51451 +1907 222 26.13 20.13 24.48 0 713.82 331.85 51279 +1907 223 24.51 18.51 22.86 0 654.55 337.81 51105 +1907 224 23.14 17.14 21.49 0 607.74 342.26 50929 +1907 225 23.7 17.7 22.05 0.08 626.52 254.22 50751 +1907 226 20.89 14.89 19.24 0.05 537.02 261.09 50572 +1907 227 20.83 14.83 19.18 0.04 535.23 260.29 50392 +1907 228 19.11 13.11 17.46 0.06 486.14 263.5 50210 +1907 229 19.09 13.09 17.44 0.47 485.59 262.61 50026 +1907 230 22.03 16.03 20.38 0.01 571.92 254.42 49842 +1907 231 17.23 11.23 15.58 0.09 436.91 264.52 49656 +1907 232 16.61 10.61 14.96 1.21 421.64 264.72 49469 +1907 233 22.52 16.52 20.87 1.24 587.51 249.99 49280 +1907 234 22.78 16.78 21.13 0.56 595.92 248.24 49091 +1907 235 23.5 17.5 21.85 0.01 619.76 245.14 48900 +1907 236 23.9 17.9 22.25 0 633.35 323.94 48709 +1907 237 22.46 16.46 20.81 0.05 585.58 245.77 48516 +1907 238 22.15 16.15 20.5 0.4 575.7 245.36 48323 +1907 239 18.23 12.23 16.58 0.08 462.54 253.42 48128 +1907 240 18.26 12.26 16.61 0.62 463.33 252.04 47933 +1907 241 17.67 11.67 16.02 0.27 448.04 251.94 47737 +1907 242 15.28 9.28 13.63 0.59 390.41 255.08 47541 +1907 243 12.85 6.85 11.2 0.38 338.42 257.56 47343 +1907 244 7.06 1.06 5.41 0.1 237.82 263.39 47145 +1907 245 9.04 3.04 7.39 0 268.85 346.34 46947 +1907 246 10.42 4.42 8.77 0 292.48 342.05 46747 +1907 247 17.26 11.26 15.61 0 437.66 325.84 46547 +1907 248 20.55 14.55 18.9 0 526.96 314.72 46347 +1907 249 22.62 16.62 20.97 0 590.73 306.01 46146 +1907 250 23.01 17.01 21.36 0 603.45 302.78 45945 +1907 251 20.42 14.42 18.77 0 523.16 309.09 45743 +1907 252 19.09 13.09 17.44 0 485.59 310.78 45541 +1907 253 15.37 9.37 13.72 0 392.46 317.87 45339 +1907 254 20.58 14.58 18.93 0 527.84 302.33 45136 +1907 255 25.48 19.48 23.83 0 689.52 283.46 44933 +1907 256 25.96 19.96 24.31 0.57 707.39 209.59 44730 +1907 257 20.64 14.64 18.99 0.87 529.61 221.71 44527 +1907 258 20.33 14.33 18.68 0.21 520.54 220.67 44323 +1907 259 18.52 12.52 16.87 0.08 470.21 222.56 44119 +1907 260 16.37 10.37 14.72 2.3 415.85 224.67 43915 +1907 261 19.57 13.57 17.92 0.15 498.88 216.92 43711 +1907 262 18.03 12.03 16.38 0 457.31 290.85 43507 +1907 263 16.75 10.75 15.1 0 425.05 291.42 43303 +1907 264 17.73 11.73 16.08 0.1 449.57 214.95 43099 +1907 265 15.21 9.21 13.56 0 388.82 289.79 42894 +1907 266 12.93 6.93 11.28 0 340.04 291.62 42690 +1907 267 17.22 11.22 15.57 0 436.66 280.32 42486 +1907 268 22.81 16.81 21.16 0 596.9 262.96 42282 +1907 269 22.36 16.36 20.71 0 582.38 261.94 42078 +1907 270 23.05 17.05 21.4 0 604.77 257.33 41875 +1907 271 21.97 15.97 20.32 0.01 570.04 193.55 41671 +1907 272 25.35 19.35 23.7 0.07 684.74 183.59 41468 +1907 273 25.91 19.91 24.26 0.02 705.51 180.38 41265 +1907 274 25.73 19.73 24.08 0.19 698.78 179.01 41062 +1907 275 20.72 14.72 19.07 0.05 531.97 188.44 40860 +1907 276 18.94 12.94 17.29 0.54 481.5 189.79 40658 +1907 277 18.46 12.46 16.81 0 468.61 251.57 40456 +1907 278 16.41 10.41 14.76 0.22 416.81 189.84 40255 +1907 279 12.91 6.91 11.26 0 339.63 256.6 40054 +1907 280 15.27 9.27 13.62 0 390.18 249.9 39854 +1907 281 11.51 5.51 9.86 0.32 312.38 190 39654 +1907 282 13.39 7.39 11.74 0 349.43 247.7 39455 +1907 283 12.66 6.66 11.01 0 334.62 246.02 39256 +1907 284 15.53 9.53 13.88 0.02 396.12 178.68 39058 +1907 285 16.58 10.58 14.93 0.78 420.91 175.28 38861 +1907 286 11.68 5.68 10.03 0.04 315.59 179.26 38664 +1907 287 15.13 9.13 13.48 0.05 387.01 173.04 38468 +1907 288 17.65 11.65 16 0 447.52 223.35 38273 +1907 289 20.08 14.08 18.43 0 513.33 215.69 38079 +1907 290 22.67 16.67 21.02 0 592.35 206.73 37885 +1907 291 20.85 14.85 19.2 0 535.82 208.63 37693 +1907 292 19.09 13.09 17.44 0.02 485.59 157.44 37501 +1907 293 18.01 12.01 16.36 0 456.79 209.45 37311 +1907 294 19.95 13.95 18.3 0.11 509.61 152.05 37121 +1907 295 16.67 10.67 15.02 1.28 423.1 154.76 36933 +1907 296 17.45 11.45 15.8 0.04 442.44 151.84 36745 +1907 297 15.7 9.7 14.05 0 400.05 202.81 36560 +1907 298 17.5 11.5 15.85 0 443.71 197.21 36375 +1907 299 16.41 10.41 14.76 1.14 416.81 147.29 36191 +1907 300 18.74 12.74 17.09 0 476.09 189.68 36009 +1907 301 18.46 12.46 16.81 0 468.61 187.79 35829 +1907 302 22.04 16.04 20.39 0 572.24 178.04 35650 +1907 303 19.58 13.58 17.93 0 499.16 180.73 35472 +1907 304 19.13 13.13 17.48 0 486.69 179.24 35296 +1907 305 4.98 -1.02 3.33 0.02 208.58 145.68 35122 +1907 306 4.12 -1.88 2.47 0.35 197.43 144.45 34950 +1907 307 2.99 -3.01 1.34 0.25 183.56 143.13 34779 +1907 308 2.41 -3.59 0.76 0.31 176.78 141.42 34610 +1907 309 -0.45 -6.45 -2.1 0 146.39 187.85 34444 +1907 310 3.08 -2.92 1.43 0 184.64 183.28 34279 +1907 311 1.97 -4.03 0.32 0 171.77 181.76 34116 +1907 312 6.57 0.57 4.92 0.34 230.63 131.9 33956 +1907 313 10.3 4.3 8.65 0.05 290.36 127.77 33797 +1907 314 4.19 -1.81 2.54 0.13 198.32 130.14 33641 +1907 315 2.12 -3.88 0.47 0.15 173.47 129.2 33488 +1907 316 0.77 -5.23 -0.88 0 158.75 170.8 33337 +1907 317 5.57 -0.43 3.92 0 216.54 165.58 33188 +1907 318 10.59 4.59 8.94 0 295.51 158.98 33042 +1907 319 14.71 8.71 13.06 0 377.64 152.72 32899 +1907 320 14 8 12.35 0.12 362.24 113.84 32758 +1907 321 14.27 8.27 12.62 0 368.03 149.41 32620 +1907 322 11.38 5.38 9.73 0 309.95 150.81 32486 +1907 323 12.36 6.36 10.71 0 328.69 148.22 32354 +1907 324 10.03 4.03 8.38 0 285.63 148.49 32225 +1907 325 11.35 5.35 9.7 0 309.39 145.55 32100 +1907 326 6.09 0.09 4.44 0.05 223.77 111.35 31977 +1907 327 10.01 4.01 8.36 0 285.28 143.55 31858 +1907 328 7.93 1.93 6.28 0 251.05 143.31 31743 +1907 329 5.64 -0.36 3.99 1.08 217.5 107.6 31631 +1907 330 -0.41 -6.41 -2.06 0.27 146.78 151.67 31522 +1907 331 4.37 -1.63 2.72 0 200.62 183.77 31417 +1907 332 6.54 0.54 4.89 0 230.2 138.46 31316 +1907 333 6.84 0.84 5.19 0.22 234.57 102.87 31218 +1907 334 8.41 2.41 6.76 0 258.62 134.93 31125 +1907 335 6.67 0.67 5.02 0 232.08 135.02 31035 +1907 336 7.34 1.34 5.69 0.36 242.01 100.12 30949 +1907 337 3.56 -2.44 1.91 0.15 190.45 100.65 30867 +1907 338 4.98 -1.02 3.33 0.01 208.58 99.33 30790 +1907 339 2.03 -3.97 0.38 0.5 172.45 99.94 30716 +1907 340 0.57 -5.43 -1.08 0.11 156.66 99.9 30647 +1907 341 -0.46 -6.46 -2.11 0.29 146.29 143.61 30582 +1907 342 0.69 -5.31 -0.96 0 157.91 175.52 30521 +1907 343 1.56 -4.44 -0.09 0.09 167.22 141.61 30465 +1907 344 -1.01 -7.01 -2.66 0.38 141 142.86 30413 +1907 345 0.73 -5.27 -0.92 0.18 158.33 141.96 30366 +1907 346 3.91 -2.09 2.26 0.02 194.79 139.92 30323 +1907 347 5.07 -0.93 3.42 0 209.78 169.78 30284 +1907 348 4.73 -1.27 3.08 0 205.29 125.51 30251 +1907 349 5.97 -0.03 4.32 0 222.09 124.39 30221 +1907 350 8.78 2.78 7.13 0 264.59 122.16 30197 +1907 351 10.56 4.56 8.91 0.44 294.97 90.42 30177 +1907 352 7.55 1.55 5.9 0.25 245.19 92.04 30162 +1907 353 2.97 -3.03 1.32 0.04 183.33 94.02 30151 +1907 354 2.63 -3.37 0.98 0.2 179.33 94.12 30145 +1907 355 4.03 -1.97 2.38 0.1 196.29 93.58 30144 +1907 356 4.73 -1.27 3.08 0 205.29 124.41 30147 +1907 357 5.87 -0.13 4.22 1.84 220.69 92.85 30156 +1907 358 2.41 -3.59 0.76 0 176.78 125.78 30169 +1907 359 6.44 0.44 4.79 0 228.76 123.64 30186 +1907 360 9.28 3.28 7.63 0 272.84 122.02 30208 +1907 361 11.84 5.84 10.19 0 318.63 120.23 30235 +1907 362 10.42 4.42 8.77 0.38 292.48 91.41 30267 +1907 363 6.91 0.91 5.26 0.07 235.6 93.79 30303 +1907 364 4.43 -1.57 2.78 0.24 201.39 95.22 30343 +1907 365 4.4 -1.6 2.75 0.18 201 95.66 30388 +1908 1 -1.17 -7.17 -2.82 0 139.49 131.07 30438 +1908 2 -1.21 -7.21 -2.86 0 139.11 131.82 30492 +1908 3 -0.81 -6.81 -2.46 0 142.9 132.62 30551 +1908 4 -2.05 -8.05 -3.7 0 131.44 134.02 30614 +1908 5 0.3 -5.7 -1.35 0 153.88 133.73 30681 +1908 6 -1.28 -7.28 -2.93 0 138.46 135.28 30752 +1908 7 0.77 -5.23 -0.88 0 158.75 135.21 30828 +1908 8 3.15 -2.85 1.5 0 185.47 135.53 30907 +1908 9 2.66 -3.34 1.01 0.08 179.67 102.78 30991 +1908 10 0.26 -5.74 -1.39 0 153.47 139.52 31079 +1908 11 -0.83 -6.83 -2.48 0 142.71 140.99 31171 +1908 12 0.99 -5.01 -0.66 0 161.07 141.2 31266 +1908 13 2.53 -3.47 0.88 0 178.16 142.05 31366 +1908 14 0.23 -5.77 -1.42 0 153.17 144.67 31469 +1908 15 -0.05 -6.05 -1.7 0 150.34 146.26 31575 +1908 16 2.29 -3.71 0.64 0 175.4 146.4 31686 +1908 17 1.8 -4.2 0.15 0 169.87 148.35 31800 +1908 18 2.82 -3.18 1.17 0 181.55 149.7 31917 +1908 19 2.02 -3.98 0.37 0 172.34 152.07 32038 +1908 20 -0.54 -6.54 -2.19 0 145.51 154.94 32161 +1908 21 -2.15 -8.15 -3.8 0 130.55 157.66 32289 +1908 22 -4.35 -10.35 -6 0.12 112.28 161.28 32419 +1908 23 -1.93 -7.93 -3.58 0 132.51 202.05 32552 +1908 24 -1.76 -7.76 -3.41 0 134.05 203.9 32688 +1908 25 -1.5 -7.5 -3.15 0 136.42 205.52 32827 +1908 26 0.74 -5.26 -0.91 0 158.43 206.12 32969 +1908 27 2.59 -3.41 0.94 0.1 178.86 125.12 33114 +1908 28 -1.01 -7.01 -2.66 0 141 170.97 33261 +1908 29 -0.98 -6.98 -2.63 0.01 141.28 169.55 33411 +1908 30 -2.79 -8.79 -4.44 0.11 124.99 172 33564 +1908 31 -3.55 -9.55 -5.2 0 118.65 218.65 33718 +1908 32 2.78 -3.22 1.13 0 181.08 217.05 33875 +1908 33 2.94 -3.06 1.29 0 182.97 180.6 34035 +1908 34 2.82 -3.18 1.17 0.02 181.55 137.17 34196 +1908 35 4.35 -1.65 2.7 0 200.36 184.01 34360 +1908 36 1.31 -4.69 -0.34 0 164.5 188.52 34526 +1908 37 2.36 -3.64 0.71 0.04 176.2 142.73 34694 +1908 38 0.04 -5.96 -1.61 0 151.25 194.45 34863 +1908 39 3.85 -2.15 2.2 0 194.04 194.66 35035 +1908 40 4.49 -1.51 2.84 0.72 202.16 147.61 35208 +1908 41 2.73 -3.27 1.08 0 180.49 200.7 35383 +1908 42 1.78 -4.22 0.13 0.01 169.65 152.93 35560 +1908 43 -1.34 -7.34 -2.99 0 137.9 208.47 35738 +1908 44 1.3 -4.7 -0.35 0 164.39 209.53 35918 +1908 45 1.88 -4.12 0.23 0 170.77 211.79 36099 +1908 46 2.21 -3.79 0.56 0.64 174.49 160.71 36282 +1908 47 6.33 0.33 4.68 0 227.18 213.82 36466 +1908 48 6.98 0.98 5.33 0 236.63 216.01 36652 +1908 49 7.39 1.39 5.74 0 242.76 218.37 36838 +1908 50 5.95 -0.05 4.3 0 221.81 222.4 37026 +1908 51 11.52 5.52 9.87 0 312.57 219.2 37215 +1908 52 7.35 1.35 5.7 0.98 242.16 170.12 37405 +1908 53 6.47 0.47 4.82 0.44 229.19 172.98 37596 +1908 54 6.08 0.08 4.43 0.02 223.63 175.33 37788 +1908 55 4.14 -1.86 2.49 0 197.68 238.52 37981 +1908 56 3.32 -2.68 1.67 0 187.52 241.91 38175 +1908 57 6.14 0.14 4.49 0 224.48 242.27 38370 +1908 58 7.06 1.06 5.41 0 237.82 244.26 38565 +1908 59 7.38 1.38 5.73 0 242.61 246.62 38761 +1908 60 7.64 1.64 5.99 0.27 246.57 186.9 38958 +1908 61 4.99 -1.01 3.34 0.69 208.72 191.14 39156 +1908 62 4.05 -1.95 2.4 0.18 196.55 193.9 39355 +1908 63 5.08 -0.92 3.43 0 209.91 260.6 39553 +1908 64 3.42 -2.58 1.77 0.49 188.74 198.79 39753 +1908 65 3.49 -2.51 1.84 0 189.59 267.91 39953 +1908 66 2.91 -3.09 1.26 0 182.61 271.18 40154 +1908 67 6.32 0.32 4.67 0 227.04 270.8 40355 +1908 68 1.74 -4.26 0.09 0 169.21 278 40556 +1908 69 6.52 0.52 4.87 0 229.91 276.09 40758 +1908 70 9.14 3.14 7.49 0 270.51 275.75 40960 +1908 71 7.43 1.43 5.78 0 243.37 280.81 41163 +1908 72 8.47 2.47 6.82 0 259.58 282.34 41366 +1908 73 7.12 1.12 5.47 0 238.71 286.68 41569 +1908 74 5.06 -0.94 3.41 0 209.65 291.74 41772 +1908 75 7.04 1.04 5.39 0.23 237.52 219.19 41976 +1908 76 9.65 3.65 8 0.05 279.08 218.6 42179 +1908 77 7.36 1.36 5.71 0.74 242.31 222.84 42383 +1908 78 5.72 -0.28 4.07 1.08 218.61 226.31 42587 +1908 79 4.69 -1.31 3.04 1.77 204.76 229.22 42791 +1908 80 8.29 2.29 6.64 0.04 256.71 227.9 42996 +1908 81 10.35 4.35 8.7 0.38 291.24 227.6 43200 +1908 82 10.54 4.54 8.89 0.06 294.62 229.36 43404 +1908 83 12.37 6.37 10.72 0 328.89 305.23 43608 +1908 84 7.8 1.8 6.15 0 249.03 314.81 43812 +1908 85 5.24 -0.76 3.59 0.3 212.06 240.37 44016 +1908 86 4.84 -1.16 3.19 0 206.73 323.38 44220 +1908 87 6.83 0.83 5.18 0.52 234.42 242.67 44424 +1908 88 9.09 3.09 7.44 0 269.68 322.8 44627 +1908 89 9.48 3.48 7.83 0 276.2 324.5 44831 +1908 90 7.24 1.24 5.59 0 240.5 330.08 45034 +1908 91 11.54 5.54 9.89 0 312.94 325.73 45237 +1908 92 13.8 7.8 12.15 0.49 357.99 242.76 45439 +1908 93 12.03 6.03 10.38 0 322.28 329.28 45642 +1908 94 7.35 1.35 5.7 1.65 242.16 254.16 45843 +1908 95 10.12 4.12 8.47 0.57 287.2 252.66 46045 +1908 96 6.61 0.61 4.96 0 231.21 344.19 46246 +1908 97 13.04 7.04 11.39 0 342.26 335.75 46446 +1908 98 10.42 4.42 8.77 0 292.48 342.52 46647 +1908 99 7.14 1.14 5.49 0 239.01 349.59 46846 +1908 100 10.68 4.68 9.03 0 297.12 346.04 47045 +1908 101 11.19 5.19 9.54 0.54 306.42 260.31 47243 +1908 102 12.27 6.27 10.62 0.43 326.93 260.22 47441 +1908 103 12.14 6.14 10.49 1.87 324.4 261.79 47638 +1908 104 12.33 6.33 10.68 0.31 328.11 262.88 47834 +1908 105 8.48 2.48 6.83 0.16 259.74 269.27 48030 +1908 106 10.38 4.38 8.73 0.19 291.77 268.17 48225 +1908 107 9.98 3.98 8.33 0.01 284.76 269.96 48419 +1908 108 13.43 7.43 11.78 0 350.26 355.1 48612 +1908 109 14.26 8.26 12.61 0 367.81 354.89 48804 +1908 110 11.4 5.4 9.75 0 310.32 362.19 48995 +1908 111 12.36 6.36 10.71 0 328.69 361.87 49185 +1908 112 13.26 7.26 11.61 0.03 346.76 271.15 49374 +1908 113 14.2 8.2 12.55 0.46 366.52 270.61 49561 +1908 114 13.06 7.06 11.41 0.88 342.67 273.59 49748 +1908 115 8.61 2.61 6.96 1.62 261.83 280.86 49933 +1908 116 9.36 3.36 7.71 0.25 274.18 280.87 50117 +1908 117 12.48 6.48 10.83 0.09 331.05 277.48 50300 +1908 118 15.38 9.38 13.73 0 392.69 364.75 50481 +1908 119 11.92 5.92 10.27 0 320.16 373.63 50661 +1908 120 13.6 7.6 11.95 0 353.8 371.27 50840 +1908 121 22.67 16.67 21.02 0 592.35 345.76 51016 +1908 122 19.96 13.96 18.31 0.09 509.9 267.28 51191 +1908 123 20.48 14.48 18.83 0.87 524.91 266.75 51365 +1908 124 18.3 12.3 16.65 0.01 464.38 272.68 51536 +1908 125 20.78 14.78 19.13 0 533.75 356.64 51706 +1908 126 24.68 18.68 23.03 0 660.57 342.69 51874 +1908 127 19.59 13.59 17.94 0 499.44 362.41 52039 +1908 128 15.02 9.02 13.37 0 384.54 376.26 52203 +1908 129 17.29 11.29 15.64 0 438.42 371.13 52365 +1908 130 15.66 9.66 14.01 0.08 399.12 282.23 52524 +1908 131 17.23 11.23 15.58 0.06 436.91 279.66 52681 +1908 132 14.82 8.82 13.17 0 380.08 380.03 52836 +1908 133 18.81 12.81 17.16 0 477.98 369.72 52989 +1908 134 19.98 13.98 18.33 0 510.47 366.67 53138 +1908 135 18.16 12.16 16.51 0 460.7 373.09 53286 +1908 136 18.27 12.27 16.62 0 463.59 373.39 53430 +1908 137 20.31 14.31 18.66 0 519.96 367.56 53572 +1908 138 23.44 17.44 21.79 0 617.74 356.53 53711 +1908 139 22.36 16.36 20.71 0 582.38 361.44 53848 +1908 140 25.03 19.03 23.38 0.01 673.11 263.19 53981 +1908 141 21.43 15.43 19.78 0 553.32 365.79 54111 +1908 142 18.29 12.29 16.64 0 464.12 376.71 54238 +1908 143 19.36 13.36 17.71 0 493.03 373.89 54362 +1908 144 16.99 10.99 15.34 0 430.95 381.53 54483 +1908 145 18.69 12.69 17.04 0 474.75 376.96 54600 +1908 146 20.01 14.01 18.36 0 511.32 373.05 54714 +1908 147 22.78 16.78 21.13 0 595.92 363.44 54824 +1908 148 23.83 17.83 22.18 0 630.95 359.55 54931 +1908 149 27.11 21.11 25.46 0 751.83 344.86 55034 +1908 150 21.81 15.81 20.16 0.75 565.04 276.11 55134 +1908 151 18.87 12.87 17.22 0.72 479.6 283.99 55229 +1908 152 21.23 15.23 19.58 0.1 547.23 278.08 55321 +1908 153 18.09 12.09 16.44 0.13 458.88 286.06 55409 +1908 154 23.23 17.23 21.58 0 610.73 363.66 55492 +1908 155 23.89 17.89 22.24 0 633 361.12 55572 +1908 156 23.26 17.26 21.61 0 611.72 364.04 55648 +1908 157 21.49 15.49 19.84 1.2 555.15 278.28 55719 +1908 158 24.17 18.17 22.52 0.23 642.66 270.43 55786 +1908 159 25.24 19.24 23.59 0.91 680.72 267.08 55849 +1908 160 27.03 21.03 25.38 0 748.66 347.76 55908 +1908 161 23.81 17.81 22.16 0 630.27 362.58 55962 +1908 162 23.07 17.07 21.42 0 605.43 365.67 56011 +1908 163 22.5 16.5 20.85 0 586.86 368.14 56056 +1908 164 23.46 17.46 21.81 0.17 618.41 273.25 56097 +1908 165 21.35 15.35 19.7 0 550.88 372.62 56133 +1908 166 18.39 12.39 16.74 0 466.76 382.66 56165 +1908 167 20.87 14.87 19.22 0.15 536.42 280.78 56192 +1908 168 21.65 15.65 20 0 560.08 371.62 56214 +1908 169 22.66 16.66 21.01 0.17 592.02 275.82 56231 +1908 170 25.28 19.28 23.63 0 682.18 356.67 56244 +1908 171 22.74 16.74 21.09 0 594.62 367.51 56252 +1908 172 24.24 18.24 22.59 0 645.09 361.31 56256 +1908 173 24.01 18.01 22.36 0 637.13 362.28 56255 +1908 174 22.61 16.61 20.96 0 590.41 367.91 56249 +1908 175 25.46 19.46 23.81 0 688.78 355.77 56238 +1908 176 24.07 18.07 22.42 0 639.2 361.88 56223 +1908 177 25.52 19.52 23.87 0.01 690.99 266.52 56203 +1908 178 22.41 16.41 20.76 0 583.98 368.55 56179 +1908 179 22.9 16.9 21.25 0 599.84 366.52 56150 +1908 180 20.54 14.54 18.89 0 526.67 375.21 56116 +1908 181 20.71 14.71 19.06 0 531.67 374.55 56078 +1908 182 19.78 13.78 18.13 0 504.78 377.59 56035 +1908 183 22.26 16.26 20.61 0.04 579.19 276.39 55987 +1908 184 18.26 12.26 16.61 1.49 463.33 286.59 55935 +1908 185 17.9 11.9 16.25 0.91 453.94 287.34 55879 +1908 186 17.26 11.26 15.61 0.05 437.66 288.56 55818 +1908 187 19.76 13.76 18.11 0.04 504.22 282.6 55753 +1908 188 19.71 13.71 18.06 0.35 502.81 282.52 55684 +1908 189 18.49 12.49 16.84 0 469.41 380.43 55611 +1908 190 17.17 11.17 15.52 0.07 435.41 287.99 55533 +1908 191 19.12 13.12 17.47 0 486.41 377.8 55451 +1908 192 25.66 19.66 24.01 0 696.18 352.17 55366 +1908 193 28.13 22.13 26.48 0 793.19 339.72 55276 +1908 194 27.1 21.1 25.45 0.48 751.43 258.59 55182 +1908 195 27.28 21.28 25.63 0.2 758.59 257.73 55085 +1908 196 24.71 18.71 23.06 0 661.64 355.31 54984 +1908 197 21.71 15.71 20.06 0 561.93 366.94 54879 +1908 198 20.16 14.16 18.51 0 515.63 372 54770 +1908 199 22.03 16.03 20.38 0.03 571.92 273.73 54658 +1908 200 20.19 14.19 18.54 0.19 516.49 278.36 54542 +1908 201 23.33 17.33 21.68 0.06 614.06 269.29 54423 +1908 202 26.77 20.77 25.12 0 738.45 343.25 54301 +1908 203 23.98 17.98 22.33 0 636.09 355.35 54176 +1908 204 25.52 19.52 23.87 0.21 690.99 261.12 54047 +1908 205 23.8 17.8 22.15 0.01 629.93 266.32 53915 +1908 206 25.66 19.66 24.01 0 696.18 346.48 53780 +1908 207 23.68 17.68 22.03 0.91 625.84 265.8 53643 +1908 208 25.38 19.38 23.73 0 685.84 346.49 53502 +1908 209 24.49 18.49 22.84 0.63 653.85 262.31 53359 +1908 210 23.76 17.76 22.11 0 628.56 352.19 53213 +1908 211 25.87 19.87 24.22 0 704.01 342.31 53064 +1908 212 25.73 19.73 24.08 0 698.78 342.19 52913 +1908 213 26.5 20.5 24.85 0.03 727.97 253.42 52760 +1908 214 25.48 19.48 23.83 0.22 689.52 256.4 52604 +1908 215 24.26 18.26 22.61 0.2 645.79 259.86 52445 +1908 216 23.81 17.81 22.16 0.77 630.27 260.51 52285 +1908 217 21.01 15.01 19.36 1.51 540.6 267.74 52122 +1908 218 21.65 15.65 20 0.21 560.08 265.44 51958 +1908 219 18.8 12.8 17.15 0.29 477.71 271.73 51791 +1908 220 18.82 12.82 17.17 1.83 478.25 270.97 51622 +1908 221 20.79 14.79 19.14 0 534.04 353.96 51451 +1908 222 21.43 15.43 19.78 0.22 553.32 263.04 51279 +1908 223 19.72 13.72 18.07 0.08 503.09 266.47 51105 +1908 224 15.71 9.71 14.06 0.1 400.28 274.19 50929 +1908 225 19.49 13.49 17.84 0.04 496.64 265.36 50751 +1908 226 18.37 12.37 16.72 0.14 466.23 267.03 50572 +1908 227 20.28 14.28 18.63 0 519.09 348.87 50392 +1908 228 20.07 14.07 18.42 1.05 513.04 261.25 50210 +1908 229 17.74 11.74 16.09 0.85 449.83 265.55 50026 +1908 230 15.41 9.41 13.76 1.61 393.37 269.13 49842 +1908 231 16.64 10.64 14.99 0.64 422.37 265.69 49656 +1908 232 22.3 16.3 20.65 0 580.46 335.5 49469 +1908 233 19.6 13.6 17.95 0 499.72 343.07 49280 +1908 234 23.31 17.31 21.66 0.84 613.39 246.76 49091 +1908 235 18.86 12.86 17.21 0.07 479.33 256.78 48900 +1908 236 22.71 16.71 21.06 0.01 593.64 246.3 48709 +1908 237 22.84 16.84 21.19 0.04 597.88 244.74 48516 +1908 238 20.79 14.79 19.14 0.01 534.04 248.79 48323 +1908 239 21.79 15.79 20.14 0.89 564.42 245.19 48128 +1908 240 21.17 15.17 19.52 0 545.42 327.26 47933 +1908 241 18.93 12.93 17.28 0 481.23 332.43 47737 +1908 242 20.05 14.05 18.4 0 512.47 327.38 47541 +1908 243 18.83 12.83 17.18 0.92 478.52 246.84 47343 +1908 244 13.91 7.91 12.26 1.2 360.32 254.52 47145 +1908 245 10.23 4.23 8.58 0.12 289.12 258.31 46947 +1908 246 13.18 7.18 11.53 0 345.12 336.96 46747 +1908 247 12.77 6.77 11.12 0 336.82 335.86 46547 +1908 248 12.5 6.5 10.85 0 331.45 334.38 46347 +1908 249 13.32 7.32 11.67 0 347.99 330.67 46146 +1908 250 13.86 7.86 12.21 0 359.26 327.58 45945 +1908 251 16.18 10.18 14.53 0 411.32 320.35 45743 +1908 252 14.17 8.17 12.52 0.05 365.87 241.94 45541 +1908 253 12.52 6.52 10.87 0.59 331.84 242.74 45339 +1908 254 14.02 8.02 12.37 0 362.66 318.56 45136 +1908 255 24.34 18.34 22.69 0 648.58 287.75 44933 +1908 256 19.91 13.91 18.26 0 508.47 299.84 44730 +1908 257 21.38 15.38 19.73 0 551.79 293.4 44527 +1908 258 23.8 17.8 22.15 0 629.93 283.25 44323 +1908 259 22.68 16.68 21.03 0 592.67 284.69 44119 +1908 260 23.11 17.11 21.46 0.74 606.75 210.75 43915 +1908 261 16.89 10.89 15.24 0.11 428.48 221.94 43711 +1908 262 17.51 11.51 15.86 0 443.96 292.11 43507 +1908 263 17.67 11.67 16.02 0 448.04 289.28 43303 +1908 264 15.05 9.05 13.4 0.35 385.21 219.37 43099 +1908 265 16.02 10.02 14.37 0 407.53 288.1 42894 +1908 266 19.19 13.19 17.54 0.18 488.33 208.67 42690 +1908 267 17.62 11.62 15.97 0 446.76 279.41 42486 +1908 268 14.37 8.37 12.72 0 370.19 283.69 42282 +1908 269 17.26 11.26 15.61 0.06 437.66 206.41 42078 +1908 270 21.3 15.3 19.65 0.82 549.35 196.86 41875 +1908 271 20.97 14.97 19.32 0 539.4 260.88 41671 +1908 272 20.62 14.62 18.97 0 529.02 259.19 41468 +1908 273 20.31 14.31 18.66 0 519.96 257.56 41265 +1908 274 14.9 8.9 13.25 0.02 381.86 200.21 41062 +1908 275 14.18 8.18 12.53 0 366.09 265.51 40860 +1908 276 15.09 9.09 13.44 0 386.11 261.15 40658 +1908 277 15.65 9.65 14 0 398.89 257.44 40456 +1908 278 13.38 7.38 11.73 0 349.23 258.65 40255 +1908 279 13.94 7.94 12.29 0 360.96 254.89 40054 +1908 280 12.28 6.28 10.63 0 327.13 254.92 39854 +1908 281 13.86 7.86 12.21 0 359.26 249.67 39654 +1908 282 14.82 8.82 13.17 0 380.08 245.29 39455 +1908 283 14.17 8.17 12.52 0 365.87 243.6 39256 +1908 284 10.2 4.2 8.55 0 288.6 246.47 39058 +1908 285 6.09 0.09 4.44 0 223.77 248.48 38861 +1908 286 3.24 -2.76 1.59 0 186.56 248.23 38664 +1908 287 5.34 -0.66 3.69 0 213.41 243.37 38468 +1908 288 7.98 1.98 6.33 0 251.83 237.84 38273 +1908 289 12.67 6.67 11.02 0 334.82 229.23 38079 +1908 290 11.39 5.39 9.74 0 310.13 228.15 37885 +1908 291 12.4 6.4 10.75 0.27 329.48 168.05 37693 +1908 292 12.15 6.15 10.5 0.02 324.6 166.3 37501 +1908 293 13.72 7.72 12.07 0.03 356.31 162.57 37311 +1908 294 16.04 10.04 14.39 0 408 210.21 37121 +1908 295 13.09 7.09 11.44 0.72 343.28 159 36933 +1908 296 11.73 5.73 10.08 0.13 316.53 158.45 36745 +1908 297 11.73 5.73 10.08 0.42 316.53 156.41 36560 +1908 298 13.35 7.35 11.7 0.1 348.61 152.85 36375 +1908 299 13.54 7.54 11.89 0 352.55 200.77 36191 +1908 300 15.75 9.75 14.1 0 401.21 194.86 36009 +1908 301 17.28 11.28 15.63 0 438.16 189.89 35829 +1908 302 12.65 6.65 11 0 334.42 194.27 35650 +1908 303 10.95 4.95 9.3 0 302.02 193.78 35472 +1908 304 14.57 8.57 12.92 0 374.56 186.7 35296 +1908 305 1.96 -4.04 0.31 0 171.66 196.38 35122 +1908 306 4.05 -1.95 2.4 0.08 196.55 144.49 34950 +1908 307 4.78 -1.22 3.13 0.26 205.94 142.17 34779 +1908 308 3.2 -2.8 1.55 0 186.07 188.04 34610 +1908 309 3.5 -2.5 1.85 0 189.71 185.48 34444 +1908 310 -1.12 -7.12 -2.77 0 139.96 185.68 34279 +1908 311 -1.63 -7.63 -3.28 0.09 135.23 176.71 34116 +1908 312 1.02 -4.98 -0.63 0.1 161.39 173.73 33956 +1908 313 1.16 -4.84 -0.49 0.23 162.88 133.04 33797 +1908 314 -0.15 -6.15 -1.8 1.24 149.35 174.84 33641 +1908 315 3.02 -2.98 1.37 0 183.92 214.33 33488 +1908 316 3.17 -2.83 1.52 0 185.71 211.83 33337 +1908 317 3.68 -2.32 2.03 0 191.93 209.03 33188 +1908 318 2.61 -3.39 0.96 0 179.09 207.19 33042 +1908 319 8.31 2.31 6.66 0 257.03 200.58 32899 +1908 320 6.34 0.34 4.69 0 227.32 199.67 32758 +1908 321 6.89 0.89 5.24 0 235.3 156.56 32620 +1908 322 5.45 -0.55 3.8 0 214.9 155.78 32486 +1908 323 3.52 -2.48 1.87 0 189.96 155.39 32354 +1908 324 5.01 -0.99 3.36 0 208.98 152.39 32225 +1908 325 -0.41 -6.41 -2.06 0.38 146.78 157.49 32100 +1908 326 6.07 0.07 4.42 0 223.49 190.14 31977 +1908 327 5.03 -0.97 3.38 0 209.25 147.33 31858 +1908 328 3.99 -2.01 2.34 0 195.79 146 31743 +1908 329 5.71 -0.29 4.06 0.03 218.47 107.56 31631 +1908 330 2.92 -3.08 1.27 0.14 182.73 107.74 31522 +1908 331 0.83 -5.17 -0.82 0.65 159.38 107.55 31417 +1908 332 -0.84 -6.84 -2.49 0 142.61 142.48 31316 +1908 333 -0.7 -6.7 -2.35 0 143.96 141.32 31218 +1908 334 -1.7 -7.7 -3.35 0.42 134.59 149.16 31125 +1908 335 0.41 -5.59 -1.24 0 155.01 182.3 31035 +1908 336 1.89 -4.11 0.24 0.14 170.88 146.21 30949 +1908 337 2.55 -3.45 0.9 0 178.39 178.17 30867 +1908 338 -0.69 -6.69 -2.34 0 144.05 178.83 30790 +1908 339 -3.19 -9.19 -4.84 0 121.62 179.07 30716 +1908 340 -8.06 -14.06 -9.71 0.57 86.46 147.6 30647 +1908 341 -5.56 -11.56 -7.21 0.36 103.21 147.62 30582 +1908 342 -5.15 -11.15 -6.8 0.09 106.21 147.33 30521 +1908 343 -5.68 -11.68 -7.33 0.44 102.34 148.29 30465 +1908 344 -5.41 -11.41 -7.06 0.14 104.3 147.9 30413 +1908 345 -0.98 -6.98 -2.63 0 141.28 178.95 30366 +1908 346 -0.09 -6.09 -1.74 0 149.94 178.1 30323 +1908 347 0.27 -5.73 -1.38 0 153.58 177.38 30284 +1908 348 1.36 -4.64 -0.29 0 165.04 176.42 30251 +1908 349 5.05 -0.95 3.4 0 209.51 173.5 30221 +1908 350 4.69 -1.31 3.04 0 204.76 172.78 30197 +1908 351 4.39 -1.61 2.74 0 200.88 172.18 30177 +1908 352 2.65 -3.35 1 0 179.56 172.67 30162 +1908 353 5.98 -0.02 4.33 0 222.23 169.98 30151 +1908 354 7.55 1.55 5.9 0 245.19 167.93 30145 +1908 355 7.05 1.05 5.4 0.15 237.67 136.58 30144 +1908 356 3.79 -2.21 2.14 0 193.29 168.77 30147 +1908 357 3.93 -2.07 2.28 0.35 195.04 93.68 30156 +1908 358 4.43 -1.57 2.78 0.19 201.39 93.54 30169 +1908 359 -1.05 -7.05 -2.7 0 140.62 127.41 30186 +1908 360 -0.59 -6.59 -2.24 0.12 145.02 139.77 30208 +1908 361 -1.11 -7.11 -2.76 0.14 140.05 140.58 30235 +1908 362 0.73 -5.27 -0.92 0 158.33 172.16 30267 +1908 363 0.12 -5.88 -1.53 0.2 152.05 140.77 30303 +1908 364 0.04 -5.96 -1.61 0.04 151.25 141.04 30343 +1908 365 -1.54 -7.54 -3.19 0 136.05 174.45 30388 +1909 1 -1.4 -7.4 -3.05 0 137.34 175.23 30438 +1909 2 -2.29 -8.29 -3.94 0 129.32 176.22 30492 +1909 3 0.08 -5.92 -1.57 0 151.65 176.14 30551 +1909 4 0.31 -5.69 -1.34 0 153.98 176.83 30614 +1909 5 2.87 -3.13 1.22 0 182.14 175.79 30681 +1909 6 1.64 -4.36 -0.01 0 168.1 176.98 30752 +1909 7 2.04 -3.96 0.39 0 172.56 134.61 30828 +1909 8 0.45 -5.55 -1.2 0 155.42 136.86 30907 +1909 9 0.7 -5.3 -0.95 0.56 158.01 103.51 30991 +1909 10 4.98 -1.02 3.33 0.09 208.58 102.77 31079 +1909 11 6.3 0.3 4.65 0.02 226.75 102.87 31171 +1909 12 2.55 -3.45 0.9 0.17 178.39 105.31 31266 +1909 13 -1.5 -7.5 -3.15 0 136.42 143.93 31366 +1909 14 1.59 -4.41 -0.06 0 167.55 144.02 31469 +1909 15 2.26 -3.74 0.61 0 175.06 145.12 31575 +1909 16 2.95 -3.05 1.3 0 183.09 146.04 31686 +1909 17 5.27 -0.73 3.62 0 212.46 146.31 31800 +1909 18 2.67 -3.33 1.02 0 179.79 149.78 31917 +1909 19 -3.2 -9.2 -4.85 0 121.53 154.44 32038 +1909 20 -1.82 -7.82 -3.47 0.38 133.5 158.8 32161 +1909 21 -2.73 -8.73 -4.38 0 125.5 199.91 32289 +1909 22 -1.04 -7.04 -2.69 0 140.71 200.8 32419 +1909 23 -0.04 -6.04 -1.69 0 150.44 201.96 32552 +1909 24 -0.56 -6.56 -2.21 0 145.31 204.12 32688 +1909 25 -6.53 -12.53 -8.18 0 96.4 208.16 32827 +1909 26 -1.09 -7.09 -2.74 0 140.24 207.87 32969 +1909 27 -1.72 -7.72 -3.37 0 134.41 210.02 33114 +1909 28 -4.22 -10.22 -5.87 0.17 113.29 170.51 33261 +1909 29 -5.45 -11.45 -7.1 0.02 104.01 172.53 33411 +1909 30 -6.73 -12.73 -8.38 0 95.05 218.86 33564 +1909 31 -2.91 -8.91 -4.56 0.07 123.97 175.14 33718 +1909 32 0.24 -5.76 -1.41 0 153.27 220.29 33875 +1909 33 -0.66 -6.66 -2.31 0 144.34 223.22 34035 +1909 34 -2.14 -8.14 -3.79 0.05 130.64 179.72 34196 +1909 35 -0.07 -6.07 -1.72 0 150.14 227.07 34360 +1909 36 -4.59 -10.59 -6.24 0 110.43 231.52 34526 +1909 37 -4.39 -10.39 -6.04 0 111.97 233.71 34694 +1909 38 -4.03 -10.03 -5.68 0 114.79 236.15 34863 +1909 39 -5.27 -11.27 -6.92 0.69 105.32 191.11 35035 +1909 40 -1.02 -7.02 -2.67 0.31 140.9 192.31 35208 +1909 41 -0.83 -6.83 -2.48 0.39 142.71 195.07 35383 +1909 42 -1.97 -7.97 -3.62 0 132.16 248.75 35560 +1909 43 -2.61 -8.61 -4.26 0 126.53 251.6 35738 +1909 44 -0.37 -6.37 -2.02 0.18 147.17 200.67 35918 +1909 45 3.86 -2.14 2.21 0.03 194.16 199.9 36099 +1909 46 1.2 -4.8 -0.45 0 163.31 256.72 36282 +1909 47 0.52 -5.48 -1.13 0 156.14 259.74 36466 +1909 48 2.75 -3.25 1.1 0 180.73 260.55 36652 +1909 49 0.01 -5.99 -1.64 0 150.94 264.98 36838 +1909 50 2.75 -3.25 1.1 0 180.73 265.31 37026 +1909 51 1.74 -4.26 0.09 0 169.21 268.64 37215 +1909 52 1.09 -4.91 -0.56 0.27 162.13 213.61 37405 +1909 53 -1.59 -7.59 -3.24 0.02 135.6 216.96 37596 +1909 54 1.41 -4.59 -0.24 0.22 165.58 217.27 37788 +1909 55 2.59 -3.41 0.94 0 178.86 278.36 37981 +1909 56 4.59 -1.41 2.94 0 203.46 278.74 38175 +1909 57 8.76 2.76 7.11 0 264.26 276.26 38370 +1909 58 11.94 5.94 10.29 0 320.54 273.61 38565 +1909 59 8.37 2.37 6.72 0.01 257.98 218.44 38761 +1909 60 13.25 7.25 11.6 0.42 346.55 181.31 38958 +1909 61 12.29 6.29 10.64 0.28 327.32 184.56 39156 +1909 62 10.74 4.74 9.09 0.14 298.21 188.28 39355 +1909 63 6.23 0.23 4.58 0 225.75 259.44 39553 +1909 64 8.96 2.96 7.31 0 267.53 259.22 39753 +1909 65 5.73 -0.27 4.08 0 218.75 265.77 39953 +1909 66 7.58 1.58 5.93 0 245.65 266.49 40154 +1909 67 6.02 0.02 4.37 0 222.79 271.12 40355 +1909 68 3.31 -2.69 1.66 0.01 187.4 207.5 40556 +1909 69 3.66 -2.34 2.01 0 191.68 279 40758 +1909 70 5.7 -0.3 4.05 0 218.33 279.84 40960 +1909 71 8.44 2.44 6.79 0 259.1 279.56 41163 +1909 72 7.95 1.95 6.3 0 251.36 283 41366 +1909 73 8.63 2.63 6.98 0 262.15 284.79 41569 +1909 74 4.62 -1.38 2.97 0.02 203.85 219.15 41772 +1909 75 4.32 -1.68 2.67 0.11 199.98 221.44 41976 +1909 76 3.85 -2.15 2.2 0.33 194.04 223.8 42179 +1909 77 1.89 -4.11 0.24 0 170.88 302.85 42383 +1909 78 3.59 -2.41 1.94 1.17 190.82 227.99 42587 +1909 79 3.92 -2.08 2.27 1.15 194.91 229.82 42791 +1909 80 0.78 -5.22 -0.87 0.72 158.85 233.9 42996 +1909 81 2.35 -3.65 0.7 0.34 176.09 234.85 43200 +1909 82 5.24 -0.76 3.59 0.05 212.06 234.66 43404 +1909 83 6.21 0.21 4.56 0 225.47 314.27 43608 +1909 84 6.37 0.37 4.72 0 227.75 316.63 43812 +1909 85 7.95 1.95 6.3 0 251.36 317.11 44016 +1909 86 9.98 3.98 8.33 0 284.76 316.57 44220 +1909 87 10.44 4.44 8.79 0 292.83 318.37 44424 +1909 88 7.57 1.57 5.92 0.2 245.5 243.72 44627 +1909 89 10.17 4.17 8.52 0 288.07 323.42 44831 +1909 90 10.25 4.25 8.6 0 289.48 325.65 45034 +1909 91 11.36 5.36 9.71 0.14 309.57 244.53 45237 +1909 92 9.33 3.33 7.68 0 273.67 331.6 45439 +1909 93 9.42 3.42 7.77 0 275.19 333.69 45642 +1909 94 12.97 6.97 11.32 0 340.85 329.64 45843 +1909 95 13.56 7.56 11.91 0.32 352.96 247.94 46045 +1909 96 13.23 7.23 11.58 0.14 346.14 250 46246 +1909 97 14.75 8.75 13.1 0 378.52 332.18 46446 +1909 98 18.84 12.84 17.19 0 478.79 323.9 46647 +1909 99 20.14 14.14 18.49 0 515.05 322.04 46846 +1909 100 15.47 9.47 13.82 0 394.74 336.37 47045 +1909 101 14.79 8.79 13.14 0.37 379.41 254.87 47243 +1909 102 15.96 9.96 14.31 0.03 406.12 254.23 47441 +1909 103 18.55 12.55 16.9 0.16 471 250.5 47638 +1909 104 13.12 7.12 11.47 0 343.89 348.92 47834 +1909 105 14.02 8.02 12.37 0.09 362.66 261.6 48030 +1909 106 14.44 8.44 12.79 0.34 371.72 262.13 48225 +1909 107 13.5 7.5 11.85 0.34 351.71 264.91 48419 +1909 108 9.31 3.31 7.66 0.47 273.34 272.12 48612 +1909 109 11.79 5.79 10.14 0 317.68 360.03 48804 +1909 110 9.98 3.98 8.33 0.05 284.76 273.57 48995 +1909 111 12.86 6.86 11.21 0 338.63 360.85 49185 +1909 112 13.37 7.37 11.72 0 349.02 361.3 49374 +1909 113 10.01 4.01 8.36 0 285.28 369.17 49561 +1909 114 11.23 5.23 9.58 0 307.16 368.45 49748 +1909 115 7.14 1.14 5.49 0 239.01 376.75 49933 +1909 116 12.52 6.52 10.87 0 331.84 368.57 50117 +1909 117 13.85 7.85 12.2 0 359.05 367.03 50300 +1909 118 14.95 8.95 13.3 0 382.97 365.79 50481 +1909 119 13.68 7.68 12.03 0 355.47 369.92 50661 +1909 120 15.11 9.11 13.46 0 386.56 367.76 50840 +1909 121 18.24 12.24 16.59 0 462.8 360.51 51016 +1909 122 20.91 14.91 19.26 0 537.61 353.22 51191 +1909 123 21.27 15.27 19.62 0 548.44 352.96 51365 +1909 124 20.45 14.45 18.8 0.21 524.04 267.6 51536 +1909 125 17.76 11.76 16.11 0.24 450.34 274.59 51706 +1909 126 17.44 11.44 15.79 0 442.19 368.01 51874 +1909 127 17.34 11.34 15.69 0 439.67 369.17 52039 +1909 128 16.07 10.07 14.42 0.48 408.71 280.2 52203 +1909 129 15.76 9.76 14.11 0.17 401.44 281.44 52365 +1909 130 13.96 7.96 12.31 0.39 361.38 285.34 52524 +1909 131 12.5 6.5 10.85 0 331.45 384.49 52681 +1909 132 11.94 5.94 10.29 0 320.54 386.5 52836 +1909 133 13.45 7.45 11.8 0.33 350.68 287.97 52989 +1909 134 13.87 7.87 12.22 0.56 359.47 287.79 53138 +1909 135 13.73 7.73 12.08 0.98 356.52 288.56 53286 +1909 136 16.64 10.64 14.99 1.49 422.37 283.55 53430 +1909 137 13.15 7.15 11.5 0.17 344.5 290.56 53572 +1909 138 16.39 10.39 14.74 0.16 416.33 285.04 53711 +1909 139 14.13 8.13 12.48 0 365.02 386.48 53848 +1909 140 21.84 15.84 20.19 0 565.97 363.86 53981 +1909 141 20.8 14.8 19.15 0.01 534.34 276.02 54111 +1909 142 20.41 14.41 18.76 0.32 522.87 277.4 54238 +1909 143 17.09 11.09 15.44 0 433.42 380.77 54362 +1909 144 15.24 9.24 13.59 0 389.5 386.21 54483 +1909 145 15.09 9.09 13.44 0.02 386.11 290.3 54600 +1909 146 14.08 8.08 12.43 1.11 363.94 292.44 54714 +1909 147 15.07 9.07 13.42 0.32 385.66 290.99 54824 +1909 148 13.6 7.6 11.95 0.1 353.8 293.94 54931 +1909 149 15.51 9.51 13.86 0 395.66 387.56 55034 +1909 150 16.36 10.36 14.71 0 415.61 385.64 55134 +1909 151 15.95 9.95 14.3 0 405.89 387.14 55229 +1909 152 21.04 15.04 19.39 0 541.5 371.45 55321 +1909 153 23.99 17.99 22.34 0 636.44 360.21 55409 +1909 154 24.22 18.22 22.57 0 644.4 359.54 55492 +1909 155 26.62 20.62 24.97 0 732.62 348.75 55572 +1909 156 22.13 16.13 20.48 0 575.07 368.48 55648 +1909 157 24.39 18.39 22.74 0 650.34 359.46 55719 +1909 158 20.88 14.88 19.23 0 536.72 373.42 55786 +1909 159 21.97 15.97 20.32 0 570.04 369.66 55849 +1909 160 20.08 14.08 18.43 0 513.33 376.62 55908 +1909 161 21.39 15.39 19.74 0 552.1 372.07 55962 +1909 162 20.11 14.11 18.46 1.35 514.19 282.49 56011 +1909 163 20.23 14.23 18.58 0.03 517.65 282.34 56056 +1909 164 20.81 14.81 19.16 0 534.64 374.47 56097 +1909 165 23.46 17.46 21.81 0 618.41 364.43 56133 +1909 166 23.74 17.74 22.09 0 627.88 363.35 56165 +1909 167 21.12 15.12 19.47 0 543.91 373.48 56192 +1909 168 19.33 13.33 17.68 0.06 492.19 284.78 56214 +1909 169 15.83 9.83 14.18 0 403.08 390.05 56231 +1909 170 18.24 12.24 16.59 0 462.8 383.16 56244 +1909 171 17.83 11.83 16.18 0.23 452.14 288.35 56252 +1909 172 16.61 10.61 14.96 0 421.64 387.97 56256 +1909 173 16.95 10.95 15.3 0.08 429.96 290.25 56255 +1909 174 16.31 10.31 14.66 0 414.42 388.7 56249 +1909 175 16.3 10.3 14.65 0.2 414.18 291.52 56238 +1909 176 22.46 16.46 20.81 0.07 585.58 276.32 56223 +1909 177 18.62 12.62 16.97 1.07 472.87 286.32 56203 +1909 178 17.06 11.06 15.41 1.06 432.68 289.84 56179 +1909 179 18.08 12.08 16.43 0.05 458.62 287.51 56150 +1909 180 17.06 11.06 15.41 0.73 432.68 289.67 56116 +1909 181 15.88 9.88 14.23 0 404.24 389.41 56078 +1909 182 16.66 10.66 15.01 0.08 422.85 290.35 56035 +1909 183 18.19 12.19 16.54 0.23 461.49 286.87 55987 +1909 184 19.59 13.59 17.94 0 499.44 377.89 55935 +1909 185 22.27 16.27 20.62 0.04 579.51 276.19 55879 +1909 186 21.35 15.35 19.7 0 550.88 371.44 55818 +1909 187 23.62 17.62 21.97 0.01 623.81 271.82 55753 +1909 188 27.35 21.35 25.7 0.22 761.39 258.79 55684 +1909 189 23.3 17.3 21.65 0.01 613.06 272.48 55611 +1909 190 22.74 16.74 21.09 0.04 594.62 273.88 55533 +1909 191 17.93 11.93 16.28 0 454.72 381.49 55451 +1909 192 17.36 11.36 15.71 0.55 440.17 287.14 55366 +1909 193 20.88 14.88 19.23 0.41 536.72 278.47 55276 +1909 194 16.59 10.59 14.94 0.31 421.16 288.39 55182 +1909 195 15.05 9.05 13.4 0.03 385.21 291.23 55085 +1909 196 22.36 16.36 20.71 0 582.38 364.94 54984 +1909 197 23.4 17.4 21.75 0 616.4 360.38 54879 +1909 198 24.64 18.64 22.99 0 659.15 354.76 54770 +1909 199 24.82 18.82 23.17 0.14 665.56 265.22 54658 +1909 200 26.68 20.68 25.03 0.25 734.95 258.5 54542 +1909 201 24.78 18.78 23.13 0 664.13 352.97 54423 +1909 202 27 21 25.35 0 747.48 342.12 54301 +1909 203 24.74 18.74 23.09 1.2 662.71 264.08 54176 +1909 204 26.77 20.77 25.12 1.67 738.45 256.72 54047 +1909 205 23.75 17.75 22.1 0.47 628.22 266.48 53915 +1909 206 21.08 15.08 19.43 0.02 542.7 273.71 53780 +1909 207 20.43 14.43 18.78 0 523.45 366.54 53643 +1909 208 16.91 10.91 15.26 0 428.97 376.73 53502 +1909 209 16.22 10.22 14.57 0.04 412.27 283.46 53359 +1909 210 17.18 11.18 15.53 0.03 435.66 281.01 53213 +1909 211 15.31 9.31 13.66 0.11 391.09 284.14 53064 +1909 212 18.13 12.13 16.48 0 459.92 370.34 52913 +1909 213 20.65 14.65 19 0.33 529.9 271.16 52760 +1909 214 25.19 19.19 23.54 0 678.9 343.16 52604 +1909 215 22.5 16.5 20.85 1.9 586.86 265.11 52445 +1909 216 21.41 15.41 19.76 1.91 552.71 267.35 52285 +1909 217 24.01 18.01 22.36 0.17 637.13 259.25 52122 +1909 218 27.81 21.81 26.16 0 780.01 327.62 51958 +1909 219 22.75 16.75 21.1 0 594.94 348.83 51791 +1909 220 24.7 18.7 23.05 0.01 661.28 255.07 51622 +1909 221 25.87 19.87 24.22 0.47 704.01 250.52 51451 +1909 222 22.82 16.82 21.17 0.19 597.22 259.23 51279 +1909 223 21.26 15.26 19.61 0.04 548.14 262.63 51105 +1909 224 25.28 19.28 23.63 0.22 682.18 250.15 50929 +1909 225 24.77 18.77 23.12 0.32 663.78 250.95 50751 +1909 226 21.2 15.2 19.55 0.4 546.32 260.3 50572 +1909 227 22.14 16.14 20.49 0 575.39 342.5 50392 +1909 228 22.28 16.28 20.63 1.08 579.83 255.6 50210 +1909 229 21.47 15.47 19.82 0.02 554.54 256.84 50026 +1909 230 26.26 20.26 24.61 0 718.77 322.28 49842 +1909 231 25.22 19.22 23.57 0.69 679.99 244.06 49656 +1909 232 23.92 17.92 22.27 0.82 634.03 247.06 49469 +1909 233 22.17 16.17 20.52 0.09 576.34 250.93 49280 +1909 234 20.71 14.71 19.06 0.8 531.67 253.61 49091 +1909 235 23.41 17.41 21.76 1 616.73 245.39 48900 +1909 236 17.14 11.14 15.49 0 434.67 345.72 48709 +1909 237 17.25 11.25 15.6 0 437.41 343.76 48516 +1909 238 18.41 12.41 16.76 0 467.28 338.91 48323 +1909 239 18.46 12.46 16.81 0.46 468.61 252.94 48128 +1909 240 22.3 16.3 20.65 0.35 580.46 242.58 47933 +1909 241 21.93 15.93 20.28 0.06 568.78 242.27 47737 +1909 242 23.46 17.46 21.81 0.03 618.41 236.93 47541 +1909 243 23.55 17.55 21.9 1.38 621.44 235.34 47343 +1909 244 16.64 10.64 14.99 0.54 422.37 249.83 47145 +1909 245 14.98 8.98 13.33 0 383.64 335.15 46947 +1909 246 15.59 9.59 13.94 0 397.51 331.76 46747 +1909 247 18.1 12.1 16.45 0 459.14 323.65 46547 +1909 248 17.19 11.19 15.54 1.21 435.91 243.05 46347 +1909 249 17.35 11.35 15.7 0 439.92 321.59 46146 +1909 250 16.38 10.38 14.73 0.03 416.09 241.5 45945 +1909 251 18.37 12.37 16.72 0 466.23 314.88 45743 +1909 252 17.96 11.96 16.31 0 455.5 313.8 45541 +1909 253 18.63 12.63 16.98 0 473.14 309.93 45339 +1909 254 22.87 16.87 21.22 0 598.86 295.06 45136 +1909 255 24.24 18.24 22.59 0.13 645.09 216.08 44933 +1909 256 25.81 19.81 24.16 0 701.77 280.04 44730 +1909 257 26.08 20.08 24.43 0.02 711.92 207.73 44527 +1909 258 23.07 17.07 21.42 0.03 605.43 214.3 44323 +1909 259 23.8 17.8 22.15 1.54 629.93 210.7 44119 +1909 260 23.79 17.79 22.14 0.47 629.58 209.03 43915 +1909 261 21.54 15.54 19.89 0 556.69 283.61 43711 +1909 262 20.27 14.27 18.62 0.77 518.8 213.74 43507 +1909 263 19.07 13.07 17.42 1.29 485.04 214.35 43303 +1909 264 18.32 12.32 16.67 0.59 464.91 213.87 43099 +1909 265 14.13 8.13 12.48 0 365.02 291.92 42894 +1909 266 16.02 10.02 14.37 0 407.53 285.62 42690 +1909 267 16.09 10.09 14.44 0 409.18 282.8 42486 +1909 268 18 12 16.35 0 456.53 275.99 42282 +1909 269 15.79 9.79 14.14 0 402.14 278.36 42078 +1909 270 14.68 8.68 13.03 1.66 376.98 208.44 41875 +1909 271 14.02 8.02 12.37 0 362.66 276.53 41671 +1909 272 17.33 11.33 15.68 0 439.42 267.16 41468 +1909 273 21.61 15.61 19.96 0.04 558.84 190.55 41265 +1909 274 18.2 12.2 16.55 0 461.75 260.1 41062 +1909 275 18.35 12.35 16.7 0 465.7 257.05 40860 +1909 276 22.02 16.02 20.37 0 571.61 245.16 40658 +1909 277 20.75 14.75 19.1 0 532.86 246.03 40456 +1909 278 14.95 8.95 13.3 0 382.97 255.91 40255 +1909 279 15.55 9.55 13.9 0 396.58 252 40054 +1909 280 14.94 8.94 13.29 0.14 382.75 187.87 39854 +1909 281 14.4 8.4 12.75 0.03 370.85 186.56 39654 +1909 282 9.73 3.73 8.08 0.37 280.45 189.74 39455 +1909 283 7.12 1.12 5.47 0 238.71 253.21 39256 +1909 284 9.85 3.85 8.2 0 282.51 246.92 39058 +1909 285 8.44 2.44 6.79 0 259.1 245.95 38861 +1909 286 12.78 6.78 11.13 0 337.02 237.42 38664 +1909 287 14.53 8.53 12.88 0 373.68 231.73 38468 +1909 288 16.81 10.81 15.16 0 426.52 224.96 38273 +1909 289 21.38 15.38 19.73 0 551.79 212.65 38079 +1909 290 20.46 14.46 18.81 0 524.33 212.09 37885 +1909 291 19.9 13.9 18.25 0.12 508.19 158.08 37693 +1909 292 15.39 9.39 13.74 0.35 392.91 162.61 37501 +1909 293 13.69 7.69 12.04 1.43 355.68 162.61 37311 +1909 294 11.17 5.17 9.52 0.13 306.05 163.06 37121 +1909 295 11.25 5.25 9.6 0.35 307.53 160.85 36933 +1909 296 12.72 6.72 11.07 0 335.82 209.95 36745 +1909 297 13.44 7.44 11.79 0.02 350.47 154.68 36560 +1909 298 16.14 10.14 14.49 0 410.37 199.54 36375 +1909 299 14.64 8.64 12.99 0 376.1 199.18 36191 +1909 300 13.95 7.95 12.3 0 361.17 197.57 36009 +1909 301 15.8 9.8 14.15 0 402.38 192.33 35829 +1909 302 13.17 7.17 11.52 0 344.91 193.58 35650 +1909 303 17.57 11.57 15.92 0 445.49 184.39 35472 +1909 304 17.62 11.62 15.97 0 446.76 181.94 35296 +1909 305 9.83 3.83 8.18 0 282.17 189.83 35122 +1909 306 9.09 3.09 7.44 0 269.68 188.34 34950 +1909 307 6.89 0.89 5.24 0 235.3 187.86 34779 +1909 308 8.69 2.69 7.04 0 263.12 183.61 34610 +1909 309 9.11 3.11 7.46 0 270.01 180.89 34444 +1909 310 4.59 -1.41 2.94 0.01 203.46 136.68 34279 +1909 311 4.19 -1.81 2.54 0 198.32 180.32 34116 +1909 312 6.65 0.65 5 0 231.79 175.8 33956 +1909 313 7.57 1.57 5.92 0.3 245.5 129.68 33797 +1909 314 7.83 1.83 6.18 0.04 249.5 128.04 33641 +1909 315 8.57 2.57 6.92 1.2 261.19 125.66 33488 +1909 316 9.89 3.89 8.24 0 283.2 164.15 33337 +1909 317 6.78 0.78 5.13 0 233.69 164.67 33188 +1909 318 6.15 0.15 4.5 0 224.62 162.8 33042 +1909 319 4.67 -1.33 3.02 0.01 204.5 121.61 32899 +1909 320 5.53 -0.47 3.88 0 215.99 159.67 32758 +1909 321 4.33 -1.67 2.68 0.13 200.11 118.77 32620 +1909 322 1.1 -4.9 -0.55 0 162.24 158.39 32486 +1909 323 2.66 -3.34 1.01 0 179.67 155.9 32354 +1909 324 4.04 -1.96 2.39 0 196.42 153.01 32225 +1909 325 6.04 0.04 4.39 0 223.07 149.96 32100 +1909 326 4.26 -1.74 2.61 0 199.21 149.67 31977 +1909 327 4.19 -1.81 2.54 0 198.32 147.86 31858 +1909 328 4.55 -1.45 2.9 0.17 202.94 109.25 31743 +1909 329 3.88 -2.12 2.23 0 194.41 144.56 31631 +1909 330 2.17 -3.83 0.52 0 174.03 144.06 31522 +1909 331 5.94 -0.06 4.29 0 221.67 140.5 31417 +1909 332 6.32 0.32 4.67 0 227.04 138.61 31316 +1909 333 7.73 1.73 6.08 0 247.95 136.53 31218 +1909 334 8.6 2.6 6.95 0 261.67 134.78 31125 +1909 335 5.13 -0.87 3.48 0.74 210.58 102.01 31035 +1909 336 1.74 -4.26 0.09 0.76 169.21 102.61 30949 +1909 337 4.25 -1.75 2.6 0.2 199.08 100.36 30867 +1909 338 5.87 -0.13 4.22 0 220.69 131.88 30790 +1909 339 7.94 1.94 6.29 0 251.21 129.7 30716 +1909 340 3.61 -2.39 1.96 0 191.06 131.7 30647 +1909 341 4.4 -1.6 2.75 0 201 130.33 30582 +1909 342 4.06 -1.94 2.41 0 196.67 129.76 30521 +1909 343 5.59 -0.41 3.94 0.06 216.82 96.03 30465 +1909 344 9.54 3.54 7.89 0 277.21 124.17 30413 +1909 345 7.33 1.33 5.68 0.45 241.86 94.03 30366 +1909 346 4.67 -1.33 3.02 0.05 204.5 94.86 30323 +1909 347 1.93 -4.07 0.28 0 171.33 127.32 30284 +1909 348 2.72 -3.28 1.07 0 180.38 126.58 30251 +1909 349 1.53 -4.47 -0.12 0 166.89 126.77 30221 +1909 350 0.19 -5.81 -1.46 0 152.76 127.03 30197 +1909 351 0.78 -5.22 -0.87 0.01 158.85 94.91 30177 +1909 352 3.9 -2.1 2.25 0.26 194.66 93.71 30162 +1909 353 4.93 -1.07 3.28 0.32 207.92 93.23 30151 +1909 354 7.96 1.96 6.31 0 251.52 122.35 30145 +1909 355 10.29 4.29 8.64 0.19 290.18 90.44 30144 +1909 356 16.62 10.62 14.97 0.52 421.88 85.78 30147 +1909 357 12.67 6.67 11.02 0.24 334.82 88.95 30156 +1909 358 13.58 7.58 11.93 0.77 353.38 88.36 30169 +1909 359 6.52 0.52 4.87 0.38 229.91 92.69 30186 +1909 360 5.56 -0.44 3.91 1.19 216.41 93.41 30208 +1909 361 4.67 -1.33 3.02 2.44 204.5 94.05 30235 +1909 362 4.87 -1.13 3.22 0 207.13 125.72 30267 +1909 363 4.78 -1.22 3.13 0.18 205.94 94.77 30303 +1909 364 3.1 -2.9 1.45 0.23 184.88 95.76 30343 +1909 365 4.25 -1.75 2.6 0 199.08 127.62 30388 +1910 1 3.36 -2.64 1.71 0 188.01 129 30438 +1910 2 5.92 -0.08 4.27 0.15 221.39 96.19 30492 +1910 3 5.76 -0.24 4.11 0 219.16 129.29 30551 +1910 4 5.39 -0.61 3.74 0 214.09 130.43 30614 +1910 5 5.32 -0.68 3.67 0 213.14 131.11 30681 +1910 6 3.58 -2.42 1.93 0 190.7 133.01 30752 +1910 7 7.6 1.6 5.95 0.41 245.96 98.45 30828 +1910 8 3.96 -2.04 2.31 0.14 195.41 101.31 30907 +1910 9 6.01 0.01 4.36 0.47 222.65 101.31 30991 +1910 10 7.44 1.44 5.79 0.25 243.52 101.54 31079 +1910 11 3.28 -2.72 1.63 0.58 187.04 104.25 31171 +1910 12 3.64 -2.36 1.99 0 191.43 139.81 31266 +1910 13 3.81 -2.19 2.16 0 193.54 141.34 31366 +1910 14 3.31 -2.69 1.66 0 187.4 143.1 31469 +1910 15 4.99 -1.01 3.34 0 208.72 143.54 31575 +1910 16 3.24 -2.76 1.59 0.08 186.56 109.41 31686 +1910 17 0.24 -5.76 -1.41 0 153.27 149.12 31800 +1910 18 -0.03 -6.03 -1.68 0 150.54 151.16 31917 +1910 19 0.35 -5.65 -1.3 0 154.39 152.92 32038 +1910 20 -0.3 -6.3 -1.95 0 147.86 154.83 32161 +1910 21 0.34 -5.66 -1.31 0 154.29 156.55 32289 +1910 22 4.1 -1.9 2.45 0.14 197.18 117.16 32419 +1910 23 6.27 0.27 4.62 0.64 226.32 117.38 32552 +1910 24 5.06 -0.94 3.41 0.01 209.65 119.56 32688 +1910 25 6.9 0.9 5.25 0.55 235.45 119.96 32827 +1910 26 2.61 -3.39 0.96 0.81 179.09 123.59 32969 +1910 27 2.52 -3.48 0.87 0.82 178.05 125.15 33114 +1910 28 2.24 -3.76 0.59 0.31 174.83 126.94 33261 +1910 29 -0.2 -6.2 -1.85 1.03 148.85 172.2 33411 +1910 30 -1.08 -7.08 -2.73 0.72 140.33 176.09 33564 +1910 31 -1.63 -7.63 -3.28 0.53 135.23 179.39 33718 +1910 32 4.18 -1.82 2.53 0.8 198.19 177.79 33875 +1910 33 3.75 -2.25 2.1 0.42 192.79 179.33 34035 +1910 34 1.16 -4.84 -0.49 0.4 162.88 181.86 34196 +1910 35 5.67 -0.33 4.02 0 217.92 226.07 34360 +1910 36 5.01 -0.99 3.36 0 208.98 228.3 34526 +1910 37 6.21 0.21 4.56 0.17 225.47 181.96 34694 +1910 38 3.78 -2.22 2.13 0 193.17 232.8 34863 +1910 39 5.77 -0.23 4.12 0.13 219.3 184.73 35035 +1910 40 5.48 -0.52 3.83 0 215.31 235.05 35208 +1910 41 4.83 -1.17 3.18 0 206.6 237.44 35383 +1910 42 9.45 3.45 7.8 0 275.69 197.47 35560 +1910 43 8.21 2.21 6.56 0 255.44 201.42 35738 +1910 44 7.61 1.61 5.96 0 246.11 204.54 35918 +1910 45 9.98 3.98 8.33 0 284.76 204.66 36099 +1910 46 5.21 -0.79 3.56 0 211.65 211.99 36282 +1910 47 5.17 -0.83 3.52 1.04 211.12 161.13 36466 +1910 48 4.1 -1.9 2.45 0.1 197.18 163.9 36652 +1910 49 4.62 -1.38 2.97 0 203.85 220.89 36838 +1910 50 5.9 -0.1 4.25 0.28 221.11 166.83 37026 +1910 51 7.37 1.37 5.72 0.32 242.46 167.99 37215 +1910 52 9.45 3.45 7.8 1.71 275.69 168.4 37405 +1910 53 8.77 2.77 7.12 0.79 264.42 171.18 37596 +1910 54 5.75 -0.25 4.1 0 219.02 234.08 37788 +1910 55 7.69 1.69 6.04 0.02 247.34 176.34 37981 +1910 56 10.39 4.39 8.74 0 291.95 234.63 38175 +1910 57 6.93 0.93 5.28 0.15 235.89 181.11 38370 +1910 58 7.97 1.97 6.32 0.26 251.67 182.46 38565 +1910 59 9.66 3.66 8.01 0 279.26 243.96 38761 +1910 60 12.32 6.32 10.67 0.17 327.91 182.37 38958 +1910 61 10.94 4.94 9.29 0.12 301.83 186.01 39156 +1910 62 7.81 1.81 6.16 0.02 249.19 191.04 39355 +1910 63 4.24 -1.76 2.59 0 198.96 261.39 39553 +1910 64 4.03 -1.97 2.38 0.05 196.29 198.38 39753 +1910 65 5.46 -0.54 3.81 0 215.04 266.04 39953 +1910 66 5.87 -0.13 4.22 0 220.69 268.37 40154 +1910 67 5.67 -0.33 4.02 0 217.92 271.49 40355 +1910 68 6.28 0.28 4.63 0 226.47 273.73 40556 +1910 69 8.35 2.35 6.7 0 257.66 273.93 40758 +1910 70 6.47 0.47 4.82 0 229.19 279 40960 +1910 71 4.8 -1.2 3.15 0 206.2 283.71 41163 +1910 72 6.09 0.09 4.44 0 223.77 285.18 41366 +1910 73 4.26 -1.74 2.61 0 199.21 289.79 41569 +1910 74 3.16 -2.84 1.51 0.1 185.59 220.22 41772 +1910 75 8.22 2.22 6.57 0 255.6 290.79 41976 +1910 76 12.8 6.8 11.15 0 337.42 286.51 42179 +1910 77 11.36 5.36 9.71 0 309.57 291.47 42383 +1910 78 11.04 5.04 9.39 0 303.66 294.61 42587 +1910 79 12.97 6.97 11.32 0 340.85 294.06 42791 +1910 80 10.15 4.15 8.5 0 287.72 301.21 42996 +1910 81 12.43 6.43 10.78 0 330.07 300.05 43200 +1910 82 13.75 7.75 12.1 0 356.94 300.25 43404 +1910 83 10.53 4.53 8.88 0 294.44 308.3 43608 +1910 84 6.78 0.78 5.13 0 233.69 316.13 43812 +1910 85 6.85 0.85 5.2 0 234.71 318.55 44016 +1910 86 7.42 1.42 5.77 0 243.22 320.24 44220 +1910 87 11.01 5.01 9.36 0 303.11 317.44 44424 +1910 88 10.93 4.93 9.28 0 301.65 319.91 44627 +1910 89 12.74 6.74 11.09 0 336.22 318.97 44831 +1910 90 13.61 7.61 11.96 0 354.01 319.63 45034 +1910 91 15.63 9.63 13.98 0 398.43 317.57 45237 +1910 92 16.66 10.66 15.01 0 422.85 317.36 45439 +1910 93 11.63 5.63 9.98 0 314.64 330 45642 +1910 94 9.11 3.11 7.46 0.23 270.01 252.25 45843 +1910 95 9.09 3.09 7.44 0.02 269.68 253.89 46045 +1910 96 7.13 1.13 5.48 0 238.86 343.49 46246 +1910 97 2.43 -3.57 0.78 0.08 177.01 263.36 46446 +1910 98 5.7 -0.3 4.05 0 218.33 349.45 46647 +1910 99 8.16 2.16 6.51 0 254.65 348.13 46846 +1910 100 8.07 2.07 6.42 0.29 253.24 262.68 47045 +1910 101 10.49 4.49 8.84 0.07 293.72 261.23 47243 +1910 102 12.08 6.08 10.43 0 323.24 347.33 47441 +1910 103 10.97 4.97 9.32 0 302.38 351.22 47638 +1910 104 10.72 4.72 9.07 0 297.85 353.5 47834 +1910 105 13 7 11.35 0 341.45 350.95 48030 +1910 106 10.28 4.28 8.63 0 290 357.74 48225 +1910 107 13.63 7.63 11.98 0 354.42 352.94 48419 +1910 108 15.54 9.54 13.89 0 396.35 350.32 48612 +1910 109 16.62 10.62 14.97 0 421.88 349.22 48804 +1910 110 16.41 10.41 14.76 0 416.81 351.14 48995 +1910 111 13.49 7.49 11.84 0.15 351.51 269.64 49185 +1910 112 11.79 5.79 10.14 0.11 317.68 273.39 49374 +1910 113 11.55 5.55 9.9 0 313.13 366.34 49561 +1910 114 12.14 6.14 10.49 0.01 324.4 275.01 49748 +1910 115 16.58 10.58 14.93 0.31 420.91 268.43 49933 +1910 116 15.82 9.82 14.17 0.11 402.84 270.79 50117 +1910 117 13.63 7.63 11.98 0.83 354.42 275.64 50300 +1910 118 13.6 7.6 11.95 0.85 353.8 276.68 50481 +1910 119 13.74 7.74 12.09 0.92 356.73 277.34 50661 +1910 120 13.05 7.05 11.4 0.8 342.47 279.35 50840 +1910 121 18.33 12.33 16.68 1.07 465.17 270.18 51016 +1910 122 20.17 14.17 18.52 0.28 515.92 266.77 51191 +1910 123 21.41 15.41 19.76 0.05 552.71 264.35 51365 +1910 124 20.24 14.24 18.59 0.02 517.94 268.13 51536 +1910 125 20.38 14.38 18.73 0.44 522 268.49 51706 +1910 126 17.38 11.38 15.73 1.73 440.68 276.13 51874 +1910 127 16.25 10.25 14.6 0.19 412.98 279.1 52039 +1910 128 14.8 8.8 13.15 0.08 379.63 282.6 52203 +1910 129 15.41 9.41 13.76 0 393.37 376.15 52365 +1910 130 14.54 8.54 12.89 0 373.9 379.08 52524 +1910 131 13.85 7.85 12.2 0 359.05 381.5 52681 +1910 132 14.15 8.15 12.5 0.01 365.44 286.23 52836 +1910 133 14.79 8.79 13.14 0 379.41 380.81 52989 +1910 134 12.49 6.49 10.84 0 331.25 386.79 53138 +1910 135 13.83 7.83 12.18 0.09 358.63 288.39 53286 +1910 136 11.56 5.56 9.91 1.24 313.32 292.56 53430 +1910 137 10.92 4.92 9.27 0.31 301.47 294.05 53572 +1910 138 14.71 8.71 13.06 0.7 377.64 288.29 53711 +1910 139 14.73 8.73 13.08 0 378.08 385.03 53848 +1910 140 19.41 13.41 17.76 0.03 494.41 279.21 53981 +1910 141 17.06 11.06 15.41 0 432.68 379.82 54111 +1910 142 15.44 9.44 13.79 0 394.06 384.68 54238 +1910 143 17.81 11.81 16.16 0 451.62 378.68 54362 +1910 144 18.68 12.68 17.03 0.9 474.48 282.39 54483 +1910 145 22.87 16.87 21.22 0.03 598.86 271.69 54600 +1910 146 19.3 13.3 17.65 0.15 491.36 281.54 54714 +1910 147 18.48 12.48 16.83 0.01 469.14 283.84 54824 +1910 148 20.04 14.04 18.39 0.28 512.18 280.35 54931 +1910 149 21.86 15.86 20.21 1.85 566.6 275.73 55034 +1910 150 18.59 12.59 16.94 1.65 472.07 284.35 55134 +1910 151 22.87 16.87 21.22 0.1 598.86 273.34 55229 +1910 152 27.26 21.26 25.61 0 757.79 344.88 55321 +1910 153 26.23 20.23 24.58 0.21 717.62 262.62 55409 +1910 154 24.61 18.61 22.96 0.27 658.09 268.39 55492 +1910 155 24.71 18.71 23.06 0.05 661.64 268.2 55572 +1910 156 18.42 12.42 16.77 0.79 467.55 285.93 55648 +1910 157 18.44 12.44 16.79 0 468.08 381.34 55719 +1910 158 16.15 10.15 14.5 0.09 410.61 291.11 55786 +1910 159 13.27 7.27 11.62 0.73 346.96 296.67 55849 +1910 160 11.55 5.55 9.9 0 313.13 399.47 55908 +1910 161 14.4 8.4 12.75 0.02 370.85 294.86 55962 +1910 162 12.31 6.31 10.66 0 327.71 398.01 56011 +1910 163 12.05 6.05 10.4 0.14 322.66 299.09 56056 +1910 164 13.55 7.55 11.9 0.14 352.75 296.63 56097 +1910 165 15.43 9.43 13.78 0.01 393.83 293.24 56133 +1910 166 18.02 12.02 16.37 0.41 457.05 287.84 56165 +1910 167 17.42 11.42 15.77 0.18 441.69 289.14 56192 +1910 168 19.51 13.51 17.86 0.09 497.2 284.34 56214 +1910 169 22.6 16.6 20.95 0.37 590.08 276 56231 +1910 170 25.72 19.72 24.07 0.26 698.41 265.98 56244 +1910 171 27.4 21.4 25.75 0.29 763.4 259.88 56252 +1910 172 25.32 19.32 23.67 1.27 683.64 267.4 56256 +1910 173 25.37 19.37 23.72 4.11 685.47 267.22 56255 +1910 174 21.67 15.67 20.02 0.8 560.7 278.63 56249 +1910 175 25.93 19.93 24.28 0 706.27 353.58 56238 +1910 176 27.29 21.29 25.64 0.06 758.99 260.17 56223 +1910 177 30.6 24.6 28.95 0.3 901.38 246.35 56203 +1910 178 26.87 20.87 25.22 0.92 742.37 261.7 56179 +1910 179 25.83 19.83 24.18 0.93 702.51 265.38 56150 +1910 180 21.82 15.82 20.17 1.2 565.35 277.93 56116 +1910 181 23.56 17.56 21.91 0.66 621.78 272.74 56078 +1910 182 24.79 18.79 23.14 0.01 664.49 268.69 56035 +1910 183 21.23 15.23 19.58 0 547.23 372.37 55987 +1910 184 20.97 14.97 19.32 0.06 539.4 279.86 55935 +1910 185 24.71 18.71 23.06 0.04 661.64 268.66 55879 +1910 186 20.57 14.57 18.92 0 527.55 374.22 55818 +1910 187 23.81 17.81 22.16 1.13 630.27 271.23 55753 +1910 188 20.43 14.43 18.78 0.88 523.45 280.69 55684 +1910 189 21.45 15.45 19.8 0.7 553.93 277.83 55611 +1910 190 23.07 17.07 21.42 0 605.43 363.87 55533 +1910 191 25.54 19.54 23.89 0 691.73 353.01 55451 +1910 192 26.07 20.07 24.42 0.08 711.55 262.69 55366 +1910 193 23.12 17.12 21.47 0 607.08 362.85 55276 +1910 194 20.38 14.38 18.73 0 522 372.81 55182 +1910 195 19.46 13.46 17.81 0 495.8 375.62 55085 +1910 196 16.73 10.73 15.08 0.54 424.56 287.58 54984 +1910 197 17.13 11.13 15.48 0.02 434.42 286.39 54879 +1910 198 15.04 9.04 13.39 0 384.99 387.01 54770 +1910 199 17.01 11.01 15.36 0 431.44 381.39 54658 +1910 200 19.43 13.43 17.78 0.04 494.97 280.25 54542 +1910 201 21.25 15.25 19.6 0.3 547.84 275.23 54423 +1910 202 19.21 13.21 17.56 0 488.88 373.33 54301 +1910 203 21.55 15.55 19.9 0.87 557 273.62 54176 +1910 204 22.78 16.78 21.13 0.53 595.92 269.77 54047 +1910 205 20.7 14.7 19.05 0.43 531.38 275.13 53915 +1910 206 17.87 11.87 16.22 0.04 453.17 281.49 53780 +1910 207 21.36 15.36 19.71 0 551.18 363.29 53643 +1910 208 22.93 16.93 21.28 0 600.82 356.76 53502 +1910 209 25.4 19.4 23.75 0 686.58 345.78 53359 +1910 210 23.44 17.44 21.79 0.43 617.74 265.12 53213 +1910 211 21.4 15.4 19.75 0.67 552.4 270.35 53064 +1910 212 19.16 13.16 17.51 0.85 487.51 275.39 52913 +1910 213 17.11 11.11 15.46 2.1 433.92 279.37 52760 +1910 214 16.51 10.51 14.86 0.14 419.22 280.03 52604 +1910 215 14.5 8.5 12.85 0 373.03 377.77 52445 +1910 216 14.67 8.67 13.02 0.31 376.76 282.24 52285 +1910 217 19.98 13.98 18.33 0.71 510.47 270.34 52122 +1910 218 20.98 14.98 19.33 0 539.7 356.28 51958 +1910 219 20.28 14.28 18.63 0 519.09 357.61 51791 +1910 220 22.93 16.93 21.28 0 600.82 347.22 51622 +1910 221 22.69 16.69 21.04 0.21 593 260.37 51451 +1910 222 25.04 19.04 23.39 0.15 673.47 252.5 51279 +1910 223 20.45 14.45 18.8 0 524.04 352.92 51105 +1910 224 21.44 15.44 19.79 0 553.62 348.5 50929 +1910 225 22.49 16.49 20.84 0 586.54 343.6 50751 +1910 226 23.35 17.35 21.7 0.72 614.73 254.42 50572 +1910 227 23.6 17.6 21.95 0 623.13 337.01 50392 +1910 228 26.25 20.25 24.6 0 718.38 324.69 50210 +1910 229 25.93 19.93 24.28 0.01 706.27 243.71 50026 +1910 230 26.94 20.94 25.29 0.1 745.11 239.37 49842 +1910 231 24.87 18.87 23.22 0.29 667.35 245.16 49656 +1910 232 23.72 17.72 22.07 0.13 627.2 247.64 49469 +1910 233 22.49 16.49 20.84 0.5 586.54 250.07 49280 +1910 234 25.4 19.4 23.75 0.75 686.58 240.49 49091 +1910 235 23.38 17.38 21.73 0.07 615.73 245.48 48900 +1910 236 21.17 15.17 19.52 0 545.42 333.75 48709 +1910 237 18.24 12.24 16.59 0.16 462.8 255.8 48516 +1910 238 23.37 17.37 21.72 0.23 615.39 242.06 48323 +1910 239 19.59 13.59 17.94 0 499.44 333.96 48128 +1910 240 18.46 12.46 16.81 0.01 468.61 251.62 47933 +1910 241 20.08 14.08 18.43 0 513.33 329.02 47737 +1910 242 21.91 15.91 20.26 0.25 568.16 241.05 47541 +1910 243 20.42 14.42 18.77 1.43 523.16 243.3 47343 +1910 244 17.49 11.49 15.84 0.81 443.46 248.2 47145 +1910 245 13.19 7.19 11.54 0 345.32 338.96 46947 +1910 246 18.53 12.53 16.88 0 470.47 324.34 46747 +1910 247 18.5 12.5 16.85 0.05 469.67 241.93 46547 +1910 248 19.26 13.26 17.61 0 490.26 318.52 46347 +1910 249 18.55 12.55 16.9 0 471 318.44 46146 +1910 250 20.22 14.22 18.57 0.02 517.36 233.82 45945 +1910 251 19 13 17.35 0.12 483.13 234.88 45743 +1910 252 15.79 9.79 14.14 0.18 402.14 239.3 45541 +1910 253 16.12 10.12 14.47 0.9 409.89 237.13 45339 +1910 254 13.35 7.35 11.7 0.75 348.61 239.92 45136 +1910 255 14.46 8.46 12.81 1.47 372.15 236.52 44933 +1910 256 17.01 11.01 15.36 0.07 431.44 230.55 44730 +1910 257 19.09 13.09 17.44 0.87 485.59 224.98 44527 +1910 258 18.81 12.81 17.16 0 477.98 298.4 44323 +1910 259 16.28 10.28 14.63 0.06 413.7 226.61 44119 +1910 260 15.47 9.47 13.82 1.9 394.74 226.15 43915 +1910 261 17.31 11.31 15.66 0 438.92 294.94 43711 +1910 262 18.16 12.16 16.51 0.37 460.7 217.9 43507 +1910 263 18.01 12.01 16.36 0.33 456.79 216.35 43303 +1910 264 22.4 16.4 20.75 0.28 583.66 205.39 43099 +1910 265 21.62 15.62 19.97 0.2 559.15 205.46 42894 +1910 266 15.87 9.87 14.22 0.68 404.01 214.45 42690 +1910 267 12.9 6.9 11.25 0 339.43 288.96 42486 +1910 268 16.2 10.2 14.55 0 411.79 280.01 42282 +1910 269 19.57 13.57 17.92 0.14 498.88 202.25 42078 +1910 270 12.17 6.17 10.52 0.55 324.99 211.78 41875 +1910 271 13.48 7.48 11.83 0.58 351.3 208.12 41671 +1910 272 15.65 9.65 14 0.61 398.89 203.01 41468 +1910 273 11.07 5.07 9.42 0 304.21 276.1 41265 +1910 274 9.4 3.4 7.75 0 274.85 275.75 41062 +1910 275 10.82 4.82 9.17 0 299.65 270.94 40860 +1910 276 8.82 2.82 7.17 0 265.24 270.92 40658 +1910 277 7.93 1.93 6.28 0.01 251.05 201.97 40456 +1910 278 8.1 2.1 6.45 0 253.71 266.16 40255 +1910 279 15.63 9.63 13.98 0 398.43 251.85 40054 +1910 280 19.93 13.93 18.28 0 509.04 240.07 39854 +1910 281 17.53 11.53 15.88 0 444.47 242.81 39654 +1910 282 18.28 12.28 16.63 0.32 463.85 178.91 39455 +1910 283 17.72 11.72 16.07 0.16 449.31 177.74 39256 +1910 284 17.62 11.62 15.97 0 446.76 234.24 39058 +1910 285 17.4 11.4 15.75 0 441.18 232.11 38861 +1910 286 15.65 9.65 14 0 398.89 232.71 38664 +1910 287 14.01 8.01 12.36 0 362.45 232.58 38468 +1910 288 12.32 6.32 10.67 0 327.91 232.37 38273 +1910 289 15.73 9.73 14.08 0 400.75 224.34 38079 +1910 290 16.96 10.96 15.31 0.08 430.2 164.49 37885 +1910 291 15.15 9.15 13.5 0 387.46 219.86 37693 +1910 292 13.59 7.59 11.94 0.02 353.59 164.75 37501 +1910 293 10.83 4.83 9.18 0 299.83 220.73 37311 +1910 294 12.85 6.85 11.2 0 338.42 215.16 37121 +1910 295 14.53 8.53 12.88 0 373.68 209.87 36933 +1910 296 13.41 7.41 11.76 0.08 349.85 156.74 36745 +1910 297 13.89 7.89 12.24 0.07 359.9 154.2 36560 +1910 298 15.15 9.15 13.5 0.31 387.46 150.85 36375 +1910 299 14.17 8.17 12.52 0.78 365.87 149.91 36191 +1910 300 14.21 8.21 12.56 0 366.73 197.2 36009 +1910 301 14.53 8.53 12.88 0 373.68 194.26 35829 +1910 302 11.75 5.75 10.1 0 316.91 195.4 35650 +1910 303 7.64 1.64 5.99 0 246.57 197.24 35472 +1910 304 6.24 0.24 4.59 0 225.9 196 35296 +1910 305 -0.9 -6.9 -2.55 1.13 142.04 189.2 35122 +1910 306 -0.93 -6.93 -2.58 0.51 141.76 189.07 34950 +1910 307 3.57 -2.43 1.92 1.37 190.57 184.9 34779 +1910 308 2.63 -3.37 0.98 0.3 179.33 183.28 34610 +1910 309 -2.85 -8.85 -4.5 0.01 124.48 183.95 34444 +1910 310 -2.7 -8.7 -4.35 0.78 125.76 184.4 34279 +1910 311 -2.75 -8.75 -4.4 0.46 125.33 184.24 34116 +1910 312 3.76 -2.24 2.11 0.16 192.92 179.32 33956 +1910 313 6.42 0.42 4.77 0 228.47 219.16 33797 +1910 314 9 3 7.35 0.02 268.19 171.7 33641 +1910 315 3.83 -2.17 2.18 0.22 193.79 172.58 33488 +1910 316 3.52 -2.48 1.87 0.51 189.96 170.85 33337 +1910 317 1.65 -4.35 0 0.01 168.21 170.02 33188 +1910 318 6.15 0.15 4.5 0.37 224.62 165.5 33042 +1910 319 7.6 1.6 5.95 0.01 245.96 162.64 32899 +1910 320 4.76 -1.24 3.11 0.1 205.68 162.4 32758 +1910 321 6.98 0.98 5.33 0 236.63 198.06 32620 +1910 322 9.96 3.96 8.31 0 284.41 152.17 32486 +1910 323 13.56 7.56 11.91 0 352.96 146.91 32354 +1910 324 14.7 8.7 13.05 0 377.42 143.58 32225 +1910 325 16.41 10.41 14.76 0.06 416.81 104.82 32100 +1910 326 13.23 7.23 11.58 1.62 346.14 106.64 31977 +1910 327 10.46 4.46 8.81 1.29 293.19 107.36 31858 +1910 328 11.76 5.76 10.11 1.7 317.1 104.98 31743 +1910 329 14.29 8.29 12.64 0.83 368.46 101.89 31631 +1910 330 12.51 6.51 10.86 0 331.65 136.35 31522 +1910 331 13.18 7.18 11.53 0.03 345.12 100.79 31417 +1910 332 9.37 3.37 7.72 0 274.35 136.32 31316 +1910 333 9.51 3.51 7.86 0 276.71 135.14 31218 +1910 334 10.59 4.59 8.94 0.22 295.51 99.85 31125 +1910 335 12.97 6.97 11.32 0 340.85 129.75 31035 +1910 336 10.18 4.18 8.53 0.27 288.25 98.47 30949 +1910 337 8.1 2.1 6.45 0 253.71 131.29 30867 +1910 338 9.25 3.25 7.6 0.76 272.34 97.11 30790 +1910 339 6.83 0.83 5.18 0.61 234.42 97.85 30716 +1910 340 2.01 -3.99 0.36 0 172.22 132.52 30647 +1910 341 2.69 -3.31 1.04 0 180.03 131.26 30582 +1910 342 3.83 -2.17 2.18 0.01 193.79 97.42 30521 +1910 343 4.75 -1.25 3.1 0 205.55 128.55 30465 +1910 344 8.41 2.41 6.76 0 258.62 125.03 30413 +1910 345 7.3 1.3 5.65 0 241.41 125.39 30366 +1910 346 4.79 -1.21 3.14 0.01 206.07 94.81 30323 +1910 347 7.24 1.24 5.59 0 240.5 124.3 30284 +1910 348 5.46 -0.54 3.81 0 215.04 125.08 30251 +1910 349 9.56 3.56 7.91 0 277.55 121.9 30221 +1910 350 9.38 3.38 7.73 0 274.51 121.71 30197 +1910 351 6.83 0.83 5.18 0 234.42 123.3 30177 +1910 352 3.86 -2.14 2.21 0 194.16 124.96 30162 +1910 353 2.4 -3.6 0.75 0.08 176.66 94.23 30151 +1910 354 5.46 -0.54 3.81 0 215.04 123.96 30145 +1910 355 7.94 1.94 6.29 0 251.21 122.36 30144 +1910 356 10.48 4.48 8.83 0 293.55 120.46 30147 +1910 357 6.31 0.31 4.66 0 226.89 123.52 30156 +1910 358 8.01 2.01 6.36 0 252.3 122.48 30169 +1910 359 10.34 4.34 8.69 0.38 291.06 90.62 30186 +1910 360 8.44 2.44 6.79 0.47 259.1 91.99 30208 +1910 361 7.44 1.44 5.79 0 243.52 123.68 30235 +1910 362 7.54 1.54 5.89 0 245.04 124.04 30267 +1910 363 5.86 -0.14 4.21 0 220.55 125.72 30303 +1910 364 3.61 -2.39 1.96 0.12 191.06 95.55 30343 +1910 365 3.7 -2.3 2.05 0.35 192.17 95.94 30388 +1911 1 -0.74 -6.74 -2.39 0 143.57 130.9 30438 +1911 2 2.5 -3.5 0.85 0 177.82 130.18 30492 +1911 3 -2.89 -8.89 -4.54 0 124.14 133.4 30551 +1911 4 -5.98 -11.98 -7.63 0.08 100.21 144.84 30614 +1911 5 -3.27 -9.27 -4.92 0 120.95 178.39 30681 +1911 6 -4.05 -10.05 -5.7 0.04 114.63 145.51 30752 +1911 7 0.43 -5.57 -1.22 0 155.21 178.5 30828 +1911 8 4.76 -1.24 3.11 0.01 205.68 100.96 30907 +1911 9 5.08 -0.92 3.43 0 209.91 135.67 30991 +1911 10 6.1 0.1 4.45 1.08 223.91 102.24 31079 +1911 11 7.56 1.56 5.91 2.19 245.35 102.21 31171 +1911 12 2.82 -3.18 1.17 0.22 181.55 105.2 31266 +1911 13 -0.71 -6.71 -2.36 0.01 143.86 149.81 31366 +1911 14 -4.17 -10.17 -5.82 0 113.69 188.39 31469 +1911 15 -3.76 -9.76 -5.41 0 116.95 189.58 31575 +1911 16 -4.98 -10.98 -6.63 0 107.47 191.16 31686 +1911 17 -2.1 -8.1 -3.75 0 131 191.67 31800 +1911 18 4.61 -1.39 2.96 0 203.72 148.63 31917 +1911 19 3.83 -2.17 2.18 0 193.79 151.04 32038 +1911 20 6.89 0.89 5.24 0 235.3 150.56 32161 +1911 21 4.23 -1.77 2.58 0 198.83 154.39 32289 +1911 22 1.11 -4.89 -0.54 0 162.35 157.93 32419 +1911 23 -1.75 -7.75 -3.4 0 134.14 161.07 32552 +1911 24 1.18 -4.82 -0.47 0 163.1 161.75 32688 +1911 25 6.76 0.76 5.11 0 233.39 160.06 32827 +1911 26 6.14 0.14 4.49 0 224.48 162.44 32969 +1911 27 3.06 -2.94 1.41 0.05 184.4 124.91 33114 +1911 28 1.52 -4.48 -0.13 0 166.78 169.67 33261 +1911 29 3.35 -2.65 1.7 0 187.89 170.96 33411 +1911 30 0.18 -5.82 -1.47 0 152.66 175.04 33564 +1911 31 1.33 -4.67 -0.32 0 164.72 176.81 33718 +1911 32 0.81 -5.19 -0.84 0.14 159.17 134.42 33875 +1911 33 -0.03 -6.03 -1.68 0 150.54 182.34 34035 +1911 34 -0.46 -6.46 -2.11 0 146.29 184.79 34196 +1911 35 5.51 -0.49 3.86 0 215.72 183.14 34360 +1911 36 6.79 0.79 5.14 0 233.83 184.61 34526 +1911 37 6.88 0.88 5.23 0 235.16 186.94 34694 +1911 38 7.87 1.87 6.22 0 250.12 188.77 34863 +1911 39 6.22 0.22 4.57 0.16 225.61 144.61 35035 +1911 40 0.69 -5.31 -0.96 0 157.91 199.36 35208 +1911 41 5.91 -0.09 4.26 0.29 221.25 148.72 35383 +1911 42 5.13 -0.87 3.48 0.16 210.58 151.11 35560 +1911 43 3.99 -2.01 2.34 0 195.79 205.08 35738 +1911 44 3.96 -2.04 2.31 0 195.41 207.67 35918 +1911 45 3.34 -2.66 1.69 0 187.77 210.77 36099 +1911 46 0.06 -5.94 -1.59 0.26 151.45 161.74 36282 +1911 47 -0.72 -6.72 -2.37 0.1 143.77 200.69 36466 +1911 48 -1.23 -7.23 -2.88 0 138.93 258.38 36652 +1911 49 -1.21 -7.21 -2.86 0 139.11 261 36838 +1911 50 3.73 -2.27 2.08 0 192.55 224.29 37026 +1911 51 0.48 -5.52 -1.17 0 155.73 229.6 37215 +1911 52 -2.42 -8.42 -4.07 0 128.18 234.17 37405 +1911 53 1.43 -4.57 -0.22 0 165.8 234.82 37596 +1911 54 2.89 -3.11 1.24 0 182.38 236.52 37788 +1911 55 3.33 -2.67 1.68 0 187.64 239.19 37981 +1911 56 1.03 -4.97 -0.62 0 161.49 243.63 38175 +1911 57 3.91 -2.09 2.26 0 194.79 244.32 38370 +1911 58 8.37 2.37 6.72 0 257.98 242.82 38565 +1911 59 10.39 4.39 8.74 0 291.95 243.02 38761 +1911 60 15.8 9.8 14.15 0 402.38 237.41 38958 +1911 61 12.89 6.89 11.24 0 339.23 245.16 39156 +1911 62 14.41 8.41 12.76 0 371.06 245.4 39355 +1911 63 12.2 6.2 10.55 0.02 325.57 188.92 39553 +1911 64 11.84 5.84 10.19 0.14 318.63 191.46 39753 +1911 65 9.99 3.99 8.34 0.12 284.93 195.56 39953 +1911 66 9.85 3.85 8.2 0.22 282.51 197.74 40154 +1911 67 5.34 -0.66 3.69 0.31 213.41 203.87 40355 +1911 68 3.43 -2.57 1.78 0.7 188.86 207.42 40556 +1911 69 3.43 -2.57 1.78 0 188.86 279.21 40758 +1911 70 3.76 -2.24 2.11 0.2 192.92 211.34 40960 +1911 71 5 -1 3.35 0.14 208.85 212.63 41163 +1911 72 7.87 1.87 6.22 0 250.12 283.1 41366 +1911 73 9.69 3.69 8.04 0 279.77 283.35 41569 +1911 74 11.25 5.25 9.6 0 307.53 283.77 41772 +1911 75 7.32 1.32 5.67 0 241.71 291.92 41976 +1911 76 6.84 0.84 5.19 0.01 234.57 221.36 42179 +1911 77 8.03 2.03 6.38 0 252.61 296.27 42383 +1911 78 6.81 0.81 5.16 0 234.13 300.47 42587 +1911 79 6.88 0.88 5.23 0.27 235.16 227.35 42791 +1911 80 5.06 -0.94 3.41 0 209.65 307.79 42996 +1911 81 4.27 -1.73 2.62 0 199.34 311.24 43200 +1911 82 7.51 1.51 5.86 0.02 244.59 232.6 43404 +1911 83 9.67 3.67 8.02 0 279.43 309.62 43608 +1911 84 11.53 5.53 9.88 0 312.76 309.19 43812 +1911 85 8.03 2.03 6.38 0.01 252.61 237.75 44016 +1911 86 8.85 2.85 7.2 0 265.73 318.26 44220 +1911 87 6.89 0.89 5.24 0.1 235.3 242.61 44424 +1911 88 6.86 0.86 5.21 0 234.86 325.89 44627 +1911 89 5.15 -0.85 3.5 0.19 210.85 247.72 44831 +1911 90 3.07 -2.93 1.42 0.41 184.52 251.22 45034 +1911 91 7.99 1.99 6.34 0 251.99 331.32 45237 +1911 92 9.31 3.31 7.66 0 273.34 331.63 45439 +1911 93 9.38 3.38 7.73 0.05 274.51 250.31 45642 +1911 94 15.8 9.8 14.15 0.27 402.38 242.73 45843 +1911 95 15.35 9.35 13.7 0 392 326.76 46045 +1911 96 15.27 9.27 13.62 0.38 390.18 246.76 46246 +1911 97 9.06 3.06 7.41 0.07 269.18 257.07 46446 +1911 98 9.8 3.8 8.15 0.21 281.65 257.66 46647 +1911 99 12.45 6.45 10.8 0 330.46 340.85 46846 +1911 100 10.62 4.62 8.97 0 296.05 346.15 47045 +1911 101 11.56 5.56 9.91 0.33 313.32 259.8 47243 +1911 102 10.97 4.97 9.32 0 302.38 349.38 47441 +1911 103 11.45 5.45 9.8 0 311.26 350.35 47638 +1911 104 10.41 4.41 8.76 0 292.3 354.05 47834 +1911 105 13.03 7.03 11.38 0 342.06 350.89 48030 +1911 106 10.46 4.46 8.81 0 293.19 357.42 48225 +1911 107 10.16 4.16 8.51 0.02 287.9 269.72 48419 +1911 108 14.72 8.72 13.07 0.79 377.86 264.19 48612 +1911 109 12.22 6.22 10.57 0.21 325.96 269.39 48804 +1911 110 13.23 7.23 11.58 0 346.14 358.53 48995 +1911 111 14.6 8.6 12.95 0 375.22 357.05 49185 +1911 112 16.81 10.81 15.16 0.15 426.52 264.84 49374 +1911 113 14.88 8.88 13.23 0.09 381.41 269.43 49561 +1911 114 13.53 7.53 11.88 0 352.34 363.78 49748 +1911 115 14.02 8.02 12.37 0 362.66 364.12 49933 +1911 116 13.4 7.4 11.75 0 349.64 366.71 50117 +1911 117 16.31 10.31 14.66 0 414.42 361.1 50300 +1911 118 15.64 9.64 13.99 0 398.66 364.11 50481 +1911 119 13.6 7.6 11.95 0 353.8 370.09 50661 +1911 120 10.15 4.15 8.5 0.16 287.72 283.64 50840 +1911 121 16.36 10.36 14.71 0.34 415.61 274.29 51016 +1911 122 18.56 12.56 16.91 0 471.27 360.73 51191 +1911 123 19.01 13.01 17.36 0.28 483.41 270.28 51365 +1911 124 20.21 14.21 18.56 0.75 517.07 268.2 51536 +1911 125 19.91 13.91 18.26 0.72 508.47 269.66 51706 +1911 126 18.11 12.11 16.46 2.93 459.4 274.56 51874 +1911 127 19.53 13.53 17.88 0 497.76 362.6 52039 +1911 128 19.1 13.1 17.45 0.23 485.86 273.7 52203 +1911 129 14.64 8.64 12.99 0.23 376.1 283.53 52365 +1911 130 11.67 5.67 10.02 0.76 315.4 289.05 52524 +1911 131 15.68 9.68 14.03 0 399.59 377.05 52681 +1911 132 18.44 12.44 16.79 0 468.08 370.16 52836 +1911 133 15.93 9.93 14.28 0.85 405.42 283.45 52989 +1911 134 16.25 10.25 14.6 0.44 412.98 283.34 53138 +1911 135 17.9 11.9 16.25 0.28 453.94 280.39 53286 +1911 136 16.95 10.95 15.3 0.63 429.96 282.91 53430 +1911 137 18.35 12.35 16.7 0.47 465.7 280.38 53572 +1911 138 13.73 7.73 12.08 0.61 356.52 290.04 53711 +1911 139 11.01 5.01 9.36 0.23 303.11 294.91 53848 +1911 140 11.2 5.2 9.55 0.47 306.61 295 53981 +1911 141 11.98 5.98 10.33 0 321.31 392.2 54111 +1911 142 13.45 7.45 11.8 0.19 350.68 292.13 54238 +1911 143 12.93 6.93 11.28 0 340.04 391.21 54362 +1911 144 12.96 6.96 11.31 0.42 340.64 293.73 54483 +1911 145 15.29 9.29 13.64 0 390.64 386.56 54600 +1911 146 22.04 16.04 20.39 0.02 572.24 274.37 54714 +1911 147 22.52 16.52 20.87 0 587.51 364.45 54824 +1911 148 25.04 19.04 23.39 0 673.47 354.33 54931 +1911 149 20.06 14.06 18.41 0.01 512.76 280.53 55034 +1911 150 19.51 13.51 17.86 1.48 497.2 282.15 55134 +1911 151 16.57 10.57 14.92 0.84 420.67 289.09 55229 +1911 152 18.29 12.29 16.64 0 464.12 380.56 55321 +1911 153 18.73 12.73 17.08 0.1 475.82 284.58 55409 +1911 154 16.18 10.18 14.53 0.86 411.32 290.4 55492 +1911 155 16.75 10.75 15.1 0.41 425.05 289.37 55572 +1911 156 14.67 8.67 13.02 0.47 376.76 293.72 55648 +1911 157 14.42 8.42 12.77 0.03 371.28 294.31 55719 +1911 158 15.3 9.3 13.65 0 390.86 390.39 55786 +1911 159 13.4 7.4 11.75 0 349.64 395.26 55849 +1911 160 15.05 9.05 13.4 0.04 385.21 293.6 55908 +1911 161 20.46 14.46 18.81 0 524.33 375.38 55962 +1911 162 23.03 17.03 21.38 0 604.11 365.83 56011 +1911 163 25.85 19.85 24.2 0.98 703.26 265.34 56056 +1911 164 21.18 15.18 19.53 0.12 545.72 279.86 56097 +1911 165 20.18 14.18 18.53 0.13 516.2 282.57 56133 +1911 166 19.28 13.28 17.63 0 490.81 379.84 56165 +1911 167 18.74 12.74 17.09 0.11 476.09 286.14 56192 +1911 168 20.17 14.17 18.52 0.02 515.92 282.67 56214 +1911 169 18.77 12.77 17.12 0.07 476.9 286.13 56231 +1911 170 19.61 13.61 17.96 0.62 500 284.1 56244 +1911 171 16.69 10.69 15.04 0.09 423.59 290.82 56252 +1911 172 21.42 15.42 19.77 0 553.01 372.53 56256 +1911 173 21.42 15.42 19.77 0 553.01 372.51 56255 +1911 174 23.7 17.7 22.05 0 626.52 363.5 56249 +1911 175 26.1 20.1 24.45 0 712.68 352.78 56238 +1911 176 27.1 21.1 25.45 0.42 751.43 260.89 56223 +1911 177 23.81 17.81 22.16 0.02 630.27 272.16 56203 +1911 178 22.18 16.18 20.53 0 576.65 369.44 56179 +1911 179 23.53 17.53 21.88 0 620.77 363.97 56150 +1911 180 22.35 16.35 20.7 0 582.06 368.56 56116 +1911 181 17.75 11.75 16.1 0.78 450.08 288.11 56078 +1911 182 22.85 16.85 21.2 0 598.2 366.39 56035 +1911 183 24.93 18.93 23.28 0.03 669.5 268.1 55987 +1911 184 25.46 19.46 23.81 0.08 688.78 266.19 55935 +1911 185 26.22 20.22 24.57 1.61 717.24 263.47 55879 +1911 186 27.23 21.23 25.58 0.05 756.6 259.57 55818 +1911 187 26.45 20.45 24.8 0 726.05 349.76 55753 +1911 188 26.72 20.72 25.07 0 736.5 348.19 55684 +1911 189 26.67 20.67 25.02 0 734.56 348.27 55611 +1911 190 27.71 21.71 26.06 0 775.93 342.69 55533 +1911 191 27.65 21.65 26 0 773.49 342.75 55451 +1911 192 23.12 17.12 21.47 0 607.08 363.11 55366 +1911 193 17.27 11.27 15.62 0 437.91 382.84 55276 +1911 194 16.54 10.54 14.89 0 419.95 384.66 55182 +1911 195 19.66 13.66 18.01 0 501.4 374.96 55085 +1911 196 19.19 13.19 17.54 0 488.33 376.08 54984 +1911 197 16.7 10.7 15.05 0.09 423.83 287.29 54879 +1911 198 19.36 13.36 17.71 0.15 493.03 280.99 54770 +1911 199 19.33 13.33 17.68 0 492.19 374.39 54658 +1911 200 17.46 11.46 15.81 0 442.7 379.7 54542 +1911 201 18.9 12.9 17.25 0.02 480.41 281.16 54423 +1911 202 22.98 16.98 21.33 0 602.46 359.9 54301 +1911 203 23.51 17.51 21.86 0 620.09 357.28 54176 +1911 204 25.42 19.42 23.77 0.28 687.31 261.46 54047 +1911 205 24.14 18.14 22.49 0 641.62 353.68 53915 +1911 206 24.48 18.48 22.83 0 653.5 351.7 53780 +1911 207 25.25 19.25 23.6 0 681.09 347.7 53643 +1911 208 31.93 25.93 30.28 0 964.61 311.35 53502 +1911 209 30.3 24.3 28.65 0 887.61 320.67 53359 +1911 210 29.29 23.29 27.64 0 842.55 325.83 53213 +1911 211 31.22 25.22 29.57 0 930.41 313.93 53064 +1911 212 32.06 26.06 30.41 0 970.99 308 52913 +1911 213 33.59 27.59 31.94 1.15 1048.73 222.94 52760 +1911 214 31.36 25.36 29.71 0 937.07 311.02 52604 +1911 215 29.94 23.94 28.29 0.03 871.32 239.08 52445 +1911 216 24.86 18.86 23.21 1.14 666.99 257.22 52285 +1911 217 23.7 17.7 22.05 0.4 626.52 260.2 52122 +1911 218 22.85 16.85 21.2 0.33 598.2 262.1 51958 +1911 219 24.18 18.18 22.53 0 643.01 343.17 51791 +1911 220 19.12 13.12 17.47 0.02 486.41 270.28 51622 +1911 221 17.95 11.95 16.3 0 455.24 362.86 51451 +1911 222 19.63 13.63 17.98 0 500.56 356.72 51279 +1911 223 19.83 13.83 18.18 0.02 506.2 266.21 51105 +1911 224 21.31 15.31 19.66 0.17 549.66 261.72 50929 +1911 225 20.01 14.01 18.36 0 511.32 352.16 50751 +1911 226 24.68 18.68 23.03 0.09 660.57 250.41 50572 +1911 227 24.48 18.48 22.83 0.4 653.5 250.11 50392 +1911 228 24.84 18.84 23.19 0 666.28 330.82 50210 +1911 229 25.9 19.9 24.25 0 705.14 325.08 50026 +1911 230 23.32 17.32 21.67 0.04 613.72 250.85 49842 +1911 231 22.76 16.76 21.11 0 595.27 335.14 49656 +1911 232 25.71 19.71 24.06 0.07 698.04 241.52 49469 +1911 233 27.45 21.45 25.8 0.49 765.41 234.6 49280 +1911 234 24.91 18.91 23.26 0 668.79 322.7 49091 +1911 235 26.13 20.13 24.48 0 713.82 316.09 48900 +1911 236 24.46 18.46 22.81 0 652.79 321.74 48709 +1911 237 21.66 15.66 20.01 0 560.39 330.48 48516 +1911 238 23.74 17.74 22.09 0.73 627.88 241.01 48323 +1911 239 21.7 15.7 20.05 0.05 561.62 245.42 48128 +1911 240 20.15 14.15 18.5 0.06 515.34 247.88 47933 +1911 241 20.13 14.13 18.48 0 514.76 328.86 47737 +1911 242 22.94 16.94 21.29 0 601.15 317.8 47541 +1911 243 24.98 18.98 23.33 0 671.3 308.28 47343 +1911 244 20.39 14.39 18.74 0 522.29 322.69 47145 +1911 245 20.68 14.68 19.03 0.04 530.79 239.98 46947 +1911 246 19.6 13.6 17.95 0 499.72 321.3 46747 +1911 247 14.06 8.06 12.41 0 363.52 333.25 46547 +1911 248 14.69 8.69 13.04 1.41 377.2 247.44 46347 +1911 249 11.72 5.72 10.07 0.1 316.34 250.28 46146 +1911 250 16.17 10.17 14.52 0.15 411.08 241.88 45945 +1911 251 15.87 9.87 14.22 0 404.01 321.07 45743 +1911 252 19.49 13.49 17.84 0 496.64 309.66 45541 +1911 253 23.48 17.48 21.83 0 619.08 295 45339 +1911 254 25.92 19.92 24.27 0 705.89 283.84 45136 +1911 255 21.53 15.53 19.88 0.04 556.38 222.93 44933 +1911 256 21.83 15.83 20.18 0.74 565.66 220.57 44730 +1911 257 18.1 12.1 16.45 0.93 459.14 226.92 44527 +1911 258 18.13 12.13 16.48 0.06 459.92 225.11 44323 +1911 259 21.39 15.39 19.74 0 552.1 288.74 44119 +1911 260 20.42 14.42 18.77 0.25 523.16 216.95 43915 +1911 261 20.22 14.22 18.57 0 517.36 287.44 43711 +1911 262 20.63 14.63 18.98 0 529.31 283.98 43507 +1911 263 22.51 16.51 20.86 0.04 587.18 206.98 43303 +1911 264 22.11 16.11 20.46 0.03 574.44 206.06 43099 +1911 265 23.87 17.87 22.22 0.82 632.32 200.15 42894 +1911 266 19.22 13.22 17.57 0 489.16 278.14 42690 +1911 267 21.26 15.26 19.61 0 548.14 270.02 42486 +1911 268 17.65 11.65 16 0.06 447.52 207.6 42282 +1911 269 16.72 10.72 15.07 0.43 424.32 207.3 42078 +1911 270 16.68 10.68 15.03 0 423.34 273.87 41875 +1911 271 20.66 14.66 19.01 0 530.2 261.72 41671 +1911 272 18.85 12.85 17.2 0 479.06 263.67 41468 +1911 273 16.16 10.16 14.51 0 410.84 267.14 41265 +1911 274 8.31 2.31 6.66 0 257.03 277.16 41062 +1911 275 11.54 5.54 9.89 0.47 312.94 202.4 40860 +1911 276 8.45 2.45 6.8 0.83 259.26 203.54 40658 +1911 277 9.82 3.82 8.17 0 282 266.89 40456 +1911 278 8.75 2.75 7.1 0.06 264.1 199.02 40255 +1911 279 10.4 4.4 8.75 0 292.12 260.33 40054 +1911 280 11.5 5.5 9.85 0.02 312.19 192.07 39854 +1911 281 12.5 6.5 10.85 1.34 331.45 188.89 39654 +1911 282 12.11 6.11 10.46 0.03 323.82 187.27 39455 +1911 283 13.09 7.09 11.44 0 343.28 245.36 39256 +1911 284 13.37 7.37 11.72 0.7 349.02 181.42 39058 +1911 285 13.69 7.69 12.04 0.07 355.68 179.07 38861 +1911 286 16.14 10.14 14.49 0 410.37 231.82 38664 +1911 287 13.95 7.95 12.3 0.14 361.17 174.5 38468 +1911 288 13.94 7.94 12.29 0.03 360.96 172.44 38273 +1911 289 10.86 4.86 9.21 0.29 300.38 173.8 38079 +1911 290 10.74 4.74 9.09 0.35 298.21 171.75 37885 +1911 291 10.7 4.7 9.05 0 297.48 226.34 37693 +1911 292 13.34 7.34 11.69 0 348.4 220.04 37501 +1911 293 15.4 9.4 13.75 0.07 393.14 160.59 37311 +1911 294 13.35 7.35 11.7 0.4 348.61 160.83 37121 +1911 295 14.5 8.5 12.85 0.09 373.03 157.44 36933 +1911 296 15.43 9.43 13.78 0.03 393.83 154.44 36745 +1911 297 10.05 4.05 8.4 0.26 285.98 157.94 36560 +1911 298 9.08 3.08 7.43 0 269.51 209.05 36375 +1911 299 13.06 7.06 11.41 0 342.67 201.44 36191 +1911 300 16.5 10.5 14.85 0 418.98 193.65 36009 +1911 301 21.79 15.79 20.14 1.03 564.42 135.78 35829 +1911 302 21.65 15.65 20 0.27 560.08 134.18 35650 +1911 303 21.64 15.64 19.99 0 559.77 176.52 35472 +1911 304 21.06 15.06 19.41 0.54 542.1 131.59 35296 +1911 305 15.87 9.87 14.22 0.2 404.01 136.58 35122 +1911 306 14.92 8.92 13.27 0.02 382.3 135.99 34950 +1911 307 14.69 8.69 13.04 0 377.2 179.2 34779 +1911 308 9.63 3.63 7.98 0 278.74 182.68 34610 +1911 309 9.13 3.13 7.48 0.71 270.34 135.65 34444 +1911 310 7.6 1.6 5.95 0.01 245.96 134.88 34279 +1911 311 5.23 -0.77 3.58 0 211.92 179.56 34116 +1911 312 8.24 2.24 6.59 0.03 255.92 130.83 33956 +1911 313 10.37 4.37 8.72 0.12 291.59 127.72 33797 +1911 314 7.18 1.18 5.53 0 239.61 171.27 33641 +1911 315 7.15 1.15 5.5 0.5 239.16 126.57 33488 +1911 316 3.53 -2.47 1.88 0.61 190.08 126.89 33337 +1911 317 8.81 2.81 7.16 0.01 265.08 122.23 33188 +1911 318 11.37 5.37 9.72 0 309.76 158.19 33042 +1911 319 12.59 6.59 10.94 0 333.23 155.22 32899 +1911 320 10.97 4.97 9.32 0.13 302.38 116.32 32758 +1911 321 10.37 4.37 8.72 0 291.59 153.59 32620 +1911 322 10.82 4.82 9.17 0 299.65 151.36 32486 +1911 323 10.58 4.58 8.93 0 295.33 150 32354 +1911 324 10.21 4.21 8.56 0 288.77 148.32 32225 +1911 325 13.35 7.35 11.7 0 348.61 143.47 32100 +1911 326 12.78 6.78 11.13 0 337.02 142.67 31977 +1911 327 12.21 6.21 10.56 0 325.76 141.46 31858 +1911 328 11.27 5.27 9.62 0 307.9 140.44 31743 +1911 329 9.67 3.67 8.02 0 279.43 140.42 31631 +1911 330 9.82 3.82 8.17 0 282 138.86 31522 +1911 331 7.09 1.09 5.44 0 238.26 139.7 31417 +1911 332 9.12 3.12 7.47 0 270.17 136.53 31316 +1911 333 8.7 2.7 7.05 0 263.29 135.79 31218 +1911 334 11.04 5.04 9.39 0 303.66 132.74 31125 +1911 335 8.02 2.02 6.37 0 252.46 134.06 31035 +1911 336 4.95 -1.05 3.3 0 208.18 135.06 30949 +1911 337 8.13 2.13 6.48 0 254.18 131.27 30867 +1911 338 9.56 3.56 7.91 0 277.55 129.23 30790 +1911 339 8.25 2.25 6.6 0 256.08 129.47 30716 +1911 340 6.89 0.89 5.24 0.02 235.3 97.28 30647 +1911 341 3.96 -2.04 2.31 0.18 195.41 97.94 30582 +1911 342 2.7 -3.3 1.05 1.29 180.14 97.87 30521 +1911 343 -0.09 -6.09 -1.74 1.34 149.94 145.76 30465 +1911 344 -1.58 -7.58 -3.23 0.5 135.69 147.02 30413 +1911 345 0.8 -5.2 -0.85 0.98 159.06 145.93 30366 +1911 346 0.12 -5.88 -1.53 0.33 152.05 145.78 30323 +1911 347 -1.25 -7.25 -2.9 0 138.74 177.98 30284 +1911 348 0.02 -5.98 -1.63 0 151.05 177.17 30251 +1911 349 2.01 -3.99 0.36 0 172.22 175.68 30221 +1911 350 -1.9 -7.9 -3.55 0 132.78 177.02 30197 +1911 351 4.28 -1.72 2.63 0 199.47 173.46 30177 +1911 352 7.37 1.37 5.72 0 242.46 170.52 30162 +1911 353 7.69 1.69 6.04 0 247.34 169.22 30151 +1911 354 5.69 -0.31 4.04 0 218.19 169.73 30145 +1911 355 8.1 2.1 6.45 0 253.71 167.07 30144 +1911 356 11.42 5.42 9.77 0 310.69 119.67 30147 +1911 357 8.62 2.62 6.97 0.02 261.99 91.47 30156 +1911 358 11.28 5.28 9.63 0 308.09 119.93 30169 +1911 359 10.12 4.12 8.47 0 287.2 121.01 30186 +1911 360 13.04 7.04 11.39 0 342.26 118.8 30208 +1911 361 13.06 7.06 11.41 0 342.67 119.1 30235 +1911 362 8.89 2.89 7.24 0.01 266.38 92.31 30267 +1911 363 7.4 1.4 5.75 0 242.92 124.72 30303 +1911 364 7.58 1.58 5.93 0 245.65 124.98 30343 +1911 365 2.3 -3.7 0.65 0.51 175.51 96.49 30388 +1912 1 -4.56 -10.56 -6.21 1.36 110.66 146.84 30438 +1912 2 -2.86 -8.86 -4.51 0 124.39 180 30492 +1912 3 -1.57 -7.57 -3.22 0 135.78 180.4 30551 +1912 4 -2.1 -8.1 -3.75 0 131 181.42 30614 +1912 5 -6.72 -12.72 -8.37 0.25 95.12 150.19 30681 +1912 6 -6.69 -12.69 -8.34 0 95.32 185.02 30752 +1912 7 -9.97 -15.97 -11.62 0 75.31 186.5 30828 +1912 8 -7.3 -13.3 -8.95 0 91.28 187.26 30907 +1912 9 -6.43 -12.43 -8.08 0.39 97.09 154.24 30991 +1912 10 -4.44 -10.44 -6.09 0 111.58 189.97 31079 +1912 11 -3.35 -9.35 -5 0 120.29 190.47 31171 +1912 12 -1.49 -7.49 -3.14 0 136.51 190.64 31266 +1912 13 3.17 -2.83 1.52 0.66 185.71 154.07 31366 +1912 14 6.67 0.67 5.02 0 232.08 187.77 31469 +1912 15 3.64 -2.36 1.99 0 191.43 190.52 31575 +1912 16 5.32 -0.68 3.67 0.01 213.14 153.78 31686 +1912 17 3.18 -2.82 1.53 0.38 185.83 155.46 31800 +1912 18 3.97 -2.03 2.32 0 195.54 193.12 31917 +1912 19 6.95 0.95 5.3 0 236.19 192 32038 +1912 20 5.37 -0.63 3.72 0.06 213.82 155.95 32161 +1912 21 7.45 1.45 5.8 0.07 243.67 155.21 32289 +1912 22 7.24 1.24 5.59 0 240.5 154.02 32419 +1912 23 4.93 -1.07 3.28 0.05 207.92 118.08 32552 +1912 24 4.53 -1.47 2.88 0.12 202.68 119.83 32688 +1912 25 3.33 -2.67 1.68 0.09 187.64 121.82 32827 +1912 26 2.57 -3.43 0.92 0 178.63 164.81 32969 +1912 27 -0.38 -6.38 -2.03 0 147.07 168.43 33114 +1912 28 1.11 -4.89 -0.54 0 162.35 169.89 33261 +1912 29 -0.38 -6.38 -2.03 0 147.07 173.06 33411 +1912 30 -2.17 -8.17 -3.82 0 130.38 176.17 33564 +1912 31 2.19 -3.81 0.54 0 174.26 176.31 33718 +1912 32 5.91 -0.09 4.26 0 221.25 175.88 33875 +1912 33 7.16 1.16 5.51 0.21 239.31 133.11 34035 +1912 34 8.93 2.93 7.28 0.42 267.04 133.55 34196 +1912 35 8.41 2.41 6.76 0 258.62 180.67 34360 +1912 36 5.89 -0.11 4.24 0 220.97 185.35 34526 +1912 37 6.44 0.44 4.79 0 228.76 187.31 34694 +1912 38 8.44 2.44 6.79 1.38 259.1 141.18 34863 +1912 39 4 -2 2.35 1.01 195.92 145.92 35035 +1912 40 3.79 -2.21 2.14 0.09 193.29 148 35208 +1912 41 5.1 -0.9 3.45 0.69 210.18 149.22 35383 +1912 42 5.97 -0.03 4.32 0.35 222.09 150.59 35560 +1912 43 3.89 -2.11 2.24 0.27 194.54 153.86 35738 +1912 44 1.22 -4.78 -0.43 0.07 163.53 157.18 35918 +1912 45 1.46 -4.54 -0.19 0 166.13 212.07 36099 +1912 46 2.4 -3.6 0.75 0 176.66 214.15 36282 +1912 47 7.66 1.66 6.01 0 246.88 212.56 36466 +1912 48 10.68 4.68 9.03 0.06 297.12 159.01 36652 +1912 49 12.15 6.15 10.5 0 324.6 212.86 36838 +1912 50 13.02 7.02 11.37 0.69 341.86 160.69 37026 +1912 51 13.51 7.51 11.86 0 351.92 216.43 37215 +1912 52 14.01 8.01 12.36 0 362.45 218.42 37405 +1912 53 13.58 7.58 11.93 0 353.38 221.95 37596 +1912 54 10.48 4.48 8.83 0 293.55 228.92 37788 +1912 55 6.28 0.28 4.63 0 226.47 236.57 37981 +1912 56 1.92 -4.08 0.27 0 171.21 242.99 38175 +1912 57 0.23 -5.77 -1.42 0 153.17 247.1 38370 +1912 58 -0.79 -6.79 -2.44 0.09 143.09 222.5 38565 +1912 59 2.28 -3.72 0.63 0 175.29 251.33 38761 +1912 60 5.86 -0.14 4.21 1.32 220.55 188.31 38958 +1912 61 5.58 -0.42 3.93 0.09 216.68 190.72 39156 +1912 62 4.68 -1.32 3.03 0.57 204.63 193.47 39355 +1912 63 8.66 2.66 7.01 0.02 262.64 192.53 39553 +1912 64 12.23 6.23 10.58 0 326.15 254.7 39753 +1912 65 15.2 9.2 13.55 0 388.59 252.52 39953 +1912 66 13.64 7.64 11.99 0.63 354.63 193.44 40154 +1912 67 12.11 6.11 10.46 0.62 323.82 197.43 40355 +1912 68 11.41 5.41 9.76 0.75 310.51 200.35 40556 +1912 69 11.89 5.89 10.24 0.1 319.59 201.74 40758 +1912 70 7.37 1.37 5.72 0.87 242.46 208.48 40960 +1912 71 2.15 -3.85 0.5 0.18 173.81 214.62 41163 +1912 72 2.9 -3.1 1.25 0.21 182.5 216.28 41366 +1912 73 8.54 2.54 6.89 0.4 260.7 213.68 41569 +1912 74 9.89 3.89 8.24 0 283.2 285.8 41772 +1912 75 7.15 1.15 5.5 0 239.16 292.13 41976 +1912 76 6.9 0.9 5.25 0 235.45 295.08 42179 +1912 77 11.34 5.34 9.69 0 309.2 291.5 42383 +1912 78 9.58 3.58 7.93 0 277.89 296.81 42587 +1912 79 15.82 9.82 14.17 0 402.84 288.51 42791 +1912 80 15.47 9.47 13.82 0 394.74 291.71 42996 +1912 81 16.52 10.52 14.87 0.09 419.46 218.95 43200 +1912 82 20.71 14.71 19.06 0 531.67 283.84 43404 +1912 83 20.76 14.76 19.11 0 533.15 286.03 43608 +1912 84 20.95 14.95 19.3 0.37 538.81 215.9 43812 +1912 85 15.83 9.83 14.18 0.4 403.08 227.49 44016 +1912 86 10.07 4.07 8.42 0.32 286.32 237.32 44220 +1912 87 8.73 2.73 7.08 0.1 263.77 240.73 44424 +1912 88 9.37 3.37 7.72 0.25 274.35 241.79 44627 +1912 89 7.34 1.34 5.69 0.14 242.01 245.67 44831 +1912 90 3.5 -2.5 1.85 0.04 189.71 250.89 45034 +1912 91 9.03 3.03 7.38 0.35 268.69 247.36 45237 +1912 92 12.24 6.24 10.59 0 326.35 326.69 45439 +1912 93 16.75 10.75 15.1 0 425.05 319.29 45642 +1912 94 15.24 9.24 13.59 0 389.5 324.91 45843 +1912 95 12.9 6.9 11.25 0 339.43 331.9 46045 +1912 96 10.14 4.14 8.49 0.28 287.55 254.22 46246 +1912 97 10.89 4.89 9.24 1 300.92 254.81 46446 +1912 98 12.04 6.04 10.39 0 322.47 339.63 46647 +1912 99 9.45 3.45 7.8 0 275.69 346.14 46846 +1912 100 9.87 3.87 8.22 0 282.86 347.42 47045 +1912 101 11.86 5.86 10.21 0.21 319.01 259.38 47243 +1912 102 14.52 8.52 12.87 0 373.46 342.3 47441 +1912 103 10.45 4.45 8.8 0 293.01 352.14 47638 +1912 104 9.03 3.03 7.38 0 268.69 356.35 47834 +1912 105 6.39 0.39 4.74 0 228.04 362.05 48030 +1912 106 4.17 -1.83 2.52 0.09 198.07 274.91 48225 +1912 107 2.1 -3.9 0.45 0 173.24 370.56 48419 +1912 108 2.73 -3.27 1.08 0 180.49 371.69 48612 +1912 109 4.94 -1.06 3.29 0 208.05 370.77 48804 +1912 110 9.55 3.55 7.9 0 277.38 365.49 48995 +1912 111 13.49 7.49 11.84 0 351.51 359.52 49185 +1912 112 9.74 3.74 8.09 0 280.62 368.27 49374 +1912 113 10.78 4.78 9.13 0 298.93 367.79 49561 +1912 114 9.63 3.63 7.98 0.03 278.74 278.5 49748 +1912 115 13.11 7.11 11.46 0.11 343.69 274.59 49933 +1912 116 12.34 6.34 10.69 0.09 328.3 276.71 50117 +1912 117 14.72 8.72 13.07 0 377.86 365.03 50300 +1912 118 15.73 9.73 14.08 0 400.75 363.88 50481 +1912 119 15.13 9.13 13.48 1.19 387.01 274.91 50661 +1912 120 13.97 7.97 12.32 0.21 361.6 277.83 50840 +1912 121 18.37 12.37 16.72 0.07 466.23 270.1 51016 +1912 122 21.14 15.14 19.49 0 544.51 352.43 51191 +1912 123 23.34 17.34 21.69 0.48 614.39 258.97 51365 +1912 124 16.55 10.55 14.9 0.88 420.19 276.37 51536 +1912 125 16.5 10.5 14.85 0.26 418.98 277.2 51706 +1912 126 17.43 11.43 15.78 0 441.94 368.03 51874 +1912 127 17.12 11.12 15.47 0.33 434.17 277.34 52039 +1912 128 14.67 8.67 13.02 0 376.76 377.12 52203 +1912 129 18.46 12.46 16.81 0 468.61 367.73 52365 +1912 130 17.56 11.56 15.91 0.16 445.23 278.36 52524 +1912 131 16.57 10.57 14.92 0.17 420.67 281.03 52681 +1912 132 20.83 14.83 19.18 1.13 535.23 271.81 52836 +1912 133 19.3 13.3 17.65 0 491.36 368.19 52989 +1912 134 22.7 16.7 21.05 0 593.32 356.93 53138 +1912 135 21.17 15.17 19.52 0 545.42 363.27 53286 +1912 136 22.42 16.42 20.77 0.01 584.3 269.46 53430 +1912 137 20.49 14.49 18.84 0.46 525.2 275.21 53572 +1912 138 18.06 12.06 16.41 0 458.09 375.31 53711 +1912 139 15.18 9.18 13.53 0 388.14 383.91 53848 +1912 140 11.78 5.78 10.13 0.8 317.49 294.12 53981 +1912 141 11.72 5.72 10.07 0.44 316.34 294.55 54111 +1912 142 10.96 4.96 9.31 0.03 302.2 296.08 54238 +1912 143 13.8 7.8 12.15 0.01 357.99 291.93 54362 +1912 144 17.57 11.57 15.92 0.93 445.49 284.9 54483 +1912 145 18.06 12.06 16.41 0.03 458.09 284.16 54600 +1912 146 16.45 10.45 14.8 0 417.77 383.87 54714 +1912 147 13.89 7.89 12.24 0 359.9 390.86 54824 +1912 148 13.94 7.94 12.29 0 360.96 391.13 54931 +1912 149 15.26 9.26 13.61 0.01 389.95 291.15 55034 +1912 150 16.36 10.36 14.71 0.06 415.61 289.23 55134 +1912 151 17.13 11.13 15.48 0.96 434.42 287.91 55229 +1912 152 20.92 14.92 19.27 0 537.91 371.88 55321 +1912 153 26.36 20.36 24.71 0.19 722.59 262.15 55409 +1912 154 28.79 22.79 27.14 0.3 820.96 253.02 55492 +1912 155 25 19 23.35 1.39 672.02 267.23 55572 +1912 156 22.93 16.93 21.28 0.31 600.82 274.02 55648 +1912 157 23.6 17.6 21.95 0 623.13 362.81 55719 +1912 158 22.97 16.97 21.32 0.43 602.13 274.15 55786 +1912 159 25.2 19.2 23.55 0.1 679.27 267.21 55849 +1912 160 24.87 18.87 23.22 0.01 667.35 268.46 55908 +1912 161 22.61 16.61 20.96 0.07 590.41 275.58 55962 +1912 162 24.01 18.01 22.36 0 637.13 361.79 56011 +1912 163 21.74 15.74 20.09 0 562.86 371.04 56056 +1912 164 21.91 15.91 20.26 0.05 568.16 277.84 56097 +1912 165 21.24 15.24 19.59 0.13 547.53 279.77 56133 +1912 166 18.78 12.78 17.13 0 477.17 381.44 56165 +1912 167 17.08 11.08 15.43 0.24 433.18 289.88 56192 +1912 168 18.21 12.21 16.56 0 462.01 383.24 56214 +1912 169 20.49 14.49 18.84 0 525.2 375.8 56231 +1912 170 22.48 16.48 20.83 0.04 586.22 276.35 56244 +1912 171 19.66 13.66 18.01 2.01 501.4 284.02 56252 +1912 172 18.24 12.24 16.59 1.13 462.8 287.41 56256 +1912 173 17.37 11.37 15.72 0.81 440.43 289.34 56255 +1912 174 16.12 10.12 14.47 1.1 409.89 291.91 56249 +1912 175 13.82 7.82 12.17 0.21 358.42 296.25 56238 +1912 176 15.2 9.2 13.55 0.24 388.59 293.68 56223 +1912 177 16.89 10.89 15.24 0.16 428.48 290.18 56203 +1912 178 16.81 10.81 15.16 0 426.52 387.16 56179 +1912 179 21.7 15.7 20.05 0 561.62 371.15 56150 +1912 180 19.25 13.25 17.6 0.04 489.98 284.67 56116 +1912 181 21.13 15.13 19.48 0 544.21 373.05 56078 +1912 182 22.08 16.08 20.43 0 573.49 369.39 56035 +1912 183 22.3 16.3 20.65 0 580.46 368.37 55987 +1912 184 23.66 17.66 22.01 0 625.16 362.78 55935 +1912 185 27.36 21.36 25.71 0 761.79 345.68 55879 +1912 186 25.46 19.46 23.81 0 688.78 354.59 55818 +1912 187 23.24 17.24 21.59 0.12 611.06 272.99 55753 +1912 188 21.28 15.28 19.63 0 548.75 371.24 55684 +1912 189 19.89 13.89 18.24 0.01 507.9 281.94 55611 +1912 190 19.97 13.97 18.32 0 510.18 375.27 55533 +1912 191 18.97 12.97 17.32 0 482.32 378.28 55451 +1912 192 24.24 18.24 22.59 0.01 645.09 268.85 55366 +1912 193 24.02 18.02 22.37 0 637.47 359.14 55276 +1912 194 20.89 14.89 19.24 0.06 537.02 278.28 55182 +1912 195 19.93 13.93 18.28 0 509.04 374.07 55085 +1912 196 20.95 14.95 19.3 0.31 538.81 277.61 54984 +1912 197 22.48 16.48 20.83 0 586.22 364.03 54879 +1912 198 22.58 16.58 20.93 0 589.44 363.22 54770 +1912 199 24.71 18.71 23.06 0 661.64 354.11 54658 +1912 200 24.09 18.09 22.44 0.11 639.89 267.29 54542 +1912 201 25.73 19.73 24.08 0.58 698.78 261.53 54423 +1912 202 21.27 15.27 19.62 0 548.44 366.35 54301 +1912 203 22.14 16.14 20.49 0 575.39 362.65 54176 +1912 204 21.29 15.29 19.64 0 549.05 365.27 54047 +1912 205 23.16 17.16 21.51 0 608.4 357.69 53915 +1912 206 22.57 16.57 20.92 0.6 589.12 269.58 53780 +1912 207 21.27 15.27 19.62 1.98 548.44 272.71 53643 +1912 208 21.71 15.71 20.06 0 561.93 361.37 53502 +1912 209 22.27 16.27 20.62 0.15 579.51 268.99 53359 +1912 210 23.94 17.94 22.29 0.05 634.72 263.59 53213 +1912 211 21.97 15.97 20.32 0 570.04 358.39 53064 +1912 212 22.11 16.11 20.46 0.27 574.44 267.82 52913 +1912 213 11.91 5.91 10.26 0 319.97 384.98 52760 +1912 214 12.69 6.69 11.04 0.29 335.22 286.92 52604 +1912 215 16.31 10.31 14.66 0 414.42 373.21 52445 +1912 216 16.89 10.89 15.24 0.43 428.48 277.96 52285 +1912 217 22.35 16.35 20.7 0.2 582.06 264.12 52122 +1912 218 18.74 12.74 17.09 0 476.09 363.54 51958 +1912 219 18.21 12.21 16.56 0.06 462.01 273.05 51791 +1912 220 18.3 12.3 16.65 0.11 464.38 272.14 51622 +1912 221 19.6 13.6 17.95 0.5 499.72 268.4 51451 +1912 222 19.13 13.13 17.48 0.85 486.69 268.71 51279 +1912 223 14.64 8.64 12.99 1.37 376.1 276.96 51105 +1912 224 17.56 11.56 15.91 0.05 445.23 270.51 50929 +1912 225 16.42 10.42 14.77 0.29 417.05 271.95 50751 +1912 226 14.36 8.36 12.71 0 369.98 366.48 50572 +1912 227 14.52 8.52 12.87 0 373.46 364.8 50392 +1912 228 19.65 13.65 18 0 501.12 349.67 50210 +1912 229 19.85 13.85 18.2 0 506.77 347.8 50026 +1912 230 22.43 16.43 20.78 0 584.62 337.79 49842 +1912 231 21.68 15.68 20.03 0 561.01 339.02 49656 +1912 232 22.14 16.14 20.49 0 575.39 336.07 49469 +1912 233 20.4 14.4 18.75 0.02 522.58 255.42 49280 +1912 234 20.62 14.62 18.97 0.2 529.02 253.83 49091 +1912 235 23.47 17.47 21.82 1.87 618.75 245.22 48900 +1912 236 19.99 13.99 18.34 0 510.75 337.54 48709 +1912 237 24.65 18.65 23 0.54 659.51 239.55 48516 +1912 238 25.48 19.48 23.83 0 689.52 314.39 48323 +1912 239 26.05 20.05 24.4 0.28 710.79 232.91 48128 +1912 240 26.8 20.8 25.15 0.65 739.62 229.2 47933 +1912 241 28.05 22.05 26.4 0 789.88 298.23 47737 +1912 242 28.59 22.59 26.94 0 812.46 294.04 47541 +1912 243 28.42 22.42 26.77 1.8 805.29 219.86 47343 +1912 244 19.18 13.18 17.53 1.45 488.06 244.72 47145 +1912 245 15.29 9.29 13.64 0.59 390.64 250.84 46947 +1912 246 10.82 4.82 9.17 0.43 299.65 256.03 46747 +1912 247 13.08 7.08 11.43 0.37 343.08 251.44 46547 +1912 248 15.07 9.07 13.42 0 385.66 329.09 46347 +1912 249 17.57 11.57 15.92 0.26 445.49 240.77 46146 +1912 250 19.82 13.82 18.17 0.63 505.92 234.7 45945 +1912 251 21.24 15.24 19.59 0.07 547.53 229.93 45743 +1912 252 14.12 8.12 12.47 0.66 364.8 242.01 45541 +1912 253 13.01 7.01 11.36 0.23 341.66 242.05 45339 +1912 254 9.99 3.99 8.34 0 284.93 325.81 45136 +1912 255 10.02 4.02 8.37 0.61 285.45 242.57 44933 +1912 256 8.84 2.84 7.19 0.11 265.57 242.15 44730 +1912 257 14.75 8.75 13.1 1.32 378.52 232.7 44527 +1912 258 15.45 9.45 13.8 0.01 394.29 229.81 44323 +1912 259 17.37 11.37 15.72 0 440.43 299.61 44119 +1912 260 19.68 13.68 18.03 0 501.96 291.33 43915 +1912 261 19.94 13.94 18.29 0.08 509.33 216.17 43711 +1912 262 17.21 11.21 15.56 0.12 436.41 219.61 43507 +1912 263 17.87 11.87 16.22 0.33 453.17 216.6 43303 +1912 264 17.31 11.31 15.66 0.12 438.92 215.69 43099 +1912 265 11.62 5.62 9.97 0.13 314.45 222.28 42894 +1912 266 6.04 0.04 4.39 1.39 223.07 226.15 42690 +1912 267 4.07 -1.93 2.42 0 196.8 300.87 42486 +1912 268 8.84 2.84 7.19 0.03 265.57 219.46 42282 +1912 269 7.03 1.03 5.38 1.17 237.37 219.25 42078 +1912 270 8.13 2.13 6.48 0.02 254.18 216.18 41875 +1912 271 11.83 5.83 10.18 0 318.44 280.27 41671 +1912 272 10.73 4.73 9.08 0 298.03 279.18 41468 +1912 273 13.7 7.7 12.05 0 355.89 271.81 41265 +1912 274 11.87 5.87 10.22 0 319.2 272.16 41062 +1912 275 11.12 5.12 9.47 0 305.13 270.5 40860 +1912 276 8.12 2.12 6.47 0.01 254.02 203.84 40658 +1912 277 9.65 3.65 8 0.25 279.08 200.34 40456 +1912 278 7.02 1.02 5.37 0 237.22 267.41 40255 +1912 279 5.43 -0.57 3.78 0 214.63 266.21 40054 +1912 280 6.02 0.02 4.37 0 222.79 262.87 39854 +1912 281 6.75 0.75 5.1 0 233.25 259.31 39654 +1912 282 8.45 2.45 6.8 0.33 259.26 190.93 39455 +1912 283 7.11 1.11 5.46 0.28 238.56 189.91 39256 +1912 284 10.25 4.25 8.6 1.56 289.48 184.8 39058 +1912 285 13.78 7.78 12.13 0.48 357.57 178.96 38861 +1912 286 14.14 8.14 12.49 0 365.23 235.28 38664 +1912 287 18.84 12.84 17.19 0 478.79 223.6 38468 +1912 288 15.32 9.32 13.67 0 391.32 227.65 38273 +1912 289 13.82 7.82 12.17 0 358.42 227.5 38079 +1912 290 10.42 4.42 8.77 0.14 292.48 172.06 37885 +1912 291 13.88 7.88 12.23 0.12 359.69 166.42 37693 +1912 292 9.26 3.26 7.61 0.12 272.5 169.03 37501 +1912 293 10.47 4.47 8.82 0.08 293.37 165.88 37311 +1912 294 10.34 4.34 8.69 0.78 291.06 163.83 37121 +1912 295 10.13 4.13 8.48 0.58 287.37 161.88 36933 +1912 296 14.47 8.47 12.82 1.71 372.37 155.56 36745 +1912 297 15.94 9.94 14.29 1.82 405.65 151.81 36560 +1912 298 15.78 9.78 14.13 0.58 401.91 150.1 36375 +1912 299 14.32 8.32 12.67 0 369.11 199.65 36191 +1912 300 12.77 6.77 11.12 0 336.82 199.19 36009 +1912 301 12.26 6.26 10.61 0 326.74 197.36 35829 +1912 302 11.68 5.68 10.03 0 315.59 195.48 35650 +1912 303 10.55 4.55 8.9 0 294.79 194.24 35472 +1912 304 9.95 3.95 8.3 0.21 284.24 144.33 35296 +1912 305 2.52 -3.48 0.87 0 178.05 196.01 35122 +1912 306 3.65 -2.35 2 0 191.56 192.94 34950 +1912 307 2.3 -3.7 0.65 0.01 175.51 143.46 34779 +1912 308 0.72 -5.28 -0.93 0 158.22 189.58 34610 +1912 309 0.5 -5.5 -1.15 0.45 155.94 140.5 34444 +1912 310 1.46 -4.54 -0.19 0 166.13 184.29 34279 +1912 311 -0.31 -6.31 -1.96 0.25 147.76 176.67 34116 +1912 312 -0.86 -6.86 -2.51 0 142.42 220.2 33956 +1912 313 3.11 -2.89 1.46 0 184.99 215.61 33797 +1912 314 -0.36 -6.36 -2.01 0 147.27 215.77 33641 +1912 315 2.83 -3.17 1.18 0 181.67 211.25 33488 +1912 316 2.04 -3.96 0.39 0 172.56 170.09 33337 +1912 317 6.72 0.72 5.07 0 232.81 164.71 33188 +1912 318 4.88 -1.12 3.23 0.03 207.26 122.79 33042 +1912 319 3.13 -2.87 1.48 0.04 185.23 122.34 32899 +1912 320 2.49 -3.51 0.84 0 177.7 161.61 32758 +1912 321 6.8 0.8 5.15 0 233.98 156.63 32620 +1912 322 8.06 2.06 6.41 0 253.08 153.82 32486 +1912 323 4.79 -1.21 3.14 0.19 206.07 115.95 32354 +1912 324 6.58 0.58 4.93 0.19 230.78 113.48 32225 +1912 325 6.67 0.67 5.02 0 232.08 149.51 32100 +1912 326 5.99 -0.01 4.34 0 222.37 148.54 31977 +1912 327 6.48 0.48 4.83 0 229.33 146.35 31858 +1912 328 10.23 4.23 8.58 0.18 289.12 106.05 31743 +1912 329 10.53 4.53 8.88 1.21 294.44 104.75 31631 +1912 330 9.37 3.37 7.72 0.17 274.35 104.43 31522 +1912 331 13.14 7.14 11.49 0.78 344.3 100.82 31417 +1912 332 11.41 5.41 9.76 0.86 310.51 100.9 31316 +1912 333 5.76 -0.24 4.11 0.03 219.16 103.42 31218 +1912 334 3.9 -2.1 2.25 0.36 194.66 103.45 31125 +1912 335 4.46 -1.54 2.81 0.52 201.78 102.32 31035 +1912 336 6.03 0.03 4.38 0 222.93 134.38 30949 +1912 337 6.9 0.9 5.25 0 235.45 132.14 30867 +1912 338 8.06 2.06 6.41 0 253.08 130.39 30790 +1912 339 6.43 0.43 4.78 0.21 228.61 98.05 30716 +1912 340 4.66 -1.34 3.01 0.59 204.37 98.33 30647 +1912 341 7.09 1.09 5.44 0 238.26 128.66 30582 +1912 342 8.22 2.22 6.57 0 255.6 127.11 30521 +1912 343 4.24 -1.76 2.59 0 198.96 128.84 30465 +1912 344 6.45 0.45 4.8 0 228.9 126.38 30413 +1912 345 7.54 1.54 5.89 0.02 245.04 93.92 30366 +1912 346 6.23 0.23 4.58 0 225.75 125.55 30323 +1912 347 8.73 2.73 7.08 0 263.77 123.24 30284 +1912 348 5.17 -0.83 3.52 0.1 211.12 93.94 30251 +1912 349 3.29 -2.71 1.64 0 187.16 125.91 30221 +1912 350 3.8 -2.2 2.15 0 193.42 125.31 30197 +1912 351 8.09 2.09 6.44 0 253.55 122.44 30177 +1912 352 5.19 -0.81 3.54 0 211.39 124.22 30162 +1912 353 3.78 -2.22 2.13 0.01 193.17 93.71 30151 +1912 354 1.5 -4.5 -0.15 0.08 166.57 94.53 30145 +1912 355 -0.88 -6.88 -2.53 0.09 142.23 139.36 30144 +1912 356 1.03 -4.97 -0.62 0 161.49 170.21 30147 +1912 357 0.8 -5.2 -0.85 0 159.06 170.25 30156 +1912 358 0.5 -5.5 -1.15 0 155.94 126.65 30169 +1912 359 5.52 -0.48 3.87 0.01 215.86 93.16 30186 +1912 360 6.55 0.55 4.9 0.29 230.34 92.95 30208 +1912 361 2.91 -3.09 1.26 0.04 182.61 94.76 30235 +1912 362 2.81 -3.19 1.16 0 181.43 126.84 30267 +1912 363 2.87 -3.13 1.22 0 182.14 127.4 30303 +1912 364 1.81 -4.19 0.16 0 169.99 128.31 30343 +1912 365 0.2 -5.8 -1.45 0 152.86 129.61 30388 +1913 1 -2.5 -8.5 -4.15 0 127.48 131.56 30438 +1913 2 -1.6 -7.6 -3.25 0 135.5 131.97 30492 +1913 3 -0.37 -6.37 -2.02 0 147.17 132.44 30551 +1913 4 3.95 -2.05 2.3 0 195.29 131.27 30614 +1913 5 7.83 1.83 6.18 0 249.5 129.45 30681 +1913 6 5.45 -0.55 3.8 0 214.9 131.92 30752 +1913 7 4.02 -1.98 2.37 0 196.17 133.56 30828 +1913 8 3.83 -2.17 2.18 0.79 193.79 101.36 30907 +1913 9 2.74 -3.26 1.09 0 180.61 137 30991 +1913 10 1.55 -4.45 -0.1 0 167.11 138.91 31079 +1913 11 0.52 -5.48 -1.13 0 156.14 140.4 31171 +1913 12 -0.26 -6.26 -1.91 0 148.25 141.77 31266 +1913 13 -2.09 -8.09 -3.74 0 131.09 144.16 31366 +1913 14 -1.74 -7.74 -3.39 0.66 134.23 153.1 31469 +1913 15 -1.71 -7.71 -3.36 0 134.5 190.78 31575 +1913 16 -1.27 -7.27 -2.92 0 138.55 191.75 31686 +1913 17 -1.13 -7.13 -2.78 0 139.86 193.23 31800 +1913 18 1.67 -4.33 0.02 0 168.43 193.45 31917 +1913 19 2.28 -3.72 0.63 0 175.29 194.62 32038 +1913 20 2.08 -3.92 0.43 0 173.01 195.89 32161 +1913 21 2.95 -3.05 1.3 0 183.09 196.88 32289 +1913 22 -0.16 -6.16 -1.81 0.59 149.25 162.22 32419 +1913 23 1.31 -4.69 -0.34 0.46 164.5 162.67 32552 +1913 24 -0.56 -6.56 -2.21 0.77 145.31 167.01 32688 +1913 25 -2.01 -8.01 -3.66 0 131.8 210.04 32827 +1913 26 -4.32 -10.32 -5.97 0.16 112.51 171.17 32969 +1913 27 -0.83 -6.83 -2.48 0 142.71 213.58 33114 +1913 28 1.42 -4.58 -0.23 0 165.69 214.28 33261 +1913 29 1.19 -4.81 -0.46 0 163.21 216.46 33411 +1913 30 2.18 -3.82 0.53 0 174.15 217.68 33564 +1913 31 -1.63 -7.63 -3.28 0 135.23 221.88 33718 +1913 32 2.59 -3.41 0.94 0 178.86 221.23 33875 +1913 33 4.1 -1.9 2.45 0 197.18 222.18 34035 +1913 34 3.36 -2.64 1.71 0 188.01 224.3 34196 +1913 35 2.85 -3.15 1.2 0 181.9 226.26 34360 +1913 36 3.75 -2.25 2.1 0 192.79 227.54 34526 +1913 37 3.76 -2.24 2.11 0.35 192.92 181.98 34694 +1913 38 1.67 -4.33 0.02 0 168.43 233.07 34863 +1913 39 -2 -8 -3.65 0.15 131.89 188.4 35035 +1913 40 -1.91 -7.91 -3.56 0 132.69 240.35 35208 +1913 41 -0.02 -6.02 -1.67 0 150.64 241.81 35383 +1913 42 -1.75 -7.75 -3.4 0.16 134.14 194.08 35560 +1913 43 -0.43 -6.43 -2.08 0 146.58 247.4 35738 +1913 44 3.91 -2.09 2.26 0 194.79 246.51 35918 +1913 45 5.58 -0.42 3.93 0 216.68 246.97 36099 +1913 46 4.18 -1.82 2.53 0 198.19 250.15 36282 +1913 47 6.92 0.92 5.27 0 235.74 249.64 36466 +1913 48 8.33 2.33 6.68 0 257.34 214.66 36652 +1913 49 2.27 -3.73 0.62 0 175.17 222.7 36838 +1913 50 4.18 -1.82 2.53 0 198.19 223.93 37026 +1913 51 4.54 -1.46 2.89 0 202.81 226.6 37215 +1913 52 1.41 -4.59 -0.24 0 165.58 231.84 37405 +1913 53 1.44 -4.56 -0.21 0 165.91 234.81 37596 +1913 54 1.31 -4.69 -0.34 0 164.5 237.68 37788 +1913 55 -0.82 -6.82 -2.47 0 142.8 242.11 37981 +1913 56 4.85 -1.15 3.2 0 206.86 240.6 38175 +1913 57 6.44 0.44 4.79 0 228.76 241.98 38370 +1913 58 7.81 1.81 6.16 0 249.19 243.45 38565 +1913 59 2.52 -3.48 0.87 0.01 178.05 188.36 38761 +1913 60 8.37 2.37 6.72 0 257.98 248.38 38958 +1913 61 11.13 5.13 9.48 0 305.31 247.75 39156 +1913 62 12.66 6.66 11.01 0 334.62 248.25 39355 +1913 63 13.84 7.84 12.19 0 358.84 249.29 39553 +1913 64 11.43 5.43 9.78 0 310.88 255.89 39753 +1913 65 12.04 6.04 10.39 0.15 322.47 193.36 39953 +1913 66 8.64 2.64 6.99 0 262.32 265.21 40154 +1913 67 7.56 1.56 5.91 0 245.35 269.41 40355 +1913 68 8.75 2.75 7.1 0 264.1 270.82 40556 +1913 69 10.72 4.72 9.07 0.4 297.85 203.06 40758 +1913 70 3.92 -2.08 2.27 0 194.91 281.63 40960 +1913 71 5.57 -0.43 3.92 0 216.54 282.91 41163 +1913 72 3.28 -2.72 1.63 0 187.04 288.03 41366 +1913 73 6 0 4.35 0 222.51 287.96 41569 +1913 74 8.04 2.04 6.39 0 252.77 288.29 41772 +1913 75 7.14 1.14 5.49 0 239.01 292.14 41976 +1913 76 9.95 3.95 8.3 0 284.24 291.04 42179 +1913 77 11.7 5.7 10.05 0 315.97 290.92 42383 +1913 78 10.44 4.44 8.79 0 292.83 295.54 42587 +1913 79 7.51 1.51 5.86 0 244.59 302.34 42791 +1913 80 10.39 4.39 8.74 0 291.95 300.84 42996 +1913 81 15.36 9.36 13.71 0 392.23 294.44 43200 +1913 82 13.52 7.52 11.87 0 352.13 300.68 43404 +1913 83 12.58 6.58 10.93 0 333.03 304.86 43608 +1913 84 12.33 6.33 10.68 0.38 328.11 230.85 43812 +1913 85 14.36 8.36 12.71 0.07 369.98 229.81 44016 +1913 86 13.01 7.01 11.36 0.56 341.66 233.55 44220 +1913 87 10.65 4.65 9 0.06 296.59 238.52 44424 +1913 88 12.58 6.58 10.93 0 333.03 317.02 44627 +1913 89 13.53 7.53 11.88 0.04 352.34 238.09 44831 +1913 90 12.14 6.14 10.49 0 324.4 322.42 45034 +1913 91 15.59 9.59 13.94 0 397.51 317.66 45237 +1913 92 14.91 8.91 13.26 0 382.08 321.35 45439 +1913 93 15.67 9.67 14.02 0 399.35 321.83 45642 +1913 94 17.91 11.91 16.26 0 454.2 318.46 45843 +1913 95 14.17 8.17 12.52 0.19 365.87 246.99 46045 +1913 96 15.19 9.19 13.54 1.87 388.37 246.89 46246 +1913 97 7.87 1.87 6.22 0.61 250.12 258.4 46446 +1913 98 8 2 6.35 0 252.14 346.33 46647 +1913 99 7.27 1.27 5.62 0 240.96 349.41 46846 +1913 100 9.41 3.41 7.76 0 275.02 348.17 47045 +1913 101 15.27 9.27 13.62 0 390.18 338.73 47243 +1913 102 12.93 6.93 11.28 0 340.04 345.66 47441 +1913 103 11.17 5.17 9.52 0 306.05 350.86 47638 +1913 104 11.86 5.86 10.21 0 319.01 351.41 47834 +1913 105 17.43 11.43 15.78 0 441.94 340.58 48030 +1913 106 11.81 5.81 10.16 0 318.06 354.95 48225 +1913 107 16.84 10.84 15.19 0 427.25 345.37 48419 +1913 108 15.18 9.18 13.53 0 388.14 351.18 48612 +1913 109 17.99 11.99 16.34 0.37 456.27 259.16 48804 +1913 110 15.58 9.58 13.93 0 397.27 353.2 48995 +1913 111 15.53 9.53 13.88 0 396.12 354.86 49185 +1913 112 13.17 7.17 11.52 0 344.91 361.72 49374 +1913 113 11 5 9.35 0.07 302.93 275.54 49561 +1913 114 11.53 5.53 9.88 0 312.76 367.88 49748 +1913 115 10.62 4.62 8.97 0 296.05 371.03 49933 +1913 116 7.39 1.39 5.74 0.11 242.76 283.22 50117 +1913 117 7.19 1.19 5.54 0.13 239.76 284.45 50300 +1913 118 9.78 3.78 8.13 0 281.31 376.43 50481 +1913 119 8.04 2.04 6.39 0 252.77 380.54 50661 +1913 120 11.1 5.1 9.45 0 304.76 376.42 50840 +1913 121 16.09 10.09 14.44 0.09 409.18 274.82 51016 +1913 122 14.63 8.63 12.98 0 375.88 371.23 51191 +1913 123 14.16 8.16 12.51 0 365.66 373.36 51365 +1913 124 14.98 8.98 13.33 0 383.64 372.5 51536 +1913 125 18.1 12.1 16.45 0 459.14 365.13 51706 +1913 126 14.36 8.36 12.71 0.3 369.98 281.97 51874 +1913 127 14.91 8.91 13.26 0 382.08 375.54 52039 +1913 128 14.9 8.9 13.25 0.08 381.86 282.42 52203 +1913 129 18.7 12.7 17.05 0.68 475.02 275.25 52365 +1913 130 20.19 14.19 18.54 0.4 516.49 272.26 52524 +1913 131 21.6 15.6 19.95 0 558.54 358.89 52681 +1913 132 20.39 14.39 18.74 0 522.29 363.92 52836 +1913 133 18.09 12.09 16.44 0 458.88 371.9 52989 +1913 134 21.19 15.19 19.54 0 546.02 362.52 53138 +1913 135 19.79 13.79 18.14 0 505.07 367.98 53286 +1913 136 19.46 13.46 17.81 0.21 495.8 277.26 53430 +1913 137 21.45 15.45 19.8 0.85 553.93 272.68 53572 +1913 138 20.04 14.04 18.39 1.3 512.18 276.79 53711 +1913 139 19.62 13.62 17.97 0 500.28 371.12 53848 +1913 140 16 10 14.35 0 407.06 382.28 53981 +1913 141 14.84 8.84 13.19 0 380.52 385.69 54111 +1913 142 11.63 5.63 9.98 0 314.64 393.43 54238 +1913 143 13.1 7.1 11.45 0.35 343.48 293.13 54362 +1913 144 13.3 7.3 11.65 0.93 347.58 293.15 54483 +1913 145 11.98 5.98 10.33 0.4 321.31 295.67 54600 +1913 146 11.06 5.06 9.41 0.02 304.03 297.36 54714 +1913 147 13.21 7.21 11.56 0 345.73 392.43 54824 +1913 148 18.13 12.13 16.48 0 459.92 379.9 54931 +1913 149 18.02 12.02 16.37 0 457.05 380.55 55034 +1913 150 17.84 11.84 16.19 0 452.4 381.42 55134 +1913 151 16.28 10.28 14.63 0.34 413.7 289.69 55229 +1913 152 22.07 16.07 20.42 0.03 573.18 275.75 55321 +1913 153 17.71 11.71 16.06 0.6 449.06 286.91 55409 +1913 154 18.89 12.89 17.24 0.1 480.14 284.44 55492 +1913 155 22.56 16.56 20.91 0 588.79 366.51 55572 +1913 156 23.47 17.47 21.82 0 618.75 363.18 55648 +1913 157 22.96 16.96 21.31 0 601.8 365.41 55719 +1913 158 25.04 19.04 23.39 0.27 673.47 267.58 55786 +1913 159 24.97 18.97 23.32 0.07 670.94 267.99 55849 +1913 160 20.9 14.9 19.25 1.06 537.31 280.33 55908 +1913 161 19.9 13.9 18.25 0.62 508.19 282.97 55962 +1913 162 18.04 12.04 16.39 0.09 457.57 287.47 56011 +1913 163 21.07 15.07 19.42 0 542.4 373.5 56056 +1913 164 20.75 14.75 19.1 0 532.86 374.68 56097 +1913 165 23.69 17.69 22.04 0 626.18 363.48 56133 +1913 166 19.15 13.15 17.5 0 487.23 380.26 56165 +1913 167 22.12 16.12 20.47 0 574.76 369.77 56192 +1913 168 21.2 15.2 19.55 0.34 546.32 279.95 56214 +1913 169 25.06 19.06 23.41 2.09 674.19 268.24 56231 +1913 170 26.05 20.05 24.4 0.15 710.79 264.82 56244 +1913 171 20.64 14.64 18.99 0.02 529.61 281.5 56252 +1913 172 18.56 12.56 16.91 0.27 471.27 286.67 56256 +1913 173 17.28 11.28 15.63 0.07 438.16 289.54 56255 +1913 174 19.79 13.79 18.14 0 505.07 378.14 56249 +1913 175 17.98 11.98 16.33 0 456.02 383.87 56238 +1913 176 20.55 14.55 18.9 0.04 526.96 281.61 56223 +1913 177 22.13 16.13 20.48 1.24 575.07 277.2 56203 +1913 178 18.65 12.65 17 0.17 473.68 286.27 56179 +1913 179 14.83 8.83 13.18 0 380.3 392.32 56150 +1913 180 17.75 11.75 16.1 0 450.08 384.21 56116 +1913 181 18.04 12.04 16.39 0.07 457.57 287.45 56078 +1913 182 17.78 11.78 16.13 0 450.85 383.91 56035 +1913 183 19.8 13.8 18.15 0 505.35 377.35 55987 +1913 184 19.24 13.24 17.59 0.01 489.71 284.28 55935 +1913 185 18.3 12.3 16.65 0.71 464.38 286.43 55879 +1913 186 16.11 10.11 14.46 2.54 409.66 290.96 55818 +1913 187 17.14 11.14 15.49 1.04 434.67 288.68 55753 +1913 188 18.64 12.64 16.99 0.52 473.41 285.11 55684 +1913 189 17.69 11.69 16.04 2.34 448.55 287.13 55611 +1913 190 17.55 11.55 15.9 0.66 444.98 287.16 55533 +1913 191 16.47 10.47 14.82 0.28 418.26 289.26 55451 +1913 192 17.22 11.22 15.57 0.01 436.66 287.44 55366 +1913 193 18.98 12.98 17.33 0.06 482.59 283.25 55276 +1913 194 17.19 11.19 15.54 1.08 435.91 287.13 55182 +1913 195 21.87 15.87 20.22 1.29 566.91 275.4 55085 +1913 196 20.49 14.49 18.84 0.36 525.2 278.82 54984 +1913 197 18.55 12.55 16.9 0.02 471 283.23 54879 +1913 198 17.44 11.44 15.79 0.01 442.19 285.4 54770 +1913 199 23.84 17.84 22.19 0.16 631.29 268.36 54658 +1913 200 21.47 15.47 19.82 0 554.54 366.65 54542 +1913 201 21.88 15.88 20.23 0.36 567.22 273.51 54423 +1913 202 21.27 15.27 19.62 0.09 548.44 274.76 54301 +1913 203 22.16 16.16 20.51 0.33 576.02 271.93 54176 +1913 204 21.57 15.57 19.92 0.93 557.61 273.19 54047 +1913 205 20.43 14.43 18.78 1.2 523.45 275.82 53915 +1913 206 24.24 18.24 22.59 0 645.09 352.72 53780 +1913 207 22.88 16.88 21.23 0 599.18 357.6 53643 +1913 208 19.57 13.57 17.92 0 498.88 368.74 53502 +1913 209 18.21 12.21 16.56 0 462.01 372.32 53359 +1913 210 17.57 11.57 15.92 0 445.49 373.57 53213 +1913 211 19.1 13.1 17.45 0 485.86 368.18 53064 +1913 212 19.11 13.11 17.46 0.63 486.14 275.51 52913 +1913 213 19.76 13.76 18.11 0.73 504.22 273.38 52760 +1913 214 18.15 12.15 16.5 0.08 460.44 276.56 52604 +1913 215 18.12 12.12 16.47 0 459.66 368.15 52445 +1913 216 18.99 12.99 17.34 0.04 482.86 273.37 52285 +1913 217 19.86 13.86 18.21 0 507.05 360.85 52122 +1913 218 16.85 10.85 15.2 0.05 427.5 276.73 51958 +1913 219 19.39 13.39 17.74 0 493.86 360.48 51791 +1913 220 19.58 13.58 17.93 0.35 499.16 269.2 51622 +1913 221 20.51 14.51 18.86 0.14 525.79 266.18 51451 +1913 222 19.16 13.16 17.51 0 487.51 358.19 51279 +1913 223 18.44 12.44 16.79 0.34 468.08 269.41 51105 +1913 224 20.74 14.74 19.09 0.18 532.56 263.18 50929 +1913 225 20.49 14.49 18.84 0 525.2 350.6 50751 +1913 226 20.35 14.35 18.7 0.41 521.12 262.44 50572 +1913 227 20.68 14.68 19.03 0 530.79 347.56 50392 +1913 228 19.17 13.17 17.52 0.08 487.78 263.36 50210 +1913 229 20.51 14.51 18.86 0 525.79 345.68 50026 +1913 230 19.35 13.35 17.7 2.05 492.75 261.06 49842 +1913 231 24.79 18.79 23.14 0.5 664.49 245.4 49656 +1913 232 26.47 20.47 24.82 0 726.82 318.66 49469 +1913 233 26.29 20.29 24.64 1.32 719.91 238.6 49280 +1913 234 24.43 18.43 22.78 2.06 651.74 243.49 49091 +1913 235 23.93 17.93 22.28 0.12 634.38 243.9 48900 +1913 236 19.05 13.05 17.4 0.12 484.5 255.29 48709 +1913 237 17.51 11.51 15.86 1.28 443.96 257.3 48516 +1913 238 15.03 9.03 13.38 0 384.76 347.56 48323 +1913 239 20.06 14.06 18.41 0.38 512.76 249.4 48128 +1913 240 23.71 17.71 22.06 0.71 626.86 238.74 47933 +1913 241 22.97 16.97 21.32 0.27 602.13 239.54 47737 +1913 242 22.29 16.29 20.64 0.89 580.15 240.07 47541 +1913 243 19.92 13.92 18.27 0.44 508.76 244.45 47343 +1913 244 16.23 10.23 14.58 0 412.51 334.11 47145 +1913 245 10.85 4.85 9.2 0 300.2 343.35 46947 +1913 246 14.67 8.67 13.02 1.01 376.76 250.38 46747 +1913 247 14.74 8.74 13.09 0.44 378.3 248.84 46547 +1913 248 14.27 8.27 12.62 0 368.03 330.82 46347 +1913 249 13.33 7.33 11.68 0 348.2 330.65 46146 +1913 250 13.12 7.12 11.47 0 343.89 329.06 45945 +1913 251 18.91 12.91 17.26 0 480.69 313.42 45743 +1913 252 23.68 17.68 22.03 0 625.84 296.32 45541 +1913 253 23.15 17.15 21.5 0.03 608.07 222.12 45339 +1913 254 20.29 14.29 18.64 0.13 519.38 227.39 45136 +1913 255 20.89 14.89 19.24 0.03 537.02 224.4 44933 +1913 256 23.47 17.47 21.82 0 618.75 288.68 44730 +1913 257 24.71 18.71 23.06 0 661.64 282.21 44527 +1913 258 23.06 17.06 21.41 0.45 605.1 214.33 44323 +1913 259 23.67 17.67 22.02 0.03 625.5 211.03 44119 +1913 260 18.84 12.84 17.19 1.21 478.79 220.18 43915 +1913 261 19.36 13.36 17.71 0.17 493.03 217.34 43711 +1913 262 22.59 16.59 20.94 0 589.76 278.08 43507 +1913 263 19.43 13.43 17.78 0.78 494.97 213.65 43303 +1913 264 18.56 12.56 16.91 1.6 471.27 213.43 43099 +1913 265 22.05 16.05 20.4 0.5 572.55 204.49 42894 +1913 266 19.63 13.63 17.98 0.05 500.56 207.81 42690 +1913 267 12.72 6.72 11.07 0 335.82 289.27 42486 +1913 268 11.13 5.13 9.48 0.04 305.31 216.96 42282 +1913 269 13.67 7.67 12.02 0 355.26 282.45 42078 +1913 270 19.19 13.19 17.54 0.3 488.33 201.04 41875 +1913 271 18.1 12.1 16.45 1.31 459.14 201.08 41671 +1913 272 18.29 12.29 16.64 0.23 464.12 198.74 41468 +1913 273 18.69 12.69 17.04 0.14 474.75 196.18 41265 +1913 274 13.73 7.73 12.08 0 356.52 269.07 41062 +1913 275 14.9 8.9 13.25 0 381.86 264.19 40860 +1913 276 14.3 8.3 12.65 0 368.68 262.59 40658 +1913 277 12.11 6.11 10.46 0 323.82 263.57 40456 +1913 278 13.56 7.56 11.91 0.01 352.96 193.76 40255 +1913 279 10.25 4.25 8.6 0.01 289.48 195.4 40054 +1913 280 9.87 3.87 8.22 0 282.86 258.35 39854 +1913 281 6.06 0.06 4.41 0 223.35 260.03 39654 +1913 282 5.02 -0.98 3.37 0 209.11 258.24 39455 +1913 283 8.24 2.24 6.59 0 255.92 251.95 39256 +1913 284 9.02 3.02 7.37 0 268.52 247.95 39058 +1913 285 9.08 3.08 7.43 0.07 269.51 183.9 38861 +1913 286 8.79 2.79 7.14 0.04 264.75 182.05 38664 +1913 287 10.38 4.38 8.73 0 291.77 237.81 38468 +1913 288 11.89 5.89 10.24 0 319.59 232.98 38273 +1913 289 15.72 9.72 14.07 0 400.51 224.36 38079 +1913 290 17.73 11.73 16.08 0 449.57 217.85 37885 +1913 291 19.1 13.1 17.45 0 485.86 212.48 37693 +1913 292 16.66 10.66 15.01 0.27 422.85 160.96 37501 +1913 293 17.03 11.03 15.38 0.84 431.94 158.46 37311 +1913 294 15.42 9.42 13.77 0 393.6 211.25 37121 +1913 295 17.61 11.61 15.96 0 446.5 204.66 36933 +1913 296 17.82 11.82 16.17 0 451.88 201.77 36745 +1913 297 18.14 12.14 16.49 0 460.18 198.55 36560 +1913 298 22.24 16.24 20.59 0.81 578.56 140.59 36375 +1913 299 17.59 11.59 15.94 0.59 446 145.76 36191 +1913 300 15.11 9.11 13.46 0 386.56 195.86 36009 +1913 301 17.93 11.93 16.28 0 454.72 188.75 35829 +1913 302 16 10 14.35 0.1 407.06 142.1 35650 +1913 303 15.35 9.35 13.7 0 392 187.96 35472 +1913 304 14.09 8.09 12.44 0 364.16 187.37 35296 +1913 305 14.18 8.18 12.53 0 366.09 184.55 35122 +1913 306 17.5 11.5 15.85 0 443.71 177.34 34950 +1913 307 15.58 9.58 13.93 1.95 397.27 133.44 34779 +1913 308 13.74 7.74 12.09 0 356.73 177.93 34610 +1913 309 13.31 7.31 11.66 0 347.78 176.21 34444 +1913 310 10.81 4.81 9.16 0 299.47 176.71 34279 +1913 311 14.2 8.2 12.55 0 366.52 170.55 34116 +1913 312 12.06 6.06 10.41 0.38 322.85 127.92 33956 +1913 313 8.5 2.5 6.85 0.25 260.06 129.07 33797 +1913 314 6.49 0.49 4.84 0.1 229.48 128.87 33641 +1913 315 6.42 0.42 4.77 0 228.47 169.34 33488 +1913 316 8.25 2.25 6.6 0 256.08 165.65 33337 +1913 317 14.22 8.22 12.57 0 366.95 157.25 33188 +1913 318 13.68 7.68 12.03 0 355.47 155.62 33042 +1913 319 11.19 5.19 9.54 0.16 306.42 117.53 32899 +1913 320 7.32 1.32 5.67 0 241.71 158.33 32758 +1913 321 9.87 3.87 8.22 0 282.86 154.06 32620 +1913 322 10.83 4.83 9.18 0.19 299.83 113.52 32486 +1913 323 7.32 1.32 5.67 1.61 241.71 114.6 32354 +1913 324 6.15 0.15 4.5 0.19 224.62 113.71 32225 +1913 325 8.18 2.18 6.53 0 254.97 148.36 32100 +1913 326 8.49 2.49 6.84 0.01 259.9 110 31977 +1913 327 9.68 3.68 8.03 0 279.6 143.83 31858 +1913 328 8.87 2.87 7.22 0.37 266.06 106.92 31743 +1913 329 8.04 2.04 6.39 0.49 252.77 106.31 31631 +1913 330 7.06 1.06 5.41 0.01 237.82 105.78 31522 +1913 331 6.5 0.5 4.85 0.22 229.62 105.09 31417 +1913 332 8.85 2.85 7.2 0.39 265.73 102.56 31316 +1913 333 3.19 -2.81 1.54 0 185.95 139.43 31218 +1913 334 6.3 0.3 4.65 0 226.75 136.44 31125 +1913 335 2.62 -3.38 0.97 0 179.21 137.45 31035 +1913 336 4.92 -1.08 3.27 0 207.79 135.08 30949 +1913 337 3.46 -2.54 1.81 0 189.23 134.25 30867 +1913 338 0.39 -5.61 -1.26 0 154.8 134.82 30790 +1913 339 0.83 -5.17 -0.82 0.97 159.38 100.37 30716 +1913 340 0.77 -5.23 -0.88 0.01 158.75 99.83 30647 +1913 341 0.71 -5.29 -0.94 0.33 158.12 99.15 30582 +1913 342 3.54 -2.46 1.89 0.67 190.2 97.54 30521 +1913 343 4.73 -1.27 3.08 0.2 205.29 96.42 30465 +1913 344 5.4 -0.6 3.75 0 214.22 127.03 30413 +1913 345 7.2 1.2 5.55 0.21 239.91 94.09 30366 +1913 346 3.21 -2.79 1.56 0 186.2 127.28 30323 +1913 347 4.27 -1.73 2.62 0 199.34 126.12 30284 +1913 348 1.84 -4.16 0.19 0 170.32 127.01 30251 +1913 349 4.86 -1.14 3.21 0 206.99 125.05 30221 +1913 350 9.18 3.18 7.53 0.03 271.17 91.39 30197 +1913 351 8.01 2.01 6.36 0 252.3 122.5 30177 +1913 352 7.14 1.14 5.49 0 239.01 123 30162 +1913 353 4.33 -1.67 2.68 0 200.11 124.64 30151 +1913 354 1.16 -4.84 -0.49 0 162.88 126.19 30145 +1913 355 3.12 -2.88 1.47 0 185.11 125.25 30144 +1913 356 2.39 -3.61 0.74 0 176.55 125.64 30147 +1913 357 5.54 -0.46 3.89 0 216.13 123.99 30156 +1913 358 5.1 -0.9 3.45 0.03 210.18 93.26 30169 +1913 359 6.05 0.05 4.4 0.2 223.21 92.92 30186 +1913 360 6.36 0.36 4.71 1.2 227.61 93.04 30208 +1913 361 6.75 0.75 5.1 0.19 233.25 93.1 30235 +1913 362 4.7 -1.3 3.05 0.66 204.89 94.37 30267 +1913 363 3.03 -2.97 1.38 0.62 184.04 95.49 30303 +1913 364 8.62 2.62 6.97 0 261.99 124.24 30343 +1913 365 8.92 2.92 7.27 0.31 266.88 93.43 30388 +1914 1 0.73 -5.27 -0.92 0 158.33 130.28 30438 +1914 2 -4.41 -10.41 -6.06 0 111.81 132.95 30492 +1914 3 -7 -13 -8.65 0 93.25 134.64 30551 +1914 4 -3.25 -9.25 -4.9 0.05 121.12 144.11 30614 +1914 5 -0.22 -6.22 -1.87 0 148.65 177.13 30681 +1914 6 1.43 -4.57 -0.22 0 165.8 134.11 30752 +1914 7 -3.24 -9.24 -4.89 0 121.2 136.82 30828 +1914 8 -2.24 -8.24 -3.89 0 129.76 137.96 30907 +1914 9 -1.36 -7.36 -3.01 0 137.72 138.89 30991 +1914 10 -0.31 -6.31 -1.96 0 147.76 139.77 31079 +1914 11 -1.16 -7.16 -2.81 0 139.58 141.13 31171 +1914 12 0.75 -5.25 -0.9 0.59 158.54 105.98 31266 +1914 13 -0.5 -6.5 -2.15 0.45 145.9 151.09 31366 +1914 14 -5.42 -11.42 -7.07 0.05 104.22 153.59 31469 +1914 15 -4.75 -10.75 -6.4 0.12 109.21 154.75 31575 +1914 16 -4.8 -10.8 -6.45 0 108.83 192.94 31686 +1914 17 -6.88 -12.88 -8.53 0 94.04 195.14 31800 +1914 18 -6.19 -12.19 -7.84 0 98.74 196.71 31917 +1914 19 -4.26 -10.26 -5.91 0 112.98 197.88 32038 +1914 20 -1.18 -7.18 -2.83 0 139.39 198.12 32161 +1914 21 2.27 -3.73 0.62 0 175.17 197.99 32289 +1914 22 -1.39 -7.39 -3.04 0 137.44 201.39 32419 +1914 23 -5.12 -11.12 -6.77 0.7 106.43 165.93 32552 +1914 24 -6.39 -12.39 -8.04 0 97.36 208.85 32688 +1914 25 -3.37 -9.37 -5.02 0 120.12 209.53 32827 +1914 26 -5.85 -11.85 -7.5 0 101.13 212.19 32969 +1914 27 0.74 -5.26 -0.91 0 158.43 211.19 33114 +1914 28 0.41 -5.59 -1.24 0 155.01 213.34 33261 +1914 29 -1.24 -7.24 -2.89 0.17 138.83 173.49 33411 +1914 30 -1.09 -7.09 -2.74 0 140.24 218.86 33564 +1914 31 0.5 -5.5 -1.15 0 155.94 220.19 33718 +1914 32 5.64 -0.36 3.99 0 217.5 218.14 33875 +1914 33 2.81 -3.19 1.16 0.27 181.43 177.04 34035 +1914 34 1.65 -4.35 0 0.03 168.21 178.85 34196 +1914 35 3.59 -2.41 1.94 0.01 190.82 178.92 34360 +1914 36 3.27 -2.73 1.62 0 186.92 227.21 34526 +1914 37 5.51 -0.49 3.86 0 215.72 227.17 34694 +1914 38 6.41 0.41 4.76 0 228.32 228.23 34863 +1914 39 7.81 1.81 6.16 0.07 249.19 143.56 35035 +1914 40 5.46 -0.54 3.81 0.53 215.04 147.04 35208 +1914 41 3.38 -2.62 1.73 0 188.25 200.25 35383 +1914 42 1.39 -4.61 -0.26 0 165.37 204.15 35560 +1914 43 -1.5 -7.5 -3.15 0 136.42 208.55 35738 +1914 44 -1.57 -7.57 -3.22 0 135.78 211.19 35918 +1914 45 -3.32 -9.32 -4.97 0 120.54 214.72 36099 +1914 46 -4.89 -10.89 -6.54 0 108.15 218.16 36282 +1914 47 -7 -13 -8.65 0 93.25 221.88 36466 +1914 48 -7.73 -13.73 -9.38 0 88.52 225.01 36652 +1914 49 -3.38 -9.38 -5.03 0 120.04 226.04 36838 +1914 50 -1.85 -7.85 -3.5 0 133.23 227.97 37026 +1914 51 0.64 -5.36 -1.01 0 157.39 229.5 37215 +1914 52 -0.06 -6.06 -1.71 0 150.24 232.81 37405 +1914 53 3.67 -2.33 2.02 0 191.8 233.13 37596 +1914 54 7.46 1.46 5.81 0 243.83 232.39 37788 +1914 55 3.9 -2.1 2.25 0 194.66 238.72 37981 +1914 56 2.47 -3.53 0.82 0 177.47 242.58 38175 +1914 57 0.8 -5.2 -0.85 0 159.06 246.71 38370 +1914 58 -0.38 -6.38 -2.03 0 147.07 250.47 38565 +1914 59 0.18 -5.82 -1.47 0 152.66 252.85 38761 +1914 60 10.72 4.72 9.07 0 297.85 245.43 38958 +1914 61 10.49 4.49 8.84 0.01 293.72 186.47 39156 +1914 62 11.18 5.18 9.53 0.29 306.24 187.82 39355 +1914 63 9.34 3.34 7.69 0.01 273.84 191.9 39553 +1914 64 8.56 2.56 6.91 0 261.02 259.72 39753 +1914 65 10.54 4.54 8.89 0.67 294.62 195 39953 +1914 66 12.06 6.06 10.41 0.88 322.85 195.36 40154 +1914 67 10.32 4.32 8.67 0.03 290.71 199.41 40355 +1914 68 13.46 7.46 11.81 0 350.88 263.86 40556 +1914 69 11.12 5.12 9.47 0.47 305.13 202.62 40758 +1914 70 10.06 4.06 8.41 0.68 286.15 205.87 40960 +1914 71 6.18 0.18 4.53 0.07 225.05 211.69 41163 +1914 72 6.93 0.93 5.28 0 235.89 284.23 41366 +1914 73 10.19 4.19 8.54 0 288.42 282.64 41569 +1914 74 8.19 2.19 6.54 0 255.13 288.1 41772 +1914 75 9.49 3.49 7.84 0 276.37 289.08 41976 +1914 76 9.95 3.95 8.3 0 284.24 291.04 42179 +1914 77 11.7 5.7 10.05 0 315.97 290.92 42383 +1914 78 7.21 1.21 5.56 0 240.06 299.98 42587 +1914 79 5.59 -0.41 3.94 0 216.82 304.64 42791 +1914 80 6.34 0.34 4.69 0.23 227.32 229.75 42996 +1914 81 8.71 2.71 7.06 0 263.45 305.87 43200 +1914 82 10.16 4.16 8.51 0.04 287.9 229.8 43404 +1914 83 10.93 4.93 9.28 0 301.65 307.66 43608 +1914 84 7.08 1.08 5.43 0.87 238.11 236.81 43812 +1914 85 8.6 2.6 6.95 0.24 261.67 237.16 44016 +1914 86 9.25 3.25 7.6 0 272.34 317.68 44220 +1914 87 6.56 0.56 4.91 0.11 230.49 242.93 44424 +1914 88 6.08 0.08 4.43 0 223.63 326.87 44627 +1914 89 3.41 -2.59 1.76 0.36 188.62 249.15 44831 +1914 90 8.15 2.15 6.5 0 254.5 328.83 45034 +1914 91 16.96 10.96 15.31 0 430.2 314.46 45237 +1914 92 19 13 17.35 0 483.13 311.35 45439 +1914 93 16.2 10.2 14.55 0 411.79 320.61 45642 +1914 94 15.98 9.98 14.33 0 406.59 323.22 45843 +1914 95 19.42 13.42 17.77 0.02 494.69 237.29 46045 +1914 96 16.03 10.03 14.38 0.19 407.77 245.44 46246 +1914 97 15.76 9.76 14.11 0 401.44 329.89 46446 +1914 98 14.64 8.64 12.99 0.45 376.1 250.76 46647 +1914 99 13.41 7.41 11.76 0 349.85 338.94 46846 +1914 100 10.19 4.19 8.54 0.09 288.42 260.16 47045 +1914 101 12.11 6.11 10.46 0 323.82 345.37 47243 +1914 102 16.26 10.26 14.61 0.07 413.22 253.68 47441 +1914 103 16.44 10.44 14.79 0.11 417.53 254.7 47638 +1914 104 17.16 11.16 15.51 0.55 435.17 254.66 47834 +1914 105 11.8 5.8 10.15 0 317.87 353.32 48030 +1914 106 8.45 2.45 6.8 0.16 259.26 270.56 48225 +1914 107 9.62 3.62 7.97 0.05 278.57 270.41 48419 +1914 108 10.35 4.35 8.7 0 291.24 361.06 48612 +1914 109 15.81 9.81 14.16 0 402.61 351.25 48804 +1914 110 16.72 10.72 15.07 0 424.32 350.34 48995 +1914 111 11.7 5.7 10.05 0 315.97 363.17 49185 +1914 112 12.28 6.28 10.63 0.02 327.13 272.67 49374 +1914 113 12.85 6.85 11.2 0 338.42 363.74 49561 +1914 114 15.66 9.66 14.01 0 399.12 358.84 49748 +1914 115 17.57 11.57 15.92 0 445.49 355.24 49933 +1914 116 17.8 11.8 16.15 0 451.37 355.79 50117 +1914 117 14.32 8.32 12.67 0 369.11 365.96 50300 +1914 118 10.81 4.81 9.16 0 299.47 374.57 50481 +1914 119 11.28 5.28 9.63 0 308.09 374.89 50661 +1914 120 12.22 6.22 10.57 0 325.96 374.21 50840 +1914 121 14.25 8.25 12.6 2.54 367.6 278.19 51016 +1914 122 15.57 9.57 13.92 1.65 397.04 276.7 51191 +1914 123 13.71 7.71 12.06 0 356.1 374.39 51365 +1914 124 17.11 11.11 15.46 0.14 433.92 275.23 51536 +1914 125 16.31 10.31 14.66 0.51 414.42 277.58 51706 +1914 126 18.52 12.52 16.87 1.02 470.21 273.64 51874 +1914 127 19.8 13.8 18.15 0.42 505.35 271.3 52039 +1914 128 23.41 17.41 21.76 0.44 616.73 262.27 52203 +1914 129 19.86 13.86 18.21 1.94 507.05 272.5 52365 +1914 130 17.89 11.89 16.24 0.73 453.69 277.65 52524 +1914 131 17.64 11.64 15.99 0.56 447.27 278.78 52681 +1914 132 16.57 10.57 14.92 0.33 420.67 281.64 52836 +1914 133 16.3 10.3 14.65 0 414.18 376.95 52989 +1914 134 16.22 10.22 14.57 0.03 412.27 283.4 53138 +1914 135 14.41 8.41 12.76 0.54 371.06 287.36 53286 +1914 136 15.19 9.19 13.54 0 388.37 381.88 53430 +1914 137 18.76 12.76 17.11 0 476.63 372.59 53572 +1914 138 16.66 10.66 15.01 0 422.85 379.32 53711 +1914 139 17.4 11.4 15.75 0.01 441.18 283.45 53848 +1914 140 13.79 7.79 12.14 0.06 357.78 290.83 53981 +1914 141 9.43 3.43 7.78 0 275.36 397.12 54111 +1914 142 10.04 4.04 8.39 0 285.8 396.53 54238 +1914 143 16.09 10.09 14.44 0 409.18 383.52 54362 +1914 144 16.76 10.76 15.11 0 425.29 382.17 54483 +1914 145 17.14 11.14 15.49 0 434.67 381.57 54600 +1914 146 18.48 12.48 16.83 0 469.14 377.98 54714 +1914 147 14.56 8.56 12.91 0 374.34 389.25 54824 +1914 148 21.11 15.11 19.46 0 543.61 370.08 54931 +1914 149 19.18 13.18 17.53 0 488.06 376.94 55034 +1914 150 20.17 14.17 18.52 0.45 515.92 280.5 55134 +1914 151 17.14 11.14 15.49 0.01 434.67 287.89 55229 +1914 152 22.95 16.95 21.3 0 601.48 364.24 55321 +1914 153 21.84 15.84 20.19 0 565.97 368.77 55409 +1914 154 22.96 16.96 21.31 0.96 601.8 273.56 55492 +1914 155 23.92 17.92 22.27 1.47 634.03 270.75 55572 +1914 156 19.53 13.53 17.88 0.45 497.76 283.27 55648 +1914 157 20.88 14.88 19.23 0 536.72 373.25 55719 +1914 158 22.97 16.97 21.32 0.06 602.13 274.15 55786 +1914 159 19.17 13.17 17.52 0 487.78 379.45 55849 +1914 160 21.24 15.24 19.59 0.1 547.53 279.41 55908 +1914 161 20.36 14.36 18.71 1.33 521.41 281.8 55962 +1914 162 19.79 13.79 18.14 1.45 505.07 283.3 56011 +1914 163 19.12 13.12 17.47 0.24 486.41 285.1 56056 +1914 164 20.24 14.24 18.59 0 517.94 376.46 56097 +1914 165 18.91 12.91 17.26 0 480.69 380.95 56133 +1914 166 19.44 13.44 17.79 0.41 495.25 284.49 56165 +1914 167 20.18 14.18 18.53 2.19 516.2 282.59 56192 +1914 168 21.33 15.33 19.68 0 550.27 372.8 56214 +1914 169 20.76 14.76 19.11 0 533.15 374.86 56231 +1914 170 15.1 9.1 13.45 0 386.34 391.95 56244 +1914 171 18.26 12.26 16.61 0 463.33 383.16 56252 +1914 172 20.87 14.87 19.22 0 536.42 374.52 56256 +1914 173 22.82 16.82 21.17 0.01 597.22 275.37 56255 +1914 174 17.71 11.71 16.06 0.04 449.06 288.53 56249 +1914 175 13.8 7.8 12.15 0 357.99 395.05 56238 +1914 176 16.35 10.35 14.7 0 415.37 388.52 56223 +1914 177 18.02 12.02 16.37 0 457.05 383.61 56203 +1914 178 18.15 12.15 16.5 0 460.44 383.24 56179 +1914 179 19.98 13.98 18.33 0 510.47 377.26 56150 +1914 180 17.37 11.37 15.72 0.01 440.43 289 56116 +1914 181 18.38 12.38 16.73 0 466.49 382.23 56078 +1914 182 17.94 11.94 16.29 0.69 454.98 287.57 56035 +1914 183 20.01 14.01 18.36 1.19 511.32 282.48 55987 +1914 184 24.13 18.13 22.48 0.01 641.27 270.6 55935 +1914 185 26.77 20.77 25.12 0.34 738.45 261.47 55879 +1914 186 24.81 18.81 23.16 1 665.2 268.14 55818 +1914 187 25.72 19.72 24.07 1.2 698.41 264.92 55753 +1914 188 24.27 18.27 22.62 0.81 646.14 269.57 55684 +1914 189 22.13 16.13 20.48 1.08 575.07 275.93 55611 +1914 190 23.49 17.49 21.84 1.52 619.42 271.62 55533 +1914 191 20.58 14.58 18.93 0.18 527.84 279.69 55451 +1914 192 22.55 16.55 20.9 0 588.47 365.36 55366 +1914 193 23.53 17.53 21.88 0 620.77 361.18 55276 +1914 194 22.83 16.83 21.18 1.82 597.55 272.84 55182 +1914 195 23.95 17.95 22.3 0.16 635.06 269.22 55085 +1914 196 20.96 14.96 19.31 1.27 539.11 277.58 54984 +1914 197 17.28 11.28 15.63 0.64 438.16 286.06 54879 +1914 198 15.87 9.87 14.22 0.72 404.01 288.65 54770 +1914 199 16.2 10.2 14.55 0.22 411.79 287.72 54658 +1914 200 12.82 6.82 11.17 0 337.82 391.44 54542 +1914 201 18.39 12.39 16.74 0 466.76 376.46 54423 +1914 202 16.29 10.29 14.64 1.46 413.94 286.44 54301 +1914 203 20.33 14.33 18.68 0.36 520.54 276.85 54176 +1914 204 20.12 14.12 18.47 1.1 514.48 277 54047 +1914 205 17.26 11.26 15.61 0.45 437.66 283.24 53915 +1914 206 21.43 15.43 19.78 0.08 553.32 272.77 53780 +1914 207 21.96 15.96 20.31 0 569.72 361.1 53643 +1914 208 24.77 18.77 23.12 0.77 663.78 261.88 53502 +1914 209 24.45 18.45 22.8 0.42 652.44 262.44 53359 +1914 210 20.07 14.07 18.42 0.03 513.04 274.37 53213 +1914 211 25.04 19.04 23.39 0.15 673.47 259.52 53064 +1914 212 20.89 14.89 19.24 0 537.02 361.47 52913 +1914 213 21.58 15.58 19.93 0.01 557.92 268.71 52760 +1914 214 20.58 14.58 18.93 0.79 527.84 270.78 52604 +1914 215 21.04 15.04 19.39 0 541.5 358.78 52445 +1914 216 20.91 14.91 19.26 0 537.61 358.22 52285 +1914 217 25.58 19.58 23.93 0 693.21 338.95 52122 +1914 218 22.06 16.06 20.41 0.21 572.86 264.33 51958 +1914 219 22 16 20.35 0 570.98 351.62 51791 +1914 220 19.6 13.6 17.95 1.83 499.72 269.15 51622 +1914 221 20.49 14.49 18.84 0.18 525.2 266.23 51451 +1914 222 22.94 16.94 21.29 0 601.15 345.18 51279 +1914 223 22.15 16.15 20.5 0.04 575.7 260.26 51105 +1914 224 19.33 13.33 17.68 0 492.19 355.46 50929 +1914 225 20.16 14.16 18.51 0 515.63 351.68 50751 +1914 226 22.92 16.92 21.27 0 600.49 340.87 50572 +1914 227 19.75 13.75 18.1 0 503.94 350.57 50392 +1914 228 21.65 15.65 20 0.04 560.08 257.28 50210 +1914 229 20.65 14.65 19 0 529.9 345.22 50026 +1914 230 21.42 15.42 19.77 0 553.01 341.36 49842 +1914 231 24.65 18.65 23 0 659.51 327.78 49656 +1914 232 26.75 20.75 25.1 0 737.67 317.39 49469 +1914 233 23.81 17.81 22.16 0 630.27 328.47 49280 +1914 234 26.61 20.61 24.96 0 732.23 315.36 49091 +1914 235 25.76 19.76 24.11 0.21 699.9 238.28 48900 +1914 236 26.39 20.39 24.74 0.12 723.74 235.21 48709 +1914 237 23.03 17.03 21.38 0 604.11 325.63 48516 +1914 238 22.31 16.31 20.66 0 580.78 326.59 48323 +1914 239 17.83 11.83 16.18 0 452.14 339 48128 +1914 240 18.71 12.71 17.06 0.62 475.29 251.09 47933 +1914 241 23.27 17.27 21.62 0.83 612.06 238.72 47737 +1914 242 24.1 18.1 22.45 0 640.23 313.5 47541 +1914 243 22.7 16.7 21.05 0 593.32 316.85 47343 +1914 244 15.89 9.89 14.24 0.04 404.48 251.19 47145 +1914 245 20.38 14.38 18.73 0 522 320.91 46947 +1914 246 19.48 13.48 17.83 0.44 496.36 241.24 46747 +1914 247 15.34 9.34 13.69 0.17 391.77 247.84 46547 +1914 248 19.05 13.05 17.4 0 484.5 319.11 46347 +1914 249 15.21 9.21 13.56 0.03 388.82 245.01 46146 +1914 250 14.68 8.68 13.03 0 376.98 325.86 45945 +1914 251 16 10 14.35 0.04 407.06 240.57 45743 +1914 252 16.09 10.09 14.44 0 409.18 318.38 45541 +1914 253 20.88 14.88 19.23 0 536.72 303.51 45339 +1914 254 17.79 11.79 16.14 0 451.11 309.99 45136 +1914 255 17.32 11.32 15.67 0.08 439.17 231.68 44933 +1914 256 19.12 13.12 17.47 0.22 486.41 226.52 44730 +1914 257 17.87 11.87 16.22 0.66 453.17 227.35 44527 +1914 258 20.7 14.7 19.05 1.98 531.38 219.87 44323 +1914 259 20.63 14.63 18.98 0.66 529.31 218.24 44119 +1914 260 18.14 12.14 16.49 0.3 460.18 221.52 43915 +1914 261 18.75 12.75 17.1 0.69 476.36 218.54 43711 +1914 262 19.89 13.89 18.24 0.01 507.9 214.53 43507 +1914 263 23.28 17.28 21.63 0 612.39 273.5 43303 +1914 264 26.54 20.54 24.89 0 729.52 259.41 43099 +1914 265 21.89 15.89 20.24 0.05 567.53 204.85 42894 +1914 266 17.73 11.73 16.08 0.52 449.57 211.35 42690 +1914 267 15.99 9.99 14.34 0.68 406.83 212.26 42486 +1914 268 15.48 9.48 13.83 0.94 394.97 211.13 42282 +1914 269 17.23 11.23 15.58 0 436.91 275.27 42078 +1914 270 13.63 7.63 11.98 0.05 354.42 209.9 41875 +1914 271 13.05 7.05 11.4 0.52 342.47 208.68 41671 +1914 272 8.95 2.95 7.3 0.23 267.37 211.26 41468 +1914 273 10.61 4.61 8.96 0.04 295.87 207.58 41265 +1914 274 3.55 -2.45 1.9 0.05 190.33 211.74 41062 +1914 275 9.23 3.23 7.58 0.98 272 204.86 40860 +1914 276 10.49 4.49 8.84 0 293.72 268.67 40658 +1914 277 11.39 5.39 9.74 0 310.13 264.67 40456 +1914 278 8.92 2.92 7.27 0 266.88 265.15 40255 +1914 279 10.22 4.22 8.57 0 288.95 260.58 40054 +1914 280 12.79 6.79 11.14 0 337.22 254.13 39854 +1914 281 12.43 6.43 10.78 0 330.07 251.96 39654 +1914 282 12.17 6.17 10.52 0 324.99 249.6 39455 +1914 283 5.94 -0.06 4.29 0 221.67 254.44 39256 +1914 284 8.5 2.5 6.85 0 260.06 248.57 39058 +1914 285 7.83 1.83 6.18 0 249.5 246.64 38861 +1914 286 11.02 5.02 9.37 0 303.3 239.92 38664 +1914 287 10.91 4.91 9.26 0.07 301.29 177.84 38468 +1914 288 12.69 6.69 11.04 0 335.22 231.83 38273 +1914 289 13.27 7.27 11.62 0.04 346.96 171.26 38079 +1914 290 16.07 10.07 14.42 0 408.71 220.94 37885 +1914 291 17.88 11.88 16.23 0 453.43 214.94 37693 +1914 292 13.66 7.66 12.01 0 355.05 219.56 37501 +1914 293 15.08 9.08 13.43 0 385.89 214.64 37311 +1914 294 16.08 10.08 14.43 0 408.95 210.14 37121 +1914 295 18.15 12.15 16.5 0 460.44 203.65 36933 +1914 296 16.8 10.8 15.15 0 426.27 203.61 36745 +1914 297 12.87 6.87 11.22 0 338.83 207.04 36560 +1914 298 13.26 7.26 11.61 0 346.76 203.92 36375 +1914 299 16.53 10.53 14.88 0.19 419.7 147.14 36191 +1914 300 16.66 10.66 15.01 0.07 422.85 145.04 36009 +1914 301 13.13 7.13 11.48 0 344.1 196.22 35829 +1914 302 17.3 11.3 15.65 0.72 438.67 140.5 35650 +1914 303 16.96 10.96 15.31 0.55 430.2 139.06 35472 +1914 304 12.49 6.49 10.84 0.07 331.25 142.11 35296 +1914 305 3.26 -2.74 1.61 0 186.8 195.51 35122 +1914 306 2.98 -3.02 1.33 0 183.44 193.4 34950 +1914 307 7.67 1.67 6.02 0 247.03 187.17 34779 +1914 308 3.41 -2.59 1.76 0 188.62 187.9 34610 +1914 309 5.09 -0.91 3.44 0 210.05 184.34 34444 +1914 310 3.01 -2.99 1.36 0.6 183.8 137.5 34279 +1914 311 5.38 -0.62 3.73 0 213.95 179.45 34116 +1914 312 5.89 -0.11 4.24 0 220.97 176.4 33956 +1914 313 6.2 0.2 4.55 0 225.33 174.02 33797 +1914 314 9.67 3.67 8.02 0 279.43 169.05 33641 +1914 315 9.41 3.41 7.76 0 275.02 166.78 33488 +1914 316 11.04 5.04 9.39 0 303.66 163 33337 +1914 317 6.47 0.47 4.82 0.61 229.19 123.68 33188 +1914 318 6.68 0.68 5.03 0 232.23 162.4 33042 +1914 319 4.46 -1.54 2.81 0 201.78 162.28 32899 +1914 320 8.06 2.06 6.41 0 253.08 157.73 32758 +1914 321 10.11 4.11 8.46 0 287.02 153.84 32620 +1914 322 12.12 6.12 10.47 0 324.02 150.05 32486 +1914 323 12.45 6.45 10.8 0.31 330.46 111.1 32354 +1914 324 8.95 2.95 7.3 0 267.37 149.43 32225 +1914 325 8.89 2.89 7.24 0.06 266.38 110.83 32100 +1914 326 7.85 1.85 6.2 0.06 249.81 110.38 31977 +1914 327 1.01 -4.99 -0.64 0 161.28 149.62 31858 +1914 328 5.36 -0.64 3.71 0 213.68 145.14 31743 +1914 329 5.63 -0.37 3.98 0 217.37 143.47 31631 +1914 330 7.31 1.31 5.66 0 241.56 140.86 31522 +1914 331 8.09 2.09 6.44 0 253.55 138.96 31417 +1914 332 4.12 -1.88 2.47 0.04 197.43 105 31316 +1914 333 3.41 -2.59 1.76 0.02 188.62 104.48 31218 +1914 334 2.44 -3.56 0.79 0 177.12 138.73 31125 +1914 335 2.27 -3.73 0.62 0 175.17 137.63 31035 +1914 336 3.98 -2.02 2.33 0 195.67 135.63 30949 +1914 337 4.52 -1.48 2.87 0 202.55 133.65 30867 +1914 338 9.92 3.92 8.27 0.1 283.72 96.7 30790 +1914 339 13.05 7.05 11.4 0 342.47 125.34 30716 +1914 340 10.89 4.89 9.24 0 300.92 126.64 30647 +1914 341 8 2 6.35 0 252.14 128.02 30582 +1914 342 8.81 2.81 7.16 0 265.08 126.67 30521 +1914 343 3.84 -2.16 2.19 0 193.91 129.06 30465 +1914 344 7.91 1.91 6.26 0 250.74 125.39 30413 +1914 345 8.12 2.12 6.47 0 254.02 124.82 30366 +1914 346 9.32 3.32 7.67 0.03 273.51 92.54 30323 +1914 347 10.34 4.34 8.69 0.17 291.06 91.49 30284 +1914 348 9.63 3.63 7.98 0.31 278.74 91.66 30251 +1914 349 8.31 2.31 6.66 0.85 257.03 92.12 30221 +1914 350 6.06 0.06 4.41 1.88 223.35 93 30197 +1914 351 2.04 -3.96 0.39 0.88 172.56 94.48 30177 +1914 352 0.47 -5.53 -1.18 1.52 155.63 94.94 30162 +1914 353 1.77 -4.23 0.12 0.22 169.54 94.46 30151 +1914 354 3.02 -2.98 1.37 0 183.92 125.3 30145 +1914 355 8.36 2.36 6.71 0.3 257.82 91.55 30144 +1914 356 8.07 2.07 6.42 0.04 253.24 91.72 30147 +1914 357 5.56 -0.44 3.91 0.16 216.41 92.99 30156 +1914 358 3.13 -2.87 1.48 0 185.23 125.42 30169 +1914 359 1.36 -4.64 -0.29 0 165.04 126.39 30186 +1914 360 0.41 -5.59 -1.24 0 155.01 127.18 30208 +1914 361 -2.97 -8.97 -4.62 0.01 123.46 140.3 30235 +1914 362 -0.39 -6.39 -2.04 0.24 146.97 140.62 30267 +1914 363 2.51 -3.49 0.86 0 177.93 171.59 30303 +1914 364 6.04 0.04 4.39 0.07 223.07 94.5 30343 +1914 365 8.49 2.49 6.84 0 259.9 124.9 30388 +1915 1 8.05 2.05 6.4 1.13 252.93 94.57 30438 +1915 2 5.5 -0.5 3.85 0.92 215.58 96.38 30492 +1915 3 3.82 -2.18 2.17 2.63 193.66 97.82 30551 +1915 4 -2.08 -8.08 -3.73 0.73 131.17 145.93 30614 +1915 5 2.38 -3.62 0.73 0.22 176.43 144.56 30681 +1915 6 8.19 2.19 6.54 0.09 255.13 141.36 30752 +1915 7 8.38 2.38 6.73 1.28 258.14 98.02 30828 +1915 8 11.59 5.59 9.94 0.28 313.89 97.12 30907 +1915 9 6.09 0.09 4.44 0 223.77 135.03 30991 +1915 10 2.92 -3.08 1.27 0.02 182.73 103.66 31079 +1915 11 4.47 -1.53 2.82 0.49 201.91 103.74 31171 +1915 12 5.15 -0.85 3.5 0 210.85 138.91 31266 +1915 13 6.69 0.69 5.04 0.1 232.37 104.63 31366 +1915 14 6.89 0.89 5.24 0 235.3 140.82 31469 +1915 15 6.14 0.14 4.49 0 224.48 142.78 31575 +1915 16 7.86 1.86 6.21 0 249.96 142.8 31686 +1915 17 7.66 1.66 6.01 0.02 246.88 108.47 31800 +1915 18 6.21 0.21 4.56 0 225.47 147.56 31917 +1915 19 4.64 -1.36 2.99 0 204.11 150.54 32038 +1915 20 3.7 -2.3 2.05 0 192.17 152.71 32161 +1915 21 5.98 -0.02 4.33 0.17 222.23 114.91 32289 +1915 22 5.68 -0.32 4.03 0 218.05 155.17 32419 +1915 23 2.51 -3.49 0.86 0.12 177.93 119.21 32552 +1915 24 1.99 -4.01 0.34 0.14 172 120.99 32688 +1915 25 0.55 -5.45 -1.1 0 156.45 163.98 32827 +1915 26 -0.82 -6.82 -2.47 0 142.8 166.6 32969 +1915 27 -1.63 -7.63 -3.28 0 135.23 169.02 33114 +1915 28 1.73 -4.27 0.08 0.03 169.1 127.16 33261 +1915 29 1.05 -4.95 -0.6 1.29 161.71 129.24 33411 +1915 30 -2.13 -8.13 -3.78 0 130.73 176.16 33564 +1915 31 -5.46 -11.46 -7.11 0 103.93 179.89 33718 +1915 32 -2.5 -8.5 -4.15 0 127.48 180.87 33875 +1915 33 0.63 -5.37 -1.02 0 157.28 181.98 34035 +1915 34 -0.99 -6.99 -2.64 0 141.19 185.06 34196 +1915 35 2.33 -3.67 0.68 0 175.86 185.36 34360 +1915 36 3.31 -2.69 1.66 0 187.4 187.25 34526 +1915 37 4.81 -1.19 3.16 0 206.34 188.61 34694 +1915 38 5.62 -0.38 3.97 0.45 217.23 143.03 34863 +1915 39 4.14 -1.86 2.49 0 197.68 194.45 35035 +1915 40 1.99 -4.01 0.34 0 172 198.56 35208 +1915 41 7.44 1.44 5.79 0 243.52 196.94 35383 +1915 42 7.42 1.42 5.77 0 243.22 199.5 35560 +1915 43 6.18 0.18 4.53 0 225.05 203.3 35738 +1915 44 6.58 0.58 4.93 0.86 230.78 154.13 35918 +1915 45 2.77 -3.23 1.12 0 180.96 211.18 36099 +1915 46 3.2 -2.8 1.55 0.94 186.07 160.18 36282 +1915 47 3.99 -2.01 2.34 0.08 195.79 161.85 36466 +1915 48 5.83 -0.17 4.18 0 220.13 217.07 36652 +1915 49 4.76 -1.24 3.11 0.11 205.68 165.58 36838 +1915 50 1.93 -4.07 0.28 0 171.33 225.63 37026 +1915 51 4.2 -1.8 2.55 0 198.45 226.89 37215 +1915 52 4.85 -1.15 3.2 0.52 206.86 171.88 37405 +1915 53 5.46 -0.54 3.81 0 215.04 231.59 37596 +1915 54 4.1 -1.9 2.45 0 197.18 235.54 37788 +1915 55 5.38 -0.62 3.73 0 213.95 237.42 37981 +1915 56 6.46 0.46 4.81 0.05 229.04 179.31 38175 +1915 57 7.89 1.89 6.24 0 250.43 240.45 38370 +1915 58 7.78 1.78 6.13 0.29 248.73 182.61 38565 +1915 59 4.13 -1.87 2.48 0 197.56 249.8 38761 +1915 60 4.82 -1.18 3.17 0 206.47 252.07 38958 +1915 61 8.47 2.47 6.82 0 259.58 251.17 39156 +1915 62 7.85 1.85 6.2 0 249.81 254.67 39355 +1915 63 8.14 2.14 6.49 0 254.34 257.33 39553 +1915 64 8.24 2.24 6.59 0 255.92 260.1 39753 +1915 65 8.68 2.68 7.03 0 262.96 262.44 39953 +1915 66 5.5 -0.5 3.85 0.02 215.58 201.56 40154 +1915 67 4.75 -1.25 3.1 0 205.55 272.42 40355 +1915 68 4.53 -1.47 2.88 0 202.68 275.53 40556 +1915 69 2.01 -3.99 0.36 0 172.22 280.44 40758 +1915 70 5.12 -0.88 3.47 0.37 210.45 210.34 40960 +1915 71 6.1 0.1 4.45 0.01 223.91 211.75 41163 +1915 72 4.95 -1.05 3.3 1.77 208.18 214.8 41366 +1915 73 5.99 -0.01 4.34 0 222.37 287.98 41569 +1915 74 7.54 1.54 5.89 0.03 245.04 216.69 41772 +1915 75 7.57 1.57 5.92 0 245.5 291.61 41976 +1915 76 10.64 4.64 8.99 0 296.41 290.02 42179 +1915 77 11.87 5.87 10.22 0 319.2 290.64 42383 +1915 78 9.02 3.02 7.37 0 268.52 297.61 42587 +1915 79 11.49 5.49 9.84 0 312.01 296.59 42791 +1915 80 7.86 1.86 6.21 0 249.96 304.43 42996 +1915 81 9.8 3.8 8.15 0 281.65 304.3 43200 +1915 82 9.7 3.7 8.05 0 279.94 307.09 43404 +1915 83 8.33 2.33 6.68 0 257.34 311.54 43608 +1915 84 9.72 3.72 8.07 0 280.28 312.08 43812 +1915 85 4.4 -1.6 2.75 0.08 201 241.07 44016 +1915 86 5.84 -0.16 4.19 0 220.27 322.23 44220 +1915 87 4.17 -1.83 2.52 0 198.07 326.69 44424 +1915 88 0.26 -5.74 -1.39 0 153.47 332.81 44627 +1915 89 -5.64 -11.64 -7.29 0.06 102.63 283.99 44831 +1915 90 -2.06 -8.06 -3.71 0.22 131.35 284.45 45034 +1915 91 7.15 1.15 5.5 0 239.16 332.48 45237 +1915 92 8.39 2.39 6.74 0.03 258.3 249.76 45439 +1915 93 14.26 8.26 12.61 0.42 367.81 243.68 45642 +1915 94 13.94 7.94 12.29 0 360.96 327.7 45843 +1915 95 13.22 7.22 11.57 0.38 345.94 248.45 46045 +1915 96 12.71 6.71 11.06 0 335.62 334.36 46246 +1915 97 12.67 6.67 11.02 0 334.82 336.48 46446 +1915 98 15.86 9.86 14.21 0 403.78 331.58 46647 +1915 99 11.89 5.89 10.24 0 319.59 341.92 46846 +1915 100 9.32 3.32 7.67 0 273.51 348.31 47045 +1915 101 7.06 1.06 5.41 0.01 237.82 265.23 47243 +1915 102 6.78 0.78 5.13 0.08 233.69 266.97 47441 +1915 103 6.58 0.58 4.93 0 230.78 358.11 47638 +1915 104 11.15 5.15 9.5 0 305.68 352.73 47834 +1915 105 12.05 6.05 10.4 0 322.66 352.84 48030 +1915 106 13.85 7.85 12.2 0 359.05 350.8 48225 +1915 107 10.4 4.4 8.75 0 292.12 359.21 48419 +1915 108 14.08 8.08 12.43 0 363.94 353.69 48612 +1915 109 16.86 10.86 15.21 0 427.74 348.6 48804 +1915 110 11.25 5.25 9.6 0 307.53 362.47 48995 +1915 111 12.19 6.19 10.54 0.07 325.37 271.66 49185 +1915 112 7.67 1.67 6.02 0.56 247.03 278.7 49374 +1915 113 7.02 1.02 5.37 0 237.22 373.94 49561 +1915 114 7.63 1.63 5.98 0.08 246.42 280.92 49748 +1915 115 12.77 6.77 11.12 1.69 336.82 275.12 49933 +1915 116 16.04 10.04 14.39 1.53 408 270.38 50117 +1915 117 17.67 11.67 16.02 0 448.04 357.44 50300 +1915 118 21.98 15.98 20.33 0 570.35 344.98 50481 +1915 119 20.41 14.41 18.76 0 522.87 351.53 50661 +1915 120 17.43 11.43 15.78 0.22 441.94 271.29 50840 +1915 121 23.54 17.54 21.89 0.88 621.1 256.8 51016 +1915 122 18.06 12.06 16.41 0.12 458.09 271.66 51191 +1915 123 22.97 16.97 21.32 0.41 602.13 260.04 51365 +1915 124 24.04 18.04 22.39 0.04 638.16 257.63 51536 +1915 125 21.32 15.32 19.67 0 549.96 354.77 51706 +1915 126 21.74 15.74 20.09 0.84 562.86 265.67 51874 +1915 127 18.26 12.26 16.61 0.35 463.33 274.88 52039 +1915 128 19.12 13.12 17.47 0 486.41 364.87 52203 +1915 129 19.61 13.61 17.96 0.2 500 273.11 52365 +1915 130 18.29 12.29 16.64 0 464.12 369.02 52524 +1915 131 17.2 11.2 15.55 0 436.16 372.96 52681 +1915 132 16.35 10.35 14.7 0 415.37 376.11 52836 +1915 133 18.68 12.68 17.03 0 474.48 370.12 52989 +1915 134 20.14 14.14 18.49 0.31 515.05 274.6 53138 +1915 135 21.27 15.27 19.62 0.33 548.44 272.19 53286 +1915 136 20.93 14.93 19.28 0.16 538.21 273.55 53430 +1915 137 20.57 14.57 18.92 0 527.55 366.67 53572 +1915 138 22.25 16.25 20.6 0 578.87 361.19 53711 +1915 139 17.93 11.93 16.28 0.02 454.72 282.29 53848 +1915 140 16.42 10.42 14.77 0.64 417.05 285.86 53981 +1915 141 16.68 10.68 15.03 0 423.34 380.88 54111 +1915 142 16.76 10.76 15.11 0 425.29 381.16 54238 +1915 143 12.97 6.97 11.32 0.05 340.85 293.34 54362 +1915 144 14.36 8.36 12.71 0 369.98 388.39 54483 +1915 145 13.89 7.89 12.24 0.03 359.9 292.49 54600 +1915 146 15.38 9.38 13.73 0.14 392.69 290.03 54714 +1915 147 11.14 5.14 9.49 1.03 305.5 297.61 54824 +1915 148 13.48 7.48 11.83 0.07 351.3 294.15 54931 +1915 149 11.89 5.89 10.24 0.07 319.59 297 55034 +1915 150 15.7 9.7 14.05 0 400.05 387.4 55134 +1915 151 17.63 11.63 15.98 0 447.01 382.43 55229 +1915 152 21.92 15.92 20.27 0.2 568.47 276.17 55321 +1915 153 25.4 19.4 23.75 0.06 686.58 265.52 55409 +1915 154 26.32 20.32 24.67 0.71 721.06 262.52 55492 +1915 155 28.82 22.82 27.17 0.34 822.25 253.03 55572 +1915 156 27.32 21.32 25.67 0.68 760.19 259.19 55648 +1915 157 22.27 16.27 20.62 0.16 579.51 276.08 55719 +1915 158 14.69 8.69 13.04 0.01 377.2 293.95 55786 +1915 159 15.86 9.86 14.21 0.42 403.78 291.88 55849 +1915 160 18.34 12.34 16.69 0 465.43 382.25 55908 +1915 161 19.8 13.8 18.15 0.23 505.35 283.23 55962 +1915 162 23.36 17.36 21.71 0.01 615.06 273.37 56011 +1915 163 25.22 19.22 23.57 0.38 679.99 267.52 56056 +1915 164 22.04 16.04 20.39 0.23 572.24 277.47 56097 +1915 165 22.04 16.04 20.39 0.18 572.24 277.54 56133 +1915 166 21.86 15.86 20.21 0.41 566.6 278.11 56165 +1915 167 21.71 15.71 20.06 0.19 561.93 278.49 56192 +1915 168 18.74 12.74 17.09 0 476.09 381.6 56214 +1915 169 15.58 9.58 13.93 0 397.27 390.71 56231 +1915 170 19.57 13.57 17.92 1.19 498.88 284.2 56244 +1915 171 19.99 13.99 18.34 0 510.75 377.58 56252 +1915 172 21.67 15.67 20.02 0 560.7 371.6 56256 +1915 173 23.81 17.81 22.16 0.62 630.27 272.34 56255 +1915 174 24.83 18.83 23.18 0 665.92 358.64 56249 +1915 175 23.72 17.72 22.07 2.83 627.2 272.54 56238 +1915 176 19.3 13.3 17.65 0 491.36 379.7 56223 +1915 177 21.39 15.39 19.74 0.31 552.1 279.28 56203 +1915 178 20.91 14.91 19.26 0.05 537.61 280.6 56179 +1915 179 19.48 13.48 17.83 0 496.36 378.92 56150 +1915 180 21.9 15.9 20.25 0.15 567.85 277.71 56116 +1915 181 26.24 20.24 24.59 0.05 718 263.79 56078 +1915 182 24.42 18.42 22.77 1.37 651.39 269.91 56035 +1915 183 21.72 15.72 20.07 0.4 562.24 277.92 55987 +1915 184 23.86 17.86 22.21 0 631.98 361.94 55935 +1915 185 24.46 18.46 22.81 0.16 652.79 269.48 55879 +1915 186 28.12 22.12 26.47 0 792.78 341.5 55818 +1915 187 24.66 18.66 23.01 0 659.86 358 55753 +1915 188 23.55 17.55 21.9 0.57 621.44 271.84 55684 +1915 189 24.03 18.03 22.38 1.06 637.82 270.21 55611 +1915 190 24.57 18.57 22.92 0.16 656.67 268.2 55533 +1915 191 23.08 17.08 21.43 0.35 605.76 272.68 55451 +1915 192 19.73 13.73 18.08 0.58 503.37 281.63 55366 +1915 193 21.65 15.65 20 0 560.08 368.51 55276 +1915 194 23.51 17.51 21.86 0.34 620.09 270.78 55182 +1915 195 20.45 14.45 18.8 0.36 524.04 279.22 55085 +1915 196 19.36 13.36 17.71 0.22 493.03 281.65 54984 +1915 197 19.67 13.67 18.02 0 501.68 374.06 54879 +1915 198 22.46 16.46 20.81 0.11 585.58 272.77 54770 +1915 199 21.67 15.67 20.02 0.01 560.7 274.74 54658 +1915 200 26.63 20.63 24.98 0.52 733 258.68 54542 +1915 201 27.36 21.36 25.71 0.19 761.79 255.65 54423 +1915 202 24.67 18.67 23.02 0.35 660.22 264.67 54301 +1915 203 24.68 18.68 23.03 1.65 660.57 264.28 54176 +1915 204 21.81 15.81 20.16 0.56 565.04 272.53 54047 +1915 205 19.56 13.56 17.91 1.65 498.6 278 53915 +1915 206 17.3 11.3 15.65 0.63 438.67 282.73 53780 +1915 207 16.42 10.42 14.77 0.08 417.05 284.06 53643 +1915 208 17.06 11.06 15.41 0.01 432.68 282.23 53502 +1915 209 15.75 9.75 14.1 0 401.21 379.18 53359 +1915 210 15.65 9.65 14 0 398.89 378.79 53213 +1915 211 19.56 13.56 17.91 0 498.6 366.72 53064 +1915 212 26.18 20.18 24.53 0 715.72 340.12 52913 +1915 213 21.69 15.69 20.04 0.46 561.31 268.41 52760 +1915 214 23.01 17.01 21.36 0.3 603.45 264.14 52604 +1915 215 20.67 14.67 19.02 0.13 530.49 270.04 52445 +1915 216 21.55 15.55 19.9 0.5 557 266.98 52285 +1915 217 15.45 9.45 13.8 0.08 394.29 280.11 52122 +1915 218 19.68 13.68 18.03 2.76 501.96 270.45 51958 +1915 219 21.16 15.16 19.51 3.32 545.11 265.96 51791 +1915 220 19.39 13.39 17.74 0.65 493.86 269.65 51622 +1915 221 15.5 9.5 13.85 0 395.43 369.45 51451 +1915 222 17.42 11.42 15.77 0 441.69 363.3 51279 +1915 223 17.16 11.16 15.51 0.03 435.17 272.15 51105 +1915 224 19.72 13.72 18.07 0.6 503.09 265.67 50929 +1915 225 17.33 11.33 15.68 0.29 439.42 270.12 50751 +1915 226 20.95 14.95 19.3 0.04 538.81 260.94 50572 +1915 227 22.78 16.78 21.13 0.36 595.92 255.11 50392 +1915 228 23.95 17.95 22.3 0.57 635.06 250.84 50210 +1915 229 25.09 19.09 23.44 0.75 675.27 246.44 50026 +1915 230 19.93 13.93 18.28 0.14 509.04 259.71 49842 +1915 231 22.54 16.54 20.89 0 588.15 335.95 49656 +1915 232 20.67 14.67 19.02 0.38 530.49 255.82 49469 +1915 233 21.29 15.29 19.64 0.45 549.05 253.22 49280 +1915 234 22.64 16.64 20.99 0.2 591.38 248.62 49091 +1915 235 22.29 16.29 20.64 0.13 580.15 248.47 48900 +1915 236 23.96 17.96 22.31 0.31 635.41 242.78 48709 +1915 237 20.81 14.81 19.16 0.43 534.64 249.98 48516 +1915 238 19.48 13.48 17.83 1.31 496.36 251.85 48323 +1915 239 18.64 12.64 16.99 1.1 473.41 252.56 48128 +1915 240 18.95 12.95 17.3 0.55 481.77 250.57 47933 +1915 241 24.08 18.08 22.43 0.11 639.54 236.44 47737 +1915 242 24.75 18.75 23.1 1 663.06 233.23 47541 +1915 243 19.59 13.59 17.94 0.17 499.44 245.19 47343 +1915 244 17.23 11.23 15.58 0 436.91 331.61 47145 +1915 245 17.33 11.33 15.68 0.03 439.42 247.12 46947 +1915 246 16.51 10.51 14.86 0.02 419.22 247.18 46747 +1915 247 17.88 11.88 16.23 0.16 453.43 243.17 46547 +1915 248 12.14 6.14 10.49 0.1 324.4 251.3 46347 +1915 249 13.66 7.66 12.01 0 355.05 329.98 46146 +1915 250 19.26 13.26 17.61 0.06 490.26 235.91 45945 +1915 251 19.44 13.44 17.79 0.17 495.25 233.96 45743 +1915 252 20.54 14.54 18.89 0.67 526.67 229.96 45541 +1915 253 17.57 11.57 15.92 0.01 445.49 234.51 45339 +1915 254 16.04 10.04 14.39 1.55 408 235.66 45136 +1915 255 16.49 10.49 14.84 0.4 418.74 233.17 44933 +1915 256 16.99 10.99 15.34 0 430.95 307.44 44730 +1915 257 19.81 13.81 18.16 0.27 505.63 223.5 44527 +1915 258 18.61 12.61 16.96 0.29 472.61 224.19 44323 +1915 259 19.51 13.51 17.86 0 497.2 294.13 44119 +1915 260 18.72 12.72 17.07 0 475.56 293.88 43915 +1915 261 17.95 11.95 16.3 1.21 455.24 220.05 43711 +1915 262 14.61 8.61 12.96 0.06 375.44 223.84 43507 +1915 263 15.94 9.94 14.29 0 405.65 293.21 43303 +1915 264 14.53 8.53 12.88 0 373.68 293.54 43099 +1915 265 14.74 8.74 13.09 0 378.3 290.73 42894 +1915 266 14.69 8.69 13.04 0.4 377.2 216.25 42690 +1915 267 15.2 9.2 13.55 0.48 388.59 213.48 42486 +1915 268 13.42 7.42 11.77 0 350.05 285.44 42282 +1915 269 13.64 7.64 11.99 0 354.63 282.51 42078 +1915 270 16.37 10.37 14.72 0 415.85 274.53 41875 +1915 271 14.33 8.33 12.68 0 369.33 275.96 41671 +1915 272 14.46 8.46 12.81 0 372.15 272.98 41468 +1915 273 18.94 12.94 17.29 0.29 481.5 195.74 41265 +1915 274 14.03 8.03 12.38 2.16 362.88 201.41 41062 +1915 275 10.35 4.35 8.7 0.96 291.24 203.71 40860 +1915 276 12.55 6.55 10.9 0.19 332.44 199.17 40658 +1915 277 11.57 5.57 9.92 0.74 313.51 198.3 40456 +1915 278 11.65 5.65 10 1.58 315.02 196.04 40255 +1915 279 9.36 3.36 7.71 0.82 274.18 196.29 40054 +1915 280 8.33 2.33 6.68 0.37 257.34 195.22 39854 +1915 281 8.28 2.28 6.63 0.53 256.55 193.18 39654 +1915 282 8.66 2.66 7.01 0.42 262.64 190.75 39455 +1915 283 7.81 1.81 6.16 0.21 249.19 189.33 39256 +1915 284 10.62 4.62 8.97 0.5 296.05 184.43 39058 +1915 285 11.31 5.31 9.66 0.68 308.64 181.73 38861 +1915 286 11.99 5.99 10.34 0.07 321.51 178.93 38664 +1915 287 10.1 4.1 8.45 0.02 286.85 178.62 38468 +1915 288 11.37 5.37 9.72 0 309.76 233.7 38273 +1915 289 16.42 10.42 14.77 0 417.05 223.11 38079 +1915 290 16.52 10.52 14.87 1.29 419.46 165.1 37885 +1915 291 20.69 14.69 19.04 1.51 531.08 156.75 37693 +1915 292 19.03 13.03 17.38 0.05 483.95 157.53 37501 +1915 293 16.49 10.49 14.84 0.13 418.74 159.19 37311 +1915 294 13.94 7.94 12.29 0 360.96 213.57 37121 +1915 295 15.28 9.28 13.63 0 390.41 208.69 36933 +1915 296 15.5 9.5 13.85 0.06 395.43 154.35 36745 +1915 297 14.93 8.93 13.28 0.08 382.52 153.02 36560 +1915 298 11.15 5.15 9.5 0 305.68 206.67 36375 +1915 299 7.29 1.29 5.64 0 241.26 208.06 36191 +1915 300 1.74 -4.26 0.09 0.19 169.21 157.32 36009 +1915 301 4.32 -1.68 2.67 1.62 199.98 154 35829 +1915 302 2.32 -3.68 0.67 1.27 175.74 153.08 35650 +1915 303 3.14 -2.86 1.49 0 185.35 200.9 35472 +1915 304 8.32 2.32 6.67 0 257.19 194.11 35296 +1915 305 2.29 -3.71 0.64 0 175.4 196.16 35122 +1915 306 0.85 -5.15 -0.8 0 159.59 194.74 34950 +1915 307 -2.06 -8.06 -3.71 0.64 131.35 185 34779 +1915 308 3.02 -2.98 1.37 0 183.92 227.73 34610 +1915 309 6.32 0.32 4.67 0 227.04 222.39 34444 +1915 310 9.42 3.42 7.77 0 275.19 178.14 34279 +1915 311 7.7 1.7 6.05 0 247.49 177.56 34116 +1915 312 7.56 1.56 5.91 0 245.35 175.04 33956 +1915 313 11 5 9.35 0 302.93 169.64 33797 +1915 314 9.58 3.58 7.93 0 277.89 169.14 33641 +1915 315 4.14 -1.86 2.49 0 197.68 170.99 33488 +1915 316 5.11 -0.89 3.46 0.36 210.31 126.09 33337 +1915 317 6.1 0.1 4.45 0.28 223.91 123.89 33188 +1915 318 3.18 -2.82 1.53 0.46 185.83 123.61 33042 +1915 319 0.23 -5.77 -1.42 0.08 153.17 123.55 32899 +1915 320 2.52 -3.48 0.87 0.14 178.05 121.2 32758 +1915 321 4.25 -1.75 2.6 0.01 199.08 118.81 32620 +1915 322 6.08 0.08 4.43 0.08 223.63 116.5 32486 +1915 323 4.5 -1.5 2.85 1.6 202.29 116.09 32354 +1915 324 4.76 -1.24 3.11 1.22 205.68 114.42 32225 +1915 325 4.14 -1.86 2.49 0 197.68 151.22 32100 +1915 326 6.39 0.39 4.74 0 228.04 148.26 31977 +1915 327 3.04 -2.96 1.39 0.05 184.16 111.4 31858 +1915 328 4.56 -1.44 2.91 0 203.07 145.65 31743 +1915 329 6.33 0.33 4.68 0 227.18 142.99 31631 +1915 330 10.85 4.85 9.2 0 300.2 137.95 31522 +1915 331 10.38 4.38 8.73 0.11 291.77 102.81 31417 +1915 332 7.94 1.94 6.29 0.36 251.21 103.09 31316 +1915 333 10.93 4.93 9.28 0.02 301.65 100.43 31218 +1915 334 7.2 1.2 5.55 0 239.91 135.82 31125 +1915 335 7.7 1.7 6.05 0 247.49 134.29 31035 +1915 336 10.58 4.58 8.93 0.01 295.33 98.21 30949 +1915 337 5.59 -0.41 3.94 0 216.82 133 30867 +1915 338 10.3 4.3 8.65 0 290.36 128.62 30790 +1915 339 10.61 4.61 8.96 0.04 295.87 95.69 30716 +1915 340 12.13 6.13 10.48 0.03 324.21 94.14 30647 +1915 341 10.67 4.67 9.02 0 296.95 125.93 30582 +1915 342 8.52 2.52 6.87 0.19 260.38 95.17 30521 +1915 343 9.3 3.3 7.65 0.28 273.17 94.11 30465 +1915 344 8.91 2.91 7.26 0 266.71 124.66 30413 +1915 345 6.36 0.36 4.71 1.14 227.61 94.51 30366 +1915 346 8.2 2.2 6.55 0.52 255.28 93.16 30323 +1915 347 9.58 3.58 7.93 0.29 277.89 91.95 30284 +1915 348 6.53 0.53 4.88 0.9 230.05 93.31 30251 +1915 349 4.32 -1.68 2.67 0.52 199.98 94.02 30221 +1915 350 3.09 -2.91 1.44 0.06 184.76 94.26 30197 +1915 351 2.52 -3.48 0.87 0.06 178.05 94.31 30177 +1915 352 2.78 -3.22 1.13 0 181.08 125.52 30162 +1915 353 5.71 -0.29 4.06 0 218.47 123.84 30151 +1915 354 -0.65 -6.65 -2.3 0 144.44 126.95 30145 +1915 355 2.36 -3.64 0.71 0 176.2 125.63 30144 +1915 356 7.25 1.25 5.6 0 240.65 122.86 30147 +1915 357 7.2 1.2 5.55 0 239.91 122.95 30156 +1915 358 9.64 3.64 7.99 0.08 278.91 90.96 30169 +1915 359 9.41 3.41 7.76 0 275.02 121.57 30186 +1915 360 11.72 5.72 10.07 0 316.34 120.02 30208 +1915 361 10.02 4.02 8.37 0 285.45 121.77 30235 +1915 362 14.21 8.21 12.56 0.1 366.73 88.78 30267 +1915 363 13.69 7.69 12.04 0 355.68 119.47 30303 +1915 364 13.37 7.37 11.72 0 349.02 120.17 30343 +1915 365 15.55 9.55 13.9 0 396.58 118.4 30388 +1916 1 10.93 4.93 9.28 0.62 301.65 92.88 30438 +1916 2 9.62 3.62 7.97 0.57 278.57 94.23 30492 +1916 3 9.46 3.46 7.81 0.15 275.86 95.02 30551 +1916 4 3.9 -2.1 2.25 0 194.66 131.3 30614 +1916 5 8.29 2.29 6.64 0 256.71 129.11 30681 +1916 6 8.33 2.33 6.68 0 257.34 129.96 30752 +1916 7 8.27 2.27 6.62 0 256.39 130.78 30828 +1916 8 7.8 1.8 6.15 0 249.03 132.6 30907 +1916 9 7.88 1.88 6.23 0 250.27 133.78 30991 +1916 10 10.4 4.4 8.75 0 292.12 133.05 31079 +1916 11 8.83 2.83 7.18 0.03 265.4 101.48 31171 +1916 12 10.23 4.23 8.58 0 289.12 135.14 31266 +1916 13 12.12 6.12 10.47 0 324.02 134.98 31366 +1916 14 8.36 2.36 6.71 0 257.82 139.73 31469 +1916 15 10.16 4.16 8.51 0 287.9 139.65 31575 +1916 16 10.73 4.73 9.08 0 298.03 140.39 31686 +1916 17 10 4 8.35 0.01 285.11 107.02 31800 +1916 18 9.44 3.44 7.79 0.06 275.52 108.79 31917 +1916 19 9.48 3.48 7.83 0.08 276.2 110.19 32038 +1916 20 3.12 -2.88 1.47 0.1 185.11 114.79 32161 +1916 21 3.17 -2.83 1.52 0.03 185.71 116.27 32289 +1916 22 0.36 -5.64 -1.29 0.73 154.5 118.73 32419 +1916 23 -2.34 -8.34 -3.99 0 128.88 161.31 32552 +1916 24 0.66 -5.34 -0.99 0.28 157.6 121.52 32688 +1916 25 -3.59 -9.59 -5.24 0 118.32 165.82 32827 +1916 26 4.81 -1.19 3.16 0 206.34 163.39 32969 +1916 27 5.39 -0.61 3.74 0 214.09 165 33114 +1916 28 0.69 -5.31 -0.96 0 157.91 170.12 33261 +1916 29 -1.8 -7.8 -3.45 0 133.69 173.74 33411 +1916 30 0.19 -5.81 -1.46 0.04 152.76 131.28 33564 +1916 31 -0.91 -6.91 -2.56 0.26 141.95 173.38 33718 +1916 32 0.6 -5.4 -1.05 0 156.97 218.98 33875 +1916 33 4.87 -1.13 3.22 0 207.13 218.15 34035 +1916 34 2.58 -3.42 0.93 0 178.74 183.05 34196 +1916 35 3.47 -2.53 1.82 0 189.35 184.62 34360 +1916 36 4.37 -1.63 2.72 0.09 200.62 139.88 34526 +1916 37 4.57 -1.43 2.92 0 203.2 188.79 34694 +1916 38 5.99 -0.01 4.34 0 222.37 190.41 34863 +1916 39 3.8 -2.2 2.15 0 193.42 194.7 35035 +1916 40 1.76 -4.24 0.11 0 169.43 198.71 35208 +1916 41 2.44 -3.56 0.79 0.69 177.12 150.67 35383 +1916 42 0.93 -5.07 -0.72 0 160.43 204.44 35560 +1916 43 4.79 -1.21 3.14 0.24 206.07 153.34 35738 +1916 44 2.68 -3.32 1.03 0 179.91 208.61 35918 +1916 45 4.46 -1.54 2.81 0.54 201.78 157.43 36099 +1916 46 5.14 -0.86 3.49 0.1 210.72 159.04 36282 +1916 47 5.63 -0.37 3.98 0.8 217.37 160.84 36466 +1916 48 5.98 -0.02 4.33 0.8 222.23 162.7 36652 +1916 49 10.26 4.26 8.61 1.2 289.65 161.43 36838 +1916 50 7.94 1.94 6.29 0 251.21 220.46 37026 +1916 51 9.47 3.47 7.82 0.02 276.03 166.29 37215 +1916 52 6.49 0.49 4.84 0.04 229.48 170.75 37405 +1916 53 5.02 -0.98 3.37 0 209.11 231.99 37596 +1916 54 3.58 -2.42 1.93 0.02 190.7 176.98 37788 +1916 55 0.39 -5.61 -1.26 0.24 154.8 181 37981 +1916 56 -0.03 -6.03 -1.68 0.14 150.54 218.19 38175 +1916 57 0.91 -5.09 -0.74 0 160.22 281.29 38370 +1916 58 5.42 -0.58 3.77 0 214.49 245.9 38565 +1916 59 8.96 2.96 7.31 0 267.53 244.82 38761 +1916 60 11.84 5.84 10.19 0 318.63 243.87 38958 +1916 61 11.51 5.51 9.86 0 312.38 247.22 39156 +1916 62 9.07 3.07 7.42 0 269.35 253.22 39355 +1916 63 11.34 5.34 9.69 0 309.2 253.16 39553 +1916 64 12.56 6.56 10.91 0 332.64 254.19 39753 +1916 65 12.53 6.53 10.88 0.1 332.04 192.8 39953 +1916 66 10.37 4.37 8.72 0.83 291.59 197.21 40154 +1916 67 9.44 3.44 7.79 0.83 275.52 200.3 40355 +1916 68 13.33 7.33 11.68 0.05 348.2 198.06 40556 +1916 69 13.66 7.66 12.01 0 355.05 266.08 40758 +1916 70 17.01 11.01 15.36 0 431.44 262.38 40960 +1916 71 17.66 11.66 16.01 0 447.78 263.75 41163 +1916 72 16.13 10.13 14.48 0.05 410.13 202.3 41366 +1916 73 17.4 11.4 15.75 1.59 441.18 202.18 41569 +1916 74 14.25 8.25 12.6 1.5 367.6 209 41772 +1916 75 16.88 10.88 15.23 0.76 428.23 206.98 41976 +1916 76 17.02 11.02 15.37 0.29 431.69 208.65 42179 +1916 77 16 10 14.35 0 407.06 282.91 42383 +1916 78 14.57 8.57 12.92 0.16 374.56 216.3 42587 +1916 79 13.83 7.83 12.18 0 358.63 292.49 42791 +1916 80 10.52 4.52 8.87 0.24 294.26 225.48 42996 +1916 81 8.29 2.29 6.64 0.65 256.71 229.83 43200 +1916 82 3.55 -2.45 1.9 0.7 190.33 236.01 43404 +1916 83 3.38 -2.62 1.73 0.05 188.25 238.03 43608 +1916 84 5.74 -0.26 4.09 0.98 218.88 238.04 43812 +1916 85 3.75 -2.25 2.1 0.2 192.79 241.59 44016 +1916 86 0.25 -5.75 -1.4 0 153.37 327.82 44220 +1916 87 5 -1 3.35 0 208.85 325.77 44424 +1916 88 6.44 0.44 4.79 0 228.76 326.43 44627 +1916 89 6.52 0.52 4.87 0.08 229.91 246.47 44831 +1916 90 7.93 1.93 6.28 0.57 251.05 246.85 45034 +1916 91 11.35 5.35 9.7 1.01 309.39 244.54 45237 +1916 92 8.73 2.73 7.08 0.16 263.77 249.38 45439 +1916 93 10.23 4.23 8.58 0.71 289.12 249.29 45642 +1916 94 11.8 5.8 10.15 0 317.87 331.84 45843 +1916 95 8.72 2.72 7.07 0.14 263.61 254.31 46045 +1916 96 10.38 4.38 8.73 0.14 291.77 253.92 46246 +1916 97 12.31 6.31 10.66 0 327.71 337.17 46446 +1916 98 10.77 4.77 9.12 0 298.75 341.92 46647 +1916 99 15.98 9.98 14.33 0 406.59 333.26 46846 +1916 100 15.72 9.72 14.07 0.11 400.51 251.84 47045 +1916 101 9.13 3.13 7.48 0.65 270.34 262.92 47243 +1916 102 8.92 2.92 7.27 0 266.88 352.82 47441 +1916 103 12.13 6.13 10.48 0 324.21 349.07 47638 +1916 104 13.63 7.63 11.98 0.2 354.42 260.89 47834 +1916 105 16.76 10.76 15.11 0 425.29 342.33 48030 +1916 106 18.53 12.53 16.88 0.47 470.47 254.36 48225 +1916 107 15.38 9.38 13.73 0 392.69 348.99 48419 +1916 108 14.81 8.81 13.16 0.17 379.85 264.03 48612 +1916 109 14.19 8.19 12.54 0.06 366.3 266.28 48804 +1916 110 15.31 9.31 13.66 0 391.09 353.86 48995 +1916 111 16.1 10.1 14.45 0.67 409.42 265.09 49185 +1916 112 12.74 6.74 11.09 2.65 336.22 271.97 49374 +1916 113 13.97 7.97 12.32 0 361.6 361.32 49561 +1916 114 12.65 6.65 11 0.03 334.42 274.23 49748 +1916 115 14.25 8.25 12.6 0 367.6 363.6 49933 +1916 116 15.32 9.32 13.67 0 391.32 362.29 50117 +1916 117 16.28 10.28 14.63 0 413.7 361.18 50300 +1916 118 13.7 7.7 12.05 2.31 355.89 276.51 50481 +1916 119 10.19 4.19 8.54 1.15 288.42 282.69 50661 +1916 120 12.12 6.12 10.47 1.01 324.02 280.81 50840 +1916 121 14.79 8.79 13.14 0 379.41 369.66 51016 +1916 122 17.8 11.8 16.15 0.36 451.37 272.22 51191 +1916 123 15.3 9.3 13.65 0 390.86 370.63 51365 +1916 124 16.98 10.98 15.33 0 430.7 367.33 51536 +1916 125 18.31 12.31 16.66 0 464.64 364.51 51706 +1916 126 20.07 14.07 18.42 0 513.04 359.98 51874 +1916 127 20.23 14.23 18.58 0 517.65 360.32 52039 +1916 128 19.07 13.07 17.42 0.25 485.04 273.77 52203 +1916 129 19.15 13.15 17.5 0.17 487.23 274.2 52365 +1916 130 22.92 16.92 21.27 0 600.49 353.18 52524 +1916 131 18.5 12.5 16.85 0 469.67 369.17 52681 +1916 132 18.04 12.04 16.39 0.41 457.57 278.52 52836 +1916 133 17.49 11.49 15.84 0.05 443.46 280.24 52989 +1916 134 17 11 15.35 0 431.19 375.74 53138 +1916 135 11.86 5.86 10.21 0.24 319.01 291.61 53286 +1916 136 12.98 6.98 11.33 0.05 341.05 290.31 53430 +1916 137 13.15 7.15 11.5 0 344.5 387.42 53572 +1916 138 17.29 11.29 15.64 0.07 438.42 283.17 53711 +1916 139 18.77 12.77 17.12 2.13 476.9 280.38 53848 +1916 140 20.18 14.18 18.53 0.03 516.2 277.3 53981 +1916 141 18.25 12.25 16.6 1.72 463.06 282.25 54111 +1916 142 17.39 11.39 15.74 0.05 440.93 284.53 54238 +1916 143 17.68 11.68 16.03 0 448.29 379.07 54362 +1916 144 17 11 15.35 0.14 431.19 286.12 54483 +1916 145 17.87 11.87 16.22 0.14 453.17 284.59 54600 +1916 146 20.05 14.05 18.4 0.41 512.47 279.69 54714 +1916 147 20.74 14.74 19.09 0 532.56 371.02 54824 +1916 148 25.76 19.76 24.11 0.7 699.9 263.3 54931 +1916 149 21.92 15.92 20.27 0.6 568.47 275.56 55034 +1916 150 21.55 15.55 19.9 0 557 369.12 55134 +1916 151 16.97 10.97 15.32 0 430.45 384.33 55229 +1916 152 20.52 14.52 18.87 0 526.08 373.29 55321 +1916 153 23.31 17.31 21.66 1.7 613.39 272.27 55409 +1916 154 22.14 16.14 20.49 0 575.39 367.94 55492 +1916 155 24.06 18.06 22.41 0 638.85 360.4 55572 +1916 156 19.92 13.92 18.27 0.08 508.76 282.3 55648 +1916 157 16.51 10.51 14.86 0 419.22 386.99 55719 +1916 158 18.19 12.19 16.54 0 461.49 382.29 55786 +1916 159 18.59 12.59 16.94 0.09 472.07 285.97 55849 +1916 160 15.29 9.29 13.64 0 390.64 390.85 55908 +1916 161 17.81 11.81 16.16 0.24 451.62 287.94 55962 +1916 162 17.78 11.78 16.13 0.06 450.85 288.06 56011 +1916 163 19.81 13.81 18.16 1 505.63 283.41 56056 +1916 164 22.95 16.95 21.3 0 601.48 366.41 56097 +1916 165 24.93 18.93 23.28 1.28 669.5 268.6 56133 +1916 166 18.08 12.08 16.43 0.75 458.62 287.71 56165 +1916 167 19.8 13.8 18.15 0.02 505.35 283.56 56192 +1916 168 18.39 12.39 16.74 0.97 466.76 287.02 56214 +1916 169 15.14 9.14 13.49 0.15 387.24 293.88 56231 +1916 170 18.66 12.66 17.01 0.34 473.94 286.4 56244 +1916 171 19.9 13.9 18.25 0.2 508.19 283.41 56252 +1916 172 18.39 12.39 16.74 0.54 466.76 287.06 56256 +1916 173 18.62 12.62 16.97 0.01 472.87 286.51 56255 +1916 174 17.17 11.17 15.52 0.6 435.41 289.71 56249 +1916 175 15.86 9.86 14.21 0 403.78 389.89 56238 +1916 176 21.01 15.01 19.36 0 540.6 373.85 56223 +1916 177 26.42 20.42 24.77 0.01 724.89 263.33 56203 +1916 178 24.88 18.88 23.23 0 667.71 358.28 56179 +1916 179 24.18 18.18 22.53 0 643.01 361.23 56150 +1916 180 23.94 17.94 22.29 0.22 634.72 271.6 56116 +1916 181 22.53 16.53 20.88 0 587.83 367.79 56078 +1916 182 27.27 21.27 25.62 0.25 758.19 259.89 56035 +1916 183 23.14 17.14 21.49 0 607.74 365.06 55987 +1916 184 22.13 16.13 20.48 0 575.07 368.87 55935 +1916 185 20.83 14.83 19.18 0 535.23 373.56 55879 +1916 186 27.03 21.03 25.38 0 748.66 347.09 55818 +1916 187 22.19 16.19 20.54 0.26 576.97 276.09 55753 +1916 188 22.93 16.93 21.28 0 600.82 364.97 55684 +1916 189 23.93 17.93 22.28 0 634.38 360.7 55611 +1916 190 23.94 17.94 22.29 0.03 634.72 270.22 55533 +1916 191 22.09 16.09 20.44 1.24 573.81 275.57 55451 +1916 192 19.82 13.82 18.17 0.83 505.92 281.41 55366 +1916 193 20.36 14.36 18.71 0.01 521.41 279.83 55276 +1916 194 20.29 14.29 18.64 0.1 519.38 279.84 55182 +1916 195 20.55 14.55 18.9 0.12 526.96 278.96 55085 +1916 196 20.67 14.67 19.02 0 530.49 371.13 54984 +1916 197 22.21 16.21 20.56 0.37 577.6 273.8 54879 +1916 198 22.79 16.79 21.14 0 596.25 362.4 54770 +1916 199 22 16 20.35 0 570.98 365.09 54658 +1916 200 22.42 16.42 20.77 0.04 584.3 272.32 54542 +1916 201 22.89 16.89 21.24 1.16 599.51 270.61 54423 +1916 202 18.98 12.98 17.33 0.05 482.59 280.55 54301 +1916 203 19.18 13.18 17.53 0 488.06 372.92 54176 +1916 204 20.53 14.53 18.88 0 526.38 367.94 54047 +1916 205 21.79 15.79 20.14 0 564.42 362.94 53915 +1916 206 23.32 17.32 21.67 0 613.72 356.5 53780 +1916 207 27.58 21.58 25.93 0 770.65 336.64 53643 +1916 208 30.92 24.92 29.27 0.04 916.26 238.19 53502 +1916 209 27.26 21.26 25.61 0.05 757.79 252.76 53359 +1916 210 20.42 14.42 18.77 0.38 523.16 273.49 53213 +1916 211 19.31 13.31 17.66 0.95 491.64 275.64 53064 +1916 212 20.33 14.33 18.68 0.56 520.54 272.54 52913 +1916 213 18.8 12.8 17.15 0.01 477.71 275.66 52760 +1916 214 18.97 12.97 17.32 0.1 482.32 274.7 52604 +1916 215 20.45 14.45 18.8 0.28 524.04 270.6 52445 +1916 216 22.77 16.77 21.12 0 595.59 351.45 52285 +1916 217 23.03 17.03 21.38 0.19 604.11 262.18 52122 +1916 218 23.89 17.89 22.24 0 633 345.37 51958 +1916 219 25.85 19.85 24.2 0.08 703.26 251.97 51791 +1916 220 22.85 16.85 21.2 0 598.2 347.53 51622 +1916 221 23.15 17.15 21.5 0.57 608.07 259.05 51451 +1916 222 20.43 14.43 18.78 0.02 523.45 265.6 51279 +1916 223 18.14 12.14 16.49 0 460.18 360.1 51105 +1916 224 16.09 10.09 14.44 0 409.18 364.62 50929 +1916 225 18.99 12.99 17.34 0.07 482.86 266.51 50751 +1916 226 20.91 14.91 19.26 0 537.61 348.06 50572 +1916 227 21.05 15.05 19.4 0 541.8 346.31 50392 +1916 228 23.23 17.23 21.58 0 610.73 337.26 50210 +1916 229 24.96 18.96 23.31 0 670.58 329.13 50026 +1916 230 21.98 15.98 20.33 0 570.35 339.41 49842 +1916 231 21.71 15.71 20.06 0 561.93 338.91 49656 +1916 232 21.53 15.53 19.88 0 556.38 338.2 49469 +1916 233 21.31 15.31 19.66 0 549.66 337.55 49280 +1916 234 22.96 16.96 21.31 0 601.8 330.32 49091 +1916 235 25.66 19.66 24.01 0 696.18 318.13 48900 +1916 236 23.33 17.33 21.68 0.13 614.06 244.58 48709 +1916 237 23.06 17.06 21.41 0 605.1 325.52 48516 +1916 238 23.81 17.81 22.16 0 630.27 321.08 48323 +1916 239 24.41 18.41 22.76 0.18 651.04 237.98 48128 +1916 240 25.19 19.19 23.54 0.02 678.9 234.37 47933 +1916 241 22.4 16.4 20.75 1.24 583.66 241.06 47737 +1916 242 22.12 16.12 20.47 0.48 574.76 240.51 47541 +1916 243 17.65 11.65 16 1.02 447.52 249.26 47343 +1916 244 12.16 6.16 10.51 0.92 324.79 257.16 47145 +1916 245 12.4 6.4 10.75 0.02 329.48 255.38 46947 +1916 246 12.35 6.35 10.7 0.32 328.5 253.94 46747 +1916 247 11.79 5.79 10.14 0.48 317.68 253.29 46547 +1916 248 12.06 6.06 10.41 0 322.85 335.21 46347 +1916 249 12.9 6.9 11.25 1.89 339.43 248.62 46146 +1916 250 14.26 8.26 12.61 0.03 367.81 245.06 45945 +1916 251 13.46 7.46 11.81 0 350.88 326.23 45743 +1916 252 13.09 7.09 11.44 0 343.28 324.74 45541 +1916 253 13.05 7.05 11.4 0.73 342.47 241.99 45339 +1916 254 11.88 5.88 10.23 0.48 319.39 241.97 45136 +1916 255 17.2 11.2 15.55 0.09 436.16 231.9 44933 +1916 256 21.23 15.23 19.58 0.45 547.23 221.97 44730 +1916 257 20.49 14.49 18.84 0 525.2 296.06 44527 +1916 258 24.48 18.48 22.83 0.08 653.5 210.62 44323 +1916 259 24.01 18.01 22.36 0 637.13 280.2 44119 +1916 260 25.34 19.34 23.69 0.18 684.38 204.86 43915 +1916 261 23.99 17.99 22.34 0.17 636.44 206.77 43711 +1916 262 24.55 18.55 22.9 0.04 655.97 203.62 43507 +1916 263 19.87 13.87 18.22 0.02 507.33 212.76 43303 +1916 264 18.58 12.58 16.93 1.77 471.8 213.39 43099 +1916 265 18.53 12.53 16.88 0 470.47 282.31 42894 +1916 266 21.52 15.52 19.87 0.08 556.07 203.89 42690 +1916 267 18.17 12.17 16.52 0.09 460.97 208.58 42486 +1916 268 16.4 10.4 14.75 0.18 416.57 209.69 42282 +1916 269 17.51 11.51 15.86 1.08 443.96 205.98 42078 +1916 270 16.16 10.16 14.51 0.93 410.84 206.23 41875 +1916 271 14.81 8.81 13.16 2.19 379.85 206.29 41671 +1916 272 16.16 10.16 14.51 0 410.84 269.65 41468 +1916 273 17.58 11.58 15.93 0 445.74 264.12 41265 +1916 274 14.06 8.06 12.41 0 363.52 268.49 41062 +1916 275 13.87 7.87 12.22 0 359.47 266.05 40860 +1916 276 13.01 7.01 11.36 0 341.66 264.81 40658 +1916 277 9.64 3.64 7.99 0.24 278.91 200.35 40456 +1916 278 6.8 0.8 5.15 1.41 233.98 200.74 40255 +1916 279 7.97 1.97 6.32 0.02 251.67 197.58 40054 +1916 280 11.54 5.54 9.89 0 312.94 256.03 39854 +1916 281 10.1 4.1 8.45 0.78 286.85 191.47 39654 +1916 282 11.5 5.5 9.85 0.25 312.19 187.94 39455 +1916 283 13 7 11.35 0 341.45 245.5 39256 +1916 284 13.33 7.33 11.68 0.02 348.2 181.47 39058 +1916 285 13.43 7.43 11.78 0 350.26 239.17 38861 +1916 286 16.9 10.9 15.25 0 428.73 230.39 38664 +1916 287 12.12 6.12 10.47 0.2 324.02 176.58 38468 +1916 288 15.12 9.12 13.47 0 386.79 227.99 38273 +1916 289 11.46 5.46 9.81 0 311.44 230.93 38079 +1916 290 12.76 6.76 11.11 0 336.62 226.25 37885 +1916 291 15.26 9.26 13.61 0 389.95 219.68 37693 +1916 292 13.77 7.77 12.12 0 357.36 219.39 37501 +1916 293 14.27 8.27 12.62 0 368.03 215.93 37311 +1916 294 14.92 8.92 13.27 0.02 382.3 159.04 37121 +1916 295 13.34 7.34 11.69 0 348.4 211.65 36933 +1916 296 10.48 4.48 8.83 0 293.55 212.82 36745 +1916 297 12.84 6.84 11.19 0 338.22 207.08 36560 +1916 298 12.67 6.67 11.02 0 334.82 204.73 36375 +1916 299 11.43 5.43 9.78 0 310.88 203.55 36191 +1916 300 13.74 7.74 12.09 0 356.73 197.87 36009 +1916 301 19.49 13.49 17.84 0 496.64 185.84 35829 +1916 302 12.72 6.72 11.07 0.35 335.82 145.63 35650 +1916 303 15.49 9.49 13.84 0 395.2 187.75 35472 +1916 304 17.11 11.11 15.46 0 433.92 182.79 35296 +1916 305 11.58 5.58 9.93 0.15 313.7 140.9 35122 +1916 306 13.15 7.15 11.5 0.19 344.5 137.79 34950 +1916 307 8.08 2.08 6.43 0.83 253.4 140.1 34779 +1916 308 2.79 -3.21 1.14 0.09 181.2 141.24 34610 +1916 309 6.17 0.17 4.52 0 224.9 183.5 34444 +1916 310 8.25 2.25 6.6 0.29 256.08 134.44 34279 +1916 311 8.11 2.11 6.46 0 253.87 177.2 34116 +1916 312 12.78 6.78 11.13 0 337.02 169.73 33956 +1916 313 11.06 5.06 9.41 0.11 304.03 127.18 33797 +1916 314 10.08 4.08 8.43 0.85 286.5 126.49 33641 +1916 315 8.31 2.31 6.66 0.02 257.03 125.83 33488 +1916 316 9.31 3.31 7.66 0 273.34 164.7 33337 +1916 317 7.41 1.41 5.76 0.25 243.07 123.12 33188 +1916 318 8.69 2.69 7.04 0 263.12 160.75 33042 +1916 319 6.92 0.92 5.27 0 235.74 160.51 32899 +1916 320 9.87 3.87 8.22 0.18 282.86 117.11 32758 +1916 321 9.33 3.33 7.68 0.07 273.67 115.91 32620 +1916 322 10 4 8.35 0.69 285.11 114.1 32486 +1916 323 9.54 3.54 7.89 0.01 277.21 113.22 32354 +1916 324 9.81 3.81 8.16 0.01 281.82 111.51 32225 +1916 325 6.48 0.48 4.83 0 229.33 149.65 32100 +1916 326 7.74 1.74 6.09 0.1 248.11 110.44 31977 +1916 327 8.27 2.27 6.62 0 256.39 145.01 31858 +1916 328 7.3 1.3 5.65 0 241.41 143.79 31743 +1916 329 9.78 3.78 8.13 0 281.31 140.32 31631 +1916 330 9.27 3.27 7.62 0 272.67 139.33 31522 +1916 331 10.08 4.08 8.43 0 286.5 137.34 31417 +1916 332 12.17 6.17 10.52 0 324.99 133.8 31316 +1916 333 12.47 6.47 10.82 0 330.86 132.46 31218 +1916 334 11.49 5.49 9.84 0.04 312.01 99.25 31125 +1916 335 6.6 0.6 4.95 1.24 231.07 101.3 31035 +1916 336 10.82 4.82 9.17 0.44 299.65 98.05 30949 +1916 337 11.73 5.73 10.08 0.65 316.53 96.21 30867 +1916 338 11.13 5.13 9.48 0.24 305.31 95.93 30790 +1916 339 9.12 3.12 7.47 0 270.17 128.81 30716 +1916 340 10.63 4.63 8.98 0.27 296.23 95.15 30647 +1916 341 6.61 0.61 4.96 0.47 231.21 96.73 30582 +1916 342 10.73 4.73 9.08 0 298.03 125.13 30521 +1916 343 9.22 3.22 7.57 0.06 271.84 94.16 30465 +1916 344 7.61 1.61 5.96 0 246.11 125.6 30413 +1916 345 8.6 2.6 6.95 0.96 261.67 93.35 30366 +1916 346 7.64 1.64 5.99 0.58 246.57 93.46 30323 +1916 347 6.38 0.38 4.73 0 227.89 124.86 30284 +1916 348 6.62 0.62 4.97 0 231.36 124.36 30251 +1916 349 6.39 0.39 4.74 0 228.04 124.13 30221 +1916 350 5.41 -0.59 3.76 0 214.36 124.4 30197 +1916 351 10.52 4.52 8.87 0.07 294.26 90.44 30177 +1916 352 10.38 4.38 8.73 0.03 291.77 90.46 30162 +1916 353 7.41 1.41 5.76 0.5 243.07 92.07 30151 +1916 354 8.84 2.84 7.19 0 265.57 121.71 30145 +1916 355 8.76 2.76 7.11 0 264.26 121.77 30144 +1916 356 9.18 3.18 7.53 0.08 271.17 91.11 30147 +1916 357 8.59 2.59 6.94 0 261.51 121.98 30156 +1916 358 3.1 -2.9 1.45 0.26 184.88 94.08 30169 +1916 359 -0.14 -6.14 -1.79 0 149.44 127.04 30186 +1916 360 -0.69 -6.69 -2.34 0 144.05 127.63 30208 +1916 361 1.34 -4.66 -0.31 0 164.82 127.1 30235 +1916 362 -0.98 -6.98 -2.63 0.8 141.28 142.55 30267 +1916 363 1.04 -4.96 -0.61 0 161.6 174.23 30303 +1916 364 2.58 -3.42 0.93 0 178.74 173.49 30343 +1916 365 8.84 2.84 7.19 0 265.57 168.95 30388 +1917 1 2.35 -3.65 0.7 0.04 176.09 141.07 30438 +1917 2 -1.13 -7.13 -2.78 0.02 139.86 142.76 30492 +1917 3 3.95 -2.05 2.3 0 195.29 173.66 30551 +1917 4 8.07 2.07 6.42 0.01 253.24 96.48 30614 +1917 5 10.96 4.96 9.31 0 302.2 126.96 30681 +1917 6 8.38 2.38 6.73 0.2 258.14 97.44 30752 +1917 7 5.32 -0.68 3.67 0 213.14 132.79 30828 +1917 8 7.05 1.05 5.4 0.07 237.67 99.85 30907 +1917 9 2.62 -3.38 0.97 1.34 179.21 102.8 30991 +1917 10 1.39 -4.61 -0.26 0.08 165.37 104.24 31079 +1917 11 0.35 -5.65 -1.3 0.03 154.39 105.36 31171 +1917 12 2.57 -3.43 0.92 0.12 178.63 105.3 31266 +1917 13 -0.07 -6.07 -1.72 0 150.14 143.32 31366 +1917 14 0.92 -5.08 -0.73 0 160.33 144.35 31469 +1917 15 -1.71 -7.71 -3.36 0 134.5 146.97 31575 +1917 16 -2.68 -8.68 -4.33 0 125.93 148.66 31686 +1917 17 -2.39 -8.39 -4.04 0 128.44 150.25 31800 +1917 18 0.89 -5.11 -0.76 0 160.01 150.71 31917 +1917 19 2.08 -3.92 0.43 0 173.01 152.04 32038 +1917 20 1.28 -4.72 -0.37 0 164.17 154.06 32161 +1917 21 -2.59 -8.59 -4.24 0 126.7 157.84 32289 +1917 22 -1.05 -7.05 -2.7 0 140.62 158.97 32419 +1917 23 -3.57 -9.57 -5.22 0 118.49 161.8 32552 +1917 24 -0.02 -6.02 -1.67 1 150.64 165.09 32688 +1917 25 -3.82 -9.82 -5.47 3.11 116.47 176.66 32827 +1917 26 -0.06 -6.06 -1.71 0 150.24 218.24 32969 +1917 27 0.54 -5.46 -1.11 0.04 156.35 177.69 33114 +1917 28 2.46 -3.54 0.81 0.26 177.35 178.03 33261 +1917 29 5.75 -0.25 4.1 0.04 219.02 177.24 33411 +1917 30 4.3 -1.7 2.65 0.1 199.72 178.95 33564 +1917 31 6.62 0.62 4.97 0 231.36 221.72 33718 +1917 32 1.78 -4.22 0.13 0 169.65 226.74 33875 +1917 33 0.08 -5.92 -1.57 0 151.65 230.1 34035 +1917 34 -3.89 -9.89 -5.54 0.25 115.9 188.08 34196 +1917 35 -4.47 -10.47 -6.12 0 111.35 236.86 34360 +1917 36 -6.84 -12.84 -8.49 0 94.31 240.05 34526 +1917 37 -7.88 -13.88 -9.53 0 87.58 242.64 34694 +1917 38 -4.8 -10.8 -6.45 0.2 108.83 195.48 34863 +1917 39 -8.15 -14.15 -9.8 0 85.9 248.27 35035 +1917 40 -4.59 -10.59 -6.24 0 110.43 249.43 35208 +1917 41 -2.26 -8.26 -3.91 0 129.58 250.82 35383 +1917 42 1.49 -4.51 -0.16 0 166.46 250.91 35560 +1917 43 0.08 -5.92 -1.57 0 151.65 254.26 35738 +1917 44 -0.81 -6.81 -2.46 0 142.9 257.13 35918 +1917 45 2.09 -3.91 0.44 0 173.13 257.53 36099 +1917 46 3.94 -2.06 2.29 0 195.16 258.22 36282 +1917 47 2.6 -3.4 0.95 0 178.98 261.54 36466 +1917 48 3.12 -2.88 1.47 0 185.11 263.41 36652 +1917 49 2.99 -3.01 1.34 0 183.56 265.75 36838 +1917 50 0.38 -5.62 -1.27 0 154.7 269.98 37026 +1917 51 -3.86 -9.86 -5.51 0 116.14 275.11 37215 +1917 52 -2.24 -8.24 -3.89 0 129.76 276.95 37405 +1917 53 -3.8 -9.8 -5.45 0 116.63 280.54 37596 +1917 54 -0.89 -6.89 -2.54 0 142.14 281.55 37788 +1917 55 -0.57 -6.57 -2.22 0 145.22 284.18 37981 +1917 56 -0.07 -6.07 -1.72 0 150.14 286.38 38175 +1917 57 -1.97 -7.97 -3.62 0 132.16 290.26 38370 +1917 58 -2.49 -8.49 -4.14 0.54 127.57 231.73 38565 +1917 59 -4.35 -10.35 -6 0.11 112.28 234.6 38761 +1917 60 2.17 -3.83 0.52 0.35 174.03 233.29 38958 +1917 61 4.22 -1.78 2.57 0.27 198.7 233.57 39156 +1917 62 6.86 0.86 5.21 0 234.86 296.75 39355 +1917 63 8.96 2.96 7.31 0 267.53 296.2 39553 +1917 64 10.1 4.1 8.45 0.06 286.85 231.94 39753 +1917 65 9.14 3.14 7.49 0 270.51 299.38 39953 +1917 66 10.37 4.37 8.72 0.46 291.59 233.49 40154 +1917 67 6.41 0.41 4.76 0.25 228.32 238.5 40355 +1917 68 6.98 0.98 5.33 0 236.63 307.55 40556 +1917 69 7.17 1.17 5.52 0.02 239.46 240.23 40758 +1917 70 7.16 1.16 5.51 0 239.31 311.06 40960 +1917 71 3.74 -2.26 2.09 0 192.67 317.06 41163 +1917 72 4.46 -1.54 2.81 0.03 201.78 215.17 41366 +1917 73 9.22 3.22 7.57 0.06 271.84 213 41569 +1917 74 7.37 1.37 5.72 0.22 242.46 216.85 41772 +1917 75 3.5 -2.5 1.85 1.57 189.71 222.05 41976 +1917 76 4.25 -1.75 2.6 0.43 199.08 223.5 42179 +1917 77 -1.4 -7.4 -3.05 0.07 137.34 260.37 42383 +1917 78 -1.77 -7.77 -3.42 0.79 133.96 264.24 42587 +1917 79 2.74 -3.26 1.09 0.67 180.61 263.19 42791 +1917 80 2.92 -3.08 1.27 0 182.73 342.07 42996 +1917 81 2.18 -3.82 0.53 0.11 174.15 266.7 43200 +1917 82 1.94 -4.06 0.29 1.95 171.44 268.56 43404 +1917 83 5.33 -0.67 3.68 0.05 213.27 267.24 43608 +1917 84 6.19 0.19 4.54 0.22 225.19 237.64 43812 +1917 85 6.08 0.08 4.43 0 223.63 319.51 44016 +1917 86 6.57 0.57 4.92 0.02 230.63 241 44220 +1917 87 6.87 0.87 5.22 0.27 235.01 242.63 44424 +1917 88 9.05 3.05 7.4 0 269.02 322.86 44627 +1917 89 7.85 1.85 6.2 0 249.81 326.87 44831 +1917 90 8.25 2.25 6.6 0.03 256.08 246.51 45034 +1917 91 11.19 5.19 9.54 0.13 306.42 244.75 45237 +1917 92 9.08 3.08 7.43 0 269.51 331.99 45439 +1917 93 10.58 4.58 8.93 0.29 295.33 248.86 45642 +1917 94 9.06 3.06 7.41 0.63 269.18 252.3 45843 +1917 95 7.93 1.93 6.28 0.38 251.05 255.18 46045 +1917 96 13.82 7.82 12.17 0 358.42 332.14 46246 +1917 97 14.35 8.35 12.7 0 369.76 333.05 46446 +1917 98 13.78 7.78 12.13 2.06 357.57 252.14 46647 +1917 99 10.22 4.22 8.57 0.45 288.95 258.66 46846 +1917 100 8.82 2.82 7.17 0 265.24 349.1 47045 +1917 101 7.97 1.97 6.32 0.28 251.67 264.25 47243 +1917 102 10.4 4.4 8.75 0.02 292.12 262.78 47441 +1917 103 11.58 5.58 9.93 0.54 313.7 262.58 47638 +1917 104 12.91 6.91 11.26 0 339.63 349.35 47834 +1917 105 13.77 7.77 12.12 0 357.36 349.34 48030 +1917 106 9.94 3.94 8.29 0 284.07 358.32 48225 +1917 107 14.1 8.1 12.45 0 364.37 351.92 48419 +1917 108 11.7 5.7 10.05 0.04 315.97 268.94 48612 +1917 109 9.64 3.64 7.99 0 278.91 363.91 48804 +1917 110 10.59 4.59 8.94 0 295.51 363.68 48995 +1917 111 8.17 2.17 6.52 0.03 254.81 276.97 49185 +1917 112 7.69 1.69 6.04 0.05 247.34 278.68 49374 +1917 113 6.22 0.22 4.57 0.23 225.61 281.3 49561 +1917 114 5.56 -0.44 3.91 0 216.41 377.49 49748 +1917 115 5.12 -0.88 3.47 0.02 210.45 284.65 49933 +1917 116 8.21 2.21 6.56 0.04 255.44 282.28 50117 +1917 117 6.94 0.94 5.29 0.02 236.04 284.73 50300 +1917 118 10.64 4.64 8.99 0 296.41 374.89 50481 +1917 119 9.31 3.31 7.66 0 273.34 378.46 50661 +1917 120 11.41 5.41 9.76 0 310.51 375.82 50840 +1917 121 22.88 16.88 21.23 0 599.18 344.96 51016 +1917 122 21.43 15.43 19.78 0 553.32 351.41 51191 +1917 123 20.56 14.56 18.91 0 527.26 355.39 51365 +1917 124 20.66 14.66 19.01 0.01 530.2 267.08 51536 +1917 125 20.64 14.64 18.99 0 529.61 357.12 51706 +1917 126 20.96 14.96 19.31 0 539.11 356.98 51874 +1917 127 21.1 15.1 19.45 0 543.31 357.36 52039 +1917 128 23.79 17.79 22.14 0 629.58 348.17 52203 +1917 129 23.93 17.93 22.28 0 634.38 348.4 52365 +1917 130 20.92 14.92 19.27 0 537.91 360.53 52524 +1917 131 18.04 12.04 16.39 0 457.57 370.54 52681 +1917 132 18 12 16.35 0 456.53 371.47 52836 +1917 133 19.32 13.32 17.67 0 491.92 368.12 52989 +1917 134 17.79 11.79 16.14 0 451.11 373.49 53138 +1917 135 21.05 15.05 19.4 0 541.8 363.69 53286 +1917 136 22.09 16.09 20.44 0 573.81 360.53 53430 +1917 137 18.42 12.42 16.77 0 467.55 373.63 53572 +1917 138 18.12 12.12 16.47 0.33 459.66 281.35 53711 +1917 139 19.01 13.01 17.36 0.01 483.41 279.81 53848 +1917 140 14.52 8.52 12.87 0.5 373.46 289.52 53981 +1917 141 15.01 9.01 13.36 0 384.31 385.27 54111 +1917 142 13.15 7.15 11.5 0.07 344.5 292.64 54238 +1917 143 15.16 9.16 13.51 0 387.69 385.94 54362 +1917 144 15.36 9.36 13.71 0 392.23 385.91 54483 +1917 145 14.94 8.94 13.29 0.27 382.75 290.58 54600 +1917 146 12.14 6.14 10.49 0.02 324.4 295.71 54714 +1917 147 16.33 10.33 14.68 0 414.89 384.68 54824 +1917 148 16.15 10.15 14.5 0 410.61 385.55 54931 +1917 149 21.42 15.42 19.77 0 553.01 369.27 55034 +1917 150 18.25 12.25 16.6 0.15 463.06 285.14 55134 +1917 151 18.48 12.48 16.83 0 469.14 379.87 55229 +1917 152 24.05 18.05 22.4 0 638.51 359.72 55321 +1917 153 25.52 19.52 23.87 0 690.99 353.48 55409 +1917 154 24.89 18.89 23.24 0.16 668.07 267.47 55492 +1917 155 27.11 21.11 25.46 0.62 751.83 259.75 55572 +1917 156 21.11 15.11 19.46 0 543.61 372.26 55648 +1917 157 18.37 12.37 16.72 0.31 466.23 286.17 55719 +1917 158 19.3 13.3 17.65 0 491.36 378.79 55786 +1917 159 21.51 15.51 19.86 0 555.77 371.38 55849 +1917 160 19.24 13.24 17.59 0 489.71 379.41 55908 +1917 161 20.46 14.46 18.81 0 524.33 375.38 55962 +1917 162 20.92 14.92 19.27 0 537.91 373.82 56011 +1917 163 22.61 16.61 20.96 0 590.41 367.71 56056 +1917 164 21.87 15.87 20.22 0.15 566.91 277.95 56097 +1917 165 20.06 14.06 18.41 0.19 512.76 282.88 56133 +1917 166 15.77 9.77 14.12 0.03 401.68 292.63 56165 +1917 167 20 14 18.35 0 511.04 377.4 56192 +1917 168 21.41 15.41 19.76 0 552.71 372.5 56214 +1917 169 22.37 16.37 20.72 0 582.7 368.89 56231 +1917 170 19.66 13.66 18.01 0 501.4 378.63 56244 +1917 171 20.54 14.54 18.89 0 526.67 375.69 56252 +1917 172 23.56 17.56 21.91 0 621.78 364.18 56256 +1917 173 23.64 17.64 21.99 0 624.48 363.83 56255 +1917 174 27.98 21.98 26.33 0 786.99 343.4 56249 +1917 175 31.21 25.21 29.56 0 929.93 324.85 56238 +1917 176 34.13 28.13 32.48 0.11 1077.39 228.88 56223 +1917 177 30.99 24.99 29.34 0 919.55 326.08 56203 +1917 178 28.92 22.92 27.27 0.14 826.53 253.65 56179 +1917 179 24.46 18.46 22.81 0 652.79 360.03 56150 +1917 180 24.74 18.74 23.09 0 662.71 358.68 56116 +1917 181 24.63 18.63 22.98 0 658.8 359.1 56078 +1917 182 22.55 16.55 20.9 0.16 588.47 275.68 56035 +1917 183 23.57 17.57 21.92 0.44 622.12 272.48 55987 +1917 184 20.34 14.34 18.69 0.03 520.83 281.52 55935 +1917 185 19.98 13.98 18.33 0 510.47 376.5 55879 +1917 186 21.51 15.51 19.86 0 555.77 370.85 55818 +1917 187 19.96 13.96 18.31 0.06 509.9 282.1 55753 +1917 188 22.93 16.93 21.28 0.35 600.82 273.73 55684 +1917 189 20.6 14.6 18.95 0.28 528.43 280.11 55611 +1917 190 20.94 14.94 19.29 0.59 538.51 278.94 55533 +1917 191 21.78 15.78 20.13 0.24 564.11 276.45 55451 +1917 192 18.9 12.9 17.25 0.18 480.41 283.65 55366 +1917 193 20.81 14.81 19.16 0 534.64 371.54 55276 +1917 194 22.48 16.48 20.83 1.04 586.22 273.86 55182 +1917 195 22.6 16.6 20.95 0.23 590.08 273.31 55085 +1917 196 18.82 12.82 17.17 0.12 478.25 282.94 54984 +1917 197 20.64 14.64 18.99 0.49 529.61 278.08 54879 +1917 198 23.66 17.66 22.01 0.33 625.16 269.18 54770 +1917 199 24.55 18.55 22.9 0.15 655.97 266.11 54658 +1917 200 21.63 15.63 19.98 0 559.46 366.06 54542 +1917 201 23.82 17.82 22.17 0 630.61 357.05 54423 +1917 202 28.48 22.48 26.83 0 807.82 334.54 54301 +1917 203 30.05 24.05 28.4 0.56 876.27 244.02 54176 +1917 204 26.01 20.01 24.36 0.08 709.28 259.43 54047 +1917 205 29.5 23.5 27.85 0.3 851.75 245.66 53915 +1917 206 28.32 22.32 26.67 0.11 801.1 250.08 53780 +1917 207 30.4 24.4 28.75 0 892.18 321.28 53643 +1917 208 30.52 24.52 28.87 0 897.69 319.97 53502 +1917 209 29.77 23.77 28.12 0.18 863.72 242.79 53359 +1917 210 26.11 20.11 24.46 0.41 713.06 256.46 53213 +1917 211 25.46 19.46 23.81 0 688.78 344.16 53064 +1917 212 24.62 18.62 22.97 0.01 658.44 260.31 52913 +1917 213 23.95 17.95 22.3 0 635.06 349.15 52760 +1917 214 23.67 17.67 22.02 0 625.5 349.56 52604 +1917 215 22.61 16.61 20.96 0 590.41 353.06 52445 +1917 216 24.96 18.96 23.31 0 670.58 342.53 52285 +1917 217 23.64 17.64 21.99 0.12 624.48 260.38 52122 +1917 218 22.97 16.97 21.32 0.35 602.13 261.76 51958 +1917 219 23.44 17.44 21.79 1.75 617.74 259.61 51791 +1917 220 21.47 15.47 19.82 1 554.54 264.45 51622 +1917 221 20.23 14.23 18.58 0.44 517.65 266.87 51451 +1917 222 19.37 13.37 17.72 0.46 493.3 268.16 51279 +1917 223 19.35 13.35 17.7 0 492.75 356.46 51105 +1917 224 20.81 14.81 19.16 0.03 534.64 263 50929 +1917 225 20.29 14.29 18.64 0 519.38 351.25 50751 +1917 226 23.5 17.5 21.85 0 619.76 338.64 50572 +1917 227 26.38 20.38 24.73 0 723.36 325.25 50392 +1917 228 26.73 20.73 25.08 0 736.89 322.5 50210 +1917 229 27.37 21.37 25.72 0.04 762.19 238.74 50026 +1917 230 25.37 19.37 23.72 0.22 685.47 244.63 49842 +1917 231 25.18 19.18 23.53 0.15 678.54 244.18 49656 +1917 232 25.23 19.23 23.58 0.22 680.36 243.06 49469 +1917 233 21.79 15.79 20.14 0.09 564.42 251.93 49280 +1917 234 22.18 16.18 20.53 0 576.65 333.15 49091 +1917 235 26.88 20.88 25.23 0.01 742.76 234.55 48900 +1917 236 30.87 24.87 29.22 0.01 913.93 218.37 48709 +1917 237 26.86 20.86 25.21 0.06 741.97 232.46 48516 +1917 238 22.75 16.75 21.1 0 594.94 325.02 48323 +1917 239 24.41 18.41 22.76 0.01 651.04 237.98 48128 +1917 240 22.04 16.04 20.39 0 572.24 324.34 47933 +1917 241 22.84 16.84 21.19 0.01 597.88 239.89 47737 +1917 242 23.39 17.39 21.74 0 616.06 316.17 47541 +1917 243 22.43 16.43 20.78 0 584.62 317.8 47343 +1917 244 16.35 10.35 14.7 0 415.37 333.82 47145 +1917 245 19.81 13.81 18.16 0 505.63 322.63 46947 +1917 246 22.49 16.49 20.84 0 586.54 312.12 46747 +1917 247 21.56 15.56 19.91 0 557.3 313.43 46547 +1917 248 22.22 16.22 20.57 0 577.92 309.36 46347 +1917 249 22.58 16.58 20.93 0 589.44 306.14 46146 +1917 250 26.55 20.55 24.9 0 729.9 289.19 45945 +1917 251 24.48 18.48 22.83 0 653.5 295.45 45743 +1917 252 22.85 16.85 21.2 0 598.2 299.22 45541 +1917 253 23.92 17.92 22.27 0.6 634.03 220.08 45339 +1917 254 21.72 15.72 20.07 0.29 562.24 224.12 45136 +1917 255 19.38 13.38 17.73 0 493.58 303.55 44933 +1917 256 19.77 13.77 18.12 0 504.5 300.23 44730 +1917 257 23.98 17.98 22.33 0 636.09 284.84 44527 +1917 258 21.9 15.9 20.25 0 567.85 289.52 44323 +1917 259 26.01 20.01 24.36 0.13 709.28 204.6 44119 +1917 260 24.37 18.37 22.72 0 649.63 276.68 43915 +1917 261 20.24 14.24 18.59 0 517.94 287.39 43711 +1917 262 19.59 13.59 17.94 0 499.44 286.85 43507 +1917 263 13.42 7.42 11.77 1.16 350.05 223.69 43303 +1917 264 15.11 9.11 13.46 0.11 386.56 219.28 43099 +1917 265 16.43 10.43 14.78 0.22 417.29 215.41 42894 +1917 266 19.75 13.75 18.1 0.31 503.94 207.57 42690 +1917 267 20.99 14.99 19.34 0.03 540 203.09 42486 +1917 268 20.3 14.3 18.65 0.38 519.67 202.65 42282 +1917 269 16.61 10.61 14.96 0.23 421.64 207.48 42078 +1917 270 21.61 15.61 19.96 0 558.84 261.61 41875 +1917 271 22.84 16.84 21.19 0 597.88 255.49 41671 +1917 272 18.53 12.53 16.88 0 470.47 264.43 41468 +1917 273 19.52 13.52 17.87 0 497.48 259.57 41265 +1917 274 11.33 5.33 9.68 0.75 309.02 204.74 41062 +1917 275 9.82 3.82 8.17 0.67 282 204.26 40860 +1917 276 15.54 9.54 13.89 0.21 396.35 195.22 40658 +1917 277 12.29 6.29 10.64 1.99 327.32 197.47 40456 +1917 278 9.4 3.4 7.75 1.08 274.85 198.4 40255 +1917 279 10.28 4.28 8.63 0.69 290 195.37 40054 +1917 280 11.25 5.25 9.6 0 307.53 256.45 39854 +1917 281 8.33 2.33 6.68 0.48 257.34 193.14 39654 +1917 282 5.03 -0.97 3.38 0.57 209.25 193.68 39455 +1917 283 8.83 2.83 7.18 0 265.4 251.25 39256 +1917 284 11.82 5.82 10.17 0.18 318.25 183.18 39058 +1917 285 11.66 5.66 10.01 0.12 315.21 181.36 38861 +1917 286 16.72 10.72 15.07 0 424.32 230.73 38664 +1917 287 19.56 13.56 17.91 0 498.6 222.04 38468 +1917 288 18.45 12.45 16.8 0.93 468.34 166.3 38273 +1917 289 17.26 11.26 15.61 0.07 437.66 166.16 38079 +1917 290 14.51 8.51 12.86 0.13 373.25 167.68 37885 +1917 291 13.93 7.93 12.28 0.11 360.75 166.36 37693 +1917 292 12.88 6.88 11.23 0.42 339.03 165.53 37501 +1917 293 11.06 5.06 9.41 0 304.03 220.44 37311 +1917 294 11.73 5.73 10.08 0 316.53 216.68 37121 +1917 295 9.64 3.64 7.99 0.37 278.91 162.31 36933 +1917 296 11.16 5.16 9.51 0.08 305.87 158.99 36745 +1917 297 14.71 8.71 13.06 0 377.64 204.37 36560 +1917 298 13.15 7.15 11.5 0 344.5 204.07 36375 +1917 299 14.88 8.88 13.23 0 381.41 198.82 36191 +1917 300 15.71 9.71 14.06 0.1 400.28 146.19 36009 +1917 301 15.82 9.82 14.17 0.04 402.84 144.22 35829 +1917 302 19.42 13.42 17.77 0.5 494.69 137.62 35650 +1917 303 23.54 17.54 21.89 0.02 621.1 129.13 35472 +1917 304 21.07 15.07 19.42 0 542.4 175.43 35296 +1917 305 16.18 10.18 14.53 1.4 411.32 136.22 35122 +1917 306 13.64 7.64 11.99 1.21 354.63 137.31 34950 +1917 307 7.65 1.65 6 0.05 246.72 140.39 34779 +1917 308 7.4 1.4 5.75 0 242.92 184.79 34610 +1917 309 4.74 -1.26 3.09 0 205.42 184.61 34444 +1917 310 6.98 0.98 5.33 0.17 236.63 135.28 34279 +1917 311 6.32 0.32 4.67 0 227.04 178.72 34116 +1917 312 2.89 -3.11 1.24 0 182.38 178.51 33956 +1917 313 6.01 0.01 4.36 0 222.65 174.17 33797 +1917 314 7.45 1.45 5.8 0 243.67 171.05 33641 +1917 315 11.01 5.01 9.36 0.19 303.11 123.89 33488 +1917 316 8.74 2.74 7.09 0.44 263.94 123.91 33337 +1917 317 11.72 5.72 10.07 0.09 316.34 120.1 33188 +1917 318 8.7 2.7 7.05 0 263.29 160.74 33042 +1917 319 11.35 5.35 9.7 0.02 309.39 117.41 32899 +1917 320 13.59 7.59 11.94 0 353.59 152.27 32758 +1917 321 12.56 6.56 10.91 0 332.64 151.36 32620 +1917 322 12.54 6.54 10.89 0 332.24 149.61 32486 +1917 323 8.49 2.49 6.84 0.01 259.9 113.89 32354 +1917 324 10.31 4.31 8.66 0.42 290.53 111.17 32225 +1917 325 11 5 9.35 0.46 302.93 109.41 32100 +1917 326 8.09 2.09 6.44 0.08 253.55 110.24 31977 +1917 327 4.31 -1.69 2.66 0 199.85 147.79 31858 +1917 328 6.46 0.46 4.81 0.92 229.04 108.3 31743 +1917 329 4.47 -1.53 2.82 0.17 201.91 108.16 31631 +1917 330 9.49 3.49 7.84 1.01 276.37 104.36 31522 +1917 331 6 0 4.35 0.04 222.51 105.34 31417 +1917 332 6.6 0.6 4.95 0 231.07 138.41 31316 +1917 333 1.44 -4.56 -0.21 0 165.91 140.34 31218 +1917 334 3.5 -2.5 1.85 0 189.71 138.15 31125 +1917 335 -2.65 -8.65 -4.3 0 126.19 139.77 31035 +1917 336 -4.94 -10.94 -6.59 0 107.77 139.45 30949 +1917 337 -3.56 -9.56 -5.21 0 118.57 137.32 30867 +1917 338 -6.05 -12.05 -7.7 0 99.72 137.13 30790 +1917 339 -4.93 -10.93 -6.58 0.09 107.85 145.25 30716 +1917 340 -4.53 -10.53 -6.18 0.03 110.89 144.78 30647 +1917 341 5.58 -0.42 3.93 0.12 216.68 97.23 30582 +1917 342 4.85 -1.15 3.2 0 206.86 129.31 30521 +1917 343 4.68 -1.32 3.03 0 204.63 128.59 30465 +1917 344 6.36 0.36 4.71 0 227.61 126.44 30413 +1917 345 1.46 -4.54 -0.19 0 166.13 128.69 30366 +1917 346 -0.1 -6.1 -1.75 0 149.84 128.83 30323 +1917 347 1.79 -4.21 0.14 0 169.76 127.39 30284 +1917 348 3.81 -2.19 2.16 0.71 193.54 94.51 30251 +1917 349 2.57 -3.43 0.92 0.18 178.63 94.71 30221 +1917 350 -2.04 -8.04 -3.69 2.18 131.53 146.57 30197 +1917 351 -1.78 -7.78 -3.43 0 133.87 178.26 30177 +1917 352 -1.48 -7.48 -3.13 0 136.61 178.08 30162 +1917 353 1.46 -4.54 -0.19 0 166.13 176.61 30151 +1917 354 -0.43 -6.43 -2.08 0.48 146.58 147.21 30145 +1917 355 2.33 -3.67 0.68 0 175.86 177.4 30144 +1917 356 4.56 -1.44 2.91 0 203.07 175.64 30147 +1917 357 2.19 -3.81 0.54 0 174.26 176.63 30156 +1917 358 3.04 -2.96 1.39 0 184.16 175.87 30169 +1917 359 5.29 -0.71 3.64 0.4 212.73 142.93 30186 +1917 360 1.23 -4.77 -0.42 0.02 163.64 144.58 30208 +1917 361 3.56 -2.44 1.91 0.01 190.45 143.46 30235 +1917 362 -0.76 -6.76 -2.41 0 143.38 177.34 30267 +1917 363 -0.02 -6.02 -1.67 0.07 150.64 145.61 30303 +1917 364 2.36 -3.64 0.71 0 176.2 176.73 30343 +1917 365 -0.73 -6.73 -2.38 0 143.67 178.61 30388 +1918 1 3.79 -2.21 2.14 0 193.29 176.8 30438 +1918 2 3.94 -2.06 2.29 0 195.16 176.84 30492 +1918 3 1.14 -4.86 -0.51 0.11 162.67 146.01 30551 +1918 4 3.19 -2.81 1.54 0 185.95 178.34 30614 +1918 5 4.19 -1.81 2.54 0.1 198.32 144.85 30681 +1918 6 2.5 -3.5 0.85 0 177.82 179.16 30752 +1918 7 3.37 -2.63 1.72 0.14 188.13 145.46 30828 +1918 8 7.31 1.31 5.66 0 241.56 176.91 30907 +1918 9 8.8 2.8 7.15 0 264.91 175.78 30991 +1918 10 8.41 2.41 6.76 1.15 258.62 101 31079 +1918 11 2 -4 0.35 0.16 172.11 104.76 31171 +1918 12 -1.09 -7.09 -2.74 0 140.24 142.12 31266 +1918 13 -0.49 -6.49 -2.14 0 145.99 143.5 31366 +1918 14 4.43 -1.57 2.78 0 201.39 142.44 31469 +1918 15 4.21 -1.79 2.56 0 198.57 144.02 31575 +1918 16 4.51 -1.49 2.86 0 202.42 145.12 31686 +1918 17 5.32 -0.68 3.67 0 213.14 146.28 31800 +1918 18 4.75 -1.25 3.1 0 205.55 148.54 31917 +1918 19 5.68 -0.32 4.03 0 218.05 149.85 32038 +1918 20 5.42 -0.58 3.77 0 214.49 151.61 32161 +1918 21 1.33 -4.67 -0.32 0 164.72 156.05 32289 +1918 22 4.53 -1.47 2.88 0 202.68 155.94 32419 +1918 23 7.38 1.38 5.73 0 242.61 155.66 32552 +1918 24 5.73 -0.27 4.08 0.29 218.75 119.21 32688 +1918 25 4.43 -1.57 2.78 0 201.39 161.72 32827 +1918 26 3.65 -2.35 2 0 191.56 164.15 32969 +1918 27 -1.06 -7.06 -2.71 0 140.52 168.76 33114 +1918 28 0.06 -5.94 -1.59 0 151.45 170.44 33261 +1918 29 -3.65 -9.65 -5.3 0 117.84 174.52 33411 +1918 30 -1.89 -7.89 -3.54 0.42 132.87 172.57 33564 +1918 31 0.99 -5.01 -0.66 0 161.07 217.23 33718 +1918 32 6.15 0.15 4.5 0 224.62 215 33875 +1918 33 7.55 1.55 5.9 0 245.19 177.15 34035 +1918 34 3.95 -2.05 2.3 0 195.29 182.14 34196 +1918 35 0.9 -5.1 -0.75 0 160.12 186.22 34360 +1918 36 3.1 -2.9 1.45 0 184.88 187.39 34526 +1918 37 -0.8 -6.8 -2.45 0 143 192.14 34694 +1918 38 1.48 -4.52 -0.17 0 166.35 193.62 34863 +1918 39 3.24 -2.76 1.59 0 186.56 195.1 35035 +1918 40 3.08 -2.92 1.43 0 184.64 197.83 35208 +1918 41 5.26 -0.74 3.61 0 212.33 198.83 35383 +1918 42 -0.19 -6.19 -1.84 0 148.95 205.1 35560 +1918 43 -1.01 -7.01 -2.66 0 141 208.29 35738 +1918 44 2.21 -3.79 0.56 0 174.49 208.93 35918 +1918 45 1.72 -4.28 0.07 0 168.99 211.9 36099 +1918 46 4 -2 2.35 0 195.92 212.97 36282 +1918 47 7.02 1.02 5.37 0 237.22 213.18 36466 +1918 48 6.59 0.59 4.94 0 230.92 216.38 36652 +1918 49 8.53 2.53 6.88 0 260.54 217.2 36838 +1918 50 5.24 -0.76 3.59 0 212.06 223.03 37026 +1918 51 7.45 1.45 5.8 0 243.67 223.91 37215 +1918 52 4.71 -1.29 3.06 0 205.02 229.29 37405 +1918 53 5.52 -0.48 3.87 0 215.86 231.54 37596 +1918 54 4.57 -1.43 2.92 0 203.2 235.14 37788 +1918 55 4.3 -1.7 2.65 0.08 199.72 178.79 37981 +1918 56 1.84 -4.16 0.19 0 170.32 243.05 38175 +1918 57 3.43 -2.57 1.78 0.02 188.86 183.54 38370 +1918 58 6.29 0.29 4.64 0.58 226.61 183.79 38565 +1918 59 1.61 -4.39 -0.04 0 167.77 251.84 38761 +1918 60 9.43 3.43 7.78 0 275.36 247.1 38958 +1918 61 10.14 4.14 8.49 0.54 287.55 186.82 39156 +1918 62 9.91 3.91 8.26 0 283.55 252.15 39355 +1918 63 6.5 0.5 4.85 0 229.62 259.16 39553 +1918 64 6.01 0.01 4.36 0 222.65 262.58 39753 +1918 65 14 8 12.35 0 362.24 254.65 39953 +1918 66 13.17 7.17 11.52 0 344.91 258.71 40154 +1918 67 12.9 6.9 11.25 0.44 339.43 196.49 40355 +1918 68 8.6 2.6 6.95 0.54 261.67 203.26 40556 +1918 69 9.21 3.21 7.56 0 271.67 272.83 40758 +1918 70 9.54 3.54 7.89 0 277.21 275.21 40960 +1918 71 4.76 -1.24 3.11 0 205.68 283.75 41163 +1918 72 7.82 1.82 6.17 0 249.34 283.16 41366 +1918 73 9 3 7.35 0 268.19 284.3 41569 +1918 74 6.84 0.84 5.19 0.1 234.57 217.32 41772 +1918 75 2.94 -3.06 1.29 0 182.97 296.59 41976 +1918 76 2.72 -3.28 1.07 0 180.38 299.47 42179 +1918 77 8.82 2.82 7.17 0 265.24 295.22 42383 +1918 78 7.79 1.79 6.14 0 248.88 299.25 42587 +1918 79 9.58 3.58 7.93 0 277.89 299.53 42791 +1918 80 6.05 0.05 4.4 0 223.21 306.67 42996 +1918 81 8.33 2.33 6.68 0 257.34 306.39 43200 +1918 82 7.88 1.88 6.23 0 250.27 309.65 43404 +1918 83 7.74 1.74 6.09 0 248.11 312.34 43608 +1918 84 8.04 2.04 6.39 0 252.77 314.48 43812 +1918 85 8.8 2.8 7.15 0 264.91 315.93 44016 +1918 86 11.08 5.08 9.43 0 304.4 314.8 44220 +1918 87 8.87 2.87 7.22 0 266.06 320.77 44424 +1918 88 7.53 1.53 5.88 0 244.89 325.01 44627 +1918 89 7.29 1.29 5.64 0 241.26 327.63 44831 +1918 90 8.37 2.37 6.72 0 257.98 328.51 45034 +1918 91 15.41 9.41 13.76 0 393.37 318.06 45237 +1918 92 15.23 9.23 13.58 0 389.27 320.65 45439 +1918 93 12.77 6.77 11.12 0.01 336.82 245.92 45642 +1918 94 13.93 7.93 12.28 0 360.75 327.72 45843 +1918 95 13.6 7.6 11.95 0 353.8 330.5 46045 +1918 96 13.91 7.91 12.26 1.23 360.32 248.97 46246 +1918 97 16.48 10.48 14.83 0.03 418.5 246.13 46446 +1918 98 16.32 10.32 14.67 0 414.65 330.48 46647 +1918 99 18.2 12.2 16.55 0 461.75 327.61 46846 +1918 100 18.35 12.35 16.7 0.37 465.7 246.81 47045 +1918 101 14.94 8.94 13.29 0.01 382.75 254.61 47243 +1918 102 10.61 4.61 8.96 0.08 295.87 262.51 47441 +1918 103 11.1 5.1 9.45 0 304.76 350.99 47638 +1918 104 12.51 6.51 10.86 0.03 331.65 262.61 47834 +1918 105 13.76 7.76 12.11 0 357.15 349.36 48030 +1918 106 15.44 9.44 13.79 0.04 394.06 260.4 48225 +1918 107 14.42 8.42 12.77 0.11 371.28 263.4 48419 +1918 108 13.56 7.56 11.91 0.24 352.96 266.12 48612 +1918 109 14.1 8.1 12.45 1.24 364.37 266.43 48804 +1918 110 12.12 6.12 10.47 0.39 324.02 270.6 48995 +1918 111 14.73 8.73 13.08 0.01 378.08 267.57 49185 +1918 112 13.64 7.64 11.99 0.88 354.63 270.54 49374 +1918 113 13.57 7.57 11.92 0.53 353.17 271.65 49561 +1918 114 11.56 5.56 9.91 0 313.32 367.82 49748 +1918 115 12.8 6.8 11.15 0 337.42 366.77 49933 +1918 116 16.3 10.3 14.65 0 414.18 359.84 50117 +1918 117 18.82 12.82 17.17 0 478.25 354.1 50300 +1918 118 18.67 12.67 17.02 0 474.21 355.83 50481 +1918 119 17.77 11.77 16.12 0 450.6 359.61 50661 +1918 120 15.07 9.07 13.42 0 385.66 367.86 50840 +1918 121 19.27 13.27 17.62 0.54 490.54 268.05 51016 +1918 122 21.4 15.4 19.75 0.22 552.4 263.64 51191 +1918 123 23.23 17.23 21.58 0 610.73 345.72 51365 +1918 124 20.91 14.91 19.26 0.32 537.61 266.44 51536 +1918 125 21.49 15.49 19.84 0.06 555.15 265.63 51706 +1918 126 14.43 8.43 12.78 0.01 371.5 281.85 51874 +1918 127 15.94 9.94 14.29 0.23 405.65 279.71 52039 +1918 128 17.89 11.89 16.24 0.03 453.69 276.43 52203 +1918 129 18.58 12.58 16.93 0.04 471.8 275.52 52365 +1918 130 21.01 15.01 19.36 0.05 540.6 270.16 52524 +1918 131 21.5 15.5 19.85 0.02 555.46 269.44 52681 +1918 132 16.8 10.8 15.15 0.59 426.27 281.17 52836 +1918 133 13.04 7.04 11.39 0 342.26 384.87 52989 +1918 134 17.12 11.12 15.47 0.33 434.17 281.56 53138 +1918 135 21.31 15.31 19.66 0 549.66 362.77 53286 +1918 136 18.84 12.84 17.19 0 478.79 371.64 53430 +1918 137 21.67 15.67 20.02 0.68 560.7 272.08 53572 +1918 138 21.86 15.86 20.21 0.06 566.6 271.99 53711 +1918 139 23.06 17.06 21.41 0 605.1 358.72 53848 +1918 140 21.11 15.11 19.46 0.05 543.61 274.89 53981 +1918 141 18.56 12.56 16.91 0 471.27 375.39 54111 +1918 142 21.23 15.23 19.58 0 547.23 366.99 54238 +1918 143 18.98 12.98 17.33 0.15 482.59 281.33 54362 +1918 144 17.31 11.31 15.66 0.42 438.92 285.46 54483 +1918 145 18.34 12.34 16.69 1.89 465.43 283.53 54600 +1918 146 13.17 7.17 11.52 0.99 344.91 294.02 54714 +1918 147 11.24 5.24 9.59 0 307.35 396.62 54824 +1918 148 17.31 11.31 15.66 0.09 438.92 286.74 54931 +1918 149 15.44 9.44 13.79 1.46 394.06 290.81 55034 +1918 150 11.1 5.1 9.45 1.37 304.76 298.47 55134 +1918 151 11.95 5.95 10.3 0 320.74 396.62 55229 +1918 152 13.05 7.05 11.4 0.11 342.47 295.77 55321 +1918 153 15.72 9.72 14.07 0 400.51 388.11 55409 +1918 154 17.01 11.01 15.36 1.08 431.44 288.67 55492 +1918 155 19.46 13.46 17.81 0 495.8 377.61 55572 +1918 156 20.19 14.19 18.54 0.39 516.49 281.61 55648 +1918 157 20.23 14.23 18.58 0 517.65 375.52 55719 +1918 158 20.06 14.06 18.41 0 512.76 376.27 55786 +1918 159 17.51 11.51 15.86 0.99 443.96 288.42 55849 +1918 160 19.75 13.75 18.1 0.93 503.94 283.3 55908 +1918 161 16.51 10.51 14.86 0.11 419.22 290.75 55962 +1918 162 17.42 11.42 15.77 0 441.69 385.14 56011 +1918 163 20.93 14.93 19.28 0 538.21 374 56056 +1918 164 22.42 16.42 20.77 0.32 584.3 276.37 56097 +1918 165 19.95 13.95 18.3 0.81 509.61 283.16 56133 +1918 166 19.59 13.59 17.94 0 499.44 378.83 56165 +1918 167 20.52 14.52 18.87 0 526.08 375.61 56192 +1918 168 18.11 12.11 16.46 2.06 459.4 287.66 56214 +1918 169 17.84 11.84 16.19 0 452.4 384.37 56231 +1918 170 15.56 9.56 13.91 0 396.81 390.76 56244 +1918 171 16.34 10.34 14.69 0.73 415.13 291.55 56252 +1918 172 15.79 9.79 14.14 0.2 402.14 292.65 56256 +1918 173 13.83 7.83 12.18 0.01 358.63 296.32 56255 +1918 174 11.49 5.49 9.84 0.15 312.01 300.12 56249 +1918 175 17.22 11.22 15.57 0.04 436.66 289.58 56238 +1918 176 13.92 7.92 12.27 0.01 360.53 296.05 56223 +1918 177 15.11 9.11 13.46 0.02 386.56 293.77 56203 +1918 178 19.99 13.99 18.34 0.43 510.75 283 56179 +1918 179 22.74 16.74 21.09 0 594.62 367.16 56150 +1918 180 26.83 20.83 25.18 0 740.8 348.92 56116 +1918 181 24.4 18.4 22.75 0.12 650.69 270.08 56078 +1918 182 23.68 17.68 22.03 0.1 625.84 272.26 56035 +1918 183 20.66 14.66 19.01 0.31 530.2 280.8 55987 +1918 184 19.44 13.44 17.79 0.02 495.25 283.79 55935 +1918 185 17.37 11.37 15.72 0 440.43 384.68 55879 +1918 186 20.87 14.87 19.22 0 536.42 373.16 55818 +1918 187 24.59 18.59 22.94 0 657.38 358.31 55753 +1918 188 23.57 17.57 21.92 0.02 622.12 271.78 55684 +1918 189 27.64 21.64 25.99 0.47 773.09 257.56 55611 +1918 190 25.98 19.98 24.33 0.75 708.15 263.41 55533 +1918 191 28.01 22.01 26.36 0.82 788.23 255.66 55451 +1918 192 29.44 23.44 27.79 0.06 849.12 249.61 55366 +1918 193 27.05 21.05 25.4 1.19 749.45 258.94 55276 +1918 194 23.86 17.86 22.21 0 631.98 359.6 55182 +1918 195 24.15 18.15 22.5 0.47 641.97 268.58 55085 +1918 196 23.57 17.57 21.92 1.44 622.12 270.1 54984 +1918 197 23.61 17.61 21.96 1.1 623.47 269.64 54879 +1918 198 19.94 13.94 18.29 0 509.33 372.74 54770 +1918 199 21.91 15.91 20.26 0 568.16 365.43 54658 +1918 200 22.09 16.09 20.44 0.18 573.81 273.27 54542 +1918 201 21.24 15.24 19.59 0 547.53 367.02 54423 +1918 202 20 14 18.35 0.6 511.04 278.06 54301 +1918 203 20.51 14.51 18.86 0.59 525.79 276.39 54176 +1918 204 18.38 12.38 16.73 0.1 466.49 281.17 54047 +1918 205 21.67 15.67 20.02 0 560.7 363.38 53915 +1918 206 22.36 16.36 20.71 0 582.38 360.25 53780 +1918 207 21.91 15.91 20.26 0.56 568.16 270.97 53643 +1918 208 18.04 12.04 16.39 0.69 457.57 280.12 53502 +1918 209 18.89 12.89 17.24 0.3 480.14 277.69 53359 +1918 210 22.34 16.34 20.69 0.01 581.74 268.33 53213 +1918 211 21.43 15.43 19.78 0.03 553.32 270.27 53064 +1918 212 19.45 13.45 17.8 0.58 495.53 274.7 52913 +1918 213 21.42 15.42 19.77 0.16 553.01 269.14 52760 +1918 214 23.01 17.01 21.36 0 603.45 352.18 52604 +1918 215 25.23 19.23 23.58 0 680.36 342.33 52445 +1918 216 21.58 15.58 19.93 0 557.92 355.86 52285 +1918 217 22.15 16.15 20.5 0.14 575.7 264.68 52122 +1918 218 20.86 14.86 19.21 0.25 536.12 267.52 51958 +1918 219 21.23 15.23 19.58 0 547.23 354.37 51791 +1918 220 18.51 12.51 16.86 0 469.94 362.23 51622 +1918 221 14.39 8.39 12.74 0 370.63 372.13 51451 +1918 222 22.16 16.16 20.51 0.63 576.02 261.07 51279 +1918 223 16.3 10.3 14.65 0.36 414.18 273.87 51105 +1918 224 15.41 9.41 13.76 0.07 393.37 274.75 50929 +1918 225 19.48 13.48 17.83 1.19 496.36 265.38 50751 +1918 226 21.02 15.02 19.37 0.92 540.9 260.76 50572 +1918 227 22.32 16.32 20.67 2.89 581.1 256.38 50392 +1918 228 23.03 17.03 21.38 1.65 604.11 253.51 50210 +1918 229 24.17 18.17 22.52 0.39 642.66 249.28 50026 +1918 230 23.17 17.17 21.52 1.01 608.73 251.28 49842 +1918 231 21.4 15.4 19.75 1.61 552.4 254.99 49656 +1918 232 21.93 15.93 20.28 0.89 568.78 252.61 49469 +1918 233 22.5 16.5 20.85 0.2 586.86 250.04 49280 +1918 234 20.49 14.49 18.84 0.37 525.2 254.14 49091 +1918 235 20.91 14.91 19.26 0.3 537.61 252.01 48900 +1918 236 23.02 17.02 21.37 0.6 603.78 245.45 48709 +1918 237 22.94 16.94 21.29 1.44 601.15 244.47 48516 +1918 238 24.05 18.05 22.4 0 638.51 320.16 48323 +1918 239 26.26 20.26 24.61 0.09 718.77 232.23 48128 +1918 240 26.01 20.01 24.36 0.09 709.28 231.79 47933 +1918 241 19.1 13.1 17.45 0.1 485.86 248.95 47737 +1918 242 19.18 13.18 17.53 0.19 488.06 247.48 47541 +1918 243 22.57 16.57 20.92 0.11 589.12 237.98 47343 +1918 244 21.78 15.78 20.13 0 564.11 318.23 47145 +1918 245 23.49 17.49 21.84 0 619.42 310.47 46947 +1918 246 21.65 15.65 20 0 560.08 314.95 46747 +1918 247 21.68 15.68 20.03 0 561.01 313.04 46547 +1918 248 21.3 15.3 19.65 0.45 549.35 234.28 46347 +1918 249 25.94 19.94 24.29 0 706.64 293.55 46146 +1918 250 23.87 17.87 22.22 0 632.32 299.72 45945 +1918 251 20.92 14.92 19.27 0 537.91 307.57 45743 +1918 252 21.04 15.04 19.39 0 541.5 305.09 45541 +1918 253 20.61 14.61 18.96 0 528.72 304.33 45339 +1918 254 17.52 11.52 15.87 0 444.22 310.67 45136 +1918 255 19.5 13.5 17.85 0.71 496.92 227.41 44933 +1918 256 15.68 9.68 14.03 0 399.59 310.46 44730 +1918 257 14.86 8.86 13.21 0.73 380.96 232.53 44527 +1918 258 16.6 10.6 14.95 0.52 421.4 227.89 44323 +1918 259 15.2 9.2 13.55 0.01 388.59 228.38 44119 +1918 260 18.18 12.18 16.53 0.91 461.23 221.44 43915 +1918 261 16.02 10.02 14.37 0 407.53 297.88 43711 +1918 262 18.25 12.25 16.6 0 463.06 290.31 43507 +1918 263 16.98 10.98 15.33 0 430.7 290.9 43303 +1918 264 21.47 15.47 19.82 0 554.54 276.66 43099 +1918 265 19.61 13.61 17.96 0 500 279.55 42894 +1918 266 21.49 15.49 19.84 0.49 555.15 203.95 42690 +1918 267 19.87 13.87 18.22 0.52 507.33 205.38 42486 +1918 268 18.28 12.28 16.63 0.44 463.85 206.49 42282 +1918 269 19.14 13.14 17.49 0 486.96 270.76 42078 +1918 270 18.63 12.63 16.98 0.06 473.14 202.07 41875 +1918 271 16.78 10.78 15.13 1.34 425.78 203.29 41671 +1918 272 16.76 10.76 15.11 0.8 425.29 201.3 41468 +1918 273 17.85 11.85 16.2 0.08 452.65 197.64 41265 +1918 274 10.56 4.56 8.91 0.91 294.97 205.6 41062 +1918 275 12.46 6.46 10.81 0.78 330.66 201.32 40860 +1918 276 12.64 6.64 10.99 1.07 334.22 199.06 40658 +1918 277 10.53 4.53 8.88 0.76 294.44 199.43 40456 +1918 278 12.4 6.4 10.75 0.24 329.48 195.17 40255 +1918 279 11.88 5.88 10.23 0 319.39 258.2 40054 +1918 280 16.43 10.43 14.78 0 417.29 247.7 39854 +1918 281 15.04 9.04 13.39 0.01 384.99 185.72 39654 +1918 282 10.6 4.6 8.95 0 295.69 251.84 39455 +1918 283 10.38 4.38 8.73 0 291.77 249.28 39256 +1918 284 14.46 8.46 12.81 0 372.15 240.11 39058 +1918 285 17.41 11.41 15.76 0 441.43 232.09 38861 +1918 286 17.52 11.52 15.87 0.33 444.22 171.88 38664 +1918 287 14.34 8.34 12.69 0.39 369.54 174.03 38468 +1918 288 16.65 10.65 15 0.12 422.61 168.95 38273 +1918 289 14.06 8.06 12.41 0.11 363.52 170.34 38079 +1918 290 8.66 2.66 7.01 0.88 262.64 173.63 37885 +1918 291 6.47 0.47 4.82 0.02 229.19 173.29 37693 +1918 292 8.46 2.46 6.81 0 259.42 226.26 37501 +1918 293 10.58 4.58 8.93 0 295.33 221.04 37311 +1918 294 10.18 4.18 8.53 0 288.25 218.63 37121 +1918 295 12.04 6.04 10.39 0.06 322.47 160.08 36933 +1918 296 12.61 6.61 10.96 0.06 333.63 157.58 36745 +1918 297 14.45 8.45 12.8 0.02 371.94 153.57 36560 +1918 298 14.63 8.63 12.98 0.5 375.88 151.45 36375 +1918 299 17.94 11.94 16.29 0 454.98 193.72 36191 +1918 300 15.24 9.24 13.59 0.43 389.5 146.74 36009 +1918 301 13.7 7.7 12.05 0.15 355.89 146.58 35829 +1918 302 15.66 9.66 14.01 0.38 399.12 142.5 35650 +1918 303 11.95 5.95 10.3 0.84 320.74 144.44 35472 +1918 304 14.44 8.44 12.79 0.56 371.72 140.16 35296 +1918 305 4.64 -1.36 2.99 0 204.11 194.51 35122 +1918 306 5.4 -0.6 3.75 0 214.22 191.63 34950 +1918 307 9.87 3.87 8.22 0 282.86 185.03 34779 +1918 308 10.85 4.85 9.2 0 300.2 181.39 34610 +1918 309 7.36 1.36 5.71 0 242.31 182.5 34444 +1918 310 9.17 3.17 7.52 0 271 178.39 34279 +1918 311 6.2 0.2 4.55 0 225.33 178.82 34116 +1918 312 4.69 -1.31 3.04 0.03 204.76 132.97 33956 +1918 313 2.8 -3.2 1.15 0 181.32 176.41 33797 +1918 314 4.83 -1.17 3.18 0 206.6 173.07 33641 +1918 315 7.02 1.02 5.37 0 237.22 168.86 33488 +1918 316 7.71 1.71 6.06 0 247.65 166.11 33337 +1918 317 6.86 0.86 5.21 0 234.86 164.6 33188 +1918 318 4.71 -1.29 3.06 0 205.02 163.83 33042 +1918 319 10.46 4.46 8.81 0 293.19 157.43 32899 +1918 320 10.37 4.37 8.72 0 291.59 155.67 32758 +1918 321 8.28 2.28 6.63 0.01 256.55 116.59 32620 +1918 322 5.06 -0.94 3.41 0.5 209.65 117.03 32486 +1918 323 1.4 -4.6 -0.25 0 165.48 156.59 32354 +1918 324 0.99 -5.01 -0.66 0 161.07 154.72 32225 +1918 325 5.6 -0.4 3.95 0.01 216.95 112.7 32100 +1918 326 2.73 -3.27 1.08 0 180.49 150.58 31977 +1918 327 7.32 1.32 5.67 0 241.71 145.74 31858 +1918 328 9.42 3.42 7.77 0.07 275.19 106.58 31743 +1918 329 7.26 1.26 5.61 0.17 240.81 106.75 31631 +1918 330 8.43 2.43 6.78 0.11 258.94 105 31522 +1918 331 4.95 -1.05 3.3 0.45 208.18 105.85 31417 +1918 332 5.98 -0.02 4.33 0 222.23 138.83 31316 +1918 333 3.65 -2.35 2 0 191.56 139.18 31218 +1918 334 5.06 -0.94 3.41 0 209.65 137.24 31125 +1918 335 1.04 -4.96 -0.61 0.04 161.6 103.68 31035 +1918 336 1.05 -4.95 -0.6 0.06 161.71 102.86 30949 +1918 337 2.97 -3.03 1.32 0.31 183.33 100.89 30867 +1918 338 1.37 -4.63 -0.28 0.01 165.15 100.78 30790 +1918 339 3.2 -2.8 1.55 0 186.07 132.65 30716 +1918 340 4.56 -1.44 2.91 0 203.07 131.16 30647 +1918 341 5.03 -0.97 3.38 0 209.25 129.97 30582 +1918 342 8.03 2.03 6.38 0 252.61 127.24 30521 +1918 343 9.14 3.14 7.49 1.75 270.51 94.2 30465 +1918 344 9.35 3.35 7.7 0 274.01 124.32 30413 +1918 345 9.83 3.83 8.18 0.48 282.17 92.65 30366 +1918 346 4.97 -1.03 3.32 0 208.45 126.31 30323 +1918 347 3.53 -2.47 1.88 0 190.08 126.52 30284 +1918 348 5.72 -0.28 4.07 0 218.61 124.92 30251 +1918 349 6.37 0.37 4.72 0 227.75 124.14 30221 +1918 350 9.33 3.33 7.68 0 273.67 121.75 30197 +1918 351 9.27 3.27 7.62 0.29 272.67 91.18 30177 +1918 352 9.03 3.03 7.38 1.18 268.69 91.25 30162 +1918 353 7.52 1.52 5.87 0.41 244.74 92.01 30151 +1918 354 4.73 -1.27 3.08 0 205.29 124.38 30145 +1918 355 5.34 -0.66 3.69 0 213.41 124.03 30144 +1918 356 3.08 -2.92 1.43 0 184.64 125.3 30147 +1918 357 1.36 -4.64 -0.29 0.39 165.04 94.64 30156 +1918 358 2.87 -3.13 1.22 0 182.14 125.55 30169 +1918 359 4.83 -1.17 3.18 0.92 206.6 93.46 30186 +1918 360 5.18 -0.82 3.53 0 211.25 124.78 30208 +1918 361 4.91 -1.09 3.26 0 207.65 125.27 30235 +1918 362 2.9 -3.1 1.25 0 182.5 126.79 30267 +1918 363 4.48 -1.52 2.83 0 202.04 126.53 30303 +1918 364 5.72 -0.28 4.07 0 218.61 126.2 30343 +1918 365 6.51 0.51 4.86 0 229.76 126.26 30388 +1919 1 7.35 1.35 5.7 0 242.16 126.59 30438 +1919 2 5.42 -0.58 3.77 0 214.49 128.56 30492 +1919 3 5.11 -0.89 3.46 0 210.31 129.69 30551 +1919 4 6.5 0.5 4.85 0 229.62 129.72 30614 +1919 5 4.27 -1.73 2.62 0.05 199.34 98.8 30681 +1919 6 3.69 -2.31 2.04 0.02 192.05 99.71 30752 +1919 7 7.17 1.17 5.52 0.62 239.46 98.68 30828 +1919 8 4.35 -1.65 2.7 0.36 200.36 101.14 30907 +1919 9 2.8 -3.2 1.15 1.12 181.32 102.73 30991 +1919 10 2.34 -3.66 0.69 0.41 175.97 103.89 31079 +1919 11 4.91 -1.09 3.26 0.34 207.65 103.54 31171 +1919 12 11.02 5.02 9.37 0.49 303.3 100.83 31266 +1919 13 4.67 -1.33 3.02 0.01 204.5 105.62 31366 +1919 14 4.55 -1.45 2.9 0.13 202.94 106.78 31469 +1919 15 -0.42 -6.42 -2.07 0 146.68 146.42 31575 +1919 16 -0.29 -6.29 -1.94 0 147.96 147.66 31686 +1919 17 8.11 2.11 6.46 0 253.87 144.27 31800 +1919 18 7.67 1.67 6.02 0 247.03 146.49 31917 +1919 19 7.28 1.28 5.63 0 241.11 148.7 32038 +1919 20 6.8 0.8 5.15 0 233.98 150.63 32161 +1919 21 3.96 -2.04 2.31 0 195.41 154.55 32289 +1919 22 1.02 -4.98 -0.63 0.06 161.39 118.48 32419 +1919 23 2.13 -3.87 0.48 1.09 173.58 119.37 32552 +1919 24 0.27 -5.73 -1.38 0 153.58 162.22 32688 +1919 25 3.18 -2.82 1.53 0 185.83 162.51 32827 +1919 26 5.96 -0.04 4.31 0.07 221.95 121.93 32969 +1919 27 5.7 -0.3 4.05 0 218.33 164.78 33114 +1919 28 4.4 -1.6 2.75 0 201 167.89 33261 +1919 29 4.57 -1.43 2.92 0.19 203.2 127.61 33411 +1919 30 1.51 -4.49 -0.14 0.78 166.68 130.74 33564 +1919 31 0.82 -5.18 -0.83 0 159.27 177.1 33718 +1919 32 1.14 -4.86 -0.51 0.36 162.67 134.29 33875 +1919 33 -0.09 -6.09 -1.74 0 149.94 182.37 34035 +1919 34 3.32 -2.68 1.67 0 187.52 182.57 34196 +1919 35 6 0 4.35 0 222.51 182.76 34360 +1919 36 3.73 -2.27 2.08 0 192.55 186.96 34526 +1919 37 7.61 1.61 5.96 0 246.11 186.29 34694 +1919 38 4.19 -1.81 2.54 0 198.32 191.81 34863 +1919 39 4.48 -1.52 2.83 0 202.04 194.2 35035 +1919 40 2.12 -3.88 0.47 0.43 173.47 148.86 35208 +1919 41 0.74 -5.26 -0.91 0 158.43 201.97 35383 +1919 42 -1.24 -7.24 -2.89 0 138.83 205.67 35560 +1919 43 -1.55 -7.55 -3.2 0.18 135.96 193.85 35738 +1919 44 -3.1 -9.1 -4.75 0 122.37 249.18 35918 +1919 45 -0.77 -6.77 -2.42 0 143.28 250.46 36099 +1919 46 -0.14 -6.14 -1.79 0.04 149.44 198.8 36282 +1919 47 1.41 -4.59 -0.24 0.18 165.58 199.87 36466 +1919 48 4.13 -1.87 2.48 0 197.56 218.51 36652 +1919 49 6.87 0.87 5.22 0 235.01 218.88 36838 +1919 50 7.42 1.42 5.77 0 243.22 220.99 37026 +1919 51 5.41 -0.59 3.76 0 214.36 225.85 37215 +1919 52 7.41 1.41 5.76 0.01 243.07 170.07 37405 +1919 53 5.1 -0.9 3.45 0.24 210.18 173.94 37596 +1919 54 5.69 -0.31 4.04 0 218.19 234.14 37788 +1919 55 7.7 1.7 6.05 0 247.49 235.12 37981 +1919 56 6.52 0.52 4.87 0.2 229.91 179.26 38175 +1919 57 7.5 1.5 5.85 0.82 244.43 180.66 38370 +1919 58 3.92 -2.08 2.27 0.03 194.91 185.44 38565 +1919 59 4.52 -1.48 2.87 0 202.55 249.45 38761 +1919 60 11.72 5.72 10.07 0.16 316.34 183.03 38958 +1919 61 5.1 -0.9 3.45 0.53 210.18 191.07 39156 +1919 62 3.6 -2.4 1.95 0 190.94 258.93 39355 +1919 63 9.88 3.88 8.23 0 283.03 255.17 39553 +1919 64 11.53 5.53 9.88 0.16 312.76 191.81 39753 +1919 65 9.49 3.49 7.84 0 276.37 261.41 39953 +1919 66 7.12 1.12 5.47 0 238.71 267.01 40154 +1919 67 10.15 4.15 8.5 0 287.72 266.11 40355 +1919 68 7.88 1.88 6.23 0 250.27 271.89 40556 +1919 69 8.12 2.12 6.47 0 254.02 274.22 40758 +1919 70 3.69 -2.31 2.04 0 192.05 281.85 40960 +1919 71 4.75 -1.25 3.1 0 205.55 283.76 41163 +1919 72 7.77 1.77 6.12 0 248.57 283.22 41366 +1919 73 7.98 1.98 6.33 0 251.83 285.62 41569 +1919 74 5.74 -0.26 4.09 0.05 218.88 218.26 41772 +1919 75 9.21 3.21 7.56 0.34 271.67 217.1 41976 +1919 76 8.49 2.49 6.84 0 259.9 293.07 42179 +1919 77 8.02 2.02 6.37 0 252.46 296.29 42383 +1919 78 7.25 1.25 5.6 0.4 240.65 224.95 42587 +1919 79 10.87 4.87 9.22 0 300.56 297.58 42791 +1919 80 7.81 1.81 6.16 0.01 249.19 228.37 42996 +1919 81 9.73 3.73 8.08 0.74 280.45 228.3 43200 +1919 82 10.44 4.44 8.79 0 292.83 305.97 43404 +1919 83 11.61 5.61 9.96 0.02 314.26 229.9 43608 +1919 84 11.18 5.18 9.53 0.12 306.24 232.33 43812 +1919 85 11.91 5.91 10.26 0 319.97 311.01 44016 +1919 86 9.01 3.01 7.36 0 268.36 318.03 44220 +1919 87 7.64 1.64 5.99 0.28 246.57 241.87 44424 +1919 88 6.09 0.09 4.44 0 223.77 326.86 44627 +1919 89 11.68 5.68 10.03 0 315.59 320.89 44831 +1919 90 9.49 3.49 7.84 0.93 276.37 245.14 45034 +1919 91 8.33 2.33 6.68 0 257.34 330.84 45237 +1919 92 9.95 3.95 8.3 0.12 284.24 247.97 45439 +1919 93 10.85 4.85 9.2 0.46 300.2 248.52 45642 +1919 94 12.66 6.66 11.01 0 334.62 330.24 45843 +1919 95 11.65 5.65 10 0 315.02 334.24 46045 +1919 96 11.35 5.35 9.7 0.11 309.39 252.66 46246 +1919 97 10.16 4.16 8.51 0.03 287.9 255.74 46446 +1919 98 11.82 5.82 10.17 0 318.25 340.04 46647 +1919 99 9.78 3.78 8.13 1.12 281.31 259.2 46846 +1919 100 10.9 4.9 9.25 0 301.11 345.66 47045 +1919 101 13.49 7.49 11.84 0.17 351.51 256.97 47243 +1919 102 12.07 6.07 10.42 0.56 323.05 260.51 47441 +1919 103 14.96 8.96 13.31 0.03 383.2 257.35 47638 +1919 104 14.64 8.64 12.99 0.27 376.1 259.24 47834 +1919 105 13.16 7.16 11.51 0.05 344.71 262.97 48030 +1919 106 5.24 -0.76 3.59 0 212.06 365.24 48225 +1919 107 8.45 2.45 6.8 0.43 259.26 271.83 48419 +1919 108 8.66 2.66 7.01 0.57 262.64 272.91 48612 +1919 109 6.03 0.03 4.38 0 222.93 369.36 48804 +1919 110 7.22 1.22 5.57 0 240.2 369.14 48995 +1919 111 11.77 5.77 10.12 0 317.3 363.04 49185 +1919 112 13.25 7.25 11.6 0.02 346.55 271.17 49374 +1919 113 12.86 6.86 11.21 0.01 338.63 272.79 49561 +1919 114 13.69 7.69 12.04 0.27 355.68 272.57 49748 +1919 115 14.1 8.1 12.45 0.91 364.37 272.96 49933 +1919 116 9.61 3.61 7.96 0.04 278.4 280.55 50117 +1919 117 10.57 4.57 8.92 0 295.15 373.68 50300 +1919 118 12.26 6.26 10.61 0.16 326.74 278.81 50481 +1919 119 9.92 3.92 8.27 0.93 283.72 283.05 50661 +1919 120 10.89 4.89 9.24 0.38 300.92 282.61 50840 +1919 121 13.12 7.12 11.47 0.22 343.89 280.09 51016 +1919 122 14.5 8.5 12.85 0 373.03 371.54 51191 +1919 123 12.19 6.19 10.54 0.28 325.37 283.24 51365 +1919 124 8.49 2.49 6.84 0.16 259.9 289.17 51536 +1919 125 8.95 2.95 7.3 0.65 267.37 289.35 51706 +1919 126 11.65 5.65 10 0.39 315.02 286.39 51874 +1919 127 12.42 6.42 10.77 0.07 329.87 285.88 52039 +1919 128 12.3 6.3 10.65 0 327.52 382.43 52203 +1919 129 12.09 6.09 10.44 0.33 323.43 287.8 52365 +1919 130 9.84 3.84 8.19 0.33 282.34 291.67 52524 +1919 131 8.71 2.71 7.06 0.63 263.45 293.75 52681 +1919 132 8.56 2.56 6.91 0.13 261.02 294.58 52836 +1919 133 12.98 6.98 11.33 1.23 341.05 288.75 52989 +1919 134 13.48 7.48 11.83 0.84 351.3 288.46 53138 +1919 135 17.97 11.97 16.32 0 455.76 373.65 53286 +1919 136 17.72 11.72 16.07 0 449.31 375.02 53430 +1919 137 14.89 8.89 13.24 0.18 381.63 287.5 53572 +1919 138 15.83 9.83 14.18 0 403.08 381.55 53711 +1919 139 19.79 13.79 18.14 0.89 505.07 277.92 53848 +1919 140 18.62 12.62 16.97 0.6 472.87 281.08 53981 +1919 141 21.36 15.36 19.71 0.24 551.18 274.53 54111 +1919 142 18.32 12.32 16.67 0.16 464.91 282.47 54238 +1919 143 15.92 9.92 14.27 0 405.18 383.97 54362 +1919 144 14.86 8.86 13.21 0 380.96 387.17 54483 +1919 145 10.56 4.56 8.91 0 294.97 397.07 54600 +1919 146 16.77 10.77 15.12 0 425.54 382.99 54714 +1919 147 14.81 8.81 13.16 0 379.85 388.63 54824 +1919 148 16.16 10.16 14.51 0 410.84 385.53 54931 +1919 149 18.52 12.52 16.87 0.2 470.21 284.27 55034 +1919 150 20.01 14.01 18.36 0 511.32 374.54 55134 +1919 151 19.91 13.91 18.26 0.02 508.47 281.45 55229 +1919 152 23.11 17.11 21.46 0.01 606.75 272.7 55321 +1919 153 23.67 17.67 22.02 0.41 625.5 271.16 55409 +1919 154 23.99 17.99 22.34 0.27 636.44 270.39 55492 +1919 155 19.95 13.95 18.3 0 509.61 375.98 55572 +1919 156 20.4 14.4 18.75 0.13 522.58 281.07 55648 +1919 157 23.72 17.72 22.07 0 627.2 362.31 55719 +1919 158 24.36 18.36 22.71 0 649.28 359.76 55786 +1919 159 24.41 18.41 22.76 0.07 651.04 269.84 55849 +1919 160 18.18 12.18 16.53 0.05 461.23 287.06 55908 +1919 161 19.07 13.07 17.42 0.31 485.04 285.02 55962 +1919 162 19.96 13.96 18.31 0.14 509.9 282.87 56011 +1919 163 18.37 12.37 16.72 0.42 466.23 286.88 56056 +1919 164 15.34 9.34 13.69 0 391.77 391.12 56097 +1919 165 14.95 8.95 13.3 0.02 382.97 294.16 56133 +1919 166 15.22 9.22 13.57 0 389.05 391.6 56165 +1919 167 18.28 12.28 16.63 1.11 463.85 287.21 56192 +1919 168 14.98 8.98 13.33 0.23 383.64 294.18 56214 +1919 169 13.54 7.54 11.89 0.31 352.55 296.81 56231 +1919 170 13.64 7.64 11.99 0 354.63 395.51 56244 +1919 171 13.4 7.4 11.75 0 349.64 396.13 56252 +1919 172 17.61 11.61 15.96 0 446.5 385.11 56256 +1919 173 20.34 14.34 18.69 0.1 520.83 282.27 56255 +1919 174 20.38 14.38 18.73 2.83 522 282.1 56249 +1919 175 18.3 12.3 16.65 0 464.38 382.9 56238 +1919 176 19.01 13.01 17.36 0 483.41 380.63 56223 +1919 177 20.86 14.86 19.21 0.51 536.12 280.71 56203 +1919 178 23.66 17.66 22.01 0.65 625.16 272.65 56179 +1919 179 22.3 16.3 20.65 0.4 580.46 276.66 56150 +1919 180 24.28 18.28 22.63 0.04 646.49 270.52 56116 +1919 181 24.96 18.96 23.31 0.05 670.58 268.23 56078 +1919 182 27.9 21.9 26.25 0.19 783.7 257.46 56035 +1919 183 23.13 17.13 21.48 0.02 607.41 273.82 55987 +1919 184 20.73 14.73 19.08 0 532.26 374 55935 +1919 185 17.99 11.99 16.34 0.67 456.27 287.14 55879 +1919 186 17.89 11.89 16.24 0 453.69 382.89 55818 +1919 187 18.06 12.06 16.41 0.87 458.09 286.65 55753 +1919 188 17.74 11.74 16.09 0.42 449.83 287.16 55684 +1919 189 15.54 9.54 13.89 0.15 396.35 291.61 55611 +1919 190 11.65 5.65 10 0 315.02 397.47 55533 +1919 191 20.1 14.1 18.45 0 513.9 374.57 55451 +1919 192 18.36 12.36 16.71 0.83 465.96 284.91 55366 +1919 193 14.79 8.79 13.14 0.68 379.41 292.11 55276 +1919 194 10.17 4.17 8.52 0.89 288.07 299.44 55182 +1919 195 10.91 4.91 9.26 0.09 301.29 298.16 55085 +1919 196 18.75 12.75 17.1 0.26 476.36 283.11 54984 +1919 197 21.71 15.71 20.06 0.33 561.93 275.2 54879 +1919 198 20.45 14.45 18.8 0 524.04 371.01 54770 +1919 199 22.15 16.15 20.5 0.19 575.7 273.39 54658 +1919 200 20.35 14.35 18.7 1.16 521.12 277.95 54542 +1919 201 19.54 13.54 17.89 0.34 498.04 279.62 54423 +1919 202 19.93 13.93 18.28 0.09 509.04 278.24 54301 +1919 203 24.19 18.19 22.54 0.06 643.35 265.85 54176 +1919 204 27.91 21.91 26.26 0.31 784.11 252.44 54047 +1919 205 26.44 20.44 24.79 0 725.66 343.39 53915 +1919 206 25.13 19.13 23.48 1.66 676.72 261.65 53780 +1919 207 27.09 21.09 25.44 0.13 751.04 254.31 53643 +1919 208 24.69 18.69 23.04 0.1 660.93 262.14 53502 +1919 209 24 18 22.35 0.19 636.78 263.86 53359 +1919 210 22.31 16.31 20.66 0.04 580.78 268.42 53213 +1919 211 19.35 13.35 17.7 0 492.75 367.39 53064 +1919 212 21.51 15.51 19.86 0 555.77 359.28 52913 +1919 213 23.18 17.18 21.53 0.45 609.06 264.18 52760 +1919 214 23.14 17.14 21.49 0.74 607.74 263.76 52604 +1919 215 16.36 10.36 14.71 0.06 415.61 279.81 52445 +1919 216 14.69 8.69 13.04 0 377.2 376.27 52285 +1919 217 15.66 9.66 14.01 0 399.12 372.95 52122 +1919 218 17.27 11.27 15.62 0 437.91 367.82 51958 +1919 219 16.09 10.09 14.44 0 409.18 369.94 51791 +1919 220 17.64 11.64 15.99 0 447.27 364.76 51622 +1919 221 19.19 13.19 17.54 0.07 488.33 269.36 51451 +1919 222 22.11 16.11 20.46 0.4 574.44 261.21 51279 +1919 223 20.75 14.75 19.1 0.35 532.86 263.94 51105 +1919 224 19.97 13.97 18.32 0 510.18 353.43 50929 +1919 225 22.12 16.12 20.47 0.06 574.76 258.71 50751 +1919 226 25.92 19.92 24.27 0.25 705.89 246.4 50572 +1919 227 25.38 19.38 23.73 0 685.84 329.69 50392 +1919 228 26.42 20.42 24.77 1.07 724.89 242.94 50210 +1919 229 25.43 19.43 23.78 0.49 687.68 245.35 50026 +1919 230 24.87 18.87 23.22 0 667.35 328.29 49842 +1919 231 25.28 19.28 23.63 0 682.18 325.15 49656 +1919 232 22.01 16.01 20.36 0 571.29 336.53 49469 +1919 233 28.43 22.43 26.78 0 805.71 308.02 49280 +1919 234 24.09 18.09 22.44 0 639.89 326 49091 +1919 235 25.4 19.4 23.75 0.81 686.58 239.43 48900 +1919 236 29 23 27.35 0 829.97 301.18 48709 +1919 237 26.55 20.55 24.9 0 729.9 311.35 48516 +1919 238 26.37 20.37 24.72 0 722.97 310.57 48323 +1919 239 27.37 21.37 25.72 0.13 762.19 228.49 48128 +1919 240 25.16 19.16 23.51 0.94 677.81 234.46 47933 +1919 241 21.68 15.68 20.03 0 561.01 323.88 47737 +1919 242 18.16 12.16 16.51 0 460.7 332.85 47541 +1919 243 16.63 10.63 14.98 0.19 422.13 251.23 47343 +1919 244 14.4 8.4 12.75 0.91 370.85 253.74 47145 +1919 245 18.23 12.23 16.58 1.26 462.54 245.34 46947 +1919 246 18.43 12.43 16.78 0.51 467.81 243.46 46747 +1919 247 20.92 14.92 19.27 0 537.91 315.48 46547 +1919 248 24.58 18.58 22.93 0.02 657.03 225.67 46347 +1919 249 24.96 18.96 23.31 0.16 670.58 223.1 46146 +1919 250 21.48 15.48 19.83 0.01 554.85 230.91 45945 +1919 251 22.14 16.14 20.49 0.17 575.39 227.77 45743 +1919 252 21.82 15.82 20.17 0 565.35 302.63 45541 +1919 253 19.32 13.32 17.67 0 491.92 308.05 45339 +1919 254 17.22 11.22 15.57 0 436.66 311.41 45136 +1919 255 14.45 8.45 12.8 0 371.94 315.39 44933 +1919 256 18.44 12.44 16.79 0.19 468.08 227.87 44730 +1919 257 15.34 9.34 13.69 0 391.77 309.02 44527 +1919 258 19.09 13.09 17.44 0 485.59 297.66 44323 +1919 259 20.53 14.53 18.88 0 526.38 291.28 44119 +1919 260 23.76 17.76 22.11 0 628.56 278.81 43915 +1919 261 25.67 19.67 24.02 1.21 696.55 202.21 43711 +1919 262 21.4 15.4 19.75 0.04 552.4 211.3 43507 +1919 263 22.16 16.16 20.51 0 576.02 277.06 43303 +1919 264 23.79 17.79 22.14 0 629.58 269.36 43099 +1919 265 22.03 16.03 20.38 0 571.92 272.72 42894 +1919 266 26.72 20.72 25.07 0 736.5 254.27 42690 +1919 267 24.98 18.98 23.33 0.05 671.3 193.66 42486 +1919 268 24.23 18.23 22.58 0.61 644.75 193.79 42282 +1919 269 18.35 12.35 16.7 1.91 465.7 204.52 42078 +1919 270 18.19 12.19 16.54 0.08 461.49 202.86 41875 +1919 271 18.08 12.08 16.43 0 458.62 268.16 41671 +1919 272 16.32 10.32 14.67 0.02 414.65 201.99 41468 +1919 273 15.54 9.54 13.89 0 396.35 268.38 41265 +1919 274 11.91 5.91 10.26 0.26 319.97 204.07 41062 +1919 275 9.15 3.15 7.5 0.26 270.67 204.94 40860 +1919 276 16.1 10.1 14.45 0.93 409.42 194.4 40658 +1919 277 16.42 10.42 14.77 0.28 417.05 191.95 40456 +1919 278 16.09 10.09 14.44 1.3 409.18 190.31 40255 +1919 279 14.46 8.46 12.81 0.06 372.15 190.49 40054 +1919 280 16.25 10.25 14.6 0 412.98 248.05 39854 +1919 281 15.9 9.9 14.25 0 404.71 246.04 39654 +1919 282 17.84 11.84 16.19 0 452.4 239.48 39455 +1919 283 17.71 11.71 16.06 0 449.06 237 39256 +1919 284 9.27 3.27 7.62 0.08 272.67 185.73 39058 +1919 285 9.96 3.96 8.31 0.97 284.41 183.08 38861 +1919 286 11.84 5.84 10.19 0 318.63 238.79 38664 +1919 287 5.11 -0.89 3.46 0 210.31 243.58 38468 +1919 288 4.22 -1.78 2.57 0 198.7 241.51 38273 +1919 289 3.91 -2.09 2.26 0 194.79 239.06 38079 +1919 290 8.85 2.85 7.2 0 265.73 231.29 37885 +1919 291 8 2 6.35 0 252.14 229.49 37693 +1919 292 9.01 3.01 7.36 0.55 268.36 169.24 37501 +1919 293 10.15 4.15 8.5 0.73 287.72 166.17 37311 +1919 294 16.11 10.11 14.46 0.01 409.66 157.57 37121 +1919 295 18.35 12.35 16.7 0.01 465.7 152.45 36933 +1919 296 13.1 7.1 11.45 0.19 343.48 157.07 36745 +1919 297 9.95 3.95 8.3 0 284.24 210.71 36560 +1919 298 9.43 3.43 7.78 0 275.36 208.67 36375 +1919 299 12.83 6.83 11.18 0 338.02 201.75 36191 +1919 300 14.38 8.38 12.73 0 370.41 196.95 36009 +1919 301 12.63 6.63 10.98 0 334.03 196.88 35829 +1919 302 11.29 5.29 9.64 0 308.27 195.95 35650 +1919 303 7.63 1.63 5.98 0.03 246.42 147.93 35472 +1919 304 8.19 2.19 6.54 0.4 255.13 145.67 35296 +1919 305 2 -4 0.35 0.95 172.11 147.26 35122 +1919 306 5.26 -0.74 3.61 0 212.33 191.74 34950 +1919 307 5.49 -0.51 3.84 0.41 215.45 141.76 34779 +1919 308 4.34 -1.66 2.69 0.05 200.23 140.44 34610 +1919 309 6.75 0.75 5.1 0.26 233.25 137.27 34444 +1919 310 9.35 3.35 7.7 0.16 274.01 133.66 34279 +1919 311 7.23 1.23 5.58 0 240.35 177.97 34116 +1919 312 3.85 -2.15 2.2 0 194.04 177.88 33956 +1919 313 6.61 0.61 4.96 0.52 231.21 130.27 33797 +1919 314 8.41 2.41 6.76 1.63 258.62 127.66 33641 +1919 315 5.65 -0.35 4 0.22 217.64 127.44 33488 +1919 316 6.87 0.87 5.22 0 235.01 166.79 33337 +1919 317 5.79 -0.21 4.14 0.35 219.58 124.06 33188 +1919 318 3.33 -2.67 1.68 1.3 187.64 123.54 33042 +1919 319 3.94 -2.06 2.29 0.08 195.16 121.97 32899 +1919 320 4.87 -1.13 3.22 0 207.13 160.12 32758 +1919 321 6.63 0.63 4.98 0 231.5 156.76 32620 +1919 322 4.02 -1.98 2.37 0 196.17 156.72 32486 +1919 323 3.89 -2.11 2.24 0 194.54 155.17 32354 +1919 324 2.15 -3.85 0.5 0 173.81 154.11 32225 +1919 325 3.16 -2.84 1.51 0 185.59 151.8 32100 +1919 326 4.55 -1.45 2.9 0.32 202.94 112.12 31977 +1919 327 7.99 1.99 6.34 0.01 251.99 108.92 31858 +1919 328 14.9 8.9 13.25 0 381.86 136.58 31743 +1919 329 13 7 11.35 0.06 341.45 102.94 31631 +1919 330 3.87 -2.13 2.22 0.11 194.29 107.34 31522 +1919 331 8.23 2.23 6.58 1.38 255.76 104.14 31417 +1919 332 9.75 3.75 8.1 0.04 280.79 102 31316 +1919 333 8.07 2.07 6.42 0 253.24 136.27 31218 +1919 334 8.43 2.43 6.78 0.04 258.94 101.18 31125 +1919 335 11.35 5.35 9.7 0 309.39 131.31 31035 +1919 336 10.43 4.43 8.78 0 292.66 131.08 30949 +1919 337 7.3 1.3 5.65 0.02 241.41 98.9 30867 +1919 338 3.99 -2.01 2.34 0.07 195.79 99.76 30790 +1919 339 7.43 1.43 5.78 0 243.37 130.06 30716 +1919 340 6.3 0.3 4.65 0.26 226.75 97.57 30647 +1919 341 3.19 -2.81 1.54 0.17 185.95 98.25 30582 +1919 342 -0.33 -6.33 -1.98 0.52 147.56 143.8 30521 +1919 343 -3.11 -9.11 -4.76 0 122.28 177.07 30465 +1919 344 1.09 -4.91 -0.56 0.04 162.13 141.87 30413 +1919 345 5.29 -0.71 3.64 0 212.73 170.94 30366 +1919 346 5.12 -0.88 3.47 0.04 210.45 138.32 30323 +1919 347 3.82 -2.18 2.17 0.49 193.66 94.77 30284 +1919 348 3.95 -2.05 2.3 0.25 195.29 94.46 30251 +1919 349 2.75 -3.25 1.1 0.22 180.73 94.64 30221 +1919 350 1.37 -4.63 -0.28 0.06 165.15 94.88 30197 +1919 351 5.21 -0.79 3.56 0.09 211.65 93.22 30177 +1919 352 5.48 -0.52 3.83 0 215.31 124.04 30162 +1919 353 4.51 -1.49 2.86 0 202.42 124.54 30151 +1919 354 0.65 -5.35 -1 0 157.49 126.41 30145 +1919 355 4.69 -1.31 3.04 0 204.76 124.4 30144 +1919 356 2.57 -3.43 0.92 0 178.63 125.55 30147 +1919 357 1.9 -4.1 0.25 0 170.99 125.93 30156 +1919 358 0.52 -5.48 -1.13 0 156.14 126.64 30169 +1919 359 1.05 -4.95 -0.6 0 161.71 126.53 30186 +1919 360 6.55 0.55 4.9 0 230.34 123.94 30208 +1919 361 5.21 -0.79 3.56 0 211.65 125.09 30235 +1919 362 5.47 -0.53 3.82 0.03 215.17 94.03 30267 +1919 363 6.55 0.55 4.9 0 230.34 125.28 30303 +1919 364 6.73 0.73 5.08 0 232.96 125.56 30343 +1919 365 3.48 -2.52 1.83 0 189.47 128.04 30388 +1920 1 3.58 -2.42 1.93 0 190.7 128.88 30438 +1920 2 3.51 -2.49 1.86 0 189.84 129.65 30492 +1920 3 1.87 -4.13 0.22 0 170.65 131.43 30551 +1920 4 0.1 -5.9 -1.55 0 151.85 133.16 30614 +1920 5 5.07 -0.93 3.42 0 209.78 131.26 30681 +1920 6 4.44 -1.56 2.79 0 201.52 132.52 30752 +1920 7 2.73 -3.27 1.08 0.85 180.49 100.69 30828 +1920 8 3.72 -2.28 2.07 0 192.42 135.21 30907 +1920 9 2.88 -3.12 1.23 0 182.26 136.93 30991 +1920 10 3.99 -2.01 2.34 0 195.79 137.62 31079 +1920 11 9.02 3.02 7.37 0 268.52 135.16 31171 +1920 12 5.61 -0.39 3.96 0.06 217.09 103.96 31266 +1920 13 2.88 -3.12 1.23 0.87 182.26 106.39 31366 +1920 14 2.18 -3.82 0.53 0 174.15 143.71 31469 +1920 15 4.3 -1.7 2.65 0 199.72 143.96 31575 +1920 16 5.92 -0.08 4.27 0.44 221.39 108.15 31686 +1920 17 2.18 -3.82 0.53 0 174.15 148.15 31800 +1920 18 3.24 -2.76 1.59 0 186.56 149.46 31917 +1920 19 5.59 -0.41 3.94 0 216.82 149.91 32038 +1920 20 8.63 2.63 6.98 0 262.15 149.2 32161 +1920 21 9.93 3.93 8.28 0 283.89 150.04 32289 +1920 22 8.35 2.35 6.7 0.04 257.66 114.85 32419 +1920 23 7.79 1.79 6.14 0.26 248.88 116.5 32552 +1920 24 9.33 3.33 7.68 0 273.67 156.06 32688 +1920 25 13.16 7.16 11.51 0 344.71 154.01 32827 +1920 26 11.12 5.12 9.47 0.34 305.13 118.56 32969 +1920 27 8.79 2.79 7.14 0.68 264.75 121.71 33114 +1920 28 3.71 -2.29 2.06 0 192.3 168.35 33261 +1920 29 4.89 -1.11 3.24 0 207.39 169.93 33411 +1920 30 4.64 -1.36 2.99 0.05 204.11 129.26 33564 +1920 31 5.12 -0.88 3.47 0.51 210.45 130.78 33718 +1920 32 3.21 -2.79 1.56 0 186.2 177.8 33875 +1920 33 2.82 -3.18 1.17 0 181.55 180.68 34035 +1920 34 1.86 -4.14 0.21 0.01 170.54 137.62 34196 +1920 35 2.5 -3.5 0.85 0 177.82 185.26 34360 +1920 36 0.29 -5.71 -1.36 0 153.78 189.1 34526 +1920 37 2.65 -3.35 1 0 179.56 190.12 34694 +1920 38 2.68 -3.32 1.03 0 179.91 192.85 34863 +1920 39 6.32 0.32 4.67 0 227.04 192.73 35035 +1920 40 8.21 2.21 6.56 0 255.44 193.62 35208 +1920 41 9.19 3.19 7.54 0 271.34 195.23 35383 +1920 42 7.58 1.58 5.93 0 245.65 199.35 35560 +1920 43 7.19 1.19 5.54 0 239.76 202.39 35738 +1920 44 8.43 2.43 6.78 0 258.94 203.73 35918 +1920 45 8.02 2.02 6.37 0 252.46 206.74 36099 +1920 46 10.28 4.28 8.63 0.13 290 155.22 36282 +1920 47 7.72 1.72 6.07 0.1 247.8 159.37 36466 +1920 48 3.43 -2.57 1.78 0 188.86 219.05 36652 +1920 49 5.53 -0.47 3.88 0 215.99 220.11 36838 +1920 50 4.96 -1.04 3.31 0 208.32 223.27 37026 +1920 51 3.34 -2.66 1.69 0 187.77 227.57 37215 +1920 52 4.52 -1.48 2.87 0 202.55 229.46 37405 +1920 53 6.97 0.97 5.32 0 236.48 230.15 37596 +1920 54 9.45 3.45 7.8 0 275.69 230.18 37788 +1920 55 9.82 3.82 8.17 0 282 232.69 37981 +1920 56 13.46 7.46 11.81 0 350.88 230.32 38175 +1920 57 10.74 4.74 9.09 0.01 298.21 177.76 38370 +1920 58 7.19 1.19 5.54 0 239.76 244.12 38565 +1920 59 9.65 3.65 8 0 279.08 243.97 38761 +1920 60 12.22 6.22 10.57 0 325.96 243.31 38958 +1920 61 16.47 10.47 14.82 0 418.26 238.97 39156 +1920 62 13.69 7.69 12.04 0 355.68 246.61 39355 +1920 63 16.15 10.15 14.5 0 410.61 245.15 39553 +1920 64 19.73 13.73 18.08 0 503.37 240.25 39753 +1920 65 20.04 14.04 18.39 0 512.18 242.21 39953 +1920 66 18.73 12.73 17.08 0 475.82 247.88 40154 +1920 67 18.46 12.46 16.81 0 468.61 251.24 40355 +1920 68 16.74 10.74 15.09 0 424.8 257.71 40556 +1920 69 10.46 4.46 8.81 0.42 293.19 203.34 40758 +1920 70 11.14 5.14 9.49 0.22 305.5 204.7 40960 +1920 71 10.33 4.33 8.68 0.02 290.89 207.75 41163 +1920 72 9.47 3.47 7.82 0.23 276.03 210.76 41366 +1920 73 7.43 1.43 5.78 0.18 243.37 214.73 41569 +1920 74 4.95 -1.05 3.3 0.01 208.18 218.89 41772 +1920 75 5.46 -0.54 3.81 0 215.04 294.07 41976 +1920 76 8.33 2.33 6.68 0 257.34 293.28 42179 +1920 77 7.02 1.02 5.37 0 237.22 297.54 42383 +1920 78 7.65 1.65 6 0.16 246.72 224.57 42587 +1920 79 7.52 1.52 5.87 0 244.74 302.33 42791 +1920 80 8.94 2.94 7.29 0 267.2 302.97 42996 +1920 81 9.73 3.73 8.08 0.09 280.45 228.3 43200 +1920 82 7.24 1.24 5.59 0.07 240.5 232.86 43404 +1920 83 7.16 1.16 5.51 0.01 239.31 234.82 43608 +1920 84 6.73 0.73 5.08 0 232.96 316.19 43812 +1920 85 2.93 -3.07 1.28 0 182.85 322.94 44016 +1920 86 1.99 -4.01 0.34 0 172 326.29 44220 +1920 87 5.24 -0.76 3.59 0 212.06 325.49 44424 +1920 88 8.23 2.23 6.58 0 255.76 324.05 44627 +1920 89 8.08 2.08 6.43 0 253.4 326.55 44831 +1920 90 12.92 6.92 11.27 0 339.83 320.97 45034 +1920 91 15.87 9.87 14.22 0 404.01 317.03 45237 +1920 92 16.34 10.34 14.69 0 415.13 318.12 45439 +1920 93 19.39 13.39 17.74 0 493.86 312.37 45642 +1920 94 19.22 13.22 17.57 0 489.16 314.91 45843 +1920 95 15.94 9.94 14.29 0.09 405.65 244.05 46045 +1920 96 12.38 6.38 10.73 0 329.09 334.99 46246 +1920 97 10.67 4.67 9.02 0 296.95 340.13 46446 +1920 98 12.35 6.35 10.7 1.27 328.5 254.28 46647 +1920 99 13.68 7.68 12.03 0.04 355.47 253.79 46846 +1920 100 16.62 10.62 14.97 0.02 421.88 250.2 47045 +1920 101 19.08 13.08 17.43 0.39 485.32 246.66 47243 +1920 102 18.56 12.56 16.91 0.03 471.27 249.15 47441 +1920 103 18.17 12.17 16.52 0.73 460.97 251.3 47638 +1920 104 11.1 5.1 9.45 0.02 304.76 264.62 47834 +1920 105 9.32 3.32 7.67 0 273.51 357.69 48030 +1920 106 12.17 6.17 10.52 0.01 324.99 265.69 48225 +1920 107 15.59 9.59 13.94 0 397.51 348.49 48419 +1920 108 17.73 11.73 16.08 0 449.57 344.7 48612 +1920 109 14.4 8.4 12.75 0 370.85 354.57 48804 +1920 110 15.16 9.16 13.51 0 387.69 354.21 48995 +1920 111 14.39 8.39 12.74 0 370.63 357.53 49185 +1920 112 14.11 8.11 12.46 0 364.59 359.68 49374 +1920 113 17.45 11.45 15.8 0 442.44 352.71 49561 +1920 114 16.45 10.45 14.8 0 417.77 356.84 49748 +1920 115 18.47 12.47 16.82 0.19 468.88 264.51 49933 +1920 116 19.42 13.42 17.77 0.01 494.69 263.25 50117 +1920 117 17.97 11.97 16.32 1.72 455.76 267.44 50300 +1920 118 15.12 9.12 13.47 0.19 386.79 274.04 50481 +1920 119 14.36 8.36 12.71 0.29 369.98 276.28 50661 +1920 120 13.37 7.37 11.72 0 349.02 371.78 50840 +1920 121 19.67 13.67 18.02 0.01 501.68 267.11 51016 +1920 122 17.67 11.67 16.02 0 448.04 363.33 51191 +1920 123 14.98 8.98 13.33 0.27 383.64 278.56 51365 +1920 124 17 11 15.35 0.16 431.19 275.46 51536 +1920 125 15.58 9.58 13.93 0.03 397.27 278.99 51706 +1920 126 19.3 13.3 17.65 0 491.36 362.46 51874 +1920 127 20.78 14.78 19.13 0 533.75 358.46 52039 +1920 128 22.86 16.86 21.21 0 598.53 351.85 52203 +1920 129 22.02 16.02 20.37 0.1 571.61 266.87 52365 +1920 130 23.99 17.99 22.34 0.36 636.44 261.67 52524 +1920 131 23.32 17.32 21.67 0.04 613.72 264.27 52681 +1920 132 24.95 18.95 23.3 0.48 670.22 259.77 52836 +1920 133 22.56 16.56 20.91 0 588.79 356.79 52989 +1920 134 22.84 16.84 21.19 0.28 597.88 267.29 53138 +1920 135 19.37 13.37 17.72 1.22 493.3 277.01 53286 +1920 136 18.13 12.13 16.48 1.35 459.92 280.36 53430 +1920 137 16.74 10.74 15.09 0.12 424.8 283.87 53572 +1920 138 16.71 10.71 15.06 0 424.07 379.18 53711 +1920 139 20.63 14.63 18.98 0.09 529.31 275.8 53848 +1920 140 17.79 11.79 16.14 0.19 451.11 282.96 53981 +1920 141 19.95 13.95 18.3 0.27 509.61 278.2 54111 +1920 142 19.34 13.34 17.69 0 492.47 373.43 54238 +1920 143 19.74 13.74 18.09 0.58 503.65 279.49 54362 +1920 144 17.87 11.87 16.22 0.36 453.17 284.23 54483 +1920 145 19.31 13.31 17.66 0.2 491.64 281.24 54600 +1920 146 17.12 11.12 15.47 0 434.17 382.01 54714 +1920 147 19.7 13.7 18.05 0.8 502.53 280.92 54824 +1920 148 18.48 12.48 16.83 0.53 469.14 284.13 54931 +1920 149 20.54 14.54 18.89 0.49 526.67 279.3 55034 +1920 150 17.39 11.39 15.74 0.03 440.93 287.05 55134 +1920 151 22.61 16.61 20.96 0.31 590.41 274.11 55229 +1920 152 24.13 18.13 22.48 0 641.27 359.39 55321 +1920 153 24.18 18.18 22.53 0.38 643.01 269.55 55409 +1920 154 21.03 15.03 19.38 3.98 541.2 279.03 55492 +1920 155 19.2 13.2 17.55 0.27 488.61 283.84 55572 +1920 156 20.85 14.85 19.2 0.03 535.82 279.89 55648 +1920 157 20.44 14.44 18.79 0 523.74 374.79 55719 +1920 158 19.44 13.44 17.79 0 495.25 378.34 55786 +1920 159 21.69 15.69 20.04 0 561.31 370.71 55849 +1920 160 24.58 18.58 22.93 0.01 657.03 269.41 55908 +1920 161 20.87 14.87 19.22 0.25 536.42 280.46 55962 +1920 162 21.19 15.19 19.54 0 546.02 372.85 56011 +1920 163 20.51 14.51 18.86 0.32 525.79 281.61 56056 +1920 164 19.59 13.59 17.94 1.09 499.44 283.99 56097 +1920 165 18.76 12.76 17.11 0.33 476.63 286.07 56133 +1920 166 20.35 14.35 18.7 0 521.12 376.25 56165 +1920 167 18.69 12.69 17.04 0.23 474.75 286.26 56192 +1920 168 18.17 12.17 16.52 0.35 460.97 287.52 56214 +1920 169 18.03 12.03 16.38 0.43 457.31 287.85 56231 +1920 170 20.38 14.38 18.73 0.05 522 282.14 56244 +1920 171 16.96 10.96 15.31 1.32 430.2 290.25 56252 +1920 172 18.61 12.61 16.96 0.33 472.61 286.55 56256 +1920 173 19.2 13.2 17.55 0.25 488.61 285.13 56255 +1920 174 18.48 12.48 16.83 0.04 469.14 286.78 56249 +1920 175 15.38 9.38 13.73 0 392.69 391.15 56238 +1920 176 18.69 12.69 17.04 0 474.75 381.65 56223 +1920 177 16.74 10.74 15.09 0 424.8 387.34 56203 +1920 178 17.56 11.56 15.91 0.6 445.23 288.75 56179 +1920 179 18.55 12.55 16.9 0 471 381.9 56150 +1920 180 19 13 17.35 0 483.13 380.36 56116 +1920 181 18.64 12.64 16.99 0.1 473.41 286.07 56078 +1920 182 22.17 16.17 20.52 0 576.34 369.04 56035 +1920 183 24.77 18.77 23.12 0 663.78 358.17 55987 +1920 184 24.77 18.77 23.12 0.68 663.78 268.52 55935 +1920 185 22.01 16.01 20.36 0 571.29 369.24 55879 +1920 186 24.01 18.01 22.36 0.01 637.13 270.73 55818 +1920 187 22.38 16.38 20.73 0.1 583.02 275.54 55753 +1920 188 22.44 16.44 20.79 0.02 584.94 275.17 55684 +1920 189 27.17 21.17 25.52 0 754.21 345.79 55611 +1920 190 23.32 17.32 21.67 1.39 613.72 272.14 55533 +1920 191 23 17 21.35 0.81 603.12 272.92 55451 +1920 192 25.09 19.09 23.44 1.47 675.27 266.07 55366 +1920 193 24.8 18.8 23.15 0.67 664.85 266.84 55276 +1920 194 26.62 20.62 24.97 0.35 732.62 260.36 55182 +1920 195 26.44 20.44 24.79 0.1 725.66 260.82 55085 +1920 196 23.09 17.09 21.44 0 606.09 362.08 54984 +1920 197 22.58 16.58 20.93 0.37 589.44 272.73 54879 +1920 198 26.33 20.33 24.68 0.25 721.44 260.3 54770 +1920 199 27.97 21.97 26.32 0 786.58 338.56 54658 +1920 200 27.43 21.43 25.78 0 764.6 340.96 54542 +1920 201 28.74 22.74 27.09 0.49 818.83 250.25 54423 +1920 202 24.15 18.15 22.5 1.29 641.97 266.34 54301 +1920 203 21.05 15.05 19.4 0.89 541.8 274.97 54176 +1920 204 25.4 19.4 23.75 0 686.58 348.7 54047 +1920 205 25.48 19.48 23.83 0.13 689.52 260.88 53915 +1920 206 26.18 20.18 24.53 0.57 715.72 258.06 53780 +1920 207 19.47 13.47 17.82 0.35 496.08 277.29 53643 +1920 208 19.17 13.17 17.52 0.25 487.78 277.52 53502 +1920 209 20.82 14.82 19.17 1.1 534.93 272.93 53359 +1920 210 18.1 12.1 16.45 0 459.14 372.02 53213 +1920 211 14.23 8.23 12.58 0 367.17 381.49 53064 +1920 212 20 14 18.35 0 511.04 364.49 52913 +1920 213 20.77 14.77 19.12 0.26 533.45 270.85 52760 +1920 214 20.19 14.19 18.54 0 516.49 362.35 52604 +1920 215 17.81 11.81 16.16 0.01 451.62 276.79 52445 +1920 216 21.64 15.64 19.99 0 559.77 355.65 52285 +1920 217 22.24 16.24 20.59 0.53 578.56 264.43 52122 +1920 218 21.26 15.26 19.61 0.08 548.14 266.48 51958 +1920 219 20.94 14.94 19.29 0.05 538.51 266.53 51791 +1920 220 20.64 14.64 18.99 0.03 529.61 266.6 51622 +1920 221 19.71 13.71 18.06 0.12 502.81 268.14 51451 +1920 222 16.07 10.07 14.42 0.4 408.71 275.19 51279 +1920 223 17.38 11.38 15.73 0 440.68 362.25 51105 +1920 224 16.94 10.94 15.29 1.41 429.71 271.79 50929 +1920 225 17.56 11.56 15.91 0 445.23 359.52 50751 +1920 226 19.24 13.24 17.59 0 489.71 353.44 50572 +1920 227 20.42 14.42 18.77 0.67 523.16 261.31 50392 +1920 228 21.34 15.34 19.69 0.44 550.57 258.09 50210 +1920 229 23.92 17.92 22.27 0 634.03 333.37 50026 +1920 230 24.61 18.61 22.96 0 658.09 329.36 49842 +1920 231 23.1 17.1 21.45 0.63 606.42 250.41 49656 +1920 232 18.33 12.33 16.68 0 465.17 348.27 49469 +1920 233 21.06 15.06 19.41 0 542.1 338.39 49280 +1920 234 24.02 18.02 22.37 0 637.47 326.28 49091 +1920 235 24.06 18.06 22.41 0 638.85 324.69 48900 +1920 236 25.45 19.45 23.8 0.21 688.41 238.26 48709 +1920 237 22.16 16.16 20.51 0 576.02 328.75 48516 +1920 238 21.95 15.95 20.3 0 569.41 327.85 48323 +1920 239 21.66 15.66 20.01 0 560.39 327.36 48128 +1920 240 19.28 13.28 17.63 0.21 490.81 249.85 47933 +1920 241 23.67 17.67 22.02 0.79 625.5 237.6 47737 +1920 242 18.12 12.12 16.47 0.83 459.66 249.72 47541 +1920 243 15.91 9.91 14.26 1.19 404.95 252.55 47343 +1920 244 13.76 7.76 12.11 0 357.15 339.68 47145 +1920 245 14.58 8.58 12.93 0 374.78 336.04 46947 +1920 246 14.56 8.56 12.91 0 374.34 334.08 46747 +1920 247 15.84 9.84 14.19 0.83 403.31 246.98 46547 +1920 248 15.73 9.73 14.08 0.48 400.75 245.69 46347 +1920 249 17.19 11.19 15.54 0 435.91 321.99 46146 +1920 250 17.82 11.82 16.17 0.25 451.88 238.82 45945 +1920 251 22.49 16.49 20.84 0 586.54 302.52 45743 +1920 252 20.4 14.4 18.75 0.02 522.58 230.27 45541 +1920 253 23.86 17.86 22.21 0 631.98 293.65 45339 +1920 254 21.23 15.23 19.58 0 547.23 300.36 45136 +1920 255 24.04 18.04 22.39 0 638.16 288.83 44933 +1920 256 25.92 19.92 24.27 0 705.89 279.61 44730 +1920 257 28.81 22.81 27.16 0 821.82 265.31 44527 +1920 258 26.83 20.83 25.18 0 740.8 271.77 44323 +1920 259 28.02 22.02 26.37 0 788.64 264.51 44119 +1920 260 24.68 18.68 23.03 0 660.57 275.57 43915 +1920 261 19.71 13.71 18.06 0.21 502.81 216.64 43711 +1920 262 22.22 16.22 20.57 0 577.92 279.24 43507 +1920 263 24.22 18.22 22.57 0.01 644.4 202.75 43303 +1920 264 19.98 13.98 18.33 0 510.47 280.88 43099 +1920 265 16.42 10.42 14.77 0 417.05 287.23 42894 +1920 266 15.5 9.5 13.85 1.11 395.43 215.03 42690 +1920 267 13.09 7.09 11.44 0.43 343.28 216.47 42486 +1920 268 13.29 7.29 11.64 0 347.37 285.68 42282 +1920 269 12.46 6.46 10.81 0.33 330.66 213.42 42078 +1920 270 12.74 6.74 11.09 0.03 336.22 211.07 41875 +1920 271 12.23 6.23 10.58 0.12 326.15 209.71 41671 +1920 272 13.98 7.98 12.33 0 361.81 273.86 41468 +1920 273 20.15 14.15 18.5 0 515.34 257.98 41265 +1920 274 10.53 4.53 8.88 0 294.44 274.17 41062 +1920 275 11.67 5.67 10.02 0 315.4 269.67 40860 +1920 276 9.72 3.72 8.07 0 280.28 269.74 40658 +1920 277 8.25 2.25 6.6 0 256.08 268.91 40456 +1920 278 7.62 1.62 5.97 0 246.26 266.72 40255 +1920 279 3.57 -2.43 1.92 0 190.57 267.97 40054 +1920 280 4.8 -1.2 3.15 0 206.2 264.09 39854 +1920 281 6.31 0.31 4.66 0.33 226.89 194.83 39654 +1920 282 5.88 -0.12 4.23 0 220.83 257.4 39455 +1920 283 7.02 1.02 5.37 0 237.22 253.32 39256 +1920 284 9.52 3.52 7.87 0.07 276.88 185.5 39058 +1920 285 10.05 4.05 8.4 0 285.98 243.99 38861 +1920 286 10.98 4.98 9.33 0 302.56 239.98 38664 +1920 287 14.03 8.03 12.38 0 362.88 232.54 38468 +1920 288 13.65 7.65 12 0.07 354.84 172.79 38273 +1920 289 11.94 5.94 10.29 0 320.54 230.27 38079 +1920 290 13.86 7.86 12.21 0.05 359.26 168.45 37885 +1920 291 10.53 4.53 8.88 0 294.44 226.55 37693 +1920 292 18.9 12.9 17.25 0 480.41 210.31 37501 +1920 293 15.49 9.49 13.84 0 395.2 213.97 37311 +1920 294 17.5 11.5 15.85 0 443.71 207.61 37121 +1920 295 13.45 7.45 11.8 0.58 350.68 158.62 36933 +1920 296 10.17 4.17 8.52 0.49 288.07 159.89 36745 +1920 297 10.49 4.49 8.84 0.34 293.72 157.56 36560 +1920 298 8.45 2.45 6.8 0 259.26 209.72 36375 +1920 299 10 4 8.35 0 285.11 205.24 36191 +1920 300 14.12 8.12 12.47 0 364.8 197.33 36009 +1920 301 15.84 9.84 14.19 0 403.31 192.26 35829 +1920 302 15.26 9.26 13.61 0.75 389.95 142.96 35650 +1920 303 12.84 6.84 11.19 0.19 338.22 143.6 35472 +1920 304 6.77 0.77 5.12 0.01 233.54 146.65 35296 +1920 305 -1 -7 -2.65 0.03 141.09 186.23 35122 +1920 306 -1.16 -7.16 -2.81 0 139.58 233.69 34950 +1920 307 -3 -9 -4.65 0 123.21 232.17 34779 +1920 308 2.73 -3.27 1.08 0 180.49 188.36 34610 +1920 309 0.82 -5.18 -0.83 0 159.27 187.15 34444 +1920 310 3.36 -2.64 1.71 0 188.01 183.1 34279 +1920 311 5.14 -0.86 3.49 0 210.72 179.63 34116 +1920 312 5.79 -0.21 4.14 0 219.58 176.48 33956 +1920 313 9.94 3.94 8.29 0 284.07 170.72 33797 +1920 314 9.3 3.3 7.65 0.12 273.17 127.05 33641 +1920 315 7.07 1.07 5.42 0 237.97 168.82 33488 +1920 316 2.22 -3.78 0.57 0 174.6 169.99 33337 +1920 317 4.82 -1.18 3.17 0.01 206.47 124.58 33188 +1920 318 1.94 -4.06 0.29 0 171.44 165.55 33042 +1920 319 0.65 -5.35 -1 0.08 157.49 123.39 32899 +1920 320 1.2 -4.8 -0.45 0 163.31 162.33 32758 +1920 321 -0.08 -6.08 -1.73 0 150.04 160.83 32620 +1920 322 1.32 -4.68 -0.33 0 164.61 158.28 32486 +1920 323 2.01 -3.99 0.36 0 172.22 156.26 32354 +1920 324 3.5 -2.5 1.85 0 189.71 153.34 32225 +1920 325 2.13 -3.87 0.48 0 173.58 152.38 32100 +1920 326 2.45 -3.55 0.8 0.06 177.24 113.05 31977 +1920 327 5.81 -0.19 4.16 0 219.85 146.82 31858 +1920 328 1.48 -4.52 -0.17 0 166.35 147.39 31743 +1920 329 -0.23 -6.23 -1.88 0 148.55 146.69 31631 +1920 330 2.5 -3.5 0.85 0 177.82 143.88 31522 +1920 331 3.83 -2.17 2.18 0 193.79 141.81 31417 +1920 332 4.49 -1.51 2.84 0 202.16 139.78 31316 +1920 333 6.31 0.31 4.66 0 226.89 137.53 31218 +1920 334 5.17 -0.83 3.52 0 211.12 137.17 31125 +1920 335 4.31 -1.69 2.66 0 199.85 136.51 31035 +1920 336 3.92 -2.08 2.27 0 194.91 135.66 30949 +1920 337 3.32 -2.68 1.67 0 187.52 134.33 30867 +1920 338 1.44 -4.56 -0.21 0 165.91 134.34 30790 +1920 339 1.42 -4.58 -0.23 0 165.69 133.55 30716 +1920 340 4.17 -1.83 2.52 0 198.07 131.39 30647 +1920 341 7.07 1.07 5.42 0 237.97 128.67 30582 +1920 342 7.38 1.38 5.73 0 242.61 127.7 30521 +1920 343 5.56 -0.44 3.91 0 216.41 128.06 30465 +1920 344 4.04 -1.96 2.39 0 196.42 127.82 30413 +1920 345 3.23 -2.77 1.58 0.23 186.44 95.87 30366 +1920 346 4.06 -1.94 2.41 0 196.67 126.83 30323 +1920 347 3.15 -2.85 1.5 0.06 185.47 95.04 30284 +1920 348 2.6 -3.4 0.95 0.3 178.98 94.98 30251 +1920 349 5.25 -0.75 3.6 0.37 212.19 93.62 30221 +1920 350 4.97 -1.03 3.32 0 208.45 124.66 30197 +1920 351 3.01 -2.99 1.36 0.17 183.8 94.13 30177 +1920 352 6.1 0.1 4.45 0.07 223.91 92.75 30162 +1920 353 4.6 -1.4 2.95 0.04 203.59 93.37 30151 +1920 354 0.53 -5.47 -1.12 0 156.25 126.47 30145 +1920 355 1.63 -4.37 -0.02 0.31 167.99 94.48 30144 +1920 356 2.91 -3.09 1.26 0.58 182.61 94.04 30147 +1920 357 1.5 -4.5 -0.15 1.09 166.57 94.59 30156 +1920 358 0.49 -5.51 -1.16 1.56 155.83 94.99 30169 +1920 359 3.91 -2.09 2.26 1.44 194.79 93.85 30186 +1920 360 5.05 -0.95 3.4 1.43 209.51 93.64 30208 +1920 361 7.32 1.32 5.67 1.71 241.71 92.82 30235 +1920 362 7.26 1.26 5.61 0.01 240.81 93.17 30267 +1920 363 2.8 -3.2 1.15 0 181.32 127.43 30303 +1920 364 6.38 0.38 4.73 0 227.89 125.78 30343 +1920 365 7.66 1.66 6.01 0 246.88 125.49 30388 +1921 1 6.47 0.47 4.82 0 229.19 127.17 30438 +1921 2 4.84 -1.16 3.19 0 206.73 128.91 30492 +1921 3 7.41 1.41 5.76 0 243.07 128.2 30551 +1921 4 7.59 1.59 5.94 1.09 245.81 96.74 30614 +1921 5 4.92 -1.08 3.27 0 207.79 131.35 30681 +1921 6 5.7 -0.3 4.05 0 218.33 131.76 30752 +1921 7 7.99 1.99 6.34 0 251.99 130.99 30828 +1921 8 4.46 -1.54 2.81 0 201.78 134.79 30907 +1921 9 6.95 0.95 5.3 0 236.19 134.45 30991 +1921 10 10.94 4.94 9.29 0 301.83 132.58 31079 +1921 11 11.23 5.23 9.58 0 307.16 133.27 31171 +1921 12 12.05 6.05 10.4 0 322.66 133.47 31266 +1921 13 9.82 3.82 8.17 0 282 137.08 31366 +1921 14 9.9 3.9 8.25 0 283.37 138.46 31469 +1921 15 8.5 2.5 6.85 0 260.06 141.04 31575 +1921 16 7.01 1.01 5.36 0 237.08 143.44 31686 +1921 17 3.31 -2.69 1.66 0 187.4 147.52 31800 +1921 18 1.96 -4.04 0.31 0 171.66 150.17 31917 +1921 19 3.85 -2.15 2.2 0 194.04 151.03 32038 +1921 20 5.76 -0.24 4.11 0 219.16 151.37 32161 +1921 21 6.47 0.47 4.82 0 229.19 152.86 32289 +1921 22 5.73 -0.27 4.08 0 218.75 155.13 32419 +1921 23 12.29 6.29 10.64 0.28 327.32 113.36 32552 +1921 24 11.86 5.86 10.21 0 319.01 153.61 32688 +1921 25 10.9 4.9 9.25 0 301.11 156.43 32827 +1921 26 7.73 1.73 6.08 0 247.95 161.19 32969 +1921 27 4.28 -1.72 2.63 0 199.47 165.76 33114 +1921 28 2.71 -3.29 1.06 0 180.26 168.97 33261 +1921 29 0.92 -5.08 -0.73 0 160.33 172.39 33411 +1921 30 0.39 -5.61 -1.26 0 154.8 174.94 33564 +1921 31 -0.72 -6.72 -2.37 0.6 143.77 174.28 33718 +1921 32 -2.25 -8.25 -3.9 0.01 129.67 176.26 33875 +1921 33 -1.75 -7.75 -3.4 0 134.14 223.69 34035 +1921 34 -0.7 -6.7 -2.35 0 143.96 225.23 34196 +1921 35 0.59 -5.41 -1.06 0.8 156.87 179.85 34360 +1921 36 2.72 -3.28 1.07 0 180.38 227.18 34526 +1921 37 4.26 -1.74 2.61 0.01 199.21 180.62 34694 +1921 38 7.16 1.16 5.51 0 239.31 189.41 34863 +1921 39 7.07 1.07 5.42 0 237.97 192.08 35035 +1921 40 9.06 3.06 7.41 0 269.18 192.78 35208 +1921 41 7.93 1.93 6.28 0 251.05 196.48 35383 +1921 42 8 2 6.35 0 252.14 198.94 35560 +1921 43 5.82 -0.18 4.17 0 219.99 203.61 35738 +1921 44 5.92 -0.08 4.27 0.24 221.39 154.56 35918 +1921 45 4.76 -1.24 3.11 0 205.68 209.67 36099 +1921 46 3.8 -2.2 2.15 1.62 193.42 159.84 36282 +1921 47 2.71 -3.29 1.06 0 180.26 216.76 36466 +1921 48 3.61 -2.39 1.96 0 191.06 218.91 36652 +1921 49 3.15 -2.85 1.5 0 185.47 222.06 36838 +1921 50 6.27 0.27 4.62 0 226.32 222.1 37026 +1921 51 6.63 0.63 4.98 0.39 231.5 168.54 37215 +1921 52 5.41 -0.59 3.76 0 214.36 228.68 37405 +1921 53 4.14 -1.86 2.49 0 197.68 232.74 37596 +1921 54 7.66 1.66 6.01 0 246.88 232.18 37788 +1921 55 6.9 0.9 5.25 0 235.45 235.95 37981 +1921 56 6.03 0.03 4.38 0.76 222.93 179.62 38175 +1921 57 1.65 -4.35 0 0.9 168.21 184.58 38370 +1921 58 1.95 -4.05 0.3 0 171.55 248.85 38565 +1921 59 5.21 -0.79 3.56 0 211.65 248.81 38761 +1921 60 11.12 5.12 9.47 0 305.13 244.88 38958 +1921 61 13.03 7.03 11.38 0 342.06 244.95 39156 +1921 62 15.55 9.55 13.9 0 396.58 243.37 39355 +1921 63 13.03 7.03 11.38 0.05 342.06 187.96 39553 +1921 64 8.7 2.7 7.05 0 263.29 259.54 39753 +1921 65 6.51 0.51 4.86 0 229.76 264.95 39953 +1921 66 7.47 1.47 5.82 0 243.98 266.62 40154 +1921 67 12.09 6.09 10.44 0 323.43 263.28 40355 +1921 68 9.73 3.73 8.08 0 280.45 269.53 40556 +1921 69 10.08 4.08 8.43 0 286.5 271.65 40758 +1921 70 10.04 4.04 8.39 0 285.8 274.53 40960 +1921 71 10.24 4.24 8.59 0 289.3 277.13 41163 +1921 72 10.84 4.84 9.19 0 300.02 279.05 41366 +1921 73 8.27 2.27 6.62 0 256.39 285.26 41569 +1921 74 11.02 5.02 9.37 0.13 303.3 213.1 41772 +1921 75 8.05 2.05 6.4 0 252.93 291.01 41976 +1921 76 11.67 5.67 10.02 0 315.4 288.4 42179 +1921 77 14.87 8.87 13.22 0.07 381.19 213.92 42383 +1921 78 9.41 3.41 7.76 0 275.02 297.06 42587 +1921 79 12.54 6.54 10.89 0 332.24 294.82 42791 +1921 80 10.93 4.93 9.28 0 301.65 300 42996 +1921 81 7.59 1.59 5.94 0 245.81 307.37 43200 +1921 82 8.62 2.62 6.97 0 261.99 308.65 43404 +1921 83 10.75 4.75 9.1 0 298.39 307.95 43608 +1921 84 8.48 2.48 6.83 0 259.74 313.88 43812 +1921 85 2.65 -3.35 1 0 179.56 323.21 44016 +1921 86 6.02 0.02 4.37 0 222.79 322.01 44220 +1921 87 5.74 -0.26 4.09 0 218.88 324.91 44424 +1921 88 7.17 1.17 5.52 0 239.46 325.49 44627 +1921 89 6.25 0.25 4.6 0 226.04 328.97 44831 +1921 90 6.64 0.64 4.99 0 231.65 330.87 45034 +1921 91 10.71 4.71 9.06 0.12 297.67 245.36 45237 +1921 92 14.87 8.87 13.22 0.05 381.19 241.08 45439 +1921 93 14.74 8.74 13.09 0.01 378.3 242.92 45642 +1921 94 13.74 7.74 12.09 0.91 356.73 246.08 45843 +1921 95 11.8 5.8 10.15 0.69 317.87 250.48 46045 +1921 96 9.4 3.4 7.75 0.24 274.85 255.12 46246 +1921 97 9.49 3.49 7.84 0.84 276.37 256.56 46446 +1921 98 8.42 2.42 6.77 0 258.78 345.71 46647 +1921 99 10.42 4.42 8.77 0.25 292.48 258.4 46846 +1921 100 15.1 9.1 13.45 0.63 386.34 252.92 47045 +1921 101 14.14 8.14 12.49 1.11 365.23 255.94 47243 +1921 102 11.85 5.85 10.2 0 318.82 347.76 47441 +1921 103 15.22 9.22 13.57 0 389.05 342.53 47638 +1921 104 12.8 6.8 11.15 0 337.42 349.57 47834 +1921 105 13.13 7.13 11.48 0 344.1 350.68 48030 +1921 106 13.7 7.7 12.05 0.1 355.89 263.34 48225 +1921 107 16.39 10.39 14.74 0 416.33 346.52 48419 +1921 108 14.06 8.06 12.41 0 363.52 353.73 48612 +1921 109 14.7 8.7 13.05 0.18 377.42 265.42 48804 +1921 110 12.81 6.81 11.16 1.57 337.62 269.56 48995 +1921 111 9.9 3.9 8.25 0 283.37 366.46 49185 +1921 112 7.77 1.77 6.12 0.59 248.57 278.59 49374 +1921 113 11.49 5.49 9.84 0.1 312.01 274.84 49561 +1921 114 10.95 4.95 9.3 0.15 302.02 276.73 49748 +1921 115 14.74 8.74 13.09 0 378.3 362.47 49933 +1921 116 12.21 6.21 10.56 0 325.76 369.21 50117 +1921 117 9.06 3.06 7.41 0 269.18 376.32 50300 +1921 118 7.67 1.67 6.02 0.1 247.03 284.92 50481 +1921 119 8.96 2.96 7.31 0.17 267.53 284.29 50661 +1921 120 5.75 -0.25 4.1 0.08 219.02 288.82 50840 +1921 121 18 12 16.35 0.11 456.53 270.91 51016 +1921 122 15.19 9.19 13.54 0.02 388.37 277.41 51191 +1921 123 17.39 11.39 15.74 0.08 440.93 273.85 51365 +1921 124 16.33 10.33 14.68 0.11 414.89 276.81 51536 +1921 125 12.99 6.99 11.34 0 341.25 378.06 51706 +1921 126 12.49 6.49 10.84 0 331.25 380.13 51874 +1921 127 17.09 11.09 15.44 0 433.42 369.86 52039 +1921 128 20.62 14.62 18.97 0.05 529.02 269.98 52203 +1921 129 19.48 13.48 17.83 0.4 496.36 273.42 52365 +1921 130 15.59 9.59 13.94 0 397.51 376.48 52524 +1921 131 19.28 13.28 17.63 0.16 490.81 275.06 52681 +1921 132 17.13 11.13 15.48 0 434.42 373.98 52836 +1921 133 15.56 9.56 13.91 0 396.81 378.89 52989 +1921 134 18.38 12.38 16.73 0.1 466.49 278.8 53138 +1921 135 17.19 11.19 15.54 0.76 435.91 281.93 53286 +1921 136 16.01 10.01 14.36 0 407.3 379.76 53430 +1921 137 11.74 5.74 10.09 0 316.72 390.43 53572 +1921 138 10.87 4.87 9.22 0 300.56 392.78 53711 +1921 139 19.89 13.89 18.24 0 507.9 370.24 53848 +1921 140 21.42 15.42 19.77 0 553.01 365.4 53981 +1921 141 26.93 20.93 25.28 0 744.72 342.46 54111 +1921 142 29.03 23.03 27.38 0 831.27 332 54238 +1921 143 27.02 21.02 25.37 0.1 748.27 257.24 54362 +1921 144 26.2 20.2 24.55 0 716.48 347.39 54483 +1921 145 23.78 17.78 22.13 0.59 629.24 268.93 54600 +1921 146 22.36 16.36 20.71 0.03 582.38 273.45 54714 +1921 147 22.94 16.94 21.29 0.99 601.15 272.1 54824 +1921 148 22.34 16.34 20.69 1.37 581.74 274.14 54931 +1921 149 20.85 14.85 19.2 1.16 535.82 278.48 55034 +1921 150 21.52 15.52 19.87 0.93 556.07 276.92 55134 +1921 151 20.07 14.07 18.42 0.22 513.04 281.04 55229 +1921 152 17.32 11.32 15.67 0.1 439.17 287.58 55321 +1921 153 17.25 11.25 15.6 0 437.41 383.89 55409 +1921 154 15.28 9.28 13.63 0 390.41 389.57 55492 +1921 155 16.86 10.86 15.21 0.52 427.74 289.14 55572 +1921 156 15.83 9.83 14.18 1.83 403.08 291.49 55648 +1921 157 17.26 11.26 15.61 0 437.66 384.87 55719 +1921 158 16.51 10.51 14.86 0 419.22 387.16 55786 +1921 159 18.92 12.92 17.27 0.47 480.96 285.19 55849 +1921 160 21.41 15.41 19.76 0.29 552.71 278.95 55908 +1921 161 20.4 14.4 18.75 0 522.58 375.59 55962 +1921 162 21.57 15.57 19.92 0.33 557.61 278.6 56011 +1921 163 22.53 16.53 20.88 0.98 587.83 276.02 56056 +1921 164 23.03 17.03 21.38 0.29 604.11 274.57 56097 +1921 165 24.23 18.23 22.58 0.38 644.75 270.9 56133 +1921 166 21.15 15.15 19.5 0.96 544.81 280.07 56165 +1921 167 23.35 17.35 21.7 0.04 614.73 273.68 56192 +1921 168 24.51 18.51 22.86 0.18 654.55 270.06 56214 +1921 169 22.94 16.94 21.29 2.21 601.15 274.99 56231 +1921 170 25.49 19.49 23.84 0.05 689.89 266.78 56244 +1921 171 23.45 17.45 21.8 0.02 618.08 273.48 56252 +1921 172 23.08 17.08 21.43 0.27 605.76 274.6 56256 +1921 173 20.3 14.3 18.65 0.24 519.67 282.37 56255 +1921 174 16.38 10.38 14.73 0 416.09 388.51 56249 +1921 175 16.74 10.74 15.09 0 424.8 387.48 56238 +1921 176 14.47 8.47 12.82 0 372.37 393.4 56223 +1921 177 16.32 10.32 14.67 0 414.65 388.5 56203 +1921 178 18.9 12.9 17.25 0 480.41 380.9 56179 +1921 179 20.86 14.86 19.21 0.26 536.12 280.65 56150 +1921 180 20.59 14.59 18.94 0.3 528.14 281.28 56116 +1921 181 22.76 16.76 21.11 0.06 595.27 275.17 56078 +1921 182 18.57 12.57 16.92 0 471.54 381.5 56035 +1921 183 15.73 9.73 14.08 0 400.75 389.48 55987 +1921 184 18.33 12.33 16.68 0 465.17 381.91 55935 +1921 185 16.85 10.85 15.2 0 427.5 386.17 55879 +1921 186 17.54 11.54 15.89 0 444.72 383.93 55818 +1921 187 22.38 16.38 20.73 0 583.02 367.39 55753 +1921 188 24.08 18.08 22.43 0 639.54 360.24 55684 +1921 189 23.23 17.23 21.58 0 610.73 363.59 55611 +1921 190 21.7 15.7 20.05 0 561.62 369.15 55533 +1921 191 25 19 23.35 0 672.02 355.45 55451 +1921 192 25.25 19.25 23.6 0 681.09 354.04 55366 +1921 193 21.68 15.68 20.03 0.43 561.01 276.3 55276 +1921 194 19.64 13.64 17.99 0.33 500.84 281.48 55182 +1921 195 20.27 14.27 18.62 1.7 518.8 279.69 55085 +1921 196 29.1 23.1 27.45 0 834.29 333.65 54984 +1921 197 25.92 19.92 24.27 0 705.89 349.4 54879 +1921 198 24.86 18.86 23.21 0 666.99 353.79 54770 +1921 199 24.46 18.46 22.81 0 652.79 355.2 54658 +1921 200 25.84 19.84 24.19 0 702.89 348.65 54542 +1921 201 24.54 18.54 22.89 0.01 655.61 265.51 54423 +1921 202 23.39 17.39 21.74 0 616.06 358.26 54301 +1921 203 27.14 21.14 25.49 0 753.02 340.95 54176 +1921 204 28.93 22.93 27.28 0.51 826.96 248.38 54047 +1921 205 27.98 21.98 26.33 0 786.99 335.74 53915 +1921 206 28.5 22.5 26.85 0 808.66 332.49 53780 +1921 207 28.44 22.44 26.79 0 806.14 332.2 53643 +1921 208 24.19 18.19 22.54 0 643.35 351.65 53502 +1921 209 30.56 24.56 28.91 0 899.53 319.15 53359 +1921 210 29.54 23.54 27.89 0 853.52 324.44 53213 +1921 211 28.01 22.01 26.36 0.14 788.23 248.94 53064 +1921 212 31.8 25.8 30.15 0.25 958.27 232.23 52913 +1921 213 26.2 20.2 24.55 0.9 716.48 254.48 52760 +1921 214 26.49 20.49 24.84 0 727.59 337.24 52604 +1921 215 22.28 16.28 20.63 0.03 579.83 265.73 52445 +1921 216 21.29 15.29 19.64 0.14 549.05 267.67 52285 +1921 217 19.73 13.73 18.08 1.79 503.37 270.95 52122 +1921 218 17.33 11.33 15.68 0 439.42 367.65 51958 +1921 219 18.73 12.73 17.08 0 475.82 362.52 51791 +1921 220 19.56 13.56 17.91 0 498.6 359 51622 +1921 221 20.71 14.71 19.06 0.09 531.67 265.67 51451 +1921 222 20.13 14.13 18.48 0.43 514.76 266.34 51279 +1921 223 22.44 16.44 20.79 0.23 584.94 259.46 51105 +1921 224 23.61 17.61 21.96 0 623.47 340.43 50929 +1921 225 25.05 19.05 23.4 0 673.83 333.42 50751 +1921 226 24.72 18.72 23.07 0 661.99 333.71 50572 +1921 227 29.56 23.56 27.91 0 854.4 309.45 50392 +1921 228 27.77 21.77 26.12 0.71 778.38 238.16 50210 +1921 229 24.43 18.43 22.78 0 651.74 331.32 50026 +1921 230 25.58 19.58 23.93 0 693.21 325.27 49842 +1921 231 23.42 17.42 21.77 0 617.07 332.66 49656 +1921 232 25.51 19.51 23.86 0 690.62 322.89 49469 +1921 233 24.28 18.28 22.63 0 646.49 326.62 49280 +1921 234 22.11 16.11 20.46 0.06 574.44 250.04 49091 +1921 235 24.41 18.41 22.76 0.17 651.04 242.48 48900 +1921 236 23.73 17.73 22.08 0.05 627.54 243.45 48709 +1921 237 22.61 16.61 20.96 0.95 590.41 245.37 48516 +1921 238 23.62 17.62 21.97 0 623.81 321.81 48323 +1921 239 26.26 20.26 24.61 0 718.77 309.64 48128 +1921 240 26.75 20.75 25.1 0 737.67 305.82 47933 +1921 241 27.34 21.34 25.69 0 760.99 301.55 47737 +1921 242 24.28 18.28 22.63 0.16 646.49 234.61 47541 +1921 243 24.79 18.79 23.14 0.6 664.49 231.78 47343 +1921 244 22.52 16.52 20.87 0.63 587.51 236.78 47145 +1921 245 17.6 11.6 15.95 0.11 446.25 246.6 46947 +1921 246 20.26 14.26 18.61 0 518.51 319.34 46747 +1921 247 21.56 15.56 19.91 0 557.3 313.43 46547 +1921 248 22.5 16.5 20.85 0 586.86 308.41 46347 +1921 249 18.75 12.75 17.1 0 476.36 317.89 46146 +1921 250 14.91 8.91 13.26 0 382.08 325.36 45945 +1921 251 14.73 8.73 13.08 0 378.08 323.6 45743 +1921 252 18.27 12.27 16.62 0 463.59 312.99 45541 +1921 253 21.41 15.41 19.76 0 552.71 301.88 45339 +1921 254 21.06 15.06 19.41 0 542.1 300.88 45136 +1921 255 18.82 12.82 17.17 0 478.25 305.07 44933 +1921 256 18.87 12.87 17.22 0.14 479.6 227.02 44730 +1921 257 14.74 8.74 13.09 0 378.3 310.29 44527 +1921 258 14.78 8.78 13.13 0 379.19 307.84 44323 +1921 259 14.73 8.73 13.08 0 378.08 305.49 44119 +1921 260 15.55 9.55 13.9 0 396.58 301.36 43915 +1921 261 22.44 16.44 20.79 0 584.94 280.83 43711 +1921 262 22.06 16.06 20.41 0 572.86 279.74 43507 +1921 263 16.49 10.49 14.84 0 418.74 292.01 43303 +1921 264 15.61 9.61 13.96 0 397.97 291.34 43099 +1921 265 15.32 9.32 13.67 0 391.32 289.56 42894 +1921 266 24.66 18.66 23.01 0 659.86 261.84 42690 +1921 267 20.77 14.77 19.12 0 533.45 271.4 42486 +1921 268 21.2 15.2 19.55 0 546.32 267.72 42282 +1921 269 21.69 15.69 20.04 0 561.31 263.91 42078 +1921 270 19.44 13.44 17.79 0 495.25 267.43 41875 +1921 271 18.27 12.27 16.62 0 463.59 267.72 41671 +1921 272 16.65 10.65 15 0.13 422.61 201.47 41468 +1921 273 19.07 13.07 17.42 0 485.04 260.67 41265 +1921 274 13.52 7.52 11.87 0.01 352.13 202.08 41062 +1921 275 17.22 11.22 15.57 0.92 436.66 194.66 40860 +1921 276 16.04 10.04 14.39 0.01 408 194.49 40658 +1921 277 18.73 12.73 17.08 0 475.82 250.96 40456 +1921 278 18.49 12.49 16.84 0.48 469.41 186.53 40255 +1921 279 17.04 11.04 15.39 0.27 432.18 186.81 40054 +1921 280 19.16 13.16 17.51 0.23 487.51 181.41 39854 +1921 281 18.95 12.95 17.3 0.11 481.77 179.8 39654 +1921 282 18.01 12.01 16.36 0.6 456.79 179.34 39455 +1921 283 16.61 10.61 14.96 0.01 421.64 179.4 39256 +1921 284 14.42 8.42 12.77 0.12 371.28 180.14 39058 +1921 285 12.4 6.4 10.75 1.3 329.48 180.56 38861 +1921 286 13.82 7.82 12.17 0.48 358.42 176.85 38664 +1921 287 12.64 6.64 10.99 0.1 334.22 176.02 38468 +1921 288 12.06 6.06 10.41 0.35 322.85 174.56 38273 +1921 289 16.01 10.01 14.36 0.34 407.3 167.89 38079 +1921 290 15.31 9.31 13.66 0 391.09 222.25 37885 +1921 291 14.55 8.55 12.9 0 374.12 220.84 37693 +1921 292 15.69 9.69 14.04 0 399.82 216.31 37501 +1921 293 15.96 9.96 14.31 0 406.12 213.17 37311 +1921 294 15.65 9.65 14 0 398.89 210.87 37121 +1921 295 16.91 10.91 15.26 0.01 428.97 154.45 36933 +1921 296 12.32 6.32 10.67 0 327.91 210.49 36745 +1921 297 11.58 5.58 9.93 0 313.7 208.74 36560 +1921 298 11.86 5.86 10.21 0 319.01 205.79 36375 +1921 299 10.17 4.17 8.52 0.19 288.07 153.79 36191 +1921 300 11.67 5.67 10.02 0 315.4 200.6 36009 +1921 301 12.22 6.22 10.57 0 325.96 197.41 35829 +1921 302 8.63 2.63 6.98 0 262.15 198.87 35650 +1921 303 13.38 7.38 11.73 0 349.23 190.76 35472 +1921 304 16.2 10.2 14.55 0 411.79 184.26 35296 +1921 305 1.66 -4.34 0.01 0.03 168.32 147.42 35122 +1921 306 2.42 -3.58 0.77 0.68 176.89 145.33 34950 +1921 307 -1.44 -7.44 -3.09 0.1 136.97 183.28 34779 +1921 308 1.66 -4.34 0.01 0 168.32 227.25 34610 +1921 309 4.57 -1.43 2.92 0 203.2 184.73 34444 +1921 310 4.86 -1.14 3.21 0 206.99 182.04 34279 +1921 311 9.25 3.25 7.6 0 272.34 176.14 34116 +1921 312 12 6 10.35 0 321.7 170.63 33956 +1921 313 7.15 1.15 5.5 0 239.16 173.26 33797 +1921 314 7.48 1.48 5.83 0.29 244.13 128.27 33641 +1921 315 4.12 -1.88 2.47 0 197.43 171.01 33488 +1921 316 5.95 -0.05 4.3 0 221.81 167.5 33337 +1921 317 7.66 1.66 6.01 0.01 246.88 122.97 33188 +1921 318 6.06 0.06 4.41 0 223.35 162.87 33042 +1921 319 2.62 -3.38 0.97 0.02 179.21 122.57 32899 +1921 320 2.14 -3.86 0.49 0 173.69 161.81 32758 +1921 321 6.53 0.53 4.88 0.01 230.05 117.62 32620 +1921 322 3.69 -2.31 2.04 0.15 192.05 117.69 32486 +1921 323 3.69 -2.31 2.04 0.01 192.05 116.47 32354 +1921 324 3.95 -2.05 2.3 0.39 195.29 114.8 32225 +1921 325 5.42 -0.58 3.77 0 214.49 150.39 32100 +1921 326 3.11 -2.89 1.46 0 184.99 150.36 31977 +1921 327 3.91 -2.09 2.26 0 194.79 148.03 31858 +1921 328 7.55 1.55 5.9 0 245.19 143.6 31743 +1921 329 8.9 2.9 7.25 0 266.55 141.06 31631 +1921 330 5.38 -0.62 3.73 1.4 213.95 106.64 31522 +1921 331 1.86 -4.14 0.21 1.87 170.54 107.17 31417 +1921 332 0.17 -5.83 -1.48 0.04 152.56 106.53 31316 +1921 333 3.34 -2.66 1.69 0 187.77 139.35 31218 +1921 334 2.48 -3.52 0.83 0 177.58 138.7 31125 +1921 335 -1.7 -7.7 -3.35 0 134.59 139.41 31035 +1921 336 -0.57 -6.57 -2.22 0 145.22 137.86 30949 +1921 337 -2.47 -8.47 -4.12 0 127.74 136.93 30867 +1921 338 0.58 -5.42 -1.07 0 156.76 134.73 30790 +1921 339 3.91 -2.09 2.26 0 194.79 132.27 30716 +1921 340 -0.3 -6.3 -1.95 0.12 147.86 143.63 30647 +1921 341 3.2 -2.8 1.55 0 186.07 130.99 30582 +1921 342 3.27 -2.73 1.62 0 186.92 130.19 30521 +1921 343 0.71 -5.29 -0.94 0 158.12 130.61 30465 +1921 344 3.74 -2.26 2.09 0 192.67 127.98 30413 +1921 345 -1.61 -7.61 -3.26 0 135.41 129.98 30366 +1921 346 -0.55 -6.55 -2.2 0 145.41 129.01 30323 +1921 347 1.97 -4.03 0.32 0 171.77 127.3 30284 +1921 348 4.55 -1.45 2.9 0 202.94 125.61 30251 +1921 349 2.02 -3.98 0.37 0 172.34 126.54 30221 +1921 350 -0.42 -6.42 -2.07 0 146.68 127.28 30197 +1921 351 1.61 -4.39 -0.04 0 167.77 126.18 30177 +1921 352 3.36 -2.64 1.71 0.07 188.01 93.92 30162 +1921 353 1.54 -4.46 -0.11 0 167 126.05 30151 +1921 354 3.35 -2.65 1.7 0.6 187.89 93.85 30145 +1921 355 3.23 -2.77 1.58 0.05 186.44 93.89 30144 +1921 356 4.84 -1.16 3.19 0.07 206.73 93.26 30147 +1921 357 3.32 -2.68 1.67 0 187.52 125.23 30156 +1921 358 -1.41 -7.41 -3.06 0 137.25 127.42 30169 +1921 359 1.13 -4.87 -0.52 0.09 162.56 94.87 30186 +1921 360 2.64 -3.36 0.99 0 179.44 126.15 30208 +1921 361 8.08 2.08 6.43 0 253.4 123.23 30235 +1921 362 6.36 0.36 4.71 0 227.61 124.82 30267 +1921 363 6.04 0.04 4.39 0 223.07 125.61 30303 +1921 364 11 5 9.35 0 302.93 122.35 30343 +1921 365 8.29 2.29 6.64 0 256.71 125.04 30388 +1922 1 7.59 1.59 5.94 0 245.81 126.42 30438 +1922 2 2.92 -3.08 1.27 0.88 182.73 97.47 30492 +1922 3 -0.47 -6.47 -2.12 0 146.19 132.48 30551 +1922 4 3.14 -2.86 1.49 0 185.35 131.71 30614 +1922 5 -0.11 -6.11 -1.76 0 149.74 133.9 30681 +1922 6 2.58 -3.42 0.93 0.39 178.74 100.15 30752 +1922 7 2.67 -3.33 1.02 0.43 179.79 100.72 30828 +1922 8 0.17 -5.83 -1.48 0.06 152.56 102.74 30907 +1922 9 0.03 -5.97 -1.62 0.61 151.15 103.73 30991 +1922 10 -6.87 -12.87 -8.52 0.08 94.11 149.25 31079 +1922 11 -8.87 -14.87 -10.52 0 81.57 186.16 31171 +1922 12 -6.73 -12.73 -8.38 0 95.05 186.52 31266 +1922 13 -5.24 -11.24 -6.89 0 105.54 187.59 31366 +1922 14 -4.2 -10.2 -5.85 0 113.45 188.62 31469 +1922 15 -3.87 -9.87 -5.52 0 116.06 189.83 31575 +1922 16 -3.14 -9.14 -4.79 0.05 122.03 153.67 31686 +1922 17 -5.4 -11.4 -7.05 0 104.37 193.21 31800 +1922 18 -0.16 -6.16 -1.81 0.5 149.25 156.66 31917 +1922 19 0.39 -5.61 -1.26 0 154.8 195.94 32038 +1922 20 7.48 1.48 5.83 0.04 244.13 154.52 32161 +1922 21 4.78 -1.22 3.13 0.87 205.94 156.7 32289 +1922 22 1.23 -4.77 -0.42 0 163.64 198.72 32419 +1922 23 2.19 -3.81 0.54 0 174.26 159.13 32552 +1922 24 2.66 -3.34 1.01 0.05 179.67 120.7 32688 +1922 25 5.04 -0.96 3.39 0 209.38 161.31 32827 +1922 26 5.34 -0.66 3.69 0.06 213.41 122.27 32969 +1922 27 6.81 0.81 5.16 1.01 234.13 122.95 33114 +1922 28 7.54 1.54 5.89 0 245.04 165.54 33261 +1922 29 0.97 -5.03 -0.68 0 160.86 172.36 33411 +1922 30 -1.84 -7.84 -3.49 0 133.32 176.03 33564 +1922 31 -2.48 -8.48 -4.13 0.05 127.66 173.33 33718 +1922 32 2.61 -3.39 0.96 0 179.09 178.18 33875 +1922 33 6.64 0.64 4.99 0 231.65 177.92 34035 +1922 34 4.63 -1.37 2.98 0 203.98 181.66 34196 +1922 35 3.43 -2.57 1.78 0.13 188.86 138.49 34360 +1922 36 0.88 -5.12 -0.77 0.52 159.9 141.58 34526 +1922 37 -1.53 -7.53 -3.18 0.14 136.15 182.81 34694 +1922 38 -4.05 -10.05 -5.7 0 114.63 234.68 34863 +1922 39 -1.26 -7.26 -2.91 0 138.65 235.85 35035 +1922 40 1.03 -4.97 -0.62 0 161.49 236.91 35208 +1922 41 2.66 -3.34 1.01 0 179.67 200.75 35383 +1922 42 2.25 -3.75 0.6 0 174.94 203.6 35560 +1922 43 3.25 -2.75 1.6 0 186.68 205.62 35738 +1922 44 3.5 -2.5 1.85 0 189.71 208.02 35918 +1922 45 2.9 -3.1 1.25 0 182.5 211.09 36099 +1922 46 1.53 -4.47 -0.12 0 166.89 214.74 36282 +1922 47 -1.76 -7.76 -3.41 0.06 134.05 201.01 36466 +1922 48 -2.88 -8.88 -4.53 0.62 124.22 205.02 36652 +1922 49 -3.33 -9.33 -4.98 0.13 120.46 207.46 36838 +1922 50 -4.03 -10.03 -5.68 0.31 114.79 210.36 37026 +1922 51 -3.81 -9.81 -5.46 0 116.55 270.35 37215 +1922 52 -3.93 -9.93 -5.58 0 115.59 273.1 37405 +1922 53 -3.12 -9.12 -4.77 0.09 122.2 216.36 37596 +1922 54 -5.14 -11.14 -6.79 0 106.28 279.33 37788 +1922 55 0.3 -5.7 -1.35 0 153.88 279.18 37981 +1922 56 3.01 -2.99 1.36 0 183.8 279.43 38175 +1922 57 3.14 -2.86 1.49 0.11 185.35 220.47 38370 +1922 58 5.72 -0.28 4.07 0 218.61 281.58 38565 +1922 59 7.43 1.43 5.78 0 243.37 281.58 38761 +1922 60 16.39 10.39 14.74 0 416.33 236.31 38958 +1922 61 13.1 7.1 11.45 0 343.48 244.84 39156 +1922 62 10.94 4.94 9.29 0.12 301.83 188.07 39355 +1922 63 11.32 5.32 9.67 0.15 308.83 189.89 39553 +1922 64 9.93 3.93 8.28 1.46 283.89 193.48 39753 +1922 65 12.84 6.84 11.19 0.09 338.22 192.43 39953 +1922 66 9.68 3.68 8.03 1.06 279.6 197.91 40154 +1922 67 10 4 8.35 1.31 285.11 199.74 40355 +1922 68 12.55 6.55 10.9 0.5 332.44 199.03 40556 +1922 69 13.9 7.9 12.25 0 360.11 265.66 40758 +1922 70 14.36 8.36 12.71 0.04 369.98 200.7 40960 +1922 71 8.15 2.15 6.5 0.01 254.5 209.95 41163 +1922 72 12.74 6.74 11.09 0 336.22 276.04 41366 +1922 73 9.16 3.16 7.51 0.01 270.84 213.06 41569 +1922 74 8.63 2.63 6.98 0.23 262.15 215.65 41772 +1922 75 7.63 1.63 5.98 0 246.42 291.54 41976 +1922 76 8.66 2.66 7.01 0 262.64 292.84 42179 +1922 77 12.58 6.58 10.93 0 333.03 289.45 42383 +1922 78 10.63 4.63 8.98 0 296.23 295.25 42587 +1922 79 8.98 2.98 7.33 0 267.86 300.38 42791 +1922 80 2.97 -3.03 1.32 0 183.33 309.93 42996 +1922 81 0.68 -5.32 -0.97 0 157.8 314.59 43200 +1922 82 -1.47 -7.47 -3.12 0 136.7 318.96 43404 +1922 83 1.69 -4.31 0.04 0.04 168.65 239.23 43608 +1922 84 3.09 -2.91 1.44 0 184.76 320.24 43812 +1922 85 5.89 -0.11 4.24 0 220.97 319.73 44016 +1922 86 11.1 5.1 9.45 0.26 304.76 236.08 44220 +1922 87 13.83 7.83 12.18 0.86 358.63 234.24 44424 +1922 88 14.18 8.18 12.53 0 366.09 313.92 44627 +1922 89 11.32 5.32 9.67 0 308.83 321.51 44831 +1922 90 14.2 8.2 12.55 0.06 366.52 238.83 45034 +1922 91 13.42 7.42 11.77 0.03 350.05 241.67 45237 +1922 92 13.53 7.53 11.88 0.87 352.34 243.17 45439 +1922 93 14.2 8.2 12.55 0.29 366.52 243.78 45642 +1922 94 13.26 7.26 11.61 0 346.76 329.07 45843 +1922 95 12.11 6.11 10.46 0 323.82 333.4 46045 +1922 96 14.21 8.21 12.56 0 366.73 331.32 46246 +1922 97 14.53 8.53 12.88 0 373.68 332.66 46446 +1922 98 12.11 6.11 10.46 0.01 323.82 254.62 46647 +1922 99 11.64 5.64 9.99 0 314.83 342.38 46846 +1922 100 16.89 10.89 15.24 0 428.48 332.93 47045 +1922 101 15.3 9.3 13.65 0.05 390.86 254 47243 +1922 102 12.64 6.64 10.99 0 334.22 346.24 47441 +1922 103 10.98 4.98 9.33 0 302.56 351.21 47638 +1922 104 8.48 2.48 6.83 1.83 259.74 267.91 47834 +1922 105 9.11 3.11 7.46 0.9 270.01 268.52 48030 +1922 106 7.05 1.05 5.4 1.85 237.67 272.11 48225 +1922 107 6.25 0.25 4.6 0.79 226.04 274.23 48419 +1922 108 5.49 -0.51 3.84 0.86 215.45 276.32 48612 +1922 109 10.01 4.01 8.36 1.24 285.28 272.46 48804 +1922 110 9.1 3.1 7.45 0.76 269.84 274.68 48995 +1922 111 7.85 1.85 6.2 0.02 249.81 277.34 49185 +1922 112 9.93 3.93 8.28 0 283.89 367.95 49374 +1922 113 12.14 6.14 10.49 0 324.4 365.19 49561 +1922 114 15.64 9.64 13.99 0.14 398.66 269.17 49748 +1922 115 15.82 9.82 14.17 0 402.84 359.85 49933 +1922 116 13.74 7.74 12.09 0.11 356.73 274.48 50117 +1922 117 10.54 4.54 8.89 0.05 294.62 280.3 50300 +1922 118 12.47 6.47 10.82 0 330.86 371.31 50481 +1922 119 8.09 2.09 6.44 0.01 253.55 285.34 50661 +1922 120 6.49 0.49 4.84 0 229.48 384.06 50840 +1922 121 14.63 8.63 12.98 0 375.88 370.04 51016 +1922 122 15.26 9.26 13.61 0.57 389.95 277.28 51191 +1922 123 15.68 9.68 14.03 0.3 399.59 277.26 51365 +1922 124 18.2 12.2 16.55 1.33 461.75 272.9 51536 +1922 125 17.51 11.51 15.86 0 443.96 366.83 51706 +1922 126 22.02 16.02 20.37 0.19 571.61 264.91 51874 +1922 127 24.67 18.67 23.02 0.03 660.22 257.67 52039 +1922 128 22.94 16.94 21.29 0 601.15 351.54 52203 +1922 129 20.92 14.92 19.27 0.03 537.91 269.83 52365 +1922 130 22.75 16.75 21.1 0 594.94 353.84 52524 +1922 131 22.02 16.02 20.37 0.46 571.61 268.02 52681 +1922 132 25.82 19.82 24.17 1.3 702.14 256.85 52836 +1922 133 21.9 15.9 20.25 0 567.85 359.27 52989 +1922 134 22.65 16.65 21 0.13 591.7 267.84 53138 +1922 135 14.87 8.87 13.22 0 381.19 382.03 53286 +1922 136 17.49 11.49 15.84 0.1 443.46 281.76 53430 +1922 137 18.07 12.07 16.42 0.76 458.35 281.01 53572 +1922 138 17.77 11.77 16.12 0 450.6 376.17 53711 +1922 139 19.48 13.48 17.83 0 496.36 371.58 53848 +1922 140 13.83 7.83 12.18 0.42 358.63 290.76 53981 +1922 141 13.27 7.27 11.62 0 346.96 389.4 54111 +1922 142 16.11 10.11 14.46 0 409.66 382.93 54238 +1922 143 15.81 9.81 14.16 0 402.61 384.26 54362 +1922 144 17.17 11.17 15.52 0.24 435.41 285.76 54483 +1922 145 15.28 9.28 13.63 0 390.41 386.59 54600 +1922 146 17.79 11.79 16.14 0.08 451.11 285.05 54714 +1922 147 14.98 8.98 13.33 0 383.64 388.21 54824 +1922 148 13.22 7.22 11.57 0 345.94 392.79 54931 +1922 149 13.79 7.79 12.14 0 357.78 391.8 55034 +1922 150 16.52 10.52 14.87 0 419.46 385.2 55134 +1922 151 16.43 10.43 14.78 0 417.29 385.84 55229 +1922 152 24.26 18.26 22.61 0.18 645.79 269.12 55321 +1922 153 22.97 16.97 21.32 0.28 602.13 273.3 55409 +1922 154 23.82 17.82 22.17 0 630.61 361.23 55492 +1922 155 28.54 22.54 26.89 0 810.35 338.89 55572 +1922 156 26.72 20.72 25.07 0 736.5 348.57 55648 +1922 157 24.74 18.74 23.09 0.06 662.71 268.45 55719 +1922 158 22.05 16.05 20.4 0 572.55 369.12 55786 +1922 159 22.17 16.17 20.52 0 576.34 368.9 55849 +1922 160 23.1 17.1 21.45 0.05 606.42 274.07 55908 +1922 161 24.39 18.39 22.74 0.79 650.34 270.08 55962 +1922 162 23.81 17.81 22.16 0.01 630.27 271.97 56011 +1922 163 26.37 20.37 24.72 0 722.97 351.32 56056 +1922 164 20.44 14.44 18.79 2.14 523.74 281.83 56097 +1922 165 16.34 10.34 14.69 0 415.13 388.55 56133 +1922 166 17.58 11.58 15.93 0.11 445.74 288.83 56165 +1922 167 16.64 10.64 14.99 0 422.37 387.75 56192 +1922 168 20.56 14.56 18.91 0 527.26 375.55 56214 +1922 169 21.71 15.71 20.06 0.41 561.93 278.55 56231 +1922 170 17.71 11.71 16.06 0 449.06 384.76 56244 +1922 171 15.04 9.04 13.39 0 384.99 392.16 56252 +1922 172 18.2 12.2 16.55 0 461.75 383.33 56256 +1922 173 20.29 14.29 18.64 0 519.38 376.53 56255 +1922 174 19.48 13.48 17.83 0.21 496.36 284.38 56249 +1922 175 20.99 14.99 19.34 0.36 540 280.47 56238 +1922 176 18.3 12.3 16.65 0.69 464.38 287.14 56223 +1922 177 20.82 14.82 19.17 0.04 534.93 280.82 56203 +1922 178 22.43 16.43 20.78 0 584.62 368.47 56179 +1922 179 21.87 15.87 20.22 0 566.91 370.51 56150 +1922 180 24.1 18.1 22.45 0 640.23 361.46 56116 +1922 181 20.58 14.58 18.93 0 527.84 375 56078 +1922 182 17.1 11.1 15.45 0 433.67 385.89 56035 +1922 183 19.77 13.77 18.12 0 504.5 377.45 55987 +1922 184 20.42 14.42 18.77 0 523.16 375.08 55935 +1922 185 16.82 10.82 15.17 0 426.76 386.26 55879 +1922 186 18.64 12.64 16.99 0 473.41 380.6 55818 +1922 187 22.21 16.21 20.56 0 577.6 368.04 55753 +1922 188 22.86 16.86 21.21 0.01 598.53 273.94 55684 +1922 189 21.44 15.44 19.79 0.53 553.62 277.86 55611 +1922 190 24.17 18.17 22.52 0.1 642.66 269.49 55533 +1922 191 24.32 18.32 22.67 0 647.88 358.42 55451 +1922 192 24.95 18.95 23.3 1.12 670.22 266.54 55366 +1922 193 25.09 19.09 23.44 0 675.27 354.5 55276 +1922 194 25.49 19.49 23.84 0 689.89 352.48 55182 +1922 195 24.14 18.14 22.49 0.07 641.62 268.62 55085 +1922 196 23.57 17.57 21.92 0 622.12 360.14 54984 +1922 197 22.91 16.91 21.26 0 600.17 362.35 54879 +1922 198 25.85 19.85 24.2 0 703.26 349.32 54770 +1922 199 25.61 19.61 23.96 0.39 694.32 262.57 54658 +1922 200 22.8 16.8 21.15 0.22 596.57 271.22 54542 +1922 201 23.48 17.48 21.83 0 619.08 358.45 54423 +1922 202 19.86 13.86 18.21 0 507.05 371.21 54301 +1922 203 23.25 17.25 21.6 0 611.39 358.33 54176 +1922 204 23.77 17.77 22.12 0 628.9 355.72 54047 +1922 205 28.6 22.6 26.95 0.8 812.89 249.36 53915 +1922 206 25.8 19.8 24.15 0 701.39 345.84 53780 +1922 207 22.2 16.2 20.55 0 577.29 360.2 53643 +1922 208 21.96 15.96 20.31 0.11 569.72 270.34 53502 +1922 209 22.52 16.52 20.87 0 587.51 357.7 53359 +1922 210 21.55 15.55 19.9 0 557 360.69 53213 +1922 211 23.15 17.15 21.5 0.65 608.07 265.41 53064 +1922 212 18.57 12.57 16.92 0 471.54 369.02 52913 +1922 213 19.87 13.87 18.22 0.55 507.33 273.11 52760 +1922 214 22.71 16.71 21.06 0.43 593.64 265.01 52604 +1922 215 22.84 16.84 21.19 0 597.88 352.18 52445 +1922 216 19.71 13.71 18.06 0.22 502.81 271.67 52285 +1922 217 19.76 13.76 18.11 0 504.22 361.17 52122 +1922 218 22.55 16.55 20.9 0 588.47 350.61 51958 +1922 219 24.53 18.53 22.88 0.2 655.26 256.28 51791 +1922 220 27.29 21.29 25.64 0.03 758.99 246.25 51622 +1922 221 25.54 19.54 23.89 0.54 691.73 251.62 51451 +1922 222 23.71 17.71 22.06 0 626.86 342.17 51279 +1922 223 23.49 17.49 21.84 0.13 619.42 256.45 51105 +1922 224 21.86 15.86 20.21 0 566.6 347.02 50929 +1922 225 21.43 15.43 19.78 0.01 553.32 260.55 50751 +1922 226 20.05 14.05 18.4 0 512.47 350.89 50572 +1922 227 20.86 14.86 19.21 0.08 536.12 260.22 50392 +1922 228 16.74 10.74 15.09 0.23 424.8 268.53 50210 +1922 229 21.45 15.45 19.8 0.57 553.93 256.89 50026 +1922 230 22.38 16.38 20.73 0.04 583.02 253.48 49842 +1922 231 24.34 18.34 22.69 0 648.58 329.04 49656 +1922 232 21.59 15.59 19.94 0.02 558.23 253.5 49469 +1922 233 22.87 16.87 21.22 0.39 598.86 249.03 49280 +1922 234 17.07 11.07 15.42 2.78 432.93 261.65 49091 +1922 235 17.96 11.96 16.31 0 455.5 344.94 48900 +1922 236 18.83 12.83 17.18 0.47 478.52 255.78 48709 +1922 237 21.96 15.96 20.31 0.74 569.72 247.09 48516 +1922 238 25.52 19.52 23.87 0.02 690.99 235.67 48323 +1922 239 27.26 21.26 25.61 0.03 757.79 228.87 48128 +1922 240 26.92 20.92 25.27 0 744.33 305.06 47933 +1922 241 25.49 19.49 23.84 0 689.89 309.62 47737 +1922 242 26.68 20.68 25.03 0 734.95 302.9 47541 +1922 243 26.09 20.09 24.44 0.06 712.3 227.78 47343 +1922 244 18.4 12.4 16.75 0.19 467.02 246.37 47145 +1922 245 16.7 10.7 15.05 1.75 423.83 248.32 46947 +1922 246 17.34 11.34 15.69 0.01 439.67 245.62 46747 +1922 247 17.7 11.7 16.05 0.16 448.8 243.53 46547 +1922 248 13.62 7.62 11.97 0.76 354.21 249.13 46347 +1922 249 15.76 9.76 14.11 0.52 401.44 244.07 46146 +1922 250 15.34 9.34 13.69 0.34 391.77 243.31 45945 +1922 251 15.41 9.41 13.76 0.37 393.37 241.58 45743 +1922 252 14.73 8.73 13.08 0.2 378.08 241.05 45541 +1922 253 11.71 5.71 10.06 0.01 316.16 243.85 45339 +1922 254 12.52 6.52 10.87 0.37 331.84 241.1 45136 +1922 255 15.95 9.95 14.3 0.29 405.89 234.1 44933 +1922 256 20.4 14.4 18.75 0.56 522.58 223.82 44730 +1922 257 20.48 14.48 18.83 0.53 524.91 222.06 44527 +1922 258 21.45 15.45 19.8 0.2 553.93 218.19 44323 +1922 259 21.32 15.32 19.67 0.02 549.96 216.71 44119 +1922 260 16.23 10.23 14.58 0.23 412.51 224.9 43915 +1922 261 17.93 11.93 16.28 2.29 454.72 220.09 43711 +1922 262 20.15 14.15 18.5 0.29 515.34 213.99 43507 +1922 263 16.8 10.8 15.15 0.55 426.27 218.48 43303 +1922 264 13.93 7.93 12.28 1.21 360.75 221.02 43099 +1922 265 11.46 5.46 9.81 2.39 311.44 222.48 42894 +1922 266 13.25 7.25 11.6 0.98 346.55 218.29 42690 +1922 267 13.62 7.62 11.97 0.22 354.21 215.75 42486 +1922 268 13.02 7.02 11.37 0.03 341.86 214.62 42282 +1922 269 15.65 9.65 14 0.69 398.89 208.99 42078 +1922 270 17.43 11.43 15.78 0 441.94 272.22 41875 +1922 271 21.55 15.55 19.9 0 557 259.27 41671 +1922 272 26.23 20.23 24.58 1.09 717.62 181.25 41468 +1922 273 19.35 13.35 17.7 0 492.75 259.99 41265 +1922 274 10.59 4.59 8.94 0.92 295.51 205.56 41062 +1922 275 11.44 5.44 9.79 0 311.07 270.02 40860 +1922 276 8.74 2.74 7.09 0.45 263.94 203.27 40658 +1922 277 11.23 5.23 9.58 0.01 307.16 198.68 40456 +1922 278 9.83 3.83 8.18 0.01 282.17 197.97 40255 +1922 279 14.5 8.5 12.85 0.11 373.03 190.44 40054 +1922 280 14.08 8.08 12.43 0 363.94 252.01 39854 +1922 281 15.25 9.25 13.6 1.25 389.73 185.43 39654 +1922 282 11.86 5.86 10.21 0.68 319.01 187.54 39455 +1922 283 12.58 6.58 10.93 0.33 333.03 184.61 39256 +1922 284 12.78 6.78 11.13 0.23 337.02 182.11 39058 +1922 285 11.17 5.17 9.52 0 306.05 242.5 38861 +1922 286 9.31 3.31 7.66 1.18 273.34 181.59 38664 +1922 287 14.57 8.57 12.92 0.88 374.56 173.75 38468 +1922 288 11.99 5.99 10.34 2.19 321.51 174.63 38273 +1922 289 8.78 2.78 7.13 1.1 264.59 175.7 38079 +1922 290 7.42 1.42 5.77 0 243.22 232.85 37885 +1922 291 9.01 3.01 7.36 0 268.36 228.37 37693 +1922 292 11.71 5.71 10.06 0.38 316.16 166.75 37501 +1922 293 9.69 3.69 8.04 0.09 279.77 166.58 37311 +1922 294 6.32 0.32 4.67 0.26 227.04 167.04 37121 +1922 295 4.82 -1.18 3.17 0.04 206.47 165.87 36933 +1922 296 9.33 3.33 7.68 0 273.67 214.15 36745 +1922 297 9.42 3.42 7.77 0.02 275.19 158.48 36560 +1922 298 13.72 7.72 12.07 0 356.31 203.27 36375 +1922 299 12.88 6.88 11.23 0.56 339.03 151.26 36191 +1922 300 13.59 7.59 11.94 1.58 353.59 148.56 36009 +1922 301 8.18 2.18 6.53 1 254.97 151.46 35829 +1922 302 10.21 4.21 8.56 0.02 288.77 147.9 35650 +1922 303 9.82 3.82 8.17 0.27 282 146.28 35472 +1922 304 9.8 3.8 8.15 0.33 281.65 144.45 35296 +1922 305 4.16 -1.84 2.51 0.09 197.94 146.15 35122 +1922 306 3.02 -2.98 1.37 0 183.92 193.37 34950 +1922 307 6.78 0.78 5.13 0 233.69 187.96 34779 +1922 308 8 2 6.35 0 252.14 184.25 34610 +1922 309 5.65 -0.35 4 0 217.64 183.91 34444 +1922 310 3.45 -2.55 1.8 0.13 189.1 137.28 34279 +1922 311 5.9 -0.1 4.25 0 221.11 179.05 34116 +1922 312 11.81 5.81 10.16 0.02 318.06 128.14 33956 +1922 313 9.96 3.96 8.31 0.17 284.41 128.03 33797 +1922 314 6.78 0.78 5.13 0 233.69 171.6 33641 +1922 315 7.23 1.23 5.58 0 240.35 168.69 33488 +1922 316 13.26 7.26 11.61 0 346.76 160.55 33337 +1922 317 10.28 4.28 8.63 0 290 161.6 33188 +1922 318 4.28 -1.72 2.63 0 199.47 164.12 33042 +1922 319 -0.12 -6.12 -1.77 0 149.64 164.9 32899 +1922 320 5.32 -0.68 3.67 0 213.14 159.82 32758 +1922 321 0.61 -5.39 -1.04 0.06 157.08 120.37 32620 +1922 322 6.17 0.17 4.52 0 224.9 155.27 32486 +1922 323 7.25 1.25 5.6 0 240.65 152.85 32354 +1922 324 3.35 -2.65 1.7 0.25 187.89 115.07 32225 +1922 325 2.69 -3.31 1.04 0.49 180.03 114.05 32100 +1922 326 2.06 -3.94 0.41 0.06 172.79 113.21 31977 +1922 327 4.15 -1.85 2.5 0.1 197.81 110.91 31858 +1922 328 -0.51 -6.51 -2.16 1.05 145.8 156.01 31743 +1922 329 2.77 -3.23 1.12 0 180.96 189.76 31631 +1922 330 8.8 2.8 7.15 0 264.91 183.3 31522 +1922 331 5.04 -0.96 3.39 0 209.38 184.17 31417 +1922 332 5.98 -0.02 4.33 0 222.23 181.3 31316 +1922 333 6.83 0.83 5.18 0 234.42 137.17 31218 +1922 334 4.74 -1.26 3.09 0 205.42 137.43 31125 +1922 335 9 3 7.35 0 268.19 133.31 31035 +1922 336 4.91 -1.09 3.26 0 207.65 135.08 30949 +1922 337 6.42 0.42 4.77 0 228.47 132.46 30867 +1922 338 3.86 -2.14 2.21 0 194.16 133.08 30790 +1922 339 -0.42 -6.42 -2.07 0 146.68 134.37 30716 +1922 340 -0.29 -6.29 -1.94 0 147.96 133.57 30647 +1922 341 -0.4 -6.4 -2.05 0 146.88 132.68 30582 +1922 342 0.67 -5.33 -0.98 0 157.7 131.46 30521 +1922 343 1.55 -4.45 -0.1 0.57 167.11 97.67 30465 +1922 344 1.14 -4.86 -0.51 0 162.67 129.28 30413 +1922 345 2.84 -3.16 1.19 0 181.79 128.02 30366 +1922 346 -0.09 -6.09 -1.74 0 149.94 128.82 30323 +1922 347 1.95 -4.05 0.3 0 171.55 127.31 30284 +1922 348 3.55 -2.45 1.9 0 190.33 126.16 30251 +1922 349 3.74 -2.26 2.09 0 192.67 125.67 30221 +1922 350 -0.39 -6.39 -2.04 0.02 146.97 139.23 30197 +1922 351 5.37 -0.63 3.72 0 213.82 124.2 30177 +1922 352 4.46 -1.54 2.81 0 201.78 124.63 30162 +1922 353 -0.46 -6.46 -2.11 0 146.29 126.91 30151 +1922 354 3.15 -2.85 1.5 0 185.47 125.24 30145 +1922 355 5.36 -0.64 3.71 0 213.68 124.02 30144 +1922 356 7.16 1.16 5.51 0 239.31 122.92 30147 +1922 357 6.68 0.68 5.03 0 232.23 123.29 30156 +1922 358 7.95 1.95 6.3 0 251.36 122.52 30169 +1922 359 5.84 -0.16 4.19 0 220.27 124.02 30186 +1922 360 6.46 0.46 4.81 0 229.04 123.99 30208 +1922 361 5.97 -0.03 4.32 0 222.09 124.63 30235 +1922 362 10.84 4.84 9.19 0 300.02 121.53 30267 +1922 363 9.61 3.61 7.96 0 278.4 123.1 30303 +1922 364 6.95 0.95 5.3 0 236.19 125.41 30343 +1922 365 7.31 1.31 5.66 0 241.56 125.73 30388 +1923 1 8.08 2.08 6.43 0 253.4 126.08 30438 +1923 2 3.35 -2.65 1.7 0 187.89 129.74 30492 +1923 3 4.43 -1.57 2.78 0 201.39 130.08 30551 +1923 4 7.3 1.3 5.65 0 241.41 129.19 30614 +1923 5 12.11 6.11 10.46 0.03 323.82 94.44 30681 +1923 6 10.31 4.31 8.66 0 290.53 128.39 30752 +1923 7 8.02 2.02 6.37 0 252.46 130.97 30828 +1923 8 4.23 -1.77 2.58 0 198.83 134.92 30907 +1923 9 3 -3 1.35 0 183.68 136.86 30991 +1923 10 2.62 -3.38 0.97 0 179.21 138.37 31079 +1923 11 0.85 -5.15 -0.8 0.14 159.59 105.18 31171 +1923 12 1.82 -4.18 0.17 0 170.1 140.79 31266 +1923 13 0.56 -5.44 -1.09 0.03 156.56 107.27 31366 +1923 14 -1.67 -7.67 -3.32 0.61 134.87 152.92 31469 +1923 15 1.09 -4.91 -0.56 0.1 162.13 152.81 31575 +1923 16 0.01 -5.99 -1.64 0.02 150.94 154.01 31686 +1923 17 2.61 -3.39 0.96 0.57 179.09 153.81 31800 +1923 18 -0.77 -6.77 -2.42 0.13 143.28 156.73 31917 +1923 19 -2.27 -8.27 -3.92 0.07 129.49 158.72 32038 +1923 20 1.6 -4.4 -0.05 0.22 167.66 158.22 32161 +1923 21 0.88 -5.12 -0.77 0.15 159.9 159.73 32289 +1923 22 3.67 -2.33 2.02 0 191.8 198.37 32419 +1923 23 3.37 -2.63 1.72 0 188.13 199.74 32552 +1923 24 5.02 -0.98 3.37 0.41 209.11 160.09 32688 +1923 25 5.76 -0.24 4.11 0.1 219.16 120.6 32827 +1923 26 2.26 -3.74 0.61 0 175.06 164.99 32969 +1923 27 4.81 -1.19 3.16 0 206.34 165.41 33114 +1923 28 7.87 1.87 6.22 0 250.12 165.26 33261 +1923 29 7.64 1.64 5.99 0 246.57 167.81 33411 +1923 30 3.49 -2.51 1.84 0.57 189.59 129.84 33564 +1923 31 1.7 -4.3 0.05 0.02 168.77 132.45 33718 +1923 32 2.1 -3.9 0.45 0 173.24 178.49 33875 +1923 33 -3.41 -9.41 -5.06 0.9 119.8 179.27 34035 +1923 34 -2.77 -8.77 -4.42 0.23 125.16 181.19 34196 +1923 35 -1.54 -7.54 -3.19 0.02 136.05 182.26 34360 +1923 36 -2.51 -8.51 -4.16 0 127.4 231.94 34526 +1923 37 1.23 -4.77 -0.42 0 163.64 232.1 34694 +1923 38 3.32 -2.68 1.67 0.01 187.52 184.82 34863 +1923 39 3.53 -2.47 1.88 0.03 190.08 186.07 35035 +1923 40 4.55 -1.45 2.9 0 202.94 235.95 35208 +1923 41 4.45 -1.55 2.8 0 201.65 237.94 35383 +1923 42 6.09 0.09 4.44 0 223.77 238.28 35560 +1923 43 4.44 -1.56 2.79 0 201.52 204.73 35738 +1923 44 3.69 -2.31 2.04 0 192.05 207.88 35918 +1923 45 7.25 1.25 5.6 0 240.65 207.49 36099 +1923 46 9.34 3.34 7.69 0.3 273.84 156.01 36282 +1923 47 6.88 0.88 5.23 0.81 235.16 159.99 36466 +1923 48 5.82 -0.18 4.17 0.26 219.99 162.81 36652 +1923 49 2.6 -3.4 0.95 0.02 178.98 166.85 36838 +1923 50 2.83 -3.17 1.18 1.19 181.67 168.73 37026 +1923 51 -1.07 -7.07 -2.72 0 140.43 230.55 37215 +1923 52 -1.48 -7.48 -3.13 0 136.61 233.65 37405 +1923 53 1.46 -4.54 -0.19 0.02 166.13 176.1 37596 +1923 54 0.61 -5.39 -1.04 0.47 157.08 178.62 37788 +1923 55 5.05 -0.95 3.4 0.07 209.51 178.29 37981 +1923 56 10.49 4.49 8.84 0.32 293.72 175.88 38175 +1923 57 11.98 5.98 10.33 0 321.31 235.32 38370 +1923 58 8.45 2.45 6.8 0 259.26 242.73 38565 +1923 59 10.86 4.86 9.21 0.25 300.38 181.8 38761 +1923 60 14.35 8.35 12.7 0.07 369.76 179.96 38958 +1923 61 9 3 7.35 0 268.19 250.53 39156 +1923 62 9.82 3.82 8.17 0.07 282 189.2 39355 +1923 63 10.35 4.35 8.7 0 291.24 254.54 39553 +1923 64 11.71 5.71 10.06 0.17 316.16 191.61 39753 +1923 65 11.48 5.48 9.83 0.28 311.82 193.99 39953 +1923 66 11.89 5.89 10.24 0.37 319.59 195.55 40154 +1923 67 7.28 1.28 5.63 0.11 241.11 202.3 40355 +1923 68 6.27 0.27 4.62 0 226.32 273.74 40556 +1923 69 7.8 1.8 6.15 0.24 249.03 205.96 40758 +1923 70 8.41 2.41 6.76 0 258.62 276.69 40960 +1923 71 10.47 4.47 8.82 0.28 293.37 207.6 41163 +1923 72 6.44 0.44 4.79 0 228.76 284.79 41366 +1923 73 8.87 2.87 7.22 0 266.06 284.47 41569 +1923 74 8.67 2.67 7.02 0 262.8 287.48 41772 +1923 75 9.18 3.18 7.53 0.04 271.17 217.13 41976 +1923 76 8.72 2.72 7.07 0.11 263.61 219.57 42179 +1923 77 8.65 2.65 7 0 262.48 295.45 42383 +1923 78 8.41 2.41 6.76 0 258.62 298.44 42587 +1923 79 6.81 0.81 5.16 0 234.13 303.21 42791 +1923 80 4.22 -1.78 2.57 0 198.7 308.68 42996 +1923 81 6.17 0.17 4.52 0 224.9 309.13 43200 +1923 82 8.16 2.16 6.51 0.21 254.65 231.96 43404 +1923 83 10.09 4.09 8.44 0 286.67 308.99 43608 +1923 84 8.4 2.4 6.75 0.08 258.46 235.49 43812 +1923 85 9.38 3.38 7.73 0.57 274.51 236.31 44016 +1923 86 10.93 4.93 9.28 0 301.65 315.05 44220 +1923 87 8.31 2.31 6.66 0.79 257.03 241.18 44424 +1923 88 5.36 -0.64 3.71 0.93 213.68 245.8 44627 +1923 89 3.46 -2.54 1.81 0.01 189.23 249.11 44831 +1923 90 0.95 -5.05 -0.7 0 160.64 336.98 45034 +1923 91 6.29 0.29 4.64 0.55 226.61 250.2 45237 +1923 92 4.91 -1.09 3.26 0 207.65 337.54 45439 +1923 93 5.5 -0.5 3.85 0 215.58 339.09 45642 +1923 94 4.1 -1.9 2.45 0 197.18 342.91 45843 +1923 95 9.29 3.29 7.64 0 273.01 338.2 46045 +1923 96 8.21 2.21 6.56 0 255.44 341.96 46246 +1923 97 8.93 2.93 7.28 0.29 267.04 257.22 46446 +1923 98 6.15 0.15 4.5 0 224.62 348.88 46647 +1923 99 6.77 0.77 5.12 0.62 233.54 262.57 46846 +1923 100 9.57 3.57 7.92 0.37 277.72 260.93 47045 +1923 101 5.31 -0.69 3.66 1.3 213 266.96 47243 +1923 102 9.33 3.33 7.68 0.96 273.67 264.12 47441 +1923 103 9.56 3.56 7.91 0 277.55 353.65 47638 +1923 104 6.73 0.73 5.08 0 232.96 359.76 47834 +1923 105 6.4 0.4 4.75 0 228.18 362.04 48030 +1923 106 10.72 4.72 9.07 0 297.85 356.96 48225 +1923 107 12.09 6.09 10.44 0 323.43 356.08 48419 +1923 108 12.74 6.74 11.09 0 336.22 356.53 48612 +1923 109 14.79 8.79 13.14 0.66 379.41 265.26 48804 +1923 110 15.79 9.79 14.14 0.82 402.14 264.52 48995 +1923 111 13.77 7.77 12.12 1.73 357.36 269.19 49185 +1923 112 16.88 10.88 15.23 0.64 428.23 264.7 49374 +1923 113 14.84 8.84 13.19 0 380.52 359.34 49561 +1923 114 17.3 11.3 15.65 0 438.67 354.58 49748 +1923 115 17.65 11.65 16 0.06 447.52 266.26 49933 +1923 116 21.52 15.52 19.87 0.04 556.07 258.08 50117 +1923 117 14.5 8.5 12.85 0.47 373.03 274.16 50300 +1923 118 16.77 10.77 15.12 0 425.54 361.19 50481 +1923 119 13.84 7.84 12.19 0.29 358.84 277.17 50661 +1923 120 12.82 6.82 11.17 1.26 337.82 279.72 50840 +1923 121 19.6 13.6 17.95 0.18 499.72 267.28 51016 +1923 122 19.79 13.79 18.14 0 505.07 356.93 51191 +1923 123 19.67 13.67 18.02 0 501.68 358.31 51365 +1923 124 16.88 10.88 15.23 0 428.23 367.6 51536 +1923 125 15.15 9.15 13.5 0.27 387.46 279.8 51706 +1923 126 20.12 14.12 18.47 0 514.48 359.82 51874 +1923 127 20.48 14.48 18.83 0.08 524.91 269.61 52039 +1923 128 20.27 14.27 18.62 0.32 518.8 270.87 52203 +1923 129 23.97 17.97 22.32 0 635.75 348.23 52365 +1923 130 25.76 19.76 24.11 0 699.9 341.23 52524 +1923 131 24.43 18.43 22.78 0 651.74 347.81 52681 +1923 132 20.27 14.27 18.62 0 518.8 364.33 52836 +1923 133 19.47 13.47 17.82 0 496.08 367.64 52989 +1923 134 19.01 13.01 17.36 0 483.41 369.8 53138 +1923 135 13.63 7.63 11.98 0 354.42 384.98 53286 +1923 136 10.4 4.4 8.75 0 292.12 392.34 53430 +1923 137 15.03 9.03 13.38 0.45 384.76 287.24 53572 +1923 138 14.77 8.77 13.12 0.01 378.97 288.18 53711 +1923 139 13.03 7.03 11.38 0.33 342.06 291.75 53848 +1923 140 12.49 6.49 10.84 0.03 331.25 293 53981 +1923 141 12.58 6.58 10.93 0.29 333.03 293.19 54111 +1923 142 19.1 13.1 17.45 0.72 485.86 280.65 54238 +1923 143 20.8 14.8 19.15 0.36 534.34 276.78 54362 +1923 144 22.01 16.01 20.36 0.75 571.29 273.84 54483 +1923 145 18.79 12.79 17.14 0 477.44 376.64 54600 +1923 146 19.67 13.67 18.02 0.09 501.68 280.64 54714 +1923 147 15.32 9.32 13.67 0.09 391.32 290.51 54824 +1923 148 22.33 16.33 20.68 0.36 581.42 274.17 54931 +1923 149 21.09 15.09 19.44 0.22 543 277.84 55034 +1923 150 18.56 12.56 16.91 1.13 471.27 284.42 55134 +1923 151 17.61 11.61 15.96 0 446.5 382.49 55229 +1923 152 16.89 10.89 15.24 0.76 428.48 288.5 55321 +1923 153 18.41 12.41 16.76 0.8 467.28 285.33 55409 +1923 154 15.04 9.04 13.39 0 384.99 390.18 55492 +1923 155 17.99 11.99 16.34 0 456.27 382.22 55572 +1923 156 15.9 9.9 14.25 0.06 404.71 291.35 55648 +1923 157 16.71 10.71 15.06 2.07 424.07 289.82 55719 +1923 158 13.85 7.85 12.2 1.49 359.05 295.47 55786 +1923 159 13.26 7.26 11.61 0 346.76 395.58 55849 +1923 160 16.11 10.11 14.46 0 409.66 388.69 55908 +1923 161 18.65 12.65 17 1.78 473.68 286.02 55962 +1923 162 19.68 13.68 18.03 0.35 501.96 283.57 56011 +1923 163 18.96 12.96 17.31 1.14 482.04 285.49 56056 +1923 164 14.26 8.26 12.61 0.31 367.81 295.36 56097 +1923 165 12.54 6.54 10.89 0.12 332.24 298.41 56133 +1923 166 8.86 2.86 7.21 0.29 265.89 303.86 56165 +1923 167 13.36 7.36 11.71 0 348.81 396.07 56192 +1923 168 19.8 13.8 18.15 0 505.35 378.15 56214 +1923 169 23.74 17.74 22.09 0 627.88 363.38 56231 +1923 170 21.77 15.77 20.12 2.12 563.79 278.39 56244 +1923 171 18.94 12.94 17.29 1.12 481.5 285.77 56252 +1923 172 23.01 17.01 21.36 0.35 603.45 274.82 56256 +1923 173 20.91 14.91 19.26 0.1 537.61 280.77 56255 +1923 174 17.25 11.25 15.6 0.01 437.41 289.54 56249 +1923 175 16.65 10.65 15 0.35 422.61 290.8 56238 +1923 176 15.75 9.75 14.1 0 401.21 390.14 56223 +1923 177 20.05 14.05 18.4 0.06 512.47 282.82 56203 +1923 178 17.73 11.73 16.08 0.02 449.57 288.38 56179 +1923 179 19.05 13.05 17.4 0 484.5 380.32 56150 +1923 180 19.16 13.16 17.51 0 487.51 379.85 56116 +1923 181 21.36 15.36 19.71 0 551.18 372.21 56078 +1923 182 23.3 17.3 21.65 0 613.06 364.58 56035 +1923 183 20.94 14.94 19.29 0 538.51 373.41 55987 +1923 184 23.17 17.17 21.52 0 608.73 364.79 55935 +1923 185 23.06 17.06 21.41 0 605.1 365.15 55879 +1923 186 22.61 16.61 20.96 0 590.41 366.68 55818 +1923 187 25 19 23.35 0 672.02 356.5 55753 +1923 188 22.78 16.78 21.13 0 595.92 365.56 55684 +1923 189 25.87 19.87 24.22 0 704.01 352.09 55611 +1923 190 22.03 16.03 20.38 0.53 571.92 275.94 55533 +1923 191 24.79 18.79 23.14 0.28 664.49 267.28 55451 +1923 192 26.93 20.93 25.28 0.08 744.72 259.57 55366 +1923 193 28.59 22.59 26.94 1.1 812.46 252.95 55276 +1923 194 28.16 22.16 26.51 0.19 794.43 254.52 55182 +1923 195 25.27 19.27 23.62 0.47 681.82 264.91 55085 +1923 196 22.96 16.96 21.31 0 601.8 362.6 54984 +1923 197 24.01 18.01 22.36 0.22 637.13 268.4 54879 +1923 198 24.37 18.37 22.72 0.66 649.63 266.94 54770 +1923 199 24.3 18.3 22.65 1.11 647.19 266.91 54658 +1923 200 24.21 18.21 22.56 0 644.05 355.87 54542 +1923 201 23.65 17.65 22 0 624.82 357.75 54423 +1923 202 23 17 21.35 0 603.12 359.82 54301 +1923 203 23.93 17.93 22.28 0 634.38 355.55 54176 +1923 204 23.19 17.19 21.54 0.2 609.4 268.56 54047 +1923 205 22.25 16.25 20.6 0 578.87 361.22 53915 +1923 206 20.81 14.81 19.16 0.37 534.64 274.42 53780 +1923 207 24.23 18.23 22.58 0 644.75 352.12 53643 +1923 208 22.51 16.51 20.86 0 587.18 358.38 53502 +1923 209 22.13 16.13 20.48 0 575.07 359.18 53359 +1923 210 22.79 16.79 21.14 1.01 596.25 267.04 53213 +1923 211 19.67 13.67 18.02 0 501.68 366.36 53064 +1923 212 19.68 13.68 18.03 0.48 501.96 274.15 52913 +1923 213 15.16 9.16 13.51 0.32 387.69 283.23 52760 +1923 214 17.17 11.17 15.52 0.29 435.41 278.68 52604 +1923 215 19.69 13.69 18.04 0 502.24 363.3 52445 +1923 216 19.21 13.21 17.56 0.12 488.88 272.86 52285 +1923 217 21.53 15.53 19.88 0 556.38 355.16 52122 +1923 218 19.7 13.7 18.05 0 502.53 360.54 51958 +1923 219 17.58 11.58 15.93 0 445.74 365.89 51791 +1923 220 21.99 15.99 20.34 0.07 570.66 263.05 51622 +1923 221 19.82 13.82 18.17 0.06 505.92 267.87 51451 +1923 222 19.4 13.4 17.75 0.02 494.14 268.09 51279 +1923 223 21.84 15.84 20.19 0.11 565.97 261.1 51105 +1923 224 20.85 14.85 19.2 0 535.82 350.53 50929 +1923 225 20.85 14.85 19.2 0.07 535.82 262.05 50751 +1923 226 22.82 16.82 21.17 1.66 597.22 255.93 50572 +1923 227 22.96 16.96 21.31 0 601.8 339.47 50392 +1923 228 23.72 17.72 22.07 1.03 627.2 251.52 50210 +1923 229 24.91 18.91 23.26 0.02 668.79 247 50026 +1923 230 26.18 20.18 24.53 0 715.72 322.63 49842 +1923 231 29.3 23.3 27.65 0 842.98 306.1 49656 +1923 232 31.28 25.28 29.63 0 933.26 293.91 49469 +1923 233 29.47 23.47 27.82 0 850.43 302.68 49280 +1923 234 28.61 22.61 26.96 0 813.31 305.82 49091 +1923 235 27.08 21.08 25.43 0.54 750.64 233.86 48900 +1923 236 22.67 16.67 21.02 1.06 592.35 246.41 48709 +1923 237 20.57 14.57 18.92 1.58 527.55 250.56 48516 +1923 238 19.38 13.38 17.73 0 493.58 336.1 48323 +1923 239 20.98 14.98 19.33 0 539.7 329.61 48128 +1923 240 24.34 18.34 22.69 0 648.58 315.89 47933 +1923 241 26.95 20.95 25.3 0 745.51 303.32 47737 +1923 242 27.25 21.25 25.6 0 757.39 300.35 47541 +1923 243 26.82 20.82 25.17 0 740.41 300.54 47343 +1923 244 22.29 16.29 20.64 0.36 580.15 237.38 47145 +1923 245 22.63 16.63 20.98 1.61 591.05 235.16 46947 +1923 246 23.78 17.78 22.13 0.28 629.24 230.64 46747 +1923 247 23.62 17.62 21.97 0 623.81 306.33 46547 +1923 248 19.38 13.38 17.73 0 493.58 318.18 46347 +1923 249 20.58 14.58 18.93 0.04 527.84 234.45 46146 +1923 250 18.42 12.42 16.77 0 467.55 316.85 45945 +1923 251 16.71 10.71 15.06 0.02 424.07 239.32 45743 +1923 252 19.64 13.64 17.99 0.99 500.84 231.93 45541 +1923 253 17.19 11.19 15.54 0 435.91 313.62 45339 +1923 254 19.4 13.4 17.75 0 494.14 305.72 45136 +1923 255 17.94 11.94 16.29 0.01 454.98 230.52 44933 +1923 256 15.14 9.14 13.49 0.13 387.24 233.73 44730 +1923 257 16.02 10.02 14.37 1.65 407.53 230.64 44527 +1923 258 16.58 10.58 14.93 0.17 420.91 227.92 44323 +1923 259 22.2 16.2 20.55 0.05 577.29 214.67 44119 +1923 260 16.13 10.13 14.48 0.09 410.13 225.07 43915 +1923 261 18.39 12.39 16.74 0.35 466.76 219.23 43711 +1923 262 18.57 12.57 16.92 0 471.54 289.51 43507 +1923 263 18.68 12.68 17.03 0.26 474.48 215.1 43303 +1923 264 20.02 14.02 18.37 0 511.61 280.77 43099 +1923 265 14.99 8.99 13.34 0 383.87 290.23 42894 +1923 266 15.77 9.77 14.12 0 401.68 286.15 42690 +1923 267 18.53 12.53 16.88 0 470.47 277.24 42486 +1923 268 18.64 12.64 16.99 0 473.41 274.46 42282 +1923 269 20.37 14.37 18.72 0 521.7 267.58 42078 +1923 270 17.38 11.38 15.73 0 440.68 272.33 41875 +1923 271 18.12 12.12 16.47 0 459.66 268.06 41671 +1923 272 16.43 10.43 14.78 0 417.29 269.09 41468 +1923 273 17.82 11.82 16.17 0.08 451.88 197.69 41265 +1923 274 14.65 8.65 13 0.06 376.32 200.56 41062 +1923 275 15.38 9.38 13.73 0.01 392.69 197.46 40860 +1923 276 12.6 6.6 10.95 0.15 333.43 199.11 40658 +1923 277 15.32 9.32 13.67 1.36 391.32 193.55 40456 +1923 278 14.68 8.68 13.03 0.08 376.98 192.3 40255 +1923 279 14.08 8.08 12.43 0 363.94 254.65 40054 +1923 280 15.36 9.36 13.71 0 392.23 249.73 39854 +1923 281 14.74 8.74 13.09 1.18 378.3 186.12 39654 +1923 282 15.67 9.67 14.02 0 399.35 243.76 39455 +1923 283 17.47 11.47 15.82 0.07 442.95 178.12 39256 +1923 284 18.55 12.55 16.9 0 471 232.29 39058 +1923 285 18.06 12.06 16.41 0.36 458.09 173.07 38861 +1923 286 19.17 13.17 17.52 0.23 487.78 169.3 38664 +1923 287 20.02 14.02 18.37 0.6 511.61 165.75 38468 +1923 288 20.78 14.78 19.13 1.47 533.75 162.43 38273 +1923 289 20.59 14.59 18.94 0.02 528.14 160.89 38079 +1923 290 14.81 8.81 13.16 0.03 379.85 167.31 37885 +1923 291 15.14 9.14 13.49 0.08 387.24 164.91 37693 +1923 292 13.43 7.43 11.78 0.46 350.26 164.93 37501 +1923 293 13.93 7.93 12.28 0 360.75 216.45 37311 +1923 294 14.95 8.95 13.3 0 382.97 212.01 37121 +1923 295 17.31 11.31 15.66 0 438.92 205.21 36933 +1923 296 16.1 10.1 14.45 0.06 409.42 153.61 36745 +1923 297 16.13 10.13 14.48 0.01 410.13 151.58 36560 +1923 298 16.85 10.85 15.2 0 427.5 198.35 36375 +1923 299 16.74 10.74 15.09 0.54 424.8 146.87 36191 +1923 300 17.21 11.21 15.56 0.45 436.41 144.33 36009 +1923 301 17.42 11.42 15.77 0 441.69 189.65 35829 +1923 302 17.19 11.19 15.54 0 435.91 187.52 35650 +1923 303 17.13 11.13 15.48 0.05 434.42 138.85 35472 +1923 304 15.71 9.71 14.06 0 400.28 185.02 35296 +1923 305 5.98 -0.02 4.33 0 222.23 193.44 35122 +1923 306 4.96 -1.04 3.31 0 208.32 191.97 34950 +1923 307 2.46 -3.54 0.81 0 177.35 191.18 34779 +1923 308 4.18 -1.82 2.53 0 198.19 187.36 34610 +1923 309 4.74 -1.26 3.09 0 205.42 184.61 34444 +1923 310 7.19 1.19 5.54 0 239.76 180.19 34279 +1923 311 9.82 3.82 8.17 0 282 175.58 34116 +1923 312 13.28 7.28 11.63 0 347.17 169.12 33956 +1923 313 10.97 4.97 9.32 0 302.38 169.67 33797 +1923 314 11.15 5.15 9.5 0 305.68 167.55 33641 +1923 315 15.71 9.71 14.06 0.07 400.28 119.65 33488 +1923 316 17.39 11.39 15.74 0.37 440.93 116.26 33337 +1923 317 20.56 14.56 18.91 0 527.26 147.71 33188 +1923 318 17.39 11.39 15.74 0.21 440.93 113.01 33042 +1923 319 14.91 8.91 13.26 0.4 382.08 114.35 32899 +1923 320 12.26 6.26 10.61 1.76 326.74 115.32 32758 +1923 321 11.05 5.05 9.4 0.01 303.84 114.7 32620 +1923 322 9.54 3.54 7.89 0 277.21 152.56 32486 +1923 323 6.84 0.84 5.19 0.29 234.57 114.87 32354 +1923 324 4.22 -1.78 2.57 0.68 198.7 114.67 32225 +1923 325 0.93 -5.07 -0.72 0 160.43 153.01 32100 +1923 326 6.81 0.81 5.16 0.28 234.13 110.97 31977 +1923 327 6.09 0.09 4.44 0 223.77 146.62 31858 +1923 328 5.66 -0.34 4.01 0.06 217.78 108.71 31743 +1923 329 3.37 -2.63 1.72 0.29 188.13 108.65 31631 +1923 330 7.57 1.57 5.92 0.01 245.5 105.5 31522 +1923 331 9.27 3.27 7.62 1.89 272.67 103.52 31417 +1923 332 10.59 4.59 8.94 1.15 295.51 101.46 31316 +1923 333 7.32 1.32 5.67 1.59 241.71 102.62 31218 +1923 334 6.72 0.72 5.07 0 232.81 136.15 31125 +1923 335 3.2 -2.8 1.55 0 186.07 137.14 31035 +1923 336 4.82 -1.18 3.17 0 206.47 135.14 30949 +1923 337 6.42 0.42 4.77 0 228.47 132.46 30867 +1923 338 7.32 1.32 5.67 0 241.71 130.92 30790 +1923 339 6.12 0.12 4.47 0.02 224.2 98.2 30716 +1923 340 6.28 0.28 4.63 0 226.47 130.11 30647 +1923 341 6.78 0.78 5.13 0 233.69 128.86 30582 +1923 342 8.57 2.57 6.92 0 261.19 126.85 30521 +1923 343 6.94 0.94 5.29 0.62 236.04 95.39 30465 +1923 344 6.2 0.2 4.55 1.16 225.33 94.9 30413 +1923 345 6.15 0.15 4.5 0.18 224.62 94.61 30366 +1923 346 9.01 3.01 7.36 0.63 268.36 92.72 30323 +1923 347 6.47 0.47 4.82 0.44 229.19 93.6 30284 +1923 348 6.45 0.45 4.8 0.96 228.9 93.35 30251 +1923 349 2.91 -3.09 1.26 0.01 182.61 94.58 30221 +1923 350 3.98 -2.02 2.33 0.05 195.67 93.91 30197 +1923 351 -3.16 -9.16 -4.81 0 121.87 128.07 30177 +1923 352 0.43 -5.57 -1.22 0.67 155.21 94.96 30162 +1923 353 2.01 -3.99 0.36 0.01 172.22 94.37 30151 +1923 354 1.93 -4.07 0.28 0.05 171.33 94.38 30145 +1923 355 -2.72 -8.72 -4.37 0.32 125.59 140.6 30144 +1923 356 -0.09 -6.09 -1.74 0 149.94 171.56 30147 +1923 357 3.24 -2.76 1.59 0 186.56 169.63 30156 +1923 358 0.86 -5.14 -0.79 0 159.69 170.72 30169 +1923 359 3.53 -2.47 1.88 0 190.08 125.33 30186 +1923 360 4.33 -1.67 2.68 0 200.11 125.26 30208 +1923 361 -1.49 -7.49 -3.14 0.2 136.51 140.5 30235 +1923 362 -5.11 -11.11 -6.76 0.49 106.5 143.25 30267 +1923 363 -7.22 -13.22 -8.87 0.27 91.8 144.93 30303 +1923 364 -7.22 -13.22 -8.87 0 91.8 178.05 30343 +1923 365 -3.08 -9.08 -4.73 0.16 122.54 145.13 30388 +1924 1 -8.41 -14.41 -10.06 0 84.31 180.18 30438 +1924 2 -4.66 -10.66 -6.31 0.08 109.89 146.83 30492 +1924 3 -3.79 -9.79 -5.44 0.24 116.71 148.01 30551 +1924 4 -2.58 -8.58 -4.23 0.37 126.79 149.45 30614 +1924 5 -5.74 -11.74 -7.39 0 101.91 184.58 30681 +1924 6 -1.21 -7.21 -2.86 0 139.11 183.83 30752 +1924 7 -3.54 -9.54 -5.19 0.26 118.73 151.96 30828 +1924 8 -1.31 -7.31 -2.96 0 138.18 186.74 30907 +1924 9 -5.62 -11.62 -7.27 0.01 102.78 154.31 30991 +1924 10 -3.56 -9.56 -5.21 0 118.57 189.92 31079 +1924 11 1.94 -4.06 0.29 0 171.44 188.21 31171 +1924 12 5.34 -0.66 3.69 0.04 213.41 151.76 31266 +1924 13 0.34 -5.66 -1.31 0.2 154.29 154.82 31366 +1924 14 0.62 -5.38 -1.03 0 157.18 191.73 31469 +1924 15 2.74 -3.26 1.09 0 180.61 191.59 31575 +1924 16 4.86 -1.14 3.21 0 206.99 190.85 31686 +1924 17 4.37 -1.63 2.72 0.23 200.62 155.39 31800 +1924 18 5.89 -0.11 4.24 0 220.97 192.1 31917 +1924 19 6.73 0.73 5.08 0 232.96 192.41 32038 +1924 20 4.54 -1.46 2.89 0 202.81 194.75 32161 +1924 21 2.1 -3.9 0.45 0 173.24 197.78 32289 +1924 22 1.84 -4.16 0.19 0 170.32 199.28 32419 +1924 23 0.39 -5.61 -1.26 0 154.8 201.6 32552 +1924 24 1.48 -4.52 -0.17 0 166.35 202.76 32688 +1924 25 0.08 -5.92 -1.57 0.1 151.65 164.14 32827 +1924 26 -1.14 -7.14 -2.79 0 139.77 207.55 32969 +1924 27 -3.68 -9.68 -5.33 0.01 117.59 168.06 33114 +1924 28 -4.16 -10.16 -5.81 0 113.76 212.77 33261 +1924 29 -7.64 -13.64 -9.29 0 89.1 216.18 33411 +1924 30 -4.02 -10.02 -5.67 0 114.87 217.05 33564 +1924 31 2.14 -3.86 0.49 0 173.69 216.01 33718 +1924 32 4.76 -1.24 3.11 0 205.68 176.74 33875 +1924 33 6.69 0.69 5.04 0 232.37 177.87 34035 +1924 34 5.88 -0.12 4.23 0.09 220.83 135.54 34196 +1924 35 6.46 0.46 4.81 0 229.04 182.38 34360 +1924 36 5.61 -0.39 3.96 0.15 217.09 139.18 34526 +1924 37 4.32 -1.68 2.67 0 199.98 188.97 34694 +1924 38 3.72 -2.28 2.07 0 192.42 192.14 34863 +1924 39 1.77 -4.23 0.12 0 169.54 196.07 35035 +1924 40 -0.89 -6.89 -2.54 0 142.14 200.24 35208 +1924 41 -0.89 -6.89 -2.54 0 142.14 202.89 35383 +1924 42 4.8 -1.2 3.15 0.01 206.2 151.31 35560 +1924 43 -0.58 -6.58 -2.23 2.37 145.12 199.34 35738 +1924 44 3.12 -2.88 1.47 0.03 185.11 198.96 35918 +1924 45 -1.54 -7.54 -3.19 0.37 136.05 203.88 36099 +1924 46 -0.41 -6.41 -2.06 0.11 146.78 205.53 36282 +1924 47 0.83 -5.17 -0.82 0 159.38 261.3 36466 +1924 48 -0.32 -6.32 -1.97 0 147.66 264.62 36652 +1924 49 -3.71 -9.71 -5.36 0 117.35 269.03 36838 +1924 50 0.55 -5.45 -1.1 0 156.45 269.11 37026 +1924 51 -1.08 -7.08 -2.73 0.03 140.33 215.33 37215 +1924 52 -1.5 -7.5 -3.15 0 136.42 275.86 37405 +1924 53 -4.39 -10.39 -6.04 0 111.97 280.15 37596 +1924 54 -0.32 -6.32 -1.97 0 147.66 280.53 37788 +1924 55 0.45 -5.55 -1.2 0.3 155.42 222.48 37981 +1924 56 1.25 -4.75 -0.4 0.75 163.85 223.77 38175 +1924 57 -0.04 -6.04 -1.69 0.35 150.44 227.29 38370 +1924 58 -2.42 -8.42 -4.07 0 128.18 293.32 38565 +1924 59 -2.35 -8.35 -4 0.39 128.79 233.19 38761 +1924 60 5.65 -0.35 4 0 217.64 292.86 38958 +1924 61 6.6 0.6 4.95 0.65 231.07 230.63 39156 +1924 62 5.21 -0.79 3.56 0 211.65 297.4 39355 +1924 63 3.79 -2.21 2.14 0 193.29 301.16 39553 +1924 64 7.84 1.84 6.19 0 249.65 298.94 39753 +1924 65 7.84 1.84 6.19 0 249.65 300.84 39953 +1924 66 9.84 3.84 8.19 0 282.34 299.87 40154 +1924 67 10.45 4.45 8.8 0 293.01 300.68 40355 +1924 68 8.32 2.32 6.67 0 257.19 305.34 40556 +1924 69 7.78 1.78 6.13 0 248.73 307.68 40758 +1924 70 5.13 -0.87 3.48 0 210.58 312.81 40960 +1924 71 8.18 2.18 6.53 0 254.97 279.89 41163 +1924 72 6.91 0.91 5.26 0 235.6 284.25 41366 +1924 73 8.91 2.91 7.26 0 266.71 284.42 41569 +1924 74 11.19 5.19 9.54 0 306.42 283.87 41772 +1924 75 9.83 3.83 8.18 0 282.17 288.59 41976 +1924 76 9.77 3.77 8.12 0 281.14 291.3 42179 +1924 77 10 4 8.35 0 285.11 293.55 42383 +1924 78 13.34 7.34 11.69 0.02 348.4 218.04 42587 +1924 79 8.98 2.98 7.33 0.36 267.86 225.29 42791 +1924 80 6.09 0.09 4.44 0 223.77 306.62 42996 +1924 81 2.84 -3.16 1.19 0 181.79 312.67 43200 +1924 82 3.48 -2.52 1.83 0.05 189.47 236.06 43404 +1924 83 4.12 -1.88 2.47 0 197.43 316.62 43608 +1924 84 4.83 -1.17 3.18 0 206.6 318.42 43812 +1924 85 4.13 -1.87 2.48 0 197.56 321.72 44016 +1924 86 2.21 -3.79 0.56 0.6 174.49 244.57 44220 +1924 87 0.99 -5.01 -0.66 0.2 161.07 247.33 44424 +1924 88 4.13 -1.87 2.48 0 197.56 329.12 44627 +1924 89 3.55 -2.45 1.9 0 190.33 332.06 44831 +1924 90 1.65 -4.35 0 0.75 168.21 252.26 45034 +1924 91 5.41 -0.59 3.76 0 214.36 334.68 45237 +1924 92 2.94 -3.06 1.29 0.05 182.97 254.77 45439 +1924 93 4.66 -1.34 3.01 0.32 204.37 255.06 45642 +1924 94 9.85 3.85 8.2 0 282.51 335.17 45843 +1924 95 12.58 6.58 10.93 0.02 333.03 249.38 46045 +1924 96 9.75 3.75 8.1 0 280.79 339.6 46246 +1924 97 9.98 3.98 8.33 0.05 284.76 255.96 46446 +1924 98 10.72 4.72 9.07 0 297.85 342.01 46647 +1924 99 10.68 4.68 9.03 0 297.12 344.09 46846 +1924 100 12.6 6.6 10.95 0 333.43 342.5 47045 +1924 101 19.31 13.31 17.66 0.1 491.64 246.16 47243 +1924 102 18.43 12.43 16.78 0 467.81 332.56 47441 +1924 103 17.35 11.35 15.7 0 439.92 337.27 47638 +1924 104 18.47 12.47 16.82 0.08 468.88 251.99 47834 +1924 105 21.71 15.71 20.06 0.38 561.93 245.75 48030 +1924 106 15.49 9.49 13.84 0.4 395.2 260.31 48225 +1924 107 15.97 9.97 14.32 0.31 406.36 260.67 48419 +1924 108 13.06 7.06 11.41 0.07 342.67 266.91 48612 +1924 109 10.78 4.78 9.13 0.58 298.93 271.43 48804 +1924 110 11.27 5.27 9.62 0 307.9 362.43 48995 +1924 111 10.78 4.78 9.13 0 298.93 364.9 49185 +1924 112 10.62 4.62 8.97 0 296.05 366.72 49374 +1924 113 9.99 3.99 8.34 0.9 284.93 276.9 49561 +1924 114 8.74 2.74 7.09 0 263.94 372.82 49748 +1924 115 11.47 5.47 9.82 0 311.63 369.44 49933 +1924 116 11.47 5.47 9.82 0.05 311.63 278 50117 +1924 117 10.92 4.92 9.27 1.61 301.47 279.78 50300 +1924 118 9.51 3.51 7.86 0.04 276.71 282.68 50481 +1924 119 8.89 2.89 7.24 0 266.38 379.16 50661 +1924 120 7.36 1.36 5.71 0.25 242.31 287.09 50840 +1924 121 20.79 14.79 19.14 0 534.04 352.47 51016 +1924 122 23.68 17.68 22.03 0.52 625.84 257.23 51191 +1924 123 19.83 13.83 18.18 0.03 506.2 268.35 51365 +1924 124 23.79 17.79 22.14 1.44 629.58 258.39 51536 +1924 125 25.97 19.97 24.32 2.06 707.77 252.07 51706 +1924 126 24.7 18.7 23.05 0.39 661.28 256.95 51874 +1924 127 24.8 18.8 23.15 0.26 664.85 257.26 52039 +1924 128 20.35 14.35 18.7 0 521.12 360.89 52203 +1924 129 22.52 16.52 20.87 1.02 587.51 265.47 52365 +1924 130 20.34 14.34 18.69 1.75 520.83 271.89 52524 +1924 131 17 11 15.35 0.23 431.19 280.14 52681 +1924 132 17 11 15.35 0.02 431.19 280.75 52836 +1924 133 15.54 9.54 13.89 0 396.35 378.94 52989 +1924 134 12.51 6.51 10.86 0.84 331.65 290.06 53138 +1924 135 14.61 8.61 12.96 0.21 375.44 287 53286 +1924 136 17.87 11.87 16.22 0.76 453.17 280.93 53430 +1924 137 21.21 15.21 19.56 0 546.63 364.43 53572 +1924 138 20.29 14.29 18.64 0 519.38 368.22 53711 +1924 139 16.5 10.5 14.85 0.03 418.98 285.34 53848 +1924 140 17.24 11.24 15.59 0.64 437.16 284.15 53981 +1924 141 13.96 7.96 12.31 0 361.38 387.81 54111 +1924 142 18.85 12.85 17.2 0 479.06 374.99 54238 +1924 143 16.96 10.96 15.31 0.64 430.2 285.85 54362 +1924 144 13.3 7.3 11.65 0.07 347.58 293.15 54483 +1924 145 13.82 7.82 12.17 0.69 358.42 292.62 54600 +1924 146 15.37 9.37 13.72 0.19 392.46 290.05 54714 +1924 147 13.61 7.61 11.96 0 354.01 391.51 54824 +1924 148 18.51 12.51 16.86 0 469.94 378.74 54931 +1924 149 21.12 15.12 19.47 0 543.91 370.35 55034 +1924 150 18.47 12.47 16.82 0.06 468.88 284.63 55134 +1924 151 20.28 14.28 18.63 0.34 519.09 280.51 55229 +1924 152 24.78 18.78 23.13 0.62 664.13 267.43 55321 +1924 153 20.9 14.9 19.25 0.66 537.31 279.15 55409 +1924 154 14.39 8.39 12.74 0.18 370.63 293.85 55492 +1924 155 15.59 9.59 13.94 0.29 397.51 291.72 55572 +1924 156 19.73 13.73 18.08 0.79 503.37 282.78 55648 +1924 157 16 10 14.35 0.55 407.06 291.28 55719 +1924 158 21.29 15.29 19.64 0 549.05 371.95 55786 +1924 159 22.6 16.6 20.95 1.14 590.08 275.43 55849 +1924 160 21.95 15.95 20.3 0.37 569.41 277.44 55908 +1924 161 21.16 15.16 19.51 0 545.11 372.9 55962 +1924 162 21.55 15.55 19.9 0 557 371.54 56011 +1924 163 20.14 14.14 18.49 0 515.05 376.76 56056 +1924 164 18.58 12.58 16.93 1.53 471.8 286.42 56097 +1924 165 17.72 11.72 16.07 0 449.31 384.61 56133 +1924 166 19.21 13.21 17.56 0.09 488.88 285.05 56165 +1924 167 20 14 18.35 0 511.04 377.4 56192 +1924 168 22.38 16.38 20.73 0 583.02 368.85 56214 +1924 169 19.92 13.92 18.27 0.29 508.76 283.32 56231 +1924 170 23.76 17.76 22.11 0.13 628.56 272.47 56244 +1924 171 21.9 15.9 20.25 0.03 567.85 278.06 56252 +1924 172 20.23 14.23 18.58 0.19 517.65 282.56 56256 +1924 173 18.82 12.82 17.17 0.51 478.25 286.04 56255 +1924 174 22.8 16.8 21.15 0 596.57 367.16 56249 +1924 175 22.91 16.91 21.26 0.08 600.17 275.02 56238 +1924 176 24.51 18.51 22.86 0.57 654.55 269.99 56223 +1924 177 19.76 13.76 18.11 0.01 504.22 283.56 56203 +1924 178 19.64 13.64 17.99 0.11 500.84 283.88 56179 +1924 179 18.75 12.75 17.1 0 476.36 381.27 56150 +1924 180 21.33 15.33 19.68 1.01 550.27 279.29 56116 +1924 181 22.44 16.44 20.79 1.23 584.94 276.11 56078 +1924 182 25.28 19.28 23.63 1.97 682.18 267.05 56035 +1924 183 23.72 17.72 22.07 0 627.2 362.68 55987 +1924 184 19.86 13.86 18.21 0.01 507.05 282.74 55935 +1924 185 17.06 11.06 15.41 0 432.68 385.58 55879 +1924 186 17.82 11.82 16.17 0 451.88 383.1 55818 +1924 187 22.56 16.56 20.91 0 588.79 366.69 55753 +1924 188 24.45 18.45 22.8 0.01 652.44 268.99 55684 +1924 189 22.03 16.03 20.38 0.75 571.92 276.21 55611 +1924 190 19.7 13.7 18.05 0.07 502.53 282.13 55533 +1924 191 23.56 17.56 21.91 0 621.78 361.62 55451 +1924 192 21.84 15.84 20.19 0 565.97 368.07 55366 +1924 193 21.12 15.12 19.47 0 543.91 370.44 55276 +1924 194 26.14 20.14 24.49 0 714.2 349.45 55182 +1924 195 23.08 17.08 21.43 0 605.76 362.52 55085 +1924 196 22.56 16.56 20.91 0 588.79 364.17 54984 +1924 197 19.89 13.89 18.24 0.02 507.9 280 54879 +1924 198 23.07 17.07 21.42 0 605.43 361.3 54770 +1924 199 20.85 14.85 19.2 0.07 535.82 276.95 54658 +1924 200 25.54 19.54 23.89 0.41 691.73 262.52 54542 +1924 201 23.52 17.52 21.87 1.55 620.43 268.71 54423 +1924 202 22.66 16.66 21.01 0 592.02 361.15 54301 +1924 203 22.28 16.28 20.63 0 579.83 362.12 54176 +1924 204 22.67 16.67 21.02 0 592.35 360.12 54047 +1924 205 24.44 18.44 22.79 0 652.09 352.41 53915 +1924 206 23.22 17.22 21.57 0.02 610.39 267.67 53780 +1924 207 24.37 18.37 22.72 0.43 649.63 263.64 53643 +1924 208 19.14 13.14 17.49 0.06 486.96 277.59 53502 +1924 209 19.77 13.77 18.12 0.05 504.5 275.58 53359 +1924 210 15.18 9.18 13.53 0 388.14 379.98 53213 +1924 211 18.55 12.55 16.9 0 471 369.88 53064 +1924 212 23.07 17.07 21.42 0 605.43 353.42 52913 +1924 213 22.4 16.4 20.75 0.42 583.66 266.44 52760 +1924 214 22.07 16.07 20.42 0 573.18 355.75 52604 +1924 215 24.39 18.39 22.74 0.05 650.34 259.46 52445 +1924 216 24.78 18.78 23.13 0 664.13 343.3 52285 +1924 217 25.47 19.47 23.82 0 689.15 339.44 52122 +1924 218 24.25 18.25 22.6 0.11 645.44 257.92 51958 +1924 219 24.77 18.77 23.12 0 663.78 340.7 51791 +1924 220 23.55 17.55 21.9 0.95 621.44 258.6 51622 +1924 221 21.58 15.58 19.93 1.04 557.92 263.41 51451 +1924 222 22.4 16.4 20.75 0 583.66 347.21 51279 +1924 223 21.74 15.74 20.09 0.01 562.86 261.37 51105 +1924 224 18.55 12.55 16.9 0 471 357.82 50929 +1924 225 19.73 13.73 18.08 0 503.37 353.06 50751 +1924 226 19.47 13.47 17.82 0.45 496.08 264.54 50572 +1924 227 18.11 12.11 16.46 0 459.4 355.5 50392 +1924 228 15.27 9.27 13.62 0 390.18 361.77 50210 +1924 229 19.2 13.2 17.55 0 488.61 349.81 50026 +1924 230 19.99 13.99 18.34 0 510.75 346.09 49842 +1924 231 20.47 14.47 18.82 0 524.62 343.08 49656 +1924 232 19.13 13.13 17.48 0 486.69 345.92 49469 +1924 233 19.46 13.46 17.81 0 495.8 343.5 49280 +1924 234 19.06 13.06 17.41 0.33 484.77 257.46 49091 +1924 235 22.71 16.71 21.06 0 593.64 329.79 48900 +1924 236 21.13 15.13 19.48 0.19 544.21 250.41 48709 +1924 237 18.23 12.23 16.58 0 462.54 341.1 48516 +1924 238 17.57 11.57 15.92 0.7 445.49 255.92 48323 +1924 239 15.09 9.09 13.44 1.14 386.11 259.41 48128 +1924 240 13.39 7.39 11.74 0.29 349.43 260.85 47933 +1924 241 15.05 9.05 13.4 2.08 385.21 256.81 47737 +1924 242 17.95 11.95 16.3 0 455.24 333.42 47541 +1924 243 17.95 11.95 16.3 0.01 455.24 248.66 47343 +1924 244 16.81 10.81 15.16 0 426.52 332.68 47145 +1924 245 19.41 13.41 17.76 0.2 494.41 242.85 46947 +1924 246 19.52 13.52 17.87 0.01 497.48 241.15 46747 +1924 247 24.18 18.18 22.53 0 643.01 304.26 46547 +1924 248 23.13 17.13 21.48 0.45 607.41 229.67 46347 +1924 249 19.84 13.84 18.19 0.01 506.48 236.1 46146 +1924 250 23.12 17.12 21.47 0.87 607.08 226.8 45945 +1924 251 19.06 13.06 17.41 0.02 484.77 234.75 45743 +1924 252 15.04 9.04 13.39 0 384.99 320.74 45541 +1924 253 15.67 9.67 14.02 0 399.35 317.2 45339 +1924 254 17.44 11.44 15.79 0 442.19 310.87 45136 +1924 255 18.88 12.88 17.23 0.01 479.87 228.68 44933 +1924 256 17.12 11.12 15.47 0.78 434.17 230.35 44730 +1924 257 19.35 13.35 17.7 0 492.75 299.27 44527 +1924 258 15.44 9.44 13.79 0 394.06 306.44 44323 +1924 259 17.34 11.34 15.69 0 439.67 299.68 44119 +1924 260 21.22 15.22 19.57 0.27 546.93 215.2 43915 +1924 261 24.15 18.15 22.5 0 641.97 275.14 43711 +1924 262 25.8 19.8 24.15 1.02 701.39 200.19 43507 +1924 263 27.65 21.65 26 0.54 773.49 192.97 43303 +1924 264 21.08 15.08 19.43 0.31 542.7 208.35 43099 +1924 265 18.03 12.03 16.38 0 457.31 283.53 42894 +1924 266 14.9 8.9 13.25 0 381.86 287.92 42690 +1924 267 16.95 10.95 15.3 0 429.96 280.93 42486 +1924 268 15.52 9.52 13.87 0.24 395.89 211.07 42282 +1924 269 13.27 7.27 11.62 0.08 346.96 212.38 42078 +1924 270 15.74 9.74 14.09 0 400.98 275.84 41875 +1924 271 20.25 14.25 18.6 0.01 518.22 197.1 41671 +1924 272 22.81 16.81 21.16 0.28 596.9 189.74 41468 +1924 273 21.65 15.65 20 0 560.08 253.95 41265 +1924 274 16.08 10.08 14.43 0 408.95 264.65 41062 +1924 275 16.7 10.7 15.05 0 423.83 260.65 40860 +1924 276 14.45 8.45 12.8 0.01 371.94 196.74 40658 +1924 277 13.15 7.15 11.5 0.01 344.5 196.43 40456 +1924 278 14.3 8.3 12.65 0 368.68 257.07 40255 +1924 279 12.63 6.63 10.98 0.02 334.03 192.78 40054 +1924 280 10.89 4.89 9.24 0 300.92 256.96 39854 +1924 281 10.16 4.16 8.51 0 287.9 255.21 39654 +1924 282 14.58 8.58 12.93 0 374.78 245.71 39455 +1924 283 13.83 7.83 12.18 0 358.63 244.17 39256 +1924 284 10.54 4.54 8.89 0.67 294.62 184.51 39058 +1924 285 9.44 3.44 7.79 0 275.52 244.75 38861 +1924 286 13.96 7.96 12.31 0 361.38 235.58 38664 +1924 287 14.36 8.36 12.71 0 369.98 232.01 38468 +1924 288 11.03 5.03 9.38 0 303.48 234.15 38273 +1924 289 12.48 6.48 10.83 0 331.05 229.51 38079 +1924 290 11.12 5.12 9.47 0 305.13 228.51 37885 +1924 291 9.74 3.74 8.09 0.41 280.62 170.64 37693 +1924 292 11.13 5.13 9.48 0 305.31 223.09 37501 +1924 293 14.66 8.66 13.01 0 376.54 215.31 37311 +1924 294 16.24 10.24 14.59 0 412.74 209.87 37121 +1924 295 14.43 8.43 12.78 0 371.5 210.03 36933 +1924 296 17.98 11.98 16.33 0 456.02 201.47 36745 +1924 297 16.07 10.07 14.42 0 408.71 202.2 36560 +1924 298 15.06 9.06 13.41 0.19 385.44 150.96 36375 +1924 299 15.64 9.64 13.99 0 398.66 197.64 36191 +1924 300 13.78 7.78 12.13 0 357.57 197.81 36009 +1924 301 14.52 8.52 12.87 0 373.46 194.27 35829 +1924 302 13.9 7.9 12.25 0 360.11 192.59 35650 +1924 303 12.32 6.32 10.67 0 327.91 192.13 35472 +1924 304 13.26 7.26 11.61 0.39 346.76 141.37 35296 +1924 305 2.07 -3.93 0.42 0 172.9 196.31 35122 +1924 306 5.48 -0.52 3.83 0 215.31 191.56 34950 +1924 307 1.04 -4.96 -0.61 0 161.6 192.06 34779 +1924 308 4.3 -1.7 2.65 0 199.72 187.28 34610 +1924 309 6.78 0.78 5.13 0 233.69 183 34444 +1924 310 3.46 -2.54 1.81 0 189.23 183.03 34279 +1924 311 2.95 -3.05 1.3 0 183.09 181.15 34116 +1924 312 3.79 -2.21 2.14 0 193.29 177.92 33956 +1924 313 2.25 -3.75 0.6 0 174.94 176.75 33797 +1924 314 1.42 -4.58 -0.23 0 165.69 175.24 33641 +1924 315 3.22 -2.78 1.57 0 186.32 171.59 33488 +1924 316 15.24 9.24 13.59 0 389.5 158.06 33337 +1924 317 15.63 9.63 13.98 0 398.43 155.42 33188 +1924 318 13.14 7.14 11.49 0 344.3 156.26 33042 +1924 319 9.41 3.41 7.76 0 275.02 158.42 32899 +1924 320 7.5 1.5 5.85 0 244.43 158.19 32758 +1924 321 6.15 0.15 4.5 0 224.62 157.11 32620 +1924 322 2.72 -3.28 1.07 0 180.38 157.5 32486 +1924 323 3.66 -2.34 2.01 0 191.68 155.31 32354 +1924 324 7.68 1.68 6.03 0 247.19 150.47 32225 +1924 325 6.97 0.97 5.32 0 236.48 149.29 32100 +1924 326 7.29 1.29 5.64 0 241.26 147.6 31977 +1924 327 6.67 0.67 5.02 0 232.08 146.22 31858 +1924 328 7.44 1.44 5.79 0 243.52 143.69 31743 +1924 329 8.21 2.21 6.56 0 255.44 141.61 31631 +1924 330 11.4 5.4 9.75 0 310.32 137.44 31522 +1924 331 10.75 4.75 9.1 0 298.39 136.75 31417 +1924 332 7.56 1.56 5.91 0 245.35 137.73 31316 +1924 333 5.08 -0.92 3.43 0 209.91 138.33 31218 +1924 334 3.81 -2.19 2.16 0 193.54 137.98 31125 +1924 335 1.07 -4.93 -0.58 0 161.92 138.22 31035 +1924 336 3.85 -2.15 2.2 0 194.04 135.7 30949 +1924 337 2.96 -3.04 1.31 0 183.21 134.52 30867 +1924 338 5.22 -0.78 3.57 0 211.79 132.29 30790 +1924 339 4.08 -1.92 2.43 0 196.93 132.17 30716 +1924 340 -0.87 -6.87 -2.52 0 142.33 133.81 30647 +1924 341 -1.63 -7.63 -3.28 0 135.23 133.17 30582 +1924 342 -1.35 -7.35 -3 0 137.81 132.29 30521 +1924 343 4.05 -1.95 2.4 0 196.55 128.94 30465 +1924 344 7.22 1.22 5.57 0 240.2 125.87 30413 +1924 345 7.61 1.61 5.96 0 246.11 125.18 30366 +1924 346 6.21 0.21 4.56 0.12 225.47 94.17 30323 +1924 347 3.45 -2.55 1.8 0 189.1 126.56 30284 +1924 348 -0.27 -6.27 -1.92 0 148.15 127.94 30251 +1924 349 -1.29 -7.29 -2.94 0 138.37 127.96 30221 +1924 350 1.88 -4.12 0.23 0 170.77 126.27 30197 +1924 351 1.41 -4.59 -0.24 0 165.58 126.27 30177 +1924 352 0.21 -5.79 -1.44 0 152.96 126.7 30162 +1924 353 -0.63 -6.63 -2.28 0 144.63 126.98 30151 +1924 354 -3.08 -9.08 -4.73 0 122.54 127.84 30145 +1924 355 -1.07 -7.07 -2.72 0 140.43 127.11 30144 +1924 356 2.24 -3.76 0.59 0 174.83 125.71 30147 +1924 357 4.79 -1.21 3.14 0 206.07 124.43 30156 +1924 358 3.87 -2.13 2.22 0 194.29 125.03 30169 +1924 359 3.49 -2.51 1.84 0 189.59 125.35 30186 +1924 360 3.28 -2.72 1.63 0.08 187.04 94.37 30208 +1924 361 2.87 -3.13 1.22 0.45 182.14 94.78 30235 +1924 362 0.48 -5.52 -1.17 0 155.73 127.93 30267 +1924 363 7.48 1.48 5.83 0 244.13 124.66 30303 +1924 364 7.96 1.96 6.31 0 251.52 124.72 30343 +1924 365 4.89 -1.11 3.24 0 207.39 127.26 30388 +1925 1 2.18 -3.82 0.53 0 174.15 129.6 30438 +1925 2 2.33 -3.67 0.68 0 175.86 130.26 30492 +1925 3 -2.79 -8.79 -4.44 0 124.99 133.36 30551 +1925 4 -0.75 -6.75 -2.4 0 143.48 133.52 30614 +1925 5 -0.31 -6.31 -1.96 0 147.76 133.99 30681 +1925 6 3.62 -2.38 1.97 0 191.19 132.99 30752 +1925 7 4.65 -1.35 3 0 204.24 133.19 30828 +1925 8 4.58 -1.42 2.93 0 203.33 134.72 30907 +1925 9 2.21 -3.79 0.56 0 174.49 137.28 30991 +1925 10 1.88 -4.12 0.23 0 170.77 138.75 31079 +1925 11 2.46 -3.54 0.81 0 177.35 139.44 31171 +1925 12 2.11 -3.89 0.46 0 173.35 140.64 31266 +1925 13 5.95 -0.05 4.3 0 221.81 140.01 31366 +1925 14 4.75 -1.25 3.1 0 205.55 142.25 31469 +1925 15 5.52 -0.48 3.87 0 215.86 143.19 31575 +1925 16 7.76 1.76 6.11 0 248.42 142.88 31686 +1925 17 7.91 1.91 6.26 0 250.74 144.43 31800 +1925 18 4.37 -1.63 2.72 0 200.62 148.78 31917 +1925 19 0.53 -5.47 -1.12 0 156.25 152.84 32038 +1925 20 6.21 0.21 4.56 0 225.47 151.06 32161 +1925 21 5.75 -0.25 4.1 0 219.02 153.38 32289 +1925 22 8.83 2.83 7.18 0 265.4 152.73 32419 +1925 23 7.61 1.61 5.96 0 246.11 155.48 32552 +1925 24 8.93 2.93 7.28 0 267.04 156.42 32688 +1925 25 8.28 2.28 6.63 0 256.55 158.83 32827 +1925 26 3.18 -2.82 1.53 0 185.83 164.44 32969 +1925 27 1.76 -4.24 0.11 0 169.43 167.31 33114 +1925 28 0.82 -5.18 -0.83 0 159.27 170.05 33261 +1925 29 -1.38 -7.38 -3.03 0 137.53 173.54 33411 +1925 30 -1.81 -7.81 -3.46 0 133.59 176.01 33564 +1925 31 -0.34 -6.34 -1.99 0 147.46 177.71 33718 +1925 32 9.13 3.13 7.48 0 270.34 173.12 33875 +1925 33 9.76 3.76 8.11 0.05 280.97 131.32 34035 +1925 34 8.42 2.42 6.77 1.56 258.78 133.91 34196 +1925 35 8.55 2.55 6.9 0.94 260.86 135.41 34360 +1925 36 11.12 5.12 9.47 0.82 305.13 135.29 34526 +1925 37 11.55 5.55 9.9 0 313.13 182.26 34694 +1925 38 8.98 2.98 7.33 0 267.86 187.71 34863 +1925 39 8.26 2.26 6.61 0.39 256.23 143.24 35035 +1925 40 7.63 1.63 5.98 0.24 246.42 145.63 35208 +1925 41 6.24 0.24 4.59 0 225.9 198.01 35383 +1925 42 3.16 -2.84 1.51 0.02 185.59 152.23 35560 +1925 43 4.96 -1.04 3.31 0.04 208.32 153.24 35738 +1925 44 3.87 -2.13 2.22 0 194.29 207.74 35918 +1925 45 4.79 -1.21 3.14 0 206.07 209.65 36099 +1925 46 7.41 1.41 5.76 0 243.07 210 36282 +1925 47 4.59 -1.41 2.94 0 203.46 215.32 36466 +1925 48 3.56 -2.44 1.91 0 190.45 218.95 36652 +1925 49 3.51 -2.49 1.86 0 189.84 221.78 36838 +1925 50 8.6 2.6 6.95 0.16 261.67 164.82 37026 +1925 51 7.34 1.34 5.69 0.25 242.01 168.01 37215 +1925 52 9.21 3.21 7.56 0.14 271.67 168.61 37405 +1925 53 10.73 4.73 9.08 0.03 298.03 169.42 37596 +1925 54 8.46 2.46 6.81 0 259.42 231.31 37788 +1925 55 6.95 0.95 5.3 0.19 236.19 176.92 37981 +1925 56 4.36 -1.64 2.71 0.06 200.49 180.77 38175 +1925 57 7.02 1.02 5.37 0 237.22 241.38 38370 +1925 58 6.87 0.87 5.22 0.05 235.01 183.35 38565 +1925 59 13.19 7.19 11.54 0 345.32 239.02 38761 +1925 60 12.46 6.46 10.81 0.14 330.66 182.22 38958 +1925 61 9.39 3.39 7.74 0 274.68 250.05 39156 +1925 62 9.91 3.91 8.26 0 283.55 252.15 39355 +1925 63 10.56 4.56 8.91 0 294.97 254.26 39553 +1925 64 5.35 -0.65 3.7 0 213.54 263.25 39753 +1925 65 5.44 -0.56 3.79 0.08 214.77 199.55 39953 +1925 66 6.33 0.33 4.68 0 227.18 267.88 40154 +1925 67 4.69 -1.31 3.04 0 204.76 272.48 40355 +1925 68 6.25 0.25 4.6 0 226.04 273.76 40556 +1925 69 5.64 -0.36 3.99 0 217.5 277.05 40758 +1925 70 4.55 -1.45 2.9 0 202.94 281.02 40960 +1925 71 7.58 1.58 5.93 0.34 245.65 210.47 41163 +1925 72 2.55 -3.45 0.9 0.22 178.39 216.51 41366 +1925 73 5.78 -0.22 4.13 0.01 219.44 216.15 41569 +1925 74 3.54 -2.46 1.89 0 190.2 293.26 41772 +1925 75 5.26 -0.74 3.61 0 212.33 294.28 41976 +1925 76 6.33 0.33 4.68 0 227.18 295.75 42179 +1925 77 6.84 0.84 5.19 0.14 234.57 223.32 42383 +1925 78 6.44 0.44 4.79 0 228.76 300.91 42587 +1925 79 4.27 -1.73 2.62 0 199.34 306.06 42791 +1925 80 6.22 0.22 4.57 0 225.61 306.47 42996 +1925 81 9.18 3.18 7.53 0 271.17 305.2 43200 +1925 82 9.94 3.94 8.29 0 284.07 306.73 43404 +1925 83 9.79 3.79 8.14 0 281.48 309.44 43608 +1925 84 5.74 -0.26 4.09 0 218.88 317.39 43812 +1925 85 4.21 -1.79 2.56 0 198.57 321.63 44016 +1925 86 1.86 -4.14 0.21 0 170.54 326.41 44220 +1925 87 3.19 -2.81 1.54 0 185.95 327.71 44424 +1925 88 5.86 -0.14 4.21 0.4 220.55 245.36 44627 +1925 89 3.04 -2.96 1.39 0.76 184.16 249.44 44831 +1925 90 4.89 -1.11 3.24 0.34 207.39 249.75 45034 +1925 91 9.16 3.16 7.51 0 270.84 329.61 45237 +1925 92 9.69 3.69 8.04 0.04 279.77 248.28 45439 +1925 93 13.34 7.34 11.69 0 348.4 326.78 45642 +1925 94 12.74 6.74 11.09 0 336.22 330.08 45843 +1925 95 12.34 6.34 10.69 0.05 328.3 249.73 46045 +1925 96 11.23 5.23 9.58 0 307.16 337.1 46246 +1925 97 12.85 6.85 11.2 0 338.42 336.12 46446 +1925 98 13.99 7.99 12.34 0.01 362.02 251.81 46647 +1925 99 15.74 9.74 14.09 0.08 400.98 250.37 46846 +1925 100 14.53 8.53 12.88 0.07 373.68 253.87 47045 +1925 101 17.17 11.17 15.52 0 435.41 334.09 47243 +1925 102 18.89 12.89 17.24 0.25 480.14 248.45 47441 +1925 103 16.57 10.57 14.92 0.05 420.67 254.45 47638 +1925 104 16.33 10.33 14.68 0 414.89 341.66 47834 +1925 105 12.19 6.19 10.54 0 325.37 352.57 48030 +1925 106 9.22 3.22 7.57 0 271.84 359.52 48225 +1925 107 11.57 5.57 9.92 1.23 313.51 267.81 48419 +1925 108 9.67 3.67 8.02 1.64 279.43 271.67 48612 +1925 109 11.83 5.83 10.18 0 318.44 359.95 48804 +1925 110 11.33 5.33 9.68 0 309.02 362.32 48995 +1925 111 13.22 7.22 11.57 0.38 345.94 270.07 49185 +1925 112 18.06 12.06 16.41 0.65 458.09 262.28 49374 +1925 113 13.78 7.78 12.13 0.02 357.57 271.31 49561 +1925 114 13.66 7.66 12.01 0.12 355.05 272.62 49748 +1925 115 12.99 6.99 11.34 0.29 341.25 274.78 49933 +1925 116 14.75 8.75 13.1 0 378.52 363.66 50117 +1925 117 14.6 8.6 12.95 0.03 375.22 273.99 50300 +1925 118 13.81 7.81 12.16 0.02 358.21 276.33 50481 +1925 119 10.83 4.83 9.18 0.97 299.83 281.81 50661 +1925 120 11.4 5.4 9.75 0.11 310.32 281.88 50840 +1925 121 18.15 12.15 16.5 0 460.44 360.77 51016 +1925 122 13.78 7.78 12.13 0 357.57 373.2 51191 +1925 123 15.08 9.08 13.43 0 385.89 371.17 51365 +1925 124 15.83 9.83 14.18 0 403.08 370.37 51536 +1925 125 19.19 13.19 17.54 0 488.33 361.83 51706 +1925 126 20.96 14.96 19.31 0.42 539.11 267.74 51874 +1925 127 21.13 15.13 19.48 0 544.21 357.25 52039 +1925 128 21.31 15.31 19.66 0.18 549.66 268.19 52203 +1925 129 21.12 15.12 19.47 0.74 543.91 269.3 52365 +1925 130 20.02 14.02 18.37 1.05 511.61 272.69 52524 +1925 131 18.73 12.73 17.08 1.42 475.82 276.35 52681 +1925 132 16.76 10.76 15.11 0.25 425.29 281.25 52836 +1925 133 17.14 11.14 15.49 0.23 434.67 280.99 52989 +1925 134 19.54 13.54 17.89 1.69 498.04 276.08 53138 +1925 135 18.79 12.79 17.14 0.08 477.44 278.38 53286 +1925 136 15.2 9.2 13.55 0.35 388.59 286.39 53430 +1925 137 14.84 8.84 13.19 0 380.52 383.46 53572 +1925 138 15.59 9.59 13.94 0.04 397.51 286.63 53711 +1925 139 18.02 12.02 16.37 0.16 457.05 282.09 53848 +1925 140 21.11 15.11 19.46 0.08 543.61 274.89 53981 +1925 141 20.44 14.44 18.79 0.01 523.74 276.96 54111 +1925 142 16.11 10.11 14.46 0.05 409.66 287.2 54238 +1925 143 19.37 13.37 17.72 0 493.3 373.86 54362 +1925 144 18.14 12.14 16.49 0.12 460.18 283.63 54483 +1925 145 17.25 11.25 15.6 0.03 437.41 285.94 54600 +1925 146 15.87 9.87 14.22 1.76 404.01 289.08 54714 +1925 147 16.85 10.85 15.2 0 427.5 383.25 54824 +1925 148 16.62 10.62 14.97 0 421.88 384.27 54931 +1925 149 18.46 12.46 16.81 0 468.61 379.21 55034 +1925 150 19.16 13.16 17.51 0 487.51 377.34 55134 +1925 151 19.61 13.61 17.96 0 500 376.26 55229 +1925 152 19.88 13.88 18.23 0 507.62 375.47 55321 +1925 153 17.1 11.1 15.45 0.09 433.67 288.24 55409 +1925 154 19.51 13.51 17.86 0.16 497.2 282.94 55492 +1925 155 21.4 15.4 19.75 0.37 552.4 278.17 55572 +1925 156 20.48 14.48 18.83 0.75 524.91 280.87 55648 +1925 157 17.88 11.88 16.23 0 453.43 383.05 55719 +1925 158 22.2 16.2 20.55 0.72 577.29 276.41 55786 +1925 159 22.66 16.66 21.01 0.15 592.02 275.25 55849 +1925 160 25.97 19.97 24.32 0.01 707.77 264.68 55908 +1925 161 27.92 21.92 26.27 0.76 784.52 257.45 55962 +1925 162 24.71 18.71 23.06 0.02 661.64 269.07 56011 +1925 163 21.37 15.37 19.72 0 551.49 372.41 56056 +1925 164 19.43 13.43 17.78 0.12 494.97 284.38 56097 +1925 165 20.76 14.76 19.11 0 533.15 374.74 56133 +1925 166 19.28 13.28 17.63 1.16 490.81 284.88 56165 +1925 167 18.17 12.17 16.52 0 460.97 383.29 56192 +1925 168 19.67 13.67 18.02 0 501.68 378.59 56214 +1925 169 19.76 13.76 18.11 0 504.22 378.3 56231 +1925 170 21.76 15.76 20.11 0.68 563.48 278.41 56244 +1925 171 21.46 15.46 19.81 0.02 554.23 279.29 56252 +1925 172 21.08 15.08 19.43 0.7 542.7 280.32 56256 +1925 173 18.29 12.29 16.64 2.32 464.12 287.28 56255 +1925 174 20.78 14.78 19.13 0.42 533.75 281.05 56249 +1925 175 16.95 10.95 15.3 0.42 429.96 290.16 56238 +1925 176 14.94 8.94 13.29 0 382.75 392.23 56223 +1925 177 12.77 6.77 11.12 0.16 336.82 297.94 56203 +1925 178 14.2 8.2 12.55 0 366.52 393.98 56179 +1925 179 19.46 13.46 17.81 0.57 495.8 284.24 56150 +1925 180 14.82 8.82 13.17 0.29 380.08 294.17 56116 +1925 181 16.99 10.99 15.34 0.97 430.95 289.76 56078 +1925 182 16.32 10.32 14.67 0 414.65 388.07 56035 +1925 183 19.6 13.6 17.95 0.49 499.72 283.51 55987 +1925 184 17.18 11.18 15.53 0.13 435.66 288.99 55935 +1925 185 21.39 15.39 19.74 0.19 552.1 278.66 55879 +1925 186 16.23 10.23 14.58 0.98 412.51 290.72 55818 +1925 187 19.79 13.79 18.14 0 505.07 376.7 55753 +1925 188 24.12 18.12 22.47 0 640.93 360.07 55684 +1925 189 25.37 19.37 23.72 0 685.47 354.4 55611 +1925 190 24.89 18.89 23.24 0 668.07 356.19 55533 +1925 191 24.78 18.78 23.13 0 664.13 356.42 55451 +1925 192 26.86 20.86 25.21 0.52 741.97 259.83 55366 +1925 193 23.96 17.96 22.31 1.16 635.41 269.55 55276 +1925 194 29.07 23.07 27.42 0.07 832.99 250.83 55182 +1925 195 30.78 24.78 29.13 0 909.73 324.3 55085 +1925 196 30.81 24.81 29.16 0 911.12 323.74 54984 +1925 197 27.56 21.56 25.91 0.23 769.85 256.05 54879 +1925 198 26.23 20.23 24.58 0.41 717.62 260.65 54770 +1925 199 25.66 19.66 24.01 0.14 696.18 262.4 54658 +1925 200 28.16 22.16 26.51 0.03 794.43 252.9 54542 +1925 201 23.09 17.09 21.44 0.94 606.09 270.01 54423 +1925 202 23.29 17.29 21.64 0.25 612.72 269 54301 +1925 203 24.79 18.79 23.14 0 664.49 351.89 54176 +1925 204 22.52 16.52 20.87 0 587.51 360.7 54047 +1925 205 20.85 14.85 19.2 0 535.82 366.31 53915 +1925 206 18.35 12.35 16.7 0.12 465.7 280.42 53780 +1925 207 16.53 10.53 14.88 0 419.7 378.45 53643 +1925 208 18.33 12.33 16.68 0.03 465.17 279.46 53502 +1925 209 15.07 9.07 13.42 0 385.66 380.9 53359 +1925 210 15.69 9.69 14.04 0.38 399.82 284.02 53213 +1925 211 18.67 12.67 17.02 0 474.21 369.51 53064 +1925 212 22.97 16.97 21.32 0 602.13 353.81 52913 +1925 213 19.16 13.16 17.51 0 487.51 366.43 52760 +1925 214 18.83 12.83 17.18 0 478.52 366.7 52604 +1925 215 20.3 14.3 18.65 0 519.67 361.3 52445 +1925 216 21.57 15.57 19.92 0.01 557.61 266.92 52285 +1925 217 21.62 15.62 19.97 1.36 559.15 266.13 52122 +1925 218 23.21 17.21 21.56 0.1 610.06 261.06 51958 +1925 219 22.14 16.14 20.49 0.39 575.39 263.33 51791 +1925 220 22.73 16.73 21.08 0 594.29 347.99 51622 +1925 221 21.31 15.31 19.66 0.14 549.66 264.13 51451 +1925 222 23.49 17.49 21.84 0 619.42 343.05 51279 +1925 223 25.23 19.23 23.58 0 680.36 334.76 51105 +1925 224 25.18 19.18 23.53 0 678.54 333.96 50929 +1925 225 23.64 17.64 21.99 0 624.48 339.2 50751 +1925 226 28.72 22.72 27.07 0.18 817.98 236.3 50572 +1925 227 27.3 21.3 25.65 0 759.39 320.95 50392 +1925 228 23.25 17.25 21.6 0.54 611.39 252.89 50210 +1925 229 22.12 16.12 20.47 0 574.76 340.16 50026 +1925 230 19.3 13.3 17.65 0 491.36 348.23 49842 +1925 231 22.85 16.85 21.2 0 598.2 334.81 49656 +1925 232 24.53 18.53 22.88 0.02 655.26 245.23 49469 +1925 233 22.08 16.08 20.43 1.22 573.49 251.17 49280 +1925 234 18.07 12.07 16.42 0.67 458.35 259.6 49091 +1925 235 17.14 11.14 15.49 0.12 434.67 260.38 48900 +1925 236 20.03 14.03 18.38 0 511.9 337.42 48709 +1925 237 21.81 15.81 20.16 0 565.04 329.97 48516 +1925 238 21.94 15.94 20.29 0 569.1 327.88 48323 +1925 239 17.83 11.83 16.18 0.02 452.14 254.25 48128 +1925 240 22.39 16.39 20.74 0.62 583.34 242.34 47933 +1925 241 20.41 14.41 18.76 0.02 522.87 245.99 47737 +1925 242 21.09 15.09 19.44 0 543 324.11 47541 +1925 243 21.33 15.33 19.68 0 550.27 321.5 47343 +1925 244 20.42 14.42 18.77 0 523.16 322.6 47145 +1925 245 18.93 12.93 17.28 0 481.23 325.18 46947 +1925 246 19.52 13.52 17.87 0 497.48 321.54 46747 +1925 247 17.37 11.37 15.72 0 440.43 325.56 46547 +1925 248 18.61 12.61 16.96 0 472.61 320.33 46347 +1925 249 17.78 11.78 16.13 0.33 450.85 240.36 46146 +1925 250 17.13 11.13 15.48 0.13 434.42 240.14 45945 +1925 251 12.46 6.46 10.81 0.34 330.66 246.12 45743 +1925 252 11.34 5.34 9.69 1.04 309.2 245.97 45541 +1925 253 10.2 4.2 8.55 3.54 288.6 245.76 45339 +1925 254 13 7 11.35 1.22 341.45 240.42 45136 +1925 255 15.22 9.22 13.57 0.72 389.05 235.32 44933 +1925 256 13.91 7.91 12.26 0.15 360.32 235.63 44730 +1925 257 18.47 12.47 16.82 0.25 468.88 226.2 44527 +1925 258 18.9 12.9 17.25 0.02 480.41 223.62 44323 +1925 259 16.75 10.75 15.1 0.21 425.05 225.8 44119 +1925 260 16.89 10.89 15.24 0 428.48 298.37 43915 +1925 261 17.8 11.8 16.15 0.05 451.37 220.32 43711 +1925 262 18.03 12.03 16.38 0.03 457.31 218.14 43507 +1925 263 13.44 7.44 11.79 0.18 350.47 223.67 43303 +1925 264 13.32 7.32 11.67 0.05 347.99 221.88 43099 +1925 265 17.45 11.45 15.8 0 442.44 284.9 42894 +1925 266 15.27 9.27 13.62 0.28 390.18 215.39 42690 +1925 267 20.6 14.6 18.95 0.17 528.43 203.9 42486 +1925 268 20.78 14.78 19.13 0 533.75 268.89 42282 +1925 269 20.32 14.32 18.67 0.02 520.25 200.78 42078 +1925 270 20.02 14.02 18.37 0.72 511.61 199.46 41875 +1925 271 19.33 13.33 17.68 0 492.19 265.16 41671 +1925 272 16.6 10.6 14.95 0.12 421.4 201.55 41468 +1925 273 18.54 12.54 16.89 0.95 470.74 196.45 41265 +1925 274 13.37 7.37 11.72 0 349.02 269.7 41062 +1925 275 17.71 11.71 16.06 0 449.06 258.49 40860 +1925 276 15.61 9.61 13.96 0.46 397.97 195.12 40658 +1925 277 14.89 8.89 13.24 0 381.63 258.87 40456 +1925 278 12.74 6.74 11.09 0 336.22 259.69 40255 +1925 279 13.79 7.79 12.14 0 357.78 255.15 40054 +1925 280 17.33 11.33 15.68 0.07 439.42 184.41 39854 +1925 281 14.26 8.26 12.61 0 367.81 248.99 39654 +1925 282 16.41 10.41 14.76 0.05 416.81 181.77 39455 +1925 283 17.63 11.63 15.98 0 447.01 237.17 39256 +1925 284 18.36 12.36 16.71 0 465.96 232.7 39058 +1925 285 14.32 8.32 12.67 0.41 369.11 178.3 38861 +1925 286 20.93 14.93 19.28 0 538.21 221.67 38664 +1925 287 16.24 10.24 14.59 0 412.74 228.75 38468 +1925 288 15.56 9.56 13.91 0 396.81 227.23 38273 +1925 289 15.42 9.42 13.77 0.11 393.6 168.66 38079 +1925 290 8.34 2.34 6.69 0 257.5 231.86 37885 +1925 291 7.28 1.28 5.63 0 241.11 230.24 37693 +1925 292 12.66 6.66 11.01 0 334.62 221.02 37501 +1925 293 14.54 8.54 12.89 0.87 373.9 161.63 37311 +1925 294 13.56 7.56 11.91 0 352.96 214.14 37121 +1925 295 13.86 7.86 12.21 0.01 359.26 158.17 36933 +1925 296 12.85 6.85 11.2 0 338.42 209.77 36745 +1925 297 14.59 8.59 12.94 0 375 204.55 36560 +1925 298 11.7 5.7 10.05 0 315.97 205.99 36375 +1925 299 9.89 3.89 8.24 0 283.2 205.36 36191 +1925 300 9.07 3.07 7.42 0 269.35 203.58 36009 +1925 301 9.32 3.32 7.67 0.48 273.51 150.59 35829 +1925 302 9.52 3.52 7.87 0.01 276.88 148.46 35650 +1925 303 8.81 2.81 7.16 0 265.08 196.1 35472 +1925 304 7.56 1.56 5.91 0 245.35 194.83 35296 +1925 305 5.91 -0.09 4.26 1.05 221.25 145.13 35122 +1925 306 5.64 -0.36 3.99 0 217.5 191.44 34950 +1925 307 3.18 -2.82 1.53 2.59 185.83 143.03 34779 +1925 308 2 -4 0.35 0.8 172.11 141.61 34610 +1925 309 -0.6 -6.6 -2.25 0.15 144.92 179.68 34444 +1925 310 -0.33 -6.33 -1.98 0.68 147.56 179.79 34279 +1925 311 4.02 -1.98 2.37 0.01 196.17 175.88 34116 +1925 312 4.9 -1.1 3.25 0.47 207.52 173.02 33956 +1925 313 8.79 2.79 7.14 0.19 264.75 168.17 33797 +1925 314 6.99 0.99 5.34 0.17 236.78 128.57 33641 +1925 315 3.49 -2.51 1.84 0.41 189.59 128.56 33488 +1925 316 3 -3 1.35 0 183.68 169.52 33337 +1925 317 5.98 -0.02 4.33 0 222.23 165.28 33188 +1925 318 9.28 3.28 7.63 0 272.84 160.22 33042 +1925 319 9.47 3.47 7.82 1.54 276.03 118.77 32899 +1925 320 13.84 7.84 12.19 0.57 358.84 113.98 32758 +1925 321 15.85 9.85 14.2 0.85 403.54 110.56 32620 +1925 322 17.74 11.74 16.09 0.25 449.83 107.28 32486 +1925 323 11.73 5.73 10.08 0 316.53 148.87 32354 +1925 324 7.82 1.82 6.17 0.1 249.34 112.77 32225 +1925 325 4.06 -1.94 2.41 0.72 196.67 113.45 32100 +1925 326 4.06 -1.94 2.41 0 196.67 149.8 31977 +1925 327 9.89 3.89 8.24 0 283.2 143.65 31858 +1925 328 8.85 2.85 7.2 0 265.73 142.58 31743 +1925 329 9.32 3.32 7.67 0.61 273.51 105.54 31631 +1925 330 7.13 1.13 5.48 0 238.86 140.99 31522 +1925 331 7.56 1.56 5.91 2.15 245.35 104.52 31417 +1925 332 6.7 0.7 5.05 0 232.52 138.34 31316 +1925 333 9.49 3.49 7.84 0.45 276.37 101.37 31218 +1925 334 12.27 6.27 10.62 0.23 326.93 98.69 31125 +1925 335 5.9 -0.1 4.25 0 221.11 135.53 31035 +1925 336 4.13 -1.87 2.48 0 197.56 135.54 30949 +1925 337 3.9 -2.1 2.25 0.36 194.66 100.51 30867 +1925 338 7.19 1.19 5.54 0.03 239.76 98.25 30790 +1925 339 2.92 -3.08 1.27 0.07 182.73 99.6 30716 +1925 340 5.32 -0.68 3.67 1.25 213.14 98.03 30647 +1925 341 4.08 -1.92 2.43 0.06 196.93 97.89 30582 +1925 342 1.88 -4.12 0.23 0 170.77 130.9 30521 +1925 343 -2.21 -8.21 -3.86 0.22 130.02 142.86 30465 +1925 344 -4.99 -10.99 -6.64 0.33 107.4 143.81 30413 +1925 345 -2.51 -8.51 -4.16 0 127.4 175.52 30366 +1925 346 0.36 -5.64 -1.29 0 154.5 173.86 30323 +1925 347 1.86 -4.14 0.21 0 170.54 172.39 30284 +1925 348 0.08 -5.92 -1.57 0 151.65 172.87 30251 +1925 349 3.28 -2.72 1.63 0 187.04 170.6 30221 +1925 350 2.15 -3.85 0.5 0 173.81 170.57 30197 +1925 351 2.26 -3.74 0.61 0.01 175.06 138.56 30177 +1925 352 2.04 -3.96 0.39 0 172.56 169.79 30162 +1925 353 3.1 -2.9 1.45 0 184.88 125.3 30151 +1925 354 1.3 -4.7 -0.35 0.06 164.39 94.6 30145 +1925 355 -0.97 -6.97 -2.62 0.31 141.38 140.08 30144 +1925 356 0.2 -5.8 -1.45 0 152.86 171.38 30147 +1925 357 -2.25 -8.25 -3.9 0.02 129.67 140.53 30156 +1925 358 -1.85 -7.85 -3.5 0 133.23 172.36 30169 +1925 359 -0.09 -6.09 -1.74 0 149.94 171.77 30186 +1925 360 3.21 -2.79 1.56 0 186.2 170.15 30208 +1925 361 1.12 -4.88 -0.53 0 162.45 171.31 30235 +1925 362 4.23 -1.77 2.58 0 198.83 126.09 30267 +1925 363 3.24 -2.76 1.59 0 186.56 127.21 30303 +1925 364 2.29 -3.71 0.64 0 175.4 128.08 30343 +1925 365 4.34 -1.66 2.69 0 200.23 127.57 30388 +1926 1 -0.26 -6.26 -1.91 0 148.25 130.7 30438 +1926 2 -0.68 -6.68 -2.33 0.02 144.15 142.06 30492 +1926 3 -2.18 -8.18 -3.83 0 130.29 176.41 30551 +1926 4 -0.33 -6.33 -1.98 0.07 147.56 143.41 30614 +1926 5 -0.16 -6.16 -1.81 0 149.25 177.23 30681 +1926 6 -1.67 -7.67 -3.32 0.94 134.87 147.72 30752 +1926 7 -0.63 -6.63 -2.28 0.34 144.63 148.95 30828 +1926 8 0.14 -5.86 -1.51 0.21 152.26 149.69 30907 +1926 9 -0.78 -6.78 -2.43 1.22 143.19 154.59 30991 +1926 10 -0.07 -6.07 -1.72 0 150.14 190.12 31079 +1926 11 1.15 -4.85 -0.5 0.37 162.78 155.23 31171 +1926 12 -1.12 -7.12 -2.77 0.19 139.96 157.19 31266 +1926 13 1.23 -4.77 -0.42 0 163.64 192.98 31366 +1926 14 4.92 -1.08 3.27 0 207.79 191.62 31469 +1926 15 5.35 -0.65 3.7 0.04 213.54 156.1 31575 +1926 16 2.78 -3.22 1.13 0.23 181.08 157.7 31686 +1926 17 4.89 -1.11 3.24 0.43 207.39 157.23 31800 +1926 18 4.09 -1.91 2.44 0.04 197.05 158.33 31917 +1926 19 5.16 -0.84 3.51 0 210.98 195.99 32038 +1926 20 2.64 -3.36 0.99 0 179.44 198.61 32161 +1926 21 1.65 -4.35 0 0.12 168.21 161.81 32289 +1926 22 -0.38 -6.38 -2.03 0 147.07 203.38 32419 +1926 23 0.24 -5.76 -1.41 0.1 153.27 164.62 32552 +1926 24 2.5 -3.5 0.85 0 177.82 205.04 32688 +1926 25 -0.37 -6.37 -2.02 0.28 147.17 167.97 32827 +1926 26 2.45 -3.55 0.8 0.51 177.24 167.82 32969 +1926 27 -0.56 -6.56 -2.21 0.01 145.31 170.38 33114 +1926 28 2.67 -3.33 1.02 0 179.79 212.47 33261 +1926 29 4.08 -1.92 2.43 0 196.93 213.27 33411 +1926 30 5.42 -0.58 3.77 0 214.49 213.72 33564 +1926 31 8.6 2.6 6.95 0 261.67 212.25 33718 +1926 32 11.77 5.77 10.12 0 317.3 209.53 33875 +1926 33 11.97 5.97 10.32 0 321.12 172.74 34035 +1926 34 8.55 2.55 6.9 0 260.86 178.43 34196 +1926 35 8.31 2.31 6.66 0 257.03 180.77 34360 +1926 36 8.1 2.1 6.45 0 253.71 183.45 34526 +1926 37 5.83 -0.17 4.18 0 220.13 187.81 34694 +1926 38 8.8 2.8 7.15 0 264.91 187.89 34863 +1926 39 4.79 -1.21 3.14 0.29 206.07 145.47 35035 +1926 40 7.2 1.2 5.55 0.04 239.91 145.92 35208 +1926 41 10.12 4.12 8.47 0.01 287.2 145.68 35383 +1926 42 10.78 4.78 9.13 0.14 298.93 147 35560 +1926 43 4.88 -1.12 3.23 0 207.26 204.39 35738 +1926 44 4.28 -1.72 2.63 0 199.47 207.43 35918 +1926 45 4.94 -1.06 3.29 0.22 208.05 157.14 36099 +1926 46 7.16 1.16 5.51 0.09 239.31 157.68 36282 +1926 47 9.52 3.52 7.87 0.28 276.88 157.95 36466 +1926 48 9.55 3.55 7.9 0 277.38 213.33 36652 +1926 49 7.65 1.65 6 0.02 246.72 163.58 36838 +1926 50 5.1 -0.9 3.45 0 210.18 223.15 37026 +1926 51 4.81 -1.19 3.16 0.4 206.34 169.78 37215 +1926 52 6.83 0.83 5.18 0.12 234.42 170.51 37405 +1926 53 7.21 1.21 5.56 0 240.06 229.91 37596 +1926 54 10.7 4.7 9.05 0.02 297.48 171.48 37788 +1926 55 6.94 0.94 5.29 0 236.04 235.91 37981 +1926 56 6.77 0.77 5.12 0.22 233.54 179.07 38175 +1926 57 10.72 4.72 9.07 0.06 297.85 177.78 38370 +1926 58 10 4 8.35 0.2 285.11 180.64 38565 +1926 59 9.48 3.48 7.83 0.75 276.2 183.14 38761 +1926 60 7.1 1.1 5.45 0.07 238.41 187.35 38958 +1926 61 6.5 0.5 4.85 0.08 229.62 190.02 39156 +1926 62 9.71 3.71 8.06 0 280.11 252.41 39355 +1926 63 13.67 7.67 12.02 0 355.26 249.57 39553 +1926 64 13.82 7.82 12.17 0 358.42 252.15 39753 +1926 65 15.6 9.6 13.95 0 397.74 251.77 39953 +1926 66 16.93 10.93 15.28 0 429.47 251.78 40154 +1926 67 14.25 8.25 12.6 0 367.6 259.7 40355 +1926 68 15.86 9.86 14.21 0 403.78 259.48 40556 +1926 69 16.71 10.71 15.06 0.15 424.07 195.21 40758 +1926 70 13.97 7.97 12.32 0 361.6 268.3 40960 +1926 71 12.49 6.49 10.84 0 331.25 273.68 41163 +1926 72 15.84 9.84 14.19 1.16 403.31 202.75 41366 +1926 73 9.08 3.08 7.43 0.07 269.51 213.14 41569 +1926 74 5.68 -0.32 4.03 0 218.05 291.08 41772 +1926 75 4.74 -1.26 3.09 0 205.42 294.83 41976 +1926 76 5.85 -0.15 4.2 0 220.41 296.29 42179 +1926 77 6.88 0.88 5.23 0.42 235.16 223.28 42383 +1926 78 5.86 -0.14 4.21 0.28 220.55 226.19 42587 +1926 79 2.18 -3.82 0.53 0 174.15 308.08 42791 +1926 80 0.85 -5.15 -0.8 0 159.59 311.82 42996 +1926 81 -0.1 -6.1 -1.75 0 149.84 315.21 43200 +1926 82 2.21 -3.79 0.56 0 174.49 315.96 43404 +1926 83 4.81 -1.19 3.16 0 206.34 315.88 43608 +1926 84 4.82 -1.18 3.17 0 206.47 318.43 43812 +1926 85 4.94 -1.06 3.29 0.23 208.05 240.62 44016 +1926 86 -1.06 -7.06 -2.71 0.11 140.52 276.73 44220 +1926 87 -3.14 -9.14 -4.79 0.65 122.03 281.05 44424 +1926 88 0.5 -5.5 -1.15 0 155.94 363.78 44627 +1926 89 0.21 -5.79 -1.44 0 152.96 366.2 44831 +1926 90 -1.11 -7.11 -2.76 0.01 140.05 284.9 45034 +1926 91 8.83 2.83 7.18 0 265.4 360.07 45237 +1926 92 12.33 6.33 10.68 0.35 328.11 244.89 45439 +1926 93 12.46 6.46 10.81 0 330.66 328.48 45642 +1926 94 13.21 7.21 11.56 0.38 345.73 246.88 45843 +1926 95 15.98 9.98 14.33 0.17 406.59 243.98 46045 +1926 96 14.83 8.83 13.18 0.18 380.3 247.49 46246 +1926 97 11.26 5.26 9.61 0 307.72 339.1 46446 +1926 98 11.29 5.29 9.64 0 308.27 341 46647 +1926 99 15.53 9.53 13.88 0.02 396.12 250.74 46846 +1926 100 15.1 9.1 13.45 0.55 386.34 252.92 47045 +1926 101 14.91 8.91 13.26 0 382.08 339.55 47243 +1926 102 12.14 6.14 10.49 0 324.4 347.21 47441 +1926 103 12.79 6.79 11.14 0 337.22 347.77 47638 +1926 104 16.83 10.83 15.18 0.07 427.01 255.3 47834 +1926 105 16.36 10.36 14.71 0.16 415.61 257.5 48030 +1926 106 20.1 14.1 18.45 0.83 513.9 250.85 48225 +1926 107 19.16 13.16 17.51 0.39 487.51 254.2 48419 +1926 108 14.92 8.92 13.27 0 382.3 351.79 48612 +1926 109 10 4 8.35 0 285.11 363.29 48804 +1926 110 15.9 9.9 14.25 0 404.71 352.42 48995 +1926 111 15.3 9.3 13.65 0 390.86 355.41 49185 +1926 112 14.66 8.66 13.01 0 376.54 358.42 49374 +1926 113 11.74 5.74 10.09 0 316.72 365.97 49561 +1926 114 12.07 6.07 10.42 0 323.05 366.82 49748 +1926 115 14.56 8.56 12.91 0 374.34 362.89 49933 +1926 116 14.61 8.61 12.96 0 375.44 363.99 50117 +1926 117 14.52 8.52 12.87 0 373.46 365.5 50300 +1926 118 14.8 8.8 13.15 0.02 379.63 274.61 50481 +1926 119 12.74 6.74 11.09 0 336.22 371.95 50661 +1926 120 12.18 6.18 10.53 0 325.18 374.29 50840 +1926 121 17.68 11.68 16.03 0.01 448.29 271.59 51016 +1926 122 13.47 7.47 11.82 0.18 351.09 280.42 51191 +1926 123 15.97 9.97 14.32 0 406.36 368.94 51365 +1926 124 19.06 13.06 17.41 0.07 484.77 270.96 51536 +1926 125 21.57 15.57 19.92 0.01 557.61 265.41 51706 +1926 126 22.21 16.21 20.56 0 577.6 352.51 51874 +1926 127 19.75 13.75 18.1 0 503.94 361.89 52039 +1926 128 21.41 15.41 19.76 0 552.71 357.23 52203 +1926 129 17.25 11.25 15.6 0 437.41 371.25 52365 +1926 130 17.77 11.77 16.12 0.71 450.6 277.91 52524 +1926 131 17.31 11.31 15.66 0.58 438.92 279.49 52681 +1926 132 18.75 12.75 17.1 0 476.36 369.22 52836 +1926 133 21.4 15.4 19.75 0 552.4 361.09 52989 +1926 134 19.5 13.5 17.85 0 496.92 368.24 53138 +1926 135 21.75 15.75 20.1 0 563.17 361.18 53286 +1926 136 20.65 14.65 19 0 529.9 365.71 53430 +1926 137 15.58 9.58 13.93 0 397.27 381.59 53572 +1926 138 18.75 12.75 17.1 0 476.36 373.21 53711 +1926 139 18.57 12.57 16.92 0.31 471.54 280.84 53848 +1926 140 17.84 11.84 16.19 0.23 452.4 282.85 53981 +1926 141 17.84 11.84 16.19 1.02 452.4 283.17 54111 +1926 142 18.09 12.09 16.44 0.69 458.88 282.99 54238 +1926 143 20.08 14.08 18.43 1.45 513.33 278.64 54362 +1926 144 16.74 10.74 15.09 0.05 424.8 286.67 54483 +1926 145 14.43 8.43 12.78 0.23 371.5 291.53 54600 +1926 146 10.4 4.4 8.75 0 292.12 397.77 54714 +1926 147 11.13 5.13 9.48 1.87 305.31 297.63 54824 +1926 148 8.08 2.08 6.43 0.41 253.4 302.07 54931 +1926 149 7.32 1.32 5.67 0.12 241.71 303.23 55034 +1926 150 7.06 1.06 5.41 0.59 237.82 303.8 55134 +1926 151 7.67 1.67 6.02 0.67 247.03 303.38 55229 +1926 152 13.15 7.15 11.5 0.05 344.5 295.6 55321 +1926 153 16.09 10.09 14.44 1.19 409.18 290.34 55409 +1926 154 17.37 11.37 15.72 1.92 440.43 287.9 55492 +1926 155 19.97 13.97 18.32 1.54 510.18 281.93 55572 +1926 156 22.23 16.23 20.58 0.47 578.24 276.07 55648 +1926 157 17.52 11.52 15.87 0 444.22 384.11 55719 +1926 158 14.29 8.29 12.64 0 368.46 392.91 55786 +1926 159 16.46 10.46 14.81 0 418.01 387.54 55849 +1926 160 18.16 12.16 16.51 0.05 460.7 287.1 55908 +1926 161 15.99 9.99 14.34 0 406.83 389.08 55962 +1926 162 16.52 10.52 14.87 0 419.46 387.7 56011 +1926 163 19.99 13.99 18.34 0 510.75 377.27 56056 +1926 164 19.37 13.37 17.72 0.02 493.3 284.53 56097 +1926 165 21.27 15.27 19.62 0.31 548.44 279.69 56133 +1926 166 18.11 12.11 16.46 0 459.4 383.52 56165 +1926 167 20.82 14.82 19.17 0.01 534.93 280.92 56192 +1926 168 20.86 14.86 19.21 0.06 536.12 280.87 56214 +1926 169 18.11 12.11 16.46 0.52 459.4 287.67 56231 +1926 170 14.45 8.45 12.8 0.65 371.94 295.18 56244 +1926 171 18.45 12.45 16.8 0.5 468.34 286.93 56252 +1926 172 20.16 14.16 18.51 0 515.63 376.99 56256 +1926 173 23.93 17.93 22.28 0 634.38 362.62 56255 +1926 174 25.5 19.5 23.85 1.18 690.25 266.71 56249 +1926 175 20.48 14.48 18.83 1.18 524.91 281.82 56238 +1926 176 20.01 14.01 18.36 0.03 511.32 283 56223 +1926 177 18.49 12.49 16.84 0.38 469.41 286.63 56203 +1926 178 18.06 12.06 16.41 0.09 458.09 287.63 56179 +1926 179 21.28 15.28 19.63 0.13 548.75 279.52 56150 +1926 180 21.92 15.92 20.27 0 568.47 370.2 56116 +1926 181 23.38 17.38 21.73 0 615.73 364.4 56078 +1926 182 26.77 20.77 25.12 0.07 738.45 261.76 56035 +1926 183 26.77 20.77 25.12 0.14 738.45 261.63 55987 +1926 184 26.67 20.67 25.02 0.19 734.56 261.89 55935 +1926 185 21.53 15.53 19.88 0.14 556.38 278.27 55879 +1926 186 24.76 18.76 23.11 0 663.42 357.74 55818 +1926 187 24.82 18.82 23.17 0.2 665.56 267.97 55753 +1926 188 21.49 15.49 19.84 2.51 555.15 277.86 55684 +1926 189 17.47 11.47 15.82 1.24 442.95 287.62 55611 +1926 190 16.88 10.88 15.23 1.59 428.23 288.6 55533 +1926 191 14.78 8.78 13.13 2.71 379.19 292.57 55451 +1926 192 14.54 8.54 12.89 0 373.9 390.38 55366 +1926 193 19.62 13.62 17.97 0 500.28 375.6 55276 +1926 194 23.88 17.88 22.23 0 632.66 359.51 55182 +1926 195 22.8 16.8 21.15 0 596.57 363.63 55085 +1926 196 21.43 15.43 19.78 0.02 553.32 276.31 54984 +1926 197 21.05 15.05 19.4 0 541.8 369.33 54879 +1926 198 20.1 14.1 18.45 0.48 513.9 279.15 54770 +1926 199 18.17 12.17 16.52 1.76 460.97 283.51 54658 +1926 200 17.98 11.98 16.33 0.22 456.02 283.63 54542 +1926 201 16.06 10.06 14.41 0.2 408.48 287.33 54423 +1926 202 18.07 12.07 16.42 0 458.35 376.86 54301 +1926 203 18.68 12.68 17.03 0.05 474.48 280.87 54176 +1926 204 17.05 11.05 15.4 0.44 432.43 284.09 54047 +1926 205 20.89 14.89 19.24 1.59 537.02 274.63 53915 +1926 206 21.8 15.8 20.15 0.43 564.73 271.76 53780 +1926 207 20.6 14.6 18.95 0.63 528.43 274.47 53643 +1926 208 19.48 13.48 17.83 0.23 496.36 276.78 53502 +1926 209 25 19 23.35 0 672.02 347.55 53359 +1926 210 26.6 20.6 24.95 0 731.84 339.64 53213 +1926 211 27.88 21.88 26.23 0.54 782.88 249.44 53064 +1926 212 31.05 25.05 29.4 0 922.37 314.25 52913 +1926 213 29.49 23.49 27.84 0 851.31 322.58 52760 +1926 214 25.9 19.9 24.25 0 705.14 339.97 52604 +1926 215 28.31 22.31 26.66 0 800.68 327.6 52445 +1926 216 27.26 21.26 25.61 0.16 757.79 248.95 52285 +1926 217 26.76 20.76 25.11 1.11 738.06 250.13 52122 +1926 218 26.1 20.1 24.45 0.05 712.68 251.87 51958 +1926 219 29.06 23.06 27.41 0.82 832.56 240.12 51791 +1926 220 24.94 18.94 23.29 0.21 669.86 254.3 51622 +1926 221 25.82 19.82 24.17 1.98 702.14 250.69 51451 +1926 222 23.25 17.25 21.6 1.97 611.39 257.99 51279 +1926 223 22.59 16.59 20.94 0.48 589.76 259.04 51105 +1926 224 18.5 12.5 16.85 0.07 469.67 268.48 50929 +1926 225 15.62 9.62 13.97 0 398.2 364.64 50751 +1926 226 15.71 9.71 14.06 0 400.28 363.24 50572 +1926 227 15.22 9.22 13.57 0 389.05 363.14 50392 +1926 228 18.37 12.37 16.72 0.05 466.23 265.14 50210 +1926 229 12.2 6.2 10.55 1.77 325.57 275.45 50026 +1926 230 16.88 10.88 15.23 0.21 428.23 266.34 49842 +1926 231 16.16 10.16 14.51 0.05 410.84 266.61 49656 +1926 232 19.76 13.76 18.11 0.02 504.22 258 49469 +1926 233 16.01 10.01 14.36 0.1 407.3 264.77 49280 +1926 234 18.16 12.16 16.51 0 460.7 345.89 49091 +1926 235 18.26 12.26 16.61 0 463.33 344.1 48900 +1926 236 20.22 14.22 18.57 0.22 517.36 252.62 48709 +1926 237 20.07 14.07 18.42 0 513.04 335.66 48516 +1926 238 18.17 12.17 16.52 0.22 460.97 254.69 48323 +1926 239 19.88 13.88 18.23 0.39 507.62 249.81 48128 +1926 240 18.53 12.53 16.88 0.19 470.47 251.47 47933 +1926 241 18.53 12.53 16.88 0 470.47 333.57 47737 +1926 242 19.64 13.64 17.99 0 500.84 328.62 47541 +1926 243 18.86 12.86 17.21 0 479.33 329.03 47343 +1926 244 14.62 8.62 12.97 0.61 375.66 253.37 47145 +1926 245 18.69 12.69 17.04 0.05 474.75 244.39 46947 +1926 246 16.17 10.17 14.52 0 411.08 330.4 46747 +1926 247 17.72 11.72 16.07 0 449.31 324.65 46547 +1926 248 16.75 10.75 15.1 0.43 425.05 243.87 46347 +1926 249 14.96 8.96 13.31 0.2 383.2 245.42 46146 +1926 250 20.16 14.16 18.51 0 515.63 311.94 45945 +1926 251 21.36 15.36 19.71 0 551.18 306.2 45743 +1926 252 20.8 14.8 19.15 0 534.34 305.83 45541 +1926 253 20.47 14.47 18.82 0.24 524.62 228.56 45339 +1926 254 25.98 19.98 24.33 0 708.15 283.6 45136 +1926 255 26.03 20.03 24.38 0 710.03 281.29 44933 +1926 256 22.89 16.89 21.24 0.84 599.51 217.99 44730 +1926 257 23.97 17.97 22.32 0.12 635.75 213.66 44527 +1926 258 26.05 20.05 24.4 0 710.79 274.91 44323 +1926 259 23.99 17.99 22.34 0 636.44 280.27 44119 +1926 260 20.21 14.21 18.56 0.68 517.07 217.4 43915 +1926 261 19.65 13.65 18 0.03 501.12 216.76 43711 +1926 262 20.85 14.85 19.2 0 535.82 283.35 43507 +1926 263 29.22 23.22 27.57 0.02 839.5 187.86 43303 +1926 264 22.65 16.65 21 0 591.7 273.07 43099 +1926 265 19.2 13.2 17.55 0 488.61 280.62 42894 +1926 266 17.32 11.32 15.67 0.05 439.17 212.06 42690 +1926 267 19.56 13.56 17.91 1.4 498.6 205.99 42486 +1926 268 18.09 12.09 16.44 0.19 458.88 206.83 42282 +1926 269 15.24 9.24 13.59 0 389.5 279.47 42078 +1926 270 18.44 12.44 16.79 0.41 468.08 202.41 41875 +1926 271 17.3 11.3 15.65 0 438.67 269.92 41671 +1926 272 17.69 11.69 16.04 0.25 448.55 199.77 41468 +1926 273 12.47 6.47 10.82 1.15 330.86 205.43 41265 +1926 274 10.4 4.4 8.75 0.18 292.12 205.77 41062 +1926 275 6.21 0.21 4.56 0 225.47 276.78 40860 +1926 276 10.19 4.19 8.54 1.36 288.42 201.82 40658 +1926 277 6.21 0.21 4.56 0.31 225.47 203.44 40456 +1926 278 10.35 4.35 8.7 0.7 291.24 197.44 40255 +1926 279 10.63 4.63 8.98 0 296.23 260.01 40054 +1926 280 11.16 5.16 9.51 0.53 305.87 192.44 39854 +1926 281 15.32 9.32 13.67 0.02 391.32 185.34 39654 +1926 282 13.77 7.77 12.12 0.01 357.36 185.31 39455 +1926 283 14.24 8.24 12.59 0.47 367.38 182.62 39256 +1926 284 16.16 10.16 14.51 0.92 410.84 177.82 39058 +1926 285 14.72 8.72 13.07 0.59 377.86 177.79 38861 +1926 286 18.21 12.21 16.56 0.61 462.01 170.83 38664 +1926 287 19.05 13.05 17.4 0.76 484.5 167.36 38468 +1926 288 13.34 7.34 11.69 0.02 348.4 173.14 38273 +1926 289 10.73 4.73 9.08 0 298.03 231.9 38079 +1926 290 12.66 6.66 11.01 0 334.62 226.39 37885 +1926 291 18.18 12.18 16.53 0.19 461.23 160.77 37693 +1926 292 18.91 12.91 17.26 0 480.69 210.29 37501 +1926 293 17.3 11.3 15.65 0.08 438.67 158.09 37311 +1926 294 17.21 11.21 15.56 0 436.41 208.15 37121 +1926 295 15.31 9.31 13.66 0.8 391.09 156.48 36933 +1926 296 17.85 11.85 16.2 0.6 452.65 151.29 36745 +1926 297 18.44 12.44 16.79 1.05 468.08 148.48 36560 +1926 298 17.28 11.28 15.63 0.16 438.16 148.2 36375 +1926 299 13.66 7.66 12.01 0 355.05 200.61 36191 +1926 300 17.75 11.75 16.1 0.07 450.08 143.62 36009 +1926 301 17.32 11.32 15.67 0 439.17 189.82 35829 +1926 302 17.43 11.43 15.78 0 441.94 187.11 35650 +1926 303 14.47 8.47 12.82 0.46 372.37 141.94 35472 +1926 304 13.86 7.86 12.21 0.09 359.26 140.77 35296 +1926 305 9.48 3.48 7.83 0 276.2 190.19 35122 +1926 306 6.28 0.28 4.63 0 226.47 190.91 34950 +1926 307 11.84 5.84 10.19 0.93 318.63 137.14 34779 +1926 308 12.86 6.86 11.21 0 338.63 179.05 34610 +1926 309 18.44 12.44 16.79 0.48 468.08 126.48 34444 +1926 310 18.96 12.96 17.31 0.27 482.04 124.07 34279 +1926 311 18.2 12.2 16.55 0.03 461.75 123.49 34116 +1926 312 15.87 9.87 14.22 0 404.01 165.69 33956 +1926 313 15.68 9.68 14.03 0 399.59 163.92 33797 +1926 314 14.64 8.64 12.99 0.01 376.1 122.58 33641 +1926 315 16.25 10.25 14.6 0.18 412.98 119.09 33488 +1926 316 15.67 9.67 14.02 0 399.35 157.49 33337 +1926 317 13.28 7.28 11.63 0 347.17 158.38 33188 +1926 318 18.55 12.55 16.9 0 471 148.9 33042 +1926 319 18.06 12.06 16.41 0 458.09 148.07 32899 +1926 320 15.44 9.44 13.79 0 394.06 149.99 32758 +1926 321 13.37 7.37 11.72 0.65 349.02 112.85 32620 +1926 322 14.02 8.02 12.37 0.38 362.66 110.96 32486 +1926 323 14.85 8.85 13.2 0.11 380.74 109.04 32354 +1926 324 14.7 8.7 13.05 0.6 377.42 107.68 32225 +1926 325 17.02 11.02 15.37 0.19 431.69 104.2 32100 +1926 326 12.18 6.18 10.53 0 325.18 143.3 31977 +1926 327 6.63 0.63 4.98 0 231.5 146.24 31858 +1926 328 7.03 1.03 5.38 0 237.37 143.99 31743 +1926 329 7.17 1.17 5.52 0 239.46 142.4 31631 +1926 330 8.34 2.34 6.69 0 257.5 140.08 31522 +1926 331 13.77 7.77 12.12 0 357.36 133.76 31417 +1926 332 12.22 6.22 10.57 0 325.96 133.76 31316 +1926 333 13.14 7.14 11.49 0 344.3 131.78 31218 +1926 334 12.71 6.71 11.06 0 335.62 131.15 31125 +1926 335 -0.65 -6.65 -2.3 0 144.44 138.99 31035 +1926 336 1.98 -4.02 0.33 0.85 171.89 102.52 30949 +1926 337 -0.86 -6.86 -2.51 0.17 142.42 145.52 30867 +1926 338 -1.35 -7.35 -3 0 137.81 178.95 30790 +1926 339 4.27 -1.73 2.62 0 199.34 132.06 30716 +1926 340 2.11 -3.89 0.46 0.01 173.35 99.36 30647 +1926 341 4.16 -1.84 2.51 0.21 197.94 97.85 30582 +1926 342 1.03 -4.97 -0.62 0 161.49 131.29 30521 +1926 343 -1.28 -7.28 -2.93 0.01 138.46 141.93 30465 +1926 344 -4.42 -10.42 -6.07 0 111.74 174.82 30413 +1926 345 -1.02 -7.02 -2.67 0 140.9 173.26 30366 +1926 346 2.5 -3.5 0.85 0 177.82 127.64 30323 +1926 347 2.94 -3.06 1.29 1.07 182.97 95.12 30284 +1926 348 3.67 -2.33 2.02 0 191.8 126.09 30251 +1926 349 5.86 -0.14 4.21 0.06 220.55 93.34 30221 +1926 350 2.89 -3.11 1.24 0.01 182.38 94.33 30197 +1926 351 6.72 0.72 5.07 0.28 232.81 92.53 30177 +1926 352 6.9 0.9 5.25 0 235.45 123.16 30162 +1926 353 7.24 1.24 5.59 0 240.5 122.87 30151 +1926 354 9.47 3.47 7.82 0 276.03 121.24 30145 +1926 355 6.7 0.7 5.05 0 232.52 123.19 30144 +1926 356 9.95 3.95 8.3 0.02 284.24 90.67 30147 +1926 357 9.25 3.25 7.6 0 272.34 121.49 30156 +1926 358 10.41 4.41 8.76 0 292.3 120.66 30169 +1926 359 5.55 -0.45 3.9 0 216.27 124.19 30186 +1926 360 5.44 -0.56 3.79 0.36 214.77 93.47 30208 +1926 361 5.85 -0.15 4.2 1.41 220.41 93.53 30235 +1926 362 0.39 -5.61 -1.26 0.21 154.8 95.97 30267 +1926 363 -1.08 -7.08 -2.73 0.51 140.33 142.04 30303 +1926 364 -3.79 -9.79 -5.44 0 116.71 175.64 30343 +1926 365 -3.91 -9.91 -5.56 0 115.74 176.19 30388 +1927 1 -2.7 -8.7 -4.35 0 125.76 176.61 30438 +1927 2 -4.13 -10.13 -5.78 0 114 177.75 30492 +1927 3 -2.42 -8.42 -4.07 0.03 128.18 144.83 30551 +1927 4 -3.89 -9.89 -5.54 0 115.9 179.47 30614 +1927 5 -1.44 -7.44 -3.09 0 136.97 179.16 30681 +1927 6 0.44 -5.56 -1.21 0 155.32 179.11 30752 +1927 7 4.23 -1.77 2.58 0 198.83 177.32 30828 +1927 8 3.36 -2.64 1.71 1.81 188.01 144.9 30907 +1927 9 3.49 -2.51 1.84 0.28 189.59 145.21 30991 +1927 10 6.94 0.94 5.29 0.05 236.04 101.81 31079 +1927 11 4.72 -1.28 3.07 0 205.16 138.17 31171 +1927 12 4.46 -1.54 2.81 0.17 201.78 104.5 31266 +1927 13 8.03 2.03 6.38 0.62 252.61 103.89 31366 +1927 14 6.3 0.3 4.65 0.31 226.75 105.93 31469 +1927 15 8.8 2.8 7.15 0.13 264.91 105.6 31575 +1927 16 7.85 1.85 6.2 0.02 249.81 107.11 31686 +1927 17 7.71 1.71 6.06 0.19 247.65 108.44 31800 +1927 18 5.06 -0.94 3.41 0 209.65 148.34 31917 +1927 19 5.4 -0.6 3.75 0.08 214.22 112.53 32038 +1927 20 4.69 -1.31 3.04 0.01 204.76 114.07 32161 +1927 21 5.46 -0.54 3.81 0 215.04 153.58 32289 +1927 22 6.16 0.16 4.51 0 224.76 154.83 32419 +1927 23 8.12 2.12 6.47 0.09 254.02 116.3 32552 +1927 24 4.03 -1.97 2.38 0 196.29 160.1 32688 +1927 25 5.53 -0.47 3.88 0 215.99 160.97 32827 +1927 26 7.29 1.29 5.64 0 241.26 161.55 32969 +1927 27 6.62 0.62 4.97 0.04 231.36 123.06 33114 +1927 28 4.65 -1.35 3 0.46 204.24 125.79 33261 +1927 29 2.06 -3.94 0.41 0.02 172.79 128.81 33411 +1927 30 5.48 -0.52 3.83 0.43 215.31 128.81 33564 +1927 31 6.53 0.53 4.88 0 230.05 173.3 33718 +1927 32 2.37 -3.63 0.72 0.01 176.32 133.74 33875 +1927 33 7.11 1.11 5.46 0 238.56 177.53 34035 +1927 34 6.27 0.27 4.62 0 226.32 180.41 34196 +1927 35 6.98 0.98 5.33 0.02 236.63 136.46 34360 +1927 36 9.03 3.03 7.38 0.01 268.69 136.92 34526 +1927 37 5.94 -0.06 4.29 0 221.67 187.72 34694 +1927 38 1.25 -4.75 -0.4 0 163.85 193.76 34863 +1927 39 4.8 -1.2 3.15 0 206.2 193.96 35035 +1927 40 3.28 -2.72 1.63 0 187.04 197.69 35208 +1927 41 4.71 -1.29 3.06 0 205.02 199.26 35383 +1927 42 1.39 -4.61 -0.26 0.26 165.37 153.12 35560 +1927 43 0.59 -5.41 -1.06 0.11 156.87 155.53 35738 +1927 44 2.78 -3.22 1.13 0 181.08 208.54 35918 +1927 45 2.7 -3.3 1.05 0 180.14 211.23 36099 +1927 46 4.33 -1.67 2.68 0.31 200.11 159.53 36282 +1927 47 8.91 2.91 7.26 0.03 266.71 158.45 36466 +1927 48 5.23 -0.77 3.58 0 211.92 217.6 36652 +1927 49 2.65 -3.35 1 0 179.56 222.43 36838 +1927 50 4.06 -1.94 2.41 0 196.67 224.02 37026 +1927 51 3.21 -2.79 1.56 0 186.2 227.67 37215 +1927 52 1.44 -4.56 -0.21 0 165.91 231.82 37405 +1927 53 3.54 -2.46 1.89 0 190.2 233.24 37596 +1927 54 2.74 -3.26 1.09 0 180.61 236.64 37788 +1927 55 -0.23 -6.23 -1.88 0 148.55 241.74 37981 +1927 56 1.43 -4.57 -0.22 0 165.8 243.35 38175 +1927 57 1.69 -4.31 0.04 0 168.65 246.08 38370 +1927 58 -0.46 -6.46 -2.11 0 146.29 250.52 38565 +1927 59 3.77 -2.23 2.12 0 193.04 250.11 38761 +1927 60 9.95 3.95 8.3 0.06 284.24 184.83 38958 +1927 61 7.68 1.68 6.03 0 247.19 252.08 39156 +1927 62 7.5 1.5 5.85 0 244.43 255.07 39355 +1927 63 7.08 1.08 5.43 0 238.11 258.53 39553 +1927 64 12.67 6.67 11.02 0.1 334.82 190.51 39753 +1927 65 13.68 7.68 12.03 0.73 355.47 191.4 39953 +1927 66 10.63 4.63 8.98 0.14 296.23 196.93 40154 +1927 67 9.27 3.27 7.62 0.32 272.67 200.47 40355 +1927 68 13.1 7.1 11.45 0 343.48 264.47 40556 +1927 69 17.26 11.26 15.61 0 437.66 259.12 40758 +1927 70 18.63 12.63 16.98 0 473.14 258.76 40960 +1927 71 14.06 8.06 12.41 1.26 363.52 203.24 41163 +1927 72 10.74 4.74 9.09 0 298.21 279.2 41366 +1927 73 11.3 5.3 9.65 0.11 308.46 210.74 41569 +1927 74 11.62 5.62 9.97 0.03 314.45 212.39 41772 +1927 75 9.95 3.95 8.3 0 284.24 288.42 41976 +1927 76 6.93 0.93 5.28 0 235.89 295.04 42179 +1927 77 9.43 3.43 7.78 0.04 275.36 220.78 42383 +1927 78 6.49 0.49 4.84 0.88 229.48 225.64 42587 +1927 79 7.71 1.71 6.06 0 247.65 302.09 42791 +1927 80 9.35 3.35 7.7 0 274.01 302.39 42996 +1927 81 8.8 2.8 7.15 0.17 264.91 229.31 43200 +1927 82 5.72 -0.28 4.07 0.96 218.61 234.25 43404 +1927 83 6.94 0.94 5.29 0 236.04 313.37 43608 +1927 84 6.89 0.89 5.24 0 235.3 315.99 43812 +1927 85 9.34 3.34 7.69 0 273.84 315.14 44016 +1927 86 13.87 7.87 12.22 0 359.47 309.75 44220 +1927 87 12.48 6.48 10.83 0.08 331.05 236.16 44424 +1927 88 6.41 0.41 4.76 0.06 228.32 244.85 44627 +1927 89 10.23 4.23 8.58 0.62 289.12 242.49 44831 +1927 90 7.89 1.89 6.24 1.07 250.43 246.9 45034 +1927 91 11.68 5.68 10.03 1.42 315.59 244.11 45237 +1927 92 12.89 6.89 11.24 0.2 339.23 244.1 45439 +1927 93 11.72 5.72 10.07 0 316.34 329.84 45642 +1927 94 10.97 4.97 9.32 0 302.38 333.3 45843 +1927 95 9.81 3.81 8.16 0 281.82 337.38 46045 +1927 96 11.03 5.03 9.38 0 303.48 337.45 46246 +1927 97 11.28 5.28 9.63 0 308.09 339.06 46446 +1927 98 12.46 6.46 10.81 0 330.66 338.83 46647 +1927 99 13.33 7.33 11.68 0 348.2 339.11 46846 +1927 100 11.76 5.76 10.11 0.02 317.1 258.08 47045 +1927 101 12.98 6.98 11.33 1.29 341.05 257.75 47243 +1927 102 12.54 6.54 10.89 0.66 332.24 259.83 47441 +1927 103 13.46 7.46 11.81 0.32 350.88 259.8 47638 +1927 104 14.59 8.59 12.94 0 375 345.77 47834 +1927 105 16.02 10.02 14.37 0 407.53 344.18 48030 +1927 106 14.05 8.05 12.4 0.63 363.3 262.77 48225 +1927 107 13.63 7.63 11.98 0.16 354.42 264.7 48419 +1927 108 10.32 4.32 8.67 0 290.71 361.11 48612 +1927 109 9.07 3.07 7.42 0 269.35 364.85 48804 +1927 110 12.01 6.01 10.36 0 321.89 361.01 48995 +1927 111 14.3 8.3 12.65 0 368.68 357.74 49185 +1927 112 14.34 8.34 12.69 0 369.54 359.16 49374 +1927 113 14.65 8.65 13 0 376.32 359.78 49561 +1927 114 14.35 8.35 12.7 0.09 369.76 271.46 49748 +1927 115 13.01 7.01 11.36 0.32 341.66 274.75 49933 +1927 116 13.6 7.6 11.95 0 353.8 366.28 50117 +1927 117 11.26 5.26 9.61 0.05 307.72 279.29 50300 +1927 118 11.76 5.76 10.11 0 317.1 372.75 50481 +1927 119 12.2 6.2 10.55 0 325.57 373.07 50661 +1927 120 18.57 12.57 16.92 0 471.54 358.43 50840 +1927 121 19.6 13.6 17.95 1.18 499.72 267.28 51016 +1927 122 19.41 13.41 17.76 0.32 494.41 268.6 51191 +1927 123 13.48 7.48 11.83 0.03 351.3 281.18 51365 +1927 124 10.63 4.63 8.98 0 296.23 381.81 51536 +1927 125 18.36 12.36 16.71 0 465.96 364.36 51706 +1927 126 16.11 10.11 14.46 0 409.66 371.62 51874 +1927 127 17.48 11.48 15.83 0 443.2 368.77 52039 +1927 128 17.91 11.91 16.26 0 454.2 368.52 52203 +1927 129 15.56 9.56 13.91 0 396.81 375.77 52365 +1927 130 18.96 12.96 17.31 0 482.04 366.98 52524 +1927 131 17.56 11.56 15.91 0 445.23 371.94 52681 +1927 132 18.54 12.54 16.89 0.7 470.74 277.39 52836 +1927 133 18.13 12.13 16.48 0.24 459.92 278.84 52989 +1927 134 14.54 8.54 12.89 1.46 373.9 286.6 53138 +1927 135 17.11 11.11 15.46 0.14 433.92 282.1 53286 +1927 136 17.86 11.86 16.21 0 452.91 374.61 53430 +1927 137 17.8 11.8 16.15 0 451.37 375.48 53572 +1927 138 17.02 11.02 15.37 0 431.69 378.32 53711 +1927 139 15.18 9.18 13.53 0.06 388.14 287.93 53848 +1927 140 18.54 12.54 16.89 1.11 470.74 281.27 53981 +1927 141 18.24 12.24 16.59 0 462.8 376.37 54111 +1927 142 16.09 10.09 14.44 0.01 409.18 287.24 54238 +1927 143 15.46 9.46 13.81 0.1 394.52 288.88 54362 +1927 144 16.23 10.23 14.58 0 412.51 383.62 54483 +1927 145 15.07 9.07 13.42 0 385.66 387.12 54600 +1927 146 15.73 9.73 14.08 0 400.75 385.8 54714 +1927 147 16.81 10.81 15.16 0 426.52 383.36 54824 +1927 148 12.09 6.09 10.44 0 323.43 395.26 54931 +1927 149 12.75 6.75 11.1 0 336.42 394.16 55034 +1927 150 18.34 12.34 16.69 0.06 465.43 284.93 55134 +1927 151 23.39 17.39 21.74 0.6 616.06 271.78 55229 +1927 152 22.84 16.84 21.19 0.13 597.88 273.51 55321 +1927 153 22.42 16.42 20.77 0.89 584.3 274.92 55409 +1927 154 17.94 11.94 16.29 2.21 454.98 286.64 55492 +1927 155 19.03 13.03 17.38 0.19 483.95 284.25 55572 +1927 156 17.93 11.93 16.28 0 454.72 382.73 55648 +1927 157 17.96 11.96 16.31 0 455.5 382.81 55719 +1927 158 23.26 17.26 21.61 0 611.72 364.37 55786 +1927 159 23.29 17.29 21.64 0.32 612.72 273.36 55849 +1927 160 22.52 16.52 20.87 0 587.51 367.73 55908 +1927 161 25.44 19.44 23.79 0 688.04 355.43 55962 +1927 162 25.69 19.69 24.04 0.76 697.29 265.75 56011 +1927 163 25.45 19.45 23.8 0 688.41 355.65 56056 +1927 164 23.48 17.48 21.83 0 619.08 364.26 56097 +1927 165 20.37 14.37 18.72 0 521.7 376.11 56133 +1927 166 24.3 18.3 22.65 0.42 647.19 270.73 56165 +1927 167 23.17 17.17 21.52 0 608.73 365.64 56192 +1927 168 26 20 24.35 0 708.9 353.32 56214 +1927 169 21.93 15.93 20.28 0 568.78 370.58 56231 +1927 170 26.08 20.08 24.43 0 711.92 352.95 56244 +1927 171 27.25 21.25 25.6 0.19 757.39 260.45 56252 +1927 172 25.65 19.65 24 0.07 695.8 266.26 56256 +1927 173 23.62 17.62 21.97 0 623.81 363.91 56255 +1927 174 23.76 17.76 22.11 0 628.56 363.25 56249 +1927 175 19.73 13.73 18.08 0 503.37 378.32 56238 +1927 176 21.96 15.96 20.31 0 569.72 370.35 56223 +1927 177 19.07 13.07 17.42 0 485.04 380.34 56203 +1927 178 19 13 17.35 0.21 483.13 285.44 56179 +1927 179 16.01 10.01 14.36 0.23 407.3 291.94 56150 +1927 180 13.74 7.74 12.09 0.36 356.73 296.13 56116 +1927 181 18.6 12.6 16.95 0.55 472.34 286.16 56078 +1927 182 21.93 15.93 20.28 0.06 568.78 277.47 56035 +1927 183 20.08 14.08 18.43 0 513.33 376.4 55987 +1927 184 25.58 19.58 23.93 0 693.21 354.37 55935 +1927 185 24.36 18.36 22.71 0.13 649.28 269.8 55879 +1927 186 27.27 21.27 25.62 0.54 758.19 259.42 55818 +1927 187 25.48 19.48 23.83 0.66 689.52 265.75 55753 +1927 188 24.61 18.61 22.96 0.69 658.09 268.47 55684 +1927 189 24.44 18.44 22.79 0 652.09 358.53 55611 +1927 190 26.19 20.19 24.54 0 716.1 350.22 55533 +1927 191 29.3 23.3 27.65 0 842.98 333.88 55451 +1927 192 25.16 19.16 23.51 0 677.81 354.44 55366 +1927 193 23.79 17.79 22.14 0 629.58 360.11 55276 +1927 194 25.21 19.21 23.56 0 679.63 353.74 55182 +1927 195 29.02 23.02 27.37 0.64 830.83 250.85 55085 +1927 196 26.82 20.82 25.17 0.51 740.41 259.15 54984 +1927 197 23.16 17.16 21.51 0 608.4 361.35 54879 +1927 198 20.47 14.47 18.82 0.15 524.62 278.21 54770 +1927 199 20.3 14.3 18.65 0 519.67 371.17 54658 +1927 200 23.11 17.11 21.46 0 606.75 360.4 54542 +1927 201 22.33 16.33 20.68 0.73 581.42 272.24 54423 +1927 202 26.34 20.34 24.69 0.02 721.82 258.98 54301 +1927 203 25.49 19.49 23.84 0 689.89 348.78 54176 +1927 204 24.81 18.81 23.16 0 665.2 351.31 54047 +1927 205 23.43 17.43 21.78 0 617.4 356.61 53915 +1927 206 24.01 18.01 22.36 0.37 637.13 265.26 53780 +1927 207 21.02 15.02 19.37 0.01 540.9 273.38 53643 +1927 208 19.34 13.34 17.69 0.97 492.47 277.11 53502 +1927 209 19.46 13.46 17.81 0.02 495.8 276.33 53359 +1927 210 23.2 17.2 21.55 0.71 609.73 265.84 53213 +1927 211 19.73 13.73 18.08 0 503.37 366.17 53064 +1927 212 22.73 16.73 21.08 0 594.29 354.74 52913 +1927 213 21.92 15.92 20.27 1.14 568.47 267.78 52760 +1927 214 20.51 14.51 18.86 0 525.79 361.27 52604 +1927 215 17.79 11.79 16.14 0.14 451.11 276.83 52445 +1927 216 18.59 12.59 16.94 0.45 472.07 274.29 52285 +1927 217 20.76 14.76 19.11 0 533.15 357.85 52122 +1927 218 20.5 14.5 18.85 0 525.5 357.91 51958 +1927 219 23.9 17.9 22.25 0 633.35 344.31 51791 +1927 220 24.45 18.45 22.8 0 652.44 341.14 51622 +1927 221 23.15 17.15 21.5 0.15 608.07 259.05 51451 +1927 222 22.35 16.35 20.7 0.27 582.06 260.55 51279 +1927 223 20.55 14.55 18.9 0 526.96 352.59 51105 +1927 224 22.37 16.37 20.72 0 582.7 345.16 50929 +1927 225 24.43 18.43 22.78 2.71 651.74 252.01 50751 +1927 226 24.29 18.29 22.64 0.58 646.84 251.62 50572 +1927 227 26.11 20.11 24.46 0.15 713.06 244.85 50392 +1927 228 23.66 17.66 22.01 0.54 625.16 251.69 50210 +1927 229 22.13 16.13 20.48 0 575.07 340.12 50026 +1927 230 22.41 16.41 20.76 0.04 583.98 253.4 49842 +1927 231 21.8 15.8 20.15 0.29 564.73 253.95 49656 +1927 232 25.26 19.26 23.61 0.61 681.45 242.96 49469 +1927 233 25.07 19.07 23.42 0 674.55 323.39 49280 +1927 234 24.84 18.84 23.19 0.1 666.28 242.24 49091 +1927 235 29.36 23.36 27.71 1.44 845.61 225.46 48900 +1927 236 26.96 20.96 25.31 0.08 745.9 233.28 48709 +1927 237 25.46 19.46 23.81 0.19 688.78 237.05 48516 +1927 238 22.24 16.24 20.59 0.4 578.56 245.13 48323 +1927 239 21.44 15.44 19.79 0.27 553.62 246.07 48128 +1927 240 19.78 13.78 18.13 0 504.78 331.64 47933 +1927 241 23.04 17.04 21.39 0.02 604.44 239.35 47737 +1927 242 23.22 17.22 21.57 0.12 610.39 237.59 47541 +1927 243 27.84 21.84 26.19 0.68 781.24 221.93 47343 +1927 244 25.53 19.53 23.88 0.28 691.36 228.24 47145 +1927 245 26.58 20.58 24.93 0 731.07 298.17 46947 +1927 246 25.3 19.3 23.65 0.02 682.91 226.24 46747 +1927 247 24.59 18.59 22.94 0 657.38 302.7 46547 +1927 248 23.78 17.78 22.13 0.01 629.24 227.91 46347 +1927 249 23.48 17.48 21.83 0.63 619.08 227.25 46146 +1927 250 26.02 20.02 24.37 0 709.66 291.4 45945 +1927 251 21.88 15.88 20.23 0 567.22 304.54 45743 +1927 252 19.2 13.2 17.55 0 488.61 310.48 45541 +1927 253 18.88 12.88 17.23 0 479.87 309.26 45339 +1927 254 19.81 13.81 18.16 0.12 505.63 228.43 45136 +1927 255 21.55 15.55 19.9 1.24 557 222.88 44933 +1927 256 18.29 12.29 16.64 0.49 464.12 228.16 44730 +1927 257 20.24 14.24 18.59 0.62 517.94 222.58 44527 +1927 258 19.65 13.65 18 0.76 501.12 222.1 44323 +1927 259 19.06 13.06 17.41 0.49 484.77 221.51 44119 +1927 260 15.51 9.51 13.86 2.7 395.66 226.08 43915 +1927 261 14.7 8.7 13.05 1.5 377.42 225.5 43711 +1927 262 15.14 9.14 13.49 0.69 387.24 223.03 43507 +1927 263 13.36 7.36 11.71 0.23 348.81 223.78 43303 +1927 264 16.68 10.68 15.03 0 423.34 289.02 43099 +1927 265 15.95 9.95 14.3 0.4 405.89 216.18 42894 +1927 266 11.17 5.17 9.52 0.42 306.05 220.93 42690 +1927 267 13.82 7.82 12.17 0.03 358.42 215.48 42486 +1927 268 15.52 9.52 13.87 0.03 395.89 211.07 42282 +1927 269 14.92 8.92 13.27 0.19 382.3 210.08 42078 +1927 270 17.33 11.33 15.68 0.26 439.42 204.33 41875 +1927 271 24.18 18.18 22.53 0 643.01 251.27 41671 +1927 272 25.44 19.44 23.79 0 688.04 244.48 41468 +1927 273 27.75 21.75 26.1 0.03 777.56 175.24 41265 +1927 274 21.83 15.83 20.18 0 565.66 250.9 41062 +1927 275 21.88 15.88 20.23 0.03 567.22 186.09 40860 +1927 276 22.66 16.66 21.01 0 592.02 243.34 40658 +1927 277 20.83 14.83 19.18 0.85 535.23 184.37 40456 +1927 278 13.04 7.04 11.39 0.48 342.26 194.41 40255 +1927 279 13.62 7.62 11.97 0 354.21 255.43 40054 +1927 280 12.5 6.5 10.85 0 331.45 254.58 39854 +1927 281 10.75 4.75 9.1 0 298.39 254.41 39654 +1927 282 10.47 4.47 8.82 0 293.37 252.02 39455 +1927 283 9.12 3.12 7.47 0.01 270.17 188.17 39256 +1927 284 9.79 3.79 8.14 0.01 281.48 185.25 39058 +1927 285 10.29 4.29 8.64 0 290.18 243.68 38861 +1927 286 11.89 5.89 10.24 0 319.59 238.72 38664 +1927 287 13.89 7.89 12.24 0 359.9 232.77 38468 +1927 288 14.08 8.08 12.43 0 363.94 229.7 38273 +1927 289 14.34 8.34 12.69 0 369.54 226.68 38079 +1927 290 14.6 8.6 12.95 0.62 375.22 167.57 37885 +1927 291 10.4 4.4 8.75 0 292.12 226.72 37693 +1927 292 6.41 0.41 4.76 0 228.32 228.36 37501 +1927 293 10.42 4.42 8.77 0.11 292.48 165.93 37311 +1927 294 14.93 8.93 13.28 0.02 382.52 159.03 37121 +1927 295 6.01 0.01 4.36 0 222.65 220.12 36933 +1927 296 8.36 2.36 6.71 0 257.82 215.2 36745 +1927 297 12.34 6.34 10.69 0.72 328.3 155.82 36560 +1927 298 11.36 5.36 9.71 0.13 309.57 154.81 36375 +1927 299 11.9 5.9 10.25 0.19 319.78 152.22 36191 +1927 300 10.49 4.49 8.84 0.11 293.72 151.51 36009 +1927 301 16.85 10.85 15.2 0 427.5 190.62 35829 +1927 302 16.99 10.99 15.34 0 430.95 187.86 35650 +1927 303 18.27 12.27 16.62 0 463.59 183.16 35472 +1927 304 13.43 7.43 11.78 0 350.26 188.27 35296 +1927 305 8.19 2.19 6.54 0.83 255.13 143.61 35122 +1927 306 8.28 2.28 6.63 0.01 256.55 141.84 34950 +1927 307 8.73 2.73 7.08 0 263.77 186.18 34779 +1927 308 6.29 0.29 4.64 0 226.61 185.74 34610 +1927 309 9.93 3.93 8.28 0 283.89 180.06 34444 +1927 310 8.5 2.5 6.85 0.05 260.06 134.27 34279 +1927 311 8.37 2.37 6.72 1 257.98 132.72 34116 +1927 312 9.13 3.13 7.48 0.31 270.34 130.21 33956 +1927 313 7.33 1.33 5.68 0.08 241.86 129.83 33797 +1927 314 8.8 2.8 7.15 0.04 264.91 127.4 33641 +1927 315 8.45 2.45 6.8 0.33 259.26 125.74 33488 +1927 316 8.06 2.06 6.41 0.13 253.08 124.36 33337 +1927 317 6.59 0.59 4.94 0.06 230.92 123.61 33188 +1927 318 4.98 -1.02 3.33 0 208.58 163.64 33042 +1927 319 7.91 1.91 6.26 0 250.74 159.72 32899 +1927 320 9.07 3.07 7.42 0 269.35 156.87 32758 +1927 321 11.47 5.47 9.82 0 311.63 152.51 32620 +1927 322 9.7 3.7 8.05 0 279.94 152.41 32486 +1927 323 7.23 1.23 5.58 0 240.35 152.86 32354 +1927 324 11.74 5.74 10.09 0.12 316.72 110.14 32225 +1927 325 8.16 2.16 6.51 0 254.65 148.37 32100 +1927 326 11.05 5.05 9.4 0.01 303.84 108.31 31977 +1927 327 8.06 2.06 6.41 0 253.08 145.17 31858 +1927 328 9.13 3.13 7.48 0 270.34 142.35 31743 +1927 329 12.27 6.27 10.62 0.24 326.93 103.5 31631 +1927 330 9 3 7.35 0.45 268.19 104.66 31522 +1927 331 4.86 -1.14 3.21 0.1 206.99 105.9 31417 +1927 332 4.39 -1.61 2.74 0 200.88 139.84 31316 +1927 333 5.34 -0.66 3.69 0.67 213.41 103.62 31218 +1927 334 6.62 0.62 4.97 0.09 231.36 102.17 31125 +1927 335 -3.5 -9.5 -5.15 0.16 119.06 148.08 31035 +1927 336 -5.21 -11.21 -6.86 0 105.76 182.68 30949 +1927 337 -2.37 -8.37 -4.02 0 128.62 180.16 30867 +1927 338 -4.47 -10.47 -6.12 0 111.35 180.02 30790 +1927 339 -2.45 -8.45 -4.1 0 127.92 178.63 30716 +1927 340 -2.43 -8.43 -4.08 0 128.09 177.98 30647 +1927 341 -2.53 -8.53 -4.18 0 127.22 177.17 30582 +1927 342 2.31 -3.69 0.66 0 175.63 174.13 30521 +1927 343 0.31 -5.69 -1.34 0 153.98 174.27 30465 +1927 344 -1.89 -7.89 -3.54 0 132.87 174.08 30413 +1927 345 -2.61 -8.61 -4.26 0.7 126.53 143.6 30366 +1927 346 -0.75 -6.75 -2.4 0.12 143.48 143.1 30323 +1927 347 3.01 -2.99 1.36 0 183.8 172.73 30284 +1927 348 2.66 -3.34 1.01 0 179.67 172.25 30251 +1927 349 6.28 0.28 4.63 0.2 226.47 138 30221 +1927 350 4.15 -1.85 2.5 0 197.81 169.45 30197 +1927 351 6.82 0.82 5.17 0 234.27 123.3 30177 +1927 352 4.51 -1.49 2.86 0 202.42 124.61 30162 +1927 353 4.02 -1.98 2.37 0 196.17 124.81 30151 +1927 354 -0.6 -6.6 -2.25 0 144.92 126.93 30145 +1927 355 -0.79 -6.79 -2.44 0 143.09 127.01 30144 +1927 356 -1.79 -7.79 -3.44 0 133.78 127.41 30147 +1927 357 0.25 -5.75 -1.4 0.04 153.37 95 30156 +1927 358 1.85 -4.15 0.2 1.17 170.43 94.53 30169 +1927 359 -2.79 -8.79 -4.44 0 124.99 128.04 30186 +1927 360 -1.65 -7.65 -3.3 0 135.05 128 30208 +1927 361 -4.52 -10.52 -6.17 0.02 110.96 140.7 30235 +1927 362 -4.03 -10.03 -5.68 0 114.79 173.28 30267 +1927 363 0.57 -5.43 -1.08 0 156.66 128.48 30303 +1927 364 -1.32 -7.32 -2.97 0 138.09 129.65 30343 +1927 365 -4.04 -10.04 -5.69 1.3 114.71 145.93 30388 +1928 1 -2.43 -8.43 -4.08 0 128.09 179.01 30438 +1928 2 3.41 -2.59 1.76 0 188.62 176.64 30492 +1928 3 5.07 -0.93 3.42 0 209.78 175.88 30551 +1928 4 5.62 -0.38 3.97 0 217.23 175.62 30614 +1928 5 0.14 -5.86 -1.51 0 152.26 179.02 30681 +1928 6 0.74 -5.26 -0.91 0 158.43 179.45 30752 +1928 7 -1.28 -7.28 -2.93 0 138.46 181 30828 +1928 8 0.65 -5.35 -1 0.03 157.49 147.28 30907 +1928 9 2.44 -3.56 0.79 0 177.12 181.43 30991 +1928 10 3.16 -2.84 1.51 0 185.59 181.81 31079 +1928 11 4.49 -1.51 2.84 0 202.16 181.33 31171 +1928 12 9.91 3.91 8.26 0 283.55 135.41 31266 +1928 13 8.27 2.27 6.62 0 256.39 138.34 31366 +1928 14 0.8 -5.2 -0.85 0 159.06 144.4 31469 +1928 15 -1.38 -7.38 -3.03 0 137.53 146.83 31575 +1928 16 -1.86 -7.86 -3.51 0 133.14 148.33 31686 +1928 17 1.6 -4.4 -0.05 0.34 167.66 111.34 31800 +1928 18 -1.95 -7.95 -3.6 0.04 132.33 155.47 31917 +1928 19 -0.02 -6.02 -1.67 0 150.64 194.42 32038 +1928 20 -0.78 -6.78 -2.43 0 143.19 196.21 32161 +1928 21 -2.2 -8.2 -3.85 0 130.11 198.69 32289 +1928 22 -1.23 -7.23 -2.88 0 138.93 199.88 32419 +1928 23 0.26 -5.74 -1.39 0 153.47 200.78 32552 +1928 24 0.87 -5.13 -0.78 0 159.8 161.92 32688 +1928 25 1.74 -4.26 0.09 0 169.21 163.35 32827 +1928 26 6.14 0.14 4.49 0 224.48 162.44 32969 +1928 27 5.88 -0.12 4.23 0 220.83 164.64 33114 +1928 28 7.05 1.05 5.4 0 237.67 165.94 33261 +1928 29 7.18 1.18 5.53 0 239.61 168.19 33411 +1928 30 6.66 0.66 5.01 0 231.94 170.83 33564 +1928 31 6.86 0.86 5.21 0 234.86 173.03 33718 +1928 32 8.95 2.95 7.3 0 267.37 173.29 33875 +1928 33 13.14 7.14 11.49 0 344.3 171.36 34035 +1928 34 11.84 5.84 10.19 0 318.63 175.03 34196 +1928 35 5.85 -0.15 4.2 0 220.41 182.88 34360 +1928 36 3.47 -2.53 1.82 0 189.35 187.14 34526 +1928 37 2.18 -3.82 0.53 0.25 174.15 142.82 34694 +1928 38 2.59 -3.41 0.94 0 178.86 192.91 34863 +1928 39 -0.49 -6.49 -2.14 0 145.99 197.38 35035 +1928 40 -2.02 -8.02 -3.67 0 131.71 200.82 35208 +1928 41 -2.48 -8.48 -4.13 0 127.66 203.7 35383 +1928 42 1.43 -4.57 -0.22 0.13 165.8 153.1 35560 +1928 43 -0.23 -6.23 -1.88 0 148.55 207.86 35738 +1928 44 -0.55 -6.55 -2.2 0.03 145.41 194.81 35918 +1928 45 4.26 -1.74 2.61 0 199.21 210.07 36099 +1928 46 2.09 -3.91 0.44 0.09 173.13 160.77 36282 +1928 47 -0.05 -6.05 -1.7 0 150.34 218.58 36466 +1928 48 -1.28 -7.28 -2.93 0 138.46 222.13 36652 +1928 49 -0.42 -6.42 -2.07 0 146.68 224.45 36838 +1928 50 2.97 -3.03 1.32 0 183.33 224.87 37026 +1928 51 7.22 1.22 5.57 1.92 240.2 168.1 37215 +1928 52 8.21 2.21 6.56 0.35 255.44 169.44 37405 +1928 53 8.93 2.93 7.28 0 267.04 228.06 37596 +1928 54 10.54 4.54 8.89 0.53 294.62 171.63 37788 +1928 55 9.41 3.41 7.76 0 275.02 233.19 37981 +1928 56 9.16 3.16 7.51 0 270.84 236.14 38175 +1928 57 10.93 4.93 9.28 0 301.65 236.77 38370 +1928 58 9.71 3.71 8.06 0 280.11 241.22 38565 +1928 59 8.66 2.66 7.01 0 262.64 245.17 38761 +1928 60 8.29 2.29 6.64 0 256.71 248.47 38958 +1928 61 6.66 0.66 5.01 0 231.94 253.19 39156 +1928 62 5.38 -0.62 3.73 0 213.95 257.29 39355 +1928 63 0.79 -5.21 -0.86 0 158.96 264.21 39553 +1928 64 6.25 0.25 4.6 0.56 226.04 196.75 39753 +1928 65 10.2 4.2 8.55 0.18 288.6 195.35 39953 +1928 66 9.53 3.53 7.88 0 277.05 264.07 40154 +1928 67 8.76 2.76 7.11 0.19 264.26 200.96 40355 +1928 68 8.28 2.28 6.63 0.3 256.55 203.56 40556 +1928 69 8.42 2.42 6.77 0 258.78 273.85 40758 +1928 70 6.97 0.97 5.32 0.74 236.48 208.83 40960 +1928 71 4.97 -1.03 3.32 0.69 208.45 212.65 41163 +1928 72 2.63 -3.37 0.98 0.21 179.33 216.46 41366 +1928 73 2.1 -3.9 0.45 0.38 173.24 218.84 41569 +1928 74 3.84 -2.16 2.19 0 193.91 292.98 41772 +1928 75 2.62 -3.38 0.97 0 179.21 296.88 41976 +1928 76 5.12 -0.88 3.47 0 210.45 297.09 42179 +1928 77 7.54 1.54 5.89 0 245.04 296.9 42383 +1928 78 10.9 4.9 9.25 0 301.11 294.83 42587 +1928 79 6.84 0.84 5.19 0 234.57 303.18 42791 +1928 80 4.66 -1.34 3.01 0 204.37 308.22 42996 +1928 81 8.12 2.12 6.47 0 254.02 306.67 43200 +1928 82 8.32 2.32 6.67 0 257.19 309.06 43404 +1928 83 10.33 4.33 8.68 0 290.89 308.61 43608 +1928 84 4.65 -1.35 3 0.28 204.24 238.97 43812 +1928 85 0.46 -5.54 -1.19 0.99 155.52 243.88 44016 +1928 86 4.09 -1.91 2.44 0.58 197.05 243.15 44220 +1928 87 5.05 -0.95 3.4 0 209.51 325.71 44424 +1928 88 1.36 -4.64 -0.29 0.3 165.04 248.89 44627 +1928 89 4.61 -1.39 2.96 0.02 203.72 248.18 44831 +1928 90 8.55 2.55 6.9 0 260.86 328.26 45034 +1928 91 16.31 10.31 14.66 0.09 414.42 237.01 45237 +1928 92 15.11 9.11 13.46 0 386.56 320.92 45439 +1928 93 16.74 10.74 15.09 1.21 424.8 239.49 45642 +1928 94 8.87 2.87 7.22 0 266.06 336.7 45843 +1928 95 7.58 1.58 5.93 0 245.65 340.73 46045 +1928 96 8.65 2.65 7 0 262.48 341.31 46246 +1928 97 7.73 1.73 6.08 0 247.95 344.73 46446 +1928 98 10.38 4.38 8.73 0 291.77 342.59 46647 +1928 99 9.79 3.79 8.14 0 281.48 345.59 46846 +1928 100 11.48 5.48 9.83 0 311.82 344.62 47045 +1928 101 12.42 6.42 10.77 0 329.87 344.77 47243 +1928 102 14.89 8.89 13.24 0 381.63 341.47 47441 +1928 103 17.64 11.64 15.99 0 447.27 336.5 47638 +1928 104 19.46 13.46 17.81 0 495.8 333.12 47834 +1928 105 19.66 13.66 18.01 0 501.4 334.25 48030 +1928 106 20.09 14.09 18.44 0.03 513.62 250.88 48225 +1928 107 18.16 12.16 16.51 0 460.7 341.81 48419 +1928 108 14.3 8.3 12.65 0 368.68 353.2 48612 +1928 109 17.26 11.26 15.61 1.43 437.66 260.65 48804 +1928 110 15.45 9.45 13.8 0 394.29 353.52 48995 +1928 111 17.15 11.15 15.5 0.16 434.92 263.04 49185 +1928 112 15.27 9.27 13.62 0.03 390.18 267.74 49374 +1928 113 10.58 4.58 8.93 0.73 295.33 276.11 49561 +1928 114 6.03 0.03 4.38 0.36 222.93 282.64 49748 +1928 115 6.17 0.17 4.52 0 224.9 378.13 49933 +1928 116 6.83 0.83 5.18 0 234.42 378.45 50117 +1928 117 12.84 6.84 11.19 0 338.22 369.22 50300 +1928 118 14.8 8.8 13.15 0 379.63 366.15 50481 +1928 119 11.36 5.36 9.71 0.48 309.57 281.05 50661 +1928 120 11.92 5.92 10.27 0 320.16 374.82 50840 +1928 121 14.84 8.84 13.19 0.02 380.52 277.15 51016 +1928 122 16.1 10.1 14.45 0 409.42 367.58 51191 +1928 123 17.55 11.55 15.9 1.14 444.98 273.51 51365 +1928 124 14.03 8.03 12.38 2.53 362.88 281.06 51536 +1928 125 12.79 6.79 11.14 1.37 337.22 283.86 51706 +1928 126 14.16 8.16 12.51 1.83 365.66 282.32 51874 +1928 127 13.79 7.79 12.14 0.87 357.78 283.63 52039 +1928 128 8.92 2.92 7.27 0.14 266.88 291.6 52203 +1928 129 8.36 2.36 6.71 0 257.82 390.61 52365 +1928 130 9.52 3.52 7.87 0 276.88 389.46 52524 +1928 131 7.97 1.97 6.32 0.63 251.67 294.66 52681 +1928 132 9.76 3.76 8.11 0 280.97 390.69 52836 +1928 133 9.27 3.27 7.62 0 272.67 392.28 52989 +1928 134 8.79 2.79 7.14 0 264.75 393.84 53138 +1928 135 9.85 3.85 8.2 0.01 282.51 294.52 53286 +1928 136 13.7 7.7 12.05 0 355.89 385.46 53430 +1928 137 15.18 9.18 13.53 0.39 388.14 286.96 53572 +1928 138 17.15 11.15 15.5 0.08 434.92 283.47 53711 +1928 139 18.91 12.91 17.26 0 480.69 373.4 53848 +1928 140 16.06 10.06 14.41 1 408.48 286.59 53981 +1928 141 14.76 8.76 13.11 0.15 378.75 289.42 54111 +1928 142 15.79 9.79 14.14 0.29 402.14 287.83 54238 +1928 143 13.84 7.84 12.19 0 358.84 389.15 54362 +1928 144 19.33 13.33 17.68 0.29 492.19 280.84 54483 +1928 145 18.09 12.09 16.44 0.71 458.88 284.09 54600 +1928 146 15.86 9.86 14.21 0.69 403.78 289.1 54714 +1928 147 17.16 11.16 15.51 0.05 435.17 286.78 54824 +1928 148 17.97 11.97 16.32 0.68 455.76 285.29 54931 +1928 149 16.16 10.16 14.51 0.02 410.84 289.38 55034 +1928 150 18.03 12.03 16.38 0.76 457.31 285.64 55134 +1928 151 21.4 15.4 19.75 0.1 552.4 277.54 55229 +1928 152 24.06 18.06 22.41 0.3 638.85 269.76 55321 +1928 153 27.84 21.84 26.19 0 781.24 342.13 55409 +1928 154 26.35 20.35 24.7 0.15 722.21 262.41 55492 +1928 155 21.64 15.64 19.99 0.01 559.77 277.5 55572 +1928 156 25.72 19.72 24.07 0.31 698.41 265.01 55648 +1928 157 20.48 14.48 18.83 0.07 524.91 280.99 55719 +1928 158 20.52 14.52 18.87 0.23 526.08 281.02 55786 +1928 159 15.99 9.99 14.34 0.04 406.83 291.62 55849 +1928 160 19.14 13.14 17.49 0.02 486.96 284.8 55908 +1928 161 18.96 12.96 17.31 0.1 482.04 285.28 55962 +1928 162 14.92 8.92 13.27 0.63 382.3 293.94 56011 +1928 163 15.64 9.64 13.99 0.8 398.66 292.72 56056 +1928 164 15.99 9.99 14.34 0 406.83 389.4 56097 +1928 165 13.45 7.45 11.8 0 350.68 395.83 56133 +1928 166 15.84 9.84 14.19 0.14 403.31 292.49 56165 +1928 167 15.68 9.68 14.03 0 399.59 390.35 56192 +1928 168 16.49 10.49 14.84 0.05 418.74 291.18 56214 +1928 169 18.76 12.76 17.11 0.8 476.63 286.16 56231 +1928 170 19.36 13.36 17.71 0.09 493.03 284.71 56244 +1928 171 19.83 13.83 18.18 0 506.2 378.12 56252 +1928 172 20.07 14.07 18.42 0.62 513.04 282.98 56256 +1928 173 22.82 16.82 21.17 1.76 597.22 275.37 56255 +1928 174 20.69 14.69 19.04 0.91 531.08 281.29 56249 +1928 175 17.95 11.95 16.3 0.94 455.24 287.97 56238 +1928 176 18.74 12.74 17.09 0.75 476.09 286.12 56223 +1928 177 20.39 14.39 18.74 1.38 522.29 281.95 56203 +1928 178 21.99 15.99 20.34 0 570.66 370.16 56179 +1928 179 18.69 12.69 17.04 0 474.75 381.46 56150 +1928 180 24.13 18.13 22.48 0 641.27 361.33 56116 +1928 181 22.42 16.42 20.77 1.1 584.3 276.17 56078 +1928 182 26.39 20.39 24.74 0.01 723.74 263.15 56035 +1928 183 21.45 15.45 19.8 0 553.93 371.56 55987 +1928 184 22.82 16.82 21.17 0.29 597.22 274.64 55935 +1928 185 20.82 14.82 19.17 0.41 534.93 280.2 55879 +1928 186 22.29 16.29 20.64 0.86 580.15 275.94 55818 +1928 187 19.59 13.59 17.94 0 499.44 377.36 55753 +1928 188 18.12 12.12 16.47 0 459.66 381.74 55684 +1928 189 20.24 14.24 18.59 0 517.94 374.73 55611 +1928 190 27.57 21.57 25.92 0.07 770.25 257.56 55533 +1928 191 29.09 23.09 27.44 0 833.86 335.06 55451 +1928 192 25.19 19.19 23.54 0 678.9 354.31 55366 +1928 193 24.79 18.79 23.14 0 664.49 355.83 55276 +1928 194 21.36 15.36 19.71 0.16 551.18 277.01 55182 +1928 195 17.4 11.4 15.75 0.69 441.18 286.46 55085 +1928 196 18.72 12.72 17.07 0 475.56 377.57 54984 +1928 197 19.83 13.83 18.18 0 506.2 373.53 54879 +1928 198 26.99 20.99 25.34 0 747.08 343.86 54770 +1928 199 28.2 22.2 26.55 0.63 796.1 253.02 54658 +1928 200 25.46 19.46 23.81 0 688.78 350.39 54542 +1928 201 28.88 22.88 27.23 0.12 824.81 249.68 54423 +1928 202 31.82 25.82 30.17 0.04 959.24 236.31 54301 +1928 203 26.23 20.23 24.58 0 717.62 345.35 54176 +1928 204 28.17 22.17 26.52 0 794.85 335.23 54047 +1928 205 30.25 24.25 28.6 0.02 885.33 242.45 53915 +1928 206 32.27 26.27 30.62 0 981.36 310.35 53780 +1928 207 30.73 24.73 29.08 0 907.4 319.32 53643 +1928 208 30.46 24.46 28.81 0 894.93 320.33 53502 +1928 209 30.96 24.96 29.31 0 918.14 316.77 53359 +1928 210 29.71 23.71 28.06 0 861.05 323.49 53213 +1928 211 31.69 25.69 30.04 0 952.93 311.04 53064 +1928 212 29.64 23.64 27.99 0 857.94 322.44 52913 +1928 213 27.79 21.79 26.14 0 779.19 331.58 52760 +1928 214 27.63 21.63 25.98 0.07 772.68 248.77 52604 +1928 215 25.94 19.94 24.29 0.15 706.64 254.36 52445 +1928 216 27.38 21.38 25.73 0 762.6 331.35 52285 +1928 217 27.79 21.79 26.14 0 779.19 328.47 52122 +1928 218 24.69 18.69 23.04 0.52 660.93 256.53 51958 +1928 219 23.27 17.27 21.62 0.01 612.06 260.12 51791 +1928 220 21.67 15.67 20.02 0.28 560.7 263.92 51622 +1928 221 23.02 17.02 21.37 0.33 603.78 259.42 51451 +1928 222 21.11 15.11 19.46 0.38 543.61 263.87 51279 +1928 223 21.82 15.82 20.17 0.75 565.35 261.15 51105 +1928 224 22.4 16.4 20.75 0.69 583.66 258.79 50929 +1928 225 24.09 18.09 22.44 0 639.89 337.41 50751 +1928 226 22.53 16.53 20.88 0 587.83 342.33 50572 +1928 227 19.49 13.49 17.84 0 496.64 351.38 50392 +1928 228 19.31 13.31 17.66 1.04 491.64 263.04 50210 +1928 229 21.82 15.82 20.17 0.08 565.35 255.92 50026 +1928 230 22.57 16.57 20.92 0.1 589.12 252.96 49842 +1928 231 23.83 17.83 22.18 0.8 630.95 248.3 49656 +1928 232 25.57 19.57 23.92 0 692.84 322.63 49469 +1928 233 24.19 18.19 22.54 0 643.35 326.97 49280 +1928 234 25.2 19.2 23.55 0 679.27 321.5 49091 +1928 235 26.91 20.91 25.26 0.4 743.94 234.45 48900 +1928 236 28.24 22.24 26.59 0.27 797.76 228.73 48709 +1928 237 28.9 22.9 27.25 1.16 825.67 225.13 48516 +1928 238 24.35 18.35 22.7 1.91 648.93 239.24 48323 +1928 239 21.59 15.59 19.94 0.05 558.23 245.69 48128 +1928 240 18.28 12.28 16.63 0.2 463.85 251.99 47933 +1928 241 18.02 12.02 16.37 0.44 457.05 251.23 47737 +1928 242 19.39 13.39 17.74 0.02 493.86 247.02 47541 +1928 243 20.36 14.36 18.71 0 521.41 324.59 47343 +1928 244 15.27 9.27 13.62 0.66 390.18 252.28 47145 +1928 245 18.02 12.02 16.37 0.77 457.05 245.76 46947 +1928 246 19.24 13.24 17.59 0.39 489.71 241.76 46747 +1928 247 18.36 12.36 16.71 2.04 465.96 242.21 46547 +1928 248 14.48 8.48 12.83 1.8 372.59 247.78 46347 +1928 249 17.03 11.03 15.38 0.07 431.94 241.79 46146 +1928 250 18.38 12.38 16.73 0 466.49 316.96 45945 +1928 251 21.9 15.9 20.25 0 567.85 304.47 45743 +1928 252 25.73 19.73 24.08 0.1 698.78 216.43 45541 +1928 253 25.84 19.84 24.19 0.94 702.89 214.61 45339 +1928 254 24.5 18.5 22.85 1.18 654.2 216.97 45136 +1928 255 21.11 15.11 19.46 1.22 543.61 223.9 44933 +1928 256 21.97 15.97 20.32 0.33 570.04 220.24 44730 +1928 257 22.67 16.67 21.02 0.34 592.35 216.98 44527 +1928 258 21.87 15.87 20.22 0.19 566.91 217.21 44323 +1928 259 16.79 10.79 15.14 0 426.03 300.98 44119 +1928 260 12.97 6.97 11.32 0 340.85 306.49 43915 +1928 261 14.61 8.61 12.96 0 375.44 300.85 43711 +1928 262 15.78 9.78 14.13 0.32 401.91 222.02 43507 +1928 263 18.6 12.6 16.95 0.26 472.34 215.25 43303 +1928 264 17.64 11.64 15.99 0.01 447.27 215.11 43099 +1928 265 15.6 9.6 13.95 0.7 397.74 216.74 42894 +1928 266 19.16 13.16 17.51 0 487.51 278.3 42690 +1928 267 17.96 11.96 16.31 0 455.5 278.61 42486 +1928 268 20.34 14.34 18.69 0 520.83 270.09 42282 +1928 269 18.06 12.06 16.41 0 458.09 273.37 42078 +1928 270 16.65 10.65 15 0 422.61 273.93 41875 +1928 271 20.34 14.34 18.69 0.43 520.83 196.93 41671 +1928 272 16.63 10.63 14.98 0.04 422.13 201.51 41468 +1928 273 14.7 8.7 13.05 0.01 377.42 202.5 41265 +1928 274 12.75 6.75 11.1 0 336.42 270.74 41062 +1928 275 16.13 10.13 14.48 0 410.13 261.81 40860 +1928 276 17.53 11.53 15.88 0 444.47 256.23 40658 +1928 277 12.17 6.17 10.52 0.5 324.99 197.61 40456 +1928 278 13.52 7.52 11.87 0.35 352.13 193.81 40255 +1928 279 15.97 9.97 14.32 0.1 406.36 188.4 40054 +1928 280 17.21 11.21 15.56 0.01 436.41 184.6 39854 +1928 281 14.25 8.25 12.6 0.02 367.6 186.75 39654 +1928 282 12.6 6.6 10.95 0 333.43 248.95 39455 +1928 283 15.74 9.74 14.09 0.01 400.98 180.63 39256 +1928 284 14.93 8.93 13.28 0 382.52 239.31 39058 +1928 285 13.9 7.9 12.25 0.15 360.11 178.81 38861 +1928 286 10.28 4.28 8.63 0 290 240.9 38664 +1928 287 12 6 10.35 0.58 321.7 176.71 38468 +1928 288 9.96 3.96 8.31 0.89 284.41 176.65 38273 +1928 289 9.78 3.78 8.13 0.34 281.31 174.82 38079 +1928 290 9.82 3.82 8.17 0.1 282 172.61 37885 +1928 291 6.63 0.63 4.98 0 231.5 230.89 37693 +1928 292 8.57 2.57 6.92 0 261.19 226.14 37501 +1928 293 8.23 2.23 6.58 0 255.76 223.74 37311 +1928 294 5.76 -0.24 4.11 0 219.16 223.24 37121 +1928 295 8.02 2.02 6.37 0 252.46 218.17 36933 +1928 296 14.24 8.24 12.59 0 367.38 207.77 36745 +1928 297 12.87 6.87 11.22 0.06 338.83 155.28 36560 +1928 298 17.46 11.46 15.81 0 442.7 197.28 36375 +1928 299 16.19 10.19 14.54 0 411.56 196.75 36191 +1928 300 20.41 14.41 18.76 0 522.87 186.37 36009 +1928 301 20.28 14.28 18.63 0.28 519.09 138.2 35829 +1928 302 18.85 12.85 17.2 0 479.06 184.57 35650 +1928 303 18.75 12.75 17.1 0.71 476.36 136.72 35472 +1928 304 17.45 11.45 15.8 0 442.44 182.22 35296 +1928 305 12.26 6.26 10.61 0.38 326.74 140.29 35122 +1928 306 9.41 3.41 7.76 0.03 275.02 141.01 34950 +1928 307 7.38 1.38 5.73 0.1 242.61 140.57 34779 +1928 308 11.1 5.1 9.45 0.23 304.76 135.84 34610 +1928 309 9.64 3.64 7.99 0.5 278.91 135.27 34444 +1928 310 10.01 4.01 8.36 0.17 285.28 133.16 34279 +1928 311 8.95 2.95 7.3 0 267.37 176.42 34116 +1928 312 9.96 3.96 8.31 0 284.41 172.81 33956 +1928 313 10.03 4.03 8.38 0.44 285.63 127.98 33797 +1928 314 9.91 3.91 8.26 0.06 283.55 126.61 33641 +1928 315 11.88 5.88 10.23 0 319.39 164.26 33488 +1928 316 12.58 6.58 10.93 0.61 333.03 121 33337 +1928 317 13.28 7.28 11.63 0 347.17 158.38 33188 +1928 318 12.14 6.14 10.49 0 324.4 157.37 33042 +1928 319 9.68 3.68 8.03 0 279.6 158.17 32899 +1928 320 9.47 3.47 7.82 0.13 276.03 117.38 32758 +1928 321 12.2 6.2 10.55 0 325.57 151.75 32620 +1928 322 13.65 7.65 12 0.03 354.84 111.28 32486 +1928 323 11.96 5.96 10.31 0 320.93 148.64 32354 +1928 324 8.54 2.54 6.89 0.5 260.7 112.33 32225 +1928 325 8.43 2.43 6.78 0.24 258.94 111.12 32100 +1928 326 9.79 3.79 8.14 1.14 281.48 109.17 31977 +1928 327 11.93 5.93 10.28 0.11 320.35 106.3 31858 +1928 328 11.68 5.68 10.03 0 315.59 140.05 31743 +1928 329 10.99 4.99 9.34 0 302.75 139.24 31631 +1928 330 11.85 5.85 10.2 0 318.82 137.01 31522 +1928 331 7.55 1.55 5.9 0.2 245.19 104.53 31417 +1928 332 7.11 1.11 5.46 0.49 238.56 103.54 31316 +1928 333 7.11 1.11 5.46 0 238.56 136.98 31218 +1928 334 9.92 3.92 8.27 0.02 283.72 100.29 31125 +1928 335 -1.37 -7.37 -3.02 0 137.62 139.28 31035 +1928 336 -5.74 -11.74 -7.39 0 101.91 139.69 30949 +1928 337 -1.26 -7.26 -2.91 0 138.65 136.47 30867 +1928 338 -0.79 -6.79 -2.44 0 143.09 135.32 30790 +1928 339 0.95 -5.05 -0.7 0 160.64 133.77 30716 +1928 340 -3.7 -9.7 -5.35 0.04 117.43 144.33 30647 +1928 341 0.68 -5.32 -0.97 0 157.8 175.42 30582 +1928 342 -0.24 -6.24 -1.89 0 148.45 175.13 30521 +1928 343 4.06 -1.94 2.41 0 196.67 128.94 30465 +1928 344 6.49 0.49 4.84 0 229.48 126.35 30413 +1928 345 6.05 0.05 4.4 0 223.21 126.21 30366 +1928 346 6.54 0.54 4.89 0 230.2 125.35 30323 +1928 347 4.11 -1.89 2.46 0 197.3 126.2 30284 +1928 348 6.28 0.28 4.63 0.53 226.47 93.43 30251 +1928 349 4.79 -1.21 3.14 0 206.07 125.09 30221 +1928 350 8.51 2.51 6.86 0 260.22 122.36 30197 +1928 351 5.86 -0.14 4.21 0 220.55 123.91 30177 +1928 352 3.03 -2.97 1.38 0.13 184.04 94.05 30162 +1928 353 1.82 -4.18 0.17 0 170.1 125.92 30151 +1928 354 0.18 -5.82 -1.47 0 152.66 126.62 30145 +1928 355 3.36 -2.64 1.71 0 188.01 125.13 30144 +1928 356 3.22 -2.78 1.57 0 186.32 125.23 30147 +1928 357 4.78 -1.22 3.13 0 205.94 124.44 30156 +1928 358 6.43 0.43 4.78 0 228.61 123.53 30169 +1928 359 7.64 1.64 5.99 0.39 246.57 92.14 30186 +1928 360 4.91 -1.09 3.26 0.58 207.65 93.7 30208 +1928 361 3.81 -2.19 2.16 0.25 193.54 94.41 30235 +1928 362 3.76 -2.24 2.11 0 192.92 126.34 30267 +1928 363 3.59 -2.41 1.94 0.21 190.82 95.27 30303 +1928 364 2.42 -3.58 0.77 0.48 176.89 96.01 30343 +1928 365 -1.06 -7.06 -2.71 0 140.52 130.13 30388 +1929 1 -5.47 -11.47 -7.12 0 103.86 132.52 30438 +1929 2 -4.98 -10.98 -6.63 0.16 107.47 143.63 30492 +1929 3 -2.91 -8.91 -4.56 0 123.97 177.11 30551 +1929 4 -1.24 -7.24 -2.89 0 138.83 177.33 30614 +1929 5 -0.89 -6.89 -2.54 0.13 142.14 144.6 30681 +1929 6 0.77 -5.23 -0.88 0.61 158.75 144.54 30752 +1929 7 -0.41 -6.41 -2.06 0 146.78 179.35 30828 +1929 8 -5.32 -11.32 -6.97 0 104.95 182.51 30907 +1929 9 -6.35 -12.35 -8 0 97.63 183.97 30991 +1929 10 -7.21 -13.21 -8.86 0 91.87 185.4 31079 +1929 11 -6.39 -12.39 -8.04 0.65 97.36 152.33 31171 +1929 12 -7.69 -13.69 -9.34 0.09 88.78 153.51 31266 +1929 13 -7.58 -13.58 -9.23 0 89.48 191.07 31366 +1929 14 -4.05 -10.05 -5.7 0 114.63 191.36 31469 +1929 15 -1.65 -7.65 -3.3 0 135.05 191.78 31575 +1929 16 -2.97 -8.97 -4.62 0 123.46 193.45 31686 +1929 17 -1.55 -7.55 -3.2 0.61 135.96 158.79 31800 +1929 18 -1.62 -7.62 -3.27 0.7 135.32 162.19 31917 +1929 19 -0.91 -6.91 -2.56 1.53 141.95 167.83 32038 +1929 20 -1.71 -7.71 -3.36 0.95 134.5 171.92 32161 +1929 21 -0.25 -6.25 -1.9 0.35 148.35 173.78 32289 +1929 22 -3.32 -9.32 -4.97 0 120.54 215.83 32419 +1929 23 -0.22 -6.22 -1.87 0 148.65 216.08 32552 +1929 24 -3.83 -9.83 -5.48 0 116.38 219.47 32688 +1929 25 -5.6 -11.6 -7.25 0 102.92 221.78 32827 +1929 26 -3.13 -9.13 -4.78 0 122.12 222.6 32969 +1929 27 -0.2 -6.2 -1.85 0 148.85 223.1 33114 +1929 28 1.21 -4.79 -0.44 0.1 163.42 181.75 33261 +1929 29 0.06 -5.94 -1.59 0 151.45 226.96 33411 +1929 30 2 -4 0.35 0.61 172.11 184.16 33564 +1929 31 -0.87 -6.87 -2.52 0 142.33 231.36 33718 +1929 32 -6.3 -12.3 -7.95 0 97.98 235.47 33875 +1929 33 -6.3 -12.3 -7.95 0 97.98 237.9 34035 +1929 34 -6.3 -12.3 -7.95 0 97.98 239.9 34196 +1929 35 -6.3 -12.3 -7.95 0 97.98 241.85 34360 +1929 36 -6.3 -12.3 -7.95 0 97.98 244.16 34526 +1929 37 -6.3 -12.3 -7.95 1.06 97.98 200.7 34694 +1929 38 -6.3 -12.3 -7.95 1.27 97.98 206.02 34863 +1929 39 -6.3 -12.3 -7.95 0.33 97.98 208.64 35035 +1929 40 -6.3 -12.3 -7.95 0 97.98 261.01 35208 +1929 41 -6.3 -12.3 -7.95 0 97.98 263.39 35383 +1929 42 -6.3 -12.3 -7.95 0 97.98 265.72 35560 +1929 43 -6.3 -12.3 -7.95 0.04 97.98 215.63 35738 +1929 44 -6.3 -12.3 -7.95 0 97.98 270.63 35918 +1929 45 -6.3 -12.3 -7.95 0.01 97.98 219.06 36099 +1929 46 -6.3 -12.3 -7.95 0 97.98 275.51 36282 +1929 47 -6.3 -12.3 -7.95 0.02 97.98 222.76 36466 +1929 48 -6.3 -12.3 -7.95 0 97.98 280.74 36652 +1929 49 -6.3 -12.3 -7.95 0.01 97.98 226.49 36838 +1929 50 -6.3 -12.3 -7.95 1 97.98 230.85 37026 +1929 51 -6.3 -12.3 -7.95 0.19 97.98 233.32 37215 +1929 52 -6.3 -12.3 -7.95 0 97.98 294.19 37405 +1929 53 -6.3 -12.3 -7.95 0.14 97.98 237.52 37596 +1929 54 -6.3 -12.3 -7.95 0 97.98 299.8 37788 +1929 55 -6.3 -12.3 -7.95 0.67 97.98 243.04 37981 +1929 56 -6.3 -12.3 -7.95 0 97.98 306.72 38175 +1929 57 -6.3 -12.3 -7.95 0 97.98 309.37 38370 +1929 58 -6.3 -12.3 -7.95 0.02 97.98 248.73 38565 +1929 59 -6.3 -12.3 -7.95 0.42 97.98 251.56 38761 +1929 60 1.94 -4.06 0.29 0 171.44 313.28 38958 +1929 61 4.87 -1.13 3.22 0 207.13 312.94 39156 +1929 62 3.68 -2.32 2.03 0 191.93 316.16 39355 +1929 63 1.3 -4.7 -0.35 0 164.39 320.72 39553 +1929 64 3.46 -2.54 1.81 0 189.23 321.26 39753 +1929 65 -0.23 -6.23 -1.88 0 148.55 326.79 39953 +1929 66 0.64 -5.36 -1.01 0 157.39 328.61 40154 +1929 67 4.82 -1.18 3.17 0 206.47 327.21 40355 +1929 68 6.15 0.15 4.5 0 224.62 327.84 40556 +1929 69 4.62 -1.38 2.97 0 203.85 331.33 40758 +1929 70 2.63 -3.37 0.98 0 179.33 335.53 40960 +1929 71 6.96 0.96 5.31 0 236.34 333.15 41163 +1929 72 6.18 0.18 4.53 0 225.05 336.01 41366 +1929 73 6.63 0.63 4.98 0 231.5 337.29 41569 +1929 74 4.64 -1.36 2.99 0 204.11 341.53 41772 +1929 75 3.01 -2.99 1.36 0 183.8 345.34 41976 +1929 76 6.29 0.29 4.64 0 226.61 343.77 42179 +1929 77 5.64 -0.36 3.99 0 217.5 346.36 42383 +1929 78 6.93 0.93 5.28 0 235.89 346.66 42587 +1929 79 10.49 4.49 8.84 0 293.72 343.29 42791 +1929 80 7.68 1.68 6.03 0 247.19 348.86 42996 +1929 81 7.58 1.58 5.93 0 245.65 350.66 43200 +1929 82 10.34 4.34 8.69 0 291.06 348.23 43404 +1929 83 6.44 0.44 4.79 0 228.76 355.31 43608 +1929 84 6.89 0.89 5.24 0 235.3 356.48 43812 +1929 85 7.07 1.07 5.42 0 237.97 357.93 44016 +1929 86 8.35 2.35 6.7 0 257.66 357.69 44220 +1929 87 5.13 -0.87 3.48 0 210.58 363.69 44424 +1929 88 3.25 -2.75 1.6 0 186.68 367.64 44627 +1929 89 4.44 -1.56 2.79 0 201.52 368.13 44831 +1929 90 7.61 1.61 5.96 0 246.11 365.76 45034 +1929 91 10.42 4.42 8.77 0.24 292.48 280.81 45237 +1929 92 6.97 0.97 5.32 0.06 236.48 285.55 45439 +1929 93 5.99 -0.01 4.34 0 222.37 372.12 45642 +1929 94 2.77 -3.23 1.12 0 180.96 377.57 45843 +1929 95 4.73 -1.27 3.08 0.08 205.29 290.97 46045 +1929 96 5.64 -0.36 3.99 0 217.5 377.49 46246 +1929 97 11.15 5.15 9.5 0.09 305.68 285.41 46446 +1929 98 10.04 4.04 8.39 0.09 285.8 287.31 46647 +1929 99 5.1 -0.9 3.45 0 210.18 381.62 46846 +1929 100 6.33 0.33 4.68 0 227.18 381.38 47045 +1929 101 9.87 3.87 8.22 0.02 282.86 262.02 47243 +1929 102 10.54 4.54 8.89 0.05 294.62 262.6 47441 +1929 103 9.7 3.7 8.05 0 279.94 353.41 47638 +1929 104 6.99 0.99 5.34 0.58 236.78 269.55 47834 +1929 105 4.35 -1.65 2.7 0 200.36 364.64 48030 +1929 106 7.59 1.59 5.94 0 245.81 362.04 48225 +1929 107 6.13 0.13 4.48 0 224.34 365.8 48419 +1929 108 10.15 4.15 8.5 0.32 287.72 271.06 48612 +1929 109 10.78 4.78 9.13 1.08 298.93 271.43 48804 +1929 110 15.77 9.77 14.12 0.04 401.68 264.56 48995 +1929 111 14.88 8.88 13.23 0.09 381.41 267.3 49185 +1929 112 11.85 5.85 10.2 0.37 318.82 273.31 49374 +1929 113 11.94 5.94 10.29 0.73 320.54 274.19 49561 +1929 114 10.33 4.33 8.68 0.02 290.89 277.58 49748 +1929 115 13.17 7.17 11.52 0 344.91 365.99 49933 +1929 116 14.08 8.08 12.43 0.01 363.94 273.9 50117 +1929 117 12.32 6.32 10.67 0.66 327.91 277.72 50300 +1929 118 14.95 8.95 13.3 0.41 382.97 274.35 50481 +1929 119 7.14 1.14 5.49 1.03 239.01 286.43 50661 +1929 120 8.2 2.2 6.55 0.04 255.28 286.11 50840 +1929 121 20.18 14.18 18.53 0 516.2 354.5 51016 +1929 122 18.58 12.58 16.93 0 471.8 360.67 51191 +1929 123 22.73 16.73 21.08 0.09 594.29 260.73 51365 +1929 124 26.6 20.6 24.95 0.08 731.84 249.2 51536 +1929 125 23.07 17.07 21.42 0.32 605.43 261.22 51706 +1929 126 25.13 19.13 23.48 0.06 676.72 255.57 51874 +1929 127 23.61 17.61 21.96 2.13 623.47 260.96 52039 +1929 128 19.18 13.18 17.53 0.36 488.06 273.51 52203 +1929 129 18.06 12.06 16.41 0 458.09 368.92 52365 +1929 130 18.06 12.06 16.41 0 458.09 369.7 52524 +1929 131 15.23 9.23 13.58 0.03 389.27 283.64 52681 +1929 132 12.99 6.99 11.34 0.72 341.25 288.2 52836 +1929 133 12.83 6.83 11.18 0.1 338.02 289 52989 +1929 134 14.8 8.8 13.15 0 379.63 381.5 53138 +1929 135 13.65 7.65 12 0.36 354.84 288.7 53286 +1929 136 15.31 9.31 13.66 1.37 391.09 286.18 53430 +1929 137 16.58 10.58 14.93 0.2 420.91 284.2 53572 +1929 138 18.48 12.48 16.83 0 469.14 374.05 53711 +1929 139 21.84 15.84 20.19 0 565.97 363.4 53848 +1929 140 24.14 18.14 22.49 0 641.62 354.76 53981 +1929 141 22.74 16.74 21.09 0 594.62 360.86 54111 +1929 142 21.62 15.62 19.97 0.33 559.15 274.18 54238 +1929 143 15.92 9.92 14.27 0.01 405.18 287.98 54362 +1929 144 18.47 12.47 16.82 0 468.88 377.17 54483 +1929 145 14.97 8.97 13.32 0 383.42 387.37 54600 +1929 146 11.46 5.46 9.81 0 311.44 395.68 54714 +1929 147 12.12 6.12 10.47 0 324.02 394.81 54824 +1929 148 15 9 13.35 0 384.09 388.55 54931 +1929 149 16.73 10.73 15.08 0 424.56 384.28 55034 +1929 150 18.26 12.26 16.61 0 463.33 380.15 55134 +1929 151 19.57 13.57 17.92 0 498.88 376.39 55229 +1929 152 18.41 12.41 16.76 1.66 467.28 285.15 55321 +1929 153 19.72 13.72 18.07 1.84 503.09 282.19 55409 +1929 154 20.15 14.15 18.5 0.94 515.34 281.34 55492 +1929 155 18.71 12.71 17.06 0.14 475.29 285.01 55572 +1929 156 19.45 13.45 17.8 0.01 495.53 283.47 55648 +1929 157 18.12 12.12 16.47 0 459.66 382.32 55719 +1929 158 19.25 13.25 17.6 0 489.98 378.95 55786 +1929 159 23.34 17.34 21.69 0.43 614.39 273.21 55849 +1929 160 24.11 18.11 22.46 0.19 640.58 270.93 55908 +1929 161 26.77 20.77 25.12 0.04 738.45 261.83 55962 +1929 162 24.69 18.69 23.04 0.07 660.93 269.14 56011 +1929 163 25.72 19.72 24.07 0.13 698.41 265.8 56056 +1929 164 23.93 17.93 22.28 0.01 634.38 271.79 56097 +1929 165 20.18 14.18 18.53 0.72 516.2 282.57 56133 +1929 166 18.69 12.69 17.04 0.6 474.75 286.3 56165 +1929 167 19.84 13.84 18.19 0.93 506.48 283.45 56192 +1929 168 19.22 13.22 17.57 1.03 489.16 285.05 56214 +1929 169 20.17 14.17 18.52 0.91 515.92 282.68 56231 +1929 170 16.75 10.75 15.1 0.61 425.05 290.65 56244 +1929 171 18.45 12.45 16.8 1.65 468.34 286.93 56252 +1929 172 23.07 17.07 21.42 0.31 605.43 274.63 56256 +1929 173 20.79 14.79 19.14 0.01 534.04 281.09 56255 +1929 174 19.63 13.63 17.98 0 500.56 378.68 56249 +1929 175 20.32 14.32 18.67 0.01 520.25 282.24 56238 +1929 176 20.87 14.87 19.22 0 536.42 374.35 56223 +1929 177 14.22 8.22 12.57 0 366.95 393.9 56203 +1929 178 16.45 10.45 14.8 0 417.77 388.17 56179 +1929 179 18.46 12.46 16.81 0 468.61 382.18 56150 +1929 180 18.47 12.47 16.82 0.05 468.88 286.52 56116 +1929 181 20.31 14.31 18.66 0 519.96 375.94 56078 +1929 182 23.71 17.71 22.06 0 626.86 362.89 56035 +1929 183 19.29 13.29 17.64 0 491.09 379.03 55987 +1929 184 20.8 14.8 19.15 0 534.34 373.75 55935 +1929 185 21.15 15.15 19.5 0 544.81 372.42 55879 +1929 186 20.77 14.77 19.12 1.91 533.45 280.14 55818 +1929 187 19.5 13.5 17.85 0.57 496.92 283.24 55753 +1929 188 20.14 14.14 18.49 0.03 515.05 281.44 55684 +1929 189 19.17 13.17 17.52 0 487.78 378.28 55611 +1929 190 19.03 13.03 17.38 0 483.95 378.36 55533 +1929 191 18.51 12.51 16.86 0 469.94 379.72 55451 +1929 192 20.22 14.22 18.57 0 517.36 373.86 55366 +1929 193 22.61 16.61 20.96 0 590.41 364.86 55276 +1929 194 24.65 18.65 23 0 659.51 356.23 55182 +1929 195 25.91 19.91 24.26 0 705.51 350.28 55085 +1929 196 22.62 16.62 20.97 0 590.73 363.94 54984 +1929 197 24.67 18.67 23.02 0.33 660.22 266.28 54879 +1929 198 22.6 16.6 20.95 0.38 590.08 272.36 54770 +1929 199 23.33 17.33 21.68 0 614.06 359.91 54658 +1929 200 27.67 21.67 26.02 0 774.3 339.74 54542 +1929 201 29.07 23.07 27.42 0 832.99 331.87 54423 +1929 202 27.9 21.9 26.25 0 783.7 337.58 54301 +1929 203 24.04 18.04 22.39 0 638.16 355.1 54176 +1929 204 26.05 20.05 24.4 0.01 710.79 259.29 54047 +1929 205 25.22 19.22 23.57 0.37 679.99 261.75 53915 +1929 206 22.59 16.59 20.94 0 589.76 359.37 53780 +1929 207 21.04 15.04 19.39 0 541.5 364.43 53643 +1929 208 21.43 15.43 19.78 0 553.32 362.39 53502 +1929 209 24.09 18.09 22.44 0 639.89 351.44 53359 +1929 210 28.56 22.56 26.91 0 811.19 329.77 53213 +1929 211 26.41 20.41 24.76 0 724.51 339.8 53064 +1929 212 25.55 19.55 23.9 0 692.1 343 52913 +1929 213 26.21 20.21 24.56 0 716.86 339.26 52760 +1929 214 25.14 19.14 23.49 0.01 677.09 257.53 52604 +1929 215 24.53 18.53 22.88 0 655.26 345.35 52445 +1929 216 22.38 16.38 20.73 0.07 583.02 264.7 52285 +1929 217 20.54 14.54 18.89 0 526.67 358.59 52122 +1929 218 23.75 17.75 22.1 0 628.22 345.93 51958 +1929 219 23.74 17.74 22.09 0 627.88 344.96 51791 +1929 220 20.85 14.85 19.2 0.32 535.82 266.07 51622 +1929 221 17.4 11.4 15.75 0.06 441.18 273.32 51451 +1929 222 17.16 11.16 15.51 0 435.17 364.02 51279 +1929 223 21.46 15.46 19.81 0.06 554.23 262.11 51105 +1929 224 23.19 17.19 21.54 0.36 609.4 256.55 50929 +1929 225 23.19 17.19 21.54 0 609.4 340.96 50751 +1929 226 21.68 15.68 20.03 0.02 561.01 259.05 50572 +1929 227 18.66 12.66 17.01 0 473.94 353.9 50392 +1929 228 22.54 16.54 20.89 0 588.15 339.85 50210 +1929 229 25.69 19.69 24.04 0.18 697.29 244.5 50026 +1929 230 23.43 17.43 21.78 2.7 617.4 250.54 49842 +1929 231 24.2 18.2 22.55 0.55 643.7 247.2 49656 +1929 232 23.06 17.06 21.41 0 605.1 332.71 49469 +1929 233 20.45 14.45 18.8 0 524.04 340.39 49280 +1929 234 19.75 13.75 18.1 0 503.94 341.19 49091 +1929 235 19.45 13.45 17.8 0.03 495.53 255.47 48900 +1929 236 17.77 11.77 16.12 0 450.6 344.03 48709 +1929 237 24.99 18.99 23.34 0 671.66 318.02 48516 +1929 238 28.16 22.16 26.51 0 794.43 302.3 48323 +1929 239 31.52 25.52 29.87 0 944.73 283.18 48128 +1929 240 30.64 24.64 28.99 0.03 903.23 214.92 47933 +1929 241 32.29 26.29 30.64 0 982.36 275.62 47737 +1929 242 32.02 26.02 30.37 0.06 969.02 206.77 47541 +1929 243 26.58 20.58 24.93 0.16 731.07 226.19 47343 +1929 244 22.38 16.38 20.73 0.98 583.02 237.15 47145 +1929 245 24.22 18.22 22.57 1.19 644.4 230.81 46947 +1929 246 17.46 11.46 15.81 0.11 442.7 245.39 46747 +1929 247 19.64 13.64 17.99 0 500.84 319.35 46547 +1929 248 18.88 12.88 17.23 0 479.87 319.59 46347 +1929 249 25.43 19.43 23.78 0 687.68 295.61 46146 +1929 250 22 16 20.35 0 570.98 306.2 45945 +1929 251 17.88 11.88 16.23 0.01 453.43 237.12 45743 +1929 252 20.3 14.3 18.65 0 519.67 307.32 45541 +1929 253 21.33 15.33 19.68 0 550.27 302.13 45339 +1929 254 23.22 17.22 21.57 0 610.39 293.87 45136 +1929 255 24.5 18.5 22.85 0 654.2 287.16 44933 +1929 256 25.49 19.49 23.84 0 689.89 281.29 44730 +1929 257 23.73 17.73 22.08 0.69 627.54 214.29 44527 +1929 258 21.94 15.94 20.29 0.17 569.1 217.05 44323 +1929 259 26.2 20.2 24.55 0.17 716.48 204.04 44119 +1929 260 21.07 15.07 19.42 0.48 542.4 215.54 43915 +1929 261 18.83 12.83 17.18 0 478.52 291.18 43711 +1929 262 15.25 9.25 13.6 0 389.73 297.15 43507 +1929 263 14.31 8.31 12.66 0.26 368.89 222.42 43303 +1929 264 11.31 5.31 9.66 0.02 308.64 224.48 43099 +1929 265 15.33 9.33 13.68 0 391.55 289.54 42894 +1929 266 21.73 15.73 20.08 0 562.55 271.24 42690 +1929 267 20.05 14.05 18.4 0 512.47 273.36 42486 +1929 268 18.84 12.84 17.19 0 478.79 273.96 42282 +1929 269 17.11 11.11 15.46 0 433.92 275.54 42078 +1929 270 18.51 12.51 16.86 0 469.94 269.72 41875 +1929 271 14.19 8.19 12.54 0 366.3 276.21 41671 +1929 272 17.94 11.94 16.29 0 454.98 265.8 41468 +1929 273 18.05 12.05 16.4 0 457.83 263.06 41265 +1929 274 12.1 6.1 10.45 0 323.63 271.8 41062 +1929 275 13.27 7.27 11.62 0 346.96 267.09 40860 +1929 276 15.6 9.6 13.95 0.28 397.74 195.13 40658 +1929 277 14.47 8.47 12.82 0.17 372.37 194.72 40456 +1929 278 13 7 11.35 0.03 341.45 194.45 40255 +1929 279 10.63 4.63 8.98 0 296.23 260.01 40054 +1929 280 13.31 7.31 11.66 0.03 347.78 189.97 39854 +1929 281 8.35 2.35 6.7 0 257.66 257.49 39654 +1929 282 11.26 5.26 9.61 0 307.72 250.92 39455 +1929 283 10.15 4.15 8.5 0.24 287.72 187.19 39256 +1929 284 10.16 4.16 8.51 0.39 287.9 184.89 39058 +1929 285 12.48 6.48 10.83 0 331.05 240.62 38861 +1929 286 10.94 4.94 9.29 1.03 301.83 180.02 38664 +1929 287 10.2 4.2 8.55 1.06 288.6 178.53 38468 +1929 288 13.72 7.72 12.07 0.25 356.31 172.7 38273 +1929 289 15.5 9.5 13.85 0.25 395.43 168.56 38079 +1929 290 16.54 10.54 14.89 0.05 419.95 165.07 37885 +1929 291 15.35 9.35 13.7 1.49 392 164.64 37693 +1929 292 13.83 7.83 12.18 0 358.63 219.3 37501 +1929 293 14.32 8.32 12.67 0.5 369.11 161.89 37311 +1929 294 18.21 12.21 16.56 1.35 462.01 154.7 37121 +1929 295 19.4 13.4 17.75 0.34 494.14 150.88 36933 +1929 296 21.38 15.38 19.73 0.65 551.79 145.83 36745 +1929 297 14.93 8.93 13.28 1.03 382.52 153.02 36560 +1929 298 15.97 9.97 14.32 0 406.36 199.82 36375 +1929 299 14.04 8.04 12.39 0.19 363.09 150.05 36191 +1929 300 12.71 6.71 11.06 0 335.62 199.27 36009 +1929 301 17.44 11.44 15.79 0.31 442.19 142.21 35829 +1929 302 19.25 13.25 17.6 0 489.98 183.81 35650 +1929 303 18.2 12.2 16.55 0.07 461.75 137.46 35472 +1929 304 20.62 14.62 18.97 0 529.02 176.35 35296 +1929 305 15.55 9.55 13.9 0 396.58 182.59 35122 +1929 306 14.21 8.21 12.56 0.04 366.73 136.73 34950 +1929 307 11.4 5.4 9.75 0.13 310.32 137.52 34779 +1929 308 9.05 3.05 7.4 0 269.02 183.26 34610 +1929 309 8.95 2.95 7.3 0 267.37 181.04 34444 +1929 310 10.29 4.29 8.64 0.01 290.18 132.95 34279 +1929 311 8.89 2.89 7.24 0.07 266.38 132.36 34116 +1929 312 6.97 0.97 5.32 1.23 236.48 131.65 33956 +1929 313 9.08 3.08 7.43 0.8 269.51 128.66 33797 +1929 314 6.1 0.1 4.45 0.01 223.91 129.1 33641 +1929 315 7.32 1.32 5.67 0.1 241.71 126.46 33488 +1929 316 9.3 3.3 7.65 0.02 273.17 123.53 33337 +1929 317 9.6 3.6 7.95 0 278.23 162.25 33188 +1929 318 12.41 6.41 10.76 0 329.68 157.08 33042 +1929 319 10.44 4.44 8.79 0 292.83 157.45 32899 +1929 320 10.75 4.75 9.1 0 298.39 155.31 32758 +1929 321 13.81 7.81 12.16 0.5 358.21 112.47 32620 +1929 322 10.69 4.69 9.04 0.38 297.3 113.62 32486 +1929 323 11.83 5.83 10.18 0 318.44 148.77 32354 +1929 324 15.35 9.35 13.7 0.92 392 107.08 32225 +1929 325 14.84 8.84 13.19 0.29 380.52 106.31 32100 +1929 326 14.58 8.58 12.93 1.22 374.78 105.5 31977 +1929 327 7.8 1.8 6.15 0.33 249.03 109.03 31858 +1929 328 4.24 -1.76 2.59 0.33 198.96 109.39 31743 +1929 329 2.27 -3.73 0.62 0.01 175.17 109.1 31631 +1929 330 5.1 -0.9 3.45 0.04 210.18 106.77 31522 +1929 331 6.1 0.1 4.45 0.79 223.91 105.29 31417 +1929 332 2.99 -3.01 1.34 0.48 183.56 105.48 31316 +1929 333 3.82 -2.18 2.17 0 193.66 139.08 31218 +1929 334 6.58 0.58 4.93 0.16 230.78 102.19 31125 +1929 335 0.47 -5.53 -1.18 0 155.63 138.5 31035 +1929 336 1.86 -4.14 0.21 0 170.54 136.75 30949 +1929 337 2.49 -3.51 0.84 0 177.7 134.77 30867 +1929 338 6.18 0.18 4.53 0 225.05 131.68 30790 +1929 339 4.43 -1.57 2.78 0.52 201.39 98.98 30716 +1929 340 1.99 -4.01 0.34 0 172 132.53 30647 +1929 341 3.64 -2.36 1.99 0.51 191.43 98.07 30582 +1929 342 2.27 -3.73 0.62 0.72 175.17 98.03 30521 +1929 343 1.32 -4.68 -0.33 0 164.61 130.33 30465 +1929 344 10.9 4.9 9.25 0 301.11 123.06 30413 +1929 345 9.4 3.4 7.75 0 274.85 123.86 30366 +1929 346 5.8 -0.2 4.15 0 219.72 125.81 30323 +1929 347 6.95 0.95 5.3 0 236.19 124.49 30284 +1929 348 8.24 2.24 6.59 0 255.92 123.26 30251 +1929 349 4.63 -1.37 2.98 0.2 203.98 93.89 30221 +1929 350 5.32 -0.68 3.67 0 213.14 124.45 30197 +1929 351 6.96 0.96 5.31 0.01 236.34 92.41 30177 +1929 352 8.36 2.36 6.71 0 257.82 122.16 30162 +1929 353 7.47 1.47 5.82 0.11 243.98 92.04 30151 +1929 354 5.27 -0.73 3.62 0 212.46 124.07 30145 +1929 355 5.5 -0.5 3.85 0.36 215.58 92.95 30144 +1929 356 4.67 -1.33 3.02 0.43 204.5 93.33 30147 +1929 357 6.38 0.38 4.73 0 227.89 123.48 30156 +1929 358 6.3 0.3 4.65 0 226.75 123.62 30169 +1929 359 5.88 -0.12 4.23 0 220.83 123.99 30186 +1929 360 9.42 3.42 7.77 0 275.19 121.92 30208 +1929 361 7.04 1.04 5.39 0 237.52 123.95 30235 +1929 362 5.22 -0.78 3.57 0 211.79 125.52 30267 +1929 363 5.43 -0.57 3.78 0 214.63 125.98 30303 +1929 364 5.82 -0.18 4.17 0 219.99 126.14 30343 +1929 365 0.01 -5.99 -1.64 0 150.94 129.69 30388 +1930 1 -0.49 -6.49 -2.14 0 145.99 130.8 30438 +1930 2 -3.01 -9.01 -4.66 0 123.12 132.49 30492 +1930 3 -2.84 -8.84 -4.49 0.24 124.56 144 30551 +1930 4 -1.94 -7.94 -3.59 0.18 132.42 144.92 30614 +1930 5 -4.03 -10.03 -5.68 0 114.79 179.71 30681 +1930 6 -2.42 -8.42 -4.07 0.01 128.18 146.05 30752 +1930 7 -0.6 -6.6 -2.25 0 144.92 179.97 30828 +1930 8 5.06 -0.94 3.41 0 209.65 177.81 30907 +1930 9 7.7 1.7 6.05 0 247.49 133.92 30991 +1930 10 2.76 -3.24 1.11 0 180.85 138.3 31079 +1930 11 8.04 2.04 6.39 0 252.77 135.92 31171 +1930 12 4.24 -1.76 2.59 0 198.96 139.46 31266 +1930 13 2.52 -3.48 0.87 0 178.05 142.05 31366 +1930 14 6.31 0.31 4.66 0 226.89 141.23 31469 +1930 15 2.37 -3.63 0.72 0 176.32 145.06 31575 +1930 16 4.15 -1.85 2.5 0 197.81 145.34 31686 +1930 17 1.65 -4.35 0 0 168.21 148.42 31800 +1930 18 0.62 -5.38 -1.03 0 157.18 150.85 31917 +1930 19 3.23 -2.77 1.58 0 186.44 151.4 32038 +1930 20 2.95 -3.05 1.3 0.43 183.09 114.86 32161 +1930 21 2.34 -3.66 0.69 0 175.97 155.51 32289 +1930 22 4.44 -1.56 2.79 0 201.52 156 32419 +1930 23 8.04 2.04 6.39 0.22 252.77 116.35 32552 +1930 24 5.75 -0.25 4.1 0 219.02 158.93 32688 +1930 25 5.27 -0.73 3.62 0.05 212.46 120.86 32827 +1930 26 2.13 -3.87 0.48 0 173.58 165.07 32969 +1930 27 3.56 -2.44 1.91 0.14 190.45 124.67 33114 +1930 28 3.86 -2.14 2.21 0.37 194.16 126.19 33261 +1930 29 1.51 -4.49 -0.14 0 166.68 172.06 33411 +1930 30 4.89 -1.11 3.24 0.02 207.39 129.13 33564 +1930 31 1.3 -4.7 -0.35 0.25 164.39 132.62 33718 +1930 32 -3.25 -9.25 -4.9 0.55 121.12 176.42 33875 +1930 33 -1.71 -7.71 -3.36 0 134.5 223.51 34035 +1930 34 -1.29 -7.29 -2.94 0.2 138.37 179.61 34196 +1930 35 -0.45 -6.45 -2.1 0.17 146.39 181.21 34360 +1930 36 -2.55 -8.55 -4.2 0.03 127.05 183.77 34526 +1930 37 -3.83 -9.83 -5.48 1.69 116.38 190.52 34694 +1930 38 -4.39 -10.39 -6.04 0 111.97 241.7 34863 +1930 39 -7.15 -13.15 -8.8 0 92.26 245.17 35035 +1930 40 -1.22 -7.22 -2.87 0.01 139.02 195.03 35208 +1930 41 3.39 -2.61 1.74 0 188.37 244.35 35383 +1930 42 4.21 -1.79 2.56 0 198.57 245.61 35560 +1930 43 3.21 -2.79 1.56 0 186.2 248.49 35738 +1930 44 2.84 -3.16 1.19 0 181.79 250.8 35918 +1930 45 0.48 -5.52 -1.17 0.04 155.73 201.55 36099 +1930 46 5 -1 3.35 0 208.85 253.43 36282 +1930 47 8.12 2.12 6.47 0.1 254.02 199.23 36466 +1930 48 12.21 6.21 10.56 0 325.76 248.69 36652 +1930 49 10.9 4.9 9.25 0.28 301.11 198.08 36838 +1930 50 9.28 3.28 7.63 0.84 272.84 200.28 37026 +1930 51 5.01 -0.99 3.36 0 208.98 226.2 37215 +1930 52 6.09 0.09 4.44 0 223.77 228.05 37405 +1930 53 2.42 -3.58 0.77 0 176.89 234.1 37596 +1930 54 4.16 -1.84 2.51 0.52 197.94 176.62 37788 +1930 55 3.58 -2.42 1.93 0 190.7 238.98 37981 +1930 56 6.39 0.39 4.74 0 228.04 239.15 38175 +1930 57 7.3 1.3 5.65 0 241.41 241.09 38370 +1930 58 9.43 3.43 7.78 0 275.36 241.57 38565 +1930 59 12.65 6.65 11 0.01 334.42 179.89 38761 +1930 60 14.35 8.35 12.7 0.05 369.76 179.96 38958 +1930 61 13.06 7.06 11.41 0.92 342.67 183.67 39156 +1930 62 9.18 3.18 7.53 0.59 271.17 189.81 39355 +1930 63 7.6 1.6 5.95 0.25 245.96 193.47 39553 +1930 64 10.65 4.65 9 0 296.59 257 39753 +1930 65 8.09 2.09 6.44 0 253.55 263.16 39953 +1930 66 5.88 -0.12 4.23 0.24 220.83 201.27 40154 +1930 67 8.01 2.01 6.36 0 252.3 268.87 40355 +1930 68 10.93 4.93 9.28 0 301.65 267.85 40556 +1930 69 9.06 3.06 7.41 0.44 269.18 204.77 40758 +1930 70 10.26 4.26 8.61 0.07 289.65 205.66 40960 +1930 71 11.94 5.94 10.29 0.01 320.54 205.93 41163 +1930 72 13.08 7.08 11.43 0.32 343.08 206.6 41366 +1930 73 12.76 6.76 11.11 0 336.62 278.62 41569 +1930 74 9.26 3.26 7.61 0 272.5 286.68 41772 +1930 75 5.47 -0.53 3.82 0 215.17 294.05 41976 +1930 76 7.3 1.3 5.65 0 241.41 294.59 42179 +1930 77 10.53 4.53 8.88 0 294.44 292.76 42383 +1930 78 3.85 -2.15 2.2 0 194.04 303.73 42587 +1930 79 5.99 -0.01 4.34 0 222.37 304.18 42791 +1930 80 5.2 -0.8 3.55 0.11 211.52 230.73 42996 +1930 81 7.8 1.8 6.15 0 249.03 307.1 43200 +1930 82 14.03 8.03 12.38 0.14 362.88 224.78 43404 +1930 83 14.83 8.83 13.18 0 380.3 300.55 43608 +1930 84 11.56 5.56 9.91 0 313.32 309.13 43812 +1930 85 5.99 -0.01 4.34 0.4 222.37 239.71 44016 +1930 86 7.34 1.34 5.69 1.54 242.01 240.26 44220 +1930 87 8.12 2.12 6.47 1.42 254.02 241.38 44424 +1930 88 15.54 9.54 13.89 0 396.35 311.05 44627 +1930 89 15.19 9.19 13.54 0.01 388.37 235.52 44831 +1930 90 16.74 10.74 15.09 0 424.8 312.81 45034 +1930 91 19.49 13.49 17.84 0.65 496.64 230.88 45237 +1930 92 19.22 13.22 17.57 0.22 489.16 233.05 45439 +1930 93 17.49 11.49 15.84 0 443.46 317.46 45642 +1930 94 12.85 6.85 11.2 0.18 338.42 247.4 45843 +1930 95 9.91 3.91 8.26 0.31 283.55 252.91 46045 +1930 96 8.62 2.62 6.97 0.05 261.99 256.02 46246 +1930 97 11.72 5.72 10.07 0 316.34 338.27 46446 +1930 98 9.32 3.32 7.67 0.05 273.51 258.24 46647 +1930 99 8.28 2.28 6.63 0 256.55 347.95 46846 +1930 100 14 8 12.35 0.03 362.24 254.73 47045 +1930 101 14.17 8.17 12.52 0 365.87 341.19 47243 +1930 102 13.02 7.02 11.37 0.02 341.86 259.11 47441 +1930 103 12.95 6.95 11.3 0 340.44 347.45 47638 +1930 104 10.43 4.43 8.78 0.35 292.66 265.51 47834 +1930 105 11.15 5.15 9.5 0 305.68 354.53 48030 +1930 106 17.45 11.45 15.8 0.09 442.44 256.6 48225 +1930 107 17.35 11.35 15.7 0.31 439.92 258.02 48419 +1930 108 16.59 10.59 14.94 0.1 421.16 260.79 48612 +1930 109 10.22 4.22 8.57 1.92 288.95 272.18 48804 +1930 110 12.89 6.89 11.24 0.04 339.23 269.43 48995 +1930 111 15.89 9.89 14.24 0.35 404.48 265.48 49185 +1930 112 13.54 7.54 11.89 0.68 352.55 270.7 49374 +1930 113 13.16 7.16 11.51 0.76 344.71 272.31 49561 +1930 114 9.81 3.81 8.16 0.08 281.82 278.27 49748 +1930 115 13.04 7.04 11.39 0.46 342.26 274.7 49933 +1930 116 16.04 10.04 14.39 0 408 360.5 50117 +1930 117 15.6 9.6 13.95 0 397.74 362.9 50300 +1930 118 16.78 10.78 15.13 0.14 425.78 270.87 50481 +1930 119 17.53 11.53 15.88 0.4 444.47 270.21 50661 +1930 120 20.49 14.49 18.84 0.03 525.2 264.29 50840 +1930 121 19.05 13.05 17.4 0 484.5 358.08 51016 +1930 122 16.66 10.66 15.01 0.55 422.85 274.58 51191 +1930 123 21.65 15.65 20 0.26 560.08 263.71 51365 +1930 124 16.27 10.27 14.62 0 413.46 369.23 51536 +1930 125 15.88 9.88 14.23 0 404.24 371.23 51706 +1930 126 14.11 8.11 12.46 0 364.59 376.55 51874 +1930 127 16.66 10.66 15.01 0 422.85 371.04 52039 +1930 128 21.86 15.86 20.21 0.01 566.6 266.7 52203 +1930 129 20.58 14.58 18.93 0 527.84 360.93 52365 +1930 130 17.55 11.55 15.9 0 444.98 371.18 52524 +1930 131 17.77 11.77 16.12 0 450.6 371.33 52681 +1930 132 11.14 5.14 9.49 0 305.5 388.1 52836 +1930 133 11.9 5.9 10.25 0 319.78 387.3 52989 +1930 134 13.42 7.42 11.77 0 350.05 384.75 53138 +1930 135 9.85 3.85 8.2 0 282.51 392.7 53286 +1930 136 9.12 3.12 7.47 0.04 270.17 295.99 53430 +1930 137 17.35 11.35 15.7 0.05 439.92 282.59 53572 +1930 138 20.54 14.54 18.89 0 526.67 367.36 53711 +1930 139 23.72 17.72 22.07 0.05 627.2 267.04 53848 +1930 140 19.71 13.71 18.06 0.13 502.81 278.48 53981 +1930 141 21.43 15.43 19.78 0.02 553.32 274.34 54111 +1930 142 14.59 8.59 12.94 0 375 386.81 54238 +1930 143 15.38 9.38 13.73 0.32 392.69 289.03 54362 +1930 144 16.5 10.5 14.85 0.47 418.98 287.17 54483 +1930 145 17.1 11.1 15.45 0.49 433.67 286.26 54600 +1930 146 13.6 7.6 11.95 0.88 353.8 293.29 54714 +1930 147 14.47 8.47 12.82 0.84 372.37 292.1 54824 +1930 148 16.16 10.16 14.51 0.6 410.84 289.15 54931 +1930 149 18.35 12.35 16.7 0 465.7 379.55 55034 +1930 150 16.56 10.56 14.91 0.16 420.43 288.82 55134 +1930 151 18.31 12.31 16.66 0 464.64 380.39 55229 +1930 152 25.94 19.94 24.29 0 706.64 351.3 55321 +1930 153 23.14 17.14 21.49 0 607.74 363.72 55409 +1930 154 28.14 22.14 26.49 0 793.6 340.86 55492 +1930 155 22.85 16.85 21.2 0.69 598.2 274.02 55572 +1930 156 19.68 13.68 18.03 0 501.96 377.2 55648 +1930 157 19.74 13.74 18.09 0 503.65 377.17 55719 +1930 158 23.69 17.69 22.04 0.04 626.18 271.95 55786 +1930 159 22.52 16.52 20.87 0.39 587.51 275.66 55849 +1930 160 26.11 20.11 24.46 0.14 713.06 264.18 55908 +1930 161 26.37 20.37 24.72 0.05 722.97 263.29 55962 +1930 162 25.41 19.41 23.76 0.4 686.94 266.72 56011 +1930 163 21.36 15.36 19.71 0 551.18 372.45 56056 +1930 164 23.76 17.76 22.11 0 628.56 363.09 56097 +1930 165 29 23 27.35 0.22 829.97 253.37 56133 +1930 166 24.36 18.36 22.71 0.05 649.28 270.53 56165 +1930 167 27.71 21.71 26.06 0 775.93 344.77 56192 +1930 168 26.94 20.94 25.29 0.89 745.11 261.57 56214 +1930 169 25.26 19.26 23.61 0.21 681.45 267.57 56231 +1930 170 24.81 18.81 23.16 0.15 665.2 269.08 56244 +1930 171 22.7 16.7 21.05 0.37 593.32 275.75 56252 +1930 172 21.8 15.8 20.15 0 564.73 371.12 56256 +1930 173 22.07 16.07 20.42 1.47 573.18 277.56 56255 +1930 174 22.21 16.21 20.56 0.29 577.6 277.1 56249 +1930 175 24.34 18.34 22.69 0.06 648.58 270.57 56238 +1930 176 21.77 15.77 20.12 0 563.79 371.07 56223 +1930 177 19.61 13.61 17.96 0 500 378.57 56203 +1930 178 22.17 16.17 20.52 0.71 576.34 277.11 56179 +1930 179 18.79 12.79 17.14 0.12 477.44 285.86 56150 +1930 180 17.55 11.55 15.9 0 444.98 384.81 56116 +1930 181 22.83 16.83 21.18 0.07 597.55 274.96 56078 +1930 182 21.16 15.16 19.51 0 545.11 372.8 56035 +1930 183 23.18 17.18 21.53 0.27 609.06 273.67 55987 +1930 184 21.52 15.52 19.87 0.03 556.07 278.37 55935 +1930 185 21.15 15.15 19.5 0.9 544.81 279.31 55879 +1930 186 22.73 16.73 21.08 0.06 594.29 274.65 55818 +1930 187 26.61 20.61 24.96 0 732.23 348.99 55753 +1930 188 25.38 19.38 23.73 0 685.84 354.53 55684 +1930 189 25.68 19.68 24.03 0.13 696.92 264.73 55611 +1930 190 24.09 18.09 22.44 2.03 639.89 269.75 55533 +1930 191 25.5 19.5 23.85 0.28 690.25 264.89 55451 +1930 192 22.68 16.68 21.03 0 592.67 364.86 55366 +1930 193 23.07 17.07 21.42 0 605.43 363.05 55276 +1930 194 22.48 16.48 20.83 1.94 586.22 273.86 55182 +1930 195 16.35 10.35 14.7 0.05 415.37 288.67 55085 +1930 196 20.85 14.85 19.2 0.44 535.82 277.87 54984 +1930 197 21.73 15.73 20.08 0.14 562.55 275.15 54879 +1930 198 23.25 17.25 21.6 0.42 611.39 270.43 54770 +1930 199 20.27 14.27 18.62 0.79 518.8 278.46 54658 +1930 200 19.09 13.09 17.44 0 485.59 374.75 54542 +1930 201 19.75 13.75 18.1 0 503.94 372.14 54423 +1930 202 20 14 18.35 0.07 511.04 278.06 54301 +1930 203 18.37 12.37 16.72 0 466.23 375.44 54176 +1930 204 22.51 16.51 20.86 0.07 587.18 270.55 54047 +1930 205 19.12 13.12 17.47 1.08 486.41 279.05 53915 +1930 206 17.02 11.02 15.37 0.01 431.69 283.32 53780 +1930 207 18.82 12.82 17.17 0 478.25 371.78 53643 +1930 208 22.6 16.6 20.95 0 590.08 358.04 53502 +1930 209 22.71 16.71 21.06 0.38 593.64 267.73 53359 +1930 210 21.99 15.99 20.34 0.06 570.66 269.31 53213 +1930 211 25.76 19.76 24.11 0.06 699.9 257.11 53064 +1930 212 26.22 20.22 24.57 0.43 717.24 254.95 52913 +1930 213 23.35 17.35 21.7 1.09 614.73 263.68 52760 +1930 214 22.85 16.85 21.2 0.59 598.2 264.6 52604 +1930 215 22.89 16.89 21.24 0 599.51 351.99 52445 +1930 216 21.87 15.87 20.22 0.15 566.91 266.11 52285 +1930 217 23.92 17.92 22.27 0.09 634.03 259.53 52122 +1930 218 26.76 20.76 25.11 0 738.06 332.75 51958 +1930 219 27.68 21.68 26.03 0.76 774.71 245.46 51791 +1930 220 22.77 16.77 21.12 0.38 595.59 260.87 51622 +1930 221 24.82 18.82 23.17 0 665.56 338.62 51451 +1930 222 22.97 16.97 21.32 0.03 602.13 258.8 51279 +1930 223 21.58 15.58 19.93 0 557.92 349.06 51105 +1930 224 23.36 17.36 21.71 0 615.06 341.41 50929 +1930 225 22.79 16.79 21.14 0 596.25 342.48 50751 +1930 226 26.7 20.7 25.05 0 735.72 324.99 50572 +1930 227 26.86 20.86 25.21 0.38 741.97 242.28 50392 +1930 228 24.85 18.85 23.2 0.52 666.63 248.08 50210 +1930 229 19.27 13.27 17.62 0 490.54 349.6 50026 +1930 230 21.45 15.45 19.8 0 553.93 341.26 49842 +1930 231 18.59 12.59 16.94 0.15 472.07 261.66 49656 +1930 232 22.28 16.28 20.63 0 579.83 335.57 49469 +1930 233 21.24 15.24 19.59 0 547.53 337.79 49280 +1930 234 19.95 13.95 18.3 0.68 509.61 255.43 49091 +1930 235 20.13 14.13 18.48 0.77 514.76 253.89 48900 +1930 236 15.78 9.78 14.13 0.35 401.91 261.88 48709 +1930 237 13.22 7.22 11.57 0.85 345.94 264.94 48516 +1930 238 13.06 7.06 11.41 0 342.67 351.86 48323 +1930 239 16.75 10.75 15.1 0.1 425.05 256.38 48128 +1930 240 20.61 14.61 18.96 0.09 528.72 246.8 47933 +1930 241 21.14 15.14 19.49 2.52 544.51 244.25 47737 +1930 242 22.01 16.01 20.36 1.12 571.29 240.79 47541 +1930 243 16.05 10.05 14.4 0.23 408.24 252.3 47343 +1930 244 18.46 12.46 16.81 0 468.61 328.33 47145 +1930 245 20.73 14.73 19.08 0 532.26 319.82 46947 +1930 246 22.08 16.08 20.43 0.93 573.49 235.14 46747 +1930 247 24.31 18.31 22.66 0.06 647.54 227.82 46547 +1930 248 18.24 12.24 16.59 0.31 462.8 241 46347 +1930 249 16.57 10.57 14.92 0.04 420.67 242.64 46146 +1930 250 15.37 9.37 13.72 0 392.46 324.34 45945 +1930 251 16.22 10.22 14.57 1.09 412.27 240.19 45743 +1930 252 14.23 8.23 12.58 0.05 367.17 241.84 45541 +1930 253 15 9 13.35 0.03 384.09 239.01 45339 +1930 254 18.42 12.42 16.77 0.35 467.55 231.28 45136 +1930 255 18.65 12.65 17 0 473.68 305.52 44933 +1930 256 24.33 18.33 22.68 0.23 648.23 214.22 44730 +1930 257 19.93 13.93 18.28 0.5 509.04 223.25 44527 +1930 258 18.6 12.6 16.95 0 472.34 298.95 44323 +1930 259 20.94 14.94 19.29 0.51 538.51 217.56 44119 +1930 260 16.84 10.84 15.19 0.63 427.25 223.86 43915 +1930 261 19.72 13.72 18.07 0.05 503.09 216.62 43711 +1930 262 19.75 13.75 18.1 0 503.94 286.42 43507 +1930 263 19.25 13.25 17.6 0 489.98 285.34 43303 +1930 264 22.2 16.2 20.55 0 577.29 274.47 43099 +1930 265 24.17 18.17 22.52 0.11 642.66 199.39 42894 +1930 266 21.4 15.4 19.75 0.83 552.4 204.15 42690 +1930 267 20.13 14.13 18.48 0.44 514.76 204.86 42486 +1930 268 21.79 15.79 20.14 0.22 564.42 199.52 42282 +1930 269 19.83 13.83 18.18 0.77 506.2 201.75 42078 +1930 270 17.91 11.91 16.26 0.58 454.2 203.35 41875 +1930 271 19.51 13.51 17.86 0 497.2 264.71 41671 +1930 272 20.16 14.16 18.51 0 515.63 260.4 41468 +1930 273 25.27 19.27 23.62 0.77 681.82 182.05 41265 +1930 274 19.42 13.42 17.77 0.6 494.69 192.91 41062 +1930 275 12.74 6.74 11.09 0.16 336.22 200.98 40860 +1930 276 14.03 8.03 12.38 0 362.88 263.07 40658 +1930 277 19.71 13.71 18.06 0 502.81 248.64 40456 +1930 278 15.8 9.8 14.15 0 402.38 254.31 40255 +1930 279 11.77 5.77 10.12 0 317.3 258.36 40054 +1930 280 11.42 5.42 9.77 0 310.69 256.21 39854 +1930 281 15.82 9.82 14.17 0 402.84 246.19 39654 +1930 282 13.72 7.72 12.07 0.92 356.31 185.37 39455 +1930 283 15.58 9.58 13.93 0.42 397.27 180.85 39256 +1930 284 15.57 9.57 13.92 0.75 397.04 178.63 39058 +1930 285 15.96 9.96 14.31 0.61 406.12 176.15 38861 +1930 286 15.93 9.93 14.28 0.99 405.42 174.15 38664 +1930 287 16.65 10.65 15 0.23 422.61 170.99 38468 +1930 288 18.01 12.01 16.36 1.81 456.79 166.97 38273 +1930 289 15.1 9.1 13.45 0.39 386.34 169.07 38079 +1930 290 12.06 6.06 10.41 0.18 322.85 170.43 37885 +1930 291 10.22 4.22 8.57 0.64 288.95 170.2 37693 +1930 292 9.25 3.25 7.6 0.47 272.34 169.03 37501 +1930 293 8.5 2.5 6.85 0.27 260.06 167.59 37311 +1930 294 10.61 4.61 8.96 0 295.87 218.11 37121 +1930 295 12.17 6.17 10.52 0.25 324.99 159.95 36933 +1930 296 12.69 6.69 11.04 0.18 335.22 157.49 36745 +1930 297 12.05 6.05 10.4 1.34 322.66 156.1 36560 +1930 298 11.37 5.37 9.72 2.63 309.76 154.8 36375 +1930 299 10.06 4.06 8.41 0.86 286.15 153.88 36191 +1930 300 10.9 4.9 9.25 0.6 301.11 151.15 36009 +1930 301 12.07 6.07 10.42 0.28 323.05 148.2 35829 +1930 302 13.12 7.12 11.47 0.07 343.89 145.24 35650 +1930 303 11.28 5.28 9.63 0 308.09 193.4 35472 +1930 304 14.54 8.54 12.89 0.01 373.9 140.06 35296 +1930 305 10.19 4.19 8.54 0.47 288.42 142.08 35122 +1930 306 11.92 5.92 10.27 0.18 320.16 138.93 34950 +1930 307 15.94 9.94 14.29 0.07 405.65 133.04 34779 +1930 308 14.13 8.13 12.48 0.71 365.02 133.06 34610 +1930 309 9.79 3.79 8.14 1.88 281.48 135.16 34444 +1930 310 7.38 1.38 5.73 0 242.61 180.03 34279 +1930 311 12.75 6.75 11.1 0 336.42 172.36 34116 +1930 312 14.39 8.39 12.74 0 370.63 167.72 33956 +1930 313 11.55 5.55 9.9 0 313.13 169.05 33797 +1930 314 11.51 5.51 9.86 0 312.38 167.17 33641 +1930 315 9.49 3.49 7.84 0.15 276.37 125.03 33488 +1930 316 9.42 3.42 7.77 0 275.19 164.6 33337 +1930 317 10.56 4.56 8.91 0.19 294.97 120.99 33188 +1930 318 8.04 2.04 6.39 0 252.77 161.31 33042 +1930 319 11.13 5.13 9.48 0 305.31 156.77 32899 +1930 320 8.83 2.83 7.18 0.06 265.4 117.81 32758 +1930 321 8.45 2.45 6.8 0 259.26 155.31 32620 +1930 322 10.53 4.53 8.88 0.01 294.44 113.73 32486 +1930 323 10.18 4.18 8.53 0 288.25 150.38 32354 +1930 324 13.27 7.27 11.62 0.29 346.96 108.92 32225 +1930 325 15.13 9.13 13.48 0 387.01 141.39 32100 +1930 326 15.45 9.45 13.8 0 394.29 139.61 31977 +1930 327 14.67 8.67 13.02 0.05 376.76 104.07 31858 +1930 328 10.24 4.24 8.59 0.1 289.3 106.04 31743 +1930 329 7.92 1.92 6.27 0 250.9 141.84 31631 +1930 330 5.7 -0.3 4.05 0 218.33 141.98 31522 +1930 331 7.42 1.42 5.77 0.01 243.22 104.6 31417 +1930 332 8.3 2.3 6.65 0.25 256.87 102.88 31316 +1930 333 10.03 4.03 8.38 0.07 285.63 101.03 31218 +1930 334 12.46 6.46 10.81 0 330.66 131.4 31125 +1930 335 4.52 -1.48 2.87 0 202.55 136.39 31035 +1930 336 6.55 0.55 4.9 0 230.34 134.03 30949 +1930 337 4.69 -1.31 3.04 0.53 204.76 100.16 30867 +1930 338 3.42 -2.58 1.77 0.17 188.74 100 30790 +1930 339 3.43 -2.57 1.78 0.14 188.86 99.4 30716 +1930 340 1.16 -4.84 -0.49 0.04 162.88 99.7 30647 +1930 341 -2.27 -8.27 -3.92 0 129.49 133.41 30582 +1930 342 -0.96 -6.96 -2.61 0.01 141.47 142.39 30521 +1930 343 2.25 -3.75 0.6 0.35 174.94 97.41 30465 +1930 344 4.71 -1.29 3.06 0.02 205.02 95.58 30413 +1930 345 4.35 -1.65 2.7 0.02 200.36 95.41 30366 +1930 346 6.25 0.25 4.6 0.2 226.04 94.15 30323 +1930 347 5.83 -0.17 4.18 0.2 220.13 93.9 30284 +1930 348 5.4 -0.6 3.75 0.21 214.22 93.84 30251 +1930 349 9.25 3.25 7.6 1.64 272.34 91.6 30221 +1930 350 9.24 3.24 7.59 0.32 272.17 91.36 30197 +1930 351 9.86 3.86 8.21 0 282.68 121.12 30177 +1930 352 3.71 -2.29 2.06 0.25 192.3 93.78 30162 +1930 353 3.95 -2.05 2.3 0 195.29 124.85 30151 +1930 354 2.2 -3.8 0.55 0 174.37 125.71 30145 +1930 355 5.49 -0.51 3.84 0 215.45 123.94 30144 +1930 356 6.54 0.54 4.89 0 230.2 123.32 30147 +1930 357 5.42 -0.58 3.77 0 214.49 124.07 30156 +1930 358 4.14 -1.86 2.49 1.31 197.68 93.66 30169 +1930 359 2.69 -3.31 1.04 0.69 180.03 94.32 30186 +1930 360 2.82 -3.18 1.17 0.17 181.55 94.55 30208 +1930 361 2.41 -3.59 0.76 0.48 176.78 94.95 30235 +1930 362 -0.93 -6.93 -2.58 1.44 141.76 144.56 30267 +1930 363 -2.68 -8.68 -4.33 0 125.93 177.87 30303 +1930 364 -2.05 -8.05 -3.7 0 131.44 177.98 30343 +1930 365 -2.32 -8.32 -3.97 0 129.05 178.59 30388 +1931 1 -4.12 -10.12 -5.77 0 114.08 180.02 30438 +1931 2 -3.31 -9.31 -4.96 0 120.62 180.41 30492 +1931 3 0.39 -5.61 -1.26 0 154.8 179.79 30551 +1931 4 -2.05 -8.05 -3.7 0 131.44 181.6 30614 +1931 5 0.11 -5.89 -1.54 1.14 151.95 147.82 30681 +1931 6 2.2 -3.8 0.55 0.32 174.37 147.36 30752 +1931 7 0.88 -5.12 -0.77 0.13 159.9 148.21 30828 +1931 8 0.55 -5.45 -1.1 0.44 156.45 149.25 30907 +1931 9 5.78 -0.22 4.13 0 219.44 180.99 30991 +1931 10 4.96 -1.04 3.31 0 208.32 182.03 31079 +1931 11 5.9 -0.1 4.25 0 221.11 181.52 31171 +1931 12 3.72 -2.28 2.07 0 192.42 183.25 31266 +1931 13 2.66 -3.34 1.01 0 179.67 184.98 31366 +1931 14 1.11 -4.89 -0.54 0 162.35 186.97 31469 +1931 15 2.64 -3.36 0.99 0.04 179.44 150.92 31575 +1931 16 6.79 0.79 5.14 0 233.83 143.6 31686 +1931 17 9.38 3.38 7.73 0 274.51 143.23 31800 +1931 18 8.49 2.49 6.84 0.14 259.9 109.38 31917 +1931 19 9.11 3.11 7.46 0.03 270.01 110.43 32038 +1931 20 10.06 4.06 8.41 0.11 286.15 110.97 32161 +1931 21 8.77 2.77 7.12 0.36 264.42 113.29 32289 +1931 22 8.44 2.44 6.79 0 259.1 153.06 32419 +1931 23 2.78 -3.22 1.13 0.41 181.08 119.09 32552 +1931 24 -1.73 -7.73 -3.38 0.19 134.32 163.3 32688 +1931 25 -1.01 -7.01 -2.66 0 141 205.5 32827 +1931 26 2.04 -3.96 0.39 0 172.56 205.46 32969 +1931 27 1.89 -4.11 0.24 0 170.88 207.17 33114 +1931 28 0.5 -5.5 -1.15 0 155.94 209.91 33261 +1931 29 3.96 -2.04 2.31 0 195.41 170.56 33411 +1931 30 3.12 -2.88 1.47 0 185.11 173.36 33564 +1931 31 6.21 0.21 4.56 0 225.47 173.55 33718 +1931 32 8.38 2.38 6.73 0 258.14 173.81 33875 +1931 33 6 0 4.35 0.14 222.51 133.82 34035 +1931 34 5.34 -0.66 3.69 0 213.41 181.13 34196 +1931 35 1.7 -4.3 0.05 0 168.77 185.75 34360 +1931 36 3.56 -2.44 1.91 0.55 190.45 140.31 34526 +1931 37 6.28 0.28 4.63 0 226.47 187.44 34694 +1931 38 4.78 -1.22 3.13 0.13 205.94 143.52 34863 +1931 39 5.09 -0.91 3.44 0 210.05 193.73 35035 +1931 40 0.22 -5.78 -1.43 0.67 153.07 149.72 35208 +1931 41 0.19 -5.81 -1.46 0 152.76 202.3 35383 +1931 42 -0.6 -6.6 -2.25 0.58 144.92 192.68 35560 +1931 43 -4.57 -10.57 -6.22 0 110.58 248.49 35738 +1931 44 -3.84 -9.84 -5.49 0 116.3 250.59 35918 +1931 45 3.38 -2.62 1.73 0.02 188.25 195.79 36099 +1931 46 4.79 -1.21 3.14 0 206.07 249.34 36282 +1931 47 4.7 -1.3 3.05 0.04 204.89 197.73 36466 +1931 48 5.94 -0.06 4.29 0.54 221.67 162.73 36652 +1931 49 8.07 2.07 6.42 0.04 253.24 163.26 36838 +1931 50 6.5 0.5 4.85 1.67 229.62 166.41 37026 +1931 51 4.2 -1.8 2.55 0 198.45 226.89 37215 +1931 52 2 -4 0.35 0.06 172.11 173.57 37405 +1931 53 2.37 -3.63 0.72 0.73 176.32 175.6 37596 +1931 54 1.83 -4.17 0.18 1.09 170.21 177.99 37788 +1931 55 4.72 -1.28 3.07 0.01 205.16 178.51 37981 +1931 56 3.95 -2.05 2.3 0.02 195.29 181.04 38175 +1931 57 0.44 -5.56 -1.21 0.19 155.32 185.22 38370 +1931 58 -1.33 -7.33 -2.98 0.8 137.99 224.52 38565 +1931 59 -0.25 -6.25 -1.9 0 148.35 289.18 38761 +1931 60 -0.54 -6.54 -2.19 0 145.51 292.11 38958 +1931 61 -1.31 -7.31 -2.96 0.33 138.18 231.28 39156 +1931 62 -0.09 -6.09 -1.74 0.18 149.94 233.07 39355 +1931 63 -0.19 -6.19 -1.84 0.38 148.95 236.15 39553 +1931 64 2.45 -3.55 0.8 0 177.24 302.91 39753 +1931 65 1.39 -4.61 -0.26 0.51 165.37 238.94 39953 +1931 66 4.98 -1.02 3.33 0.03 208.58 237.98 40154 +1931 67 3.34 -2.66 1.69 0 187.77 309.25 40355 +1931 68 2.92 -3.08 1.27 0.02 182.73 242.81 40556 +1931 69 0.33 -5.67 -1.32 0 154.19 316.6 40758 +1931 70 1.18 -4.82 -0.47 0.36 163.1 247.56 40960 +1931 71 1.66 -4.34 0.01 0.05 168.32 249.15 41163 +1931 72 -0.79 -6.79 -2.44 0 143.09 325.36 41366 +1931 73 4.14 -1.86 2.49 0 197.68 323.39 41569 +1931 74 6.8 0.8 5.15 0 233.98 322.48 41772 +1931 75 7.77 1.77 6.12 0 248.57 323.12 41976 +1931 76 11.58 5.58 9.93 0 313.7 288.55 42179 +1931 77 11.83 5.83 10.18 0 318.44 290.71 42383 +1931 78 13.46 7.46 11.81 0.35 350.88 217.88 42587 +1931 79 13.53 7.53 11.88 0 352.34 293.05 42791 +1931 80 8.95 2.95 7.3 0 267.37 302.95 42996 +1931 81 6.58 0.58 4.93 0 230.78 308.64 43200 +1931 82 6.69 0.69 5.04 0.21 232.37 233.38 43404 +1931 83 4.56 -1.44 2.91 0.22 203.07 237.11 43608 +1931 84 4.09 -1.91 2.44 0 197.05 319.22 43812 +1931 85 3.52 -2.48 1.87 2.29 189.96 241.76 44016 +1931 86 2.91 -3.09 1.26 0.01 182.61 244.06 44220 +1931 87 -1.32 -7.32 -2.97 0 138.09 331.64 44424 +1931 88 1.08 -4.92 -0.57 0 162.03 332.11 44627 +1931 89 2.78 -3.22 1.13 0 181.08 332.84 44831 +1931 90 7.33 1.33 5.68 0 241.86 329.96 45034 +1931 91 13.92 7.92 12.27 0.13 360.53 240.92 45237 +1931 92 15.18 9.18 13.53 0 388.14 320.76 45439 +1931 93 12.69 6.69 11.04 0.05 335.22 246.03 45642 +1931 94 12.12 6.12 10.47 0 324.02 331.25 45843 +1931 95 12.22 6.22 10.57 0.13 325.96 249.89 46045 +1931 96 12.13 6.13 10.48 0.28 324.21 251.6 46246 +1931 97 12.48 6.48 10.83 0 331.05 336.84 46446 +1931 98 13.91 7.91 12.26 0.15 360.32 251.94 46647 +1931 99 12.66 6.66 11.01 0.5 334.62 255.33 46846 +1931 100 13.4 7.4 11.75 0 349.64 340.9 47045 +1931 101 16.68 10.68 15.03 0 423.34 335.34 47243 +1931 102 16.86 10.86 15.21 0.13 427.74 252.56 47441 +1931 103 13.29 7.29 11.64 0 347.37 346.76 47638 +1931 104 8.64 2.64 6.99 0 262.32 356.96 47834 +1931 105 8.28 2.28 6.63 0.39 256.55 269.5 48030 +1931 106 7.82 1.82 6.17 0 249.34 361.7 48225 +1931 107 10.08 4.08 8.43 0.47 286.5 269.83 48419 +1931 108 7.56 1.56 5.91 0 245.35 365.56 48612 +1931 109 6.87 0.87 5.22 0.2 235.01 276.15 48804 +1931 110 7.16 1.16 5.51 0 239.31 369.23 48995 +1931 111 9.71 3.71 8.06 0 280.11 366.79 49185 +1931 112 11.86 5.86 10.21 0.68 319.01 273.29 49374 +1931 113 9.56 3.56 7.91 0 277.55 369.94 49561 +1931 114 11.12 5.12 9.47 0 305.13 368.66 49748 +1931 115 9.48 3.48 7.83 0.24 276.2 279.78 49933 +1931 116 5.6 -0.4 3.95 0.07 216.95 285.12 50117 +1931 117 6.88 0.88 5.23 1.05 235.16 284.79 50300 +1931 118 8.87 2.87 7.22 0.89 266.06 283.48 50481 +1931 119 7.16 1.16 5.51 0 239.31 381.88 50661 +1931 120 5.02 -0.98 3.37 0.61 209.11 289.55 50840 +1931 121 17.79 11.79 16.14 0.03 451.11 271.36 51016 +1931 122 16.16 10.16 14.51 0.37 410.84 275.57 51191 +1931 123 17.09 11.09 15.44 0 433.42 365.96 51365 +1931 124 20.92 14.92 19.27 0 537.91 355.21 51536 +1931 125 22.77 16.77 21.12 0.32 595.59 262.09 51706 +1931 126 18.25 12.25 16.6 0 463.06 365.66 51874 +1931 127 19.42 13.42 17.77 0 494.69 362.95 52039 +1931 128 22.05 16.05 20.4 0 572.55 354.91 52203 +1931 129 20.39 14.39 18.74 0.19 522.29 271.18 52365 +1931 130 22.96 16.96 21.31 0.33 601.8 264.77 52524 +1931 131 26.24 20.24 24.59 0.46 718 254.82 52681 +1931 132 24.29 18.29 22.64 0.32 646.84 261.88 52836 +1931 133 26.71 20.71 25.06 0.19 736.11 254.21 52989 +1931 134 24.75 18.75 23.1 0 663.06 348.55 53138 +1931 135 24.69 18.69 23.04 0 660.93 349.46 53286 +1931 136 21.24 15.24 19.59 0 547.53 363.64 53430 +1931 137 21.65 15.65 20 0 560.08 362.84 53572 +1931 138 19.41 13.41 17.76 0.11 494.41 278.34 53711 +1931 139 17.9 11.9 16.25 0.29 453.94 282.35 53848 +1931 140 17.54 11.54 15.89 1.11 444.72 283.51 53981 +1931 141 18.45 12.45 16.8 0.05 468.34 281.8 54111 +1931 142 19.65 13.65 18 0 501.12 372.42 54238 +1931 143 16.77 10.77 15.12 0 425.54 381.66 54362 +1931 144 15.02 9.02 13.37 0 384.54 386.77 54483 +1931 145 17.92 11.92 16.27 0 454.46 379.3 54600 +1931 146 16.84 10.84 15.19 0 427.25 382.8 54714 +1931 147 16.51 10.51 14.86 0 419.22 384.19 54824 +1931 148 18.09 12.09 16.44 0 458.88 380.02 54931 +1931 149 18.96 12.96 17.31 0.08 482.04 283.23 55034 +1931 150 22.8 16.8 21.15 0 596.57 364.35 55134 +1931 151 19.18 13.18 17.53 0.01 488.06 283.25 55229 +1931 152 19.25 13.25 17.6 0 489.98 377.54 55321 +1931 153 17.24 11.24 15.59 0 437.16 383.92 55409 +1931 154 17.89 11.89 16.24 0 453.69 382.33 55492 +1931 155 19.23 13.23 17.58 0 489.43 378.36 55572 +1931 156 18.91 12.91 17.26 0.4 480.69 284.78 55648 +1931 157 15.83 9.83 14.18 0.45 403.08 291.62 55719 +1931 158 19.17 13.17 17.52 0.41 487.78 284.41 55786 +1931 159 20.81 14.81 19.16 0.03 534.64 280.43 55849 +1931 160 19.91 13.91 18.26 0 508.47 377.2 55908 +1931 161 17.22 11.22 15.57 0.11 436.66 289.24 55962 +1931 162 16.03 10.03 14.38 0 407.77 389.03 56011 +1931 163 18.3 12.3 16.65 0 464.38 382.72 56056 +1931 164 21.58 15.58 19.93 0 557.92 371.68 56097 +1931 165 25.99 19.99 24.34 0 708.52 353.27 56133 +1931 166 25.49 19.49 23.84 0.16 689.89 266.75 56165 +1931 167 26.58 20.58 24.93 0 731.07 350.45 56192 +1931 168 24.72 18.72 23.07 0.34 661.99 269.37 56214 +1931 169 27.51 21.51 25.86 1.16 767.83 259.41 56231 +1931 170 23.29 17.29 21.64 0.27 612.72 273.93 56244 +1931 171 23.99 17.99 22.34 0.12 636.44 271.79 56252 +1931 172 24.67 18.67 23.02 0 660.22 359.44 56256 +1931 173 25.06 19.06 23.41 0 674.19 357.69 56255 +1931 174 25.58 19.58 23.93 0 693.21 355.24 56249 +1931 175 27.13 21.13 25.48 0.11 752.62 260.81 56238 +1931 176 25.31 19.31 23.66 0 683.28 356.42 56223 +1931 177 25.69 19.69 24.04 0.18 697.29 265.93 56203 +1931 178 26.32 20.32 24.67 0.52 721.06 263.72 56179 +1931 179 28.44 22.44 26.79 1.41 806.14 255.54 56150 +1931 180 28.49 22.49 26.84 0.61 808.24 255.26 56116 +1931 181 26.45 20.45 24.8 0.03 726.05 263.04 56078 +1931 182 22.8 16.8 21.15 0 596.57 366.59 56035 +1931 183 20.25 14.25 18.6 0 518.22 375.82 55987 +1931 184 22.01 16.01 20.36 0.01 571.29 276.99 55935 +1931 185 23.78 17.78 22.13 0.11 629.24 271.65 55879 +1931 186 22.31 16.31 20.66 0 580.78 367.84 55818 +1931 187 25.32 19.32 23.67 0 683.64 355.06 55753 +1931 188 24.81 18.81 23.16 0 665.2 357.08 55684 +1931 189 25.8 19.8 24.15 0 701.39 352.42 55611 +1931 190 26.42 20.42 24.77 0.09 724.89 261.84 55533 +1931 191 23.31 17.31 21.66 0 613.39 362.64 55451 +1931 192 21.6 15.6 19.95 0 558.54 368.96 55366 +1931 193 23.26 17.26 21.61 0 611.72 362.28 55276 +1931 194 25.13 19.13 23.48 0 676.72 354.1 55182 +1931 195 25.32 19.32 23.67 0 683.64 352.99 55085 +1931 196 25.29 19.29 23.64 0 682.55 352.73 54984 +1931 197 21.33 15.33 19.68 0.02 550.27 276.25 54879 +1931 198 21.3 15.3 19.65 0.07 549.35 276.01 54770 +1931 199 24.33 18.33 22.68 1.77 648.23 266.81 54658 +1931 200 24.09 18.09 22.44 0 639.89 356.38 54542 +1931 201 25.65 19.65 24 0 695.8 349.07 54423 +1931 202 24.39 18.39 22.74 0.02 650.34 265.58 54301 +1931 203 23.81 17.81 22.16 0.12 630.27 267.04 54176 +1931 204 27.67 21.67 26.02 0 774.3 337.81 54047 +1931 205 26.06 20.06 24.41 0 711.17 345.18 53915 +1931 206 23.36 17.36 21.71 0.43 615.06 267.25 53780 +1931 207 20.31 14.31 18.66 0.38 519.96 275.21 53643 +1931 208 24.65 18.65 23 0.49 659.51 262.27 53502 +1931 209 23.97 17.97 22.32 0.17 635.75 263.95 53359 +1931 210 24.02 18.02 22.37 0.43 637.47 263.34 53213 +1931 211 24.12 18.12 22.47 0 640.93 349.95 53064 +1931 212 24.81 18.81 23.16 0 665.2 346.26 52913 +1931 213 22.47 16.47 20.82 0.46 585.9 266.24 52760 +1931 214 25.46 19.46 23.81 0.4 688.78 256.47 52604 +1931 215 26.98 20.98 25.33 0.39 746.69 250.7 52445 +1931 216 30.04 24.04 28.39 0 875.82 317.27 52285 +1931 217 30.32 24.32 28.67 0.06 888.52 236.14 52122 +1931 218 26 20 24.35 1.03 708.9 252.21 51958 +1931 219 26.23 20.23 24.58 1.65 717.62 250.67 51791 +1931 220 26.84 20.84 25.19 0.06 741.19 247.87 51622 +1931 221 25.82 19.82 24.17 0.46 702.14 250.69 51451 +1931 222 21.37 15.37 19.72 0.26 551.49 263.19 51279 +1931 223 24.64 18.64 22.99 0.02 659.15 252.95 51105 +1931 224 22.99 16.99 21.34 0.76 602.79 257.13 50929 +1931 225 19.21 13.21 17.56 0 488.88 354.68 50751 +1931 226 21.32 15.32 19.67 0 549.96 346.66 50572 +1931 227 24.19 18.19 22.54 0.63 643.35 251 50392 +1931 228 20.88 14.88 19.23 0.3 536.72 259.26 50210 +1931 229 19.57 13.57 17.92 1.42 498.88 261.51 50026 +1931 230 17.95 11.95 16.3 0.14 455.24 264.14 49842 +1931 231 13.64 7.64 11.99 0.27 354.63 271.06 49656 +1931 232 18.74 12.74 17.09 0 476.09 347.08 49469 +1931 233 17.06 11.06 15.41 0.4 432.68 262.75 49280 +1931 234 17.16 11.16 15.51 0.36 435.17 261.47 49091 +1931 235 19.34 13.34 17.69 0.07 492.47 255.72 48900 +1931 236 20.7 14.7 19.05 0.16 531.38 251.47 48709 +1931 237 20.98 14.98 19.33 0.13 539.7 249.56 48516 +1931 238 17.6 11.6 15.95 0.09 446.25 255.86 48323 +1931 239 16.36 10.36 14.71 0 415.61 342.82 48128 +1931 240 19.07 13.07 17.42 0 485.04 333.75 47933 +1931 241 20.2 14.2 18.55 0 516.78 328.65 47737 +1931 242 22.59 16.59 20.94 0 589.76 319.05 47541 +1931 243 20.81 14.81 19.16 0.15 534.64 242.38 47343 +1931 244 15.25 9.25 13.6 0 389.73 336.42 47145 +1931 245 15.36 9.36 13.71 0 392.23 334.29 46947 +1931 246 15.87 9.87 14.22 0 404.01 331.11 46747 +1931 247 19 13 17.35 0 483.13 321.18 46547 +1931 248 25.25 19.25 23.6 0 681.09 298.28 46347 +1931 249 23.02 17.02 21.37 0 603.78 304.62 46146 +1931 250 22.93 16.93 21.28 0.21 600.82 227.29 45945 +1931 251 17.82 11.82 16.17 0.93 451.88 237.24 45743 +1931 252 17.78 11.78 16.13 1.4 450.85 235.7 45541 +1931 253 13.23 7.23 11.58 0.04 346.14 241.73 45339 +1931 254 13.86 7.86 12.21 0.19 359.26 239.16 45136 +1931 255 13.72 7.72 12.07 0 356.31 316.86 44933 +1931 256 13.44 7.44 11.79 0 350.47 315.1 44730 +1931 257 10.67 4.67 9.02 0 296.95 317.81 44527 +1931 258 12.6 6.6 10.95 0.83 333.43 234.06 44323 +1931 259 12.59 6.59 10.94 0.87 333.23 232.21 44119 +1931 260 12.25 6.25 10.6 0 326.54 307.79 43915 +1931 261 10.35 4.35 8.7 0.01 291.24 231.32 43711 +1931 262 10.07 4.07 8.42 0 286.32 306.42 43507 +1931 263 15.68 9.68 14.03 0.15 399.59 220.33 43303 +1931 264 15.55 9.55 13.9 1.34 396.58 218.6 43099 +1931 265 13.4 7.4 11.75 0.14 349.64 219.96 42894 +1931 266 17 11 15.35 0 431.19 283.48 42690 +1931 267 15.52 9.52 13.87 0 395.89 283.99 42486 +1931 268 14.69 8.69 13.04 0.01 377.2 212.31 42282 +1931 269 13.25 7.25 11.6 0 346.55 283.2 42078 +1931 270 10.24 4.24 8.59 0.34 289.3 214.02 41875 +1931 271 14.87 8.87 13.22 0.7 381.19 206.2 41671 +1931 272 13.66 7.66 12.01 1.65 355.05 205.82 41468 +1931 273 16.45 10.45 14.8 0.05 417.77 199.91 41265 +1931 274 15.65 9.65 14 0 398.89 265.51 41062 +1931 275 18.13 12.13 16.48 0 459.92 257.55 40860 +1931 276 16.84 10.84 15.19 0.19 427.25 193.27 40658 +1931 277 17.34 11.34 15.69 0 439.67 254.03 40456 +1931 278 15.07 9.07 13.42 0 385.66 255.69 40255 +1931 279 16.16 10.16 14.51 0 410.84 250.84 40054 +1931 280 12.12 6.12 10.47 0 324.02 255.17 39854 +1931 281 13.31 7.31 11.66 0.05 347.78 187.93 39654 +1931 282 11.94 5.94 10.29 0 320.54 249.94 39455 +1931 283 14.19 8.19 12.54 0 366.3 243.57 39256 +1931 284 13.66 7.66 12.01 0 355.05 241.44 39058 +1931 285 10.86 4.86 9.21 0.06 300.38 182.19 38861 +1931 286 11.42 5.42 9.77 0.14 310.69 179.53 38664 +1931 287 9.74 3.74 8.09 0 280.62 238.61 38468 +1931 288 10.19 4.19 8.54 0 288.42 235.24 38273 +1931 289 7.46 1.46 5.81 0 243.83 235.72 38079 +1931 290 9.1 3.1 7.45 0 269.84 231 37885 +1931 291 8.61 2.61 6.96 0 261.83 228.82 37693 +1931 292 10.38 4.38 8.73 0.77 291.77 168.03 37501 +1931 293 10.27 4.27 8.62 0.01 289.83 166.07 37311 +1931 294 9.66 3.66 8.01 0.93 279.26 164.43 37121 +1931 295 7.76 1.76 6.11 0.48 248.42 163.83 36933 +1931 296 9.61 3.61 7.96 0.06 278.4 160.38 36745 +1931 297 9.87 3.87 8.22 0 282.86 210.8 36560 +1931 298 12.33 6.33 10.68 0.04 328.11 153.88 36375 +1931 299 12.64 6.64 10.99 0 334.22 202 36191 +1931 300 14.39 8.39 12.74 0.01 370.63 147.7 36009 +1931 301 17.6 11.6 15.95 1.57 446.25 142 35829 +1931 302 16.12 10.12 14.47 0 409.89 189.28 35650 +1931 303 14.66 8.66 13.01 0 376.54 188.98 35472 +1931 304 15.65 9.65 14 0 398.89 185.11 35296 +1931 305 12.86 6.86 11.21 0 338.63 186.3 35122 +1931 306 13.04 7.04 11.39 0 342.26 183.86 34950 +1931 307 9.22 3.22 7.57 0 271.84 185.69 34779 +1931 308 11.93 5.93 10.28 0 320.35 180.17 34610 +1931 309 6.5 0.5 4.85 0 229.62 183.23 34444 +1931 310 5.25 -0.75 3.6 0.03 212.19 136.32 34279 +1931 311 2.38 -3.62 0.73 0.02 176.43 136.13 34116 +1931 312 7.1 1.1 5.45 0 238.41 175.43 33956 +1931 313 6.34 0.34 4.69 0.07 227.32 130.44 33797 +1931 314 5.82 -0.18 4.17 0.15 219.99 129.26 33641 +1931 315 10.01 4.01 8.36 0 285.28 166.2 33488 +1931 316 12.53 6.53 10.88 0 332.04 161.39 33337 +1931 317 11.72 5.72 10.07 0.25 316.34 120.1 33188 +1931 318 8.51 2.51 6.86 0 260.22 160.9 33042 +1931 319 7.43 1.43 5.78 0.58 243.37 120.08 32899 +1931 320 6.09 0.09 4.44 1.16 223.77 119.45 32758 +1931 321 4.18 -1.82 2.53 0.38 198.19 118.84 32620 +1931 322 1.96 -4.04 0.31 0 171.66 157.93 32486 +1931 323 4.77 -1.23 3.12 0.01 205.81 115.96 32354 +1931 324 5.06 -0.94 3.41 0.21 209.65 114.27 32225 +1931 325 3.46 -2.54 1.81 1.03 189.23 113.72 32100 +1931 326 3.11 -2.89 1.46 0.02 184.99 112.77 31977 +1931 327 4.18 -1.82 2.53 0.15 198.19 110.9 31858 +1931 328 7.71 1.71 6.06 0.35 247.65 107.61 31743 +1931 329 6.52 0.52 4.87 0.12 229.91 107.15 31631 +1931 330 6.33 0.33 4.68 0 227.18 141.55 31522 +1931 331 7.08 1.08 5.43 0 238.11 139.71 31417 +1931 332 6.35 0.35 4.7 0.01 227.47 103.94 31316 +1931 333 8.6 2.6 6.95 0 261.67 135.87 31218 +1931 334 8.55 2.55 6.9 0 260.86 134.82 31125 +1931 335 4.55 -1.45 2.9 0 202.94 136.37 31035 +1931 336 4.74 -1.26 3.09 0 205.42 135.18 30949 +1931 337 3.59 -2.41 1.94 0.78 190.82 100.64 30867 +1931 338 -1.88 -7.88 -3.53 0.33 132.96 145.71 30790 +1931 339 0.4 -5.6 -1.25 0 154.91 177.97 30716 +1931 340 1.21 -4.79 -0.44 0 163.42 176.8 30647 +1931 341 3.11 -2.89 1.46 0 184.99 174.62 30582 +1931 342 -0.1 -6.1 -1.75 0 149.84 175.45 30521 +1931 343 -1.78 -7.78 -3.43 0 133.87 175.37 30465 +1931 344 -1.64 -7.64 -3.29 0 135.14 174.25 30413 +1931 345 0.67 -5.33 -0.98 0 157.7 172.85 30366 +1931 346 2.89 -3.11 1.24 0.03 182.38 95.58 30323 +1931 347 7.08 1.08 5.43 0 238.11 124.4 30284 +1931 348 4.36 -1.64 2.71 0.65 200.49 94.29 30251 +1931 349 3.43 -2.57 1.78 0 188.86 125.84 30221 +1931 350 1.64 -4.36 -0.01 0 168.1 126.39 30197 +1931 351 2.64 -3.36 0.99 0 179.44 125.69 30177 +1931 352 6.11 0.11 4.46 0 224.06 123.66 30162 +1931 353 7.37 1.37 5.72 0 242.46 122.78 30151 +1931 354 3.82 -2.18 2.17 0 193.66 124.89 30145 +1931 355 2.44 -3.56 0.79 0 177.12 125.59 30144 +1931 356 0.07 -5.93 -1.58 0 151.55 126.69 30147 +1931 357 3.34 -2.66 1.69 0 187.77 125.22 30156 +1931 358 -0.06 -6.06 -1.71 0 150.24 126.89 30169 +1931 359 -1.62 -7.62 -3.27 0 135.32 127.62 30186 +1931 360 0.23 -5.77 -1.42 0.01 153.17 95.44 30208 +1931 361 3.81 -2.19 2.16 0 193.54 125.88 30235 +1931 362 1.8 -4.2 0.15 0 169.87 127.33 30267 +1931 363 0.47 -5.53 -1.18 0 155.63 128.52 30303 +1931 364 -0.92 -6.92 -2.57 0 141.85 129.5 30343 +1931 365 2.99 -3.01 1.34 0 183.56 128.3 30388 +1932 1 1.11 -4.89 -0.54 0 162.35 130.11 30438 +1932 2 1.39 -4.61 -0.26 0 165.37 130.71 30492 +1932 3 1.54 -4.46 -0.11 0 167 131.59 30551 +1932 4 0.35 -5.65 -1.3 0 154.39 133.05 30614 +1932 5 -0.35 -6.35 -2 0 147.37 134.01 30681 +1932 6 -0.54 -6.54 -2.19 0 145.51 134.98 30752 +1932 7 -1.13 -7.13 -2.78 0 139.86 136.03 30828 +1932 8 1.15 -4.85 -0.5 0 162.78 136.53 30907 +1932 9 0.73 -5.27 -0.92 0 158.33 137.99 30991 +1932 10 5.49 -0.51 3.84 0 215.45 136.71 31079 +1932 11 4.09 -1.91 2.44 0.06 197.05 103.91 31171 +1932 12 3.45 -2.55 1.8 0.01 189.1 104.94 31266 +1932 13 1.93 -4.07 0.28 0 171.33 142.36 31366 +1932 14 3.99 -2.01 2.34 0.17 195.79 107.03 31469 +1932 15 4.65 -1.35 3 0.28 204.24 107.81 31575 +1932 16 2.35 -3.65 0.7 0 176.09 146.37 31686 +1932 17 5.26 -0.74 3.61 0.3 212.33 109.74 31800 +1932 18 2.44 -3.56 0.79 0 177.12 149.91 31917 +1932 19 2.78 -3.22 1.13 0 181.08 151.66 32038 +1932 20 3.3 -2.7 1.65 0 187.28 152.95 32161 +1932 21 5.36 -0.64 3.71 0 213.68 153.65 32289 +1932 22 -1.99 -7.99 -3.64 0 131.98 159.37 32419 +1932 23 -5.11 -11.11 -6.76 0 106.5 162.35 32552 +1932 24 -2.63 -8.63 -4.28 0.39 126.36 164.17 32688 +1932 25 1.59 -4.41 -0.06 0 167.55 204.59 32827 +1932 26 1.7 -4.3 0.05 0.09 168.77 164.75 32969 +1932 27 1.94 -4.06 0.29 0.19 171.44 165.76 33114 +1932 28 4.52 -1.48 2.87 0 202.55 167.81 33261 +1932 29 3.76 -2.24 2.11 0 192.92 170.7 33411 +1932 30 6.98 0.98 5.33 0 236.63 170.58 33564 +1932 31 7.35 1.35 5.7 0 242.16 172.62 33718 +1932 32 4.4 -1.6 2.75 0 201 176.99 33875 +1932 33 7.22 1.22 5.57 0 240.2 177.43 34035 +1932 34 1.66 -4.34 0.01 0 168.32 183.61 34196 +1932 35 0.6 -5.4 -1.05 0 156.97 186.39 34360 +1932 36 0.53 -5.47 -1.12 0 156.25 188.97 34526 +1932 37 0.5 -5.5 -1.15 0.14 155.94 143.57 34694 +1932 38 -3.2 -9.2 -4.85 0.01 121.53 184.94 34863 +1932 39 -3.53 -9.53 -5.18 0 118.81 236.56 35035 +1932 40 -4.79 -10.79 -6.44 0.04 108.9 189.17 35208 +1932 41 -4.79 -10.79 -6.44 0.1 108.9 191.25 35383 +1932 42 -1.96 -7.96 -3.61 0.05 132.25 192.19 35560 +1932 43 0.15 -5.85 -1.5 0 152.36 245.09 35738 +1932 44 1.46 -4.54 -0.19 0.18 166.13 194.17 35918 +1932 45 1.66 -4.34 0.01 0 168.32 248.67 36099 +1932 46 3.82 -2.18 2.17 0.1 193.66 159.83 36282 +1932 47 -0.82 -6.82 -2.47 0 142.8 219.03 36466 +1932 48 -1.46 -7.46 -3.11 0 136.79 222.23 36652 +1932 49 0.36 -5.64 -1.29 0.35 154.5 167.98 36838 +1932 50 -0.48 -6.48 -2.13 0 146.09 227.19 37026 +1932 51 -0.63 -6.63 -2.28 0 144.63 230.29 37215 +1932 52 -1.19 -7.19 -2.84 0 139.3 233.49 37405 +1932 53 -4.36 -10.36 -6.01 0 112.2 238.15 37596 +1932 54 -6.59 -12.59 -8.24 0 95.99 241.94 37788 +1932 55 -9.54 -15.54 -11.19 0 77.7 246.09 37981 +1932 56 -6.39 -12.39 -8.04 0 97.36 247.69 38175 +1932 57 -3.45 -9.45 -5.1 0 119.47 249.27 38370 +1932 58 -2.33 -8.33 -3.98 0 128.97 251.65 38565 +1932 59 -1.5 -7.5 -3.15 0 136.42 253.93 38761 +1932 60 7.3 1.3 5.65 0 241.41 249.58 38958 +1932 61 7.08 1.08 5.43 0.1 238.11 189.56 39156 +1932 62 7.6 1.6 5.95 0 245.96 254.95 39355 +1932 63 8.89 2.89 7.24 0 266.38 256.43 39553 +1932 64 13.35 7.35 11.7 0.27 348.61 189.69 39753 +1932 65 10.43 4.43 8.78 0 292.66 260.15 39953 +1932 66 3.94 -2.06 2.29 0.08 195.16 202.7 40154 +1932 67 0.35 -5.65 -1.3 0.85 154.39 207.11 40355 +1932 68 2.13 -3.87 0.48 0.09 173.58 208.26 40556 +1932 69 -1.49 -7.49 -3.14 0 136.51 283.03 40758 +1932 70 1.05 -4.95 -0.6 0 161.71 284.11 40960 +1932 71 3.37 -2.63 1.72 0.01 188.13 213.82 41163 +1932 72 4.68 -1.32 3.03 0 204.63 286.67 41366 +1932 73 0.36 -5.64 -1.29 0 154.5 293.19 41569 +1932 74 -1.04 -7.04 -2.69 0 140.71 297.02 41772 +1932 75 0.46 -5.54 -1.19 0.04 155.52 224.02 41976 +1932 76 0.61 -5.39 -1.04 0 157.08 301.27 42179 +1932 77 6.42 0.42 4.77 0.01 228.47 223.69 42383 +1932 78 5.81 -0.19 4.16 0.5 219.85 226.23 42587 +1932 79 5.56 -0.44 3.91 0 216.41 304.67 42791 +1932 80 6.01 0.01 4.36 0.18 222.65 230.04 42996 +1932 81 6.34 0.34 4.69 1.04 227.32 231.7 43200 +1932 82 1.34 -4.66 -0.31 0.05 164.82 237.55 43404 +1932 83 0.97 -5.03 -0.68 0.22 160.86 239.7 43608 +1932 84 1.42 -4.58 -0.23 0.07 165.69 241.35 43812 +1932 85 2.54 -3.46 0.89 0 178.28 323.32 44016 +1932 86 -0.31 -6.31 -1.96 0 147.76 328.27 44220 +1932 87 -3.09 -9.09 -4.74 0 122.45 332.89 44424 +1932 88 -4.64 -10.64 -6.29 0.39 110.04 282.63 44627 +1932 89 -5.77 -11.77 -7.42 0 101.7 369.57 44831 +1932 90 -2.52 -8.52 -4.17 0.29 127.31 285.55 45034 +1932 91 5.05 -0.95 3.4 0.02 209.51 281.5 45237 +1932 92 6.54 0.54 4.89 0 230.2 365 45439 +1932 93 8.86 2.86 7.21 0 265.89 334.54 45642 +1932 94 9.8 3.8 8.15 0.11 281.65 251.44 45843 +1932 95 12 6 10.35 0 321.7 333.6 46045 +1932 96 14.92 8.92 13.27 0 382.3 329.79 46246 +1932 97 17.63 11.63 15.98 0 447.01 325.28 46446 +1932 98 17.9 11.9 16.25 0 453.94 326.47 46647 +1932 99 17.43 11.43 15.78 0.36 441.94 247.24 46846 +1932 100 14.39 8.39 12.74 0.1 370.63 254.1 47045 +1932 101 15.82 9.82 14.17 0.03 402.84 253.08 47243 +1932 102 12.78 6.78 11.13 0.03 337.02 259.47 47441 +1932 103 11.26 5.26 9.61 0.1 307.72 263.03 47638 +1932 104 7.92 1.92 6.27 0.83 250.9 268.54 47834 +1932 105 8.35 2.35 6.7 0.8 257.66 269.42 48030 +1932 106 12.45 6.45 10.8 0 330.46 353.7 48225 +1932 107 13.93 7.93 12.28 0 360.75 352.29 48419 +1932 108 12.86 6.86 11.21 0 338.63 356.29 48612 +1932 109 12.77 6.77 11.12 0 336.82 358.08 48804 +1932 110 11.88 5.88 10.23 0 319.39 361.27 48995 +1932 111 14.68 8.68 13.03 0 376.98 356.87 49185 +1932 112 13.94 7.94 12.29 0 360.96 360.06 49374 +1932 113 10.29 4.29 8.64 0 290.18 368.67 49561 +1932 114 12.91 6.91 11.26 0 339.63 365.11 49748 +1932 115 13.73 7.73 12.08 0 356.52 364.77 49933 +1932 116 17.61 11.61 15.96 0 446.5 356.32 50117 +1932 117 16.87 10.87 15.22 0.49 427.99 269.72 50300 +1932 118 10.77 4.77 9.12 0 298.75 374.65 50481 +1932 119 9.39 3.39 7.74 0 274.68 378.32 50661 +1932 120 8.72 2.72 7.07 0 263.61 380.64 50840 +1932 121 13.99 7.99 12.34 0.01 362.02 278.64 51016 +1932 122 13.95 7.95 12.3 0 361.17 372.81 51191 +1932 123 10.77 4.77 9.12 1.21 298.75 285.34 51365 +1932 124 9.7 3.7 8.05 0.12 279.94 287.62 51536 +1932 125 10.61 4.61 8.96 0 295.87 382.85 51706 +1932 126 13.2 7.2 11.55 0.45 345.53 283.95 51874 +1932 127 18.33 12.33 16.68 0.11 465.17 274.73 52039 +1932 128 21.24 15.24 19.59 0 547.53 357.83 52203 +1932 129 18.61 12.61 16.96 0.03 472.61 275.45 52365 +1932 130 19.23 13.23 17.58 0.38 489.43 274.6 52524 +1932 131 20.42 14.42 18.77 0.03 523.16 272.26 52681 +1932 132 19.22 13.22 17.57 0 489.16 367.75 52836 +1932 133 16.67 10.67 15.02 0.4 423.1 281.96 52989 +1932 134 15.47 9.47 13.82 0 394.74 379.83 53138 +1932 135 21.92 15.92 20.27 0.13 568.47 270.41 53286 +1932 136 18.98 12.98 17.33 1.66 482.59 278.4 53430 +1932 137 21.74 15.74 20.09 0 562.86 362.51 53572 +1932 138 19.91 13.91 18.26 1.09 508.47 277.12 53711 +1932 139 21.37 15.37 19.72 0.77 551.49 273.84 53848 +1932 140 23.57 17.57 21.92 0.13 622.12 267.85 53981 +1932 141 22.81 16.81 21.16 0.03 596.9 270.44 54111 +1932 142 19.4 13.4 17.75 0.22 494.14 279.93 54238 +1932 143 18.87 12.87 17.22 0.44 479.6 281.59 54362 +1932 144 19.05 13.05 17.4 0 484.5 375.36 54483 +1932 145 19.68 13.68 18.03 0.78 501.96 280.34 54600 +1932 146 16.84 10.84 15.19 0.2 427.25 287.1 54714 +1932 147 19.51 13.51 17.86 0 497.2 375.18 54824 +1932 148 19.66 13.66 18.01 0 501.4 375.07 54931 +1932 149 19.55 13.55 17.9 0.09 498.32 281.81 55034 +1932 150 19.7 13.7 18.05 0.26 502.53 281.68 55134 +1932 151 16.8 10.8 15.15 0.33 426.27 288.61 55229 +1932 152 18.35 12.35 16.7 0 465.7 380.38 55321 +1932 153 20 14 18.35 0 511.04 375.31 55409 +1932 154 18.03 12.03 16.38 0 457.31 381.91 55492 +1932 155 19.13 13.13 17.48 0 486.69 378.68 55572 +1932 156 20.35 14.35 18.7 0 521.12 374.94 55648 +1932 157 21.77 15.77 20.12 0 563.79 370 55719 +1932 158 23.55 17.55 21.9 0 621.44 363.18 55786 +1932 159 24.11 18.11 22.46 0 640.58 361.07 55849 +1932 160 21.14 15.14 19.49 0 544.51 372.91 55908 +1932 161 18.19 12.19 16.54 0.11 461.49 287.09 55962 +1932 162 14.02 8.02 12.37 0.48 362.66 295.6 56011 +1932 163 16.04 10.04 14.39 0 408 389.22 56056 +1932 164 17.74 11.74 16.09 0 449.83 384.46 56097 +1932 165 23.4 17.4 21.75 0 616.4 364.68 56133 +1932 166 22.69 16.69 21.04 0 593 367.61 56165 +1932 167 23.86 17.86 22.21 0.28 631.98 272.09 56192 +1932 168 18.19 12.19 16.54 0.04 461.49 287.48 56214 +1932 169 21.49 15.49 19.84 0 555.15 372.22 56231 +1932 170 17.57 11.57 15.92 0 445.49 385.18 56244 +1932 171 15.18 9.18 13.53 0 388.14 391.8 56252 +1932 172 16.56 10.56 14.91 0.11 420.43 291.08 56256 +1932 173 20.8 14.8 19.15 0 534.34 374.75 56255 +1932 174 22.39 16.39 20.74 0 583.34 368.77 56249 +1932 175 21.74 15.74 20.09 0 562.86 371.21 56238 +1932 176 19.52 13.52 17.87 0.04 497.48 284.23 56223 +1932 177 18.62 12.62 16.97 0 472.87 381.76 56203 +1932 178 16.38 10.38 14.73 0 416.09 388.36 56179 +1932 179 19.5 13.5 17.85 0.79 496.92 284.14 56150 +1932 180 21.29 15.29 19.64 0 549.05 372.54 56116 +1932 181 17.4 11.4 15.75 0.01 441.18 288.88 56078 +1932 182 18.6 12.6 16.95 0.18 472.34 286.05 56035 +1932 183 21.1 15.1 19.45 1.29 543.31 279.63 55987 +1932 184 20.34 14.34 18.69 0 520.83 375.36 55935 +1932 185 21.69 15.69 20.04 0 561.31 370.44 55879 +1932 186 23.52 17.52 21.87 0 620.43 363.02 55818 +1932 187 25.77 19.77 24.12 0.24 700.27 264.74 55753 +1932 188 23.66 17.66 22.01 0 625.16 362 55684 +1932 189 22.5 16.5 20.85 0.04 586.86 274.86 55611 +1932 190 21.87 15.87 20.22 0 566.91 368.52 55533 +1932 191 25.58 19.58 23.93 0 693.21 352.82 55451 +1932 192 28.78 22.78 27.13 0 820.54 336.48 55366 +1932 193 29.1 23.1 27.45 0 834.29 334.47 55276 +1932 194 24.41 18.41 22.76 0 651.04 357.27 55182 +1932 195 20.26 14.26 18.61 0 518.51 372.95 55085 +1932 196 23.38 17.38 21.73 0 615.73 360.91 54984 +1932 197 26.56 20.56 24.91 0 730.29 346.36 54879 +1932 198 24.48 18.48 22.83 0.94 653.5 266.59 54770 +1932 199 27.42 21.42 25.77 0.58 764.2 256.04 54658 +1932 200 23.07 17.07 21.42 0.83 605.43 270.42 54542 +1932 201 20.12 14.12 18.47 0.06 514.48 278.18 54423 +1932 202 20.86 14.86 19.21 0 536.12 367.8 54301 +1932 203 24.4 18.4 22.75 0.06 650.69 265.18 54176 +1932 204 28.09 22.09 26.44 0 791.53 335.65 54047 +1932 205 26.42 20.42 24.77 0 724.89 343.48 53915 +1932 206 20.28 14.28 18.63 0 519.09 367.71 53780 +1932 207 19.84 13.84 18.19 0 506.48 368.52 53643 +1932 208 25.14 19.14 23.49 0 677.09 347.56 53502 +1932 209 26.68 20.68 25.03 0 734.95 339.84 53359 +1932 210 23.58 17.58 21.93 0 622.45 352.93 53213 +1932 211 23.2 17.2 21.55 0.03 609.73 265.27 53064 +1932 212 23.17 17.17 21.52 0 608.73 353.03 52913 +1932 213 24.7 18.7 23.05 0 661.28 346 52760 +1932 214 24.53 18.53 22.88 0 655.26 346 52604 +1932 215 27.71 21.71 26.06 1.11 775.93 248 52445 +1932 216 28.38 22.38 26.73 0.64 803.62 244.71 52285 +1932 217 22.33 16.33 20.68 0 581.42 352.24 52122 +1932 218 21.14 15.14 19.49 0 544.51 355.72 51958 +1932 219 23.68 17.68 22.03 0 625.84 345.2 51791 +1932 220 23.73 17.73 22.08 0.84 627.54 258.06 51622 +1932 221 25.75 19.75 24.1 0.07 699.53 250.92 51451 +1932 222 20.18 14.18 18.53 0.24 516.2 266.21 51279 +1932 223 22.7 16.7 21.05 0.05 593.32 258.73 51105 +1932 224 22.11 16.11 20.46 0.01 574.44 259.59 50929 +1932 225 22.64 16.64 20.99 0.47 591.38 257.28 50751 +1932 226 24.14 18.14 22.49 0 641.62 336.1 50572 +1932 227 25.84 19.84 24.19 0 702.89 327.68 50392 +1932 228 27.23 21.23 25.58 0 756.6 320.15 50210 +1932 229 24.92 18.92 23.27 0 669.14 329.3 50026 +1932 230 23.86 17.86 22.21 0 631.98 332.38 49842 +1932 231 26.6 20.6 24.95 0 731.84 319.34 49656 +1932 232 23.7 17.7 22.05 0 626.52 330.27 49469 +1932 233 18.84 12.84 17.19 0.01 478.79 259.02 49280 +1932 234 22.53 16.53 20.88 0 587.83 331.89 49091 +1932 235 22.75 16.75 21.1 0 594.94 329.64 48900 +1932 236 21.62 15.62 19.97 0.32 559.15 249.17 48709 +1932 237 23.52 17.52 21.87 0 620.43 323.8 48516 +1932 238 22.79 16.79 21.14 0 596.25 324.88 48323 +1932 239 23.6 17.6 21.95 0 623.13 320.43 48128 +1932 240 25.35 19.35 23.7 0 684.74 311.83 47933 +1932 241 26.56 20.56 24.91 0 730.29 305.05 47737 +1932 242 30.07 24.07 28.42 0 877.17 286.52 47541 +1932 243 28.84 22.84 27.19 0 823.1 291.11 47343 +1932 244 21.78 15.78 20.13 0 564.11 318.23 47145 +1932 245 19.82 13.82 18.17 0.25 505.92 241.95 46947 +1932 246 23.32 17.32 21.67 0 613.72 309.2 46747 +1932 247 21.59 15.59 19.94 0 558.23 313.33 46547 +1932 248 19.58 13.58 17.93 0.01 499.16 238.2 46347 +1932 249 17.91 11.91 16.26 0 454.2 320.15 46146 +1932 250 20.76 14.76 19.11 0 533.15 310.13 45945 +1932 251 25 19 23.35 0.04 672.02 220.1 45743 +1932 252 28.09 22.09 26.44 0 791.53 278.51 45541 +1932 253 31.68 25.68 30.03 0 952.45 258.73 45339 +1932 254 32.01 26.01 30.36 0 968.53 255.08 45136 +1932 255 24.5 18.5 22.85 0 654.2 287.16 44933 +1932 256 26.35 20.35 24.7 0 722.21 277.89 44730 +1932 257 25.17 19.17 23.52 0 678.18 280.49 44527 +1932 258 25.85 19.85 24.2 0.4 703.26 206.77 44323 +1932 259 23.33 17.33 21.68 0.07 614.06 211.9 44119 +1932 260 27.39 21.39 25.74 0.01 763 198.77 43915 +1932 261 25.13 19.13 23.48 1.15 676.72 203.72 43711 +1932 262 25 19 23.35 0.36 672.02 202.41 43507 +1932 263 19.91 13.91 18.26 0.16 508.47 212.68 43303 +1932 264 20.29 14.29 18.64 0.79 519.38 210.02 43099 +1932 265 18.13 12.13 16.48 0 459.92 283.29 42894 +1932 266 20.7 14.7 19.05 0 531.38 274.19 42690 +1932 267 22.17 16.17 20.52 0.17 576.34 200.52 42486 +1932 268 18.98 12.98 17.33 0.29 482.59 205.21 42282 +1932 269 19.14 13.14 17.49 0.01 486.96 203.07 42078 +1932 270 19.83 13.83 18.18 0 506.2 266.44 41875 +1932 271 17.25 11.25 15.6 0 437.41 270.03 41671 +1932 272 15.44 9.44 13.79 0 394.06 271.1 41468 +1932 273 14.36 8.36 12.71 0 369.98 270.63 41265 +1932 274 7.32 1.32 5.67 0 241.71 278.37 41062 +1932 275 5.76 -0.24 4.11 0.21 219.16 207.94 40860 +1932 276 9.35 3.35 7.7 0.26 274.01 202.67 40658 +1932 277 12.16 6.16 10.51 0.4 324.79 197.62 40456 +1932 278 8.94 2.94 7.29 0.24 267.2 198.84 40255 +1932 279 12.97 6.97 11.32 0.43 340.85 192.37 40054 +1932 280 13.8 7.8 12.15 0.25 357.99 189.36 39854 +1932 281 9.47 3.47 7.82 0.43 276.03 192.08 39654 +1932 282 13.83 7.83 12.18 0.53 358.63 185.24 39455 +1932 283 16.54 10.54 14.89 0.65 419.95 179.5 39256 +1932 284 17.98 11.98 16.33 0.29 456.02 175.12 39058 +1932 285 13.95 7.95 12.3 0.31 361.17 178.75 38861 +1932 286 15 9 13.35 0.51 384.09 175.38 38664 +1932 287 15.9 9.9 14.25 0.08 404.71 172.02 38468 +1932 288 10.59 4.59 8.94 0.08 295.51 176.05 38273 +1932 289 11.18 5.18 9.53 0 306.24 231.31 38079 +1932 290 13.18 7.18 11.53 0.68 345.12 169.22 37885 +1932 291 12.2 6.2 10.55 2.19 325.57 168.26 37693 +1932 292 13.31 7.31 11.66 0.45 347.78 165.06 37501 +1932 293 14.2 8.2 12.55 0 366.52 216.03 37311 +1932 294 17.63 11.63 15.98 0.55 447.01 155.53 37121 +1932 295 15.47 9.47 13.82 0.42 394.74 156.29 36933 +1932 296 18.82 12.82 17.17 0.91 478.25 149.9 36745 +1932 297 16.66 10.66 15.01 0.34 422.85 150.9 36560 +1932 298 17.4 11.4 15.75 0 441.18 197.38 36375 +1932 299 15.34 9.34 13.69 0 391.77 198.11 36191 +1932 300 18.33 12.33 16.68 0.25 465.17 142.84 36009 +1932 301 18.62 12.62 16.97 0.47 472.87 140.62 35829 +1932 302 21.12 15.12 19.47 0.91 543.91 135.04 35650 +1932 303 21.14 15.14 19.49 0.22 544.51 133.19 35472 +1932 304 23 17 21.35 0.04 603.12 128.39 35296 +1932 305 16.14 10.14 14.49 0 410.37 181.69 35122 +1932 306 13.98 7.98 12.33 0 361.81 182.62 34950 +1932 307 7.47 1.47 5.82 0.12 243.98 140.51 34779 +1932 308 7.92 1.92 6.27 0.35 250.9 138.25 34610 +1932 309 3.66 -2.34 2.01 0 191.68 185.37 34444 +1932 310 5.17 -0.83 3.52 0 211.12 181.81 34279 +1932 311 3.05 -2.95 1.4 0.49 184.28 135.81 34116 +1932 312 5.89 -0.11 4.24 0 220.97 176.4 33956 +1932 313 6.99 0.99 5.34 0 236.78 173.39 33797 +1932 314 9.87 3.87 8.22 0 282.86 168.85 33641 +1932 315 9.3 3.3 7.65 0 273.17 166.88 33488 +1932 316 6.19 0.19 4.54 0.05 225.19 125.49 33337 +1932 317 7.23 1.23 5.58 0.61 240.35 123.23 33188 +1932 318 7.44 1.44 5.79 0 243.52 161.8 33042 +1932 319 8.39 2.39 6.74 0 258.3 159.32 32899 +1932 320 7.39 1.39 5.74 0 242.76 158.28 32758 +1932 321 4.14 -1.86 2.49 0 197.68 158.48 32620 +1932 322 7.59 1.59 5.94 0 245.81 154.2 32486 +1932 323 3.12 -2.88 1.47 0 185.11 155.63 32354 +1932 324 7.4 1.4 5.75 0.35 242.92 113.01 32225 +1932 325 9.06 3.06 7.41 0.02 269.18 110.72 32100 +1932 326 9.72 3.72 8.07 0.01 280.28 109.22 31977 +1932 327 9.61 3.61 7.96 0 278.4 143.9 31858 +1932 328 9.38 3.38 7.73 0 274.51 142.14 31743 +1932 329 10.2 4.2 8.55 0 288.6 139.96 31631 +1932 330 7.4 1.4 5.75 0 242.92 140.79 31522 +1932 331 5.3 -0.7 3.65 0 212.87 140.92 31417 +1932 332 4.65 -1.35 3 0 204.24 139.68 31316 +1932 333 2.78 -3.22 1.13 0 181.08 139.66 31218 +1932 334 7.58 1.58 5.93 0 245.65 135.55 31125 +1932 335 0.27 -5.73 -1.38 0 153.58 138.59 31035 +1932 336 3.9 -2.1 2.25 0.03 194.66 101.75 30949 +1932 337 4.47 -1.53 2.82 0 201.91 133.68 30867 +1932 338 2.46 -3.54 0.81 0 177.35 133.83 30790 +1932 339 2.78 -3.22 1.13 0.03 181.08 99.66 30716 +1932 340 2.59 -3.41 0.94 0 178.86 132.23 30647 +1932 341 -1.05 -7.05 -2.7 0 140.62 132.95 30582 +1932 342 -1.8 -7.8 -3.45 0 133.69 132.47 30521 +1932 343 1.74 -4.26 0.09 0 169.21 130.13 30465 +1932 344 1.67 -4.33 0.02 0 168.43 129.03 30413 +1932 345 -0.12 -6.12 -1.77 0.12 149.64 140.89 30366 +1932 346 -1.92 -7.92 -3.57 0 132.6 173.45 30323 +1932 347 0.81 -5.19 -0.84 0.03 159.17 139.74 30284 +1932 348 0.23 -5.77 -1.42 0 153.17 171.61 30251 +1932 349 2.09 -3.91 0.44 0 173.13 126.51 30221 +1932 350 3.56 -2.44 1.91 0 190.45 125.43 30197 +1932 351 -0.13 -6.13 -1.78 0 149.54 126.94 30177 +1932 352 3.69 -2.31 2.04 0 192.05 125.05 30162 +1932 353 7.56 1.56 5.91 0 245.35 122.66 30151 +1932 354 7.91 1.91 6.26 0.44 250.74 91.79 30145 +1932 355 9.09 3.09 7.44 0 269.68 121.53 30144 +1932 356 8.73 2.73 7.08 0.33 263.77 91.36 30147 +1932 357 5.08 -0.92 3.43 0 209.91 124.27 30156 +1932 358 2.62 -3.38 0.97 0.02 179.21 94.26 30169 +1932 359 0.36 -5.64 -1.29 0.01 154.5 95.13 30186 +1932 360 1.65 -4.35 0 0 168.21 126.63 30208 +1932 361 2.99 -3.01 1.34 0.26 183.56 94.73 30235 +1932 362 2.29 -3.71 0.64 0 175.4 127.1 30267 +1932 363 0.73 -5.27 -0.92 0.17 158.33 96.31 30303 +1932 364 -0.48 -6.48 -2.13 0 146.09 129.32 30343 +1932 365 9.64 3.64 7.99 0 278.91 124.02 30388 +1933 1 3.66 -2.34 2.01 0 191.68 128.84 30438 +1933 2 0.92 -5.08 -0.73 0 160.33 130.93 30492 +1933 3 -2.65 -8.65 -4.3 0.23 126.19 143.91 30551 +1933 4 -4.03 -10.03 -5.68 0.1 114.79 145.18 30614 +1933 5 -6.12 -12.12 -7.77 0 99.23 180.06 30681 +1933 6 -4.14 -10.14 -5.79 0 113.92 180.26 30752 +1933 7 -4.75 -10.75 -6.4 0 109.21 181.16 30828 +1933 8 -1.85 -7.85 -3.5 0 133.23 181.55 30907 +1933 9 -2.37 -8.37 -4.02 0.44 128.62 149.44 30991 +1933 10 -4.03 -10.03 -5.68 0 114.79 186.04 31079 +1933 11 -0.01 -6.01 -1.66 0 150.74 185.35 31171 +1933 12 1.7 -4.3 0.05 0 168.77 185.21 31266 +1933 13 -2.34 -8.34 -3.99 0.17 128.88 152.94 31366 +1933 14 0.54 -5.46 -1.11 0.33 156.35 152.92 31469 +1933 15 -1.36 -7.36 -3.01 0 137.72 191.2 31575 +1933 16 -1.22 -7.22 -2.87 0 139.02 192.29 31686 +1933 17 -4.8 -10.8 -6.45 0 108.83 195.18 31800 +1933 18 -7.93 -13.93 -9.58 0 87.27 197.88 31917 +1933 19 -3.72 -9.72 -5.37 0 117.27 198.36 32038 +1933 20 -4.11 -10.11 -5.76 0 114.16 199.95 32161 +1933 21 -1.71 -7.71 -3.36 0.01 134.5 161.54 32289 +1933 22 0.9 -5.1 -0.75 0 160.12 201.17 32419 +1933 23 0.49 -5.51 -1.16 0 155.83 202.93 32552 +1933 24 5.62 -0.38 3.97 0 217.23 201.06 32688 +1933 25 6.88 0.88 5.23 0 235.16 200.98 32827 +1933 26 2.81 -3.19 1.16 0 181.43 205.16 32969 +1933 27 -0.3 -6.3 -1.95 0.68 147.86 168.58 33114 +1933 28 -1.55 -7.55 -3.2 0.32 135.96 171.43 33261 +1933 29 1.89 -4.11 0.24 0 170.88 214.44 33411 +1933 30 2.39 -3.61 0.74 0 176.55 215.92 33564 +1933 31 -0.32 -6.32 -1.97 0.02 147.66 175.25 33718 +1933 32 3.58 -2.42 1.93 0.64 190.7 174.52 33875 +1933 33 2.46 -3.54 0.81 0.79 177.35 176.56 34035 +1933 34 2.02 -3.98 0.37 0 172.34 223.84 34196 +1933 35 1.1 -4.9 -0.55 0 162.24 226.23 34360 +1933 36 0.12 -5.88 -1.53 0 152.05 229.11 34526 +1933 37 -0.16 -6.16 -1.81 0 149.25 231.52 34694 +1933 38 -0.08 -6.08 -1.73 0 150.04 234.05 34863 +1933 39 1.11 -4.89 -0.54 0 162.35 235.68 35035 +1933 40 4.53 -1.47 2.88 0 202.68 235.27 35208 +1933 41 3.99 -2.01 2.34 0.06 195.79 187.71 35383 +1933 42 6.28 0.28 4.63 0.22 226.47 150.39 35560 +1933 43 6.34 0.34 4.69 0.03 227.32 152.37 35738 +1933 44 5.24 -0.76 3.59 0 212.06 206.66 35918 +1933 45 6.81 0.81 5.16 0 234.13 207.9 36099 +1933 46 10.73 4.73 9.08 0 298.03 206.43 36282 +1933 47 8.33 2.33 6.68 0.02 257.34 158.91 36466 +1933 48 4.37 -1.63 2.72 0 200.62 218.31 36652 +1933 49 4.49 -1.51 2.84 0 202.16 221 36838 +1933 50 2.41 -3.59 0.76 0 176.78 225.29 37026 +1933 51 4.65 -1.35 3 0 204.24 226.51 37215 +1933 52 3.93 -2.07 2.28 0.31 195.04 172.46 37405 +1933 53 4.33 -1.67 2.68 0 200.11 232.58 37596 +1933 54 4.37 -1.63 2.72 0 200.62 235.32 37788 +1933 55 3.47 -2.53 1.82 0.33 189.35 179.31 37981 +1933 56 3.57 -2.43 1.92 0 190.57 241.7 38175 +1933 57 7.47 1.47 5.82 0 243.98 240.91 38370 +1933 58 3.4 -2.6 1.75 0.64 188.49 185.77 38565 +1933 59 3.64 -2.36 1.99 0 191.43 250.22 38761 +1933 60 7.09 1.09 5.44 0 238.26 249.81 38958 +1933 61 7.58 1.58 5.93 0 245.65 252.19 39156 +1933 62 9.88 3.88 8.23 0 283.03 252.19 39355 +1933 63 9.37 3.37 7.72 0 274.35 255.83 39553 +1933 64 8.38 2.38 6.73 0 258.14 259.93 39753 +1933 65 13.03 7.03 11.38 0 342.06 256.27 39953 +1933 66 11.12 5.12 9.47 0 305.13 261.88 40154 +1933 67 11.76 5.76 10.11 0 317.1 263.78 40355 +1933 68 12.17 6.17 10.52 0 324.99 265.97 40556 +1933 69 6.59 0.59 4.94 0.26 230.92 207.01 40758 +1933 70 10.18 4.18 8.53 0.03 288.25 205.75 40960 +1933 71 7.64 1.64 5.99 0 246.57 280.56 41163 +1933 72 6.51 0.51 4.86 0.03 229.76 213.53 41366 +1933 73 8.64 2.64 6.99 0 262.32 284.78 41569 +1933 74 2.96 -3.04 1.31 0 183.21 293.81 41772 +1933 75 4.89 -1.11 3.24 0 207.39 294.67 41976 +1933 76 5.85 -0.15 4.2 0 220.41 296.29 42179 +1933 77 10.5 4.5 8.85 0 293.9 292.81 42383 +1933 78 12.25 6.25 10.6 0.96 326.54 219.48 42587 +1933 79 10.43 4.43 8.78 0.02 292.66 223.7 42791 +1933 80 7.35 1.35 5.7 0 242.16 305.09 42996 +1933 81 6.32 0.32 4.67 0 227.04 308.95 43200 +1933 82 5.53 -0.47 3.88 0 215.99 312.55 43404 +1933 83 8.35 2.35 6.7 0 257.66 311.52 43608 +1933 84 10.12 4.12 8.47 0.07 287.2 233.6 43812 +1933 85 10.76 4.76 9.11 0.57 298.57 234.7 44016 +1933 86 9.43 3.43 7.78 0.66 275.36 238.06 44220 +1933 87 8.3 2.3 6.65 0.22 256.87 241.19 44424 +1933 88 7.93 1.93 6.28 0.04 251.05 243.35 44627 +1933 89 4.8 -1.2 3.15 0 206.2 330.69 44831 +1933 90 9.94 3.94 8.29 0 284.07 326.15 45034 +1933 91 11.96 5.96 10.31 0.66 320.93 243.73 45237 +1933 92 13.23 7.23 11.58 0.12 346.14 243.61 45439 +1933 93 15.54 9.54 13.89 0 396.35 322.13 45642 +1933 94 11.18 5.18 9.53 0 306.24 332.94 45843 +1933 95 12.74 6.74 11.09 0 336.22 332.21 46045 +1933 96 11.31 5.31 9.66 0 308.64 336.96 46246 +1933 97 11.67 5.67 10.02 0.12 315.4 253.77 46446 +1933 98 9.82 3.82 8.17 0.36 282 257.64 46647 +1933 99 7.94 1.94 6.29 0.08 251.21 261.34 46846 +1933 100 7.78 1.78 6.13 0.33 248.73 262.99 47045 +1933 101 9.35 3.35 7.7 0 274.01 350.21 47243 +1933 102 14.99 8.99 13.34 0 383.87 341.25 47441 +1933 103 13.67 7.67 12.02 0 355.26 345.96 47638 +1933 104 15.62 9.62 13.97 0.36 398.2 257.54 47834 +1933 105 12.77 6.77 11.12 0 336.82 351.42 48030 +1933 106 13.48 7.48 11.83 0 351.3 351.59 48225 +1933 107 14.45 8.45 12.8 0 371.94 351.14 48419 +1933 108 12.36 6.36 10.71 0 328.69 357.3 48612 +1933 109 16.33 10.33 14.68 0.05 414.89 262.47 48804 +1933 110 11.48 5.48 9.83 0.1 311.82 271.53 48995 +1933 111 11.66 5.66 10.01 0 315.21 363.25 49185 +1933 112 8.28 2.28 6.63 0 256.55 370.67 49374 +1933 113 6.45 0.45 4.8 0.04 228.9 281.06 49561 +1933 114 6.42 0.42 4.77 0.61 228.47 282.24 49748 +1933 115 9.31 3.31 7.66 0.7 273.34 280 49933 +1933 116 7.01 1.01 5.36 0 237.08 378.19 50117 +1933 117 8.07 2.07 6.42 0 253.24 377.93 50300 +1933 118 7.7 1.7 6.05 0 247.49 379.84 50481 +1933 119 7.98 1.98 6.33 0 251.83 380.63 50661 +1933 120 10.36 4.36 8.71 0.08 291.42 283.35 50840 +1933 121 12.99 6.99 11.34 0.18 341.25 280.3 51016 +1933 122 16.05 10.05 14.4 0.09 408.24 275.79 51191 +1933 123 15.34 9.34 13.69 0.14 391.77 277.9 51365 +1933 124 15.05 9.05 13.4 0 385.21 372.33 51536 +1933 125 18.55 12.55 16.9 0 471 363.79 51706 +1933 126 17.36 11.36 15.71 1 440.17 276.17 51874 +1933 127 16.03 10.03 14.38 0.21 407.77 279.54 52039 +1933 128 18.22 12.22 16.57 0.3 462.28 275.71 52203 +1933 129 16.49 10.49 14.84 0.03 418.74 280 52365 +1933 130 16.62 10.62 14.97 0 421.88 373.77 52524 +1933 131 14.83 8.83 13.18 0.02 380.3 284.38 52681 +1933 132 15.92 9.92 14.27 0.06 405.18 282.94 52836 +1933 133 12.36 6.36 10.71 1.06 328.69 289.75 52989 +1933 134 16.71 10.71 15.06 0.87 424.07 282.41 53138 +1933 135 15.86 9.86 14.21 1.44 403.78 284.64 53286 +1933 136 19.86 13.86 18.21 0.05 507.05 276.28 53430 +1933 137 17.34 11.34 15.69 0.15 439.67 282.61 53572 +1933 138 17.03 11.03 15.38 0.87 431.94 283.72 53711 +1933 139 18.58 12.58 16.93 0.99 471.8 280.82 53848 +1933 140 15.13 9.13 13.48 0 387.01 384.53 53981 +1933 141 16.88 10.88 15.23 0 428.23 380.32 54111 +1933 142 16.43 10.43 14.78 0.87 417.29 286.55 54238 +1933 143 18.24 12.24 16.59 1.51 462.8 283.05 54362 +1933 144 16.09 10.09 14.44 0.56 409.18 288 54483 +1933 145 13.08 7.08 11.43 1.46 343.08 293.89 54600 +1933 146 14.99 8.99 13.34 0.05 383.87 290.78 54714 +1933 147 14.67 8.67 13.02 0 376.76 388.98 54824 +1933 148 14.95 8.95 13.3 0.14 382.97 291.5 54931 +1933 149 13.98 7.98 12.33 0 361.81 391.36 55034 +1933 150 17.02 11.02 15.37 0 431.69 383.8 55134 +1933 151 16.48 10.48 14.83 0.1 418.5 289.28 55229 +1933 152 17.49 11.49 15.84 0 443.46 382.95 55321 +1933 153 18.52 12.52 16.87 0.63 470.21 285.07 55409 +1933 154 21.26 15.26 19.61 0.07 548.14 278.41 55492 +1933 155 20.35 14.35 18.7 0.17 521.12 280.96 55572 +1933 156 19.02 13.02 17.37 0.13 483.68 284.51 55648 +1933 157 16.11 10.11 14.46 0 409.66 388.08 55719 +1933 158 16.53 10.53 14.88 0 419.7 387.11 55786 +1933 159 13.83 7.83 12.18 0 358.63 394.26 55849 +1933 160 15.31 9.31 13.66 0.04 391.09 293.1 55908 +1933 161 15.15 9.15 13.5 0.17 387.46 293.46 55962 +1933 162 15.45 9.45 13.8 0.2 394.29 292.93 56011 +1933 163 16.89 10.89 15.24 4.51 428.48 290.16 56056 +1933 164 19.45 13.45 17.8 0.62 495.53 284.33 56097 +1933 165 18.19 12.19 16.54 0 461.49 383.2 56133 +1933 166 18.23 12.23 16.58 0.12 462.54 287.37 56165 +1933 167 14.71 8.71 13.06 0.59 377.64 294.63 56192 +1933 168 14.65 8.65 13 0 376.32 393.07 56214 +1933 169 14.67 8.67 13.02 0 376.76 393.03 56231 +1933 170 16.74 10.74 15.09 0.04 424.8 290.67 56244 +1933 171 19.92 13.92 18.27 0.05 508.76 283.36 56252 +1933 172 23.42 17.42 21.77 0 617.07 364.76 56256 +1933 173 24.87 18.87 23.22 0.01 667.35 268.91 56255 +1933 174 22.34 16.34 20.69 0.16 581.74 276.72 56249 +1933 175 24.33 18.33 22.68 0.17 648.23 270.6 56238 +1933 176 20.38 14.38 18.73 0.49 522 282.05 56223 +1933 177 20.26 14.26 18.61 0.1 518.51 282.29 56203 +1933 178 18.6 12.6 16.95 0.3 472.34 286.39 56179 +1933 179 21.08 15.08 19.43 0.5 542.7 280.06 56150 +1933 180 20.56 14.56 18.91 0 527.26 375.14 56116 +1933 181 18.49 12.49 16.84 0 469.41 381.89 56078 +1933 182 21.07 15.07 19.42 0.08 542.4 279.84 56035 +1933 183 21.08 15.08 19.43 0 542.7 372.91 55987 +1933 184 21.13 15.13 19.48 0.31 544.21 279.43 55935 +1933 185 20.98 14.98 19.33 0.3 539.7 279.77 55879 +1933 186 21.9 15.9 20.25 0.1 567.85 277.05 55818 +1933 187 20.67 14.67 19.02 0.28 530.49 280.27 55753 +1933 188 22.71 16.71 21.06 0 593.64 365.84 55684 +1933 189 23.24 17.24 21.59 0.01 611.06 272.66 55611 +1933 190 23.23 17.23 21.58 0 610.73 363.22 55533 +1933 191 23.19 17.19 21.54 0 609.4 363.13 55451 +1933 192 25.99 19.99 24.34 0.23 708.52 262.97 55366 +1933 193 26.91 20.91 25.26 0 743.94 345.94 55276 +1933 194 26.81 20.81 25.16 0.06 740.02 259.67 55182 +1933 195 26.18 20.18 24.53 0.42 715.72 261.75 55085 +1933 196 25.35 19.35 23.7 0 684.74 352.46 54984 +1933 197 25.96 19.96 24.31 0 707.39 349.21 54879 +1933 198 25.11 19.11 23.46 0 676 352.69 54770 +1933 199 23.59 17.59 21.94 0 622.79 358.85 54658 +1933 200 25.99 19.99 24.34 0 708.52 347.95 54542 +1933 201 24.65 18.65 23 0.48 659.51 265.15 54423 +1933 202 22.51 16.51 20.86 0 587.18 361.73 54301 +1933 203 20.28 14.28 18.63 0.11 519.09 276.98 54176 +1933 204 21.83 15.83 20.18 1.05 565.66 272.48 54047 +1933 205 22.53 16.53 20.88 0 587.83 360.15 53915 +1933 206 16.01 10.01 14.36 0 407.3 380.51 53780 +1933 207 21.19 15.19 19.54 0 546.02 363.9 53643 +1933 208 21.33 15.33 19.68 0 550.27 362.75 53502 +1933 209 24.41 18.41 22.76 0 651.04 350.09 53359 +1933 210 22.78 16.78 21.13 0 595.92 356.09 53213 +1933 211 22.89 16.89 21.24 0.56 599.51 266.18 53064 +1933 212 20.34 14.34 18.69 0.69 520.83 272.51 52913 +1933 213 18.32 12.32 16.67 0.05 464.91 276.75 52760 +1933 214 16.25 10.25 14.6 0.16 412.98 280.55 52604 +1933 215 18.69 12.69 17.04 0 474.75 366.44 52445 +1933 216 21.21 15.21 19.56 1.12 546.63 267.88 52285 +1933 217 23.51 17.51 21.86 0.02 620.09 260.77 52122 +1933 218 23.72 17.72 22.07 0.01 627.2 259.54 51958 +1933 219 19.82 13.82 18.17 0.68 505.92 269.33 51791 +1933 220 17.19 11.19 15.54 0.04 435.91 274.52 51622 +1933 221 19.35 13.35 17.7 0.17 492.75 268.99 51451 +1933 222 17.45 11.45 15.8 0.11 442.44 272.41 51279 +1933 223 18.53 12.53 16.88 0.01 470.47 269.21 51105 +1933 224 22.09 16.09 20.44 1.02 573.81 259.64 50929 +1933 225 23.39 17.39 21.74 0 616.06 340.18 50751 +1933 226 22.03 16.03 20.38 0.56 571.92 258.11 50572 +1933 227 24.59 18.59 22.94 0.03 657.38 249.77 50392 +1933 228 24.72 18.72 23.07 0 661.99 331.32 50210 +1933 229 22.26 16.26 20.61 0 579.19 339.65 50026 +1933 230 22.73 16.73 21.08 0.04 594.29 252.52 49842 +1933 231 22.57 16.57 20.92 0.87 589.12 251.88 49656 +1933 232 24.18 18.18 22.53 1.37 643.01 246.29 49469 +1933 233 22.4 16.4 20.75 0.46 583.66 250.31 49280 +1933 234 23.16 17.16 21.51 0.14 608.4 247.18 49091 +1933 235 18.96 12.96 17.31 0.82 482.04 256.56 48900 +1933 236 24.9 18.9 23.25 1.84 668.43 239.97 48709 +1933 237 24.6 18.6 22.95 0.08 657.73 239.7 48516 +1933 238 25.89 19.89 24.24 0.6 704.76 234.49 48323 +1933 239 24.32 18.32 22.67 0.44 647.88 238.24 48128 +1933 240 25.59 19.59 23.94 0.35 693.58 233.13 47933 +1933 241 30.89 24.89 29.24 0.31 914.86 212.73 47737 +1933 242 29.83 23.83 28.18 0.94 866.39 215.84 47541 +1933 243 28.87 22.87 27.22 0.62 824.39 218.22 47343 +1933 244 22.92 16.92 21.27 0.03 600.49 235.73 47145 +1933 245 22.35 16.35 20.7 0.03 582.06 235.88 46947 +1933 246 19.87 13.87 18.22 0.05 507.33 240.38 46747 +1933 247 17.19 11.19 15.54 0 435.91 326.01 46547 +1933 248 17.03 11.03 15.38 0.05 431.94 243.35 46347 +1933 249 18.41 12.41 16.76 0 467.28 318.82 46146 +1933 250 15.74 9.74 14.09 0.07 400.98 242.63 45945 +1933 251 18.32 12.32 16.67 0.49 464.91 236.26 45743 +1933 252 19.27 13.27 17.62 1.16 490.54 232.71 45541 +1933 253 19.1 13.1 17.45 0.26 485.86 231.49 45339 +1933 254 17.17 11.17 15.52 0.44 435.41 233.65 45136 +1933 255 16.98 10.98 15.33 0.52 430.7 232.3 44933 +1933 256 20.83 14.83 19.18 0.69 535.23 222.87 44730 +1933 257 18.09 12.09 16.44 0.04 458.88 226.94 44527 +1933 258 19.58 13.58 17.93 0.35 499.16 222.25 44323 +1933 259 19.21 13.21 17.56 0 488.88 294.94 44119 +1933 260 19.02 13.02 17.37 0 483.68 293.1 43915 +1933 261 20.43 14.43 18.78 0.02 523.45 215.14 43711 +1933 262 20.1 14.1 18.45 0 513.9 285.46 43507 +1933 263 19.81 13.81 18.16 0 505.63 283.85 43303 +1933 264 17.09 11.09 15.44 0 433.42 288.09 43099 +1933 265 11.28 5.28 9.63 0 308.09 296.93 42894 +1933 266 12.59 6.59 10.94 0 333.23 292.21 42690 +1933 267 10.97 4.97 9.32 0 302.38 292.15 42486 +1933 268 15.01 9.01 13.36 0 384.31 282.45 42282 +1933 269 13.9 7.9 12.25 0 360.11 282.03 42078 +1933 270 17.66 11.66 16.01 0.27 447.78 203.78 41875 +1933 271 17.49 11.49 15.84 0 443.46 269.5 41671 +1933 272 21.64 15.64 19.99 0.02 559.77 192.3 41468 +1933 273 22.52 16.52 20.87 0.29 587.51 188.59 41265 +1933 274 19.3 13.3 17.65 0.14 491.36 193.13 41062 +1933 275 17.77 11.77 16.12 0.57 450.6 193.77 40860 +1933 276 13.85 7.85 12.2 0.42 359.05 197.54 40658 +1933 277 14.61 8.61 12.96 0 375.44 259.38 40456 +1933 278 15.06 9.06 13.41 0 385.44 255.71 40255 +1933 279 14.61 8.61 12.96 0.11 375.44 190.29 40054 +1933 280 14.11 8.11 12.46 0.05 364.59 188.97 39854 +1933 281 19.36 13.36 17.71 0.4 493.03 179.1 39654 +1933 282 19.41 13.41 17.76 0.16 494.41 177.03 39455 +1933 283 18.72 12.72 17.07 0.48 475.56 176.14 39256 +1933 284 14.04 8.04 12.39 0.62 363.09 180.61 39058 +1933 285 16.48 10.48 14.83 0.08 418.5 175.42 38861 +1933 286 16.69 10.69 15.04 0 423.59 230.79 38664 +1933 287 18.81 12.81 17.16 0 477.98 223.67 38468 +1933 288 18.89 12.89 17.24 0 480.14 220.81 38273 +1933 289 15.83 9.83 14.18 0.02 403.08 168.13 38079 +1933 290 12.24 6.24 10.59 0.32 326.35 170.24 37885 +1933 291 12.2 6.2 10.55 0.07 325.57 168.26 37693 +1933 292 10.95 4.95 9.3 0 302.02 223.32 37501 +1933 293 12.78 6.78 11.13 0 337.02 218.13 37311 +1933 294 16.38 10.38 14.73 0.29 416.09 157.22 37121 +1933 295 13.34 7.34 11.69 1.09 348.4 158.74 36933 +1933 296 12.27 6.27 10.62 0.24 326.93 157.92 36745 +1933 297 12.56 6.56 10.91 0 332.64 207.46 36560 +1933 298 7.63 1.63 5.98 0.41 246.42 157.91 36375 +1933 299 9.32 3.32 7.67 1.71 273.51 154.49 36191 +1933 300 5.02 -0.98 3.37 1.88 209.11 155.51 36009 +1933 301 6.4 0.4 4.75 0 228.18 203.62 35829 +1933 302 6.78 0.78 5.13 0.29 233.69 150.47 35650 +1933 303 3.71 -2.29 2.06 0.05 192.3 150.37 35472 +1933 304 6.8 0.8 5.15 0 233.98 195.51 35296 +1933 305 4.23 -1.77 2.58 0 198.83 194.82 35122 +1933 306 6.1 0.1 4.45 0 223.91 191.06 34950 +1933 307 3.48 -2.52 1.83 0.06 189.47 142.88 34779 +1933 308 4.45 -1.55 2.8 0.56 201.65 140.38 34610 +1933 309 4.71 -1.29 3.06 0.51 205.02 138.47 34444 +1933 310 6.63 0.63 4.98 0.46 231.5 135.5 34279 +1933 311 8.67 2.67 7.02 0 262.8 176.69 34116 +1933 312 6.43 0.43 4.78 0 228.61 175.98 33956 +1933 313 5.87 -0.13 4.22 0 220.69 174.28 33797 +1933 314 5.49 -0.51 3.84 0 215.45 172.59 33641 +1933 315 6.48 0.48 4.83 0.02 229.33 126.97 33488 +1933 316 5.69 -0.31 4.04 1.9 218.19 125.77 33337 +1933 317 7.73 1.73 6.08 1.45 247.95 122.92 33188 +1933 318 8.95 2.95 7.3 0.29 267.37 120.39 33042 +1933 319 7.1 1.1 5.45 0.02 238.41 120.28 32899 +1933 320 3.85 -2.15 2.2 0 194.04 160.79 32758 +1933 321 3.93 -2.07 2.28 0 195.04 158.62 32620 +1933 322 2.61 -3.39 0.96 0.28 179.09 118.18 32486 +1933 323 7.05 1.05 5.4 0.21 237.67 114.75 32354 +1933 324 8.48 2.48 6.83 0.03 259.74 112.37 32225 +1933 325 7.39 1.39 5.74 0.1 242.76 111.73 32100 +1933 326 8.25 2.25 6.6 0 256.08 146.86 31977 +1933 327 11.39 5.39 9.74 0.01 310.13 106.7 31858 +1933 328 8.66 2.66 7.01 0.05 262.64 107.05 31743 +1933 329 8.66 2.66 7.01 0.39 262.64 105.94 31631 +1933 330 13.94 7.94 12.29 0.94 360.96 101.13 31522 +1933 331 6.86 0.86 5.21 0.14 234.86 104.9 31417 +1933 332 12.01 6.01 10.36 1.11 321.89 100.47 31316 +1933 333 11.17 5.17 9.52 0 306.05 133.7 31218 +1933 334 14.9 8.9 13.25 0.66 381.86 96.61 31125 +1933 335 2.37 -3.63 0.72 0.2 176.32 103.18 31035 +1933 336 0.55 -5.45 -1.1 0.85 156.45 103.03 30949 +1933 337 1.06 -4.94 -0.59 0.67 161.81 101.6 30867 +1933 338 -0.19 -6.19 -1.84 0.11 148.95 144.52 30790 +1933 339 -0.38 -6.38 -2.03 0 147.07 177.67 30716 +1933 340 -0.26 -6.26 -1.91 0 148.25 176.97 30647 +1933 341 -0.53 -6.53 -2.18 0 145.6 176.25 30582 +1933 342 -2.47 -8.47 -4.12 0.02 127.74 143.19 30521 +1933 343 -1.37 -7.37 -3.02 0 137.62 175.21 30465 +1933 344 -0.13 -6.13 -1.78 0 149.54 173.64 30413 +1933 345 1.7 -4.3 0.05 0 168.77 172.24 30366 +1933 346 -1.61 -7.61 -3.26 0.84 135.41 143.44 30323 +1933 347 -5.02 -11.02 -6.67 0.15 107.17 144.38 30284 +1933 348 -5.17 -11.17 -6.82 0 106.06 176.61 30251 +1933 349 -7.3 -13.3 -8.95 0 91.28 176.84 30221 +1933 350 -3.76 -9.76 -5.41 0 116.95 175.53 30197 +1933 351 -3.32 -9.32 -4.97 0 120.54 175.2 30177 +1933 352 -3 -9 -4.65 0 123.21 175.02 30162 +1933 353 -3.05 -9.05 -4.7 0.03 122.79 143.11 30151 +1933 354 -0.59 -6.59 -2.24 0.19 145.02 143.03 30145 +1933 355 -0.5 -6.5 -2.15 0.02 145.9 143.06 30144 +1933 356 -3.88 -9.88 -5.53 0 115.98 176.01 30147 +1933 357 -3.44 -9.44 -5.09 0 119.55 175.92 30156 +1933 358 -1.88 -7.88 -3.53 0.09 132.96 143.84 30169 +1933 359 -0.98 -6.98 -2.63 0.02 141.28 143.71 30186 +1933 360 -0.27 -6.27 -1.92 0.15 148.15 144.22 30208 +1933 361 -5.22 -11.22 -6.87 0.17 105.69 146.25 30235 +1933 362 -2.01 -8.01 -3.66 1.8 131.8 151.46 30267 +1933 363 -2.95 -8.95 -4.6 0.38 123.63 153.29 30303 +1933 364 -2.7 -8.7 -4.35 0 125.76 185.99 30343 +1933 365 0.06 -5.94 -1.59 0.03 151.45 153 30388 +1934 1 3.96 -2.04 2.31 0 195.41 183.81 30438 +1934 2 4.9 -1.1 3.25 0 207.52 183.26 30492 +1934 3 1.83 -4.17 0.18 0.1 170.21 152.63 30551 +1934 4 1.64 -4.36 -0.01 0 168.1 186.17 30614 +1934 5 0.5 -5.5 -1.15 0.35 155.94 153.76 30681 +1934 6 1.84 -4.16 0.19 0 170.32 187.07 30752 +1934 7 4.38 -1.62 2.73 0.03 200.75 152.47 30828 +1934 8 3.24 -2.76 1.59 0.98 186.56 153.51 30907 +1934 9 -3.59 -9.59 -5.24 0.45 118.32 157.94 30991 +1934 10 -2.44 -8.44 -4.09 0 128.01 193.63 31079 +1934 11 -1.19 -7.19 -2.84 0 139.3 193.99 31171 +1934 12 -3.27 -9.27 -4.92 0 120.95 195.65 31266 +1934 13 -0.35 -6.35 -2 0.04 147.37 160.22 31366 +1934 14 -5.02 -11.02 -6.67 0.61 107.17 164.35 31469 +1934 15 -2.32 -8.32 -3.97 0 129.05 201.36 31575 +1934 16 1.27 -4.73 -0.38 0 164.07 200.72 31686 +1934 17 0.55 -5.45 -1.1 0 156.45 202.51 31800 +1934 18 -1.67 -7.67 -3.32 0 134.87 205.21 31917 +1934 19 -0.38 -6.38 -2.03 0 147.07 206.4 32038 +1934 20 4.57 -1.43 2.92 0 203.2 204.53 32161 +1934 21 5.81 -0.19 4.16 0 219.85 204.76 32289 +1934 22 4.02 -1.98 2.37 0 196.17 206.99 32419 +1934 23 2.3 -3.7 0.65 0 175.51 209.29 32552 +1934 24 -0.59 -6.59 -2.24 0 145.02 212.66 32688 +1934 25 -1.63 -7.63 -3.28 0 135.23 214.83 32827 +1934 26 1.06 -4.94 -0.59 0 161.81 215.12 32969 +1934 27 3.7 -2.3 2.05 0.01 192.17 173.41 33114 +1934 28 4.64 -1.36 2.99 0 204.11 215.75 33261 +1934 29 4.33 -1.67 2.68 0 200.11 217.6 33411 +1934 30 2.41 -3.59 0.76 0 176.78 220.57 33564 +1934 31 5.45 -0.55 3.8 0.18 214.9 176.51 33718 +1934 32 6.88 0.88 5.23 0 235.16 219.99 33875 +1934 33 6.57 0.57 4.92 0 230.63 221.86 34035 +1934 34 5.9 -0.1 4.25 0 221.11 223.69 34196 +1934 35 3.73 -2.27 2.08 0.01 192.55 180.68 34360 +1934 36 4.06 -1.94 2.41 0 196.67 228.4 34526 +1934 37 6.66 0.66 5.01 0 231.94 227.82 34694 +1934 38 4.63 -1.37 2.98 0.13 203.98 183.57 34863 +1934 39 1.23 -4.77 -0.42 0 163.64 236.02 35035 +1934 40 -0.68 -6.68 -2.33 0.31 144.15 190.37 35208 +1934 41 3.6 -2.4 1.95 0 190.94 239.75 35383 +1934 42 6.73 0.73 5.08 0 232.96 238.83 35560 +1934 43 2.93 -3.07 1.28 0 182.85 244.03 35738 +1934 44 7.19 1.19 5.54 0 239.76 242.12 35918 +1934 45 8.7 2.7 7.05 0 263.29 206.05 36099 +1934 46 3.72 -2.28 2.07 0 192.42 213.18 36282 +1934 47 2.38 -3.62 0.73 0.3 176.43 162.75 36466 +1934 48 7.76 1.76 6.11 0 248.42 215.24 36652 +1934 49 8.99 2.99 7.34 0 268.03 216.7 36838 +1934 50 5.92 -0.08 4.27 0.03 221.39 166.82 37026 +1934 51 1.51 -4.49 -0.14 0.17 166.68 171.69 37215 +1934 52 2.4 -3.6 0.75 0.07 176.66 173.35 37405 +1934 53 0.49 -5.51 -1.16 0 155.83 235.45 37596 +1934 54 -0.68 -6.68 -2.33 0 144.15 238.98 37788 +1934 55 3.72 -2.28 2.07 0 192.42 238.87 37981 +1934 56 0.23 -5.77 -1.42 0 153.17 244.18 38175 +1934 57 2.09 -3.91 0.44 0 173.13 245.78 38370 +1934 58 2.47 -3.53 0.82 0 177.47 248.45 38565 +1934 59 6.31 0.31 4.66 0.07 226.89 185.8 38761 +1934 60 11 5 9.35 0 302.93 245.05 38958 +1934 61 10.39 4.39 8.74 0 291.95 248.76 39156 +1934 62 7.12 1.12 5.47 0 238.71 255.49 39355 +1934 63 4.07 -1.93 2.42 0.06 196.8 196.16 39553 +1934 64 4.87 -1.13 3.22 0.01 207.13 197.79 39753 +1934 65 4.17 -1.83 2.52 0 198.07 267.29 39953 +1934 66 4.23 -1.77 2.58 0 198.83 269.99 40154 +1934 67 5.98 -0.02 4.33 0.15 222.23 203.38 40355 +1934 68 9.12 3.12 7.47 0 270.17 270.34 40556 +1934 69 10.58 4.58 8.93 0 295.33 270.94 40758 +1934 70 7.71 1.71 6.06 0.03 247.65 208.17 40960 +1934 71 8 2 6.35 0 252.14 280.12 41163 +1934 72 8.03 2.03 6.38 0 252.61 282.9 41366 +1934 73 5.19 -0.81 3.54 0 211.39 288.84 41569 +1934 74 8.9 2.9 7.25 0 266.55 287.17 41772 +1934 75 9.93 3.93 8.28 0 283.89 288.45 41976 +1934 76 9.67 3.67 8.02 0 279.43 291.44 42179 +1934 77 13.44 7.44 11.79 0 350.47 287.93 42383 +1934 78 15.31 9.31 13.66 0.02 391.09 215.2 42587 +1934 79 13.36 7.36 11.71 0.22 348.81 220.02 42791 +1934 80 14.67 8.67 13.02 0.05 376.76 220 42996 +1934 81 13.97 7.97 12.32 0 361.6 297.22 43200 +1934 82 16.08 10.08 14.43 0 408.95 295.48 43404 +1934 83 16.65 10.65 15 0 422.61 296.61 43608 +1934 84 13.06 7.06 11.41 0 342.67 306.48 43812 +1934 85 11.75 5.75 10.1 0 316.91 311.28 44016 +1934 86 12.66 6.66 11.01 0 334.62 312.05 44220 +1934 87 11.09 5.09 9.44 0 304.58 317.3 44424 +1934 88 10.45 4.45 8.8 0 293.01 320.69 44627 +1934 89 15.93 9.93 14.28 0 405.42 312.39 44831 +1934 90 16.98 10.98 15.33 0 430.7 312.24 45034 +1934 91 19.92 13.92 18.27 0 508.76 306.62 45237 +1934 92 20.6 14.6 18.95 0 528.43 306.74 45439 +1934 93 17.1 11.1 15.45 0 433.67 318.44 45642 +1934 94 20.6 14.6 18.95 0 528.43 310.87 45843 +1934 95 20.54 14.54 18.89 0 526.67 313.08 46045 +1934 96 15.34 9.34 13.69 0 391.77 328.85 46246 +1934 97 14.13 8.13 12.48 0 365.02 333.52 46446 +1934 98 10.12 4.12 8.47 0 287.2 343.03 46647 +1934 99 12.99 6.99 11.34 0.12 341.25 254.84 46846 +1934 100 14.98 8.98 13.33 0.49 383.64 253.12 47045 +1934 101 11.79 5.79 10.14 0 317.68 345.97 47243 +1934 102 13.93 7.93 12.28 0 360.75 343.59 47441 +1934 103 11.01 5.01 9.36 0 303.11 351.15 47638 +1934 104 10.54 4.54 8.89 0 294.62 353.82 47834 +1934 105 11.02 5.02 9.37 0 303.3 354.77 48030 +1934 106 12.76 6.76 11.11 0 336.62 353.08 48225 +1934 107 15.46 9.46 13.81 0 394.52 348.8 48419 +1934 108 16.24 10.24 14.59 0 412.74 348.6 48612 +1934 109 19.61 13.61 17.96 0 500 340.81 48804 +1934 110 17.42 11.42 15.77 0 441.69 348.48 48995 +1934 111 16 10 14.35 0 407.06 353.7 49185 +1934 112 18.34 12.34 16.69 0 465.43 348.91 49374 +1934 113 15.82 9.82 14.17 0 402.84 356.97 49561 +1934 114 17.76 11.76 16.11 0 450.34 353.31 49748 +1934 115 15.28 9.28 13.63 0 390.41 361.18 49933 +1934 116 11.94 5.94 10.29 0.36 320.54 277.31 50117 +1934 117 16.91 10.91 15.26 0 428.97 359.52 50300 +1934 118 15.7 9.7 14.05 0 400.05 363.96 50481 +1934 119 17.47 11.47 15.82 0 442.95 360.45 50661 +1934 120 15.79 9.79 14.14 0 402.14 366.07 50840 +1934 121 19.44 13.44 17.79 0.13 495.25 267.66 51016 +1934 122 17.38 11.38 15.73 0.78 440.68 273.11 51191 +1934 123 17.11 11.11 15.46 0.54 433.92 274.43 51365 +1934 124 19.25 13.25 17.6 0 489.98 360.69 51536 +1934 125 18.55 12.55 16.9 0.11 471 272.84 51706 +1934 126 16.25 10.25 14.6 0.25 412.98 278.44 51874 +1934 127 18.06 12.06 16.41 0.05 458.09 275.32 52039 +1934 128 13.87 7.87 12.22 0.06 359.47 284.25 52203 +1934 129 12.5 6.5 10.85 0.02 331.45 287.16 52365 +1934 130 14.95 8.95 13.3 0.01 382.97 283.56 52524 +1934 131 17.49 11.49 15.84 0 443.46 372.14 52681 +1934 132 19.87 13.87 18.22 0 507.33 365.65 52836 +1934 133 22.45 16.45 20.8 0.79 585.26 267.91 52989 +1934 134 22.52 16.52 20.87 0.29 587.51 268.22 53138 +1934 135 25.66 19.66 24.01 0.03 696.18 258.87 53286 +1934 136 28.47 22.47 26.82 0.34 807.4 248.95 53430 +1934 137 25.73 19.73 24.08 0.53 698.78 259.57 53572 +1934 138 21.03 15.03 19.38 0.4 541.2 274.24 53711 +1934 139 19.17 13.17 17.52 1.25 487.78 279.43 53848 +1934 140 21.57 15.57 19.92 0.28 557.61 273.64 53981 +1934 141 19.63 13.63 17.98 0 500.56 371.99 54111 +1934 142 22.97 16.97 21.32 0 602.13 360.43 54238 +1934 143 22.82 16.82 21.17 0.62 597.22 271.16 54362 +1934 144 22.7 16.7 21.05 0 593.32 362.47 54483 +1934 145 23.85 17.85 22.2 0.03 631.63 268.71 54600 +1934 146 20.99 14.99 19.34 0.19 540 277.25 54714 +1934 147 19.53 13.53 17.88 0.08 497.76 281.34 54824 +1934 148 15.06 9.06 13.41 0.02 385.44 291.3 54931 +1934 149 15.36 9.36 13.71 0 392.23 387.95 55034 +1934 150 15.76 9.76 14.11 0 401.44 387.25 55134 +1934 151 14.55 8.55 12.9 0 374.12 390.72 55229 +1934 152 16.04 10.04 14.39 0.05 408 290.26 55321 +1934 153 16.64 10.64 14.99 0.21 422.37 289.21 55409 +1934 154 21.22 15.22 19.57 0.12 546.93 278.52 55492 +1934 155 16.78 10.78 15.13 0.19 425.78 289.3 55572 +1934 156 17.78 11.78 16.13 0.22 450.85 287.38 55648 +1934 157 19.17 13.17 17.52 0 487.78 379.04 55719 +1934 158 20.4 14.4 18.75 0.64 522.58 281.33 55786 +1934 159 18.32 12.32 16.67 0.33 464.91 286.6 55849 +1934 160 22.78 16.78 21.13 0.32 595.92 275.03 55908 +1934 161 24.26 18.26 22.61 0.27 645.79 270.5 55962 +1934 162 20.33 14.33 18.68 0.86 520.54 281.92 56011 +1934 163 18.19 12.19 16.54 0.06 461.49 287.29 56056 +1934 164 18.39 12.39 16.74 0 466.76 382.49 56097 +1934 165 17.83 11.83 16.18 0.01 452.14 288.21 56133 +1934 166 17.64 11.64 15.99 0.4 447.27 288.7 56165 +1934 167 19.35 13.35 17.7 0 492.75 379.56 56192 +1934 168 16.91 10.91 15.26 1.46 428.97 290.3 56214 +1934 169 13.75 7.75 12.1 0.28 356.94 296.44 56231 +1934 170 18.53 12.53 16.88 0.32 470.47 286.7 56244 +1934 171 21.96 15.96 20.31 1.28 569.72 277.89 56252 +1934 172 20.03 14.03 18.38 1.25 511.9 283.08 56256 +1934 173 21.79 15.79 20.14 0 564.42 371.14 56255 +1934 174 20.15 14.15 18.5 0.57 515.34 282.7 56249 +1934 175 23.27 17.27 21.62 0.92 612.06 273.93 56238 +1934 176 24.51 18.51 22.86 0.26 654.55 269.99 56223 +1934 177 25.15 19.15 23.5 0 677.45 357.04 56203 +1934 178 25.99 19.99 24.34 0.03 708.52 264.89 56179 +1934 179 23.87 17.87 22.22 0.37 632.32 271.91 56150 +1934 180 21.56 15.56 19.91 0.29 557.3 278.66 56116 +1934 181 21.34 15.34 19.69 1.06 550.57 279.22 56078 +1934 182 28.24 22.24 26.59 0 797.76 341.49 56035 +1934 183 25.7 19.7 24.05 0.19 697.66 265.47 55987 +1934 184 25.15 19.15 23.5 0.2 677.45 267.25 55935 +1934 185 24.21 18.21 22.56 0.4 644.05 270.28 55879 +1934 186 20.19 14.19 18.54 1 516.49 281.65 55818 +1934 187 21.13 15.13 19.48 0.08 544.21 279.04 55753 +1934 188 26.53 20.53 24.88 0.33 729.13 261.84 55684 +1934 189 21.7 15.7 20.05 0 561.62 369.52 55611 +1934 190 22 16 20.35 0 570.98 368.03 55533 +1934 191 25.55 19.55 23.9 0 692.1 352.96 55451 +1934 192 30.01 24.01 28.36 0.09 874.47 247.16 55366 +1934 193 25.76 19.76 24.11 0.14 699.9 263.58 55276 +1934 194 26.27 20.27 24.62 0.16 719.15 261.63 55182 +1934 195 27.71 21.71 26.06 0 775.93 341.45 55085 +1934 196 25.53 19.53 23.88 0 691.36 351.64 54984 +1934 197 21.81 15.81 20.16 1.3 565.04 274.93 54879 +1934 198 22.02 16.02 20.37 1.36 571.61 274.02 54770 +1934 199 23.91 17.91 22.26 1.74 633.69 268.14 54658 +1934 200 20.24 14.24 18.59 0.77 517.94 278.23 54542 +1934 201 19.32 13.32 17.67 0 491.92 373.54 54423 +1934 202 17.04 11.04 15.39 0 432.18 379.85 54301 +1934 203 21.06 15.06 19.41 0 542.1 366.59 54176 +1934 204 23.06 17.06 21.41 0 605.1 358.59 54047 +1934 205 22.35 16.35 20.7 0.09 582.06 270.63 53915 +1934 206 23.61 17.61 21.96 0 623.47 355.33 53780 +1934 207 24.39 18.39 22.74 0.02 650.34 263.58 53643 +1934 208 20.33 14.33 18.68 0 520.54 366.23 53502 +1934 209 23.97 17.97 22.32 0.12 635.75 263.95 53359 +1934 210 22.73 16.73 21.08 0 594.29 356.29 53213 +1934 211 24.64 18.64 22.99 0 659.15 347.76 53064 +1934 212 22.99 16.99 21.34 0.1 602.79 265.3 52913 +1934 213 21.44 15.44 19.79 0.04 553.62 269.08 52760 +1934 214 22.72 16.72 21.07 0.04 593.97 264.98 52604 +1934 215 25.62 19.62 23.97 0.53 694.69 255.45 52445 +1934 216 19.97 13.97 18.32 0.93 510.18 271.03 52285 +1934 217 17.82 11.82 16.17 0 451.88 367.09 52122 +1934 218 19.87 13.87 18.22 0.85 507.33 270 51958 +1934 219 17.94 11.94 16.29 0 454.98 364.86 51791 +1934 220 17.09 11.09 15.44 0.28 433.42 274.73 51622 +1934 221 16.54 10.54 14.89 0.88 419.95 275.07 51451 +1934 222 16.57 10.57 14.92 1.56 420.67 274.21 51279 +1934 223 18.86 12.86 17.21 0.36 479.33 268.47 51105 +1934 224 23.49 17.49 21.84 0 619.42 340.91 50929 +1934 225 26.31 20.31 24.66 0 720.68 327.86 50751 +1934 226 25.98 19.98 24.33 0.06 708.15 246.2 50572 +1934 227 24.54 18.54 22.89 0 655.61 333.23 50392 +1934 228 25.93 19.93 24.28 0.27 706.27 244.59 50210 +1934 229 21.09 15.09 19.44 1.2 543 257.81 50026 +1934 230 23.24 17.24 21.59 0.73 611.06 251.08 49842 +1934 231 21.66 15.66 20.01 0.76 560.39 254.31 49656 +1934 232 20.9 14.9 19.25 0.14 537.31 255.25 49469 +1934 233 23.28 17.28 21.63 0.07 612.39 247.88 49280 +1934 234 25.02 19.02 23.37 0.3 672.74 241.68 49091 +1934 235 22.87 16.87 21.22 0.05 598.86 246.9 48900 +1934 236 21.42 15.42 19.77 0.08 553.01 249.68 48709 +1934 237 24.35 18.35 22.7 0.48 648.93 240.44 48516 +1934 238 26.05 20.05 24.4 0.09 710.79 233.97 48323 +1934 239 27.27 21.27 25.62 0.02 758.19 228.83 48128 +1934 240 24.52 18.52 22.87 0.14 654.91 236.39 47933 +1934 241 23.39 17.39 21.74 0 616.06 317.85 47737 +1934 242 24.66 18.66 23.01 0 659.86 311.33 47541 +1934 243 24.43 18.43 22.78 0 651.74 310.45 47343 +1934 244 26.06 20.06 24.41 0.01 711.17 226.58 47145 +1934 245 23.77 17.77 22.12 0 628.9 309.44 46947 +1934 246 25.43 19.43 23.78 0 687.68 301.13 46747 +1934 247 21.78 15.78 20.13 0 564.11 312.71 46547 +1934 248 19.13 13.13 17.48 0.07 486.69 239.17 46347 +1934 249 20.13 14.13 18.48 0 514.76 313.95 46146 +1934 250 21.75 15.75 20.1 0.4 563.17 230.26 45945 +1934 251 20.71 14.71 19.06 0 531.67 308.22 45743 +1934 252 22.03 16.03 20.38 0 571.92 301.95 45541 +1934 253 21.35 15.35 19.7 0.59 550.88 226.55 45339 +1934 254 20.18 14.18 18.53 0.29 516.2 227.63 45136 +1934 255 25 19 23.35 0.95 672.02 213.97 44933 +1934 256 24.45 18.45 22.8 0.18 652.44 213.9 44730 +1934 257 18.99 12.99 17.34 0 482.86 300.24 44527 +1934 258 18.42 12.42 16.77 0.12 467.55 224.56 44323 +1934 259 19.22 13.22 17.57 0 489.16 294.92 44119 +1934 260 21.31 15.31 19.66 0 549.66 286.67 43915 +1934 261 25.81 19.81 24.16 0.25 701.77 201.81 43711 +1934 262 24.23 18.23 22.58 0.61 644.75 204.46 43507 +1934 263 24.87 18.87 23.22 0 667.35 268.04 43303 +1934 264 24.06 18.06 22.41 0.01 638.85 201.34 43099 +1934 265 17.83 11.83 16.18 0.69 452.14 213.01 42894 +1934 266 13.86 7.86 12.21 0.15 359.26 217.45 42690 +1934 267 16.08 10.08 14.43 0.55 408.95 212.12 42486 +1934 268 15.79 9.79 14.14 0 402.14 280.87 42282 +1934 269 17.25 11.25 15.6 0 437.41 275.23 42078 +1934 270 13.41 7.41 11.76 0.05 349.85 210.2 41875 +1934 271 13.45 7.45 11.8 0.5 350.68 208.16 41671 +1934 272 10.95 4.95 9.3 0.03 302.02 209.14 41468 +1934 273 12.39 6.39 10.74 0 329.28 274.03 41265 +1934 274 6.9 0.9 5.25 0 235.45 278.86 41062 +1934 275 8.92 2.92 7.27 0.2 266.88 205.16 40860 +1934 276 9.64 3.64 7.99 0 278.91 269.84 40658 +1934 277 13.82 7.82 12.17 0.25 358.42 195.58 40456 +1934 278 11.4 5.4 9.75 0 310.32 261.75 40255 +1934 279 15.19 9.19 13.54 0.03 388.37 189.51 40054 +1934 280 16.46 10.46 14.81 0 418.01 247.64 39854 +1934 281 15.42 9.42 13.77 0.85 393.6 185.2 39654 +1934 282 12.39 6.39 10.74 0.08 329.28 186.95 39455 +1934 283 11.96 5.96 10.31 0.03 320.93 185.31 39256 +1934 284 12.57 6.57 10.92 0 332.83 243.14 39058 +1934 285 14.45 8.45 12.8 0 371.94 237.51 38861 +1934 286 16.02 10.02 14.37 0.53 407.53 174.03 38664 +1934 287 15.13 9.13 13.48 0 387.01 230.72 38468 +1934 288 14.77 8.77 13.12 0.46 378.97 171.43 38273 +1934 289 13.92 7.92 12.27 0.49 360.53 170.51 38079 +1934 290 11.78 5.78 10.13 0.04 317.49 170.72 37885 +1934 291 13.34 7.34 11.69 0.23 348.4 167.03 37693 +1934 292 17.2 11.2 15.55 1.56 436.16 160.22 37501 +1934 293 16.83 10.83 15.18 0.93 427.01 158.74 37311 +1934 294 13.27 7.27 11.62 0.01 346.96 160.92 37121 +1934 295 12.36 6.36 10.71 0.4 328.69 159.76 36933 +1934 296 8.14 2.14 6.49 0.49 254.34 161.57 36745 +1934 297 8.38 2.38 6.73 0.16 258.14 159.32 36560 +1934 298 10.51 4.51 8.86 0.06 294.08 155.58 36375 +1934 299 10.93 4.93 9.28 0 301.65 204.16 36191 +1934 300 10.66 4.66 9.01 0 296.77 201.82 36009 +1934 301 13.23 7.23 11.58 0 346.14 196.08 35829 +1934 302 16.02 10.02 14.37 0.13 407.53 142.08 35650 +1934 303 21.23 15.23 19.58 0 547.23 177.4 35472 +1934 304 18.29 12.29 16.64 0 464.12 180.77 35296 +1934 305 12.69 6.69 11.04 0 335.22 186.52 35122 +1934 306 14.54 8.54 12.89 0 373.9 181.86 34950 +1934 307 13.94 7.94 12.29 0 360.96 180.22 34779 +1934 308 11.74 5.74 10.09 0 316.72 180.39 34610 +1934 309 11.1 5.1 9.45 0.13 304.76 134.12 34444 +1934 310 5.51 -0.49 3.86 0.17 215.72 136.17 34279 +1934 311 3.58 -2.42 1.93 0 190.7 180.73 34116 +1934 312 5.91 -0.09 4.26 0 221.25 176.39 33956 +1934 313 8.95 2.95 7.3 0.03 267.37 128.76 33797 +1934 314 10.01 4.01 8.36 0.46 285.28 126.54 33641 +1934 315 9.94 3.94 8.29 0.41 284.07 124.7 33488 +1934 316 7.35 1.35 5.7 0.25 242.16 124.81 33337 +1934 317 6.46 0.46 4.81 0.7 229.04 123.69 33188 +1934 318 4.36 -1.64 2.71 0.12 200.49 123.05 33042 +1934 319 6.3 0.3 4.65 0 226.75 160.99 32899 +1934 320 11.96 5.96 10.31 0.75 320.93 115.56 32758 +1934 321 10.03 4.03 8.38 0.68 285.63 115.43 32620 +1934 322 9.43 3.43 7.78 0.2 275.36 114.49 32486 +1934 323 7.94 1.94 6.29 0.26 251.21 114.23 32354 +1934 324 9.53 3.53 7.88 0.14 277.05 111.7 32225 +1934 325 6.88 0.88 5.23 0 235.16 149.36 32100 +1934 326 10.61 4.61 8.96 0.04 295.87 108.62 31977 +1934 327 8.08 2.08 6.43 0 253.4 145.16 31858 +1934 328 7.82 1.82 6.17 0.83 249.34 107.55 31743 +1934 329 7.13 1.13 5.48 0 238.86 142.43 31631 +1934 330 6.69 0.69 5.04 0 232.37 141.3 31522 +1934 331 11.51 5.51 9.86 0.01 312.38 102.04 31417 +1934 332 13.65 7.65 12 0 354.84 132.29 31316 +1934 333 10.79 4.79 9.14 0.27 299.11 100.53 31218 +1934 334 12.15 6.15 10.5 0 324.6 131.7 31125 +1934 335 13.5 7.5 11.85 0 351.71 129.21 31035 +1934 336 12.14 6.14 10.49 0 324.4 129.53 30949 +1934 337 8.03 2.03 6.38 0.05 252.61 98.5 30867 +1934 338 10.27 4.27 8.62 0.06 289.83 96.49 30790 +1934 339 6.31 0.31 4.66 0.03 226.89 98.11 30716 +1934 340 6.3 0.3 4.65 0.68 226.75 97.57 30647 +1934 341 3.31 -2.69 1.66 0 187.4 130.94 30582 +1934 342 3.42 -2.58 1.77 0 188.74 130.11 30521 +1934 343 4.94 -1.06 3.29 0 208.05 128.44 30465 +1934 344 2.92 -3.08 1.27 0.33 182.73 96.31 30413 +1934 345 2.81 -3.19 1.16 0.08 181.43 96.03 30366 +1934 346 3.74 -2.26 2.09 0 192.67 127 30323 +1934 347 8.61 2.61 6.96 0.01 261.83 92.5 30284 +1934 348 8.94 2.94 7.29 0.01 267.2 92.06 30251 +1934 349 9.34 3.34 7.69 0.01 273.84 91.55 30221 +1934 350 5.04 -0.96 3.39 0.32 209.38 93.46 30197 +1934 351 4.24 -1.76 2.59 1.85 198.96 93.64 30177 +1934 352 2.24 -3.76 0.59 0.01 174.83 94.34 30162 +1934 353 6.65 0.65 5 0.24 231.79 92.44 30151 +1934 354 12.6 6.6 10.95 0 333.43 118.59 30145 +1934 355 11.1 5.1 9.45 0.17 304.76 89.94 30144 +1934 356 12.51 6.51 10.86 0.04 331.65 89.02 30147 +1934 357 17.14 11.14 15.49 0.04 434.67 85.35 30156 +1934 358 13.92 7.92 12.27 0 360.53 117.47 30169 +1934 359 13.88 7.88 12.23 0 359.69 117.62 30186 +1934 360 12.49 6.49 10.84 0 331.25 119.32 30208 +1934 361 6.93 0.93 5.28 0 235.89 124.02 30235 +1934 362 5.21 -0.79 3.56 0 211.65 125.53 30267 +1934 363 4.76 -1.24 3.11 0.5 205.68 94.78 30303 +1934 364 3.9 -2.1 2.25 0 194.66 127.25 30343 +1934 365 3.41 -2.59 1.76 0 188.62 128.08 30388 +1935 1 -3.85 -9.85 -5.5 0 116.22 132.02 30438 +1935 2 2.93 -3.07 1.28 0 182.85 129.96 30492 +1935 3 2.95 -3.05 1.3 0 183.09 130.89 30551 +1935 4 3.62 -2.38 1.97 0 191.19 131.45 30614 +1935 5 3.01 -2.99 1.36 0.03 183.8 99.32 30681 +1935 6 2.64 -3.36 0.99 0.1 179.44 100.13 30752 +1935 7 2.22 -3.78 0.57 0 174.6 134.52 30828 +1935 8 1.21 -4.79 -0.44 0 163.42 136.51 30907 +1935 9 -1.53 -7.53 -3.18 0 136.15 138.96 30991 +1935 10 -2.34 -8.34 -3.99 0 128.88 140.59 31079 +1935 11 0.28 -5.72 -1.37 0 153.68 140.51 31171 +1935 12 1.47 -4.53 -0.18 0 166.24 140.96 31266 +1935 13 1.6 -4.4 -0.05 0 167.66 142.53 31366 +1935 14 0.28 -5.72 -1.37 0 153.68 144.65 31469 +1935 15 0.61 -5.39 -1.04 0.7 157.08 109.46 31575 +1935 16 -2.79 -8.79 -4.44 0 124.99 148.7 31686 +1935 17 -0.55 -6.55 -2.2 0.32 145.41 154.58 31800 +1935 18 -2.08 -8.08 -3.73 0 131.17 194.36 31917 +1935 19 -0.9 -6.9 -2.55 0 142.04 195.66 32038 +1935 20 -4.04 -10.04 -5.69 0.3 114.71 160.16 32161 +1935 21 -1.58 -7.58 -3.23 0.45 135.69 162.13 32289 +1935 22 -1.65 -7.65 -3.3 0.55 135.05 164.94 32419 +1935 23 -6.42 -12.42 -8.07 0.01 97.15 167.44 32552 +1935 24 -2.2 -8.2 -3.85 0 130.11 208.52 32688 +1935 25 -0.35 -6.35 -2 0.06 147.37 168.47 32827 +1935 26 2.47 -3.53 0.82 0 177.47 209.53 32969 +1935 27 0.96 -5.04 -0.69 0.18 160.75 170.16 33114 +1935 28 1.1 -4.9 -0.55 0 162.24 213.91 33261 +1935 29 -0.48 -6.48 -2.13 0 146.09 216.93 33411 +1935 30 -4.53 -10.53 -6.18 0 110.89 220.75 33564 +1935 31 -0.82 -6.82 -2.47 0 142.8 221.36 33718 +1935 32 8.03 2.03 6.38 0 252.61 216.39 33875 +1935 33 9.93 3.93 8.28 0 283.89 215.81 34035 +1935 34 8.22 2.22 6.57 0 255.6 218.46 34196 +1935 35 7.35 1.35 5.7 0.22 242.16 174.89 34360 +1935 36 7.83 1.83 6.18 0.47 249.5 137.77 34526 +1935 37 6.02 0.02 4.37 0 222.79 187.66 34694 +1935 38 1.72 -4.28 0.07 0 168.99 193.47 34863 +1935 39 6.42 0.42 4.77 0.46 228.47 144.49 35035 +1935 40 3.78 -2.22 2.13 1.96 193.17 148 35208 +1935 41 4.32 -1.68 2.67 0.19 199.98 149.67 35383 +1935 42 2.27 -3.73 0.62 0 175.17 203.58 35560 +1935 43 3.15 -2.85 1.5 0 185.47 205.69 35738 +1935 44 4.66 -1.34 3.01 0 204.37 207.13 35918 +1935 45 -1.38 -7.38 -3.03 0.01 137.53 196.91 36099 +1935 46 2.56 -3.44 0.91 0.14 178.51 160.52 36282 +1935 47 4.3 -1.7 2.65 0 199.72 215.56 36466 +1935 48 7.29 1.29 5.64 0.01 241.26 161.78 36652 +1935 49 7.24 1.24 5.59 0 240.5 218.52 36838 +1935 50 8.34 2.34 6.69 0 257.5 220.04 37026 +1935 51 2.38 -3.62 0.73 0 176.43 228.3 37215 +1935 52 3.25 -2.75 1.6 0.01 186.68 172.87 37405 +1935 53 2.19 -3.81 0.54 0 174.26 234.27 37596 +1935 54 1.79 -4.21 0.14 0 169.76 237.34 37788 +1935 55 6.19 0.19 4.54 0.04 225.19 177.49 37981 +1935 56 2.66 -3.34 1.01 0 179.67 242.43 38175 +1935 57 2.92 -3.08 1.27 0 182.73 245.13 38370 +1935 58 1.25 -4.75 -0.4 0.23 163.85 187.02 38565 +1935 59 0.34 -5.66 -1.31 0.01 154.29 189.56 38761 +1935 60 2.03 -3.97 0.38 0 172.45 254.44 38958 +1935 61 4.53 -1.47 2.88 0 202.68 255.29 39156 +1935 62 2.34 -3.66 0.69 0.25 175.97 194.99 39355 +1935 63 7.41 1.41 5.76 0.7 243.07 193.63 39553 +1935 64 5.42 -0.58 3.77 0.35 214.49 197.39 39753 +1935 65 4.3 -1.7 2.65 0.01 199.72 200.38 39953 +1935 66 7.31 1.31 5.66 0 241.56 266.8 40154 +1935 67 8.57 2.57 6.92 0 261.19 268.19 40355 +1935 68 9.14 3.14 7.49 0 270.51 270.32 40556 +1935 69 9.98 3.98 8.33 0 284.76 271.79 40758 +1935 70 9.62 3.62 7.97 0.14 278.57 206.33 40960 +1935 71 10.27 4.27 8.62 0 289.83 277.09 41163 +1935 72 10.53 4.53 8.88 0 294.44 279.51 41366 +1935 73 11.86 5.86 10.21 0 319.01 280.1 41569 +1935 74 10.3 4.3 8.65 0.35 290.36 213.9 41772 +1935 75 6.55 0.55 4.9 0 230.34 292.84 41976 +1935 76 6 0 4.35 0 222.51 296.12 42179 +1935 77 7.92 1.92 6.27 0.15 250.9 222.31 42383 +1935 78 11.13 5.13 9.48 0 305.31 294.47 42587 +1935 79 7.62 1.62 5.97 0.35 246.26 226.65 42791 +1935 80 5.21 -0.79 3.56 0.01 211.65 230.72 42996 +1935 81 2.63 -3.37 0.98 0 179.33 312.87 43200 +1935 82 2.06 -3.94 0.41 0 172.79 316.1 43404 +1935 83 6.26 0.26 4.61 0 226.18 314.21 43608 +1935 84 6.51 0.51 4.86 0 229.76 316.46 43812 +1935 85 5.09 -0.91 3.44 0 210.05 320.66 44016 +1935 86 2.81 -3.19 1.16 0 181.43 325.51 44220 +1935 87 5.31 -0.69 3.66 0 213 325.41 44424 +1935 88 3.79 -2.21 2.14 0 193.29 329.48 44627 +1935 89 6.15 0.15 4.5 0 224.62 329.09 44831 +1935 90 5.52 -0.48 3.87 1.12 215.86 249.19 45034 +1935 91 10.01 4.01 8.36 0.09 285.28 246.22 45237 +1935 92 13.22 7.22 11.57 0 345.94 324.83 45439 +1935 93 12.72 6.72 11.07 0 335.82 327.99 45642 +1935 94 14.17 8.17 12.52 0.08 365.87 245.41 45843 +1935 95 11.87 5.87 10.22 0.22 319.2 250.38 46045 +1935 96 8.13 2.13 6.48 0.64 254.18 256.56 46246 +1935 97 12.34 6.34 10.69 0.15 328.3 252.83 46446 +1935 98 11.59 5.59 9.94 0 313.89 340.46 46647 +1935 99 13.84 7.84 12.19 0.55 358.84 253.54 46846 +1935 100 13.57 7.57 11.92 0.65 353.17 255.41 47045 +1935 101 12.45 6.45 10.8 0.54 330.46 258.54 47243 +1935 102 8.73 2.73 7.08 0.09 263.77 264.83 47441 +1935 103 6.39 0.39 4.74 0.24 228.04 268.78 47638 +1935 104 10.16 4.16 8.51 0 287.9 354.48 47834 +1935 105 9.37 3.37 7.72 0.08 274.35 268.21 48030 +1935 106 11.34 5.34 9.69 0.09 309.2 266.87 48225 +1935 107 8.85 2.85 7.2 0.42 265.73 271.36 48419 +1935 108 10.91 4.91 9.26 0.02 301.29 270.04 48612 +1935 109 12.18 6.18 10.53 0 325.18 359.26 48804 +1935 110 15.47 9.47 13.82 0 394.74 353.47 48995 +1935 111 14.9 8.9 13.25 0 381.86 356.36 49185 +1935 112 18.07 12.07 16.42 0 458.35 349.68 49374 +1935 113 16.83 10.83 15.18 0 427.01 354.38 49561 +1935 114 18.03 12.03 16.38 0 457.31 352.55 49748 +1935 115 21.23 15.23 19.58 1.48 547.23 257.96 49933 +1935 116 18.25 12.25 16.6 0.44 463.06 265.88 50117 +1935 117 10.85 4.85 9.2 0.07 300.2 279.88 50300 +1935 118 11.61 5.61 9.96 0 314.26 373.04 50481 +1935 119 12.78 6.78 11.13 0.08 337.02 278.9 50661 +1935 120 13.69 7.69 12.04 0 355.68 371.07 50840 +1935 121 17.47 11.47 15.82 0 442.95 362.71 51016 +1935 122 17.5 11.5 15.85 0.29 443.71 272.86 51191 +1935 123 15.67 9.67 14.02 0 399.35 369.71 51365 +1935 124 16.94 10.94 15.29 0.21 429.71 275.58 51536 +1935 125 16.01 10.01 14.36 0.54 407.3 278.17 51706 +1935 126 15 9 13.35 0.15 384.09 280.82 51874 +1935 127 19.43 13.43 17.78 0.33 494.97 272.19 52039 +1935 128 18.08 12.08 16.43 2.82 458.62 276.02 52203 +1935 129 11.87 5.87 10.22 0.03 319.2 288.14 52365 +1935 130 14.02 8.02 12.37 0.11 362.66 285.23 52524 +1935 131 13.99 7.99 12.34 0.01 362.02 285.88 52681 +1935 132 15.42 9.42 13.77 0.11 393.6 283.9 52836 +1935 133 16.83 10.83 15.18 0.01 427.01 281.63 52989 +1935 134 14.75 8.75 13.1 0.36 378.52 286.22 53138 +1935 135 12.31 6.31 10.66 0.74 327.71 290.91 53286 +1935 136 10.45 4.45 8.8 0 293.01 392.24 53430 +1935 137 14.21 8.21 12.56 0.01 366.73 288.73 53572 +1935 138 12.41 6.41 10.76 0 329.68 389.65 53711 +1935 139 16.92 10.92 15.27 0.02 429.22 284.47 53848 +1935 140 19.18 13.18 17.53 0 488.06 373.02 53981 +1935 141 17.18 11.18 15.53 0 435.66 379.48 54111 +1935 142 16.59 10.59 14.94 0.8 421.16 286.22 54238 +1935 143 19.1 13.1 17.45 2.19 485.86 281.04 54362 +1935 144 15.62 9.62 13.97 0.07 398.2 288.93 54483 +1935 145 15.36 9.36 13.71 0 392.23 386.38 54600 +1935 146 16.99 10.99 15.34 0 430.95 382.37 54714 +1935 147 17.49 11.49 15.84 0.11 443.46 286.06 54824 +1935 148 16.88 10.88 15.23 0 428.23 383.55 54931 +1935 149 15.94 9.94 14.29 0 405.65 386.43 55034 +1935 150 15.12 9.12 13.47 1.44 386.79 291.68 55134 +1935 151 11.87 5.87 10.22 0.24 319.2 297.59 55229 +1935 152 18.43 12.43 16.78 0 467.81 380.13 55321 +1935 153 17.19 11.19 15.54 0.03 435.91 288.05 55409 +1935 154 18.66 12.66 17.01 0.08 473.94 284.98 55492 +1935 155 18.39 12.39 16.74 0 466.76 381.01 55572 +1935 156 19.96 13.96 18.31 0 509.9 376.27 55648 +1935 157 21.19 15.19 19.54 0.06 546.02 279.1 55719 +1935 158 22.16 16.16 20.51 0 576.02 368.7 55786 +1935 159 26.14 20.14 24.49 0 714.2 351.93 55849 +1935 160 29.7 23.7 28.05 0 860.6 333.44 55908 +1935 161 31.44 25.44 29.79 0 940.89 323.01 55962 +1935 162 28.43 22.43 26.78 0 805.71 340.61 56011 +1935 163 26.57 20.57 24.92 0 730.68 350.35 56056 +1935 164 24.1 18.1 22.45 0 640.23 361.66 56097 +1935 165 22.16 16.16 20.51 0 576.02 369.59 56133 +1935 166 23.05 17.05 21.4 0 604.77 366.18 56165 +1935 167 25.22 19.22 23.57 0 679.99 356.85 56192 +1935 168 23.83 17.83 22.18 0 630.95 362.99 56214 +1935 169 22.22 16.22 20.57 0.67 577.92 277.1 56231 +1935 170 20.86 14.86 19.21 2.37 536.12 280.88 56244 +1935 171 19.8 13.8 18.15 0.01 505.35 283.67 56252 +1935 172 19.16 13.16 17.51 0 487.51 380.32 56256 +1935 173 20.89 14.89 19.24 0 537.02 374.43 56255 +1935 174 25.54 19.54 23.89 0 691.73 355.43 56249 +1935 175 26.33 20.33 24.68 0 721.44 351.68 56238 +1935 176 25.87 19.87 24.22 0 704.01 353.83 56223 +1935 177 27.02 21.02 25.37 0 748.27 348.16 56203 +1935 178 24.89 18.89 23.24 0.21 668.07 268.68 56179 +1935 179 21.82 15.82 20.17 0 565.35 370.7 56150 +1935 180 18.64 12.64 16.99 1.08 473.41 286.12 56116 +1935 181 18.04 12.04 16.39 0 457.57 383.27 56078 +1935 182 20.64 14.64 18.99 0 529.61 374.65 56035 +1935 183 20.73 14.73 19.08 0 532.26 374.16 55987 +1935 184 23.14 17.14 21.49 0.35 607.74 273.68 55935 +1935 185 22.94 16.94 21.29 0 601.15 365.63 55879 +1935 186 22.68 16.68 21.03 0 592.67 366.4 55818 +1935 187 22.99 16.99 21.34 0 602.79 364.99 55753 +1935 188 27.73 21.73 26.08 0 776.75 343.11 55684 +1935 189 27.94 21.94 26.29 0 785.34 341.85 55611 +1935 190 22.51 16.51 20.86 0 587.18 366.08 55533 +1935 191 24.59 18.59 22.94 1.22 657.38 267.94 55451 +1935 192 22.49 16.49 20.84 0.01 586.54 274.2 55366 +1935 193 26.1 20.1 24.45 0.01 712.68 262.39 55276 +1935 194 23.02 17.02 21.37 0 603.78 363.03 55182 +1935 195 22.07 16.07 20.42 0.02 573.18 274.84 55085 +1935 196 21.29 15.29 19.64 0 549.05 368.93 54984 +1935 197 21.48 15.48 19.83 0 554.85 367.78 54879 +1935 198 19.67 13.67 18.02 0 501.68 373.64 54770 +1935 199 20.76 14.76 19.11 0 533.15 369.58 54658 +1935 200 19.53 13.53 17.88 0 497.76 373.34 54542 +1935 201 22.09 16.09 20.44 0 573.81 363.89 54423 +1935 202 18.5 12.5 16.85 0.19 469.67 281.66 54301 +1935 203 19.74 13.74 18.09 0.58 503.65 278.33 54176 +1935 204 17.12 11.12 15.47 0 434.17 378.59 54047 +1935 205 13.47 7.47 11.82 0.11 351.09 290.49 53915 +1935 206 19.86 13.86 18.21 0 507.05 369.11 53780 +1935 207 22.03 16.03 20.38 0 571.92 360.84 53643 +1935 208 30.46 24.46 28.81 0 894.93 320.33 53502 +1935 209 31.57 25.57 29.92 0 947.14 313.04 53359 +1935 210 32.07 26.07 30.42 0 971.48 309.34 53213 +1935 211 26.44 20.44 24.79 0 725.66 339.65 53064 +1935 212 25.89 19.89 24.24 0 704.76 341.46 52913 +1935 213 23.11 17.11 21.46 0.04 606.75 264.39 52760 +1935 214 21.25 15.25 19.6 0.23 547.84 269.04 52604 +1935 215 22.76 16.76 21.11 0 595.27 352.49 52445 +1935 216 23.82 17.82 22.17 0 630.61 347.31 52285 +1935 217 20.13 14.13 18.48 0 514.76 359.96 52122 +1935 218 17 11 15.35 0 431.19 368.57 51958 +1935 219 19.82 13.82 18.17 0 505.92 359.11 51791 +1935 220 18.95 12.95 17.3 0 481.77 360.9 51622 +1935 221 18.16 12.16 16.51 0 460.7 362.25 51451 +1935 222 24.42 18.42 22.77 0 651.39 339.29 51279 +1935 223 28.42 22.42 26.77 0 805.29 319.7 51105 +1935 224 26.08 20.08 24.43 0 711.92 329.99 50929 +1935 225 23 17 21.35 0.42 603.12 256.26 50751 +1935 226 21.93 15.93 20.28 1.46 568.78 258.38 50572 +1935 227 20.51 14.51 18.86 0.22 525.79 261.09 50392 +1935 228 17.29 11.29 15.64 2.19 438.42 267.43 50210 +1935 229 15.83 9.83 14.18 0 403.08 359.12 50026 +1935 230 16.67 10.67 15.02 0.35 423.1 266.75 49842 +1935 231 23.32 17.32 21.67 0.01 613.72 249.78 49656 +1935 232 21.56 15.56 19.91 0.09 557.3 253.58 49469 +1935 233 20.11 14.11 18.46 0 514.19 341.48 49280 +1935 234 22.46 16.46 20.81 0.59 585.58 249.11 49091 +1935 235 24 18 22.35 0.04 636.78 243.69 48900 +1935 236 25.45 19.45 23.8 0.01 688.41 238.26 48709 +1935 237 26.46 20.46 24.81 0 726.43 311.75 48516 +1935 238 21.98 15.98 20.33 0 570.35 327.74 48323 +1935 239 22.25 16.25 20.6 0.4 578.87 244 48128 +1935 240 21.73 15.73 20.08 0.03 562.55 244.05 47933 +1935 241 22.4 16.4 20.75 0 583.66 321.41 47737 +1935 242 20.45 14.45 18.8 0 524.04 326.15 47541 +1935 243 22.61 16.61 20.96 0 590.41 317.17 47343 +1935 244 18.49 12.49 16.84 0 469.41 328.25 47145 +1935 245 19.56 13.56 17.91 0 498.6 323.37 46947 +1935 246 19.17 13.17 17.52 0.1 487.78 241.91 46747 +1935 247 18.27 12.27 16.62 0.74 463.59 242.39 46547 +1935 248 16.62 10.62 14.97 0 421.88 325.48 46347 +1935 249 15.7 9.7 14.05 0 400.05 325.57 46146 +1935 250 19.32 13.32 17.67 0 491.92 314.37 45945 +1935 251 17.57 11.57 15.92 0.06 445.49 237.72 45743 +1935 252 20.75 14.75 19.1 0.01 532.86 229.48 45541 +1935 253 20.01 14.01 18.36 0 511.32 306.09 45339 +1935 254 19.81 13.81 18.16 0.17 505.63 228.43 45136 +1935 255 21.75 15.75 20.1 0.07 563.17 222.41 44933 +1935 256 23.77 17.77 22.12 0 628.9 287.63 44730 +1935 257 20.43 14.43 18.78 0 523.45 296.23 44527 +1935 258 19.3 13.3 17.65 0 491.36 297.09 44323 +1935 259 22.21 16.21 20.56 0.79 577.6 214.65 44119 +1935 260 21.87 15.87 20.22 0.78 566.91 213.72 43915 +1935 261 22.09 16.09 20.44 0.12 573.81 211.44 43711 +1935 262 19.29 13.29 17.64 0.08 491.09 215.74 43507 +1935 263 19.46 13.46 17.81 0 495.8 284.78 43303 +1935 264 20.71 14.71 19.06 0.62 531.67 209.14 43099 +1935 265 20.29 14.29 18.64 0.44 519.38 208.29 42894 +1935 266 19.83 13.83 18.18 0 506.2 276.55 42690 +1935 267 17.28 11.28 15.63 0 438.16 280.19 42486 +1935 268 15.78 9.78 14.13 0 401.91 280.89 42282 +1935 269 13.86 7.86 12.21 0 359.26 282.11 42078 +1935 270 14.21 8.21 12.56 0.01 366.73 209.11 41875 +1935 271 17.68 11.68 16.03 0.54 448.29 201.81 41671 +1935 272 17.05 11.05 15.4 0 432.43 267.78 41468 +1935 273 14.2 8.2 12.55 0 366.52 270.92 41265 +1935 274 10.74 4.74 9.09 0 298.21 273.87 41062 +1935 275 10.94 4.94 9.29 0 301.83 270.76 40860 +1935 276 11.79 5.79 10.14 0 317.68 266.75 40658 +1935 277 13.87 7.87 12.22 0.58 359.47 195.52 40456 +1935 278 15.52 9.52 13.87 0.53 395.89 191.14 40255 +1935 279 19.63 13.63 17.98 0.04 500.56 182.51 40054 +1935 280 17.69 11.69 16.04 0.31 448.55 183.85 39854 +1935 281 18.32 12.32 16.67 0.32 464.91 180.84 39654 +1935 282 16.16 10.16 14.51 0.07 410.84 182.13 39455 +1935 283 13.55 7.55 11.9 0.32 352.75 183.47 39256 +1935 284 11.77 5.77 10.12 0.51 317.3 183.24 39058 +1935 285 12.78 6.78 11.13 0.01 337.02 180.13 38861 +1935 286 13.69 7.69 12.04 0 355.68 236.01 38664 +1935 287 20.85 14.85 19.2 0.02 535.82 164.3 38468 +1935 288 19.96 13.96 18.31 0.99 509.9 163.85 38273 +1935 289 18.22 12.22 16.57 0.29 462.28 164.74 38079 +1935 290 20.02 14.02 18.37 0.01 511.61 159.81 37885 +1935 291 17.54 11.54 15.89 0 444.72 215.6 37693 +1935 292 17.98 11.98 16.33 0 456.02 212.15 37501 +1935 293 17.92 11.92 16.27 0 454.46 209.62 37311 +1935 294 14.9 8.9 13.25 0 381.86 212.09 37121 +1935 295 14.68 8.68 13.03 0 376.98 209.64 36933 +1935 296 14.02 8.02 12.37 0 362.66 208.1 36745 +1935 297 13.79 7.79 12.14 0 357.78 205.74 36560 +1935 298 15.22 9.22 13.57 0 389.05 201.02 36375 +1935 299 16.08 10.08 14.43 0.18 408.95 147.7 36191 +1935 300 13.75 7.75 12.1 2.98 356.94 148.39 36009 +1935 301 12.63 6.63 10.98 0.4 334.03 147.66 35829 +1935 302 16 10 14.35 0 407.06 189.47 35650 +1935 303 14.81 8.81 13.16 0 379.85 188.76 35472 +1935 304 17.15 11.15 15.5 0 434.92 182.73 35296 +1935 305 5.71 -0.29 4.06 0.24 218.47 145.25 35122 +1935 306 9.41 3.41 7.76 0 275.02 188.01 34950 +1935 307 3.05 -2.95 1.4 0 184.28 190.79 34779 +1935 308 8.23 2.23 6.58 0 255.76 184.04 34610 +1935 309 6.81 0.81 5.16 0 234.13 182.97 34444 +1935 310 6.8 0.8 5.15 0 233.98 180.52 34279 +1935 311 12.17 6.17 10.52 0 324.99 173.05 34116 +1935 312 10.54 4.54 8.89 0 294.62 172.22 33956 +1935 313 12.86 6.86 11.21 0.09 338.63 125.67 33797 +1935 314 8.55 2.55 6.9 0 260.86 170.09 33641 +1935 315 9.62 3.62 7.97 0 278.57 166.58 33488 +1935 316 6.93 0.93 5.28 0 235.89 166.75 33337 +1935 317 12.04 6.04 10.39 0.19 322.47 119.84 33188 +1935 318 12.86 6.86 11.21 0.12 338.63 117.43 33042 +1935 319 11.04 5.04 9.39 0.43 303.66 117.64 32899 +1935 320 6.55 0.55 4.9 0 230.34 158.93 32758 +1935 321 4.67 -1.33 3.02 0 204.5 158.14 32620 +1935 322 3.75 -2.25 2.1 0 192.79 156.89 32486 +1935 323 4.29 -1.71 2.64 0.02 199.59 116.19 32354 +1935 324 11.1 5.1 9.45 0.07 304.76 110.61 32225 +1935 325 10.55 4.55 8.9 0.24 294.79 109.73 32100 +1935 326 10.38 4.38 8.73 0 291.77 145.04 31977 +1935 327 5.47 -0.53 3.82 1.32 215.17 110.28 31858 +1935 328 4.91 -1.09 3.26 1.4 207.65 109.08 31743 +1935 329 3.72 -2.28 2.07 0 192.42 144.66 31631 +1935 330 3.09 -2.91 1.44 0 184.76 143.56 31522 +1935 331 4.86 -1.14 3.21 0 206.99 141.2 31417 +1935 332 11.16 5.16 9.51 0 305.87 134.76 31316 +1935 333 8.97 2.97 7.32 0 267.7 135.58 31218 +1935 334 6.45 0.45 4.8 0 228.9 136.34 31125 +1935 335 3.1 -2.9 1.45 0 184.88 137.19 31035 +1935 336 4.57 -1.43 2.92 0 203.2 135.29 30949 +1935 337 5.3 -0.7 3.65 0.18 212.87 99.89 30867 +1935 338 6.48 0.48 4.83 0 229.33 131.49 30790 +1935 339 7.74 1.74 6.09 0 248.11 129.84 30716 +1935 340 7.83 1.83 6.18 0 249.5 129.05 30647 +1935 341 6.75 0.75 5.1 0.2 233.25 96.66 30582 +1935 342 2.49 -3.51 0.84 2.75 177.7 97.95 30521 +1935 343 2.79 -3.21 1.14 0.73 181.2 97.21 30465 +1935 344 -0.27 -6.27 -1.92 1.62 148.15 145.93 30413 +1935 345 1.33 -4.67 -0.32 0.1 164.72 144.98 30366 +1935 346 -2.52 -8.52 -4.17 0 127.31 178.24 30323 +1935 347 -2.72 -8.72 -4.37 0 125.59 177.77 30284 +1935 348 -1.23 -7.23 -2.88 0 138.93 176.92 30251 +1935 349 -1.54 -7.54 -3.19 0.04 136.05 144.81 30221 +1935 350 2.9 -3.1 1.25 0 182.5 174.2 30197 +1935 351 1.48 -4.52 -0.17 0.29 166.35 142.94 30177 +1935 352 1.42 -4.58 -0.23 1.98 165.69 142.72 30162 +1935 353 2.13 -3.87 0.48 0.67 173.58 142.16 30151 +1935 354 3.78 -2.22 2.13 0 193.17 172.24 30145 +1935 355 2.67 -3.33 1.02 0.06 179.79 141.08 30144 +1935 356 3.08 -2.92 1.43 0 184.64 171.85 30147 +1935 357 5.59 -0.41 3.94 0 216.82 169.76 30156 +1935 358 6.91 0.91 5.26 0 235.6 168.08 30169 +1935 359 10.57 4.57 8.92 0 295.15 120.64 30186 +1935 360 7.04 1.04 5.39 0.04 237.52 92.71 30208 +1935 361 5.03 -0.97 3.38 0 209.25 125.2 30235 +1935 362 9.11 3.11 7.46 0 270.01 122.91 30267 +1935 363 3.43 -2.57 1.78 0.03 188.86 95.33 30303 +1935 364 5.05 -0.95 3.4 0.07 209.51 94.95 30343 +1935 365 6.07 0.07 4.42 0 223.49 126.54 30388 +1936 1 8.28 2.28 6.63 0 256.55 125.93 30438 +1936 2 7.6 1.6 5.95 0 245.96 127.14 30492 +1936 3 9.16 3.16 7.51 0 270.84 126.92 30551 +1936 4 9.71 3.71 8.06 0.24 280.11 95.54 30614 +1936 5 10.42 4.42 8.77 0.4 292.48 95.57 30681 +1936 6 9.85 3.85 8.2 0.49 282.51 96.58 30752 +1936 7 7.83 1.83 6.18 0.49 249.5 98.33 30828 +1936 8 8.65 2.65 7 1.47 262.48 98.97 30907 +1936 9 7.07 1.07 5.42 0.1 237.97 100.77 30991 +1936 10 3.75 -2.25 2.1 0 192.79 137.75 31079 +1936 11 3.88 -2.12 2.23 0.08 194.41 104 31171 +1936 12 2.96 -3.04 1.31 0.56 183.21 105.14 31266 +1936 13 9.8 3.8 8.15 0.2 281.65 102.83 31366 +1936 14 8.07 2.07 6.42 0 253.24 139.95 31469 +1936 15 7.25 1.25 5.6 0.27 240.65 106.49 31575 +1936 16 9.99 3.99 8.34 0 284.93 141.05 31686 +1936 17 9.25 3.25 7.6 0.21 272.34 107.51 31800 +1936 18 9.78 3.78 8.13 0 281.31 144.75 31917 +1936 19 8.72 2.72 7.07 0.33 263.61 110.67 32038 +1936 20 8.21 2.21 6.56 0 255.44 149.54 32161 +1936 21 4.57 -1.43 2.92 0 203.2 154.17 32289 +1936 22 5.25 -0.75 3.6 0.03 212.19 116.6 32419 +1936 23 3.9 -2.1 2.25 0.06 194.66 118.58 32552 +1936 24 5.21 -0.79 3.56 0 211.65 159.31 32688 +1936 25 2.23 -3.77 0.58 0 174.72 163.07 32827 +1936 26 3.91 -2.09 2.26 0 194.79 163.99 32969 +1936 27 1.59 -4.41 -0.06 0 167.55 167.41 33114 +1936 28 1.45 -4.55 -0.2 2.39 166.02 127.28 33261 +1936 29 2.8 -3.2 1.15 0 181.32 171.3 33411 +1936 30 3.2 -2.8 1.55 0 186.07 173.3 33564 +1936 31 8.38 2.38 6.73 0 258.14 171.73 33718 +1936 32 6.25 0.25 4.6 0.03 226.04 131.71 33875 +1936 33 7.71 1.71 6.06 0 247.65 177.01 34035 +1936 34 9.34 3.34 7.69 0 273.84 177.68 34196 +1936 35 9.24 3.24 7.59 1.14 272.17 134.91 34360 +1936 36 1.81 -4.19 0.16 0 169.99 188.22 34526 +1936 37 1.55 -4.45 -0.1 0.34 167.11 143.11 34694 +1936 38 1.01 -4.99 -0.64 0.64 161.28 145.42 34863 +1936 39 -0.29 -6.29 -1.94 0.38 147.96 186.67 35035 +1936 40 2.94 -3.06 1.29 0.01 182.97 186.64 35208 +1936 41 5.91 -0.09 4.26 0 221.25 235.62 35383 +1936 42 3.95 -2.05 2.3 0.71 195.29 151.8 35560 +1936 43 6.86 0.86 5.21 0 234.86 202.7 35738 +1936 44 6.56 0.56 4.91 0 230.49 205.52 35918 +1936 45 7.34 1.34 5.69 0 242.01 207.4 36099 +1936 46 6.08 0.08 4.43 1.55 223.63 158.43 36282 +1936 47 5.27 -0.73 3.62 0.32 212.46 161.07 36466 +1936 48 2.23 -3.77 0.58 0.39 174.72 164.95 36652 +1936 49 1.42 -4.58 -0.23 0.2 165.69 167.47 36838 +1936 50 -2.43 -8.43 -4.08 0 128.09 228.28 37026 +1936 51 3.89 -2.11 2.24 0.05 194.54 170.35 37215 +1936 52 4.04 -1.96 2.39 0.36 196.42 172.39 37405 +1936 53 3.35 -2.65 1.7 0.11 187.89 175.04 37596 +1936 54 6.52 0.52 4.87 0.05 229.91 175.01 37788 +1936 55 9.34 3.34 7.69 0.02 273.84 174.95 37981 +1936 56 6.51 0.51 4.86 0.29 229.76 179.27 38175 +1936 57 5.22 -0.78 3.57 0 211.79 243.15 38370 +1936 58 7.19 1.19 5.54 0 239.76 244.12 38565 +1936 59 7.96 1.96 6.31 0.7 251.52 184.48 38761 +1936 60 13.55 7.55 11.9 0.19 352.75 180.95 38958 +1936 61 12.62 6.62 10.97 0 333.83 245.58 39156 +1936 62 13.28 7.28 11.63 0 347.17 247.27 39355 +1936 63 10.7 4.7 9.05 0 297.48 254.06 39553 +1936 64 12.55 6.55 10.9 0 332.44 254.2 39753 +1936 65 10.45 4.45 8.8 0 293.01 260.13 39953 +1936 66 13.08 7.08 11.43 0 343.08 258.86 40154 +1936 67 8.45 2.45 6.8 0.02 259.26 201.25 40355 +1936 68 10.48 4.48 8.83 1.22 293.55 201.37 40556 +1936 69 12.1 6.1 10.45 0.04 323.63 201.49 40758 +1936 70 12.38 6.38 10.73 0 329.09 271 40960 +1936 71 10.99 4.99 9.34 0.09 302.75 207.03 41163 +1936 72 10.2 4.2 8.55 0.2 288.6 209.99 41366 +1936 73 11.27 5.27 9.62 0 307.9 281.03 41569 +1936 74 10.88 4.88 9.23 0 300.74 284.34 41772 +1936 75 12.27 6.27 10.62 0 326.93 284.82 41976 +1936 76 11.85 5.85 10.2 0 318.82 288.11 42179 +1936 77 9.64 3.64 7.99 0.44 278.91 220.56 42383 +1936 78 8.24 2.24 6.59 0.09 255.92 224 42587 +1936 79 9.59 3.59 7.94 0 278.06 299.51 42791 +1936 80 9.67 3.67 8.02 0 279.43 301.92 42996 +1936 81 7.96 1.96 6.31 0 251.52 306.89 43200 +1936 82 5.21 -0.79 3.56 0 211.65 312.91 43404 +1936 83 7.84 1.84 6.19 0 249.65 312.21 43608 +1936 84 7.64 1.64 5.99 0 246.57 315.02 43812 +1936 85 9.56 3.56 7.91 0.32 277.55 236.11 44016 +1936 86 8.33 2.33 6.68 0.58 257.34 239.25 44220 +1936 87 7.73 1.73 6.08 0.06 247.95 241.78 44424 +1936 88 7.21 1.21 5.56 0 240.06 325.43 44627 +1936 89 7.92 1.92 6.27 0 250.9 326.77 44831 +1936 90 9.64 3.64 7.99 0 278.91 326.62 45034 +1936 91 12.05 6.05 10.4 0 322.66 324.82 45237 +1936 92 8.9 2.9 7.25 0 266.55 332.26 45439 +1936 93 9.88 3.88 8.23 0 283.03 332.96 45642 +1936 94 8.6 2.6 6.95 0 261.67 337.1 45843 +1936 95 8.07 2.07 6.42 0.09 253.24 255.03 46045 +1936 96 12.03 6.03 10.38 0 322.28 335.65 46246 +1936 97 13.39 7.39 11.74 0 349.43 335.05 46446 +1936 98 12.04 6.04 10.39 0.44 322.47 254.72 46647 +1936 99 11.9 5.9 10.25 0.38 319.78 256.42 46846 +1936 100 12.26 6.26 10.61 0 326.74 343.16 47045 +1936 101 19.86 13.86 18.21 0 507.05 326.59 47243 +1936 102 18.29 12.29 16.64 1.33 464.12 249.71 47441 +1936 103 12.7 6.7 11.05 0.04 335.42 260.96 47638 +1936 104 13.74 7.74 12.09 0 356.73 347.62 47834 +1936 105 13.98 7.98 12.33 0 361.81 348.89 48030 +1936 106 14.95 8.95 13.3 0.99 382.97 261.26 48225 +1936 107 16.02 10.02 14.37 0 407.53 347.44 48419 +1936 108 17.17 11.17 15.52 0 435.41 346.21 48612 +1936 109 15.44 9.44 13.79 0 394.06 352.15 48804 +1936 110 17.85 11.85 16.2 0 452.65 347.31 48995 +1936 111 16.66 10.66 15.01 0.07 422.85 264.01 49185 +1936 112 18.03 12.03 16.38 0.7 457.31 262.34 49374 +1936 113 19.37 13.37 17.72 0.67 493.3 260.37 49561 +1936 114 14.71 8.71 13.06 0.03 377.64 270.84 49748 +1936 115 9.97 3.97 8.32 0.34 284.59 279.15 49933 +1936 116 7.73 1.73 6.08 0.08 247.95 282.84 50117 +1936 117 12.49 6.49 10.84 0.29 331.25 277.46 50300 +1936 118 7.56 1.56 5.91 0 245.35 380.06 50481 +1936 119 8.72 2.72 7.07 0 263.61 379.44 50661 +1936 120 5.5 -0.5 3.85 0 215.58 385.43 50840 +1936 121 14.32 8.32 12.67 0 369.11 370.76 51016 +1936 122 16.64 10.64 14.99 0.04 422.37 274.62 51191 +1936 123 20.04 14.04 18.39 0.15 512.18 267.84 51365 +1936 124 19.2 13.2 17.55 0.39 488.61 270.63 51536 +1936 125 14 8 12.35 0.02 362.24 281.85 51706 +1936 126 20.46 14.46 18.81 0.08 524.33 269.02 51874 +1936 127 23.7 17.7 22.05 1.26 626.52 260.69 52039 +1936 128 25.6 19.6 23.95 0.29 693.95 255.33 52203 +1936 129 22.38 16.38 20.73 1.11 583.02 265.87 52365 +1936 130 22.97 16.97 21.32 0.1 602.13 264.74 52524 +1936 131 22.18 16.18 20.53 0.44 576.65 267.57 52681 +1936 132 20.85 14.85 19.2 0.6 535.82 271.76 52836 +1936 133 20.78 14.78 19.13 2.87 533.75 272.45 52989 +1936 134 21.12 15.12 19.47 0.49 543.91 272.08 53138 +1936 135 18.26 12.26 16.61 0.23 463.33 279.59 53286 +1936 136 14.07 8.07 12.42 0 363.73 384.6 53430 +1936 137 15.41 9.41 13.76 0.03 393.37 286.52 53572 +1936 138 15.87 9.87 14.22 0 404.01 381.44 53711 +1936 139 15.24 9.24 13.59 0 389.5 383.76 53848 +1936 140 16.17 10.17 14.52 0.11 411.08 286.37 53981 +1936 141 13.67 7.67 12.02 1.38 355.26 291.37 54111 +1936 142 15.78 9.78 14.13 2.01 401.91 287.85 54238 +1936 143 12.39 6.39 10.74 1.42 329.28 294.29 54362 +1936 144 17.23 11.23 15.58 0.25 436.91 285.63 54483 +1936 145 11.52 5.52 9.87 2.1 312.57 296.38 54600 +1936 146 13.45 7.45 11.8 1.65 350.68 293.55 54714 +1936 147 15.57 9.57 13.92 0 397.04 386.7 54824 +1936 148 13.52 7.52 11.87 0.03 352.13 294.08 54931 +1936 149 17.39 11.39 15.74 0 440.93 382.41 55034 +1936 150 24.5 18.5 22.85 0 654.2 357.32 55134 +1936 151 24.22 18.22 22.57 0 644.4 358.9 55229 +1936 152 23.14 17.14 21.49 0.1 607.74 272.61 55321 +1936 153 24.96 18.96 23.31 0 670.58 356.01 55409 +1936 154 20.95 14.95 19.3 0.18 538.81 279.25 55492 +1936 155 21.49 15.49 19.84 0.04 555.15 277.92 55572 +1936 156 15.34 9.34 13.69 0 391.77 389.94 55648 +1936 157 15.17 9.17 13.52 0 387.92 390.55 55719 +1936 158 16.18 10.18 14.53 0.06 411.32 291.05 55786 +1936 159 16.54 10.54 14.89 0 419.95 387.32 55849 +1936 160 19.06 13.06 17.41 0.42 484.77 284.99 55908 +1936 161 20.19 14.19 18.54 0 516.49 376.31 55962 +1936 162 19.57 13.57 17.92 0.01 498.88 283.84 56011 +1936 163 18.49 12.49 16.84 0.08 469.41 286.6 56056 +1936 164 16.84 10.84 15.19 0 427.25 387.06 56097 +1936 165 16.93 10.93 15.28 0 429.47 386.91 56133 +1936 166 20.75 14.75 19.1 0.71 532.86 281.14 56165 +1936 167 22.43 16.43 20.78 0.16 584.62 276.43 56192 +1936 168 21.2 15.2 19.55 0.6 546.32 279.95 56214 +1936 169 23.57 17.57 21.92 0 622.12 364.09 56231 +1936 170 25.66 19.66 24.01 0.11 696.18 266.19 56244 +1936 171 23.79 17.79 22.14 0.74 629.58 272.42 56252 +1936 172 24.56 18.56 22.91 0.31 656.32 269.94 56256 +1936 173 20.75 14.75 19.1 0.02 532.86 281.19 56255 +1936 174 21.81 15.81 20.16 0 565.04 370.98 56249 +1936 175 27 21 25.35 0 747.48 348.39 56238 +1936 176 25.75 19.75 24.1 0 699.53 354.39 56223 +1936 177 22.24 16.24 20.59 0.17 578.56 276.88 56203 +1936 178 23.33 17.33 21.68 0.51 614.06 273.67 56179 +1936 179 21.43 15.43 19.78 0.9 553.32 279.11 56150 +1936 180 19.3 13.3 17.65 0.85 491.36 284.54 56116 +1936 181 16.6 10.6 14.95 0.23 421.4 290.59 56078 +1936 182 22.57 16.57 20.92 0 589.12 367.5 56035 +1936 183 23.91 17.91 22.26 0.05 633.69 271.41 55987 +1936 184 24.3 18.3 22.65 0.07 647.19 270.05 55935 +1936 185 28.3 22.3 26.65 0.36 800.27 255.59 55879 +1936 186 28.44 22.44 26.79 0.01 806.14 254.84 55818 +1936 187 29.52 23.52 27.87 2.32 852.64 250.24 55753 +1936 188 29.45 23.45 27.8 0 849.56 333.8 55684 +1936 189 24.39 18.39 22.74 0 650.34 358.74 55611 +1936 190 24.36 18.36 22.71 0 649.28 358.51 55533 +1936 191 18.18 12.18 16.53 0 461.23 380.73 55451 +1936 192 18.51 12.51 16.86 0 469.94 379.42 55366 +1936 193 19.98 13.98 18.33 0.11 510.47 280.8 55276 +1936 194 21.74 15.74 20.09 0.31 562.86 275.96 55182 +1936 195 23.26 17.26 21.61 0.14 611.72 271.35 55085 +1936 196 22.79 16.79 21.14 0.27 596.25 272.45 54984 +1936 197 20.73 14.73 19.08 0 532.26 370.46 54879 +1936 198 21.39 15.39 19.74 0 552.1 367.69 54770 +1936 199 20.98 14.98 19.33 0 539.7 368.81 54658 +1936 200 22.02 16.02 20.37 1.92 571.61 273.46 54542 +1936 201 24.75 18.75 23.1 0.03 663.06 264.82 54423 +1936 202 22.05 16.05 20.4 0.02 572.55 272.61 54301 +1936 203 19.41 13.41 17.76 0.03 494.41 279.13 54176 +1936 204 18.14 12.14 16.49 0 460.18 375.62 54047 +1936 205 21.04 15.04 19.39 0 541.5 365.64 53915 +1936 206 22.68 16.68 21.03 0 592.67 359.02 53780 +1936 207 22.48 16.48 20.83 0.45 586.22 269.36 53643 +1936 208 24.55 18.55 22.9 0 655.97 350.12 53502 +1936 209 27.34 21.34 25.69 0 760.99 336.62 53359 +1936 210 26.56 20.56 24.91 0.29 730.29 254.87 53213 +1936 211 27.82 21.82 26.17 0.48 780.42 249.66 53064 +1936 212 26.52 20.52 24.87 0 728.75 338.52 52913 +1936 213 28.05 22.05 26.4 0 789.88 330.26 52760 +1936 214 27.01 21.01 25.36 0 747.87 334.75 52604 +1936 215 25.13 19.13 23.48 0.06 676.72 257.08 52445 +1936 216 23.16 17.16 21.51 0 608.4 349.94 52285 +1936 217 20.09 14.09 18.44 0 513.62 360.09 52122 +1936 218 18.83 12.83 17.18 0 478.52 363.27 51958 +1936 219 21.05 15.05 19.4 0 541.8 355 51791 +1936 220 21.97 15.97 20.32 0 570.04 350.81 51622 +1936 221 20.23 14.23 18.58 0.95 517.65 266.87 51451 +1936 222 17.84 11.84 16.19 0 452.4 362.12 51279 +1936 223 21.68 15.68 20.03 0.2 561.01 261.53 51105 +1936 224 21.87 15.87 20.22 0.03 566.91 260.23 50929 +1936 225 21.72 15.72 20.07 0 562.24 346.39 50751 +1936 226 22.32 16.32 20.67 0 581.1 343.1 50572 +1936 227 21.02 15.02 19.37 0 540.9 346.42 50392 +1936 228 22.93 16.93 21.28 0 600.82 338.4 50210 +1936 229 17.93 11.93 16.28 0 454.72 353.53 50026 +1936 230 17.85 11.85 16.2 0.12 452.65 264.35 49842 +1936 231 22.56 16.56 20.91 0 588.79 335.88 49656 +1936 232 21.56 15.56 19.91 0.26 557.3 253.58 49469 +1936 233 19.31 13.31 17.66 0 491.64 343.95 49280 +1936 234 20.74 14.74 19.09 0.4 532.56 253.54 49091 +1936 235 22.78 16.78 21.13 0.07 595.92 247.15 48900 +1936 236 19.81 13.81 18.16 0 505.63 338.1 48709 +1936 237 14.99 8.99 13.34 0 383.87 349.36 48516 +1936 238 16.59 10.59 14.94 0 421.16 343.78 48323 +1936 239 20.23 14.23 18.58 0 517.65 332 48128 +1936 240 23.07 17.07 21.42 0.06 605.43 240.52 47933 +1936 241 24.1 18.1 22.45 0.16 640.23 236.38 47737 +1936 242 22.84 16.84 21.19 0.6 597.88 238.62 47541 +1936 243 23.03 17.03 21.38 0.45 604.11 236.76 47343 +1936 244 22.55 16.55 20.9 0.41 588.47 236.7 47145 +1936 245 24.73 18.73 23.08 0.1 662.35 229.34 46947 +1936 246 21.27 15.27 19.62 0.07 548.44 237.14 46747 +1936 247 20.33 14.33 18.68 0.75 520.54 237.97 46547 +1936 248 17.68 11.68 16.03 0 448.29 322.81 46347 +1936 249 19.58 13.58 17.93 0.04 499.16 236.67 46146 +1936 250 21.1 15.1 19.45 0.28 543.31 231.81 45945 +1936 251 23.28 17.28 21.63 0 612.39 299.81 45743 +1936 252 19.2 13.2 17.55 0 488.61 310.48 45541 +1936 253 19.69 13.69 18.04 0 502.24 307.01 45339 +1936 254 17.64 11.64 15.99 0 447.27 310.37 45136 +1936 255 16.27 10.27 14.62 0 413.46 311.41 44933 +1936 256 18.49 12.49 16.84 0 469.41 303.7 44730 +1936 257 19.68 13.68 18.03 0.11 501.96 223.77 44527 +1936 258 15.06 9.06 13.41 0 385.44 307.25 44323 +1936 259 15.3 9.3 13.65 0.48 390.86 228.22 44119 +1936 260 13.74 7.74 12.09 0.23 356.73 228.78 43915 +1936 261 12.47 6.47 10.82 0.01 330.86 228.68 43711 +1936 262 15.92 9.92 14.27 0 405.18 295.72 43507 +1936 263 14.22 8.22 12.57 0 366.95 296.74 43303 +1936 264 17.13 11.13 15.48 0 434.42 288 43099 +1936 265 17.78 11.78 16.13 0 450.85 284.13 42894 +1936 266 21.67 15.67 20.02 0.26 560.7 203.56 42690 +1936 267 19.38 13.38 17.73 0.21 493.58 206.33 42486 +1936 268 21.46 15.46 19.81 0.33 554.23 200.24 42282 +1936 269 17.43 11.43 15.78 0.51 441.94 206.12 42078 +1936 270 17.67 11.67 16.02 1.02 448.04 203.76 41875 +1936 271 19.44 13.44 17.79 1.67 495.25 198.66 41671 +1936 272 16.63 10.63 14.98 0.65 422.13 201.51 41468 +1936 273 17.43 11.43 15.78 0 441.94 264.45 41265 +1936 274 11.21 5.21 9.56 0.15 306.79 204.88 41062 +1936 275 8.81 2.81 7.16 0.02 265.08 205.27 40860 +1936 276 5.24 -0.76 3.59 1.36 212.06 206.26 40658 +1936 277 5.57 -0.43 3.92 0.61 216.54 203.94 40456 +1936 278 3.31 -2.69 1.66 0 187.4 271.11 40255 +1936 279 4.93 -1.07 3.28 0.42 207.92 200.03 40054 +1936 280 6.02 0.02 4.37 0 222.79 262.87 39854 +1936 281 7.61 1.61 5.96 0 246.11 258.35 39654 +1936 282 10.76 4.76 9.11 0 298.57 251.62 39455 +1936 283 7.88 1.88 6.23 1.09 250.27 189.27 39256 +1936 284 6.43 0.43 4.78 0.01 228.61 188.14 39058 +1936 285 13.38 7.38 11.73 0 349.23 239.25 38861 +1936 286 13.98 7.98 12.33 0.05 361.81 176.66 38664 +1936 287 15.13 9.13 13.48 0.27 387.01 173.04 38468 +1936 288 13.46 7.46 11.81 0.98 350.88 173.01 38273 +1936 289 18.24 12.24 16.59 0 462.8 219.62 38079 +1936 290 17.4 11.4 15.75 0.88 441.18 163.87 37885 +1936 291 12.87 6.87 11.22 1.35 338.83 167.55 37693 +1936 292 14.43 8.43 12.78 0 371.5 218.37 37501 +1936 293 12.01 6.01 10.36 0.03 321.89 164.4 37311 +1936 294 11.87 5.87 10.22 1.1 319.2 162.37 37121 +1936 295 8.45 2.45 6.8 0.09 259.26 163.29 36933 +1936 296 7.21 1.21 5.56 0.52 240.06 162.27 36745 +1936 297 9.44 3.44 7.79 2.1 275.52 158.46 36560 +1936 298 10.45 4.45 8.8 0.72 293.01 155.63 36375 +1936 299 6.2 0.2 4.55 0 225.33 209.06 36191 +1936 300 4.74 -1.26 3.09 0 205.42 207.58 36009 +1936 301 4.22 -1.78 2.57 0 198.7 205.41 35829 +1936 302 7.92 1.92 6.27 0 250.9 199.57 35650 +1936 303 11.41 5.41 9.76 0 310.51 193.24 35472 +1936 304 10.53 4.53 8.88 0.02 294.44 143.85 35296 +1936 305 9.78 3.78 8.13 0 281.31 189.88 35122 +1936 306 8.34 2.34 6.69 0 257.5 189.07 34950 +1936 307 3.64 -2.36 1.99 0 191.43 190.39 34779 +1936 308 4.45 -1.55 2.8 0 201.65 187.17 34610 +1936 309 8.04 2.04 6.39 0 252.77 181.89 34444 +1936 310 8.47 2.47 6.82 0 259.58 179.05 34279 +1936 311 1.31 -4.69 -0.34 0 164.5 182.15 34116 +1936 312 1.28 -4.72 -0.37 0.05 164.17 134.61 33956 +1936 313 -0.5 -6.5 -2.15 0.13 145.9 173.12 33797 +1936 314 1.4 -4.6 -0.25 0 165.48 214.69 33641 +1936 315 3.76 -2.24 2.11 0.05 192.92 128.43 33488 +1936 316 5.77 -0.23 4.12 0.79 219.3 125.73 33337 +1936 317 2.48 -3.52 0.83 0.01 177.58 125.71 33188 +1936 318 9.43 3.43 7.78 0.39 275.36 120.06 33042 +1936 319 7.87 1.87 6.22 0 250.12 159.75 32899 +1936 320 5.13 -0.87 3.48 0 210.58 159.95 32758 +1936 321 7.34 1.34 5.69 0 242.01 156.21 32620 +1936 322 10.52 4.52 8.87 0 294.26 151.65 32486 +1936 323 10.41 4.41 8.76 0 292.3 150.16 32354 +1936 324 12.32 6.32 10.67 0 327.91 146.25 32225 +1936 325 10.29 4.29 8.64 0 290.18 146.55 32100 +1936 326 10.42 4.42 8.77 0 292.48 145 31977 +1936 327 8.36 2.36 6.71 0 257.82 144.93 31858 +1936 328 10.15 4.15 8.5 0 287.72 141.47 31743 +1936 329 8.37 2.37 6.72 0 257.98 141.49 31631 +1936 330 11.24 5.24 9.59 0.03 307.35 103.19 31522 +1936 331 8.87 2.87 7.22 0.59 266.06 103.76 31417 +1936 332 11.08 5.08 9.43 0 304.4 134.84 31316 +1936 333 8.92 2.92 7.27 0 266.88 135.62 31218 +1936 334 9.2 3.2 7.55 0 271.5 134.31 31125 +1936 335 5.27 -0.73 3.62 0 212.46 135.93 31035 +1936 336 6.02 0.02 4.37 0.17 222.79 100.79 30949 +1936 337 1.28 -4.72 -0.37 0.14 164.17 101.52 30867 +1936 338 4.35 -1.65 2.7 0.04 200.36 99.6 30790 +1936 339 4.34 -1.66 2.69 0 200.23 132.02 30716 +1936 340 8.36 2.36 6.71 0.02 257.82 96.5 30647 +1936 341 4.16 -1.84 2.51 0.37 197.94 97.85 30582 +1936 342 4.6 -1.4 2.95 0.1 203.59 97.09 30521 +1936 343 3.13 -2.87 1.48 0 185.23 129.44 30465 +1936 344 4.83 -1.17 3.18 0 206.6 127.37 30413 +1936 345 7.59 1.59 5.94 0 245.81 125.19 30366 +1936 346 3.9 -2.1 2.25 0.33 194.66 95.19 30323 +1936 347 1.13 -4.87 -0.52 0.31 162.56 95.77 30284 +1936 348 0.96 -5.04 -0.69 0 160.75 127.42 30251 +1936 349 1.02 -4.98 -0.63 0 161.39 127.01 30221 +1936 350 2.34 -3.66 0.69 0.02 175.97 94.54 30197 +1936 351 2.71 -3.29 1.06 0 180.26 125.65 30177 +1936 352 3.58 -2.42 1.93 0.3 190.7 93.83 30162 +1936 353 -0.66 -6.66 -2.31 0.56 144.34 140.81 30151 +1936 354 2.33 -3.67 0.68 0 175.86 170.9 30145 +1936 355 2.62 -3.38 0.97 0 179.21 170.41 30144 +1936 356 1.14 -4.86 -0.51 0 162.67 170.98 30147 +1936 357 1.69 -4.31 0.04 0 168.65 170.55 30156 +1936 358 2.78 -3.22 1.13 0 181.08 169.72 30169 +1936 359 3.35 -2.65 1.7 0 187.89 125.42 30186 +1936 360 3.11 -2.89 1.46 0 184.99 125.91 30208 +1936 361 4.95 -1.05 3.3 0 208.18 125.24 30235 +1936 362 6.5 0.5 4.85 0.06 229.62 93.55 30267 +1936 363 6.28 0.28 4.63 0.03 226.47 94.09 30303 +1936 364 0.28 -5.72 -1.37 0.14 153.68 96.75 30343 +1936 365 -5.84 -11.84 -7.49 0 101.2 131.72 30388 +1937 1 -8.45 -14.45 -10.1 0.2 84.07 143.97 30438 +1937 2 -10.26 -16.26 -11.91 0.04 73.73 144.87 30492 +1937 3 -5.63 -11.63 -7.28 0 102.7 178.23 30551 +1937 4 -5 -11 -6.65 0 107.32 178.88 30614 +1937 5 1.58 -4.42 -0.07 0 167.44 176.71 30681 +1937 6 0.2 -5.8 -1.45 0 152.86 178.11 30752 +1937 7 0.19 -5.81 -1.46 0 152.76 178.78 30828 +1937 8 1.56 -4.44 -0.09 0.07 167.22 145.25 30907 +1937 9 1.68 -4.32 0.03 0 168.54 180.2 30991 +1937 10 0.33 -5.67 -1.32 0 154.19 181.98 31079 +1937 11 -1.21 -7.21 -2.86 0 139.11 183.52 31171 +1937 12 -3.43 -9.43 -5.08 0 119.63 185.26 31266 +1937 13 -1.23 -7.23 -2.88 0.96 138.93 152.91 31366 +1937 14 0.01 -5.99 -1.64 0.76 150.94 153.48 31469 +1937 15 0 -6 -1.65 0 150.84 190.98 31575 +1937 16 -0.9 -6.9 -2.55 0.46 142.04 156.93 31686 +1937 17 -0.18 -6.18 -1.83 0.18 149.05 158.34 31800 +1937 18 2.32 -3.68 0.67 0 175.74 195.87 31917 +1937 19 5.02 -0.98 3.37 0 209.11 195.39 32038 +1937 20 5.37 -0.63 3.72 0 213.82 195.89 32161 +1937 21 3.19 -2.81 1.54 0 185.95 198.69 32289 +1937 22 3.13 -2.87 1.48 0.58 185.23 160.71 32419 +1937 23 3.26 -2.74 1.61 0 186.8 201.03 32552 +1937 24 3.37 -2.63 1.72 0 188.13 202.44 32688 +1937 25 2.63 -3.37 0.98 0 179.33 204.28 32827 +1937 26 2.16 -3.84 0.51 0 173.92 206.04 32969 +1937 27 0.1 -5.9 -1.55 0.46 151.85 166.95 33114 +1937 28 -0.7 -6.7 -2.35 0 143.96 211.44 33261 +1937 29 -1.56 -7.56 -3.21 0.18 135.87 171.18 33411 +1937 30 2.24 -3.76 0.59 0.63 174.83 170.92 33564 +1937 31 3 -3 1.35 0.04 183.68 171.81 33718 +1937 32 7.44 1.44 5.79 0 243.52 174.64 33875 +1937 33 2.5 -3.5 0.85 0.31 177.82 135.66 34035 +1937 34 4.44 -1.56 2.79 0 201.52 181.8 34196 +1937 35 1.03 -4.97 -0.62 0 161.49 186.15 34360 +1937 36 2.25 -3.75 0.6 0 174.94 187.94 34526 +1937 37 1.26 -4.74 -0.39 0 163.96 190.99 34694 +1937 38 4.01 -1.99 2.36 0 196.04 191.94 34863 +1937 39 -1 -7 -2.65 0 141.09 197.65 35035 +1937 40 -1.59 -7.59 -3.24 0 135.6 200.6 35208 +1937 41 -0.59 -6.59 -2.24 0 145.02 202.73 35383 +1937 42 2.23 -3.77 0.58 0 174.72 203.61 35560 +1937 43 -1.07 -7.07 -2.72 0 140.43 208.32 35738 +1937 44 0.7 -5.3 -0.95 0 158.01 209.9 35918 +1937 45 2.4 -3.6 0.75 0 176.66 211.44 36099 +1937 46 5.51 -0.49 3.86 0.34 215.72 158.8 36282 +1937 47 4.54 -1.46 2.89 0 202.81 215.36 36466 +1937 48 8.1 2.1 6.45 0 253.71 214.9 36652 +1937 49 9.1 3.1 7.45 0 269.84 216.58 36838 +1937 50 10.85 4.85 9.2 0 300.2 217.14 37026 +1937 51 12.53 6.53 10.88 0 332.04 217.84 37215 +1937 52 8.58 2.58 6.93 0 261.35 225.52 37405 +1937 53 13.1 7.1 11.45 0.03 343.48 166.99 37596 +1937 54 8.67 2.67 7.02 0.22 262.8 173.31 37788 +1937 55 10.75 4.75 9.1 0.44 298.39 173.64 37981 +1937 56 7.08 1.08 5.43 0.09 238.11 178.83 38175 +1937 57 6.17 0.17 4.52 0.79 224.9 181.68 38370 +1937 58 6.6 0.6 4.95 0 231.07 244.74 38565 +1937 59 5.58 -0.42 3.93 0 216.68 248.46 38761 +1937 60 9.53 3.53 7.88 0.37 277.05 185.23 38958 +1937 61 15.17 9.17 13.52 0.06 387.92 181.03 39156 +1937 62 11.52 5.52 9.87 1.25 312.57 187.46 39355 +1937 63 11.12 5.12 9.47 1.35 305.13 190.11 39553 +1937 64 10.32 4.32 8.67 1.23 290.71 193.09 39753 +1937 65 7.77 1.77 6.12 1.85 248.57 197.65 39953 +1937 66 8.06 2.06 6.41 0 253.08 265.92 40154 +1937 67 7.03 1.03 5.38 0 237.37 270.02 40355 +1937 68 9.51 3.51 7.86 0.07 276.71 202.37 40556 +1937 69 10.19 4.19 8.54 0.47 288.42 203.62 40758 +1937 70 11.13 5.13 9.48 0.55 305.31 204.71 40960 +1937 71 7.75 1.75 6.1 1.22 248.26 210.32 41163 +1937 72 9.37 3.37 7.72 0.02 274.35 210.86 41366 +1937 73 6.33 0.33 4.68 0.05 227.18 215.7 41569 +1937 74 7.98 1.98 6.33 0 251.83 288.37 41772 +1937 75 8.9 2.9 7.25 0 266.55 289.89 41976 +1937 76 8.85 2.85 7.2 0 265.73 292.59 42179 +1937 77 10.77 4.77 9.12 0.27 298.75 219.3 42383 +1937 78 9.77 3.77 8.12 0.06 281.14 222.4 42587 +1937 79 11.11 5.11 9.46 0 304.95 297.2 42791 +1937 80 11.76 5.76 10.11 0 317.1 298.65 42996 +1937 81 9.81 3.81 8.16 0.01 281.82 228.21 43200 +1937 82 11.95 5.95 10.3 0.29 320.74 227.62 43404 +1937 83 14.98 8.98 13.33 0.3 383.64 225.18 43608 +1937 84 11.16 5.16 9.51 0.66 305.87 232.35 43812 +1937 85 10.65 4.65 9 0 296.59 313.11 44016 +1937 86 9.52 3.52 7.87 0.4 276.88 237.96 44220 +1937 87 6.06 0.06 4.41 0 223.35 324.52 44424 +1937 88 2.32 -3.68 0.67 0.13 175.74 248.22 44627 +1937 89 1.72 -4.28 0.07 0 168.99 333.86 44831 +1937 90 2.22 -3.78 0.57 0 174.6 335.81 45034 +1937 91 8.63 2.63 6.98 0 262.15 330.4 45237 +1937 92 8.99 2.99 7.34 0 268.03 332.12 45439 +1937 93 8.57 2.57 6.92 0 261.19 334.97 45642 +1937 94 11.12 5.12 9.47 0 305.13 333.04 45843 +1937 95 16.14 10.14 14.49 0.12 410.37 243.7 46045 +1937 96 16.16 10.16 14.51 0.32 410.84 245.21 46246 +1937 97 19.19 13.19 17.54 1.7 488.33 240.77 46446 +1937 98 14.35 8.35 12.7 0 369.76 334.98 46647 +1937 99 17.11 11.11 15.46 1.53 433.92 247.86 46846 +1937 100 14.92 8.92 13.27 0.73 382.3 253.22 47045 +1937 101 15.81 9.81 14.16 0.1 402.61 253.1 47243 +1937 102 12.72 6.72 11.07 0.16 335.82 259.56 47441 +1937 103 8.66 2.66 7.01 0.43 262.64 266.31 47638 +1937 104 11.15 5.15 9.5 0.49 305.68 264.55 47834 +1937 105 11.95 5.95 10.3 0 320.74 353.03 48030 +1937 106 12.15 6.15 10.5 0.19 324.6 265.72 48225 +1937 107 13.37 7.37 11.72 0 349.02 353.49 48419 +1937 108 14.88 8.88 13.23 0 381.41 351.88 48612 +1937 109 12.85 6.85 11.2 0 338.42 357.91 48804 +1937 110 12.16 6.16 10.51 0 324.79 360.72 48995 +1937 111 13.9 7.9 12.25 0 360.11 358.63 49185 +1937 112 17.61 11.61 15.96 0.88 446.5 263.22 49374 +1937 113 14.37 8.37 12.72 0.52 370.19 270.32 49561 +1937 114 12.88 6.88 11.23 0.23 339.03 273.88 49748 +1937 115 11.53 5.53 9.88 0 312.76 369.32 49933 +1937 116 7 1 5.35 0.26 236.93 283.65 50117 +1937 117 5.97 -0.03 4.32 0 222.09 381.01 50300 +1937 118 5.19 -0.81 3.54 0.21 211.39 287.55 50481 +1937 119 5.89 -0.11 4.24 0 220.97 383.7 50661 +1937 120 9.64 3.64 7.99 0 278.91 379.08 50840 +1937 121 18.96 12.96 17.31 0 482.04 358.36 51016 +1937 122 21.68 15.68 20.03 0.18 561.01 262.9 51191 +1937 123 23.05 17.05 21.4 0.01 604.77 259.81 51365 +1937 124 23.02 17.02 21.37 0.01 603.78 260.67 51536 +1937 125 19.43 13.43 17.78 0.43 494.97 270.81 51706 +1937 126 16.15 10.15 14.5 0.17 410.61 278.64 51874 +1937 127 20.01 14.01 18.36 0 511.32 361.04 52039 +1937 128 23.03 17.03 21.38 0 604.11 351.19 52203 +1937 129 20.68 14.68 19.03 0.01 530.79 270.44 52365 +1937 130 14.27 8.27 12.62 1.08 368.03 284.79 52524 +1937 131 14.49 8.49 12.84 0 372.81 380 52681 +1937 132 14.04 8.04 12.39 0.22 363.09 286.42 52836 +1937 133 13.16 7.16 11.51 0 344.71 384.61 52989 +1937 134 18.92 12.92 17.27 0 480.96 370.08 53138 +1937 135 21.8 15.8 20.15 0.72 564.73 270.75 53286 +1937 136 18.08 12.08 16.43 0.06 458.62 280.47 53430 +1937 137 16.15 10.15 14.5 0 410.61 380.1 53572 +1937 138 13.29 7.29 11.64 0 347.37 387.72 53711 +1937 139 14.16 8.16 12.51 0.16 365.66 289.81 53848 +1937 140 19.13 13.13 17.48 0 486.69 373.18 53981 +1937 141 19.45 13.45 17.8 0.44 495.53 279.43 54111 +1937 142 23.78 17.78 22.13 0.24 629.24 267.87 54238 +1937 143 21.35 15.35 19.7 0 550.88 367.08 54362 +1937 144 21.5 15.5 19.85 0 555.46 367 54483 +1937 145 24.76 18.76 23.11 0 663.42 354.4 54600 +1937 146 21.32 15.32 19.67 0 549.96 368.48 54714 +1937 147 23.49 17.49 21.84 0 619.42 360.59 54824 +1937 148 21.91 15.91 20.26 0.08 568.16 275.36 54931 +1937 149 23.72 17.72 22.07 0.1 627.2 270.23 55034 +1937 150 24.55 18.55 22.9 0 655.97 357.11 55134 +1937 151 21.27 15.27 19.62 0 548.44 370.52 55229 +1937 152 25.07 19.07 23.42 0.12 674.55 266.46 55321 +1937 153 26.09 20.09 24.44 0.77 712.3 263.11 55409 +1937 154 24.07 18.07 22.42 0.37 639.2 270.14 55492 +1937 155 22.45 16.45 20.8 1.24 585.26 275.2 55572 +1937 156 22.87 16.87 21.22 0.33 598.86 274.2 55648 +1937 157 21.28 15.28 19.63 0 548.75 371.81 55719 +1937 158 18.62 12.62 16.97 0 472.87 380.96 55786 +1937 159 20.93 14.93 19.28 0.25 538.21 280.11 55849 +1937 160 22.14 16.14 20.49 0 575.39 369.2 55908 +1937 161 20.75 14.75 19.1 0.06 532.86 280.78 55962 +1937 162 20.5 14.5 18.85 0.22 525.5 281.48 56011 +1937 163 22.58 16.58 20.93 0.01 589.44 275.87 56056 +1937 164 25.16 19.16 23.51 0.3 677.81 267.76 56097 +1937 165 28.68 22.68 27.03 0.21 816.28 254.69 56133 +1937 166 27.86 21.86 26.21 0 782.06 344.04 56165 +1937 167 29.71 23.71 28.06 1.73 861.05 250.37 56192 +1937 168 24.53 18.53 22.88 1.84 655.26 270 56214 +1937 169 21 15 19.35 0.84 540.3 280.5 56231 +1937 170 19.11 13.11 17.46 1.2 486.14 285.32 56244 +1937 171 19.59 13.59 17.94 0.17 499.44 284.19 56252 +1937 172 22.14 16.14 20.49 0.71 575.39 277.37 56256 +1937 173 19.96 13.96 18.31 0.31 509.9 283.24 56255 +1937 174 21.58 15.58 19.93 0.01 557.92 278.88 56249 +1937 175 21.52 15.52 19.87 0.01 556.07 279.02 56238 +1937 176 21.69 15.69 20.04 0.21 561.31 278.52 56223 +1937 177 17.4 11.4 15.75 0.54 441.18 289.09 56203 +1937 178 19.17 13.17 17.52 0.15 487.78 285.03 56179 +1937 179 19.76 13.76 18.11 0 504.22 378 56150 +1937 180 17.74 11.74 16.09 0.01 449.83 288.18 56116 +1937 181 18.57 12.57 16.92 0.78 471.54 286.23 56078 +1937 182 21.18 15.18 19.53 0.06 545.72 279.54 56035 +1937 183 22.29 16.29 20.64 0.01 580.15 276.31 55987 +1937 184 23.52 17.52 21.87 0.62 620.43 272.52 55935 +1937 185 25.63 19.63 23.98 0 695.06 354.06 55879 +1937 186 23.05 17.05 21.4 0 604.77 364.93 55818 +1937 187 24.81 18.81 23.16 0.07 665.2 268.01 55753 +1937 188 25.78 19.78 24.13 0.19 700.65 264.51 55684 +1937 189 24.88 18.88 23.23 0.24 667.71 267.45 55611 +1937 190 24.97 18.97 23.32 0.06 670.94 266.88 55533 +1937 191 23.46 17.46 21.81 0.07 618.41 271.52 55451 +1937 192 20.02 14.02 18.37 0 511.61 374.54 55366 +1937 193 25.31 19.31 23.66 0 683.28 353.51 55276 +1937 194 28.2 22.2 26.55 0.62 796.1 254.36 55182 +1937 195 23.9 17.9 22.25 0.2 633.35 269.37 55085 +1937 196 21.15 15.15 19.5 0.09 544.81 277.07 54984 +1937 197 17.77 11.77 16.12 1.13 450.6 285 54879 +1937 198 17.01 11.01 15.36 1.24 431.44 286.32 54770 +1937 199 20.93 14.93 19.28 0.86 538.21 276.74 54658 +1937 200 24.54 18.54 22.89 0.72 655.61 265.85 54542 +1937 201 25.55 19.55 23.9 0.02 692.1 262.15 54423 +1937 202 25.89 19.89 24.24 0.16 704.76 260.57 54301 +1937 203 24.73 18.73 23.08 0.53 662.35 264.11 54176 +1937 204 25.16 19.16 23.51 1.51 677.81 262.33 54047 +1937 205 25.3 19.3 23.65 0.11 682.91 261.49 53915 +1937 206 21.53 15.53 19.88 0 556.38 363.33 53780 +1937 207 18.77 12.77 17.12 0.69 476.9 278.95 53643 +1937 208 16.48 10.48 14.83 0.8 418.5 283.43 53502 +1937 209 22.69 16.69 21.04 0.71 593 267.79 53359 +1937 210 20 14 18.35 1.1 511.04 274.54 53213 +1937 211 21.74 15.74 20.09 1.28 562.86 269.43 53064 +1937 212 19.78 13.78 18.13 1.29 504.78 273.91 52913 +1937 213 20.93 14.93 19.28 0.28 538.21 270.43 52760 +1937 214 16.33 10.33 14.68 0.14 414.89 280.39 52604 +1937 215 20.06 14.06 18.41 0.92 512.76 271.57 52445 +1937 216 21.69 15.69 20.04 0 561.31 355.47 52285 +1937 217 20 14 18.35 0.03 511.04 270.29 52122 +1937 218 21.64 15.64 19.99 0 559.77 353.96 51958 +1937 219 24.18 18.18 22.53 0 643.01 343.17 51791 +1937 220 23.44 17.44 21.79 0.03 617.74 258.93 51622 +1937 221 29.29 23.29 27.64 0.28 842.55 237.85 51451 +1937 222 25.46 19.46 23.81 0.04 688.78 251.14 51279 +1937 223 24.54 18.54 22.89 0.01 655.61 253.26 51105 +1937 224 23.77 17.77 22.12 0.02 628.9 254.85 50929 +1937 225 24.71 18.71 23.06 0.85 661.64 251.14 50751 +1937 226 23.8 17.8 22.15 1.94 629.93 253.1 50572 +1937 227 23.74 17.74 22.09 0.03 627.88 252.34 50392 +1937 228 22.76 16.76 21.11 0.09 595.27 254.27 50210 +1937 229 22.47 16.47 20.82 1.29 585.9 254.17 50026 +1937 230 20.33 14.33 18.68 0 520.54 345 49842 +1937 231 17.74 11.74 16.09 0 449.83 351.29 49656 +1937 232 22.9 16.9 21.25 0 599.84 333.31 49469 +1937 233 24.32 18.32 22.67 0.16 647.88 244.84 49280 +1937 234 23.58 17.58 21.93 1.69 622.45 245.99 49091 +1937 235 23.64 17.64 21.99 0.56 624.48 244.74 48900 +1937 236 22.76 16.76 21.11 0.02 595.27 246.16 48709 +1937 237 22.74 16.74 21.09 0.39 594.62 245.01 48516 +1937 238 22.87 16.87 21.22 0.16 598.86 243.44 48323 +1937 239 19.32 13.32 17.67 0.06 491.92 251.08 48128 +1937 240 15.38 9.38 13.73 1.43 392.69 257.55 47933 +1937 241 19.27 13.27 17.62 2.33 490.54 248.58 47737 +1937 242 18.81 12.81 17.16 2.72 477.98 248.28 47541 +1937 243 21.51 15.51 19.86 0.89 555.77 240.69 47343 +1937 244 18.46 12.46 16.81 0.87 468.61 246.25 47145 +1937 245 16.41 10.41 14.76 0.24 416.81 248.85 46947 +1937 246 18.77 12.77 17.12 0.68 476.9 242.75 46747 +1937 247 16.74 10.74 15.09 1.06 424.8 245.35 46547 +1937 248 18.87 12.87 17.22 0.25 479.6 239.71 46347 +1937 249 22.64 16.64 20.99 0.05 591.38 229.45 46146 +1937 250 20.1 14.1 18.45 0.25 513.9 234.09 45945 +1937 251 20.71 14.71 19.06 0.62 531.67 231.16 45743 +1937 252 19.08 13.08 17.43 0.1 485.32 233.11 45541 +1937 253 18.87 12.87 17.22 0.72 479.6 231.96 45339 +1937 254 19.67 13.67 18.02 0.14 501.68 228.72 45136 +1937 255 18.22 12.22 16.57 0.7 462.28 229.99 44933 +1937 256 20.67 14.67 19.02 0 530.49 297.64 44730 +1937 257 17.8 11.8 16.15 0 451.37 303.31 44527 +1937 258 11.66 5.66 10.01 0.96 315.21 235.31 44323 +1937 259 14.03 8.03 12.38 0.41 362.88 230.17 44119 +1937 260 12.36 6.36 10.71 0.09 328.69 230.7 43915 +1937 261 15.24 9.24 13.59 1.5 389.5 224.67 43711 +1937 262 17.55 11.55 15.9 0.36 444.98 219.01 43507 +1937 263 17.46 11.46 15.81 0 442.7 289.78 43303 +1937 264 19.45 13.45 17.8 0 495.53 282.29 43099 +1937 265 21.82 15.82 20.17 0.31 565.35 205.01 42894 +1937 266 19.93 13.93 18.28 0 509.04 276.29 42690 +1937 267 22.52 16.52 20.87 0.02 587.51 199.72 42486 +1937 268 24.13 18.13 22.48 0.22 641.27 194.04 42282 +1937 269 23 17 21.35 0.45 603.12 194.99 42078 +1937 270 24.03 18.03 22.38 0.42 637.82 190.66 41875 +1937 271 21.84 15.84 20.19 0.75 565.97 193.83 41671 +1937 272 19.22 13.22 17.57 0 489.16 262.77 41468 +1937 273 16.6 10.6 14.95 0.04 421.4 199.67 41265 +1937 274 14.83 8.83 13.18 0 380.3 267.08 41062 +1937 275 16.35 10.35 14.7 0 415.37 261.37 40860 +1937 276 11.43 5.43 9.78 0 310.88 267.3 40658 +1937 277 14.23 8.23 12.58 0 367.17 260.06 40456 +1937 278 14.58 8.58 12.93 0.91 374.78 192.43 40255 +1937 279 12.66 6.66 11.01 0.75 334.62 192.75 40054 +1937 280 12.53 6.53 10.88 0.02 332.04 190.9 39854 +1937 281 16.32 10.32 14.67 0.05 414.65 183.93 39654 +1937 282 16.8 10.8 15.15 0 426.27 241.6 39455 +1937 283 16.71 10.71 15.06 0.02 424.07 179.26 39256 +1937 284 16.64 10.64 14.99 0 422.37 236.18 39058 +1937 285 14.99 8.99 13.34 0 383.87 236.59 38861 +1937 286 15.18 9.18 13.53 0.09 388.14 175.15 38664 +1937 287 12.56 6.56 10.91 0 332.64 234.81 38468 +1937 288 14.25 8.25 12.6 0 367.6 229.43 38273 +1937 289 15.58 9.58 13.93 0 397.27 224.6 38079 +1937 290 15.68 9.68 14.03 0 399.59 221.62 37885 +1937 291 16.95 10.95 15.3 0.26 429.96 162.53 37693 +1937 292 10.31 4.31 8.66 0 290.53 224.12 37501 +1937 293 9.21 3.21 7.56 0.4 271.67 167 37311 +1937 294 11.16 5.16 9.51 0.03 305.87 163.06 37121 +1937 295 13.41 7.41 11.76 0 349.85 211.55 36933 +1937 296 11.37 5.37 9.72 0.25 309.76 158.8 36745 +1937 297 11.76 5.76 10.11 0 317.1 208.51 36560 +1937 298 14.93 8.93 13.28 0 382.52 201.47 36375 +1937 299 15.41 9.41 13.76 0.16 393.37 148.5 36191 +1937 300 16 10 14.35 0.11 407.06 145.85 36009 +1937 301 15.6 9.6 13.95 0 397.74 192.64 35829 +1937 302 17.47 11.47 15.82 0 442.95 187.04 35650 +1937 303 16.57 10.57 14.92 0.46 420.67 139.54 35472 +1937 304 12.02 6.02 10.37 0 322.08 190.07 35296 +1937 305 1.27 -4.73 -0.38 0 164.07 196.81 35122 +1937 306 7.21 1.21 5.56 0.23 240.06 142.58 34950 +1937 307 7.67 1.67 6.02 0.17 247.03 140.38 34779 +1937 308 2.92 -3.08 1.27 0 182.73 188.23 34610 +1937 309 2.41 -3.59 0.76 1.35 176.78 139.65 34444 +1937 310 5.35 -0.65 3.7 0.78 213.54 136.26 34279 +1937 311 3.7 -2.3 2.05 0.77 192.17 135.49 34116 +1937 312 4.9 -1.1 3.25 0.04 207.52 132.86 33956 +1937 313 6 0 4.35 0 222.51 174.18 33797 +1937 314 9.47 3.47 7.82 0 276.03 169.24 33641 +1937 315 9.92 3.92 8.27 0 283.72 166.29 33488 +1937 316 11.77 5.77 10.12 0.08 317.3 121.67 33337 +1937 317 13.01 7.01 11.36 0.37 341.66 119.02 33188 +1937 318 8.49 2.49 6.84 0 259.9 160.92 33042 +1937 319 11.59 5.59 9.94 0.15 313.89 117.22 32899 +1937 320 3.91 -2.09 2.26 0 194.79 160.75 32758 +1937 321 4.34 -1.66 2.69 0 200.23 158.35 32620 +1937 322 6.7 0.7 5.05 0 232.52 154.88 32486 +1937 323 8.24 2.24 6.59 0 255.92 152.06 32354 +1937 324 7.41 1.41 5.76 0 243.07 150.68 32225 +1937 325 6.96 0.96 5.31 0 236.34 149.3 32100 +1937 326 8 2 6.35 0 252.14 147.06 31977 +1937 327 6.18 0.18 4.53 0 225.05 146.56 31858 +1937 328 2.69 -3.31 1.04 0 180.03 146.75 31743 +1937 329 9.93 3.93 8.28 0 283.89 140.19 31631 +1937 330 9.82 3.82 8.17 2.96 282 104.15 31522 +1937 331 14.17 8.17 12.52 0.87 365.87 99.99 31417 +1937 332 10.08 4.08 8.43 0.27 286.5 101.79 31316 +1937 333 7.51 1.51 5.86 0.41 244.59 102.52 31218 +1937 334 11.04 5.04 9.39 0 303.66 132.74 31125 +1937 335 9.25 3.25 7.6 0.05 272.34 99.83 31035 +1937 336 9.04 3.04 7.39 0.09 268.85 99.16 30949 +1937 337 11.24 5.24 9.59 0.29 307.35 96.54 30867 +1937 338 9.83 3.83 8.18 0 282.17 129.01 30790 +1937 339 10.43 4.43 8.78 0.56 292.66 95.81 30716 +1937 340 6.37 0.37 4.72 0 227.75 130.05 30647 +1937 341 8.21 2.21 6.56 0 255.44 127.87 30582 +1937 342 6.21 0.21 4.56 0.16 225.47 96.36 30521 +1937 343 3.5 -2.5 1.85 0 189.71 129.24 30465 +1937 344 0.96 -5.04 -0.69 0.06 160.75 97.02 30413 +1937 345 0.6 -5.4 -1.05 0 156.97 129.08 30366 +1937 346 1.07 -4.93 -0.58 3.54 161.92 96.24 30323 +1937 347 2.18 -3.82 0.53 0.51 174.15 95.4 30284 +1937 348 1.03 -4.97 -0.62 3.49 161.49 95.54 30251 +1937 349 1.25 -4.75 -0.4 0.57 163.85 95.18 30221 +1937 350 0.56 -5.44 -1.09 0.01 156.56 95.15 30197 +1937 351 3.15 -2.85 1.5 0.01 185.47 94.07 30177 +1937 352 1.24 -4.76 -0.41 0 163.74 126.25 30162 +1937 353 7.17 1.17 5.52 0.01 239.46 92.19 30151 +1937 354 2.31 -3.69 0.66 0 175.63 125.65 30145 +1937 355 0.39 -5.61 -1.26 0.53 154.8 94.89 30144 +1937 356 2.95 -3.05 1.3 0.03 183.09 94.02 30147 +1937 357 5.31 -0.69 3.66 0 213 124.13 30156 +1937 358 5.21 -0.79 3.56 0 211.65 124.28 30169 +1937 359 -0.3 -6.3 -1.95 0 147.86 127.11 30186 +1937 360 -1.96 -7.96 -3.61 0 132.25 128.12 30208 +1937 361 -1.15 -7.15 -2.8 0.47 139.68 141.26 30235 +1937 362 -2.68 -8.68 -4.33 0 125.93 174.26 30267 +1937 363 -0.02 -6.02 -1.67 0.06 150.64 141.79 30303 +1937 364 -1.37 -7.37 -3.02 0 137.62 174.85 30343 +1937 365 -2.91 -8.91 -4.56 0 123.97 175.92 30388 +1938 1 -2.88 -8.88 -4.53 0 124.22 176.74 30438 +1938 2 -2.91 -8.91 -4.56 0 123.97 177.41 30492 +1938 3 -3.57 -9.57 -5.22 0 118.49 178.5 30551 +1938 4 -1.56 -7.56 -3.21 0 135.87 178.62 30614 +1938 5 -2.63 -8.63 -4.28 0 126.36 179.57 30681 +1938 6 3.54 -2.46 1.89 0 190.2 177.14 30752 +1938 7 2.79 -3.21 1.14 0 181.2 177.87 30828 +1938 8 2.14 -3.86 0.49 0 173.69 179.3 30907 +1938 9 0.25 -5.75 -1.4 0 153.37 181.31 30991 +1938 10 2.19 -3.81 0.54 0 174.26 181.29 31079 +1938 11 5.29 -0.71 3.64 0.89 212.73 103.36 31171 +1938 12 2.56 -3.44 0.91 0 178.51 140.4 31266 +1938 13 0.3 -5.7 -1.35 0.83 153.88 107.36 31366 +1938 14 0.18 -5.82 -1.47 0 152.66 144.69 31469 +1938 15 2.2 -3.8 0.55 0 174.37 145.15 31575 +1938 16 2.37 -3.63 0.72 1.24 176.32 109.77 31686 +1938 17 5.02 -0.98 3.37 0 209.11 146.48 31800 +1938 18 4.51 -1.49 2.86 0 202.42 148.69 31917 +1938 19 2.97 -3.03 1.32 0.07 183.33 113.66 32038 +1938 20 3.23 -2.77 1.58 0 186.44 152.99 32161 +1938 21 4.11 -1.89 2.46 0 197.3 154.46 32289 +1938 22 7.34 1.34 5.69 0 242.01 153.94 32419 +1938 23 6.28 0.28 4.63 0 226.47 156.5 32552 +1938 24 6.34 0.34 4.69 0 227.32 158.51 32688 +1938 25 6.45 0.45 4.8 0 228.9 160.3 32827 +1938 26 8.52 2.52 6.87 0 260.38 160.53 32969 +1938 27 7.44 1.44 5.79 0 243.52 163.43 33114 +1938 28 7.96 1.96 6.31 0.01 251.52 123.89 33261 +1938 29 4.12 -1.88 2.47 0 197.43 170.46 33411 +1938 30 2.29 -3.71 0.64 0 175.4 173.87 33564 +1938 31 -1.13 -7.13 -2.78 0 139.86 178.1 33718 +1938 32 -3.05 -9.05 -4.7 0 122.79 181.11 33875 +1938 33 -1.41 -7.41 -3.06 0 137.25 183.03 34035 +1938 34 2.16 -3.84 0.51 0 173.92 183.31 34196 +1938 35 2.13 -3.87 0.48 0 173.58 185.49 34360 +1938 36 5.72 -0.28 4.07 0 218.61 185.48 34526 +1938 37 7.13 1.13 5.48 0.15 238.86 140.04 34694 +1938 38 3.86 -2.14 2.21 0.25 194.16 144.03 34863 +1938 39 5.45 -0.55 3.8 0 214.9 193.45 35035 +1938 40 2.53 -3.47 0.88 0 178.16 198.21 35208 +1938 41 0.89 -5.11 -0.76 0.16 160.01 151.41 35383 +1938 42 1.51 -4.49 -0.14 0.34 166.68 153.06 35560 +1938 43 2.81 -3.19 1.16 0.11 181.43 154.45 35738 +1938 44 4.97 -1.03 3.32 0 208.45 206.88 35918 +1938 45 6.2 0.2 4.55 0.02 225.33 156.34 36099 +1938 46 4.31 -1.69 2.66 0 199.85 212.72 36282 +1938 47 8.46 2.46 6.81 0 259.42 211.74 36466 +1938 48 7.95 1.95 6.3 0.07 251.36 161.29 36652 +1938 49 10.01 4.01 8.36 0 285.28 215.54 36838 +1938 50 8.82 2.82 7.17 0 265.24 219.52 37026 +1938 51 11.32 5.32 9.67 0 308.83 219.46 37215 +1938 52 6.55 0.55 4.9 0 230.34 227.61 37405 +1938 53 1.37 -4.63 -0.28 0 165.15 234.86 37596 +1938 54 1.63 -4.37 -0.02 0 167.99 237.46 37788 +1938 55 3.11 -2.89 1.46 0 184.99 239.36 37981 +1938 56 2.43 -3.57 0.78 0.3 177.01 181.96 38175 +1938 57 5.57 -0.43 3.92 0 216.54 242.83 38370 +1938 58 5.25 -0.75 3.6 0 212.19 246.06 38565 +1938 59 6.1 0.1 4.45 0 223.91 247.95 38761 +1938 60 6.94 0.94 5.29 0.05 236.04 187.48 38958 +1938 61 5.37 -0.63 3.72 0 213.82 254.5 39156 +1938 62 6.36 0.36 4.71 0.24 227.61 192.22 39355 +1938 63 6.95 0.95 5.3 0 236.19 258.68 39553 +1938 64 7.78 1.78 6.13 0.09 248.73 195.48 39753 +1938 65 6.98 0.98 5.33 0 236.63 264.43 39953 +1938 66 11.35 5.35 9.7 0 309.39 261.54 40154 +1938 67 10.28 4.28 8.63 0.52 290 199.45 40355 +1938 68 7.21 1.21 5.56 0.22 240.06 204.51 40556 +1938 69 7.51 1.51 5.86 0.28 244.59 206.22 40758 +1938 70 6.74 0.74 5.09 0.37 233.1 209.02 40960 +1938 71 6.49 0.49 4.84 0.08 229.48 211.43 41163 +1938 72 8.54 2.54 6.89 0.03 260.7 211.69 41366 +1938 73 9.3 3.3 7.65 0.02 273.17 212.92 41569 +1938 74 10.39 4.39 8.74 0 291.95 285.07 41772 +1938 75 12.86 6.86 11.21 0 338.63 283.82 41976 +1938 76 13.29 7.29 11.64 0 347.37 285.65 42179 +1938 77 12.9 6.9 11.25 0 339.43 288.89 42383 +1938 78 15.71 9.71 14.06 0.04 400.28 214.58 42587 +1938 79 17.4 11.4 15.75 0 441.18 285.01 42791 +1938 80 12.69 6.69 11.04 0 335.22 297.05 42996 +1938 81 15.65 9.65 14 0 398.89 293.83 43200 +1938 82 14.05 8.05 12.4 0 363.3 299.67 43404 +1938 83 6.89 0.89 5.24 0 235.3 313.44 43608 +1938 84 9.03 3.03 7.38 0 268.69 313.09 43812 +1938 85 17.35 11.35 15.7 0.23 439.92 224.87 44016 +1938 86 17.5 11.5 15.85 0 443.71 301.78 44220 +1938 87 15.73 9.73 14.08 0 400.75 308.35 44424 +1938 88 16.93 10.93 15.28 0 429.47 307.86 44627 +1938 89 21.17 15.17 19.52 0 545.42 298.53 44831 +1938 90 19.67 13.67 18.02 0.52 501.68 228.89 45034 +1938 91 10.82 4.82 9.17 0 299.65 326.96 45237 +1938 92 11.8 5.8 10.15 0.02 317.87 245.62 45439 +1938 93 11.15 5.15 9.5 0.34 305.68 248.13 45642 +1938 94 10.44 4.44 8.79 0 292.83 334.2 45843 +1938 95 12.61 6.61 10.96 0 333.63 332.46 46045 +1938 96 10.22 4.22 8.57 0 288.95 338.83 46246 +1938 97 10.12 4.12 8.47 0 287.2 341.05 46446 +1938 98 12.67 6.67 11.02 0 334.82 338.43 46647 +1938 99 10.76 4.76 9.11 0 298.57 343.95 46846 +1938 100 10.53 4.53 8.88 0 294.44 346.3 47045 +1938 101 11.63 5.63 9.98 0 314.64 346.27 47243 +1938 102 12.31 6.31 10.66 0 327.71 346.88 47441 +1938 103 13.44 7.44 11.79 0.12 350.47 259.83 47638 +1938 104 12.57 6.57 10.92 0.32 332.83 262.52 47834 +1938 105 15.51 9.51 13.86 0.77 395.66 259.06 48030 +1938 106 14.85 8.85 13.2 0.54 380.74 261.43 48225 +1938 107 13.46 7.46 11.81 0.16 350.88 264.97 48419 +1938 108 14.83 8.83 13.18 0 380.3 352 48612 +1938 109 11.61 5.61 9.96 0.06 314.26 270.28 48804 +1938 110 9.24 3.24 7.59 0 272.17 366.01 48995 +1938 111 8.42 2.42 6.77 0.04 258.78 276.68 49185 +1938 112 8.76 2.76 7.11 0 264.26 369.91 49374 +1938 113 9.07 3.07 7.42 0 269.35 370.77 49561 +1938 114 9.3 3.3 7.65 0.15 273.17 278.92 49748 +1938 115 4.42 -1.58 2.77 0 201.26 380.41 49933 +1938 116 4.45 -1.55 2.8 0 201.65 381.64 50117 +1938 117 3.32 -2.68 1.67 0.64 187.52 288.26 50300 +1938 118 4.09 -1.91 2.44 0 197.05 384.79 50481 +1938 119 3.68 -2.32 2.03 0 191.93 386.52 50661 +1938 120 7.26 1.26 5.61 0 240.81 382.94 50840 +1938 121 15.93 9.93 14.28 0 405.42 366.84 51016 +1938 122 15.02 9.02 13.37 0.02 384.54 277.72 51191 +1938 123 14.48 8.48 12.83 0 372.59 372.61 51365 +1938 124 15.74 9.74 14.09 0 400.98 370.6 51536 +1938 125 19.07 13.07 17.42 0 485.04 362.21 51706 +1938 126 23.82 17.82 22.17 0 630.61 346.26 51874 +1938 127 25.79 19.79 24.14 0 701.02 338.65 52039 +1938 128 21.97 15.97 20.32 0.1 570.04 266.4 52203 +1938 129 19.79 13.79 18.14 0.58 505.07 272.67 52365 +1938 130 19.67 13.67 18.02 0 501.68 364.72 52524 +1938 131 14.99 8.99 13.34 0 383.87 378.79 52681 +1938 132 10.53 4.53 8.88 0.15 294.44 291.95 52836 +1938 133 12.1 6.1 10.45 0 323.63 386.88 52989 +1938 134 15.85 9.85 14.2 0.02 403.54 284.13 53138 +1938 135 17.69 11.69 16.04 0 448.55 374.47 53286 +1938 136 13.36 7.36 11.71 0.05 348.81 289.68 53430 +1938 137 12.03 6.03 10.38 1.12 322.28 292.37 53572 +1938 138 8.48 2.48 6.83 0.02 259.74 297.82 53711 +1938 139 11.45 5.45 9.8 1.15 311.26 294.25 53848 +1938 140 9.51 3.51 7.86 2.54 276.71 297.39 53981 +1938 141 10.29 4.29 8.64 0.92 290.18 296.66 54111 +1938 142 11.5 5.5 9.85 0.53 312.19 295.27 54238 +1938 143 14.22 8.22 12.57 0.17 366.95 291.19 54362 +1938 144 11.87 5.87 10.22 0 319.2 393.97 54483 +1938 145 15.12 9.12 13.47 0 386.79 386.99 54600 +1938 146 16.13 10.13 14.48 0 410.13 384.74 54714 +1938 147 18.24 12.24 16.59 1.21 462.8 284.39 54824 +1938 148 17.46 11.46 15.81 1.01 442.7 286.42 54931 +1938 149 19.83 13.83 18.18 1.58 506.2 281.11 55034 +1938 150 18.33 12.33 16.68 0.01 465.17 284.95 55134 +1938 151 21.01 15.01 19.36 0 540.6 371.46 55229 +1938 152 25.84 19.84 24.19 0 702.89 351.77 55321 +1938 153 23.96 17.96 22.31 0 635.41 360.34 55409 +1938 154 23.53 17.53 21.88 0.02 620.77 271.83 55492 +1938 155 23.59 17.59 21.94 0 622.79 362.37 55572 +1938 156 22.84 16.84 21.19 0 597.88 365.72 55648 +1938 157 23.38 17.38 21.73 0.01 615.73 272.78 55719 +1938 158 23.16 17.16 21.51 0 608.4 364.77 55786 +1938 159 26.95 20.95 25.3 0.03 745.51 260.99 55849 +1938 160 23.82 17.82 22.17 0.58 630.61 271.85 55908 +1938 161 24.04 18.04 22.39 0.01 638.16 271.21 55962 +1938 162 24.14 18.14 22.49 0.07 641.62 270.93 56011 +1938 163 24.38 18.38 22.73 0 649.98 360.42 56056 +1938 164 25.15 19.15 23.5 0 677.45 357.05 56097 +1938 165 23.9 17.9 22.25 0 633.35 362.6 56133 +1938 166 23.75 17.75 22.1 1.28 628.22 272.48 56165 +1938 167 27.53 21.53 25.88 0.67 768.63 259.27 56192 +1938 168 21.56 15.56 19.91 0.02 557.3 278.96 56214 +1938 169 24.71 18.71 23.06 0.11 661.64 269.41 56231 +1938 170 24.99 18.99 23.34 0.49 671.66 268.48 56244 +1938 171 21.7 15.7 20.05 0.39 561.62 278.63 56252 +1938 172 19.73 13.73 18.08 0.28 503.37 283.83 56256 +1938 173 20.12 14.12 18.47 0 514.48 377.11 56255 +1938 174 20.93 14.93 19.28 0 538.21 374.2 56249 +1938 175 24.88 18.88 23.23 0 667.71 358.39 56238 +1938 176 22.25 16.25 20.6 0.56 578.87 276.93 56223 +1938 177 19.53 13.53 17.88 0.05 497.76 284.13 56203 +1938 178 19.1 13.1 17.45 0.01 485.86 285.2 56179 +1938 179 14.71 8.71 13.06 0 377.64 392.62 56150 +1938 180 17.98 11.98 16.33 0 456.02 383.53 56116 +1938 181 16.28 10.28 14.63 0 413.7 388.33 56078 +1938 182 18.4 12.4 16.75 0.02 467.02 286.52 56035 +1938 183 17.66 11.66 16.01 0 447.78 384.08 55987 +1938 184 19.08 13.08 17.43 0 485.32 379.55 55935 +1938 185 22.87 16.87 21.22 0 598.86 365.9 55879 +1938 186 25.6 19.6 23.95 0.01 693.95 265.46 55818 +1938 187 22.58 16.58 20.93 0 589.44 366.61 55753 +1938 188 22.51 16.51 20.86 0 587.18 366.62 55684 +1938 189 24.49 18.49 22.84 0 653.85 358.31 55611 +1938 190 23.28 17.28 21.63 0 612.39 363.02 55533 +1938 191 23.74 17.74 22.09 0 627.88 360.87 55451 +1938 192 24.1 18.1 22.45 0 640.23 359.07 55366 +1938 193 24.56 18.56 22.91 0 656.32 356.83 55276 +1938 194 24.77 18.77 23.12 0 663.78 355.7 55182 +1938 195 24.08 18.08 22.43 0 639.54 358.41 55085 +1938 196 22.86 16.86 21.21 0 598.53 362.99 54984 +1938 197 25.53 19.53 23.88 0.03 691.36 263.4 54879 +1938 198 30.85 24.85 29.2 0 912.99 322.7 54770 +1938 199 28.41 22.41 26.76 0 804.87 336.25 54658 +1938 200 19.88 13.88 18.23 0.19 507.62 279.14 54542 +1938 201 13.69 7.69 12.04 0.29 355.68 291.74 54423 +1938 202 16.02 10.02 14.37 0 407.53 382.64 54301 +1938 203 17.47 11.47 15.82 0 442.95 378.1 54176 +1938 204 21.15 15.15 19.5 0.25 544.81 274.33 54047 +1938 205 21.56 15.56 19.91 0.43 557.3 272.83 53915 +1938 206 27.55 21.55 25.9 0.02 769.44 253.06 53780 +1938 207 24.37 18.37 22.72 1.08 649.63 263.64 53643 +1938 208 29.28 23.28 27.63 0.29 842.11 245.29 53502 +1938 209 26.74 20.74 25.09 2.1 737.28 254.66 53359 +1938 210 26.44 20.44 24.79 0.02 725.66 255.3 53213 +1938 211 24.79 18.79 23.14 0.28 664.49 260.33 53064 +1938 212 27.57 21.57 25.92 0 770.25 333.4 52913 +1938 213 30.05 24.05 28.4 0 876.27 319.43 52760 +1938 214 26.5 20.5 24.85 0 727.97 337.19 52604 +1938 215 27.49 21.49 25.84 0 767.02 331.77 52445 +1938 216 26.97 20.97 25.32 0 746.3 333.35 52285 +1938 217 22.32 16.32 20.67 0.28 581.1 264.21 52122 +1938 218 24.49 18.49 22.84 0.84 653.85 257.17 51958 +1938 219 24.85 18.85 23.2 1.7 666.63 255.27 51791 +1938 220 19.28 13.28 17.63 0.35 490.81 269.91 51622 +1938 221 20.76 14.76 19.11 0.01 533.15 265.55 51451 +1938 222 20.75 14.75 19.1 0.01 532.86 264.79 51279 +1938 223 22.33 16.33 20.68 0 581.42 346.35 51105 +1938 224 20.53 14.53 18.88 1.35 526.38 263.7 50929 +1938 225 23.5 17.5 21.85 1.36 619.76 254.81 50751 +1938 226 22.4 16.4 20.75 0.34 583.66 257.11 50572 +1938 227 20.29 14.29 18.64 0.43 519.38 261.63 50392 +1938 228 21.75 15.75 20.1 0.04 563.17 257.02 50210 +1938 229 18 12 16.35 0.03 456.53 265 50026 +1938 230 18.46 12.46 16.81 3.13 468.61 263.05 49842 +1938 231 19.46 13.46 17.81 0.51 495.8 259.7 49656 +1938 232 20.6 14.6 18.95 0.98 528.43 255.99 49469 +1938 233 25.03 19.03 23.38 0.28 673.11 242.67 49280 +1938 234 21.72 15.72 20.07 1.08 562.24 251.07 49091 +1938 235 20.03 14.03 18.38 0.8 511.9 254.13 48900 +1938 236 20.77 14.77 19.12 0.43 533.45 251.3 48709 +1938 237 20.18 14.18 18.53 0.26 516.2 251.49 48516 +1938 238 22.99 16.99 21.34 0.28 602.79 243.11 48323 +1938 239 20.38 14.38 18.73 0.21 522 248.65 48128 +1938 240 18.76 12.76 17.11 0.84 476.63 250.98 47933 +1938 241 20.63 14.63 18.98 0 529.31 327.3 47737 +1938 242 21.9 15.9 20.25 0.31 567.85 241.07 47541 +1938 243 21.95 15.95 20.3 0.04 569.41 239.58 47343 +1938 244 18.99 12.99 17.34 0 482.86 326.84 47145 +1938 245 19.29 13.29 17.64 0 491.09 324.15 46947 +1938 246 17.52 11.52 15.87 0.03 444.22 245.27 46747 +1938 247 16.06 10.06 14.41 0.57 408.48 246.59 46547 +1938 248 13.82 7.82 12.17 0.27 358.42 248.82 46347 +1938 249 14.26 8.26 12.61 0 367.81 328.74 46146 +1938 250 11.48 5.48 9.83 0 311.82 332.12 45945 +1938 251 12 6 10.35 0 321.7 329.01 45743 +1938 252 15.72 9.72 14.07 0 400.51 319.23 45541 +1938 253 18.59 12.59 16.94 0.01 472.07 232.53 45339 +1938 254 15.71 9.71 14.06 0.12 400.28 236.22 45136 +1938 255 15.58 9.58 13.93 0 397.27 312.97 44933 +1938 256 15.84 9.84 14.19 0 403.31 310.1 44730 +1938 257 15.16 9.16 13.51 0 387.69 309.41 44527 +1938 258 15.18 9.18 13.53 0 388.14 307 44323 +1938 259 16.39 10.39 14.74 0 416.33 301.9 44119 +1938 260 19.25 13.25 17.6 0 489.98 292.49 43915 +1938 261 19.57 13.57 17.92 0 498.88 289.23 43711 +1938 262 17.62 11.62 15.97 0.7 446.76 218.88 43507 +1938 263 16.88 10.88 15.23 0 428.23 291.13 43303 +1938 264 18.59 12.59 16.94 0 472.07 284.5 43099 +1938 265 19.64 13.64 17.99 0 500.84 279.47 42894 +1938 266 20.46 14.46 18.81 0 524.33 274.85 42690 +1938 267 19.81 13.81 18.16 0 505.63 274 42486 +1938 268 23.07 17.07 21.42 0 605.43 262.15 42282 +1938 269 25.62 19.62 23.97 0 694.69 251.23 42078 +1938 270 22.92 16.92 21.27 0 600.49 257.73 41875 +1938 271 20.65 14.65 19 0.09 529.9 196.31 41671 +1938 272 21.7 15.7 20.05 0 561.62 256.23 41468 +1938 273 18.4 12.4 16.75 0 467.02 262.26 41265 +1938 274 18.63 12.63 16.98 0 473.14 259.11 41062 +1938 275 20.44 14.44 18.79 0.12 523.74 188.99 40860 +1938 276 17.11 11.11 15.46 0.27 433.92 192.85 40658 +1938 277 14.84 8.84 13.19 0.74 380.52 194.22 40456 +1938 278 14.22 8.22 12.57 0.3 366.95 192.91 40255 +1938 279 19.39 13.39 17.74 0.53 493.86 182.93 40054 +1938 280 19.25 13.25 17.6 0.77 489.98 181.26 39854 +1938 281 15.61 9.61 13.96 0.04 397.97 184.93 39654 +1938 282 9.86 3.86 8.21 0.48 282.68 189.62 39455 +1938 283 12.51 6.51 10.86 0 331.65 246.25 39256 +1938 284 12.33 6.33 10.68 0 328.11 243.5 39058 +1938 285 13.53 7.53 11.88 0.01 352.34 179.26 38861 +1938 286 14.21 8.21 12.56 0 366.73 235.17 38664 +1938 287 15.37 9.37 13.72 0.57 392.46 172.73 38468 +1938 288 13.57 7.57 11.92 0 353.17 230.51 38273 +1938 289 10.45 4.45 8.8 0 293.01 232.25 38079 +1938 290 11.59 5.59 9.94 0 313.89 227.89 37885 +1938 291 12.19 6.19 10.54 0.06 325.37 168.27 37693 +1938 292 12.73 6.73 11.08 0.66 336.02 165.69 37501 +1938 293 13.25 7.25 11.6 0 346.55 217.46 37311 +1938 294 14.69 8.69 13.04 0 377.2 212.42 37121 +1938 295 9.34 3.34 7.69 0 273.84 216.75 36933 +1938 296 13.63 7.63 11.98 0 354.42 208.67 36745 +1938 297 11.51 5.51 9.86 0 312.38 208.83 36560 +1938 298 15.18 9.18 13.53 0.22 388.14 150.82 36375 +1938 299 14.52 8.52 12.87 0.04 373.46 149.52 36191 +1938 300 12.28 6.28 10.63 0 327.13 199.83 36009 +1938 301 14.03 8.03 12.38 0 362.88 194.97 35829 +1938 302 17.28 11.28 15.63 0.22 438.16 140.53 35650 +1938 303 13.07 7.07 11.42 0.04 342.87 143.38 35472 +1938 304 15.12 9.12 13.47 0 386.79 185.9 35296 +1938 305 14.5 8.5 12.85 0.25 373.03 138.08 35122 +1938 306 13.27 7.27 11.62 0.29 346.96 137.67 34950 +1938 307 8.24 2.24 6.59 0.01 255.92 139.98 34779 +1938 308 10.06 4.06 8.41 0 286.15 182.24 34610 +1938 309 10.29 4.29 8.64 0 290.18 179.69 34444 +1938 310 11.64 5.64 9.99 0 314.83 175.8 34279 +1938 311 8.64 2.64 6.99 0.15 262.32 132.54 34116 +1938 312 7.16 1.16 5.51 0 239.31 175.38 33956 +1938 313 8.09 2.09 6.44 0 253.55 172.45 33797 +1938 314 8.88 2.88 7.23 0 266.22 169.79 33641 +1938 315 7.61 1.61 5.96 0.17 246.11 126.28 33488 +1938 316 7.09 1.09 5.44 0.52 238.26 124.96 33337 +1938 317 4.77 -1.23 3.12 0.07 205.81 124.61 33188 +1938 318 2.03 -3.97 0.38 0 172.45 165.5 33042 +1938 319 3.02 -2.98 1.37 0 183.92 163.19 32899 +1938 320 2.46 -3.54 0.81 0 177.35 161.63 32758 +1938 321 4.23 -1.77 2.58 0 198.83 158.42 32620 +1938 322 4.99 -1.01 3.34 0 208.72 156.09 32486 +1938 323 7.35 1.35 5.7 0 242.16 152.77 32354 +1938 324 11.39 5.39 9.74 0 310.13 147.2 32225 +1938 325 12.82 6.82 11.17 0 337.82 144.04 32100 +1938 326 13.7 7.7 12.05 0.26 355.89 106.25 31977 +1938 327 9.95 3.95 8.3 0.02 284.24 107.7 31858 +1938 328 12.57 6.57 10.92 0 332.83 139.16 31743 +1938 329 9.01 3.01 7.36 0 268.36 140.97 31631 +1938 330 11.67 5.67 10.02 0.24 315.4 102.89 31522 +1938 331 13.12 7.12 11.47 0 343.89 134.45 31417 +1938 332 15.63 9.63 13.98 0 398.43 130.04 31316 +1938 333 14.15 8.15 12.5 0.06 365.44 98.03 31218 +1938 334 14.4 8.4 12.75 0 370.85 129.38 31125 +1938 335 5.77 -0.23 4.12 0 219.3 135.62 31035 +1938 336 7.41 1.41 5.76 0 243.07 133.44 30949 +1938 337 3.43 -2.57 1.78 0.43 188.86 100.7 30867 +1938 338 1.12 -4.88 -0.53 0 162.45 134.49 30790 +1938 339 3.5 -2.5 1.85 0 189.71 132.49 30716 +1938 340 2.78 -3.22 1.13 0 181.08 132.14 30647 +1938 341 2.41 -3.59 0.76 0 176.78 131.4 30582 +1938 342 3.34 -2.66 1.69 0 187.77 130.16 30521 +1938 343 1.75 -4.25 0.1 0.16 169.32 97.6 30465 +1938 344 5.57 -0.43 3.92 0.12 216.54 95.2 30413 +1938 345 7.09 1.09 5.44 0 238.26 125.53 30366 +1938 346 3.61 -2.39 1.96 0 191.06 127.07 30323 +1938 347 0.79 -5.21 -0.86 0.59 158.96 95.88 30284 +1938 348 -1.95 -7.95 -3.6 0.21 132.33 140.75 30251 +1938 349 -0.84 -6.84 -2.49 0 142.61 172.13 30221 +1938 350 2.75 -3.25 1.1 0.12 180.73 138.4 30197 +1938 351 2.26 -3.74 0.61 0.15 175.06 94.4 30177 +1938 352 4.35 -1.65 2.7 0.69 200.36 93.52 30162 +1938 353 1.33 -4.67 -0.32 0.65 164.72 94.61 30151 +1938 354 -1.83 -7.83 -3.48 0.78 133.41 141.82 30145 +1938 355 -2.95 -8.95 -4.6 0.37 123.63 143.3 30144 +1938 356 -1.48 -7.48 -3.13 0 136.61 174.75 30147 +1938 357 -0.26 -6.26 -1.91 0 148.25 174.32 30156 +1938 358 -1.58 -7.58 -3.23 0 135.69 174.9 30169 +1938 359 -3.5 -9.5 -5.15 0 119.06 175.66 30186 +1938 360 0.65 -5.35 -1 0 157.49 174.34 30208 +1938 361 0.99 -5.01 -0.66 0 161.07 174.35 30235 +1938 362 2.27 -3.73 0.62 0 175.17 173.84 30267 +1938 363 -1.53 -7.53 -3.18 0.24 136.15 144.44 30303 +1938 364 -2.78 -8.78 -4.43 0.18 125.07 145.59 30343 +1938 365 2.69 -3.31 1.04 0.05 180.03 143.86 30388 +1939 1 4.32 -1.68 2.67 0 199.98 175.35 30438 +1939 2 3.83 -2.17 2.18 0.04 193.79 143.39 30492 +1939 3 2.99 -3.01 1.34 0 183.56 176.67 30551 +1939 4 3.91 -2.09 2.26 0 194.79 176.48 30614 +1939 5 6.47 0.47 4.82 0 229.19 174.62 30681 +1939 6 5.95 -0.05 4.3 0 221.81 174.96 30752 +1939 7 6.5 0.5 4.85 0 229.62 132.03 30828 +1939 8 7.58 1.58 5.93 1.42 245.65 99.57 30907 +1939 9 6.54 0.54 4.89 0 230.2 134.73 30991 +1939 10 6.62 0.62 4.97 0 231.36 135.96 31079 +1939 11 6.15 0.15 4.5 0 224.62 137.26 31171 +1939 12 6.07 0.07 4.42 0 223.49 138.31 31266 +1939 13 1.98 -4.02 0.33 0 171.89 142.33 31366 +1939 14 1.37 -4.63 -0.28 0 165.15 144.13 31469 +1939 15 -0.9 -6.9 -2.55 0 142.04 146.63 31575 +1939 16 5.62 -0.38 3.97 0.19 217.23 108.31 31686 +1939 17 4.16 -1.84 2.51 0 197.94 147.01 31800 +1939 18 6.19 0.19 4.54 0 225.19 147.58 31917 +1939 19 10.51 4.51 8.86 0.28 294.08 109.49 32038 +1939 20 10.59 4.59 8.94 0 295.51 147.46 32161 +1939 21 4.88 -1.12 3.23 0 207.26 153.97 32289 +1939 22 6.8 0.8 5.15 0 233.98 154.35 32419 +1939 23 7.75 1.75 6.1 0 248.26 155.37 32552 +1939 24 10.4 4.4 8.75 0 292.12 155.07 32688 +1939 25 6.97 0.97 5.32 0.1 236.48 119.92 32827 +1939 26 1.41 -4.59 -0.24 1.32 165.58 124.1 32969 +1939 27 -1.45 -7.45 -3.1 0.05 136.88 166.71 33114 +1939 28 -0.87 -6.87 -2.52 0.03 142.33 168.09 33261 +1939 29 -0.86 -6.86 -2.51 0.18 142.42 170.23 33411 +1939 30 -2.59 -8.59 -4.24 0 126.7 216.43 33564 +1939 31 -2.37 -8.37 -4.02 0 128.62 218.55 33718 +1939 32 4.74 -1.26 3.09 0 205.42 215.89 33875 +1939 33 4.65 -1.35 3 0 204.24 179.44 34035 +1939 34 8.59 2.59 6.94 0 261.51 178.39 34196 +1939 35 7.36 1.36 5.71 0 242.31 181.62 34360 +1939 36 7.83 1.83 6.18 0 249.5 183.69 34526 +1939 37 4.11 -1.89 2.46 0 197.3 189.12 34694 +1939 38 2.89 -3.11 1.24 0 182.38 192.72 34863 +1939 39 2.73 -3.27 1.08 0.1 180.49 146.58 35035 +1939 40 -1.38 -7.38 -3.03 0 137.53 200.5 35208 +1939 41 -0.38 -6.38 -2.03 0 147.07 202.62 35383 +1939 42 -1.93 -7.93 -3.58 0 132.51 206.03 35560 +1939 43 2.67 -3.33 1.02 0.23 179.79 154.52 35738 +1939 44 1.33 -4.67 -0.32 0.32 164.72 157.13 35918 +1939 45 5.59 -0.41 3.94 0 216.82 208.98 36099 +1939 46 6.5 0.5 4.85 0 229.62 210.86 36282 +1939 47 1.13 -4.87 -0.52 0 162.56 217.84 36466 +1939 48 1.88 -4.12 0.23 0.15 170.77 165.13 36652 +1939 49 5.14 -0.86 3.49 0 210.72 220.45 36838 +1939 50 3.97 -2.03 2.32 0 195.54 224.1 37026 +1939 51 9.27 3.27 7.62 0 272.67 221.95 37215 +1939 52 9.12 3.12 7.47 0 270.17 224.91 37405 +1939 53 9.73 3.73 8.08 0 280.45 227.13 37596 +1939 54 11.36 5.36 9.71 0 309.57 227.78 37788 +1939 55 9.48 3.48 7.83 0.38 276.2 174.83 37981 +1939 56 7.32 1.32 5.67 0.33 241.71 178.65 38175 +1939 57 11.05 5.05 9.4 0 303.84 236.61 38370 +1939 58 17.24 11.24 15.59 0 437.16 229.33 38565 +1939 59 13.36 7.36 11.71 0 348.81 238.76 38761 +1939 60 11.63 5.63 9.98 0 314.64 244.17 38958 +1939 61 9.63 3.63 7.98 0 278.74 249.75 39156 +1939 62 7.72 1.72 6.07 0 247.8 254.82 39355 +1939 63 4.75 -1.25 3.1 0.05 205.55 195.69 39553 +1939 64 7.68 1.68 6.03 0 247.19 260.76 39753 +1939 65 5.91 -0.09 4.26 0 221.25 265.58 39953 +1939 66 5.64 -0.36 3.99 0 217.5 268.61 40154 +1939 67 4.52 -1.48 2.87 0.09 202.55 204.48 40355 +1939 68 4 -2 2.35 0 195.92 276.03 40556 +1939 69 6.08 0.08 4.43 0.4 223.63 207.43 40758 +1939 70 6.92 0.92 5.27 0.12 235.74 208.87 40960 +1939 71 3.08 -2.92 1.43 0 184.64 285.35 41163 +1939 72 3.35 -2.65 1.7 0 187.89 287.96 41366 +1939 73 3.83 -2.17 2.18 0 193.79 290.21 41569 +1939 74 3.39 -2.61 1.74 0 188.37 293.41 41772 +1939 75 5.21 -0.79 3.56 0.02 211.65 220.75 41976 +1939 76 5 -1 3.35 0 208.85 297.22 42179 +1939 77 5.78 -0.22 4.13 0 219.44 298.99 42383 +1939 78 7.08 1.08 5.43 0 238.11 300.14 42587 +1939 79 9.71 3.71 8.06 0 280.11 299.34 42791 +1939 80 10.41 4.41 8.76 0.03 292.3 225.61 42996 +1939 81 10.4 4.4 8.75 0.01 292.12 227.54 43200 +1939 82 7.83 1.83 6.18 0.05 249.5 232.29 43404 +1939 83 5.61 -0.39 3.96 0.05 217.09 236.23 43608 +1939 84 6.77 0.77 5.12 0 233.54 316.14 43812 +1939 85 10.2 4.2 8.55 0.26 288.6 235.37 44016 +1939 86 5.3 -0.7 3.65 0.37 212.87 242.15 44220 +1939 87 1.59 -4.41 -0.06 0.75 167.55 246.93 44424 +1939 88 -0.23 -6.23 -1.88 0 148.55 333.21 44627 +1939 89 -0.51 -6.51 -2.16 0.02 145.8 281.32 44831 +1939 90 -1.46 -7.46 -3.11 0.44 136.79 284.5 45034 +1939 91 10.56 4.56 8.91 0.01 294.97 274.76 45237 +1939 92 7.78 1.78 6.13 0 248.73 333.88 45439 +1939 93 4.43 -1.57 2.78 0 201.39 340.35 45642 +1939 94 5.66 -0.34 4.01 0 217.78 341.09 45843 +1939 95 8.53 2.53 6.88 0 260.54 339.36 46045 +1939 96 10.07 4.07 8.42 0 286.32 339.08 46246 +1939 97 11.63 5.63 9.98 0 314.64 338.43 46446 +1939 98 11.19 5.19 9.54 0 306.42 341.18 46647 +1939 99 13.31 7.31 11.66 0 347.78 339.15 46846 +1939 100 14.66 8.66 13.01 0 376.54 338.21 47045 +1939 101 18.82 12.82 17.17 0 478.25 329.63 47243 +1939 102 17.57 11.57 15.92 0 445.49 334.9 47441 +1939 103 15.87 9.87 14.22 0 404.01 340.99 47638 +1939 104 17.9 11.9 16.25 0 453.94 337.57 47834 +1939 105 17.51 11.51 15.86 0 443.96 340.37 48030 +1939 106 21.94 15.94 20.29 0 569.1 328.43 48225 +1939 107 25.11 19.11 23.46 0 676 317.99 48419 +1939 108 23.81 17.81 22.16 0 630.27 324.81 48612 +1939 109 26.12 20.12 24.47 0 713.44 316.76 48804 +1939 110 26.35 20.35 24.7 0 722.21 317.01 48995 +1939 111 23.29 17.29 21.64 0 612.72 331.05 49185 +1939 112 21.64 15.64 19.99 0 559.77 338.47 49374 +1939 113 20.7 14.7 19.05 0 531.38 342.93 49561 +1939 114 19.86 13.86 18.21 0.43 507.05 260.31 49748 +1939 115 17.52 11.52 15.87 0.16 444.22 266.54 49933 +1939 116 14.22 8.22 12.57 0 366.95 364.89 50117 +1939 117 14.59 8.59 12.94 0 375 365.34 50300 +1939 118 10.96 4.96 9.31 0 302.2 374.29 50481 +1939 119 14.12 8.12 12.47 0 364.8 368.92 50661 +1939 120 13.81 7.81 12.16 0 358.21 370.8 50840 +1939 121 12.72 6.72 11.07 2.58 335.82 280.73 51016 +1939 122 10.2 4.2 8.55 0.36 288.6 285.34 51191 +1939 123 13.75 7.75 12.1 0.05 356.94 280.72 51365 +1939 124 15.25 9.25 13.6 0.24 389.73 278.88 51536 +1939 125 13.4 7.4 11.75 0 349.64 377.16 51706 +1939 126 16.73 10.73 15.08 0.57 424.56 277.48 51874 +1939 127 16.73 10.73 15.08 0.31 424.56 278.14 52039 +1939 128 18.11 12.11 16.46 0.77 459.4 275.95 52203 +1939 129 16.43 10.43 14.78 0.5 417.29 280.12 52365 +1939 130 13.78 7.78 12.13 0 357.57 380.86 52524 +1939 131 11.93 5.93 10.28 1.2 320.35 289.26 52681 +1939 132 13.35 7.35 11.7 0.27 348.61 287.6 52836 +1939 133 19.81 13.81 18.16 0 505.63 366.54 52989 +1939 134 19.17 13.17 17.52 1.59 487.78 276.97 53138 +1939 135 18.25 12.25 16.6 0.16 463.06 279.61 53286 +1939 136 20.14 14.14 18.49 0.49 515.05 275.58 53430 +1939 137 18.95 12.95 17.3 0.27 481.77 278.99 53572 +1939 138 18.56 12.56 16.91 1.34 471.27 280.35 53711 +1939 139 18.22 12.22 16.57 0.07 462.28 281.64 53848 +1939 140 18.83 12.83 17.18 0.32 478.52 280.59 53981 +1939 141 17.75 11.75 16.1 0.64 450.08 283.37 54111 +1939 142 17.16 11.16 15.51 0.98 435.17 285.02 54238 +1939 143 14.46 8.46 12.81 0.11 372.15 290.75 54362 +1939 144 17.6 11.6 15.95 0.19 446.25 284.83 54483 +1939 145 15.98 9.98 14.33 0.51 406.59 288.57 54600 +1939 146 13.77 7.77 12.12 0.44 357.36 292.99 54714 +1939 147 14.36 8.36 12.71 0.34 369.98 292.3 54824 +1939 148 13.62 7.62 11.97 0.18 354.21 293.91 54931 +1939 149 17.47 11.47 15.82 0.09 442.95 286.63 55034 +1939 150 16.98 10.98 15.33 0.03 430.7 287.94 55134 +1939 151 17.84 11.84 16.19 0.68 452.4 286.36 55229 +1939 152 17.17 11.17 15.52 0 435.41 383.88 55321 +1939 153 15.53 9.53 13.88 0.01 396.12 291.45 55409 +1939 154 14.47 8.47 12.82 0.44 372.37 293.7 55492 +1939 155 16.78 10.78 15.13 0.01 425.78 289.3 55572 +1939 156 21.26 15.26 19.61 0.14 548.14 278.79 55648 +1939 157 20.98 14.98 19.33 1.08 539.7 279.67 55719 +1939 158 21.07 15.07 19.42 0 542.4 372.74 55786 +1939 159 19.3 13.3 17.65 0.17 491.36 284.27 55849 +1939 160 19.95 13.95 18.3 0.56 509.61 282.8 55908 +1939 161 16.42 10.42 14.77 0 417.05 387.91 55962 +1939 162 21.6 15.6 19.95 0.18 558.54 278.51 56011 +1939 163 23.37 17.37 21.72 0 615.39 364.67 56056 +1939 164 21.47 15.47 19.82 0.01 554.54 279.07 56097 +1939 165 23.92 17.92 22.27 0.2 634.03 271.89 56133 +1939 166 25.98 19.98 24.33 0 708.15 353.39 56165 +1939 167 25.51 19.51 23.86 0 690.62 355.53 56192 +1939 168 23.81 17.81 22.16 0.62 630.27 272.31 56214 +1939 169 23.27 17.27 21.62 0.95 612.06 273.99 56231 +1939 170 23.68 17.68 22.03 0 625.84 363.63 56244 +1939 171 23.71 17.71 22.06 0.87 626.86 272.67 56252 +1939 172 24.69 18.69 23.04 0 660.93 359.35 56256 +1939 173 20.6 14.6 18.95 0.38 528.43 281.59 56255 +1939 174 21.71 15.71 20.06 0.42 561.93 278.52 56249 +1939 175 21.14 15.14 19.49 0.23 544.51 280.06 56238 +1939 176 23.11 17.11 21.46 0 606.75 365.86 56223 +1939 177 22.3 16.3 20.65 0.38 580.46 276.71 56203 +1939 178 21.37 15.37 19.72 0 551.49 372.47 56179 +1939 179 19.43 13.43 17.78 0 494.97 379.09 56150 +1939 180 18.56 12.56 16.91 0 471.27 381.75 56116 +1939 181 19.84 13.84 18.19 0 506.48 377.54 56078 +1939 182 26.77 20.77 25.12 0 738.45 349.01 56035 +1939 183 27.41 21.41 25.76 0 763.8 345.64 55987 +1939 184 28.5 22.5 26.85 0 808.66 339.78 55935 +1939 185 24.73 18.73 23.08 0 662.35 358.12 55879 +1939 186 24.53 18.53 22.88 0 655.26 358.75 55818 +1939 187 26.05 20.05 24.4 0.41 710.79 263.76 55753 +1939 188 26.47 20.47 24.82 0.87 726.82 262.06 55684 +1939 189 26.56 20.56 24.91 0 730.29 348.8 55611 +1939 190 25.31 19.31 23.66 0 683.28 354.31 55533 +1939 191 24.47 18.47 22.82 0.04 653.15 268.33 55451 +1939 192 22.73 16.73 21.08 0.08 594.29 273.5 55366 +1939 193 22.51 16.51 20.86 0.06 587.18 273.94 55276 +1939 194 24.67 18.67 23.02 0.32 660.22 267.1 55182 +1939 195 22.99 16.99 21.34 0 602.79 362.88 55085 +1939 196 24.51 18.51 22.86 0 654.55 356.18 54984 +1939 197 27.29 21.29 25.64 0 758.99 342.76 54879 +1939 198 25.34 19.34 23.69 0.11 684.38 263.74 54770 +1939 199 25.41 19.41 23.76 0 686.94 351 54658 +1939 200 27.48 21.48 25.83 0 766.62 340.7 54542 +1939 201 25.69 19.69 24.04 0 697.29 348.89 54423 +1939 202 23.34 17.34 21.69 0 614.39 358.46 54301 +1939 203 21.19 15.19 19.54 0 546.02 366.13 54176 +1939 204 21.79 15.79 20.14 0 564.42 363.45 54047 +1939 205 19.15 13.15 17.5 0 487.23 371.98 53915 +1939 206 17.06 11.06 15.41 0 432.68 377.65 53780 +1939 207 15.32 9.32 13.67 0 391.32 381.62 53643 +1939 208 16.15 10.15 14.5 0 410.61 378.79 53502 +1939 209 20.33 14.33 18.68 0 520.54 365.58 53359 +1939 210 24.71 18.71 23.06 0 661.64 348.21 53213 +1939 211 20.17 14.17 18.52 0 515.92 364.71 53064 +1939 212 22.09 16.09 20.44 0.16 573.81 267.87 52913 +1939 213 24.7 18.7 23.05 0 661.28 346 52760 +1939 214 25.87 19.87 24.22 0.4 704.01 255.08 52604 +1939 215 26.57 20.57 24.92 0.25 730.68 252.17 52445 +1939 216 27.77 21.77 26.12 0 778.38 329.41 52285 +1939 217 26.55 20.55 24.9 0 729.9 334.51 52122 +1939 218 26 20 24.35 0.01 708.9 252.21 51958 +1939 219 26.59 20.59 24.94 0 731.45 332.56 51791 +1939 220 18.55 12.55 16.9 0 471 362.11 51622 +1939 221 20.6 14.6 18.95 0 528.43 354.6 51451 +1939 222 21.49 15.49 19.84 0 555.15 350.5 51279 +1939 223 18.61 12.61 16.96 0.01 472.61 269.03 51105 +1939 224 21.71 15.71 20.06 0 561.93 347.55 50929 +1939 225 20.06 14.06 18.41 0 512.76 352 50751 +1939 226 18.15 12.15 16.5 1.61 460.44 267.51 50572 +1939 227 21.87 15.87 20.22 1.8 566.91 257.6 50392 +1939 228 20.75 14.75 19.1 1.38 532.86 259.59 50210 +1939 229 21.95 15.95 20.3 0.4 569.41 255.57 50026 +1939 230 20.6 14.6 18.95 0 528.43 344.12 49842 +1939 231 22.74 16.74 21.09 0 594.62 335.22 49656 +1939 232 23.87 17.87 22.22 0.06 632.32 247.21 49469 +1939 233 28.01 22.01 26.36 0.14 788.23 232.57 49280 +1939 234 26.63 20.63 24.98 0.12 733 236.45 49091 +1939 235 29.92 23.92 28.27 0 870.42 297.65 48900 +1939 236 26.23 20.23 24.58 0 717.62 314.32 48709 +1939 237 23.27 17.27 21.62 0 612.06 324.74 48516 +1939 238 19.17 13.17 17.52 0.11 487.78 252.54 48323 +1939 239 20.79 14.79 19.14 0.41 534.04 247.67 48128 +1939 240 20.57 14.57 18.92 0.86 527.55 246.89 47933 +1939 241 22.15 16.15 20.5 0.99 575.7 241.71 47737 +1939 242 20.97 14.97 19.32 0.25 539.4 243.38 47541 +1939 243 21.11 15.11 19.46 0 543.61 322.22 47343 +1939 244 18.56 12.56 16.91 0 471.27 328.05 47145 +1939 245 18.8 12.8 17.15 0 477.71 325.54 46947 +1939 246 18.32 12.32 16.67 0.01 464.91 243.68 46747 +1939 247 19.11 13.11 17.46 1.13 486.14 240.65 46547 +1939 248 21.4 15.4 19.75 0.04 552.4 234.04 46347 +1939 249 18.13 12.13 16.48 0.94 459.92 239.67 46146 +1939 250 22.2 16.2 20.55 0 577.29 305.54 45945 +1939 251 21.25 15.25 19.6 0 547.84 306.55 45743 +1939 252 19.24 13.24 17.59 0 489.71 310.37 45541 +1939 253 19.88 13.88 18.23 0 507.62 306.47 45339 +1939 254 19.05 13.05 17.4 0.26 484.5 230.01 45136 +1939 255 17.42 11.42 15.77 0 441.69 308.67 44933 +1939 256 16.43 10.43 14.78 0.64 417.29 231.57 44730 +1939 257 17.66 11.66 16.01 0 447.78 303.66 44527 +1939 258 14.68 8.68 13.03 0.03 376.98 231.03 44323 +1939 259 20.28 14.28 18.63 0 519.09 291.99 44119 +1939 260 23.51 17.51 21.86 0 620.09 279.66 43915 +1939 261 19.6 13.6 17.95 0.65 499.72 216.86 43711 +1939 262 19.81 13.81 18.16 0 505.63 286.26 43507 +1939 263 15.42 9.42 13.77 0 393.6 294.32 43303 +1939 264 15.74 9.74 14.09 0 400.98 291.06 43099 +1939 265 10.18 4.18 8.53 0.21 288.25 223.98 42894 +1939 266 17.13 11.13 15.48 0.34 434.42 212.39 42690 +1939 267 16.33 10.33 14.68 0.02 414.89 211.72 42486 +1939 268 17 11 15.35 0 431.19 278.28 42282 +1939 269 19.85 13.85 18.2 0 506.77 268.95 42078 +1939 270 17.92 11.92 16.27 0 454.46 271.11 41875 +1939 271 19 13 17.35 0.61 483.13 199.48 41671 +1939 272 20.13 14.13 18.48 0.96 514.76 195.36 41468 +1939 273 20.4 14.4 18.75 0.51 522.58 193 41265 +1939 274 12.76 6.76 11.11 0.07 336.62 203.04 41062 +1939 275 13.12 7.12 11.47 0.25 343.89 200.51 40860 +1939 276 14.33 8.33 12.68 0.43 369.33 196.9 40658 +1939 277 12.15 6.15 10.5 0.06 324.6 197.63 40456 +1939 278 10.99 4.99 9.34 0 302.75 262.35 40255 +1939 279 11.8 5.8 10.15 0.15 317.87 193.74 40054 +1939 280 17.33 11.33 15.68 0.02 439.42 184.41 39854 +1939 281 17.44 11.44 15.79 0 442.19 242.99 39654 +1939 282 18.66 12.66 17.01 0.5 473.94 178.29 39455 +1939 283 14.33 8.33 12.68 0.9 369.33 182.5 39256 +1939 284 15.73 9.73 14.08 0.3 400.75 178.41 39058 +1939 285 11.8 5.8 10.15 0 317.87 241.62 38861 +1939 286 12.75 6.75 11.1 0 336.42 237.46 38664 +1939 287 8.6 2.6 6.95 0.82 261.67 179.98 38468 +1939 288 11.36 5.36 9.71 0.22 309.57 175.28 38273 +1939 289 7.55 1.55 5.9 0 245.19 235.62 38079 +1939 290 9.69 3.69 8.04 0 279.77 230.31 37885 +1939 291 11.13 5.13 9.48 0.5 305.31 169.34 37693 +1939 292 12.59 6.59 10.94 1.13 333.23 165.84 37501 +1939 293 13.61 7.61 11.96 1.15 354.01 162.69 37311 +1939 294 11.16 5.16 9.51 1.5 305.87 163.06 37121 +1939 295 8.02 2.02 6.37 0.17 252.46 163.63 36933 +1939 296 7.67 1.67 6.02 0 247.03 215.9 36745 +1939 297 9.54 3.54 7.89 0 277.21 211.17 36560 +1939 298 8.97 2.97 7.32 0.22 267.7 156.88 36375 +1939 299 10.93 4.93 9.28 0 301.65 204.16 36191 +1939 300 13.82 7.82 12.17 0.17 358.42 148.31 36009 +1939 301 16.17 10.17 14.52 0.09 411.08 143.8 35829 +1939 302 13.39 7.39 11.74 0 349.43 193.29 35650 +1939 303 13.55 7.55 11.9 0.54 352.75 142.9 35472 +1939 304 13.12 7.12 11.47 1.88 343.89 141.51 35296 +1939 305 7.21 1.21 5.56 0.07 240.06 144.29 35122 +1939 306 1.2 -4.8 -0.45 0 163.31 194.53 34950 +1939 307 5.59 -0.41 3.94 0 216.82 188.94 34779 +1939 308 3.59 -2.41 1.94 0.16 190.82 140.83 34610 +1939 309 4.39 -1.61 2.74 0 200.88 184.86 34444 +1939 310 9.97 3.97 8.32 0 284.59 177.59 34279 +1939 311 8.83 2.83 7.18 0 265.4 176.54 34116 +1939 312 8.56 2.56 6.91 0 261.02 174.15 33956 +1939 313 8.49 2.49 6.84 0 259.9 172.1 33797 +1939 314 11.23 5.23 9.58 0 307.16 167.47 33641 +1939 315 11.42 5.42 9.77 0 310.69 164.76 33488 +1939 316 13.61 7.61 11.96 0 354.01 160.13 33337 +1939 317 13.12 7.12 11.47 0 343.89 158.57 33188 +1939 318 12.37 6.37 10.72 0 328.89 157.12 33042 +1939 319 10.47 4.47 8.82 0 293.37 157.42 32899 +1939 320 8.63 2.63 6.98 0.08 262.15 117.94 32758 +1939 321 10.06 4.06 8.41 0.01 286.15 115.41 32620 +1939 322 7.18 1.18 5.53 0.15 239.61 115.89 32486 +1939 323 8.99 2.99 7.34 2.05 268.03 113.58 32354 +1939 324 11.97 5.97 10.32 0.99 321.12 109.96 32225 +1939 325 14.29 8.29 12.64 0.13 368.46 106.8 32100 +1939 326 13.68 7.68 12.03 0.35 355.47 106.27 31977 +1939 327 9.56 3.56 7.91 0.24 277.55 107.95 31858 +1939 328 11.63 5.63 9.98 0.23 314.64 105.07 31743 +1939 329 6.86 0.86 5.21 0.36 234.86 106.97 31631 +1939 330 6.4 0.4 4.75 0.66 228.18 106.13 31522 +1939 331 6.92 0.92 5.27 0.01 235.74 104.87 31417 +1939 332 5.93 -0.07 4.28 0 221.53 138.87 31316 +1939 333 6.74 0.74 5.09 0 233.1 137.24 31218 +1939 334 7.2 1.2 5.55 0.02 239.91 101.86 31125 +1939 335 2.62 -3.38 0.97 0.09 179.21 103.09 31035 +1939 336 2.57 -3.43 0.92 0.38 178.63 102.3 30949 +1939 337 3.64 -2.36 1.99 0 191.43 134.15 30867 +1939 338 2.88 -3.12 1.23 0 182.26 133.62 30790 +1939 339 2.47 -3.53 0.82 0.2 177.47 99.78 30716 +1939 340 3.4 -2.6 1.75 0 188.49 131.81 30647 +1939 341 0.82 -5.18 -0.83 0.03 159.27 99.12 30582 +1939 342 -0.59 -6.59 -2.24 0 145.02 131.99 30521 +1939 343 4.43 -1.57 2.78 0 201.39 128.73 30465 +1939 344 5.7 -0.3 4.05 0 218.33 126.85 30413 +1939 345 3.39 -2.61 1.74 0.02 188.37 95.8 30366 +1939 346 6.2 0.2 4.55 0 225.33 125.57 30323 +1939 347 7.66 1.66 6.01 0 246.88 124.01 30284 +1939 348 6.47 0.47 4.82 0 229.19 124.45 30251 +1939 349 7.31 1.31 5.66 0.01 241.56 92.65 30221 +1939 350 1.66 -4.34 0.01 0 168.32 126.38 30197 +1939 351 2.12 -3.88 0.47 0.53 173.47 94.45 30177 +1939 352 2.93 -3.07 1.28 0.41 182.85 94.08 30162 +1939 353 -0.3 -6.3 -1.95 0 147.86 126.85 30151 +1939 354 -3.03 -9.03 -4.68 0.44 122.96 141.06 30145 +1939 355 -5.38 -11.38 -7.03 0.42 104.52 142.94 30144 +1939 356 -4.3 -10.3 -5.95 0 112.67 174.78 30147 +1939 357 -2.6 -8.6 -4.25 0 126.62 174.27 30156 +1939 358 0.26 -5.74 -1.39 0.07 153.47 141.52 30169 +1939 359 -1.32 -7.32 -2.97 0 138.09 173.94 30186 +1939 360 1.34 -4.66 -0.31 0.11 164.82 141.29 30208 +1939 361 1.38 -4.62 -0.27 0 165.26 173.08 30235 +1939 362 5.38 -0.62 3.73 0 213.95 170.65 30267 +1939 363 7.01 1.01 5.36 0 237.08 169.22 30303 +1939 364 1.3 -4.7 -0.35 0 164.39 172.56 30343 +1939 365 3.49 -2.51 1.84 0 189.59 171.52 30388 +1940 1 -5.2 -11.2 -6.85 0 105.84 175.85 30438 +1940 2 -5.2 -11.2 -6.85 0 105.84 176.52 30492 +1940 3 -5.2 -11.2 -6.85 0 105.84 177.39 30551 +1940 4 -5.2 -11.2 -6.85 0 105.84 178.23 30614 +1940 5 -5.2 -11.2 -6.85 0.03 105.84 144.96 30681 +1940 6 -5.2 -11.2 -6.85 0 105.84 179.7 30752 +1940 7 -5.2 -11.2 -6.85 0 105.84 180.41 30828 +1940 8 -5.2 -11.2 -6.85 0 105.84 181.8 30907 +1940 9 -5.2 -11.2 -6.85 0 105.84 182.96 30991 +1940 10 -5.2 -11.2 -6.85 0 105.84 184.17 31079 +1940 11 -5.2 -11.2 -6.85 0 105.84 185.05 31171 +1940 12 -5.2 -11.2 -6.85 0 105.84 185.95 31266 +1940 13 -5.2 -11.2 -6.85 0 105.84 187.47 31366 +1940 14 -5.2 -11.2 -6.85 0 105.84 188.83 31469 +1940 15 -5.2 -11.2 -6.85 0 105.84 190.16 31575 +1940 16 -5.2 -11.2 -6.85 0.37 105.84 155.06 31686 +1940 17 -5.2 -11.2 -6.85 0.62 105.84 158.06 31800 +1940 18 -5.2 -11.2 -6.85 0.01 105.84 159.38 31917 +1940 19 -5.2 -11.2 -6.85 0 105.84 199.46 32038 +1940 20 -5.2 -11.2 -6.85 0 105.84 200.91 32161 +1940 21 -5.2 -11.2 -6.85 0 105.84 202.78 32289 +1940 22 -5.2 -11.2 -6.85 0.27 105.84 165.04 32419 +1940 23 -5.2 -11.2 -6.85 1.22 105.84 169.81 32552 +1940 24 -5.2 -11.2 -6.85 0.08 105.84 171.42 32688 +1940 25 -5.2 -11.2 -6.85 0.47 105.84 174.03 32827 +1940 26 -5.2 -11.2 -6.85 0 105.84 217.38 32969 +1940 27 -5.2 -11.2 -6.85 0 105.84 219.23 33114 +1940 28 -5.2 -11.2 -6.85 0.43 105.84 179.33 33261 +1940 29 -5.2 -11.2 -6.85 0 105.84 224.7 33411 +1940 30 -5.2 -11.2 -6.85 0.43 105.84 183.64 33564 +1940 31 -5.2 -11.2 -6.85 0.83 105.84 187.59 33718 +1940 32 -3.1 -9.1 -4.75 0.55 122.37 189.9 33875 +1940 33 -4.76 -10.76 -6.41 0 109.13 238.26 34035 +1940 34 -3.32 -9.32 -4.97 0 120.54 239.67 34196 +1940 35 -5.58 -11.58 -7.23 0 103.06 242.5 34360 +1940 36 -9.31 -15.31 -10.96 0.02 79.01 197.82 34526 +1940 37 -4.2 -10.2 -5.85 0.6 113.45 199.77 34694 +1940 38 -4.78 -10.78 -6.43 0 108.98 250.95 34863 +1940 39 -3.16 -9.16 -4.81 0 121.87 252.66 35035 +1940 40 -2.39 -8.39 -4.04 0 128.44 254.69 35208 +1940 41 -1.54 -7.54 -3.19 0.75 136.05 207.89 35383 +1940 42 -2.31 -8.31 -3.96 0 129.14 261.4 35560 +1940 43 -3.68 -9.68 -5.33 0 117.59 264.52 35738 +1940 44 -3.91 -9.91 -5.56 0 115.74 266.96 35918 +1940 45 -1.37 -7.37 -3.02 0.02 137.62 214.73 36099 +1940 46 -2.48 -8.48 -4.13 0.05 127.66 217.06 36282 +1940 47 -5.36 -11.36 -7.01 0.05 104.66 220.06 36466 +1940 48 -6.61 -12.61 -8.26 0 95.86 278.46 36652 +1940 49 -4.6 -10.6 -6.25 0.14 110.35 223.91 36838 +1940 50 -1.79 -7.79 -3.44 0 133.78 281.62 37026 +1940 51 1.94 -4.06 0.29 0.21 171.44 224.66 37215 +1940 52 1.7 -4.3 0.05 0.44 168.77 226.47 37405 +1940 53 1.04 -4.96 -0.61 0.02 161.6 228.68 37596 +1940 54 3.01 -2.99 1.36 0.28 183.8 229.1 37788 +1940 55 6.34 0.34 4.69 0 227.32 287.35 37981 +1940 56 2.45 -3.55 0.8 0 177.24 292.92 38175 +1940 57 1.94 -4.06 0.29 0 171.44 295.76 38370 +1940 58 -3.19 -9.19 -4.84 0.33 121.62 239.52 38565 +1940 59 -2.03 -8.03 -3.68 0.31 131.62 241.62 38761 +1940 60 7.42 1.42 5.77 0.31 243.22 237.01 38958 +1940 61 7.9 1.9 6.25 0 250.58 300.69 39156 +1940 62 7.94 1.94 6.29 0.89 251.21 238.72 39355 +1940 63 4.19 -1.81 2.54 0 198.32 308.56 39553 +1940 64 4.41 -1.59 2.76 0 201.13 310.6 39753 +1940 65 6.5 0.5 4.85 0 229.62 310.51 39953 +1940 66 5.84 -0.16 4.19 0 220.27 313.14 40154 +1940 67 4.48 -1.52 2.83 0 202.04 316.75 40355 +1940 68 3.2 -2.8 1.55 0 186.07 320.29 40556 +1940 69 6.71 0.71 5.06 0 232.66 318.53 40758 +1940 70 3.92 -2.08 2.27 0 194.91 323.69 40960 +1940 71 6.26 0.26 4.61 0.34 226.18 252.86 41163 +1940 72 7.87 1.87 6.22 0.28 250.12 252.59 41366 +1940 73 6.99 0.99 5.34 0 236.78 326.22 41569 +1940 74 5.04 -0.96 3.39 0.08 209.38 257.54 41772 +1940 75 5.39 -0.61 3.74 0 214.09 332.15 41976 +1940 76 6.28 0.28 4.63 0.18 226.47 259.08 42179 +1940 77 9.84 3.84 8.19 0 282.34 329.89 42383 +1940 78 8.29 2.29 6.64 0 256.71 333.75 42587 +1940 79 7.1 1.1 5.45 0 238.41 337.17 42791 +1940 80 9.67 3.67 8.02 0 279.43 335.17 42996 +1940 81 7.86 1.86 6.21 0 249.96 339.37 43200 +1940 82 4.97 -1.03 3.32 0.06 208.45 266.63 43404 +1940 83 -0.16 -6.16 -1.81 0 149.25 352.12 43608 +1940 84 1.25 -4.75 -0.4 0 163.85 353.28 43812 +1940 85 4.35 -1.65 2.7 0 200.36 352.27 44016 +1940 86 3.41 -2.59 1.76 0 188.62 355.25 44220 +1940 87 5.2 -0.8 3.55 0.89 211.52 273.88 44424 +1940 88 10.6 4.6 8.95 0.01 295.69 240.34 44627 +1940 89 5.77 -0.23 4.12 0.09 219.3 247.17 44831 +1940 90 7.22 1.22 5.57 0 240.2 330.11 45034 +1940 91 13.49 7.49 11.84 0 351.51 322.09 45237 +1940 92 16.29 10.29 14.64 0 413.94 318.24 45439 +1940 93 17.09 11.09 15.44 0.01 433.42 238.85 45642 +1940 94 14.64 8.64 12.99 0.15 376.1 244.67 45843 +1940 95 15.89 9.89 14.24 0.48 404.48 244.14 46045 +1940 96 12.16 6.16 10.51 0 324.79 335.41 46246 +1940 97 11.48 5.48 9.83 0.01 311.82 254.03 46446 +1940 98 11.24 5.24 9.59 0 307.35 341.09 46647 +1940 99 12.76 6.76 11.11 0.59 336.62 255.19 46846 +1940 100 15.53 9.53 13.88 0 396.12 336.23 47045 +1940 101 14.39 8.39 12.74 0 370.63 340.71 47243 +1940 102 14.67 8.67 13.02 0 376.76 341.97 47441 +1940 103 14.15 8.15 12.5 0.18 365.44 258.7 47638 +1940 104 10.21 4.21 8.56 0 288.77 354.39 47834 +1940 105 12.02 6.02 10.37 0 322.08 352.9 48030 +1940 106 12.73 6.73 11.08 0 336.02 353.14 48225 +1940 107 9.96 3.96 8.31 0.66 284.41 269.98 48419 +1940 108 9.15 3.15 7.5 0 270.67 363.09 48612 +1940 109 8.46 2.46 6.81 0 259.42 365.83 48804 +1940 110 8.44 2.44 6.79 0.16 259.1 275.47 48995 +1940 111 5.59 -0.41 3.94 0 216.82 372.98 49185 +1940 112 6.22 0.22 4.57 0 225.61 373.69 49374 +1940 113 8.11 2.11 6.46 0 253.87 372.3 49561 +1940 114 8.99 2.99 7.34 0 268.03 372.41 49748 +1940 115 13.08 7.08 11.43 0 343.08 366.18 49933 +1940 116 16.8 10.8 15.15 0 426.27 358.53 50117 +1940 117 16.34 10.34 14.69 0.02 415.13 270.77 50300 +1940 118 17.08 11.08 15.43 0.33 433.18 270.27 50481 +1940 119 18.41 12.41 16.76 0 467.28 357.76 50661 +1940 120 16.42 10.42 14.77 0 417.05 364.45 50840 +1940 121 14.59 8.59 12.94 0.12 375 277.6 51016 +1940 122 16.22 10.22 14.57 0 412.27 367.27 51191 +1940 123 15.82 9.82 14.17 0.11 402.84 276.99 51365 +1940 124 14.6 8.6 12.95 0.04 375.22 280.06 51536 +1940 125 17.77 11.77 16.12 0.01 450.6 274.56 51706 +1940 126 15.95 9.95 14.3 1.21 405.89 279.03 51874 +1940 127 20.78 14.78 19.13 0.75 533.75 268.85 52039 +1940 128 21.36 15.36 19.71 0.58 551.18 268.05 52203 +1940 129 16.66 10.66 15.01 0.2 422.85 279.66 52365 +1940 130 17.84 11.84 16.19 0.24 452.4 277.76 52524 +1940 131 15.44 9.44 13.79 0.07 394.06 283.25 52681 +1940 132 19.23 13.23 17.58 0 489.43 367.72 52836 +1940 133 20.03 14.03 18.38 0 511.9 365.81 52989 +1940 134 16.48 10.48 14.83 0.35 418.5 282.88 53138 +1940 135 16.69 10.69 15.04 0.25 423.59 282.97 53286 +1940 136 11.81 5.81 10.16 0 318.06 389.57 53430 +1940 137 12.91 6.91 11.26 0.69 339.63 290.96 53572 +1940 138 17.74 11.74 16.09 1.33 449.83 282.19 53711 +1940 139 12.53 6.53 10.88 1.7 332.04 292.57 53848 +1940 140 15.19 9.19 13.54 1.81 388.37 288.28 53981 +1940 141 12.31 6.31 10.66 1.2 327.71 293.63 54111 +1940 142 13.27 7.27 11.62 0.31 346.96 292.43 54238 +1940 143 12.69 6.69 11.04 0 335.22 391.74 54362 +1940 144 10.93 4.93 9.28 0.36 301.65 296.9 54483 +1940 145 11.28 5.28 9.63 0.37 308.09 296.75 54600 +1940 146 13.61 7.61 11.96 0 354.01 391.03 54714 +1940 147 14.97 8.97 13.32 0.78 383.42 291.18 54824 +1940 148 14.14 8.14 12.49 0.16 365.23 292.99 54931 +1940 149 18.73 12.73 17.08 0.04 475.82 283.78 55034 +1940 150 18.48 12.48 16.83 1.94 469.14 284.61 55134 +1940 151 16.75 10.75 15.1 3.43 425.05 288.72 55229 +1940 152 20.72 14.72 19.07 1.14 531.97 279.44 55321 +1940 153 23.23 17.23 21.58 0.52 610.73 272.51 55409 +1940 154 24.16 18.16 22.51 0.73 642.31 269.85 55492 +1940 155 25.28 19.28 23.63 0.07 682.18 266.29 55572 +1940 156 19.12 13.12 17.47 0.01 486.41 284.27 55648 +1940 157 18.9 12.9 17.25 0.21 480.41 284.93 55719 +1940 158 19.85 13.85 18.2 0.14 506.77 282.73 55786 +1940 159 20.48 14.48 18.83 0.22 524.91 281.3 55849 +1940 160 25.03 19.03 23.38 0.08 673.11 267.92 55908 +1940 161 26.31 20.31 24.66 0 720.68 351.35 55962 +1940 162 22.72 16.72 21.07 0 593.97 367.07 56011 +1940 163 22.24 16.24 20.59 0.01 578.56 276.86 56056 +1940 164 19.24 13.24 17.59 2.02 489.71 284.85 56097 +1940 165 17.82 11.82 16.17 1.33 451.88 288.24 56133 +1940 166 19.67 13.67 18.02 0 501.68 378.56 56165 +1940 167 17.63 11.63 15.98 0.53 447.01 288.68 56192 +1940 168 15.3 9.3 13.65 0.6 390.86 293.57 56214 +1940 169 14.58 8.58 12.93 0.3 374.78 294.94 56231 +1940 170 18.24 12.24 16.59 0 462.8 383.16 56244 +1940 171 21.37 15.37 19.72 0 551.49 372.72 56252 +1940 172 22.71 16.71 21.06 0 593.64 367.61 56256 +1940 173 23.08 17.08 21.43 0.06 605.76 274.59 56255 +1940 174 23.43 17.43 21.78 0 617.4 364.62 56249 +1940 175 26.51 20.51 24.86 0 728.36 350.81 56238 +1940 176 21.12 15.12 19.47 0.28 543.91 280.09 56223 +1940 177 20.92 14.92 19.27 0.33 537.91 280.55 56203 +1940 178 18.41 12.41 16.76 0.25 467.28 286.83 56179 +1940 179 17.22 11.22 15.57 0.89 436.66 289.42 56150 +1940 180 16.95 10.95 15.3 0 429.96 386.54 56116 +1940 181 17.92 11.92 16.27 0.79 454.46 287.73 56078 +1940 182 14.11 8.11 12.46 0.33 364.59 295.3 56035 +1940 183 14.63 8.63 12.98 0 375.88 392.29 55987 +1940 184 18.79 12.79 17.14 0 477.44 380.47 55935 +1940 185 23.52 17.52 21.87 3.52 620.43 272.46 55879 +1940 186 30.38 24.38 28.73 1.27 891.26 246.61 55818 +1940 187 25.57 19.57 23.92 0.21 692.84 265.44 55753 +1940 188 24.77 18.77 23.12 0 663.78 357.26 55684 +1940 189 21.27 15.27 19.62 0 548.44 371.1 55611 +1940 190 23.67 17.67 22.02 0 625.5 361.42 55533 +1940 191 25.6 19.6 23.95 0.01 693.95 264.55 55451 +1940 192 23.64 17.64 21.99 1.67 624.48 270.75 55366 +1940 193 20.64 14.64 18.99 0 529.61 372.14 55276 +1940 194 22.12 16.12 20.47 0.58 574.76 274.9 55182 +1940 195 23.78 17.78 22.13 0 629.24 359.67 55085 +1940 196 23.61 17.61 21.96 0 623.47 359.97 54984 +1940 197 23.49 17.49 21.84 0.57 619.42 270.01 54879 +1940 198 17.25 11.25 15.6 0.16 437.41 285.81 54770 +1940 199 19.33 13.33 17.68 0.61 492.19 280.79 54658 +1940 200 19.1 13.1 17.45 0.48 485.86 281.04 54542 +1940 201 17.7 11.7 16.05 0.38 448.8 283.89 54423 +1940 202 18.76 12.76 17.11 0 476.63 374.75 54301 +1940 203 18.99 12.99 17.34 0 482.86 373.52 54176 +1940 204 24.77 18.77 23.12 0 663.78 351.49 54047 +1940 205 23.66 17.66 22.01 0.08 625.16 266.75 53915 +1940 206 21.79 15.79 20.14 0.45 564.42 271.79 53780 +1940 207 17.44 11.44 15.79 0 442.19 375.9 53643 +1940 208 23.62 17.62 21.97 0 623.81 354 53502 +1940 209 23.97 17.97 22.32 0.32 635.75 263.95 53359 +1940 210 21.27 15.27 19.62 0.09 548.44 271.27 53213 +1940 211 22.88 16.88 21.23 0.02 599.18 266.21 53064 +1940 212 23.41 17.41 21.76 0 616.73 352.08 52913 +1940 213 22.59 16.59 20.94 0.23 589.76 265.9 52760 +1940 214 18.72 12.72 17.07 0.6 475.56 275.28 52604 +1940 215 21.54 15.54 19.89 0.7 556.69 267.76 52445 +1940 216 17.42 11.42 15.77 0.54 441.69 276.86 52285 +1940 217 20.8 14.8 19.15 2.13 534.34 268.28 52122 +1940 218 16.86 10.86 15.21 0.34 427.74 276.71 51958 +1940 219 14.9 8.9 13.25 2.46 381.86 279.69 51791 +1940 220 18.42 12.42 16.77 1.34 467.55 271.87 51622 +1940 221 19.3 13.3 17.65 1.57 491.36 269.11 51451 +1940 222 21.02 15.02 19.37 0.28 540.9 264.1 51279 +1940 223 21.25 15.25 19.6 1.19 547.84 262.66 51105 +1940 224 23.71 17.71 22.06 0 626.86 340.04 50929 +1940 225 19.86 13.86 18.21 0 507.05 352.64 50751 +1940 226 20.39 14.39 18.74 0 522.29 349.79 50572 +1940 227 18.03 12.03 16.38 0.01 457.31 266.8 50392 +1940 228 15.82 9.82 14.17 0.59 402.84 270.31 50210 +1940 229 15.64 9.64 13.99 0.29 398.66 269.69 50026 +1940 230 17.53 11.53 15.88 0.06 444.47 265.02 49842 +1940 231 21.95 15.95 20.3 0.03 569.41 253.55 49656 +1940 232 18.94 12.94 17.29 0.29 481.5 259.87 49469 +1940 233 19.07 13.07 17.42 0.19 485.04 258.51 49280 +1940 234 20.98 14.98 19.33 0.08 539.7 252.94 49091 +1940 235 20.11 14.11 18.46 0.91 514.19 253.94 48900 +1940 236 20.76 14.76 19.11 2.17 533.15 251.32 48709 +1940 237 22.21 16.21 20.56 0.03 577.6 246.43 48516 +1940 238 18.94 12.94 17.29 0.45 481.5 253.05 48323 +1940 239 20.26 14.26 18.61 0.78 518.51 248.93 48128 +1940 240 20.18 14.18 18.53 0.43 516.2 247.81 47933 +1940 241 19.93 13.93 18.28 0 509.04 329.47 47737 +1940 242 20.37 14.37 18.72 0.07 521.7 244.8 47541 +1940 243 17.79 11.79 16.14 0.05 451.11 248.98 47343 +1940 244 12.72 6.72 11.07 1.72 335.82 256.34 47145 +1940 245 10.62 4.62 8.97 0.37 296.05 257.81 46947 +1940 246 9.89 3.89 8.24 0 283.2 342.94 46747 +1940 247 9.57 3.57 7.92 0 277.72 341.52 46547 +1940 248 12.2 6.2 10.55 0 325.57 334.95 46347 +1940 249 16.45 10.45 14.8 0 417.77 323.81 46146 +1940 250 17.15 11.15 15.5 0.04 434.92 240.1 45945 +1940 251 18.16 12.16 16.51 0 460.7 315.43 45743 +1940 252 21.41 15.41 19.76 0 552.71 303.94 45541 +1940 253 19.19 13.19 17.54 1.65 488.33 231.31 45339 +1940 254 15.44 9.44 13.79 0.32 394.06 236.67 45136 +1940 255 16.01 10.01 14.36 0.01 407.3 234 44933 +1940 256 21.22 15.22 19.57 0 546.93 295.99 44730 +1940 257 20.9 14.9 19.25 0.26 537.31 221.14 44527 +1940 258 15.31 9.31 13.66 0.31 391.09 230.04 44323 +1940 259 17.7 11.7 16.05 0.24 448.8 224.11 44119 +1940 260 16.99 10.99 15.34 0.24 430.95 223.6 43915 +1940 261 22.36 16.36 20.71 2.19 582.38 210.81 43711 +1940 262 19.94 13.94 18.29 0.2 509.33 214.43 43507 +1940 263 22.48 16.48 20.83 0.44 586.22 207.05 43303 +1940 264 20.28 14.28 18.63 0.7 519.09 210.04 43099 +1940 265 22.14 16.14 20.49 0.42 575.39 204.29 42894 +1940 266 20.04 14.04 18.39 0.31 512.18 207 42690 +1940 267 22.06 16.06 20.41 1.17 572.86 200.76 42486 +1940 268 23.43 17.43 21.78 0.68 617.4 195.75 42282 +1940 269 22 16 20.35 0 570.98 263 42078 +1940 270 21.13 15.13 19.48 0.28 544.21 197.22 41875 +1940 271 21.09 15.09 19.44 0 543 260.55 41671 +1940 272 22.23 16.23 20.58 0 578.24 254.71 41468 +1940 273 19.53 13.53 17.88 0.03 497.76 194.66 41265 +1940 274 12.24 6.24 10.59 0.22 326.35 203.68 41062 +1940 275 10.43 4.43 8.78 0 292.66 271.5 40860 +1940 276 8.87 2.87 7.22 0 266.06 270.85 40658 +1940 277 10.99 4.99 9.34 0.18 302.75 198.94 40456 +1940 278 13.18 7.18 11.53 0 345.12 258.98 40255 +1940 279 16.21 10.21 14.56 0 412.03 250.74 40054 +1940 280 13.23 7.23 11.58 0.18 346.14 190.07 39854 +1940 281 15.84 9.84 14.19 0 403.31 246.15 39654 +1940 282 15.03 9.03 13.38 0.41 384.76 183.69 39455 +1940 283 14.4 8.4 12.75 0.27 370.85 182.41 39256 +1940 284 12.31 6.31 10.66 1.74 327.71 182.64 39058 +1940 285 10.16 4.16 8.51 0 287.9 243.85 38861 +1940 286 13.53 7.53 11.88 0 352.34 236.26 38664 +1940 287 15.55 9.55 13.9 0.16 396.58 172.49 38468 +1940 288 9.42 3.42 7.77 0.88 275.19 177.14 38273 +1940 289 8.72 2.72 7.07 0.24 263.61 175.75 38079 +1940 290 7.3 1.3 5.65 0.18 241.41 174.73 37885 +1940 291 9.11 3.11 7.46 0.74 270.01 171.19 37693 +1940 292 6.86 0.86 5.21 0.63 234.86 170.94 37501 +1940 293 8.42 2.42 6.77 1.61 258.78 167.65 37311 +1940 294 8.85 2.85 7.2 0.01 265.73 165.11 37121 +1940 295 10.13 4.13 8.48 0.01 287.37 161.88 36933 +1940 296 13.93 7.93 12.28 0.13 360.75 156.17 36745 +1940 297 14.27 8.27 12.62 0.03 368.03 153.78 36560 +1940 298 14.09 8.09 12.44 0.42 364.16 152.05 36375 +1940 299 13.17 7.17 11.52 0 344.91 201.29 36191 +1940 300 17.16 11.16 15.51 0 435.17 192.53 36009 +1940 301 16.67 10.67 15.02 0 423.1 190.92 35829 +1940 302 18.01 12.01 16.36 0 456.79 186.1 35650 +1940 303 20.1 14.1 18.45 0 513.9 179.71 35472 +1940 304 17.95 11.95 16.3 3.74 455.24 136.03 35296 +1940 305 13.81 7.81 12.16 0.56 358.21 138.79 35122 +1940 306 16.86 10.86 15.21 0 427.74 178.38 34950 +1940 307 12.6 6.6 10.95 0 333.43 181.94 34779 +1940 308 14.54 8.54 12.89 0.1 373.9 132.64 34610 +1940 309 12.12 6.12 10.47 0 324.02 177.66 34444 +1940 310 12.21 6.21 10.56 0 325.76 175.14 34279 +1940 311 10.36 4.36 8.71 0 291.42 175.03 34116 +1940 312 10.92 4.92 9.27 0.2 301.47 128.86 33956 +1940 313 12.33 6.33 10.68 0.01 328.11 126.13 33797 +1940 314 10.5 4.5 8.85 1.21 293.9 126.17 33641 +1940 315 8.19 2.19 6.54 0.35 255.13 125.91 33488 +1940 316 10.6 4.6 8.95 0.78 295.69 122.59 33337 +1940 317 10.53 4.53 8.88 0.43 294.44 121.01 33188 +1940 318 13.15 7.15 11.5 0 344.5 156.24 33042 +1940 319 11.18 5.18 9.53 0 306.24 156.72 32899 +1940 320 13.18 7.18 11.53 0 345.12 152.74 32758 +1940 321 11.75 5.75 10.1 0 316.91 152.22 32620 +1940 322 9.62 3.62 7.97 0 278.57 152.48 32486 +1940 323 9.25 3.25 7.6 0.15 272.34 113.41 32354 +1940 324 8.01 2.01 6.36 0 252.3 150.21 32225 +1940 325 6.36 0.36 4.71 0 227.61 149.74 32100 +1940 326 5.14 -0.86 3.49 0 210.72 149.11 31977 +1940 327 6.08 0.08 4.43 0 223.63 146.63 31858 +1940 328 7.29 1.29 5.64 0 241.26 143.8 31743 +1940 329 7.93 1.93 6.28 0 251.05 141.83 31631 +1940 330 8.4 2.4 6.75 0.01 258.46 105.02 31522 +1940 331 11.29 5.29 9.64 0 308.27 136.26 31417 +1940 332 7.22 1.22 5.57 0.13 240.2 103.48 31316 +1940 333 5.6 -0.4 3.95 0 216.95 138 31218 +1940 334 4.92 -1.08 3.27 0 207.79 137.32 31125 +1940 335 -3.9 -9.9 -5.55 0 115.82 140.21 31035 +1940 336 -5.88 -11.88 -7.53 0 100.92 139.73 30949 +1940 337 -3.13 -9.13 -4.78 0 122.12 137.17 30867 +1940 338 -3.6 -9.6 -5.25 0 118.24 136.37 30790 +1940 339 -2.67 -8.67 -4.32 0.18 126.02 144.97 30716 +1940 340 -0.08 -6.08 -1.73 0.53 150.04 145.4 30647 +1940 341 1.03 -4.97 -0.62 0 161.49 177.32 30582 +1940 342 -1.6 -7.6 -3.25 0.06 135.5 144.83 30521 +1940 343 0.39 -5.61 -1.26 0 154.8 176.31 30465 +1940 344 -2.35 -8.35 -4 0 128.79 176.34 30413 +1940 345 -1.73 -7.73 -3.38 0 134.32 175.74 30366 +1940 346 -4.06 -10.06 -5.71 0 114.55 176.05 30323 +1940 347 -5.41 -11.41 -7.06 0 104.3 175.91 30284 +1940 348 -4.19 -10.19 -5.84 0 113.53 175.24 30251 +1940 349 -2.76 -8.76 -4.41 0.14 125.24 142.75 30221 +1940 350 -0.07 -6.07 -1.72 0.03 150.14 141.86 30197 +1940 351 4.67 -1.33 3.02 0 204.5 170.53 30177 +1940 352 2.61 -3.39 0.96 0.03 179.09 139.8 30162 +1940 353 0.53 -5.47 -1.12 0 156.25 172.04 30151 +1940 354 -1.5 -7.5 -3.15 0 136.42 172.83 30145 +1940 355 2.31 -3.69 0.66 0.2 175.63 139.48 30144 +1940 356 -0.19 -6.19 -1.84 0.15 148.95 140.81 30147 +1940 357 -3 -9 -4.65 0.14 123.21 142.07 30156 +1940 358 -5.52 -11.52 -7.17 0 103.5 174.9 30169 +1940 359 -3.13 -9.13 -4.78 0 122.12 174.25 30186 +1940 360 -2.03 -8.03 -3.68 0 131.62 174.21 30208 +1940 361 -1.74 -7.74 -3.39 0 134.23 174.4 30235 +1940 362 3.92 -2.08 2.27 0 194.91 171.71 30267 +1940 363 1.91 -4.09 0.26 0 171.1 173.01 30303 +1940 364 1.61 -4.39 -0.04 0 167.77 173.28 30343 +1940 365 0.21 -5.79 -1.44 0 152.96 174.38 30388 +1941 1 -0.11 -6.11 -1.76 0.28 149.74 143.57 30438 +1941 2 1.77 -4.23 0.12 0 169.54 175.81 30492 +1941 3 1.24 -4.76 -0.41 0 163.74 176.75 30551 +1941 4 0.18 -5.82 -1.47 0.8 152.66 144.75 30614 +1941 5 -1.04 -7.04 -2.69 0.04 140.71 145.65 30681 +1941 6 -2.38 -8.38 -4.03 0 128.53 180.53 30752 +1941 7 0.33 -5.67 -1.32 0 154.19 180.09 30828 +1941 8 -2.44 -8.44 -4.09 0.08 128.01 148.34 30907 +1941 9 -4.43 -10.43 -6.08 0.01 111.66 149.72 30991 +1941 10 -9.33 -15.33 -10.98 0.63 78.9 153.53 31079 +1941 11 -6.4 -12.4 -8.05 0.2 97.29 154.21 31171 +1941 12 -3.45 -9.45 -5.1 0.5 119.47 155.68 31266 +1941 13 -2.95 -8.95 -4.6 0.28 123.63 157.48 31366 +1941 14 -1.33 -7.33 -2.98 0.4 137.99 159.19 31469 +1941 15 -0.24 -6.24 -1.89 0.16 148.45 160.24 31575 +1941 16 -1.13 -7.13 -2.78 0 139.86 198.34 31686 +1941 17 4.87 -1.13 3.22 1.1 207.13 159.44 31800 +1941 18 2.44 -3.56 0.79 0 177.12 198.93 31917 +1941 19 4.41 -1.59 2.76 0 201.13 198.97 32038 +1941 20 3.48 -2.52 1.83 0.13 189.47 162.29 32161 +1941 21 6.2 0.2 4.55 0 225.33 199.76 32289 +1941 22 4.82 -1.18 3.17 0 206.47 201.66 32419 +1941 23 5.82 -0.18 4.17 0 219.99 201.83 32552 +1941 24 3.12 -2.88 1.47 0 185.11 205.09 32688 +1941 25 1.34 -4.66 -0.31 0 164.82 207.65 32827 +1941 26 -2.43 -8.43 -4.08 0 128.09 211.2 32969 +1941 27 -5.22 -11.22 -6.87 0 105.69 214.14 33114 +1941 28 -3.26 -9.26 -4.91 0 121.03 215.45 33261 +1941 29 -2.53 -8.53 -4.18 0 127.22 217.37 33411 +1941 30 -3.04 -9.04 -4.69 0.08 122.87 175.75 33564 +1941 31 -5.58 -11.58 -7.23 0 103.06 223.08 33718 +1941 32 0.2 -5.8 -1.45 0 152.86 222.48 33875 +1941 33 4.09 -1.91 2.44 0 197.05 222.07 34035 +1941 34 4.81 -1.19 3.16 0 206.34 223 34196 +1941 35 4.55 -1.45 2.9 0 202.94 224.6 34360 +1941 36 5.38 -0.62 3.73 1.05 213.95 179.22 34526 +1941 37 5.67 -0.33 4.02 0.05 217.92 180.01 34694 +1941 38 9.01 3.01 7.36 0.28 268.36 140.76 34863 +1941 39 8.4 2.4 6.75 0.01 258.46 143.14 35035 +1941 40 7.78 1.78 6.13 1 248.73 145.52 35208 +1941 41 6.96 0.96 5.31 1.01 236.34 148.04 35383 +1941 42 5.22 -0.78 3.57 0.02 211.79 151.06 35560 +1941 43 6.57 0.57 4.92 0 230.63 202.96 35738 +1941 44 6.93 0.93 5.28 0 235.89 205.18 35918 +1941 45 8.32 2.32 6.67 0 257.19 206.44 36099 +1941 46 7.08 1.08 5.43 0.36 238.11 157.74 36282 +1941 47 2.37 -3.63 0.72 0.24 176.32 162.76 36466 +1941 48 2.57 -3.43 0.92 0 178.63 219.69 36652 +1941 49 3.36 -2.64 1.71 0.01 188.01 166.42 36838 +1941 50 5.54 -0.46 3.89 0 216.13 222.77 37026 +1941 51 4.78 -1.22 3.13 0 205.94 226.4 37215 +1941 52 -0.98 -6.98 -2.63 1.12 141.28 213.19 37405 +1941 53 0.1 -5.9 -1.55 0.48 151.85 214.74 37596 +1941 54 0.34 -5.66 -1.31 0 154.29 276.07 37788 +1941 55 2.9 -3.1 1.25 0 182.5 276.76 37981 +1941 56 3.45 -2.55 1.8 0 189.1 278.48 38175 +1941 57 3.1 -2.9 1.45 0 184.88 281.16 38370 +1941 58 4.87 -1.13 3.22 0.43 207.13 220.28 38565 +1941 59 6.02 0.02 4.37 0.2 222.79 220.69 38761 +1941 60 6.8 0.8 5.15 0.42 233.98 187.59 38958 +1941 61 7.49 1.49 5.84 0.32 244.28 189.22 39156 +1941 62 2.81 -3.19 1.16 0 181.43 259.6 39355 +1941 63 5.51 -0.49 3.86 0 215.72 260.18 39553 +1941 64 9.32 3.32 7.67 0.13 273.51 194.08 39753 +1941 65 11.21 5.21 9.56 1.81 306.79 194.29 39953 +1941 66 11.27 5.27 9.62 0.41 307.9 196.24 40154 +1941 67 12.82 6.82 11.17 0 337.82 262.12 40355 +1941 68 9.57 3.57 7.92 0.41 277.72 202.31 40556 +1941 69 6.14 0.14 4.49 0.74 224.48 207.38 40758 +1941 70 10.71 4.71 9.06 0.05 297.67 205.18 40960 +1941 71 9.3 3.3 7.65 0.45 273.17 208.83 41163 +1941 72 7.58 1.58 5.93 0.21 245.65 212.59 41366 +1941 73 7.71 1.71 6.06 0.27 247.65 214.47 41569 +1941 74 10.73 4.73 9.08 0 298.03 284.57 41772 +1941 75 5.09 -0.91 3.44 0 210.05 294.46 41976 +1941 76 1.4 -4.6 -0.25 0 165.48 300.62 42179 +1941 77 4.62 -1.38 2.97 0.26 203.85 225.19 42383 +1941 78 4.64 -1.36 2.99 0 204.11 302.92 42587 +1941 79 4.41 -1.59 2.76 0 201.13 305.92 42791 +1941 80 6.31 0.31 4.66 0 226.89 306.37 42996 +1941 81 4.11 -1.89 2.46 0.1 197.3 233.56 43200 +1941 82 5.04 -0.96 3.39 0.71 209.38 234.83 43404 +1941 83 7.59 1.59 5.94 0 245.81 312.54 43608 +1941 84 11.72 5.72 10.07 0.02 316.34 231.65 43812 +1941 85 11.63 5.63 9.98 0 314.64 311.49 44016 +1941 86 12.39 6.39 10.74 0 329.28 312.54 44220 +1941 87 13.54 7.54 11.89 0 352.55 312.89 44424 +1941 88 13.57 7.57 11.92 0.01 353.17 236.35 44627 +1941 89 9.91 3.91 8.26 0.02 283.55 242.87 44831 +1941 90 6.61 0.61 4.96 0.78 231.21 248.18 45034 +1941 91 7.07 1.07 5.42 1.75 237.97 249.44 45237 +1941 92 8.03 2.03 6.38 0.18 252.61 250.15 45439 +1941 93 8.25 2.25 6.6 0.57 256.08 251.58 45642 +1941 94 4.87 -1.13 3.22 0.05 207.13 256.53 45843 +1941 95 7.36 1.36 5.71 0.28 242.31 255.78 46045 +1941 96 5.99 -0.01 4.34 0 222.37 345 46246 +1941 97 7.96 1.96 6.31 0.05 251.52 258.3 46446 +1941 98 8.29 2.29 6.64 0.6 256.71 259.43 46647 +1941 99 9.3 3.3 7.65 0 273.17 346.38 46846 +1941 100 8.81 2.81 7.16 0 265.08 349.11 47045 +1941 101 14.1 8.1 12.45 0 364.37 341.34 47243 +1941 102 12.41 6.41 10.76 0 329.68 346.69 47441 +1941 103 10.92 4.92 9.27 0 301.47 351.31 47638 +1941 104 11.89 5.89 10.24 0 319.59 351.35 47834 +1941 105 14.43 8.43 12.78 0 371.5 347.9 48030 +1941 106 12.36 6.36 10.71 1.44 328.69 265.41 48225 +1941 107 11.73 5.73 10.08 0 316.53 356.78 48419 +1941 108 8.86 2.86 7.21 0 265.89 363.56 48612 +1941 109 7.74 1.74 6.09 0 248.11 366.93 48804 +1941 110 11.59 5.59 9.94 0 313.89 361.83 48995 +1941 111 15.19 9.19 13.54 0 388.37 355.67 49185 +1941 112 14.07 8.07 12.42 0.31 363.73 269.82 49374 +1941 113 15.13 9.13 13.48 0 387.01 358.65 49561 +1941 114 14.08 8.08 12.43 0 363.94 362.56 49748 +1941 115 15.77 9.77 14.12 0.62 401.68 269.98 49933 +1941 116 17.9 11.9 16.25 0 453.94 355.51 50117 +1941 117 15.81 9.81 14.16 0.25 402.61 271.78 50300 +1941 118 15.16 9.16 13.51 0.05 387.69 273.97 50481 +1941 119 14.75 8.75 13.1 0 378.52 367.46 50661 +1941 120 17.77 11.77 16.12 0.67 450.6 270.57 50840 +1941 121 18.89 12.89 17.24 0.33 480.14 268.93 51016 +1941 122 18.04 12.04 16.39 0.31 457.57 271.7 51191 +1941 123 18.39 12.39 16.74 1.49 466.76 271.69 51365 +1941 124 15.02 9.02 13.37 0.23 384.54 279.3 51536 +1941 125 12.37 6.37 10.72 0.23 328.89 284.53 51706 +1941 126 14.06 8.06 12.41 0.63 363.52 282.5 51874 +1941 127 11.47 5.47 9.82 0 311.63 383.11 52039 +1941 128 11.87 5.87 10.22 0 319.2 383.32 52203 +1941 129 11.09 5.09 9.44 0 304.58 385.74 52365 +1941 130 12.55 6.55 10.9 0 332.44 383.58 52524 +1941 131 10.39 4.39 8.74 0.02 291.95 291.52 52681 +1941 132 9.88 3.88 8.23 0 283.03 390.47 52836 +1941 133 11.92 5.92 10.27 0 320.16 387.26 52989 +1941 134 13.3 7.3 11.65 0.63 347.58 288.76 53138 +1941 135 17.45 11.45 15.8 0.31 442.44 281.37 53286 +1941 136 16.94 10.94 15.29 0.21 429.71 282.93 53430 +1941 137 17.87 11.87 16.22 0.46 453.17 281.46 53572 +1941 138 18.09 12.09 16.44 0.18 458.88 281.42 53711 +1941 139 16.19 10.19 14.54 0.02 411.56 285.97 53848 +1941 140 16.67 10.67 15.02 0.17 423.1 285.35 53981 +1941 141 16.77 10.77 15.12 0 425.54 380.63 54111 +1941 142 17 11 15.35 0 431.19 380.48 54238 +1941 143 15.9 9.9 14.25 0 404.71 384.02 54362 +1941 144 18.73 12.73 17.08 0 475.82 376.36 54483 +1941 145 21.15 15.15 19.5 0.14 544.81 276.55 54600 +1941 146 14.53 8.53 12.88 0.65 373.68 291.63 54714 +1941 147 15.12 9.12 13.47 0.23 386.79 290.89 54824 +1941 148 12.52 6.52 10.87 0.15 331.84 295.76 54931 +1941 149 11.51 5.51 9.86 0.61 312.38 297.59 55034 +1941 150 8.63 2.63 6.98 0.18 262.15 301.88 55134 +1941 151 12.37 6.37 10.72 0.38 328.89 296.8 55229 +1941 152 21.92 15.92 20.27 0 568.47 368.23 55321 +1941 153 18.69 12.69 17.04 0 474.75 379.57 55409 +1941 154 16.78 10.78 15.13 0 425.78 385.55 55492 +1941 155 17.6 11.6 15.95 0.54 446.25 287.54 55572 +1941 156 14.47 8.47 12.82 0.03 372.37 294.09 55648 +1941 157 16.29 10.29 14.64 0.38 413.94 290.69 55719 +1941 158 17.62 11.62 15.97 1.17 446.76 288 55786 +1941 159 18.24 12.24 16.59 0.02 462.8 286.78 55849 +1941 160 17.65 11.65 16 0 447.52 384.33 55908 +1941 161 17.72 11.72 16.07 0 449.31 384.19 55962 +1941 162 17.03 11.03 15.38 0.56 431.94 289.7 56011 +1941 163 19.86 13.86 18.21 0 507.05 377.71 56056 +1941 164 17.64 11.64 15.99 0.7 447.27 288.57 56097 +1941 165 19.79 13.79 18.14 0.18 505.07 283.56 56133 +1941 166 20.67 14.67 19.02 0.05 530.49 281.35 56165 +1941 167 25.17 19.17 23.52 0.09 678.18 267.81 56192 +1941 168 22.32 16.32 20.67 0.01 581.1 276.81 56214 +1941 169 25.12 19.12 23.47 0 676.36 357.39 56231 +1941 170 23.04 17.04 21.39 0 604.44 366.25 56244 +1941 171 23.63 17.63 21.98 0 624.15 363.9 56252 +1941 172 23.2 17.2 21.55 0.14 609.73 274.24 56256 +1941 173 23.76 17.76 22.11 0.06 628.56 272.5 56255 +1941 174 24.06 18.06 22.41 0 638.85 361.98 56249 +1941 175 22.5 16.5 20.85 0 586.86 368.31 56238 +1941 176 26.96 20.96 25.31 0.01 745.9 261.42 56223 +1941 177 26.57 20.57 24.92 0.04 730.68 262.78 56203 +1941 178 24.14 18.14 22.49 0.16 641.62 271.13 56179 +1941 179 20.12 14.12 18.47 0.11 514.48 282.59 56150 +1941 180 17.39 11.39 15.74 0.35 440.93 288.96 56116 +1941 181 17.1 11.1 15.45 0.15 433.67 289.53 56078 +1941 182 23.09 17.09 21.44 0 606.09 365.43 56035 +1941 183 25.36 19.36 23.71 0.08 685.11 266.64 55987 +1941 184 23.16 17.16 21.51 0 608.4 364.83 55935 +1941 185 27.71 21.71 26.06 0 775.93 343.88 55879 +1941 186 27.98 21.98 26.33 0 786.99 342.23 55818 +1941 187 29.17 23.17 27.52 0 837.32 335.62 55753 +1941 188 25.3 19.3 23.65 0.03 682.91 266.17 55684 +1941 189 23.5 17.5 21.85 0.25 619.76 271.87 55611 +1941 190 18.39 12.39 16.74 0.07 466.76 285.27 55533 +1941 191 18.91 12.91 17.26 0.02 480.69 283.85 55451 +1941 192 18.05 12.05 16.4 0.45 457.83 285.61 55366 +1941 193 21.85 15.85 20.2 0.76 566.28 275.82 55276 +1941 194 23.11 17.11 21.46 0.44 606.75 272 55182 +1941 195 20.43 14.43 18.78 0.74 523.45 279.28 55085 +1941 196 19.46 13.46 17.81 1.01 495.8 281.41 54984 +1941 197 20.98 14.98 19.33 0.04 539.7 277.19 54879 +1941 198 18.77 12.77 17.12 0.05 476.9 282.39 54770 +1941 199 18.33 12.33 16.68 0 465.17 377.52 54658 +1941 200 20.42 14.42 18.77 0 523.16 370.36 54542 +1941 201 15.71 9.71 14.06 0.18 400.28 288.02 54423 +1941 202 20.34 14.34 18.69 0 520.83 369.6 54301 +1941 203 21.22 15.22 19.57 0.46 546.93 274.52 54176 +1941 204 26.18 20.18 24.53 0.01 715.72 258.83 54047 +1941 205 25.11 19.11 23.46 0 676 349.5 53915 +1941 206 24.72 18.72 23.07 0 661.99 350.66 53780 +1941 207 25.22 19.22 23.57 0.01 679.99 260.88 53643 +1941 208 23.57 17.57 21.92 0 622.12 354.21 53502 +1941 209 21.27 15.27 19.62 0 548.44 362.32 53359 +1941 210 22.58 16.58 20.93 0 589.44 356.86 53213 +1941 211 19.53 13.53 17.88 0.28 497.76 275.11 53064 +1941 212 21.19 15.19 19.54 0 546.02 360.42 52913 +1941 213 19.54 13.54 17.89 0 498.04 365.22 52760 +1941 214 19.63 13.63 17.98 0 500.56 364.18 52604 +1941 215 18.22 12.22 16.57 0 462.28 367.85 52445 +1941 216 20.39 14.39 18.74 0 522.29 359.99 52285 +1941 217 17.97 11.97 16.32 0 455.76 366.66 52122 +1941 218 18.34 12.34 16.69 0.71 465.43 273.56 51958 +1941 219 18.3 12.3 16.65 0.02 464.38 272.85 51791 +1941 220 17.04 11.04 15.39 0.09 432.18 274.83 51622 +1941 221 18.34 12.34 16.69 0 465.43 361.72 51451 +1941 222 19.91 13.91 18.26 0.61 508.47 266.87 51279 +1941 223 22.87 16.87 21.22 0.45 598.86 258.25 51105 +1941 224 19.16 13.16 17.51 0.62 487.51 266.99 50929 +1941 225 18.81 12.81 17.16 0.55 477.98 266.92 50751 +1941 226 22.34 16.34 20.69 0 581.74 343.03 50572 +1941 227 25.61 19.61 23.96 0 694.32 328.69 50392 +1941 228 26.24 20.24 24.59 1.14 718 243.55 50210 +1941 229 22.6 16.6 20.95 0 590.08 338.41 50026 +1941 230 19.31 13.31 17.66 0 491.64 348.2 49842 +1941 231 19.47 13.47 17.82 0.23 496.08 259.68 49656 +1941 232 22.28 16.28 20.63 0.11 579.83 251.68 49469 +1941 233 25.11 19.11 23.46 0 676 323.22 49280 +1941 234 23.61 17.61 21.96 0 623.47 327.87 49091 +1941 235 23.78 17.78 22.13 0.15 629.24 244.33 48900 +1941 236 21.23 15.23 19.58 0.77 547.23 250.16 48709 +1941 237 20.2 14.2 18.55 0.51 516.78 251.44 48516 +1941 238 19.2 13.2 17.55 0.1 488.61 252.47 48323 +1941 239 22.46 16.46 20.81 0 585.58 324.59 48128 +1941 240 17.91 11.91 16.26 0.03 454.2 252.76 47933 +1941 241 23.42 17.42 21.77 0.78 617.07 238.3 47737 +1941 242 20.83 14.83 19.18 1.51 535.23 243.71 47541 +1941 243 23.18 17.18 21.53 1.19 609.06 236.35 47343 +1941 244 16.19 10.19 14.54 0 411.56 334.2 47145 +1941 245 15.56 9.56 13.91 0 396.81 333.83 46947 +1941 246 13.82 7.82 12.17 0 358.42 335.65 46747 +1941 247 11.45 5.45 9.8 0 311.26 338.33 46547 +1941 248 16.19 10.19 14.54 0 411.56 326.51 46347 +1941 249 13.98 7.98 12.33 0 361.81 329.33 46146 +1941 250 12.9 6.9 11.25 0.05 339.43 247.12 45945 +1941 251 14.38 8.38 12.73 0.86 370.41 243.26 45743 +1941 252 19.12 13.12 17.47 0 486.41 310.7 45541 +1941 253 16.62 10.62 14.97 0 421.88 315 45339 +1941 254 17.78 11.78 16.13 0 450.85 310.02 45136 +1941 255 17.9 11.9 16.25 0 453.94 307.47 44933 +1941 256 17.11 11.11 15.46 0 433.92 307.16 44730 +1941 257 20.23 14.23 18.58 0 517.65 296.81 44527 +1941 258 17.91 11.91 16.26 0 454.2 300.7 44323 +1941 259 18.35 12.35 16.7 0 465.7 297.19 44119 +1941 260 19.9 13.9 18.25 0 508.19 290.73 43915 +1941 261 19.01 13.01 17.36 0 483.41 290.72 43711 +1941 262 19.35 13.35 17.7 0.05 492.75 215.62 43507 +1941 263 23.14 17.14 21.49 0 607.74 273.96 43303 +1941 264 20.76 14.76 19.11 0 533.15 278.72 43099 +1941 265 21.74 15.74 20.09 0 562.86 273.59 42894 +1941 266 20.11 14.11 18.46 0 514.19 275.81 42690 +1941 267 15.25 9.25 13.6 0.52 389.73 213.4 42486 +1941 268 13.06 7.06 11.41 0 342.67 286.08 42282 +1941 269 15.7 9.7 14.05 0 400.05 278.55 42078 +1941 270 14.49 8.49 12.84 0 372.81 278.29 41875 +1941 271 12.62 6.62 10.97 0 333.83 278.97 41671 +1941 272 13.17 7.17 11.52 0.04 344.91 206.46 41468 +1941 273 12.48 6.48 10.83 0.57 331.05 205.41 41265 +1941 274 8.12 2.12 6.47 0 254.02 277.4 41062 +1941 275 11.47 5.47 9.82 0 311.63 269.97 40860 +1941 276 8.78 2.78 7.13 0.26 264.59 203.23 40658 +1941 277 11.87 5.87 10.22 0.07 319.2 197.96 40456 +1941 278 14.22 8.22 12.57 0 366.95 257.21 40255 +1941 279 15.54 9.54 13.89 0 396.35 252.02 40054 +1941 280 16.12 10.12 14.47 0.37 409.89 186.22 39854 +1941 281 19.26 13.26 17.61 0 490.26 239.03 39654 +1941 282 17.11 11.11 15.46 0.17 433.92 180.74 39455 +1941 283 14.29 8.29 12.64 0.04 368.46 182.55 39256 +1941 284 12.12 6.12 10.47 0 324.02 243.81 39058 +1941 285 10.18 4.18 8.53 0 288.25 243.82 38861 +1941 286 8.6 2.6 6.95 0.01 261.67 182.22 38664 +1941 287 13.12 7.12 11.47 1.45 343.89 175.48 38468 +1941 288 10.43 4.43 8.78 0.34 292.66 176.2 38273 +1941 289 10.26 4.26 8.61 0.56 289.65 174.37 38079 +1941 290 10.97 4.97 9.32 0.06 302.38 171.53 37885 +1941 291 11.89 5.89 10.24 0 319.59 224.77 37693 +1941 292 14.09 8.09 12.44 0 364.16 218.9 37501 +1941 293 13.4 7.4 11.75 2.3 349.64 162.93 37311 +1941 294 13.54 7.54 11.89 0.05 352.55 160.63 37121 +1941 295 12.64 6.64 10.99 0.03 334.22 159.47 36933 +1941 296 13.29 7.29 11.64 0 347.37 209.16 36745 +1941 297 9.26 3.26 7.61 0 272.5 211.48 36560 +1941 298 10.97 4.97 9.32 0.06 302.38 155.17 36375 +1941 299 13.93 7.93 12.28 0 360.75 200.22 36191 +1941 300 10.3 4.3 8.65 0.07 290.36 151.67 36009 +1941 301 11.44 5.44 9.79 0 311.07 198.37 35829 +1941 302 11.01 5.01 9.36 0 303.11 196.28 35650 +1941 303 11.38 5.38 9.73 0 309.95 193.28 35472 +1941 304 14.71 8.71 13.06 0 377.64 186.5 35296 +1941 305 9.45 3.45 7.8 0 275.69 190.22 35122 +1941 306 14.11 8.11 12.46 0 364.59 182.45 34950 +1941 307 12.35 6.35 10.7 0.01 328.5 136.68 34779 +1941 308 8.65 2.65 7 0.66 262.48 137.73 34610 +1941 309 4.92 -1.08 3.27 0.44 207.79 138.35 34444 +1941 310 3.43 -2.57 1.78 0.23 188.86 137.29 34279 +1941 311 3.97 -2.03 2.32 0 195.54 180.47 34116 +1941 312 3.62 -2.38 1.97 0 191.19 178.03 33956 +1941 313 1.53 -4.47 -0.12 0 166.89 177.17 33797 +1941 314 5.69 -0.31 4.04 0 218.19 172.45 33641 +1941 315 3.73 -2.27 2.08 0 192.55 171.26 33488 +1941 316 3.54 -2.46 1.89 0.9 190.2 126.88 33337 +1941 317 2.79 -3.21 1.14 0.95 181.2 125.57 33188 +1941 318 1.98 -4.02 0.33 0.05 171.89 124.15 33042 +1941 319 -1.39 -7.39 -3.04 1.27 137.44 167.95 32899 +1941 320 0.38 -5.62 -1.27 0.52 154.7 166.03 32758 +1941 321 3.92 -2.08 2.27 0.13 194.91 162.64 32620 +1941 322 5.62 -0.38 3.97 0.01 217.23 159.9 32486 +1941 323 8.39 2.39 6.74 0 258.3 194.23 32354 +1941 324 5.32 -0.68 3.67 0.23 213.14 155.93 32225 +1941 325 3.4 -2.6 1.75 0.08 188.49 155.27 32100 +1941 326 -0.16 -6.16 -1.81 0.25 149.25 156.47 31977 +1941 327 0.18 -5.82 -1.47 0 152.66 192.59 31858 +1941 328 -0.53 -6.53 -2.18 0 145.6 191.07 31743 +1941 329 -0.17 -6.17 -1.82 0.58 149.15 154.63 31631 +1941 330 3.14 -2.86 1.49 0.14 185.35 152.04 31522 +1941 331 6.04 0.04 4.39 0.26 223.07 149.09 31417 +1941 332 9.95 3.95 8.3 0.98 284.24 144.5 31316 +1941 333 6.61 0.61 4.96 2.09 231.21 102.99 31218 +1941 334 7.08 1.08 5.43 0.03 238.11 101.93 31125 +1941 335 0.45 -5.55 -1.2 0 155.42 138.51 31035 +1941 336 -0.23 -6.23 -1.88 0 148.55 137.72 30949 +1941 337 0.18 -5.82 -1.47 0.1 152.66 101.9 30867 +1941 338 2.53 -3.47 0.88 0 178.16 133.8 30790 +1941 339 2.87 -3.13 1.22 0 182.14 132.83 30716 +1941 340 2.53 -3.47 0.88 0 178.16 132.26 30647 +1941 341 4.45 -1.55 2.8 0 201.65 130.31 30582 +1941 342 3.93 -2.07 2.28 0 195.04 129.84 30521 +1941 343 8.77 2.77 7.12 0 264.42 125.89 30465 +1941 344 6.08 0.08 4.43 0 223.63 126.61 30413 +1941 345 6.24 0.24 4.59 0 225.9 126.09 30366 +1941 346 5.46 -0.54 3.81 0.38 215.04 94.52 30323 +1941 347 6.68 0.68 5.03 0.23 232.23 93.5 30284 +1941 348 7.06 1.06 5.41 0 237.82 124.07 30251 +1941 349 4.13 -1.87 2.48 0.05 197.56 94.1 30221 +1941 350 7.28 1.28 5.63 0 241.11 123.21 30197 +1941 351 4.27 -1.73 2.62 0 199.34 124.83 30177 +1941 352 3.14 -2.86 1.49 0.76 185.35 94 30162 +1941 353 4.88 -1.12 3.23 0.43 207.26 93.25 30151 +1941 354 4.27 -1.73 2.62 0.12 199.34 93.48 30145 +1941 355 1.69 -4.31 0.04 0.45 168.65 94.46 30144 +1941 356 -2.29 -8.29 -3.94 0.39 129.32 140.72 30147 +1941 357 1.17 -4.83 -0.48 0 162.99 171.13 30156 +1941 358 -0.55 -6.55 -2.2 0 145.41 171.93 30169 +1941 359 -0.51 -6.51 -2.16 0 145.8 172.01 30186 +1941 360 3.48 -2.52 1.83 0 189.47 170.04 30208 +1941 361 1.65 -4.35 0 0 168.21 171.02 30235 +1941 362 3.37 -2.63 1.72 0 188.13 126.55 30267 +1941 363 8.05 2.05 6.4 0 252.93 124.27 30303 +1941 364 6.24 0.24 4.59 0 225.9 125.87 30343 +1941 365 5.03 -0.97 3.38 0 209.25 127.18 30388 +1942 1 -6 -12 -7.65 0 100.07 132.67 30438 +1942 2 -6 -12 -7.65 0 100.07 133.42 30492 +1942 3 -6 -12 -7.65 0 100.07 134.37 30551 +1942 4 -6 -12 -7.65 0.55 100.07 146.32 30614 +1942 5 -6 -12 -7.65 0 100.07 180.71 30681 +1942 6 -6 -12 -7.65 0.08 100.07 147.55 30752 +1942 7 -6 -12 -7.65 0 100.07 182.47 30828 +1942 8 -6 -12 -7.65 0.2 100.07 149.68 30907 +1942 9 -6 -12 -7.65 0.6 100.07 152.38 30991 +1942 10 -6 -12 -7.65 0 100.07 188.69 31079 +1942 11 -6 -12 -7.65 0 100.07 189.56 31171 +1942 12 -6 -12 -7.65 0 100.07 190.45 31266 +1942 13 -6 -12 -7.65 0.07 100.07 155.79 31366 +1942 14 -6 -12 -7.65 0.28 100.07 157.62 31469 +1942 15 -6 -12 -7.65 0 100.07 195.68 31575 +1942 16 -6 -12 -7.65 0.45 100.07 160.75 31686 +1942 17 -6 -12 -7.65 0 100.07 199.74 31800 +1942 18 -6 -12 -7.65 0.08 100.07 163.37 31917 +1942 19 -6 -12 -7.65 0 100.07 203.51 32038 +1942 20 -6 -12 -7.65 0 100.07 204.95 32161 +1942 21 -6 -12 -7.65 0.09 100.07 167.31 32289 +1942 22 -6 -12 -7.65 0 100.07 208.66 32419 +1942 23 -6 -12 -7.65 0 100.07 210.27 32552 +1942 24 -6 -12 -7.65 0 100.07 212.18 32688 +1942 25 -6 -12 -7.65 0.41 100.07 173.43 32827 +1942 26 -6 -12 -7.65 0 100.07 216.86 32969 +1942 27 -6 -12 -7.65 0 100.07 218.71 33114 +1942 28 -6 -12 -7.65 0.02 100.07 177.57 33261 +1942 29 -6 -12 -7.65 0.01 100.07 179.2 33411 +1942 30 -6 -12 -7.65 0 100.07 225.11 33564 +1942 31 -6 -12 -7.65 0 100.07 227.31 33718 +1942 32 -6.5 -12.5 -8.15 0 96.61 229.42 33875 +1942 33 -3.81 -9.81 -5.46 0.14 116.55 185.26 34035 +1942 34 -5.39 -11.39 -7.04 0.01 104.44 187.2 34196 +1942 35 -3.42 -9.42 -5.07 0.01 119.71 188.07 34360 +1942 36 -2.11 -8.11 -3.76 0.5 130.91 190.71 34526 +1942 37 -1.61 -7.61 -3.26 0.28 135.41 192.92 34694 +1942 38 -5.55 -11.55 -7.2 0 103.28 245.29 34863 +1942 39 -4.74 -10.74 -6.39 0.52 109.28 198.98 35035 +1942 40 -4.06 -10.06 -5.71 1.57 114.55 204.81 35208 +1942 41 -3.94 -9.94 -5.59 0.93 115.51 209.03 35383 +1942 42 -3.78 -9.78 -5.43 1.07 116.79 213.54 35560 +1942 43 0.22 -5.78 -1.43 0 153.07 265.65 35738 +1942 44 0.55 -5.45 -1.1 0.04 156.45 215.19 35918 +1942 45 0.66 -5.34 -0.99 0.03 157.6 216.77 36099 +1942 46 3.89 -2.11 2.24 0.45 194.54 216.4 36282 +1942 47 1.02 -4.98 -0.63 0.25 161.39 219.65 36466 +1942 48 -0.77 -6.77 -2.42 0 143.28 277.77 36652 +1942 49 0.57 -5.43 -1.08 0.07 156.66 223.47 36838 +1942 50 0.37 -5.63 -1.28 0 154.6 281.93 37026 +1942 51 1.49 -4.51 -0.16 0.68 166.46 226.52 37215 +1942 52 0.44 -5.56 -1.21 0 155.32 286.98 37405 +1942 53 0.32 -5.68 -1.33 0.1 154.09 230.86 37596 +1942 54 2.44 -3.56 0.79 0.72 177.12 231.3 37788 +1942 55 -1.48 -7.48 -3.13 0.09 136.61 235.48 37981 +1942 56 1.11 -4.89 -0.54 0 162.35 296.79 38175 +1942 57 3.79 -2.21 2.14 0 193.29 296.97 38370 +1942 58 4.62 -1.38 2.97 0.24 203.85 236.78 38565 +1942 59 7.8 1.8 6.15 0 249.03 296.88 38761 +1942 60 10.23 4.23 8.58 0.13 289.12 233.97 38958 +1942 61 12.79 6.79 11.14 0 337.22 293.16 39156 +1942 62 12.1 6.1 10.45 0 323.63 295.45 39355 +1942 63 9.31 3.31 7.66 0 273.34 301.08 39553 +1942 64 6.52 0.52 4.87 0.08 229.91 240.82 39753 +1942 65 7.11 1.11 5.46 0 238.56 307.64 39953 +1942 66 9.37 3.37 7.72 0 274.35 306.48 40154 +1942 67 6.36 0.36 4.71 0.66 227.61 244.42 40355 +1942 68 2.6 -3.4 0.95 0 178.98 318.17 40556 +1942 69 1.38 -4.62 -0.27 0 165.26 321.5 40758 +1942 70 3.99 -2.01 2.34 0 195.79 321.51 40960 +1942 71 11.17 5.17 9.52 0.02 306.05 245.48 41163 +1942 72 5.06 -0.94 3.41 0 209.65 324.26 41366 +1942 73 3.27 -2.73 1.62 0.08 186.92 255.53 41569 +1942 74 5.23 -0.77 3.58 0 211.92 328.35 41772 +1942 75 2.95 -3.05 1.3 0 183.09 332.91 41976 +1942 76 1 -5 -0.65 0 161.18 337.01 42179 +1942 77 -1.28 -7.28 -2.93 0.01 138.46 264.91 42383 +1942 78 -1.41 -7.41 -3.06 0 137.25 343.89 42587 +1942 79 -0.86 -6.86 -2.51 0 142.42 346.12 42791 +1942 80 1.61 -4.39 -0.04 0 167.77 346.41 42996 +1942 81 1.71 -4.29 0.06 0 168.88 348.62 43200 +1942 82 5.36 -0.64 3.71 0 213.68 347 43404 +1942 83 4.64 -1.36 2.99 0.08 204.11 270.71 43608 +1942 84 1.72 -4.28 0.07 0.01 168.99 274.5 43812 +1942 85 1.78 -4.22 0.13 0.37 169.65 276.05 44016 +1942 86 2.81 -3.19 1.16 0.38 181.43 276.76 44220 +1942 87 5.66 -0.34 4.01 0 217.78 356.96 44424 +1942 88 6.54 0.54 4.89 0 230.2 357.52 44627 +1942 89 8.43 2.43 6.78 0 258.94 356.37 44831 +1942 90 8.99 2.99 7.34 0 268.03 356.99 45034 +1942 91 14.77 8.77 13.12 0 378.97 319.46 45237 +1942 92 17.72 11.72 16.07 0 449.31 314.74 45439 +1942 93 16.55 10.55 14.9 0.01 420.19 239.83 45642 +1942 94 14.82 8.82 13.17 0.77 380.08 244.37 45843 +1942 95 15.93 9.93 14.28 0 405.42 325.42 46045 +1942 96 13.19 7.19 11.54 0.2 345.32 250.06 46246 +1942 97 10.22 4.22 8.57 0.02 288.95 255.67 46446 +1942 98 10.43 4.43 8.78 0.29 292.66 256.88 46647 +1942 99 4.74 -1.26 3.09 0 205.42 352.68 46846 +1942 100 2.33 -3.67 0.68 0 175.86 357.33 47045 +1942 101 5.6 -0.4 3.95 0.82 216.95 266.69 47243 +1942 102 3.91 -2.09 2.26 0.07 194.79 269.67 47441 +1942 103 5.32 -0.68 3.67 0 213.14 359.76 47638 +1942 104 6.03 0.03 4.38 0 222.93 360.71 47834 +1942 105 15.36 9.36 13.71 0 392.23 345.77 48030 +1942 106 16.82 10.82 15.17 0.45 426.76 257.84 48225 +1942 107 18.46 12.46 16.81 0.91 468.61 255.72 48419 +1942 108 18.01 12.01 16.36 0 456.79 343.93 48612 +1942 109 16.87 10.87 15.22 0 427.99 348.57 48804 +1942 110 15.06 9.06 13.41 0.06 385.44 265.84 48995 +1942 111 12.83 6.83 11.18 0.02 338.02 270.69 49185 +1942 112 14 8 12.35 0 362.24 359.92 49374 +1942 113 13.42 7.42 11.77 0.09 350.05 271.9 49561 +1942 114 10.38 4.38 8.73 0.16 291.77 277.51 49748 +1942 115 9.28 3.28 7.63 2.66 272.84 280.04 49933 +1942 116 10.48 4.48 8.83 0.7 293.55 279.39 50117 +1942 117 8.88 2.88 7.23 1.04 266.22 282.47 50300 +1942 118 8.6 2.6 6.95 0.24 261.67 283.82 50481 +1942 119 8.34 2.34 6.69 0.14 257.5 285.05 50661 +1942 120 5.66 -0.34 4.01 0.05 217.78 288.91 50840 +1942 121 11.06 5.06 9.41 0.2 304.03 283.23 51016 +1942 122 13 7 11.35 0.11 341.45 281.19 51191 +1942 123 15.56 9.56 13.91 0.61 396.81 277.49 51365 +1942 124 15.3 9.3 13.65 0.17 390.86 278.78 51536 +1942 125 15.5 9.5 13.85 0.01 395.43 279.14 51706 +1942 126 12.8 6.8 11.15 0.22 337.42 284.6 51874 +1942 127 12.15 6.15 10.5 1.88 324.6 286.3 52039 +1942 128 14.1 8.1 12.45 0.03 364.37 283.85 52203 +1942 129 10.71 4.71 9.06 1.23 297.67 289.85 52365 +1942 130 16.56 10.56 14.91 0.48 420.43 280.45 52524 +1942 131 18.93 12.93 17.28 0.31 481.23 275.89 52681 +1942 132 18.62 12.62 16.97 0.2 472.87 277.21 52836 +1942 133 17.42 11.42 15.77 0 441.69 373.85 52989 +1942 134 15.08 9.08 13.43 0.87 385.89 285.61 53138 +1942 135 17.03 11.03 15.38 0 431.94 376.36 53286 +1942 136 18.06 12.06 16.41 0 458.09 374.02 53430 +1942 137 22.91 16.91 21.26 0 600.17 358.07 53572 +1942 138 21.48 15.48 19.83 0.16 554.85 273.03 53711 +1942 139 24.58 18.58 22.93 0 657.03 352.43 53848 +1942 140 22.75 16.75 21.1 0 594.94 360.4 53981 +1942 141 24.05 18.05 22.4 0.14 638.51 266.66 54111 +1942 142 18.44 12.44 16.79 0.37 468.08 282.19 54238 +1942 143 17.44 11.44 15.79 0 442.19 379.76 54362 +1942 144 15.8 9.8 14.15 0 402.38 384.77 54483 +1942 145 21.24 15.24 19.59 0 547.53 368.41 54600 +1942 146 19.97 13.97 18.32 0.9 510.18 279.89 54714 +1942 147 19.87 13.87 18.22 0.5 507.33 280.5 54824 +1942 148 19.61 13.61 17.96 0.11 500 281.43 54931 +1942 149 23.13 17.13 21.48 0.29 607.41 272.04 55034 +1942 150 22.89 16.89 21.24 0.31 599.51 273 55134 +1942 151 19.66 13.66 18.01 0.09 501.4 282.07 55229 +1942 152 23.19 17.19 21.54 0.04 609.4 272.46 55321 +1942 153 23.18 17.18 21.53 0.88 609.06 272.67 55409 +1942 154 22.84 16.84 21.19 0.1 597.88 273.92 55492 +1942 155 21.56 15.56 19.91 0 557.3 370.3 55572 +1942 156 24.34 18.34 22.69 0 648.58 359.52 55648 +1942 157 24.25 18.25 22.6 0 645.44 360.07 55719 +1942 158 21.99 15.99 20.34 0.07 570.66 277.01 55786 +1942 159 21.92 15.92 20.27 0.68 568.47 277.39 55849 +1942 160 16.74 10.74 15.09 0.02 424.8 290.21 55908 +1942 161 14.26 8.26 12.61 0 367.81 393.49 55962 +1942 162 20.09 14.09 18.44 0.23 513.62 282.54 56011 +1942 163 21.01 15.01 19.36 0.11 540.6 280.29 56056 +1942 164 20.3 14.3 18.65 0.24 519.67 282.19 56097 +1942 165 19.21 13.21 17.56 0.85 488.88 284.99 56133 +1942 166 22.31 16.31 20.66 0.3 580.78 276.82 56165 +1942 167 15.44 9.44 13.79 0.54 394.06 293.24 56192 +1942 168 11.56 5.56 9.91 0.16 313.32 300.05 56214 +1942 169 12.13 6.13 10.48 0 324.21 398.88 56231 +1942 170 19.35 13.35 17.7 0.11 492.75 284.74 56244 +1942 171 21.57 15.57 19.92 0.04 557.61 278.99 56252 +1942 172 23.83 17.83 22.18 0.07 630.95 272.29 56256 +1942 173 20.93 14.93 19.28 0 538.21 374.29 56255 +1942 174 22.41 16.41 20.76 2.3 583.98 276.52 56249 +1942 175 18.92 12.92 17.27 0.33 480.96 285.72 56238 +1942 176 20.32 14.32 18.67 0.72 520.25 282.21 56223 +1942 177 19.22 13.22 17.57 0.62 489.16 284.89 56203 +1942 178 22.07 16.07 20.42 0.16 573.18 277.39 56179 +1942 179 21.82 15.82 20.17 0 565.35 370.7 56150 +1942 180 21.38 15.38 19.73 0.04 551.79 279.16 56116 +1942 181 19.67 13.67 18.02 0 501.68 378.11 56078 +1942 182 21.76 15.76 20.11 0 563.48 370.59 56035 +1942 183 24.9 18.9 23.25 0.07 668.43 268.2 55987 +1942 184 24.38 18.38 22.73 0.04 649.98 269.8 55935 +1942 185 25.2 19.2 23.55 0.04 679.27 267.02 55879 +1942 186 26.05 20.05 24.4 0 710.79 351.85 55818 +1942 187 26.97 20.97 25.32 0 746.3 347.22 55753 +1942 188 26.46 20.46 24.81 0 726.43 349.46 55684 +1942 189 27.9 21.9 26.25 0.84 783.7 256.55 55611 +1942 190 26.77 20.77 25.12 0 738.45 347.42 55533 +1942 191 23.76 17.76 22.11 0 628.56 360.79 55451 +1942 192 22.77 16.77 21.12 0 595.59 364.5 55366 +1942 193 21.34 15.34 19.69 0.11 550.57 277.23 55276 +1942 194 24.5 18.5 22.85 0 654.2 356.88 55182 +1942 195 21.17 15.17 19.52 0.18 545.42 277.32 55085 +1942 196 23.12 17.12 21.47 0 607.08 361.96 54984 +1942 197 27.59 21.59 25.94 0.26 771.06 255.93 54879 +1942 198 25.18 19.18 23.53 0 678.54 352.37 54770 +1942 199 26.09 20.09 24.44 0.02 712.3 260.9 54658 +1942 200 21.79 15.79 20.14 0.17 564.42 274.11 54542 +1942 201 19.96 13.96 18.31 0.67 509.9 278.59 54423 +1942 202 18.48 12.48 16.83 0 469.14 375.61 54301 +1942 203 15.06 9.06 13.41 0.17 385.44 288.44 54176 +1942 204 12.38 6.38 10.73 0.12 329.09 292.69 54047 +1942 205 13.63 7.63 11.98 0.61 354.42 290.22 53915 +1942 206 16.35 10.35 14.7 0.55 415.37 284.7 53780 +1942 207 14.42 8.42 12.77 0.33 371.28 287.88 53643 +1942 208 15.08 9.08 13.43 1.85 385.89 286.16 53502 +1942 209 15.72 9.72 14.07 0.16 400.51 284.44 53359 +1942 210 17.88 11.88 16.23 0.63 453.43 279.5 53213 +1942 211 21.42 15.42 19.77 0 553.01 360.39 53064 +1942 212 21.5 15.5 19.85 0.12 555.46 269.49 52913 +1942 213 21.84 15.84 20.19 0 565.97 357.33 52760 +1942 214 22.56 16.56 20.91 0.08 588.79 265.44 52604 +1942 215 22.45 16.45 20.8 0 585.26 353.67 52445 +1942 216 20.5 14.5 18.85 0.09 525.5 269.71 52285 +1942 217 18.99 12.99 17.34 0 482.86 363.6 52122 +1942 218 20.3 14.3 18.65 0.18 519.67 268.94 51958 +1942 219 18.98 12.98 17.33 0.65 482.59 271.32 51791 +1942 220 18.95 12.95 17.3 0.18 481.77 270.68 51622 +1942 221 22.33 16.33 20.68 0 581.42 348.5 51451 +1942 222 23.4 17.4 21.75 0 616.4 343.4 51279 +1942 223 22.1 16.1 20.45 0 574.13 347.19 51105 +1942 224 26.91 20.91 25.26 0 743.94 326.16 50929 +1942 225 29.61 23.61 27.96 0 856.61 311.39 50751 +1942 226 29.83 23.83 28.18 0 866.39 309.15 50572 +1942 227 29.92 23.92 28.27 0 870.42 307.49 50392 +1942 228 28.97 22.97 27.32 0 828.68 311.47 50210 +1942 229 28.67 22.67 27.02 0.06 815.85 233.92 50026 +1942 230 27.74 21.74 26.09 0.09 777.15 236.52 49842 +1942 231 26.82 20.82 25.17 0.55 740.41 238.75 49656 +1942 232 22.09 16.09 20.44 0 573.81 336.25 49469 +1942 233 22.15 16.15 20.5 0 575.7 334.64 49280 +1942 234 19.66 13.66 18.01 0 501.4 341.47 49091 +1942 235 22.26 16.26 20.61 0 579.19 331.4 48900 +1942 236 21.94 15.94 20.29 0.1 569.1 248.35 48709 +1942 237 18.25 12.25 16.6 0 463.06 341.04 48516 +1942 238 17.09 11.09 15.44 0.02 433.42 256.87 48323 +1942 239 18.43 12.43 16.78 0.16 467.81 253 48128 +1942 240 21.5 15.5 19.85 0.69 555.46 244.63 47933 +1942 241 23.21 17.21 21.56 0.26 610.06 238.88 47737 +1942 242 24.34 18.34 22.69 0 648.58 312.58 47541 +1942 243 23.89 17.89 22.24 0 633 312.51 47343 +1942 244 23.42 17.42 21.77 0 617.07 312.5 47145 +1942 245 21.96 15.96 20.31 0 569.72 315.83 46947 +1942 246 18.69 12.69 17.04 0 474.75 323.89 46747 +1942 247 21.26 15.26 19.61 0 548.14 314.4 46547 +1942 248 20.98 14.98 19.33 0 539.7 313.39 46347 +1942 249 19.93 13.93 18.28 0 509.04 314.54 46146 +1942 250 17.21 11.21 15.56 0.12 436.41 239.99 45945 +1942 251 19.47 13.47 17.82 0 496.08 311.86 45743 +1942 252 22.29 16.29 20.64 0.01 580.15 225.82 45541 +1942 253 20.89 14.89 19.24 0 537.02 303.48 45339 +1942 254 18.21 12.21 16.56 0 462.01 308.92 45136 +1942 255 20.88 14.88 19.23 0 536.72 299.23 44933 +1942 256 26.64 20.64 24.99 0 733.39 276.71 44730 +1942 257 25.73 19.73 24.08 0 698.78 278.35 44527 +1942 258 23.88 17.88 22.23 0.42 632.66 212.22 44323 +1942 259 28.86 22.86 27.21 0.1 823.96 195.58 44119 +1942 260 28.35 22.35 26.7 0.42 802.36 195.68 43915 +1942 261 25.57 19.57 23.92 0 692.84 269.99 43711 +1942 262 24.51 18.51 22.86 0.04 654.55 203.73 43507 +1942 263 23.91 17.91 22.26 0.21 633.69 203.55 43303 +1942 264 18.98 12.98 17.33 0.1 482.59 212.63 43099 +1942 265 19.17 13.17 17.52 0 487.78 280.7 42894 +1942 266 22.45 16.45 20.8 0.13 585.26 201.8 42690 +1942 267 23.46 17.46 21.81 0 618.41 263.33 42486 +1942 268 21.86 15.86 20.21 0 566.6 265.82 42282 +1942 269 22.73 16.73 21.08 0.01 594.29 195.61 42078 +1942 270 23.95 17.95 22.3 0 635.06 254.48 41875 +1942 271 22.61 16.61 20.96 0 590.41 256.18 41671 +1942 272 20.61 14.61 18.96 0.16 528.72 194.41 41468 +1942 273 25.46 19.46 23.81 0 688.78 242.08 41265 +1942 274 21.04 15.04 19.39 0.08 541.5 189.8 41062 +1942 275 18.29 12.29 16.64 0 464.12 257.19 40860 +1942 276 17.75 11.75 16.1 0.74 450.08 191.82 40658 +1942 277 15.44 9.44 13.79 0 394.06 257.84 40456 +1942 278 14.46 8.46 12.81 0 372.15 256.79 40255 +1942 279 17.07 11.07 15.42 0 432.93 249.01 40054 +1942 280 15.99 9.99 14.34 0 406.83 248.55 39854 +1942 281 14.06 8.06 12.41 0 363.52 249.33 39654 +1942 282 15.11 9.11 13.46 0.11 386.56 183.58 39455 +1942 283 17.02 11.02 15.37 0 431.69 238.4 39256 +1942 284 15.96 9.96 14.31 0.25 406.12 178.1 39058 +1942 285 18.29 12.29 16.64 0 464.12 230.28 38861 +1942 286 18.17 12.17 16.52 0.54 460.97 170.89 38664 +1942 287 15.87 9.87 14.22 0 404.01 229.42 38468 +1942 288 16.98 10.98 15.33 0 430.7 224.64 38273 +1942 289 14.27 8.27 12.62 0 368.03 226.79 38079 +1942 290 11.63 5.63 9.98 0 314.64 227.83 37885 +1942 291 11.99 5.99 10.34 0 321.51 224.64 37693 +1942 292 15.4 9.4 13.75 0 393.14 216.8 37501 +1942 293 15.5 9.5 13.85 0.01 395.43 160.46 37311 +1942 294 16.32 10.32 14.67 0.12 414.65 157.3 37121 +1942 295 19.69 13.69 18.04 0.16 502.24 150.43 36933 +1942 296 17.42 11.42 15.77 0 441.69 202.51 36745 +1942 297 16.09 10.09 14.44 0 409.18 202.17 36560 +1942 298 10.73 4.73 9.08 0.49 298.03 155.39 36375 +1942 299 12.15 6.15 10.5 0.45 324.6 151.98 36191 +1942 300 13.17 7.17 11.52 0 344.91 198.65 36009 +1942 301 15.63 9.63 13.98 0 398.43 192.59 35829 +1942 302 12.61 6.61 10.96 0 333.63 194.32 35650 +1942 303 11.42 5.42 9.77 0 310.69 193.23 35472 +1942 304 13.06 7.06 11.41 0 342.67 188.75 35296 +1942 305 5.99 -0.01 4.34 0.12 222.37 145.08 35122 +1942 306 8.63 2.63 6.98 0 262.15 188.79 34950 +1942 307 7.8 1.8 6.15 0 249.03 187.05 34779 +1942 308 8.02 2.02 6.37 0 252.46 184.24 34610 +1942 309 11.32 5.32 9.67 0 308.83 178.58 34444 +1942 310 5.71 -0.29 4.06 0.91 218.47 136.05 34279 +1942 311 4.35 -1.65 2.7 0 200.36 180.2 34116 +1942 312 5.18 -0.82 3.53 0 211.25 176.94 33956 +1942 313 3.53 -2.47 1.88 0 190.08 175.94 33797 +1942 314 0.32 -5.68 -1.33 0 154.09 175.84 33641 +1942 315 1.42 -4.58 -0.23 0 165.69 172.67 33488 +1942 316 1.32 -4.68 -0.33 0.07 164.61 127.87 33337 +1942 317 5.7 -0.3 4.05 0 218.33 165.48 33188 +1942 318 3.43 -2.57 1.78 0 188.86 164.66 33042 +1942 319 6.06 0.06 4.41 0 223.35 161.16 32899 +1942 320 8.09 2.09 6.44 0 253.55 157.71 32758 +1942 321 7.07 1.07 5.42 0 237.97 156.42 32620 +1942 322 9.21 3.21 7.56 0.07 271.67 114.64 32486 +1942 323 9.35 3.35 7.7 0 274.01 151.12 32354 +1942 324 13.55 7.55 11.9 0 352.75 144.92 32225 +1942 325 11.1 5.1 9.45 0 304.76 145.79 32100 +1942 326 10.9 4.9 9.25 0 301.11 144.55 31977 +1942 327 8.19 2.19 6.54 0 255.13 145.07 31858 +1942 328 9.97 3.97 8.32 0 284.59 141.63 31743 +1942 329 9.45 3.45 7.8 0 275.69 140.6 31631 +1942 330 9.63 3.63 7.98 0 278.74 139.03 31522 +1942 331 5.8 -0.2 4.15 0 219.72 140.59 31417 +1942 332 5.35 -0.65 3.7 0 213.54 139.24 31316 +1942 333 2.57 -3.43 0.92 0.08 178.63 104.83 31218 +1942 334 4.21 -1.79 2.56 0.3 198.57 103.31 31125 +1942 335 -0.01 -6.01 -1.66 0 150.74 138.71 31035 +1942 336 3.66 -2.34 2.01 0 191.68 135.81 30949 +1942 337 4.36 -1.64 2.71 0 200.49 133.74 30867 +1942 338 3.75 -2.25 2.1 0 192.79 133.15 30790 +1942 339 7.57 1.57 5.92 0.01 245.5 97.47 30716 +1942 340 7.56 1.56 5.91 0.07 245.35 96.93 30647 +1942 341 7.2 1.2 5.55 0 239.91 128.58 30582 +1942 342 6.53 0.53 4.88 0.36 230.05 96.2 30521 +1942 343 7.45 1.45 5.8 0 243.67 126.84 30465 +1942 344 7.13 1.13 5.48 0 238.86 125.93 30413 +1942 345 8.13 2.13 6.48 0 254.18 124.81 30366 +1942 346 10 4 8.35 0.06 285.11 92.14 30323 +1942 347 8.02 2.02 6.37 0.05 252.46 92.82 30284 +1942 348 8.1 2.1 6.45 0.01 253.71 92.52 30251 +1942 349 11.05 5.05 9.4 0.03 303.84 90.52 30221 +1942 350 10.39 4.39 8.74 0 291.95 120.91 30197 +1942 351 7.58 1.58 5.93 0 245.65 122.8 30177 +1942 352 9.94 3.94 8.29 0.74 284.07 90.73 30162 +1942 353 5.41 -0.59 3.76 0 214.36 124.02 30151 +1942 354 3.92 -2.08 2.27 0 194.91 124.83 30145 +1942 355 3.3 -2.7 1.65 0 187.28 125.16 30144 +1942 356 2.61 -3.39 0.96 0.05 179.09 94.15 30147 +1942 357 -3.52 -9.52 -5.17 0.63 118.89 141.83 30156 +1942 358 0.34 -5.66 -1.31 0 154.29 172.44 30169 +1942 359 2.75 -3.25 1.1 0 180.73 171.05 30186 +1942 360 3.39 -2.61 1.74 0.28 188.37 139.16 30208 +1942 361 1.46 -4.54 -0.19 0 166.13 171.65 30235 +1942 362 2.09 -3.91 0.44 0.23 173.13 139.67 30267 +1942 363 1.99 -4.01 0.34 0 172 171.79 30303 +1942 364 0.57 -5.43 -1.08 0 156.66 172.7 30343 +1942 365 -0.19 -6.19 -1.84 0 148.95 173.53 30388 +1943 1 -3.1 -9.1 -4.75 0.12 122.37 142.89 30438 +1943 2 -3.65 -9.65 -5.3 0.83 117.84 146.13 30492 +1943 3 -5.54 -11.54 -7.19 0.21 103.35 147.85 30551 +1943 4 -7.06 -13.06 -8.71 0 92.85 182.66 30614 +1943 5 -8.45 -14.45 -10.1 0 84.07 183.57 30681 +1943 6 -2.97 -8.97 -4.62 0 123.46 182.78 30752 +1943 7 -2.22 -8.22 -3.87 0 129.93 183.2 30828 +1943 8 -2.6 -8.6 -4.25 0.19 126.62 150.79 30907 +1943 9 -1.95 -7.95 -3.6 0.06 132.33 151.62 30991 +1943 10 -3.68 -9.68 -5.33 0 117.59 188.21 31079 +1943 11 -2.86 -8.86 -4.51 0 124.39 188.78 31171 +1943 12 -1.72 -7.72 -3.37 0.02 134.41 153.7 31266 +1943 13 3.37 -2.63 1.72 0.01 188.13 152.53 31366 +1943 14 6.39 0.39 4.74 0.08 228.04 151.25 31469 +1943 15 7.45 1.45 5.8 0 243.67 186.11 31575 +1943 16 3.37 -2.63 1.72 0.02 188.13 153.03 31686 +1943 17 1.68 -4.32 0.03 0 168.54 191.72 31800 +1943 18 2.21 -3.79 0.56 0.37 174.49 155.4 31917 +1943 19 -3.31 -9.31 -4.96 0 120.62 197.19 32038 +1943 20 -2.96 -8.96 -4.61 0.07 123.55 159.72 32161 +1943 21 -1.04 -7.04 -2.69 0 140.71 199.78 32289 +1943 22 -0.9 -6.9 -2.55 0 142.04 201.31 32419 +1943 23 -1.6 -7.6 -3.25 0 135.5 203.24 32552 +1943 24 0 -6 -1.65 0 150.84 204.42 32688 +1943 25 2.35 -3.65 0.7 0 176.09 204.6 32827 +1943 26 5.46 -0.54 3.81 0.12 215.04 162.95 32969 +1943 27 -1.31 -7.31 -2.96 1.19 138.18 170.68 33114 +1943 28 -0.27 -6.27 -1.92 0 148.15 214.44 33261 +1943 29 -1.24 -7.24 -2.89 0 138.83 217.11 33411 +1943 30 -3.08 -9.08 -4.73 0 122.54 220 33564 +1943 31 -1.18 -7.18 -2.83 0 139.39 221.36 33718 +1943 32 5.62 -0.38 3.97 0 217.23 218.47 33875 +1943 33 8.39 2.39 6.74 0 258.3 217.58 34035 +1943 34 6.47 0.47 4.82 0 229.19 220.46 34196 +1943 35 8.77 2.77 7.12 0.28 264.42 174.25 34360 +1943 36 6.41 0.41 4.76 0.55 228.32 138.69 34526 +1943 37 6.96 0.96 5.31 0 236.34 186.87 34694 +1943 38 9.59 3.59 7.94 0.13 278.06 140.32 34863 +1943 39 11.41 5.41 9.76 0 310.51 187.65 35035 +1943 40 4.02 -1.98 2.37 0 196.17 197.16 35208 +1943 41 7.34 1.34 5.69 0.38 242.01 147.78 35383 +1943 42 8.39 2.39 6.74 0 258.3 198.56 35560 +1943 43 7.76 1.76 6.11 0.2 248.42 151.39 35738 +1943 44 8.41 2.41 6.76 0 258.62 203.75 35918 +1943 45 7.77 1.77 6.12 0 248.57 206.99 36099 +1943 46 6.07 0.07 4.42 0 223.49 211.25 36282 +1943 47 1.31 -4.69 -0.34 0 164.5 217.73 36466 +1943 48 -0.06 -6.06 -1.71 0 150.24 221.42 36652 +1943 49 5.28 -0.72 3.63 0.01 212.6 165.25 36838 +1943 50 3.19 -2.81 1.54 0 185.95 224.71 37026 +1943 51 5.3 -0.7 3.65 0 212.87 225.95 37215 +1943 52 6.36 0.36 4.71 1.1 227.61 170.85 37405 +1943 53 3.83 -2.17 2.18 0.29 193.79 174.75 37596 +1943 54 4.63 -1.37 2.98 0 203.98 235.09 37788 +1943 55 8.02 2.02 6.37 0.08 252.46 176.08 37981 +1943 56 7.78 1.78 6.13 0 248.73 237.7 38175 +1943 57 7.45 1.45 5.8 0 243.67 240.93 38370 +1943 58 8.32 2.32 6.67 0.41 257.19 182.16 38565 +1943 59 5.17 -0.83 3.52 0 211.12 248.85 38761 +1943 60 5.39 -0.61 3.74 0 214.09 251.54 38958 +1943 61 9.99 3.99 8.34 0 284.93 249.29 39156 +1943 62 5.98 -0.02 4.33 0 222.23 256.69 39355 +1943 63 9.01 3.01 7.36 0 268.36 256.28 39553 +1943 64 9.29 3.29 7.64 0 273.01 258.81 39753 +1943 65 10.55 4.55 8.9 0 294.79 259.99 39953 +1943 66 7.42 1.42 5.77 0 243.22 266.67 40154 +1943 67 7.92 1.92 6.27 0 250.9 268.98 40355 +1943 68 5.53 -0.47 3.88 0.02 215.99 205.89 40556 +1943 69 7 1 5.35 0.07 236.93 206.66 40758 +1943 70 6.72 0.72 5.07 0 232.81 278.72 40960 +1943 71 10.17 4.17 8.52 0 288.07 277.23 41163 +1943 72 10.92 4.92 9.27 0.04 301.47 209.2 41366 +1943 73 11.78 5.78 10.13 0 317.49 280.23 41569 +1943 74 10.46 4.46 8.81 0 293.19 284.97 41772 +1943 75 5.34 -0.66 3.69 0 213.41 294.2 41976 +1943 76 8.57 2.57 6.92 0.03 261.19 219.72 42179 +1943 77 9.55 3.55 7.9 0 277.38 294.2 42383 +1943 78 9.53 3.53 7.88 0 277.05 296.88 42587 +1943 79 8.34 2.34 6.69 0 257.5 301.26 42791 +1943 80 8.59 2.59 6.94 0 261.51 303.45 42996 +1943 81 8.77 2.77 7.12 0.01 264.42 229.34 43200 +1943 82 7.02 1.02 5.37 0 237.22 310.76 43404 +1943 83 8.44 2.44 6.79 0 259.1 311.39 43608 +1943 84 11.69 5.69 10.04 0 315.78 308.91 43812 +1943 85 8.68 2.68 7.03 0.01 262.96 237.07 44016 +1943 86 12.66 6.66 11.01 0.07 334.62 234.04 44220 +1943 87 10.02 4.02 8.37 0 285.45 319.04 44424 +1943 88 11.42 5.42 9.77 0 310.69 319.08 44627 +1943 89 11.24 5.24 9.59 0 307.35 321.65 44831 +1943 90 11.51 5.51 9.86 0 312.38 323.54 45034 +1943 91 15.16 9.16 13.51 0 387.69 318.62 45237 +1943 92 15.69 9.69 14.04 0 399.82 319.63 45439 +1943 93 16.47 10.47 14.82 0 418.26 319.97 45642 +1943 94 19.88 13.88 18.23 0 507.62 313.02 45843 +1943 95 20.34 14.34 18.69 0 520.83 313.69 46045 +1943 96 16.8 10.8 15.15 0.1 426.27 244.05 46246 +1943 97 17.89 11.89 16.24 0.03 453.69 243.45 46446 +1943 98 18.04 12.04 16.39 0 457.57 326.1 46647 +1943 99 16.91 10.91 15.26 0 428.97 330.98 46846 +1943 100 16.85 10.85 15.2 0 427.5 333.03 47045 +1943 101 18.46 12.46 16.81 0.02 468.61 247.98 47243 +1943 102 20.54 14.54 18.89 0 526.67 326.31 47441 +1943 103 16.88 10.88 15.23 0 428.23 338.49 47638 +1943 104 19.15 13.15 17.5 0 487.23 334.04 47834 +1943 105 22.74 16.74 21.09 0 594.62 324.07 48030 +1943 106 17.04 11.04 15.39 0 432.18 343.21 48225 +1943 107 15.68 9.68 14.03 0.22 399.59 261.2 48419 +1943 108 16.76 10.76 15.11 0.93 425.29 260.46 48612 +1943 109 12.81 6.81 11.16 1.12 337.62 268.5 48804 +1943 110 12.63 6.63 10.98 0.24 334.03 269.83 48995 +1943 111 5.37 -0.63 3.72 0 213.82 373.27 49185 +1943 112 5.4 -0.6 3.75 0 214.22 374.79 49374 +1943 113 5.01 -0.99 3.36 0 208.98 376.67 49561 +1943 114 5.77 -0.23 4.12 0 219.3 377.21 49748 +1943 115 7.38 1.38 5.73 0 242.61 376.39 49933 +1943 116 12.04 6.04 10.39 0 322.47 369.55 50117 +1943 117 12.74 6.74 11.09 0 336.22 369.43 50300 +1943 118 11.73 5.73 10.08 0 316.53 372.81 50481 +1943 119 11.65 5.65 10 0.03 315.02 280.63 50661 +1943 120 12.65 6.65 11 0.01 334.42 279.99 50840 +1943 121 11.77 5.77 10.12 0 317.3 376.26 51016 +1943 122 10.32 4.32 8.67 0.01 290.71 285.18 51191 +1943 123 9.03 3.03 7.38 1.7 268.69 287.66 51365 +1943 124 12.08 6.08 10.43 0 323.24 378.97 51536 +1943 125 12.04 6.04 10.39 0 322.47 380.05 51706 +1943 126 15.9 9.9 14.25 0 404.71 372.16 51874 +1943 127 14.83 8.83 13.18 0 380.3 375.73 52039 +1943 128 18.75 12.75 17.1 0 476.36 366.01 52203 +1943 129 18.12 12.12 16.47 0.51 459.66 276.56 52365 +1943 130 18.14 12.14 16.49 0.65 460.18 277.1 52524 +1943 131 21.98 15.98 20.33 0 570.35 357.5 52681 +1943 132 21.94 15.94 20.29 0.15 569.1 268.83 52836 +1943 133 21.33 15.33 19.68 0.3 550.27 271 52989 +1943 134 20.64 14.64 18.99 0 529.61 364.44 53138 +1943 135 16.41 10.41 14.76 0 416.81 378.06 53286 +1943 136 16.09 10.09 14.44 0.88 409.18 284.66 53430 +1943 137 17.18 11.18 15.53 0.21 435.66 282.95 53572 +1943 138 16.74 10.74 15.09 0.1 424.8 284.33 53711 +1943 139 15.65 9.65 14 0 398.89 382.71 53848 +1943 140 16.7 10.7 15.05 0.04 423.83 285.29 53981 +1943 141 17.69 11.69 16.04 0 448.55 378 54111 +1943 142 17.79 11.79 16.14 0.16 451.11 283.66 54238 +1943 143 14.76 8.76 13.11 0.2 378.75 290.2 54362 +1943 144 13.6 7.6 11.95 0.35 353.8 292.64 54483 +1943 145 12.47 6.47 10.82 0.97 330.86 294.89 54600 +1943 146 17.55 11.55 15.9 0.66 444.98 285.57 54714 +1943 147 16.2 10.2 14.55 0 411.79 385.03 54824 +1943 148 22.92 16.92 21.27 0 600.49 363.25 54931 +1943 149 16.67 10.67 15.02 0.06 423.1 288.34 55034 +1943 150 16.36 10.36 14.71 0.4 415.61 289.23 55134 +1943 151 18.8 12.8 17.15 0 477.71 378.87 55229 +1943 152 23.55 17.55 21.9 0.53 621.44 271.36 55321 +1943 153 24.24 18.24 22.59 0.15 645.09 269.36 55409 +1943 154 20.49 14.49 18.84 0 525.2 373.95 55492 +1943 155 23.57 17.57 21.92 0.08 622.12 271.84 55572 +1943 156 25.89 19.89 24.24 0.44 704.76 264.41 55648 +1943 157 22.2 16.2 20.55 0.92 577.29 276.28 55719 +1943 158 24.59 18.59 22.94 0 657.38 358.76 55786 +1943 159 20.11 14.11 18.46 0.97 514.19 282.25 55849 +1943 160 14.79 8.79 13.14 0.86 379.41 294.09 55908 +1943 161 17.66 11.66 16.01 0.1 447.78 288.28 55962 +1943 162 20.91 14.91 19.26 0.83 537.61 280.39 56011 +1943 163 17.77 11.77 16.12 1.08 450.6 288.24 56056 +1943 164 11.18 5.18 9.53 0.77 306.24 300.47 56097 +1943 165 18.11 12.11 16.46 0.06 459.4 287.58 56133 +1943 166 18.23 12.23 16.58 0 462.54 383.15 56165 +1943 167 19.43 13.43 17.78 0 494.97 379.3 56192 +1943 168 20.31 14.31 18.66 0.43 519.96 282.31 56214 +1943 169 17.84 11.84 16.19 0.16 452.4 288.28 56231 +1943 170 16.24 10.24 14.59 0.33 412.74 291.71 56244 +1943 171 19.19 13.19 17.54 0 488.33 380.23 56252 +1943 172 19.49 13.49 17.84 0 496.64 379.24 56256 +1943 173 17.88 11.88 16.23 0.01 453.43 288.21 56255 +1943 174 19.21 13.21 17.56 0.36 488.88 285.04 56249 +1943 175 16.07 10.07 14.42 2.16 408.71 291.99 56238 +1943 176 17.59 11.59 15.94 2.23 446 288.75 56223 +1943 177 18.51 12.51 16.86 0.66 469.94 286.58 56203 +1943 178 19.28 13.28 17.63 0.18 490.81 284.76 56179 +1943 179 19.94 13.94 18.29 0.11 509.33 283.04 56150 +1943 180 19.67 13.67 18.02 0.41 501.68 283.63 56116 +1943 181 18.69 12.69 17.04 0.08 474.75 285.95 56078 +1943 182 19.11 13.11 17.46 0.42 486.14 284.84 56035 +1943 183 20.92 14.92 19.27 0.32 537.91 280.11 55987 +1943 184 23.41 17.41 21.76 0.01 616.73 272.86 55935 +1943 185 24.01 18.01 22.36 0.41 637.13 270.92 55879 +1943 186 24.37 18.37 22.72 0.07 649.63 269.58 55818 +1943 187 20.8 14.8 19.15 0.28 534.34 279.92 55753 +1943 188 20.73 14.73 19.08 1.39 532.26 279.91 55684 +1943 189 20.53 14.53 18.88 0.21 526.38 280.3 55611 +1943 190 18.77 12.77 17.12 0 476.9 379.18 55533 +1943 191 20.21 14.21 18.56 0 517.07 374.19 55451 +1943 192 23.73 17.73 22.08 0 627.54 360.62 55366 +1943 193 22.55 16.55 20.9 1.61 588.47 273.82 55276 +1943 194 23.15 17.15 21.5 0.09 608.07 271.88 55182 +1943 195 23.41 17.41 21.76 0.01 616.73 270.89 55085 +1943 196 21.4 15.4 19.75 0 552.4 368.53 54984 +1943 197 22.04 16.04 20.39 0 572.24 365.71 54879 +1943 198 25.15 19.15 23.5 0.21 677.45 264.38 54770 +1943 199 20.01 14.01 18.36 0.21 511.32 279.11 54658 +1943 200 17.88 11.88 16.23 0.18 453.43 283.85 54542 +1943 201 17.12 11.12 15.47 0 434.17 380.19 54423 +1943 202 19.77 13.77 18.12 0.65 504.5 278.63 54301 +1943 203 21.71 15.71 20.06 1.02 561.93 273.19 54176 +1943 204 25.23 19.23 23.58 0 680.36 349.46 54047 +1943 205 25.12 19.12 23.47 0 676.36 349.45 53915 +1943 206 26.84 20.84 25.19 0.19 741.19 255.7 53780 +1943 207 25.9 19.9 24.25 0 705.14 344.75 53643 +1943 208 27.09 21.09 25.44 0.05 751.04 253.85 53502 +1943 209 25.27 19.27 23.62 0 681.82 346.36 53359 +1943 210 27.25 21.25 25.6 0 757.39 336.48 53213 +1943 211 26.17 20.17 24.52 0 715.34 340.92 53064 +1943 212 21.96 15.96 20.31 1.49 569.72 268.23 52913 +1943 213 26.1 20.1 24.45 0 712.68 339.77 52760 +1943 214 27.21 21.21 25.56 0 755.8 333.78 52604 +1943 215 26.44 20.44 24.79 0 725.66 336.84 52445 +1943 216 27.06 21.06 25.41 0 749.85 332.91 52285 +1943 217 27.95 21.95 26.3 0 785.75 327.67 52122 +1943 218 27.5 21.5 25.85 0.08 767.42 246.87 51958 +1943 219 25.77 19.77 24.12 0 700.27 336.32 51791 +1943 220 27.86 21.86 26.21 0.6 782.06 244.13 51622 +1943 221 23.82 17.82 22.17 0 630.61 342.75 51451 +1943 222 23.92 17.92 22.27 0 634.03 341.33 51279 +1943 223 23.65 17.65 22 0 624.82 341.3 51105 +1943 224 21.74 15.74 20.09 1.89 562.86 260.58 50929 +1943 225 25.74 19.74 24.09 0 699.15 330.42 50751 +1943 226 31.11 25.11 29.46 0.16 925.2 226.41 50572 +1943 227 28.63 22.63 26.98 0.07 814.16 235.76 50392 +1943 228 21.34 15.34 19.69 0 550.57 344.12 50210 +1943 229 19.31 13.31 17.66 0.39 491.64 262.11 50026 +1943 230 17.92 11.92 16.27 0 454.46 352.27 49842 +1943 231 19.5 13.5 17.85 0.03 496.92 259.61 49656 +1943 232 22 16 20.35 0.02 570.98 252.42 49469 +1943 233 20.75 14.75 19.1 0.18 532.86 254.56 49280 +1943 234 24 18 22.35 0.11 636.78 244.77 49091 +1943 235 22.97 16.97 21.32 0 602.13 328.83 48900 +1943 236 24.3 18.3 22.65 0 647.19 322.37 48709 +1943 237 24.28 18.28 22.63 0.04 646.49 240.65 48516 +1943 238 25.22 19.22 23.57 0 679.99 315.47 48323 +1943 239 25.81 19.81 24.16 0.56 701.77 233.68 48128 +1943 240 25.59 19.59 23.94 0.01 693.58 233.13 47933 +1943 241 25.65 19.65 24 0.24 695.8 231.72 47737 +1943 242 25.93 19.93 24.28 0.12 706.27 229.6 47541 +1943 243 24.89 18.89 23.24 0 668.07 308.64 47343 +1943 244 16.17 10.17 14.52 1.08 411.08 250.69 47145 +1943 245 18.71 12.71 17.06 0 475.29 325.8 46947 +1943 246 19.68 13.68 18.03 0.01 501.96 240.8 46747 +1943 247 17.07 11.07 15.42 0 432.93 326.32 46547 +1943 248 16.93 10.93 15.28 0.22 429.47 243.53 46347 +1943 249 22.59 16.59 20.94 0.23 589.76 229.58 46146 +1943 250 24.61 18.61 22.96 0.06 658.09 222.72 45945 +1943 251 23.54 17.54 21.89 0 621.1 298.89 45743 +1943 252 20.19 14.19 18.54 0 516.49 307.65 45541 +1943 253 20.51 14.51 18.86 0 525.79 304.63 45339 +1943 254 18.49 12.49 16.84 0 469.41 308.18 45136 +1943 255 18.75 12.75 17.1 0 476.36 305.26 44933 +1943 256 19.63 13.63 17.98 0.43 500.56 225.47 44730 +1943 257 19.15 13.15 17.5 0.58 487.23 224.86 44527 +1943 258 21.29 15.29 19.64 0.02 549.05 218.55 44323 +1943 259 19.11 13.11 17.46 0.32 486.14 221.41 44119 +1943 260 17.4 11.4 15.75 1.59 441.18 222.87 43915 +1943 261 19.77 13.77 18.12 0.24 504.5 216.52 43711 +1943 262 20.82 14.82 19.17 0 534.93 283.43 43507 +1943 263 24.03 18.03 22.38 0 637.82 270.98 43303 +1943 264 22.14 16.14 20.49 0.03 575.39 205.99 43099 +1943 265 25.2 19.2 23.55 0 679.27 262.24 42894 +1943 266 20.48 14.48 18.83 0 524.91 274.8 42690 +1943 267 13.15 7.15 11.5 0 344.5 288.52 42486 +1943 268 15.71 9.71 14.06 0.22 400.28 210.78 42282 +1943 269 18.69 12.69 17.04 0 474.75 271.87 42078 +1943 270 24.81 18.81 23.16 0.05 665.2 188.71 41875 +1943 271 23.64 17.64 21.99 0 624.48 253.01 41671 +1943 272 23.14 17.14 21.49 0 607.74 251.99 41468 +1943 273 25.3 19.3 23.65 0.24 682.91 181.97 41265 +1943 274 20.96 14.96 19.31 0 539.11 253.28 41062 +1943 275 18.52 12.52 16.87 0 470.21 256.66 40860 +1943 276 18.72 12.72 17.07 0 475.56 253.57 40658 +1943 277 18.81 12.81 17.16 0 477.98 250.77 40456 +1943 278 16.51 10.51 14.86 0.01 419.22 189.69 40255 +1943 279 18.14 12.14 16.49 0 460.18 246.75 40054 +1943 280 15.53 9.53 13.88 0.52 396.12 187.06 39854 +1943 281 17.98 11.98 16.33 0.15 456.02 181.39 39654 +1943 282 18.01 12.01 16.36 0 456.79 239.13 39455 +1943 283 20.48 14.48 18.83 0 524.91 230.8 39256 +1943 284 21.78 15.78 20.13 0 564.11 224.66 39058 +1943 285 16.53 10.53 14.88 0 419.7 233.8 38861 +1943 286 14.3 8.3 12.65 0 368.68 235.02 38664 +1943 287 14.86 8.86 13.21 0 380.96 231.18 38468 +1943 288 16.32 10.32 14.67 0 414.65 225.87 38273 +1943 289 17.36 11.36 15.71 0 440.17 221.35 38079 +1943 290 14.97 8.97 13.32 0 383.42 222.82 37885 +1943 291 15.09 9.09 13.44 0 386.11 219.96 37693 +1943 292 16.12 10.12 14.47 0 409.89 215.57 37501 +1943 293 15.73 9.73 14.08 0 400.75 213.57 37311 +1943 294 13.78 7.78 12.13 0.14 357.57 160.36 37121 +1943 295 12.62 6.62 10.97 0.12 333.83 159.49 36933 +1943 296 11.97 5.97 10.32 0.03 321.12 158.22 36745 +1943 297 10.89 4.89 9.24 0 300.92 209.6 36560 +1943 298 12.89 6.89 11.24 0 339.23 204.43 36375 +1943 299 14.55 8.55 12.9 0 374.12 199.31 36191 +1943 300 11.7 5.7 10.05 0 315.97 200.56 36009 +1943 301 9.54 3.54 7.89 0 277.21 200.55 35829 +1943 302 8.35 2.35 6.7 0.04 257.66 149.36 35650 +1943 303 13.31 7.31 11.66 0 347.78 190.85 35472 +1943 304 14.62 8.62 12.97 0 375.66 186.63 35296 +1943 305 10.11 4.11 8.46 0 287.02 189.53 35122 +1943 306 7.47 1.47 5.82 0 243.98 189.88 34950 +1943 307 8.3 2.3 6.65 0.02 256.87 139.94 34779 +1943 308 8.66 2.66 7.01 0 262.64 183.64 34610 +1943 309 9.27 3.27 7.62 0 272.67 180.73 34444 +1943 310 9.05 3.05 7.4 0.01 269.02 133.88 34279 +1943 311 6.28 0.28 4.63 0 226.47 178.75 34116 +1943 312 6.63 0.63 4.98 0.36 231.5 131.86 33956 +1943 313 5.48 -0.52 3.83 1.65 215.31 130.93 33797 +1943 314 4.92 -1.08 3.27 0.92 207.79 129.76 33641 +1943 315 4.35 -1.65 2.7 0.16 200.36 128.14 33488 +1943 316 3.24 -2.76 1.59 0 186.56 169.37 33337 +1943 317 4.59 -1.41 2.94 0.65 203.46 124.7 33188 +1943 318 4.32 -1.68 2.67 0 199.98 164.09 33042 +1943 319 5.16 -0.84 3.51 0 210.98 161.81 32899 +1943 320 9.23 3.23 7.58 0 272 156.73 32758 +1943 321 6.59 0.59 4.94 0 230.92 156.79 32620 +1943 322 5.8 -0.2 4.15 0 219.72 155.54 32486 +1943 323 6.79 0.79 5.14 0.33 233.83 114.9 32354 +1943 324 6.99 0.99 5.34 0.74 236.78 113.25 32225 +1943 325 7.45 1.45 5.8 0 243.67 148.93 32100 +1943 326 5.51 -0.49 3.86 0.53 215.72 111.65 31977 +1943 327 9.21 3.21 7.56 1.88 271.67 108.18 31858 +1943 328 7.85 1.85 6.2 0.35 249.81 107.53 31743 +1943 329 9.47 3.47 7.82 0 276.03 140.59 31631 +1943 330 6.41 0.41 4.76 0 228.32 141.5 31522 +1943 331 8.01 2.01 6.36 0 252.3 139.02 31417 +1943 332 4.62 -1.38 2.97 0.69 203.85 104.77 31316 +1943 333 3.92 -2.08 2.27 0 194.91 139.02 31218 +1943 334 4.73 -1.27 3.08 0 205.29 137.44 31125 +1943 335 1.87 -4.13 0.22 0.01 170.65 103.37 31035 +1943 336 4.94 -1.06 3.29 0 208.05 135.06 30949 +1943 337 6.96 0.96 5.31 0 236.34 132.1 30867 +1943 338 6.41 0.41 4.76 0.58 228.32 98.65 30790 +1943 339 0.74 -5.26 -0.91 0.21 158.43 100.4 30716 +1943 340 0.52 -5.48 -1.13 0 156.14 133.22 30647 +1943 341 0.92 -5.08 -0.73 1.15 160.33 99.08 30582 +1943 342 -2.41 -8.41 -4.06 0.04 128.27 142.89 30521 +1943 343 -2.96 -8.96 -4.61 0.17 123.55 143.03 30465 +1943 344 -1.74 -7.74 -3.39 0 134.23 174.53 30413 +1943 345 0.67 -5.33 -0.98 0.03 157.7 140.83 30366 +1943 346 0.69 -5.31 -0.96 0 157.91 172.5 30323 +1943 347 3.02 -2.98 1.37 0.03 183.92 138.76 30284 +1943 348 2.72 -3.28 1.07 0 180.38 126.58 30251 +1943 349 1.35 -4.65 -0.3 0.54 164.93 95.14 30221 +1943 350 3.06 -2.94 1.41 1.01 184.4 94.27 30197 +1943 351 2.64 -3.36 0.99 0.06 179.44 94.26 30177 +1943 352 4.04 -1.96 2.39 0 196.42 124.86 30162 +1943 353 0.69 -5.31 -0.96 0 157.91 126.43 30151 +1943 354 4.24 -1.76 2.59 0 198.96 124.66 30145 +1943 355 8.34 2.34 6.69 0.03 257.5 91.56 30144 +1943 356 7.27 1.27 5.62 0.18 240.96 92.13 30147 +1943 357 9.64 3.64 7.99 0.2 278.91 90.89 30156 +1943 358 5.67 -0.33 4.02 0 217.92 124 30169 +1943 359 3.86 -2.14 2.21 0 194.16 125.15 30186 +1943 360 8.16 2.16 6.51 0 254.65 122.85 30208 +1943 361 8.33 2.33 6.68 0 257.34 123.05 30235 +1943 362 8.8 2.8 7.15 0.28 264.91 92.36 30267 +1943 363 8.3 2.3 6.65 0 256.87 124.09 30303 +1943 364 7.97 1.97 6.32 0.83 251.67 93.53 30343 +1943 365 5.07 -0.93 3.42 0 209.78 127.15 30388 +1944 1 2.24 -3.76 0.59 0 174.83 129.57 30438 +1944 2 4.69 -1.31 3.04 0 204.76 128.99 30492 +1944 3 8.46 2.46 6.81 0 259.42 127.45 30551 +1944 4 6.84 0.84 5.19 0 234.57 129.5 30614 +1944 5 10.28 4.28 8.63 0.15 290 95.66 30681 +1944 6 6.97 0.97 5.32 0.06 236.48 98.2 30752 +1944 7 3.4 -2.6 1.75 0.15 188.49 100.43 30828 +1944 8 6.06 0.06 4.41 0.52 223.35 100.35 30907 +1944 9 1.24 -4.76 -0.41 0 163.74 137.75 30991 +1944 10 7.77 1.77 6.12 0 248.57 135.15 31079 +1944 11 6.4 0.4 4.75 0 228.18 137.09 31171 +1944 12 6.72 0.72 5.07 0.08 232.81 103.4 31266 +1944 13 6.22 0.22 4.57 0.02 225.61 104.87 31366 +1944 14 4.14 -1.86 2.49 0.13 197.68 106.96 31469 +1944 15 5.3 -0.7 3.65 0 212.87 143.34 31575 +1944 16 3.77 -2.23 2.12 0 193.04 145.57 31686 +1944 17 2.74 -3.26 1.09 0 180.61 147.84 31800 +1944 18 3.1 -2.9 1.45 0 184.88 149.54 31917 +1944 19 5.28 -0.72 3.63 0 212.6 150.12 32038 +1944 20 11.61 5.61 9.96 0 314.26 146.48 32161 +1944 21 8.59 2.59 6.94 0 261.51 151.21 32289 +1944 22 11.34 5.34 9.69 0 309.2 150.41 32419 +1944 23 8.01 2.01 6.36 0.32 252.3 116.37 32552 +1944 24 4.24 -1.76 2.59 0 198.96 159.96 32688 +1944 25 1.95 -4.05 0.3 0 171.55 163.23 32827 +1944 26 0.23 -5.77 -1.42 0 153.17 166.09 32969 +1944 27 4.11 -1.89 2.46 0 197.3 165.88 33114 +1944 28 2.16 -3.84 0.51 0 173.92 169.3 33261 +1944 29 -2.1 -8.1 -3.75 0 131 173.87 33411 +1944 30 -1.22 -7.22 -2.87 0 139.02 175.74 33564 +1944 31 3.87 -2.13 2.22 0 194.29 175.24 33718 +1944 32 4.07 -1.93 2.42 0.05 196.8 132.92 33875 +1944 33 1.91 -4.09 0.26 0 171.1 181.24 34035 +1944 34 2.58 -3.42 0.93 0 178.74 183.05 34196 +1944 35 4.56 -1.44 2.91 0 203.07 183.85 34360 +1944 36 0.68 -5.32 -0.97 0.82 157.8 141.66 34526 +1944 37 3.35 -2.65 1.7 0.16 187.89 142.24 34694 +1944 38 -0.87 -6.87 -2.52 0.38 142.33 185.12 34863 +1944 39 -0.33 -6.33 -1.98 0.58 147.56 188.28 35035 +1944 40 -1.51 -7.51 -3.16 0 136.33 240.67 35208 +1944 41 -0.09 -6.09 -1.74 0 149.94 242.37 35383 +1944 42 -3.3 -9.3 -4.95 0 120.7 246.39 35560 +1944 43 2.19 -3.81 0.54 0 174.26 245.63 35738 +1944 44 6.53 0.53 4.88 0 230.05 243.88 35918 +1944 45 6.36 0.36 4.71 0 227.61 245.74 36099 +1944 46 4.12 -1.88 2.47 0 197.43 249.66 36282 +1944 47 4 -2 2.35 0 195.92 215.8 36466 +1944 48 2.17 -3.83 0.52 0 174.03 219.97 36652 +1944 49 3.59 -2.41 1.94 0.05 190.82 166.29 36838 +1944 50 0.98 -5.02 -0.67 0 160.96 226.28 37026 +1944 51 4.18 -1.82 2.53 0 198.19 226.9 37215 +1944 52 2.01 -3.99 0.36 0.78 172.22 173.56 37405 +1944 53 -0.81 -6.81 -2.46 0.06 142.9 212.46 37596 +1944 54 3.78 -2.22 2.13 0 193.17 235.81 37788 +1944 55 4.62 -1.38 2.97 0.05 203.85 178.58 37981 +1944 56 2 -4 0.35 0.26 172.11 182.2 38175 +1944 57 3.3 -2.7 1.65 0.52 187.28 183.62 38370 +1944 58 3.87 -2.13 2.22 0 194.29 247.3 38565 +1944 59 2.04 -3.96 0.39 0 172.56 251.51 38761 +1944 60 4.72 -1.28 3.07 0.01 205.16 189.12 38958 +1944 61 2.22 -3.78 0.57 0.09 174.6 192.94 39156 +1944 62 1.33 -4.67 -0.32 0.09 164.72 195.58 39355 +1944 63 1.02 -4.98 -0.63 0.4 161.39 198.03 39553 +1944 64 1.62 -4.38 -0.03 0.97 167.88 199.9 39753 +1944 65 2.25 -3.75 0.6 0.01 174.94 201.72 39953 +1944 66 5.12 -0.88 3.47 0 210.45 269.13 40154 +1944 67 6.34 0.34 4.69 0 227.32 270.78 40355 +1944 68 5.58 -0.42 3.93 0 216.68 274.47 40556 +1944 69 9.19 3.19 7.54 0.16 271.34 204.64 40758 +1944 70 8.91 2.91 7.26 0.03 266.71 207.04 40960 +1944 71 6.25 0.25 4.6 0.06 226.04 211.63 41163 +1944 72 9.09 3.09 7.44 0 269.68 281.52 41366 +1944 73 13.78 7.78 12.13 0 357.57 276.84 41569 +1944 74 13.37 7.37 11.72 0.1 349.02 210.19 41772 +1944 75 9.02 3.02 7.37 0 268.52 289.72 41976 +1944 76 6.44 0.44 4.79 0.02 228.76 221.71 42179 +1944 77 7.97 1.97 6.32 0.19 251.67 222.26 42383 +1944 78 6.71 0.71 5.06 0.65 232.66 225.45 42587 +1944 79 4.26 -1.74 2.61 0 199.21 306.07 42791 +1944 80 3.05 -2.95 1.4 0.22 184.28 232.39 42996 +1944 81 0.24 -5.76 -1.41 2.72 153.27 236.21 43200 +1944 82 0.2 -5.8 -1.45 0.34 152.86 238.27 43404 +1944 83 1.02 -4.98 -0.63 0.41 161.39 239.67 43608 +1944 84 1.38 -4.62 -0.27 0 165.26 321.84 43812 +1944 85 3.12 -2.88 1.47 0 185.11 322.75 44016 +1944 86 0.54 -5.46 -1.11 0 156.35 327.58 44220 +1944 87 1.35 -4.65 -0.3 0 164.93 329.46 44424 +1944 88 2.77 -3.23 1.12 0 180.96 330.53 44627 +1944 89 2.35 -3.65 0.7 0 176.09 333.26 44831 +1944 90 4.31 -1.69 2.66 0 199.85 333.65 45034 +1944 91 16.05 10.05 14.4 0 408.24 316.62 45237 +1944 92 15.31 9.31 13.66 0 391.09 320.48 45439 +1944 93 14 8 12.35 0.04 362.24 244.09 45642 +1944 94 12.12 6.12 10.47 0 324.02 331.25 45843 +1944 95 10.97 4.97 9.32 0 302.38 335.44 46045 +1944 96 13.25 7.25 11.6 0 346.55 333.3 46246 +1944 97 12.32 6.32 10.67 0 327.91 337.15 46446 +1944 98 17.13 11.13 15.48 0 434.42 328.47 46647 +1944 99 16.49 10.49 14.84 0 418.74 332.03 46846 +1944 100 19.63 13.63 17.98 0.04 500.56 244.07 47045 +1944 101 18.85 12.85 17.2 0.12 479.06 247.16 47243 +1944 102 17.06 11.06 15.41 0 432.68 336.23 47441 +1944 103 13.25 7.25 11.6 0 346.55 346.84 47638 +1944 104 15.74 9.74 14.09 0 400.98 343.1 47834 +1944 105 13.81 7.81 12.16 0 358.21 349.25 48030 +1944 106 11.79 5.79 10.14 0 317.68 354.99 48225 +1944 107 10.43 4.43 8.78 0.05 292.66 269.37 48419 +1944 108 13.31 7.31 11.66 0.16 347.78 266.51 48612 +1944 109 11.51 5.51 9.86 0.09 312.38 270.42 48804 +1944 110 10.1 4.1 8.45 0 286.85 364.55 48995 +1944 111 10.15 4.15 8.5 0.02 287.72 274.52 49185 +1944 112 5.65 -0.35 4 0.42 217.64 280.84 49374 +1944 113 8.96 2.96 7.31 0 267.53 370.95 49561 +1944 114 12.19 6.19 10.54 0.86 325.37 274.94 49748 +1944 115 10.82 4.82 9.17 0.47 299.65 278 49933 +1944 116 15.85 9.85 14.2 0.08 403.54 270.74 50117 +1944 117 14.5 8.5 12.85 0.15 373.03 274.16 50300 +1944 118 11.18 5.18 9.53 0.39 306.24 280.41 50481 +1944 119 15.65 9.65 14 0 398.89 365.26 50661 +1944 120 13.79 7.79 12.14 0 357.78 370.85 50840 +1944 121 13.92 7.92 12.27 0 360.53 371.68 51016 +1944 122 13.5 7.5 11.85 0 351.71 373.82 51191 +1944 123 11.38 5.38 9.73 1.32 309.95 284.46 51365 +1944 124 11.41 5.41 9.76 1.97 310.51 285.24 51536 +1944 125 13.33 7.33 11.68 0.41 348.2 282.98 51706 +1944 126 13.56 7.56 11.91 0 352.96 377.8 51874 +1944 127 16 10 14.35 0 407.06 372.79 52039 +1944 128 16.78 10.78 15.13 0.34 425.78 278.78 52203 +1944 129 15.52 9.52 13.87 0 395.89 375.87 52365 +1944 130 17.96 11.96 16.31 0 455.5 369.99 52524 +1944 131 18.16 12.16 16.51 0.02 460.7 277.64 52681 +1944 132 16.09 10.09 14.44 0.29 409.18 282.6 52836 +1944 133 16.56 10.56 14.91 0.29 420.43 282.19 52989 +1944 134 21.79 15.79 20.14 0 564.42 360.36 53138 +1944 135 21.37 15.37 19.72 0.07 551.49 271.92 53286 +1944 136 17.97 11.97 16.32 0 455.76 374.28 53430 +1944 137 13.27 7.27 11.62 0.08 346.96 290.36 53572 +1944 138 13.97 7.97 12.32 0 361.6 386.16 53711 +1944 139 15.14 9.14 13.49 0 387.24 384.01 53848 +1944 140 15.9 9.9 14.25 0 404.71 382.54 53981 +1944 141 16.58 10.58 14.93 1.07 420.91 285.86 54111 +1944 142 14.3 8.3 12.65 1.62 368.68 290.64 54238 +1944 143 15.48 9.48 13.83 0 394.97 385.12 54362 +1944 144 20.81 14.81 19.16 0.06 534.64 277.11 54483 +1944 145 19.39 13.39 17.74 0 493.86 374.73 54600 +1944 146 14.57 8.57 12.92 0.99 374.56 291.56 54714 +1944 147 12.94 6.94 11.29 0 340.24 393.03 54824 +1944 148 13.92 7.92 12.27 0 360.53 391.18 54931 +1944 149 16.5 10.5 14.85 0 418.98 384.92 55034 +1944 150 16.97 10.97 15.32 0 430.45 383.94 55134 +1944 151 16.1 10.1 14.45 0 409.42 386.74 55229 +1944 152 22.45 16.45 20.8 0 585.26 366.2 55321 +1944 153 21.23 15.23 19.58 0.22 547.23 278.26 55409 +1944 154 22.24 16.24 20.59 0.41 578.56 275.67 55492 +1944 155 23.74 17.74 22.09 0.86 627.88 271.31 55572 +1944 156 19.34 13.34 17.69 0.46 492.47 283.74 55648 +1944 157 17.85 11.85 16.2 1.12 452.65 287.35 55719 +1944 158 17.03 11.03 15.38 0.68 431.94 289.28 55786 +1944 159 14.07 8.07 12.42 0 363.73 393.69 55849 +1944 160 17.1 11.1 15.45 0.18 433.67 289.45 55908 +1944 161 17.8 11.8 16.15 2 451.37 287.97 55962 +1944 162 21.67 15.67 20.02 0.02 560.7 278.32 56011 +1944 163 18.68 12.68 17.03 0 474.48 381.54 56056 +1944 164 17.01 11.01 15.36 0.11 431.44 289.94 56097 +1944 165 15.47 9.47 13.82 0.14 394.74 293.16 56133 +1944 166 16.86 10.86 15.21 0 427.74 387.18 56165 +1944 167 23.1 17.1 21.45 0 606.42 365.92 56192 +1944 168 22.39 16.39 20.74 0 583.34 368.81 56214 +1944 169 23.48 17.48 21.83 0 619.08 364.46 56231 +1944 170 22.81 16.81 21.16 1.18 596.9 275.38 56244 +1944 171 21.01 15.01 19.36 0.26 540.6 280.52 56252 +1944 172 17.76 11.76 16.11 1.65 450.34 288.5 56256 +1944 173 18.6 12.6 16.95 0 472.34 382.08 56255 +1944 174 22.25 16.25 20.6 0 578.87 369.31 56249 +1944 175 20.82 14.82 19.17 1.46 534.93 280.92 56238 +1944 176 18.58 12.58 16.93 0.03 471.8 286.49 56223 +1944 177 21.02 15.02 19.37 0.37 540.9 280.28 56203 +1944 178 17.94 11.94 16.29 0.76 454.98 287.91 56179 +1944 179 19.2 13.2 17.55 0.34 488.61 284.88 56150 +1944 180 18.23 12.23 16.58 0.02 462.54 287.08 56116 +1944 181 15.07 9.07 13.42 0.14 385.66 293.64 56078 +1944 182 22.29 16.29 20.64 1.5 580.15 276.44 56035 +1944 183 22.77 16.77 21.12 0 595.59 366.53 55987 +1944 184 24.27 18.27 22.62 0 646.14 360.2 55935 +1944 185 24.79 18.79 23.14 0.58 664.49 268.39 55879 +1944 186 21.99 15.99 20.34 0.16 570.66 276.8 55818 +1944 187 24.42 18.42 22.77 0 651.39 359.05 55753 +1944 188 23.77 17.77 22.12 0 628.9 361.55 55684 +1944 189 25.21 19.21 23.56 0 679.63 355.12 55611 +1944 190 22.99 16.99 21.34 0.62 602.79 273.14 55533 +1944 191 23.3 17.3 21.65 0 613.06 362.68 55451 +1944 192 25.16 19.16 23.51 0 677.81 354.44 55366 +1944 193 27.15 21.15 25.5 0.02 753.41 258.56 55276 +1944 194 26.85 20.85 25.2 1.14 741.58 259.52 55182 +1944 195 22.39 16.39 20.74 0.25 583.34 273.92 55085 +1944 196 21.26 15.26 19.61 0 548.14 369.03 54984 +1944 197 21.82 15.82 20.17 0.01 565.35 274.9 54879 +1944 198 19.87 13.87 18.22 0 507.33 372.98 54770 +1944 199 19.42 13.42 17.77 0 494.69 374.1 54658 +1944 200 22.37 16.37 20.72 0.11 582.7 272.47 54542 +1944 201 22.33 16.33 20.68 0 581.42 362.98 54423 +1944 202 22.98 16.98 21.33 0 602.46 359.9 54301 +1944 203 25.15 19.15 23.5 0 677.45 350.3 54176 +1944 204 23.76 17.76 22.11 0 628.56 355.77 54047 +1944 205 19.42 13.42 17.77 0 494.69 371.11 53915 +1944 206 17.54 11.54 15.89 0 444.72 376.28 53780 +1944 207 19.15 13.15 17.5 0.31 487.23 278.06 53643 +1944 208 18.64 12.64 16.99 0.04 473.41 278.76 53502 +1944 209 18.79 12.79 17.14 0.3 477.44 277.92 53359 +1944 210 16.65 10.65 15 0.18 422.61 282.11 53213 +1944 211 15.86 9.86 14.21 0 403.78 377.45 53064 +1944 212 17.35 11.35 15.7 0 439.92 372.6 52913 +1944 213 20.83 14.83 19.18 0.03 535.23 270.69 52760 +1944 214 20.82 14.82 19.17 0.31 534.93 270.16 52604 +1944 215 23.25 17.25 21.6 0.25 611.39 262.94 52445 +1944 216 23.76 17.76 22.11 0.7 628.56 260.66 52285 +1944 217 24.93 18.93 23.28 0 669.5 341.8 52122 +1944 218 28.73 22.73 27.08 0 818.41 322.88 51958 +1944 219 31.5 25.5 29.85 0 943.77 306.2 51791 +1944 220 31.47 25.47 29.82 0 942.33 305.56 51622 +1944 221 25.93 19.93 24.28 0 706.27 333.76 51451 +1944 222 25.22 19.22 23.57 0 679.99 335.9 51279 +1944 223 24.22 18.22 22.57 0 644.4 339.01 51105 +1944 224 21.62 15.62 19.97 0 559.15 347.87 50929 +1944 225 23.02 17.02 21.37 0 603.78 341.61 50751 +1944 226 25.39 19.39 23.74 0 686.21 330.87 50572 +1944 227 23.12 17.12 21.47 0.14 607.08 254.15 50392 +1944 228 27.88 21.88 26.23 0.15 782.88 237.75 50210 +1944 229 22.99 16.99 21.34 0.03 602.79 252.72 50026 +1944 230 19.88 13.88 18.23 0.29 507.62 259.83 49842 +1944 231 23.7 17.7 22.05 0.31 626.52 248.68 49656 +1944 232 21.16 15.16 19.51 0 545.11 339.46 49469 +1944 233 21.5 15.5 19.85 0 555.46 336.91 49280 +1944 234 23.07 17.07 21.42 0 605.43 329.91 49091 +1944 235 23.67 17.67 22.02 0 625.5 326.2 48900 +1944 236 24.04 18.04 22.39 0 638.16 323.4 48709 +1944 237 25.32 19.32 23.67 0 683.64 316.65 48516 +1944 238 23.32 17.32 21.67 0.63 613.72 242.2 48323 +1944 239 24.34 18.34 22.69 0.05 648.58 238.19 48128 +1944 240 24.1 18.1 22.45 0 640.23 316.83 47933 +1944 241 25.3 19.3 23.65 0 682.91 310.4 47737 +1944 242 27.38 21.38 25.73 0.15 762.6 224.82 47541 +1944 243 23.15 17.15 21.5 0.23 608.07 236.43 47343 +1944 244 19.43 13.43 17.78 0.14 494.97 244.18 47145 +1944 245 19.75 13.75 18.1 0.01 503.94 242.1 46947 +1944 246 22.59 16.59 20.94 0.04 589.76 233.83 46747 +1944 247 25.78 19.78 24.13 0.09 700.65 223.47 46547 +1944 248 25.16 19.16 23.51 1.5 677.81 223.98 46347 +1944 249 25.07 19.07 23.42 0 674.55 297.04 46146 +1944 250 21.95 15.95 20.3 0.88 569.41 229.77 45945 +1944 251 16.01 10.01 14.36 0.36 407.3 240.56 45743 +1944 252 14.91 8.91 13.26 0.09 382.08 240.76 45541 +1944 253 16.08 10.08 14.43 0 408.95 316.27 45339 +1944 254 15.24 9.24 13.59 0 389.5 315.99 45136 +1944 255 13.86 7.86 12.21 0 359.26 316.58 44933 +1944 256 13.9 7.9 12.25 0 360.11 314.2 44730 +1944 257 20.28 14.28 18.63 0 519.09 296.66 44527 +1944 258 18.7 12.7 17.05 0 475.02 298.69 44323 +1944 259 16.2 10.2 14.55 0.66 411.79 226.75 44119 +1944 260 17 11 15.35 0.08 431.19 223.58 43915 +1944 261 12.62 6.62 10.97 0 333.83 304.64 43711 +1944 262 16.72 10.72 15.07 0 424.32 293.95 43507 +1944 263 16.35 10.35 14.7 0 415.37 292.32 43303 +1944 264 17.83 11.83 16.18 0 452.14 286.36 43099 +1944 265 20.31 14.31 18.66 0.16 519.96 208.25 42894 +1944 266 20.88 14.88 19.23 0.64 536.72 205.26 42690 +1944 267 18.53 12.53 16.88 0.62 470.47 207.93 42486 +1944 268 13.98 7.98 12.33 0 361.81 284.42 42282 +1944 269 15.32 9.32 13.67 0.02 391.32 209.49 42078 +1944 270 15.61 9.61 13.96 0.39 397.97 207.07 41875 +1944 271 15.61 9.61 13.96 0 397.97 273.49 41671 +1944 272 20.1 14.1 18.45 0 513.9 260.55 41468 +1944 273 18.79 12.79 17.14 0.03 477.44 196.01 41265 +1944 274 13.23 7.23 11.58 0.49 346.14 202.45 41062 +1944 275 10.01 4.01 8.36 0.03 285.28 204.07 40860 +1944 276 10.44 4.44 8.79 1.06 292.83 201.56 40658 +1944 277 8.28 2.28 6.63 0.56 256.55 201.65 40456 +1944 278 10.85 4.85 9.2 0.11 300.2 196.91 40255 +1944 279 11.26 5.26 9.61 0.81 307.72 194.34 40054 +1944 280 17.71 11.71 16.06 0.78 449.06 183.81 39854 +1944 281 17.12 11.12 15.47 0.43 434.17 182.74 39654 +1944 282 13.91 7.91 12.26 2.6 360.32 185.14 39455 +1944 283 15.7 9.7 14.05 0.27 400.05 180.69 39256 +1944 284 15.82 9.82 14.17 0.36 402.84 178.29 39058 +1944 285 14.74 8.74 13.09 0.02 378.3 177.76 38861 +1944 286 15.07 9.07 13.42 0.91 385.66 175.29 38664 +1944 287 13.92 7.92 12.27 0.85 360.53 174.54 38468 +1944 288 10 4 8.35 0.75 285.11 176.61 38273 +1944 289 11.19 5.19 9.54 0.37 306.42 173.47 38079 +1944 290 13.95 7.95 12.3 0.68 361.17 168.34 37885 +1944 291 14.03 8.03 12.38 0.41 362.88 166.24 37693 +1944 292 13.97 7.97 12.32 0.54 361.6 164.32 37501 +1944 293 13.4 7.4 11.75 0.87 349.64 162.93 37311 +1944 294 13.2 7.2 11.55 0.15 345.53 161 37121 +1944 295 14.38 8.38 12.73 0 370.41 210.11 36933 +1944 296 14.54 8.54 12.89 0.66 373.9 155.48 36745 +1944 297 14.02 8.02 12.37 0.03 362.66 154.05 36560 +1944 298 15.57 9.57 13.92 0 397.04 200.47 36375 +1944 299 15.31 9.31 13.66 0 391.09 198.16 36191 +1944 300 12.71 6.71 11.06 0.93 335.62 149.45 36009 +1944 301 14.29 8.29 12.64 0 368.46 194.6 35829 +1944 302 15.3 9.3 13.65 0.44 390.86 142.91 35650 +1944 303 21.96 15.96 20.31 0 569.72 175.82 35472 +1944 304 19.27 13.27 17.62 0.13 490.54 134.24 35296 +1944 305 13.08 7.08 11.43 0 343.08 186.02 35122 +1944 306 13.26 7.26 11.61 0 346.76 183.58 34950 +1944 307 11.12 5.12 9.47 0.03 305.13 137.76 34779 +1944 308 8.4 2.4 6.75 0 258.46 183.88 34610 +1944 309 5.82 -0.18 4.17 0 219.99 183.78 34444 +1944 310 6.51 0.51 4.86 0.63 229.76 135.57 34279 +1944 311 4.15 -1.85 2.5 1.76 197.81 135.26 34116 +1944 312 -0.08 -6.08 -1.73 0 150.04 180.22 33956 +1944 313 1.47 -4.53 -0.18 0 166.24 177.21 33797 +1944 314 7.07 1.07 5.42 0 237.97 171.36 33641 +1944 315 6.35 0.35 4.7 1.34 227.47 127.05 33488 +1944 316 6.69 0.69 5.04 0.38 232.37 125.2 33337 +1944 317 6.86 0.86 5.21 0.83 234.86 123.45 33188 +1944 318 5.95 -0.05 4.3 1.51 221.81 122.21 33042 +1944 319 3 -3 1.35 1.1 183.68 122.4 32899 +1944 320 2.76 -3.24 1.11 0 180.85 161.46 32758 +1944 321 2.54 -3.46 0.89 0 178.28 159.45 32620 +1944 322 6.97 0.97 5.32 0 236.48 154.68 32486 +1944 323 6.89 0.89 5.24 0 235.3 153.12 32354 +1944 324 5.37 -0.63 3.72 0.21 213.82 114.11 32225 +1944 325 5.79 -0.21 4.14 0.44 219.58 112.6 32100 +1944 326 5.13 -0.87 3.48 0 210.58 149.12 31977 +1944 327 4.13 -1.87 2.48 0.15 197.56 110.92 31858 +1944 328 5.45 -0.55 3.8 0.03 214.9 108.81 31743 +1944 329 8.02 2.02 6.37 0.24 252.46 106.32 31631 +1944 330 12.28 6.28 10.63 0.01 327.13 102.44 31522 +1944 331 16 10 14.35 0 407.06 131.17 31417 +1944 332 14.58 8.58 12.93 0 374.78 131.27 31316 +1944 333 16.18 10.18 14.53 0.01 411.32 96.26 31218 +1944 334 14.25 8.25 12.6 0.37 367.6 97.16 31125 +1944 335 10.77 4.77 9.12 0.29 298.75 98.87 31035 +1944 336 5.19 -0.81 3.54 0.4 211.39 101.18 30949 +1944 337 1.93 -4.07 0.28 0 171.33 135.05 30867 +1944 338 5.01 -0.99 3.36 0 208.98 132.42 30790 +1944 339 3.06 -2.94 1.41 0 184.4 132.73 30716 +1944 340 2.92 -3.08 1.27 0.01 182.73 99.05 30647 +1944 341 3.54 -2.46 1.89 0.01 190.2 98.11 30582 +1944 342 1.57 -4.43 -0.08 0 167.33 131.04 30521 +1944 343 2.58 -3.42 0.93 0 178.74 129.72 30465 +1944 344 5.39 -0.61 3.74 0 214.09 127.04 30413 +1944 345 2.11 -3.89 0.46 0 173.35 128.39 30366 +1944 346 1.47 -4.53 -0.18 0 166.24 128.14 30323 +1944 347 -3.14 -9.14 -4.79 0 122.03 129.36 30284 +1944 348 1.7 -4.3 0.05 0 168.77 127.08 30251 +1944 349 0.59 -5.41 -1.06 0.07 156.87 95.4 30221 +1944 350 2.53 -3.47 0.88 1.03 178.16 94.47 30197 +1944 351 1.05 -4.95 -0.6 0.9 161.71 94.83 30177 +1944 352 3.66 -2.34 2.01 0.15 191.68 93.8 30162 +1944 353 3.86 -2.14 2.21 1.22 194.16 93.67 30151 +1944 354 5.41 -0.59 3.76 0.56 214.36 92.99 30145 +1944 355 5.22 -0.78 3.57 0.07 211.79 93.07 30144 +1944 356 5 -1 3.35 0 208.85 124.25 30147 +1944 357 4.82 -1.18 3.17 0 206.47 124.42 30156 +1944 358 5.75 -0.25 4.1 0 219.02 123.96 30169 +1944 359 1.5 -4.5 -0.15 0 166.57 126.33 30186 +1944 360 -1.47 -7.47 -3.12 0 136.7 127.93 30208 +1944 361 1.86 -4.14 0.21 0 170.54 126.86 30235 +1944 362 2.88 -3.12 1.23 0.31 182.26 95.1 30267 +1944 363 -0.21 -6.21 -1.86 0.13 148.75 140.58 30303 +1944 364 -12.01 -18.01 -13.66 0.02 64.8 143.37 30343 +1944 365 -12.68 -18.68 -14.33 0 61.64 177.14 30388 +1945 1 -7.98 -13.98 -9.63 0 86.96 177.02 30438 +1945 2 -6.47 -12.47 -8.12 0 96.81 177.31 30492 +1945 3 -4.09 -10.09 -5.74 0 114.32 177.48 30551 +1945 4 -3.25 -9.25 -4.9 0 121.12 178.04 30614 +1945 5 -0.49 -6.49 -2.14 0 145.99 177.56 30681 +1945 6 0.23 -5.77 -1.42 0.96 153.17 144.35 30752 +1945 7 -0.72 -6.72 -2.37 0 143.77 179.12 30828 +1945 8 -1.24 -7.24 -2.89 0 138.83 180.72 30907 +1945 9 -0.29 -6.29 -1.94 0.34 147.96 147.92 30991 +1945 10 1.68 -4.32 0.03 0.93 168.54 147.87 31079 +1945 11 0.58 -5.42 -1.07 0 156.76 183.9 31171 +1945 12 1.65 -4.35 0 0 168.21 184.06 31266 +1945 13 4.29 -1.71 2.64 0.38 199.59 148.29 31366 +1945 14 3.34 -2.66 1.69 0.56 187.77 107.31 31469 +1945 15 0.28 -5.72 -1.37 0 153.68 146.1 31575 +1945 16 -4.24 -10.24 -5.89 0 113.14 149.22 31686 +1945 17 -1.44 -7.44 -3.09 1.31 136.97 157.86 31800 +1945 18 -5.38 -11.38 -7.03 0.53 104.52 161.82 31917 +1945 19 -3.71 -9.71 -5.36 0 117.35 201.34 32038 +1945 20 -1.84 -7.84 -3.49 0.02 133.32 163.23 32161 +1945 21 -5.23 -11.23 -6.88 0.04 105.62 165.63 32289 +1945 22 -4.82 -10.82 -6.47 0.08 108.68 166.92 32419 +1945 23 -3.67 -9.67 -5.32 0.03 117.67 167.86 32552 +1945 24 -8.09 -14.09 -9.74 0 86.27 211.66 32688 +1945 25 -6.18 -12.18 -7.83 0.03 98.81 171.22 32827 +1945 26 -4.42 -10.42 -6.07 0 111.74 214.07 32969 +1945 27 -1.31 -7.31 -2.96 0.08 138.18 172.66 33114 +1945 28 -3.38 -9.38 -5.03 0 120.04 217.8 33261 +1945 29 -0.32 -6.32 -1.97 0 147.66 218.63 33411 +1945 30 0.55 -5.45 -1.1 0 156.45 220.18 33564 +1945 31 4.68 -1.32 3.03 0 204.63 219.24 33718 +1945 32 7.57 1.57 5.92 0.01 245.5 174.35 33875 +1945 33 5.1 -0.9 3.45 0 210.18 221.76 34035 +1945 34 7.78 1.78 6.13 0 248.73 220.65 34196 +1945 35 2.77 -3.23 1.12 0 180.96 226.09 34360 +1945 36 2.12 -3.88 0.47 0 173.47 228.58 34526 +1945 37 -0.92 -6.92 -2.57 0 141.85 232.56 34694 +1945 38 -1.61 -7.61 -3.26 0 135.41 235.48 34863 +1945 39 1.88 -4.12 0.23 0 170.77 235.75 35035 +1945 40 5.76 -0.24 4.11 0 219.16 234.7 35208 +1945 41 8.7 2.7 7.05 0 263.29 233.44 35383 +1945 42 5.86 -0.14 4.21 0 220.55 200.88 35560 +1945 43 7.68 1.68 6.03 0 247.19 201.93 35738 +1945 44 8.74 2.74 7.09 0.51 263.94 152.56 35918 +1945 45 6.12 0.12 4.47 0 224.2 208.52 36099 +1945 46 3.83 -2.17 2.18 0 193.79 213.1 36282 +1945 47 2.79 -3.21 1.14 0.02 181.2 162.53 36466 +1945 48 4.9 -1.1 3.25 0.23 207.52 163.41 36652 +1945 49 3.98 -2.02 2.33 0 195.67 221.41 36838 +1945 50 5.79 -0.21 4.14 0 219.58 222.54 37026 +1945 51 4.13 -1.87 2.48 0.08 197.56 170.21 37215 +1945 52 5.67 -0.33 4.02 0 217.92 228.44 37405 +1945 53 3.54 -2.46 1.89 0 190.2 233.24 37596 +1945 54 10.24 4.24 8.59 0 289.3 229.22 37788 +1945 55 9.51 3.51 7.86 0 276.71 233.07 37981 +1945 56 8.68 2.68 7.03 0 262.96 236.7 38175 +1945 57 11.4 5.4 9.75 0 310.32 236.13 38370 +1945 58 10.61 4.61 8.96 0.04 295.87 180.05 38565 +1945 59 6.54 0.54 4.89 0 230.2 247.5 38761 +1945 60 9.12 3.12 7.47 0.03 270.17 185.61 38958 +1945 61 12.79 6.79 11.14 0 337.22 245.32 39156 +1945 62 11.39 5.39 9.74 0 310.13 250.13 39355 +1945 63 8.59 2.59 6.94 0 261.51 256.79 39553 +1945 64 9.35 3.35 7.7 0 274.01 258.73 39753 +1945 65 11.74 5.74 10.09 0 316.72 258.27 39953 +1945 66 6.78 0.78 5.13 0.41 233.69 200.55 40154 +1945 67 7.19 1.19 5.54 0 239.76 269.84 40355 +1945 68 4.83 -1.17 3.18 0 206.6 275.23 40556 +1945 69 0.84 -5.16 -0.81 0 159.48 281.38 40758 +1945 70 4.22 -1.78 2.57 0 198.7 281.34 40960 +1945 71 6.12 0.12 4.47 0 224.2 282.31 41163 +1945 72 7.82 1.82 6.17 0 249.34 283.16 41366 +1945 73 5.92 -0.08 4.27 0 221.39 288.05 41569 +1945 74 11.33 5.33 9.68 0 309.02 283.65 41772 +1945 75 10.84 4.84 9.19 0 300.02 287.1 41976 +1945 76 11.13 5.13 9.48 0 305.31 289.26 42179 +1945 77 10.8 4.8 9.15 0 299.29 292.35 42383 +1945 78 9.43 3.43 7.78 0 275.36 297.03 42587 +1945 79 6.51 0.51 4.86 0.14 229.76 227.68 42791 +1945 80 4.74 -1.26 3.09 0.01 205.42 231.1 42996 +1945 81 7.96 1.96 6.31 0 251.52 306.89 43200 +1945 82 12.3 6.3 10.65 0 327.52 302.89 43404 +1945 83 12.52 6.52 10.87 0 331.84 304.96 43608 +1945 84 11.48 5.48 9.83 0 311.82 309.27 43812 +1945 85 14.83 8.83 13.18 0 380.3 305.46 44016 +1945 86 11.48 5.48 9.83 0 311.82 314.13 44220 +1945 87 12.32 6.32 10.67 0 327.91 315.17 44424 +1945 88 11.7 5.7 10.05 0 315.97 318.59 44627 +1945 89 16.72 10.72 15.07 0 424.32 310.56 44831 +1945 90 15.77 9.77 14.12 0 401.68 315.06 45034 +1945 91 14.66 8.66 13.01 0.6 376.54 239.77 45237 +1945 92 16.86 10.86 15.21 0.03 427.74 237.66 45439 +1945 93 18.74 12.74 17.09 0.06 476.09 235.63 45642 +1945 94 12.77 6.77 11.12 0.06 336.82 247.52 45843 +1945 95 15.87 9.87 14.22 0 404.01 325.56 46045 +1945 96 14.61 8.61 12.96 0.08 375.44 247.85 46246 +1945 97 11.75 5.75 10.1 0 316.91 338.21 46446 +1945 98 13.5 7.5 11.85 0 351.71 336.77 46647 +1945 99 15.7 9.7 14.05 0 400.05 333.92 46846 +1945 100 13.63 7.63 11.98 0 354.42 340.42 47045 +1945 101 13.32 7.32 11.67 0.09 347.99 257.23 47243 +1945 102 12.74 6.74 11.09 0 336.22 346.04 47441 +1945 103 13.91 7.91 12.26 0 360.32 345.45 47638 +1945 104 13.72 7.72 12.07 0 356.31 347.67 47834 +1945 105 12.22 6.22 10.57 0 325.96 352.51 48030 +1945 106 11.24 5.24 9.59 0 307.35 356.02 48225 +1945 107 8.32 2.32 6.67 0 257.19 362.64 48419 +1945 108 11.57 5.57 9.92 0.46 313.51 269.12 48612 +1945 109 9.89 3.89 8.24 0 283.2 363.48 48804 +1945 110 9.5 3.5 7.85 0 276.54 365.57 48995 +1945 111 12.79 6.79 11.14 0 337.22 361 49185 +1945 112 13.56 7.56 11.91 0.27 352.96 270.67 49374 +1945 113 14.75 8.75 13.1 0.52 378.52 269.66 49561 +1945 114 13.88 7.88 12.23 0 359.69 363.01 49748 +1945 115 12.51 6.51 10.86 0 331.65 367.37 49933 +1945 116 13.06 7.06 11.41 0 342.67 367.44 50117 +1945 117 17.16 11.16 15.51 0 435.17 358.85 50300 +1945 118 17.87 11.87 16.22 0 453.17 358.16 50481 +1945 119 14.78 8.78 13.13 0 379.19 367.39 50661 +1945 120 14.11 8.11 12.46 0.33 364.59 277.59 50840 +1945 121 23.65 17.65 22 0 624.82 341.97 51016 +1945 122 20.64 14.64 18.99 0 529.61 354.13 51191 +1945 123 19.61 13.61 17.96 0.01 500 268.87 51365 +1945 124 20.78 14.78 19.13 0.04 533.75 266.77 51536 +1945 125 18.91 12.91 17.26 0.34 480.69 272.02 51706 +1945 126 19.32 13.32 17.67 0 491.92 362.4 51874 +1945 127 18.69 12.69 17.04 0.06 474.75 273.91 52039 +1945 128 19.57 13.57 17.92 0.48 498.88 272.58 52203 +1945 129 20.52 14.52 18.87 0 526.08 361.14 52365 +1945 130 21.91 15.91 20.26 0.15 568.16 267.75 52524 +1945 131 21.82 15.82 20.17 0 565.35 358.09 52681 +1945 132 24.06 18.06 22.41 0.01 638.85 262.61 52836 +1945 133 20.78 14.78 19.13 0 533.75 363.27 52989 +1945 134 21.99 15.99 20.34 1.42 570.66 269.71 53138 +1945 135 24.67 18.67 23.02 0 660.22 349.55 53286 +1945 136 23.46 17.46 21.81 0 618.41 355.2 53430 +1945 137 24.88 18.88 23.23 0.01 667.71 262.43 53572 +1945 138 21.72 15.72 20.07 0.13 562.24 272.38 53711 +1945 139 19.61 13.61 17.96 0 500 371.16 53848 +1945 140 18.37 12.37 16.72 0.15 466.23 281.66 53981 +1945 141 16.77 10.77 15.12 1.48 425.54 285.47 54111 +1945 142 16.94 10.94 15.29 0.57 429.71 285.49 54238 +1945 143 14.7 8.7 13.05 0.08 377.42 290.31 54362 +1945 144 13.6 7.6 11.95 0.08 353.8 292.64 54483 +1945 145 16 10 14.35 0.03 407.06 288.53 54600 +1945 146 14.76 8.76 13.11 0.17 378.75 291.21 54714 +1945 147 16.53 10.53 14.88 0 419.7 384.14 54824 +1945 148 16.72 10.72 15.07 0 424.32 383.99 54931 +1945 149 19.17 13.17 17.52 0 487.78 376.97 55034 +1945 150 19.23 13.23 17.58 0.04 489.43 282.83 55134 +1945 151 23.92 17.92 22.27 0 634.03 360.17 55229 +1945 152 24.26 18.26 22.61 0.75 645.79 269.12 55321 +1945 153 25.8 19.8 24.15 0.32 701.39 264.14 55409 +1945 154 24.75 18.75 23.1 1.71 663.06 267.93 55492 +1945 155 20.82 14.82 19.17 0.44 534.93 279.73 55572 +1945 156 21.84 15.84 20.19 0.09 565.97 277.18 55648 +1945 157 20.44 14.44 18.79 0 523.74 374.79 55719 +1945 158 20.17 14.17 18.52 0 515.92 375.89 55786 +1945 159 16.34 10.34 14.69 0.04 415.13 290.91 55849 +1945 160 18.69 12.69 17.04 0.56 474.75 285.87 55908 +1945 161 21.82 15.82 20.17 1 565.35 277.85 55962 +1945 162 18.3 12.3 16.65 0.51 464.38 286.88 56011 +1945 163 20.44 14.44 18.79 0.02 523.74 281.79 56056 +1945 164 18.65 12.65 17 0.38 473.68 286.26 56097 +1945 165 17.55 11.55 15.9 0.05 444.98 288.84 56133 +1945 166 17.03 11.03 15.38 0 431.94 386.7 56165 +1945 167 21.24 15.24 19.59 0 547.53 373.05 56192 +1945 168 24.85 18.85 23.2 0 666.63 358.59 56214 +1945 169 24.51 18.51 22.86 0.1 654.55 270.07 56231 +1945 170 25.03 19.03 23.38 0 673.11 357.8 56244 +1945 171 20.62 14.62 18.97 0 529.02 375.41 56252 +1945 172 25.27 19.27 23.62 0 681.82 356.76 56256 +1945 173 22.55 16.55 20.9 0 588.47 368.23 56255 +1945 174 23.06 17.06 21.41 0.25 605.1 274.59 56249 +1945 175 24.58 18.58 22.93 0.14 657.03 269.78 56238 +1945 176 27.18 21.18 25.53 0 754.61 347.46 56223 +1945 177 27.5 21.5 25.85 0 767.42 345.73 56203 +1945 178 24.42 18.42 22.77 0.06 651.39 270.23 56179 +1945 179 22.28 16.28 20.63 0 579.83 368.95 56150 +1945 180 22.62 16.62 20.97 0 590.73 367.51 56116 +1945 181 25.27 19.27 23.62 0 681.82 356.25 56078 +1945 182 25.71 19.71 24.06 0.26 698.04 265.56 56035 +1945 183 24.95 18.95 23.3 0.03 670.22 268.03 55987 +1945 184 24.48 18.48 22.83 0 653.5 359.3 55935 +1945 185 28.36 22.36 26.71 0 802.78 340.46 55879 +1945 186 24.74 18.74 23.09 0.22 662.71 268.37 55818 +1945 187 26.38 20.38 24.73 0.01 723.36 262.58 55753 +1945 188 28 22 26.35 0.01 787.81 256.28 55684 +1945 189 24.97 18.97 23.32 0 670.94 356.2 55611 +1945 190 24.48 18.48 22.83 0 653.5 357.99 55533 +1945 191 24.08 18.08 22.43 0 639.54 359.45 55451 +1945 192 25.51 19.51 23.86 0.14 690.62 264.64 55366 +1945 193 25.38 19.38 23.73 0 685.84 353.19 55276 +1945 194 25.9 19.9 24.25 0 705.14 350.58 55182 +1945 195 27.6 21.6 25.95 0 771.46 342.01 55085 +1945 196 28.4 22.4 26.75 0 804.45 337.45 54984 +1945 197 27.15 21.15 25.5 0.16 753.41 257.6 54879 +1945 198 28.65 22.65 27 1.05 815.01 251.46 54770 +1945 199 25.07 19.07 23.42 0 674.55 352.53 54658 +1945 200 21.51 15.51 19.86 0 555.77 366.5 54542 +1945 201 23.53 17.53 21.88 1.16 620.77 268.68 54423 +1945 202 23.77 17.77 22.12 0.1 628.9 267.53 54301 +1945 203 18.43 12.43 16.78 0.01 467.81 281.44 54176 +1945 204 17.61 11.61 15.96 0 446.5 377.18 54047 +1945 205 18.93 12.93 17.28 1.11 481.23 279.5 53915 +1945 206 17.28 11.28 15.63 0.06 438.16 282.77 53780 +1945 207 21.35 15.35 19.7 0.77 550.88 272.5 53643 +1945 208 18.58 12.58 16.93 0 471.8 371.86 53502 +1945 209 18.67 12.67 17.02 0 474.21 370.93 53359 +1945 210 22.22 16.22 20.57 0 577.92 358.23 53213 +1945 211 22.77 16.77 21.12 0.13 595.59 266.53 53064 +1945 212 22.16 16.16 20.51 0.18 576.02 267.68 52913 +1945 213 18.8 12.8 17.15 0.03 477.71 275.66 52760 +1945 214 21.58 15.58 19.93 0 557.92 357.54 52604 +1945 215 25 19 23.35 0.03 672.02 257.5 52445 +1945 216 24.38 18.38 22.73 0.1 649.98 258.75 52285 +1945 217 25.41 19.41 23.76 0 686.94 339.71 52122 +1945 218 28.27 22.27 26.62 0 799.01 325.28 51958 +1945 219 25.3 19.3 23.65 0 682.91 338.41 51791 +1945 220 21.54 15.54 19.89 0 556.69 352.35 51622 +1945 221 19.09 13.09 17.44 0.04 485.59 269.6 51451 +1945 222 19.7 13.7 18.05 0 502.53 356.5 51279 +1945 223 18.69 12.69 17.04 0.28 474.75 268.86 51105 +1945 224 18.1 12.1 16.45 0.05 459.14 269.36 50929 +1945 225 19.71 13.71 18.06 0.62 502.81 264.84 50751 +1945 226 14.81 8.81 13.16 0 379.85 365.43 50572 +1945 227 20.72 14.72 19.07 0 531.97 347.42 50392 +1945 228 20.2 14.2 18.55 0 516.78 347.92 50210 +1945 229 23.4 17.4 21.75 0 616.4 335.4 50026 +1945 230 28.45 22.45 26.8 0 806.56 311.84 49842 +1945 231 27.92 21.92 26.27 0.05 784.52 234.83 49656 +1945 232 24.77 18.77 23.12 0.91 663.78 244.5 49469 +1945 233 23.3 17.3 21.65 0.59 613.06 247.82 49280 +1945 234 21.69 15.69 20.04 0 561.31 334.86 49091 +1945 235 22.18 16.18 20.53 0.01 576.65 248.77 48900 +1945 236 22.57 16.57 20.92 0 589.12 328.9 48709 +1945 237 26.35 20.35 24.7 0.29 722.21 234.17 48516 +1945 238 24.4 18.4 22.75 0.3 650.69 239.09 48323 +1945 239 22.29 16.29 20.64 0.11 580.15 243.89 48128 +1945 240 20.92 14.92 19.27 0.42 537.91 246.05 47933 +1945 241 24.4 18.4 22.75 0.22 650.69 235.51 47737 +1945 242 24.9 18.9 23.25 0 668.43 310.37 47541 +1945 243 23.74 17.74 22.09 0 627.88 313.08 47343 +1945 244 21.23 15.23 19.58 0 547.23 320.04 47145 +1945 245 25.28 19.28 23.63 0.21 682.18 227.7 46947 +1945 246 18.85 12.85 17.2 0 479.06 323.45 46747 +1945 247 20.16 14.16 18.51 0.14 515.63 238.36 46547 +1945 248 18.44 12.44 16.79 0.19 468.08 240.6 46347 +1945 249 11.76 5.76 10.11 0.46 317.1 250.23 46146 +1945 250 12.44 6.44 10.79 0.67 330.27 247.78 45945 +1945 251 11.34 5.34 9.69 0 309.2 330.19 45743 +1945 252 14.57 8.57 12.92 0.01 374.56 241.31 45541 +1945 253 11.58 5.58 9.93 0 313.7 325.36 45339 +1945 254 15.9 9.9 14.25 0 404.71 314.53 45136 +1945 255 13.58 7.58 11.93 0.38 353.38 237.85 44933 +1945 256 12.65 6.65 11 0 334.42 316.6 44730 +1945 257 14.36 8.36 12.71 0 369.98 311.07 44527 +1945 258 18.66 12.66 17.01 0 473.94 298.79 44323 +1945 259 22.3 16.3 20.65 0 580.46 285.91 44119 +1945 260 23.79 17.79 22.14 0 629.58 278.7 43915 +1945 261 23.97 17.97 22.32 0 635.75 275.76 43711 +1945 262 15.6 9.6 13.95 0 397.74 296.41 43507 +1945 263 15.88 9.88 14.23 0.76 404.24 220.01 43303 +1945 264 17.75 11.75 16.1 0 450.08 286.55 43099 +1945 265 22.23 16.23 20.58 0 578.24 272.11 42894 +1945 266 25.35 19.35 23.7 0.83 684.74 194.55 42690 +1945 267 28.95 22.95 27.3 0.36 827.82 182 42486 +1945 268 24.62 18.62 22.97 0.03 658.44 192.8 42282 +1945 269 21.16 15.16 19.51 0 545.11 265.41 42078 +1945 270 23.75 17.75 22.1 0.62 628.22 191.34 41875 +1945 271 24.11 18.11 22.46 0.06 640.58 188.62 41671 +1945 272 22.08 16.08 20.43 0 573.49 255.14 41468 +1945 273 19.63 13.63 17.98 1 500.56 194.47 41265 +1945 274 10.49 4.49 8.84 1.78 293.72 205.67 41062 +1945 275 13.12 7.12 11.47 0.34 343.89 200.51 40860 +1945 276 13.24 7.24 11.59 0.22 346.35 198.32 40658 +1945 277 8.34 2.34 6.69 0 257.5 268.8 40456 +1945 278 8.78 2.78 7.13 0 264.59 265.32 40255 +1945 279 11.63 5.63 9.98 0 314.64 258.57 40054 +1945 280 13.71 7.71 12.06 0 356.1 252.63 39854 +1945 281 14.9 8.9 13.25 0.04 381.86 185.9 39654 +1945 282 18.88 12.88 17.23 0.21 479.87 177.93 39455 +1945 283 17.18 11.18 15.53 0 435.66 238.08 39256 +1945 284 16.05 10.05 14.4 0.29 408.24 177.97 39058 +1945 285 14.15 8.15 12.5 0 365.44 238.01 38861 +1945 286 16.65 10.65 15 0 422.61 230.87 38664 +1945 287 14.79 8.79 13.14 0 379.41 231.29 38468 +1945 288 14.25 8.25 12.6 0 367.6 229.43 38273 +1945 289 14.13 8.13 12.48 0.02 365.02 170.26 38079 +1945 290 19.57 13.57 17.92 0 498.88 214.07 37885 +1945 291 18.29 12.29 16.64 0.38 464.12 160.6 37693 +1945 292 18.21 12.21 16.56 0.81 462.01 158.77 37501 +1945 293 12.88 6.88 11.23 0.1 339.03 163.49 37311 +1945 294 10.59 4.59 8.94 0.06 295.51 163.6 37121 +1945 295 11.26 5.26 9.61 0 307.72 214.46 36933 +1945 296 15.49 9.49 13.84 0 395.2 205.82 36745 +1945 297 12.83 6.83 11.18 0 338.02 207.09 36560 +1945 298 15.14 9.14 13.49 0 387.24 201.15 36375 +1945 299 11.79 5.79 10.14 0 317.68 203.1 36191 +1945 300 9.07 3.07 7.42 0 269.35 203.58 36009 +1945 301 10.44 4.44 8.79 0.05 292.83 149.66 35829 +1945 302 9.19 3.19 7.54 0 271.34 198.3 35650 +1945 303 9.65 3.65 8 0 279.08 195.23 35472 +1945 304 10.77 4.77 9.12 0 298.75 191.54 35296 +1945 305 4.23 -1.77 2.58 0.24 198.83 146.11 35122 +1945 306 3.62 -2.38 1.97 0 191.19 192.96 34950 +1945 307 2.34 -3.66 0.69 0.12 175.97 143.45 34779 +1945 308 5.63 -0.37 3.98 0 217.37 186.27 34610 +1945 309 4.04 -1.96 2.39 0.28 196.42 138.83 34444 +1945 310 3.67 -2.33 2.02 0.5 191.8 137.17 34279 +1945 311 3.41 -2.59 1.76 0.38 188.62 135.64 34116 +1945 312 3.77 -2.23 2.12 0.17 193.04 133.45 33956 +1945 313 2.82 -3.18 1.17 0.46 181.55 132.3 33797 +1945 314 -3.62 -9.62 -5.27 0 118.08 177.65 33641 +1945 315 1.13 -4.87 -0.52 0.12 162.56 129.62 33488 +1945 316 3.46 -2.54 1.81 0 189.23 169.23 33337 +1945 317 3.72 -2.28 2.07 0 192.42 166.84 33188 +1945 318 7.35 1.35 5.7 0 242.16 161.87 33042 +1945 319 8.32 2.32 6.67 0.01 257.19 119.53 32899 +1945 320 8.51 2.51 6.86 0 260.22 157.36 32758 +1945 321 15.16 9.16 13.51 0.94 387.69 111.23 32620 +1945 322 13.83 7.83 12.18 0.75 358.63 111.12 32486 +1945 323 12.77 6.77 11.12 1.46 336.82 110.84 32354 +1945 324 10.92 4.92 9.27 0 301.47 147.66 32225 +1945 325 11.09 5.09 9.44 0.16 304.58 109.35 32100 +1945 326 7.53 1.53 5.88 0 244.89 147.42 31977 +1945 327 7.64 1.64 5.99 0.96 246.57 109.12 31858 +1945 328 7.01 1.01 5.36 0.69 237.08 108 31743 +1945 329 5.67 -0.33 4.02 0.48 217.92 107.58 31631 +1945 330 6.61 0.61 4.96 0 231.21 141.36 31522 +1945 331 9.56 3.56 7.91 0 277.55 137.79 31417 +1945 332 11.86 5.86 10.21 0.22 319.01 100.58 31316 +1945 333 14.49 8.49 12.84 0.01 372.81 97.75 31218 +1945 334 10.78 4.78 9.13 0.08 298.93 99.73 31125 +1945 335 4.97 -1.03 3.32 0 208.45 136.12 31035 +1945 336 5.18 -0.82 3.53 0 211.25 134.92 30949 +1945 337 5.51 -0.49 3.86 0 215.72 133.05 30867 +1945 338 4.23 -1.77 2.58 0 198.83 132.88 30790 +1945 339 0.23 -5.77 -1.42 0 153.17 134.09 30716 +1945 340 2.38 -3.62 0.73 0.01 176.43 99.26 30647 +1945 341 3.94 -2.06 2.29 0 195.16 130.59 30582 +1945 342 8.4 2.4 6.75 0 258.46 126.98 30521 +1945 343 5.25 -0.75 3.6 0 212.19 128.25 30465 +1945 344 4.31 -1.69 2.66 0 199.85 127.67 30413 +1945 345 2.99 -3.01 1.34 0.01 183.56 95.96 30366 +1945 346 1.29 -4.71 -0.36 0 164.28 128.22 30323 +1945 347 3.55 -2.45 1.9 0 190.33 126.51 30284 +1945 348 7.65 1.65 6 0 246.72 123.67 30251 +1945 349 9.62 3.62 7.97 0 278.57 121.85 30221 +1945 350 10.58 4.58 8.93 0 295.33 120.75 30197 +1945 351 6.11 0.11 4.46 0 224.06 123.75 30177 +1945 352 4.86 -1.14 3.21 0 206.99 124.41 30162 +1945 353 0.68 -5.32 -0.97 0 157.8 126.44 30151 +1945 354 0.04 -5.96 -1.61 0 151.25 126.67 30145 +1945 355 3.61 -2.39 1.96 0 191.06 124.99 30144 +1945 356 1.38 -4.62 -0.27 0.14 165.26 94.59 30147 +1945 357 0.04 -5.96 -1.61 0 151.25 126.76 30156 +1945 358 3.75 -2.25 2.1 0.54 192.79 93.82 30169 +1945 359 3.72 -2.28 2.07 0.54 192.42 93.92 30186 +1945 360 7.76 1.76 6.11 0.96 248.42 92.35 30208 +1945 361 4.07 -1.93 2.42 0.01 196.8 94.3 30235 +1945 362 0.94 -5.06 -0.71 0 160.54 127.73 30267 +1945 363 1.15 -4.85 -0.5 0.19 162.78 96.17 30303 +1945 364 2.45 -3.55 0.8 0.07 177.24 96 30343 +1945 365 8.75 2.75 7.1 0 264.1 124.7 30388 +1946 1 -0.9 -6.9 -2.55 0 142.04 130.96 30438 +1946 2 -1.43 -7.43 -3.08 0 137.07 131.91 30492 +1946 3 -5.05 -11.05 -6.7 0 106.95 134.1 30551 +1946 4 -1.82 -7.82 -3.47 0 133.5 133.93 30614 +1946 5 -2.1 -8.1 -3.75 0 131 134.7 30681 +1946 6 0.4 -5.6 -1.25 0 154.91 134.58 30752 +1946 7 1.1 -4.9 -0.55 0 162.24 135.06 30828 +1946 8 1.49 -4.51 -0.16 0 166.46 136.37 30907 +1946 9 -1.27 -7.27 -2.92 0 138.55 138.86 30991 +1946 10 -1.03 -7.03 -2.68 0 140.81 140.07 31079 +1946 11 -0.11 -6.11 -1.76 0 149.74 140.68 31171 +1946 12 -2.05 -8.05 -3.7 0 131.44 142.51 31266 +1946 13 -0.47 -6.47 -2.12 0 146.19 143.49 31366 +1946 14 0.95 -5.05 -0.7 0 160.64 144.33 31469 +1946 15 -5.47 -11.47 -7.12 0 103.86 148.31 31575 +1946 16 -2.51 -8.51 -4.16 0 127.4 148.59 31686 +1946 17 2.95 -3.05 1.3 0 183.09 147.72 31800 +1946 18 2.89 -3.11 1.24 0 182.38 149.66 31917 +1946 19 2.05 -3.95 0.4 0.26 172.67 114.04 32038 +1946 20 -3.03 -9.03 -4.68 0 122.96 155.98 32161 +1946 21 -1.05 -7.05 -2.7 0 140.62 157.2 32289 +1946 22 -0.31 -6.31 -1.96 0 147.76 158.63 32419 +1946 23 -2.96 -8.96 -4.61 0 123.55 161.56 32552 +1946 24 -1.64 -7.64 -3.29 0.11 135.14 163.04 32688 +1946 25 0.64 -5.36 -1.01 0 157.39 204.39 32827 +1946 26 0.91 -5.09 -0.74 0.09 160.22 164.47 32969 +1946 27 -0.94 -6.94 -2.59 0.07 141.66 166.72 33114 +1946 28 -2.27 -8.27 -3.92 0 129.49 211.55 33261 +1946 29 -3.05 -9.05 -4.7 0 122.79 214.11 33411 +1946 30 -3.03 -9.03 -4.68 0 122.96 216.2 33564 +1946 31 -1.3 -7.3 -2.95 0 138.27 217.65 33718 +1946 32 11.03 5.03 9.38 0 303.48 171.21 33875 +1946 33 9.37 3.37 7.72 0 274.35 175.48 34035 +1946 34 5.82 -0.18 4.17 0 219.99 180.76 34196 +1946 35 3.78 -2.22 2.13 0.21 193.17 138.31 34360 +1946 36 9.87 3.87 8.22 0 282.86 181.72 34526 +1946 37 5.23 -0.77 3.58 0.1 211.92 141.21 34694 +1946 38 8.32 2.32 6.67 0 257.19 188.35 34863 +1946 39 4.62 -1.38 2.97 0 203.85 194.1 35035 +1946 40 1 -5 -0.65 0 161.18 199.18 35208 +1946 41 1.27 -4.73 -0.38 0 164.07 201.65 35383 +1946 42 1.62 -4.38 -0.03 1.05 167.88 153.01 35560 +1946 43 4.11 -1.89 2.46 0 197.3 204.99 35738 +1946 44 3.07 -2.93 1.42 0 184.52 208.33 35918 +1946 45 3.03 -2.97 1.38 0 184.04 211 36099 +1946 46 4.73 -1.27 3.08 0 205.29 212.39 36282 +1946 47 5.27 -0.73 3.62 0.19 212.46 161.07 36466 +1946 48 2.17 -3.83 0.52 0.26 174.03 164.98 36652 +1946 49 2.03 -3.97 0.38 0.07 172.45 167.15 36838 +1946 50 5.2 -0.8 3.55 0 211.52 223.07 37026 +1946 51 6.19 0.19 4.54 0.17 225.19 168.85 37215 +1946 52 7.32 1.32 5.67 0 241.71 226.85 37405 +1946 53 6.95 0.95 5.3 0 236.19 230.17 37596 +1946 54 7.46 1.46 5.81 0 243.83 232.39 37788 +1946 55 7.7 1.7 6.05 0 247.49 235.12 37981 +1946 56 7.78 1.78 6.13 0.22 248.73 178.28 38175 +1946 57 8.53 2.53 6.88 0 260.54 239.73 38370 +1946 58 10.87 4.87 9.22 0.15 300.56 179.8 38565 +1946 59 4.81 -1.19 3.16 0 206.34 249.19 38761 +1946 60 4.97 -1.03 3.32 0.02 208.45 188.95 38958 +1946 61 7.88 1.88 6.23 0 250.27 251.86 39156 +1946 62 9.11 3.11 7.46 0 270.01 253.17 39355 +1946 63 10.93 4.93 9.28 0.13 301.65 190.31 39553 +1946 64 10.07 4.07 8.42 0 286.32 257.79 39753 +1946 65 12.25 6.25 10.6 0 326.54 257.5 39953 +1946 66 13.15 7.15 11.5 0 344.5 258.74 40154 +1946 67 9.8 3.8 8.15 0 281.65 266.59 40355 +1946 68 9.37 3.37 7.72 0 274.35 270.01 40556 +1946 69 9.96 3.96 8.31 0 284.41 271.82 40758 +1946 70 7.64 1.64 5.99 0 246.57 277.64 40960 +1946 71 2.85 -3.15 1.2 0 181.9 285.56 41163 +1946 72 2.5 -3.5 0.85 0 177.82 288.73 41366 +1946 73 3.99 -2.01 2.34 0 195.79 290.05 41569 +1946 74 5.41 -0.59 3.76 0 214.36 291.37 41772 +1946 75 7.57 1.57 5.92 0 245.5 291.61 41976 +1946 76 9.07 3.07 7.42 0 269.35 292.28 42179 +1946 77 7.07 1.07 5.42 0.2 237.97 223.11 42383 +1946 78 9.86 3.86 8.21 0 282.68 296.41 42587 +1946 79 8.61 2.61 6.96 0 261.83 300.89 42791 +1946 80 11.76 5.76 10.11 0.11 317.1 223.99 42996 +1946 81 9.98 3.98 8.33 0 284.76 304.03 43200 +1946 82 13.59 7.59 11.94 0.26 353.59 225.41 43404 +1946 83 11.73 5.73 10.08 0 316.53 306.34 43608 +1946 84 13.01 7.01 11.36 0 341.66 306.57 43812 +1946 85 12.73 6.73 11.08 0.72 336.02 232.16 44016 +1946 86 11.31 5.31 9.66 0 308.64 314.42 44220 +1946 87 6.87 0.87 5.22 0 235.01 323.51 44424 +1946 88 11.85 5.85 10.2 0 318.82 318.33 44627 +1946 89 11.67 5.67 10.02 0.4 315.4 240.68 44831 +1946 90 9.67 3.67 8.02 0.24 279.43 244.93 45034 +1946 91 18.02 12.02 16.37 0 457.05 311.81 45237 +1946 92 15.34 9.34 13.69 0 391.77 320.41 45439 +1946 93 13.41 7.41 11.76 0 349.85 326.64 45642 +1946 94 17.02 11.02 15.37 0 431.69 320.72 45843 +1946 95 15.76 9.76 14.11 0 401.44 325.82 46045 +1946 96 15.05 9.05 13.4 0 385.21 329.5 46246 +1946 97 12.66 6.66 11.01 0 334.62 336.5 46446 +1946 98 13.68 7.68 12.03 0 355.47 336.4 46647 +1946 99 17.65 11.65 16 0 447.52 329.08 46846 +1946 100 16.09 10.09 14.44 0 409.18 334.9 47045 +1946 101 19.44 13.44 17.79 0 495.25 327.84 47243 +1946 102 17.67 11.67 16.02 0 448.04 334.63 47441 +1946 103 15.63 9.63 13.98 0 398.43 341.57 47638 +1946 104 17.69 11.69 16.04 0 448.55 338.14 47834 +1946 105 17.82 11.82 16.17 0 451.88 339.53 48030 +1946 106 19.35 13.35 17.7 0 492.75 336.76 48225 +1946 107 23.26 17.26 21.61 0 611.72 325.26 48419 +1946 108 19.86 13.86 18.21 0 507.05 338.5 48612 +1946 109 16.05 10.05 14.4 0 408.24 350.66 48804 +1946 110 14.24 8.24 12.59 0 367.38 356.33 48995 +1946 111 13.82 7.82 12.17 0 358.42 358.81 49185 +1946 112 15.84 9.84 14.19 0 403.31 355.59 49374 +1946 113 17.14 11.14 15.49 0 434.67 353.55 49561 +1946 114 15.64 9.64 13.99 0 398.66 358.89 49748 +1946 115 14.85 8.85 13.2 0 380.74 362.21 49933 +1946 116 15.97 9.97 14.32 0 406.36 360.68 50117 +1946 117 12.86 6.86 11.21 0 338.63 369.18 50300 +1946 118 11.52 5.52 9.87 0 312.57 373.22 50481 +1946 119 10.06 4.06 8.41 0 286.15 377.15 50661 +1946 120 12.82 6.82 11.17 0 337.82 372.96 50840 +1946 121 16.21 10.21 14.56 0 412.03 366.11 51016 +1946 122 17.54 11.54 15.89 0 444.72 363.69 51191 +1946 123 17.55 11.55 15.9 0 444.98 364.68 51365 +1946 124 17.14 11.14 15.49 0 434.67 366.89 51536 +1946 125 21.78 15.78 20.13 0.15 564.11 264.85 51706 +1946 126 24.12 18.12 22.47 0.53 640.93 258.78 51874 +1946 127 23.28 17.28 21.63 0.07 612.39 261.95 52039 +1946 128 21.94 15.94 20.29 0.78 569.1 266.48 52203 +1946 129 22.25 16.25 20.6 0.57 578.87 266.23 52365 +1946 130 22.32 16.32 20.67 0 581.1 355.47 52524 +1946 131 20.94 14.94 19.29 0 538.51 361.23 52681 +1946 132 20.88 14.88 19.23 0 536.72 362.24 52836 +1946 133 26.35 20.35 24.7 0 722.21 340.66 52989 +1946 134 20.51 14.51 18.86 0.08 525.79 273.67 53138 +1946 135 19.02 13.02 17.37 0.07 483.68 277.84 53286 +1946 136 16.44 10.44 14.79 0 417.53 378.61 53430 +1946 137 16.6 10.6 14.95 0 421.4 378.88 53572 +1946 138 17.77 11.77 16.12 0 450.6 376.17 53711 +1946 139 17.14 11.14 15.49 0 434.67 378.67 53848 +1946 140 16.85 10.85 15.2 0 427.5 379.97 53981 +1946 141 19.36 13.36 17.71 0 493.03 372.87 54111 +1946 142 21.54 15.54 19.89 0 556.69 365.87 54238 +1946 143 22.35 16.35 20.7 0 582.06 363.36 54362 +1946 144 24.56 18.56 22.91 0 656.32 354.82 54483 +1946 145 20.73 14.73 19.08 0 532.26 370.22 54600 +1946 146 18.51 12.51 16.86 0.1 469.94 283.41 54714 +1946 147 16.16 10.16 14.51 0 410.84 385.14 54824 +1946 148 20.88 14.88 19.23 0.05 536.72 278.18 54931 +1946 149 18.82 12.82 17.17 0.66 478.25 283.57 55034 +1946 150 18.81 12.81 17.16 2.14 477.98 283.84 55134 +1946 151 18.5 12.5 16.85 0.65 469.67 284.85 55229 +1946 152 19.37 13.37 17.72 0 493.3 377.16 55321 +1946 153 23.55 17.55 21.9 0.32 621.44 271.53 55409 +1946 154 24.18 18.18 22.53 0.35 643.01 269.78 55492 +1946 155 23.22 17.22 21.57 0.02 610.39 272.91 55572 +1946 156 23.22 17.22 21.57 0 610.39 364.2 55648 +1946 157 20.59 14.59 18.94 0.2 528.14 280.7 55719 +1946 158 21.41 15.41 19.76 0.09 552.71 278.63 55786 +1946 159 24.64 18.64 22.99 0 659.15 358.78 55849 +1946 160 24.5 18.5 22.85 0.05 654.2 269.68 55908 +1946 161 25.82 19.82 24.17 0.11 702.14 265.25 55962 +1946 162 21.43 15.43 19.78 0 553.32 371.98 56011 +1946 163 22.89 16.89 21.24 0 599.51 366.6 56056 +1946 164 21.2 15.2 19.55 0 546.32 373.07 56097 +1946 165 19.43 13.43 17.78 0 494.97 379.27 56133 +1946 166 21.42 15.42 19.77 0 553.01 372.44 56165 +1946 167 20.52 14.52 18.87 0.8 526.08 281.71 56192 +1946 168 19.76 13.76 18.11 0.11 504.22 283.71 56214 +1946 169 20.68 14.68 19.03 0.15 530.79 281.35 56231 +1946 170 19.69 13.69 18.04 0 502.24 378.53 56244 +1946 171 18.11 12.11 16.46 0 459.4 383.62 56252 +1946 172 21.41 15.41 19.76 0 552.71 372.56 56256 +1946 173 22.49 16.49 20.84 0 586.54 368.46 56255 +1946 174 24.74 18.74 23.09 0.1 662.71 269.28 56249 +1946 175 23.25 17.25 21.6 2.31 611.39 273.99 56238 +1946 176 24.31 18.31 22.66 0.58 647.54 270.64 56223 +1946 177 22.3 16.3 20.65 0.56 580.46 276.71 56203 +1946 178 19.47 13.47 17.82 0 496.08 379.06 56179 +1946 179 17.66 11.66 16.01 0.86 447.78 288.45 56150 +1946 180 19.18 13.18 17.53 0 488.06 379.78 56116 +1946 181 14.05 8.05 12.4 0 363.3 394.03 56078 +1946 182 18.28 12.28 16.63 0 463.85 382.4 56035 +1946 183 23.25 17.25 21.6 0 611.39 364.61 55987 +1946 184 25.48 19.48 23.83 0.11 689.52 266.12 55935 +1946 185 26.22 20.22 24.57 0.22 717.24 263.47 55879 +1946 186 30.17 24.17 28.52 0 881.7 330.05 55818 +1946 187 28.91 22.91 27.26 0 826.1 337.06 55753 +1946 188 31.12 25.12 29.47 0.78 925.67 242.93 55684 +1946 189 31.01 25.01 29.36 0 920.49 324.43 55611 +1946 190 33.1 27.1 31.45 0 1023.28 310.53 55533 +1946 191 31.47 25.47 29.82 0 942.33 320.99 55451 +1946 192 29.49 23.49 27.84 0.58 851.31 249.4 55366 +1946 193 27.62 21.62 25.97 2.55 772.27 256.78 55276 +1946 194 25.21 19.21 23.56 0.42 679.63 265.31 55182 +1946 195 24.87 18.87 23.22 0.09 667.35 266.25 55085 +1946 196 23.14 17.14 21.49 0 607.74 361.88 54984 +1946 197 19.95 13.95 18.3 0.55 509.61 279.85 54879 +1946 198 17.53 11.53 15.88 0.04 444.47 285.2 54770 +1946 199 17.23 11.23 15.58 0.48 436.91 285.58 54658 +1946 200 20 14 18.35 0.18 511.04 278.84 54542 +1946 201 22.61 16.61 20.96 0.07 590.41 271.43 54423 +1946 202 21.82 15.82 20.17 0.09 565.35 273.26 54301 +1946 203 22.85 16.85 21.2 0 598.2 359.92 54176 +1946 204 22.07 16.07 20.42 0 573.18 362.41 54047 +1946 205 20.58 14.58 18.93 0.01 527.84 275.44 53915 +1946 206 26.05 20.05 24.4 0 710.79 344.69 53780 +1946 207 27.2 21.2 25.55 0 755.4 338.54 53643 +1946 208 27.4 21.4 25.75 0 763.4 336.93 53502 +1946 209 24.14 18.14 22.49 0.22 641.62 263.42 53359 +1946 210 20.76 14.76 19.11 0 533.15 363.49 53213 +1946 211 18.57 12.57 16.92 0 471.54 369.82 53064 +1946 212 19.61 13.61 17.96 0 500 365.76 52913 +1946 213 19.88 13.88 18.23 0 507.62 364.12 52760 +1946 214 24.26 18.26 22.61 0 645.79 347.14 52604 +1946 215 23.77 17.77 22.12 0 628.9 348.5 52445 +1946 216 26.78 20.78 25.13 0 738.84 334.26 52285 +1946 217 28.59 22.59 26.94 0.08 812.46 243.27 52122 +1946 218 26.16 20.16 24.51 2.67 714.96 251.66 51958 +1946 219 27.13 21.13 25.48 0.25 752.62 247.49 51791 +1946 220 22.66 16.66 21.01 1.18 592.02 261.19 51622 +1946 221 20.4 14.4 18.75 0.03 522.58 266.45 51451 +1946 222 20.37 14.37 18.72 0.36 521.7 265.75 51279 +1946 223 23.14 17.14 21.49 0.32 607.74 257.47 51105 +1946 224 22.26 16.26 20.61 0.1 579.19 259.18 50929 +1946 225 26.51 20.51 24.86 0.13 728.36 245.21 50751 +1946 226 26.36 20.36 24.71 0.51 722.59 244.91 50572 +1946 227 22.68 16.68 21.03 0.17 592.67 255.39 50392 +1946 228 22.66 16.66 21.01 0 592.02 339.4 50210 +1946 229 25.25 19.25 23.6 0 681.09 327.9 50026 +1946 230 23.42 17.42 21.77 0.74 617.07 250.57 49842 +1946 231 24.81 18.81 23.16 0 665.2 327.12 49656 +1946 232 21.21 15.21 19.56 0 546.63 339.29 49469 +1946 233 18.96 12.96 17.31 0 482.04 345 49280 +1946 234 16.25 10.25 14.6 0.06 412.98 263.24 49091 +1946 235 20.35 14.35 18.7 0.13 521.12 253.37 48900 +1946 236 21.22 15.22 19.57 0 546.93 333.58 48709 +1946 237 24.96 18.96 23.31 0 670.58 318.14 48516 +1946 238 27.04 21.04 25.39 0 749.06 307.57 48323 +1946 239 29.01 23.01 27.36 0 830.4 296.72 48128 +1946 240 29.88 23.88 28.23 0 868.63 290.64 47933 +1946 241 28.63 22.63 26.98 0 814.16 295.43 47737 +1946 242 27.6 21.6 25.95 0.32 771.46 224.06 47541 +1946 243 27 21 25.35 0 747.48 299.74 47343 +1946 244 19.53 13.53 17.88 0.04 497.76 243.96 47145 +1946 245 19.75 13.75 18.1 0 503.94 322.81 46947 +1946 246 24.98 18.98 23.33 0.02 671.3 227.2 46747 +1946 247 22.99 16.99 21.34 0 602.79 308.59 46547 +1946 248 22.1 16.1 20.45 0 574.13 309.76 46347 +1946 249 23.34 17.34 21.69 0.05 614.39 227.62 46146 +1946 250 21.15 15.15 19.5 0 544.81 308.93 45945 +1946 251 18.83 12.83 17.18 0.93 478.52 235.23 45743 +1946 252 17.41 11.41 15.76 0.86 441.43 236.4 45541 +1946 253 19.92 13.92 18.27 0 508.76 306.35 45339 +1946 254 20.03 14.03 18.38 0 511.9 303.94 45136 +1946 255 18.4 12.4 16.75 0 467.02 306.18 44933 +1946 256 18.82 12.82 17.17 0 478.25 302.83 44730 +1946 257 20.78 14.78 19.13 0 533.75 295.21 44527 +1946 258 17.35 11.35 15.7 0 439.92 302.08 44323 +1946 259 22.96 16.96 21.31 0 601.8 283.77 44119 +1946 260 22.74 16.74 21.09 0 594.62 282.21 43915 +1946 261 23.36 17.36 21.71 0.06 615.06 208.37 43711 +1946 262 22.74 16.74 21.09 0.43 594.62 208.2 43507 +1946 263 22.27 16.27 20.62 0.04 579.51 207.54 43303 +1946 264 22.03 16.03 20.38 0.05 571.92 206.24 43099 +1946 265 22.03 16.03 20.38 0.03 571.92 204.54 42894 +1946 266 18.83 12.83 17.18 0.08 478.52 209.35 42690 +1946 267 20.13 14.13 18.48 0.12 514.76 204.86 42486 +1946 268 19.74 13.74 18.09 0 503.65 271.68 42282 +1946 269 19.51 13.51 17.86 0 497.2 269.83 42078 +1946 270 20.48 14.48 18.83 0 524.91 264.73 41875 +1946 271 21.76 15.76 20.11 0 563.48 258.67 41671 +1946 272 21.2 15.2 19.55 0 546.32 257.62 41468 +1946 273 18.45 12.45 16.8 0 468.34 262.14 41265 +1946 274 7.33 1.33 5.68 0.31 241.86 208.77 41062 +1946 275 7.25 1.25 5.6 0.68 240.65 206.7 40860 +1946 276 8.77 2.77 7.12 0.71 264.42 203.24 40658 +1946 277 8.27 2.27 6.62 0 256.39 268.88 40456 +1946 278 9.68 3.68 8.03 0 279.6 264.16 40255 +1946 279 13.47 7.47 11.82 0.27 351.09 191.76 40054 +1946 280 14.39 8.39 12.74 0 370.63 251.47 39854 +1946 281 14.34 8.34 12.69 0 369.54 248.85 39654 +1946 282 14.3 8.3 12.65 0.04 368.68 184.64 39455 +1946 283 12.64 6.64 10.99 0 334.22 246.06 39256 +1946 284 14.57 8.57 12.92 0.08 374.56 179.95 39058 +1946 285 16.08 10.08 14.43 1.14 408.95 175.98 38861 +1946 286 11.68 5.68 10.03 0.34 315.59 179.26 38664 +1946 287 10.42 4.42 8.77 0.02 292.48 178.32 38468 +1946 288 8.6 2.6 6.95 0 261.67 237.15 38273 +1946 289 9.94 3.94 8.29 0.05 284.07 174.67 38079 +1946 290 10.39 4.39 8.74 0 291.95 229.45 37885 +1946 291 14.14 8.14 12.49 0 365.23 221.49 37693 +1946 292 12.62 6.62 10.97 0 333.83 221.08 37501 +1946 293 9.76 3.76 8.11 0.09 280.97 166.52 37311 +1946 294 9.31 3.31 7.66 0 273.34 219.64 37121 +1946 295 5.18 -0.82 3.53 0.11 211.25 165.64 36933 +1946 296 9.39 3.39 7.74 0.86 274.68 160.56 36745 +1946 297 7.67 1.67 6.02 0 247.03 213.14 36560 +1946 298 4.77 -1.23 3.12 0 205.81 213.11 36375 +1946 299 6.93 0.93 5.28 0 235.89 208.39 36191 +1946 300 10.59 4.59 8.94 0.06 295.51 151.42 36009 +1946 301 13.27 7.27 11.62 0 346.96 196.03 35829 +1946 302 10.44 4.44 8.79 1.37 292.83 147.7 35650 +1946 303 10.22 4.22 8.57 0.22 288.95 145.96 35472 +1946 304 10.1 4.1 8.45 0 286.85 192.28 35296 +1946 305 5.01 -0.99 3.36 0 208.98 194.22 35122 +1946 306 7.28 1.28 5.63 0.15 241.11 142.54 34950 +1946 307 6.29 0.29 4.64 0 226.61 188.37 34779 +1946 308 9.73 3.73 8.08 0 280.45 182.58 34610 +1946 309 11.19 5.19 9.54 0 306.42 178.72 34444 +1946 310 10.44 4.44 8.79 0.19 292.83 132.83 34279 +1946 311 5.08 -0.92 3.43 0.51 209.91 134.76 34116 +1946 312 6.77 0.77 5.12 0.42 233.54 131.78 33956 +1946 313 9.94 3.94 8.29 0.04 284.07 128.04 33797 +1946 314 9.19 3.19 7.54 0.46 271.34 127.13 33641 +1946 315 8.32 2.32 6.67 0.27 257.19 125.83 33488 +1946 316 7.12 1.12 5.47 0 238.71 166.59 33337 +1946 317 7.42 1.42 5.77 0.06 243.22 123.12 33188 +1946 318 7.09 1.09 5.44 0.49 238.26 121.56 33042 +1946 319 9.65 3.65 8 0 279.08 158.2 32899 +1946 320 10.07 4.07 8.42 0 286.32 155.96 32758 +1946 321 11.14 5.14 9.49 0 305.5 152.84 32620 +1946 322 7.2 1.2 5.55 0 239.91 154.5 32486 +1946 323 7.5 1.5 5.85 0 244.43 152.65 32354 +1946 324 6.83 0.83 5.18 0 234.42 151.12 32225 +1946 325 7.86 1.86 6.21 0 249.96 148.61 32100 +1946 326 8.23 2.23 6.58 0.05 255.76 110.16 31977 +1946 327 11.15 5.15 9.5 0.08 305.68 106.87 31858 +1946 328 7.67 1.67 6.02 0.17 247.03 107.63 31743 +1946 329 3.7 -2.3 2.05 0.18 192.17 108.5 31631 +1946 330 7.06 1.06 5.41 0.11 237.82 105.78 31522 +1946 331 9.37 3.37 7.72 0.9 274.35 103.46 31417 +1946 332 5.36 -0.64 3.71 0.02 213.68 104.43 31316 +1946 333 2.12 -3.88 0.47 1.64 173.47 105 31218 +1946 334 5.17 -0.83 3.52 0.38 211.12 102.88 31125 +1946 335 -4.82 -10.82 -6.47 0.37 108.68 149.06 31035 +1946 336 1.15 -4.85 -0.5 1.55 162.78 146.47 30949 +1946 337 1.34 -4.66 -0.31 0.94 164.82 145.09 30867 +1946 338 -0.62 -6.62 -2.27 0.03 144.73 145.23 30790 +1946 339 0.97 -5.03 -0.68 0.14 160.86 144.09 30716 +1946 340 0.49 -5.51 -1.16 0 155.83 177.04 30647 +1946 341 1.09 -4.91 -0.56 0 162.13 175.79 30582 +1946 342 1.36 -4.64 -0.29 0 165.04 174.8 30521 +1946 343 1.92 -4.08 0.27 0 171.21 173.53 30465 +1946 344 3.46 -2.54 1.81 0 189.23 128.13 30413 +1946 345 0.71 -5.29 -0.94 0 158.12 129.03 30366 +1946 346 -2.77 -8.77 -4.42 0 125.16 129.84 30323 +1946 347 -3.08 -9.08 -4.73 0.45 122.54 142.02 30284 +1946 348 -3.4 -9.4 -5.05 0 119.88 174.16 30251 +1946 349 1.37 -4.63 -0.28 0 165.15 171.77 30221 +1946 350 0.31 -5.69 -1.34 0.06 153.98 140.15 30197 +1946 351 0.07 -5.93 -1.58 0 151.55 171.8 30177 +1946 352 -2.05 -8.05 -3.7 0.15 131.44 141.13 30162 +1946 353 -2.84 -8.84 -4.49 0 124.56 173.25 30151 +1946 354 -0.45 -6.45 -2.1 0 146.39 172.34 30145 +1946 355 -0.53 -6.53 -2.18 0.22 145.6 141.34 30144 +1946 356 -1.49 -7.49 -3.14 0 136.51 173.46 30147 +1946 357 -0.06 -6.06 -1.71 0 150.24 172.95 30156 +1946 358 3.23 -2.77 1.58 0 186.44 171.06 30169 +1946 359 5.23 -0.77 3.58 0.64 211.92 138.26 30186 +1946 360 2 -4 0.35 0.08 172.11 139.52 30208 +1946 361 5.51 -0.49 3.86 0.01 215.72 137.58 30235 +1946 362 5.27 -0.73 3.62 0.22 212.46 94.12 30267 +1946 363 5.16 -0.84 3.51 0.61 210.98 94.61 30303 +1946 364 1.98 -4.02 0.33 0 171.89 128.23 30343 +1946 365 0.39 -5.61 -1.26 0.14 154.8 97.15 30388 +1947 1 -3.6 -9.6 -5.25 0 118.24 131.94 30438 +1947 2 -3.6 -9.6 -5.25 0.34 118.24 143.87 30492 +1947 3 -3.6 -9.6 -5.25 0 118.24 177.91 30551 +1947 4 -3.6 -9.6 -5.25 0 118.24 178.75 30614 +1947 5 -3.6 -9.6 -5.25 0 118.24 179.32 30681 +1947 6 -3.6 -9.6 -5.25 0.3 118.24 147.02 30752 +1947 7 -3.6 -9.6 -5.25 0.12 118.24 147.89 30828 +1947 8 -3.6 -9.6 -5.25 0.28 118.24 149.77 30907 +1947 9 -3.6 -9.6 -5.25 0.22 118.24 151.29 30991 +1947 10 -3.6 -9.6 -5.25 0 118.24 187.4 31079 +1947 11 -3.6 -9.6 -5.25 0 118.24 188.27 31171 +1947 12 -3.6 -9.6 -5.25 0 118.24 189.16 31266 +1947 13 -3.6 -9.6 -5.25 0.54 118.24 156.13 31366 +1947 14 -3.6 -9.6 -5.25 0.19 118.24 157.68 31469 +1947 15 -3.6 -9.6 -5.25 0 118.24 195.54 31575 +1947 16 -3.6 -9.6 -5.25 0 118.24 196.68 31686 +1947 17 -3.6 -9.6 -5.25 0.24 118.24 161.27 31800 +1947 18 -3.6 -9.6 -5.25 0.52 118.24 164.1 31917 +1947 19 -3.6 -9.6 -5.25 0 118.24 204.03 32038 +1947 20 -3.6 -9.6 -5.25 0.25 118.24 167.15 32161 +1947 21 -3.6 -9.6 -5.25 0 118.24 208.03 32289 +1947 22 -3.6 -9.6 -5.25 0 118.24 209.61 32419 +1947 23 -3.6 -9.6 -5.25 0.05 118.24 170.9 32552 +1947 24 -3.6 -9.6 -5.25 0.61 118.24 174.06 32688 +1947 25 -3.6 -9.6 -5.25 0 118.24 216.74 32827 +1947 26 -3.6 -9.6 -5.25 0 118.24 218.48 32969 +1947 27 -3.6 -9.6 -5.25 0.04 118.24 177.97 33114 +1947 28 -3.6 -9.6 -5.25 0 118.24 222.45 33261 +1947 29 -3.6 -9.6 -5.25 0 118.24 224.64 33411 +1947 30 -3.6 -9.6 -5.25 0 118.24 226.69 33564 +1947 31 -3.6 -9.6 -5.25 0 118.24 228.87 33718 +1947 32 1.03 -4.97 -0.62 0.25 161.49 183.66 33875 +1947 33 -0.05 -6.05 -1.7 0.13 150.34 186.22 34035 +1947 34 -0.11 -6.11 -1.76 0.65 149.74 189.51 34196 +1947 35 -0.24 -6.24 -1.89 0.57 148.45 192.54 34360 +1947 36 -0.91 -6.91 -2.56 1.62 141.95 198.96 34526 +1947 37 -1.12 -7.12 -2.77 0.57 139.96 202.19 34694 +1947 38 -4.56 -10.56 -6.21 0.94 110.66 207.75 34863 +1947 39 -3.67 -9.67 -5.32 0.35 117.67 210.12 35035 +1947 40 -4.24 -10.24 -5.89 0.1 113.14 212.27 35208 +1947 41 -2.96 -8.96 -4.61 0 123.55 264.53 35383 +1947 42 -4.1 -10.1 -5.75 0.04 114.24 215.69 35560 +1947 43 -3.72 -9.72 -5.37 0.57 117.27 218.86 35738 +1947 44 -6.75 -12.75 -8.4 0 94.91 274.8 35918 +1947 45 -5.35 -11.35 -7 0 104.73 276.63 36099 +1947 46 -4.92 -10.92 -6.57 0.03 107.92 224.43 36282 +1947 47 -3.36 -9.36 -5.01 0 120.21 280.84 36466 +1947 48 -2.14 -8.14 -3.79 0.45 130.64 228.31 36652 +1947 49 -1.17 -7.17 -2.82 0.92 139.49 232.11 36838 +1947 50 0.4 -5.6 -1.25 1.41 154.91 233.07 37026 +1947 51 1.8 -4.2 0.15 1.25 169.87 234.1 37215 +1947 52 -1.04 -7.04 -2.69 0.08 140.71 237.5 37405 +1947 53 -0.24 -6.24 -1.89 0 148.45 298.06 37596 +1947 54 0.03 -5.97 -1.62 0 151.15 300.36 37788 +1947 55 2.45 -3.55 0.8 0.16 177.24 241.15 37981 +1947 56 2.83 -3.17 1.18 0.43 181.67 242.36 38175 +1947 57 7.23 1.23 5.58 0.67 240.35 240.44 38370 +1947 58 2.86 -3.14 1.21 0.89 182.02 245.07 38565 +1947 59 3.78 -2.22 2.13 0.1 193.17 245.85 38761 +1947 60 7.12 1.12 5.47 0.69 238.71 244.57 38958 +1947 61 8.72 2.72 7.07 0 263.61 306.93 39156 +1947 62 8.53 2.53 6.88 0.01 260.54 245.3 39355 +1947 63 8.11 2.11 6.46 0 253.87 311.16 39553 +1947 64 10.44 4.44 8.79 0 292.83 309.75 39753 +1947 65 9.36 3.36 7.71 0 274.18 312.84 39953 +1947 66 9.81 3.81 8.16 0 281.82 313.72 40154 +1947 67 10.19 4.19 8.54 0 288.42 314.81 40355 +1947 68 9.93 3.93 8.28 0.33 283.89 249.47 40556 +1947 69 13.42 7.42 11.77 0.3 350.05 245.83 40758 +1947 70 12.73 6.73 11.08 0.09 336.02 247.3 40960 +1947 71 6.92 0.92 5.27 0 235.74 324.99 41163 +1947 72 8.33 2.33 6.68 0 257.34 325.07 41366 +1947 73 10.82 4.82 9.17 0.05 299.65 252.59 41569 +1947 74 8.31 2.31 6.66 0 257.03 328.24 41772 +1947 75 6.92 0.92 5.27 0.11 235.74 258.74 41976 +1947 76 6.3 0.3 4.65 0.73 226.75 260.48 42179 +1947 77 4.47 -1.53 2.82 0.4 201.91 263.33 42383 +1947 78 0.74 -5.26 -0.91 0 158.43 344.31 42587 +1947 79 -0.73 -6.73 -2.38 0 143.67 348.06 42791 +1947 80 2 -4 0.35 0 172.11 348.06 42996 +1947 81 2.93 -3.07 1.28 0 182.85 349.37 43200 +1947 82 8.44 2.44 6.79 0 259.1 344.72 43404 +1947 83 8.74 2.74 7.09 0.1 263.94 268.08 43608 +1947 84 12.41 6.41 10.76 0.04 329.68 264.29 43812 +1947 85 12.44 6.44 10.79 0.48 330.27 264.81 44016 +1947 86 12.18 6.18 10.53 0 325.18 343.91 44220 +1947 87 15.84 9.84 14.19 0 403.31 308.1 44424 +1947 88 11.66 5.66 10.01 0 315.21 318.66 44627 +1947 89 9.95 3.95 8.3 0.1 284.24 242.82 44831 +1947 90 11.77 5.77 10.12 0.44 317.3 242.31 45034 +1947 91 17.33 11.33 15.68 0.26 439.42 235.17 45237 +1947 92 15.95 9.95 14.3 0.55 405.89 239.27 45439 +1947 93 12.06 6.06 10.41 0.5 322.85 246.92 45642 +1947 94 11.85 5.85 10.2 0.05 318.82 248.81 45843 +1947 95 9.46 3.46 7.81 0.07 275.86 253.45 46045 +1947 96 11.66 5.66 10.01 0.68 315.21 252.25 46246 +1947 97 14.81 8.81 13.16 0 379.85 332.05 46446 +1947 98 16.56 10.56 14.91 0.07 420.43 247.42 46647 +1947 99 12.35 6.35 10.7 0 328.5 341.05 46846 +1947 100 10.47 4.47 8.82 0.06 293.37 259.8 47045 +1947 101 13.57 7.57 11.92 0 353.17 342.46 47243 +1947 102 10.97 4.97 9.32 0.08 302.38 262.03 47441 +1947 103 14.04 8.04 12.39 0.01 363.09 258.88 47638 +1947 104 16.67 10.67 15.02 0 423.1 340.8 47834 +1947 105 18.47 12.47 16.82 0 468.88 337.73 48030 +1947 106 19.81 13.81 18.16 0 505.63 335.37 48225 +1947 107 16.37 10.37 14.72 0.24 415.85 259.92 48419 +1947 108 19.28 13.28 17.63 0 490.81 340.26 48612 +1947 109 20.38 14.38 18.73 0 522 338.4 48804 +1947 110 21.94 15.94 20.29 0 569.1 334.51 48995 +1947 111 19.23 13.23 17.58 0 489.43 344.82 49185 +1947 112 19 13 17.35 0 483.13 346.98 49374 +1947 113 18.19 12.19 16.54 0.16 461.49 262.98 49561 +1947 114 15.11 9.11 13.46 0.03 386.56 270.13 49748 +1947 115 19.67 13.67 18.02 0.1 501.68 261.79 49933 +1947 116 19.53 13.53 17.88 0.44 497.76 263 50117 +1947 117 15.42 9.42 13.77 0 393.6 363.35 50300 +1947 118 13.03 7.03 11.38 0 342.06 370.14 50481 +1947 119 11.25 5.25 9.6 0 307.53 374.95 50661 +1947 120 10.94 4.94 9.29 0 301.83 376.73 50840 +1947 121 17.7 11.7 16.05 0 448.8 362.07 51016 +1947 122 19.2 13.2 17.55 0 488.61 358.79 51191 +1947 123 21.67 15.67 20.02 0 560.7 351.55 51365 +1947 124 23.2 17.2 21.55 0 609.73 346.86 51536 +1947 125 20.81 14.81 19.16 0 534.64 356.54 51706 +1947 126 19.44 13.44 17.79 0 495.25 362.02 51874 +1947 127 20.2 14.2 18.55 0 516.78 360.42 52039 +1947 128 18.9 12.9 17.25 0 480.41 365.55 52203 +1947 129 22.26 16.26 20.61 0.25 579.19 266.21 52365 +1947 130 19.72 13.72 18.07 0 503.09 364.56 52524 +1947 131 20.42 14.42 18.77 0 523.16 363.02 52681 +1947 132 20.3 14.3 18.65 0.06 519.67 273.17 52836 +1947 133 17.82 11.82 16.17 0.66 451.88 279.52 52989 +1947 134 14.63 8.63 12.98 0.18 375.88 286.44 53138 +1947 135 14.33 8.33 12.68 0 369.33 383.34 53286 +1947 136 16.16 10.16 14.51 0.14 410.84 284.52 53430 +1947 137 16.55 10.55 14.9 0 420.19 379.02 53572 +1947 138 14.91 8.91 13.26 0 382.08 383.89 53711 +1947 139 11.35 5.35 9.7 0 309.39 392.54 53848 +1947 140 14.12 8.12 12.47 0.49 364.8 290.24 53981 +1947 141 18.13 12.13 16.48 0 459.92 376.7 54111 +1947 142 16 10 14.35 0 407.06 383.22 54238 +1947 143 17.65 11.65 16 0 447.52 379.15 54362 +1947 144 22.46 16.46 20.81 0.72 585.58 272.55 54483 +1947 145 26.01 20.01 24.36 0 709.28 348.73 54600 +1947 146 21.27 15.27 19.62 0.27 548.44 276.5 54714 +1947 147 19.01 13.01 17.36 0.03 483.41 282.6 54824 +1947 148 20.6 14.6 18.95 0 528.43 371.88 54931 +1947 149 19.14 13.14 17.49 1.96 486.96 282.8 55034 +1947 150 16.13 10.13 14.48 0.95 410.13 289.7 55134 +1947 151 17.27 11.27 15.62 0.42 437.91 287.61 55229 +1947 152 19.85 13.85 18.2 1.45 506.77 281.68 55321 +1947 153 17.85 11.85 16.2 0.57 452.65 286.6 55409 +1947 154 21.75 15.75 20.1 0.66 563.17 277.06 55492 +1947 155 23.37 17.37 21.72 0 615.39 363.27 55572 +1947 156 20.08 14.08 18.43 0 513.33 375.86 55648 +1947 157 22.03 16.03 20.38 0 571.92 369.03 55719 +1947 158 23.14 17.14 21.49 0 607.74 364.86 55786 +1947 159 22.05 16.05 20.4 0 572.55 369.36 55849 +1947 160 21.31 15.31 19.66 0.08 549.66 279.22 55908 +1947 161 18.22 12.22 16.57 0.16 462.28 287.02 55962 +1947 162 19.75 13.75 18.1 0 503.94 377.86 56011 +1947 163 18.57 12.57 16.92 0 471.54 381.88 56056 +1947 164 21.23 15.23 19.58 0 547.23 372.96 56097 +1947 165 22.92 16.92 21.27 0 600.49 366.62 56133 +1947 166 20.7 14.7 19.05 0.01 531.38 281.28 56165 +1947 167 23.88 17.88 22.23 0.53 632.66 272.03 56192 +1947 168 22.08 16.08 20.43 0.76 573.49 277.5 56214 +1947 169 26.25 20.25 24.6 0.44 718.38 264.1 56231 +1947 170 26.11 20.11 24.46 0.28 713.06 264.6 56244 +1947 171 27.79 21.79 26.14 0.84 779.19 258.37 56252 +1947 172 26.73 20.73 25.08 0.6 736.89 262.39 56256 +1947 173 25.31 19.31 23.66 0.3 683.28 267.42 56255 +1947 174 26.06 20.06 24.41 0.4 711.17 264.74 56249 +1947 175 23.47 17.47 21.82 0 618.75 364.42 56238 +1947 176 24.17 18.17 22.52 0 642.66 361.45 56223 +1947 177 24.02 18.02 22.37 0.24 637.47 271.49 56203 +1947 178 20.99 14.99 19.34 0 540 373.85 56179 +1947 179 22.5 16.5 20.85 0 586.86 368.1 56150 +1947 180 19.91 13.91 18.26 0.51 508.47 283.03 56116 +1947 181 20.26 14.26 18.61 0.39 518.51 282.08 56078 +1947 182 23.89 17.89 22.24 0 633 362.14 56035 +1947 183 28.84 22.84 27.19 0 823.1 338.07 55987 +1947 184 27.63 21.63 25.98 0.05 772.68 258.28 55935 +1947 185 24.13 18.13 22.48 0 641.27 360.72 55879 +1947 186 22.73 16.73 21.08 0 594.29 366.21 55818 +1947 187 24.77 18.77 23.12 0 663.78 357.52 55753 +1947 188 27.39 21.39 25.74 0.21 763 258.64 55684 +1947 189 28.21 22.21 26.56 0.01 796.51 255.32 55611 +1947 190 31.6 25.6 29.95 0 948.58 320.4 55533 +1947 191 31.56 25.56 29.91 0.22 946.66 240.31 55451 +1947 192 30.31 24.31 28.66 0.19 888.07 245.84 55366 +1947 193 30.04 24.04 28.39 0.13 875.82 246.85 55276 +1947 194 28.77 22.77 27.12 0 820.11 336.09 55182 +1947 195 28.13 22.13 26.48 0.69 793.19 254.45 55085 +1947 196 23.54 17.54 21.89 0 621.1 360.26 54984 +1947 197 21.58 15.58 19.93 0 557.92 367.42 54879 +1947 198 23.01 17.01 21.36 0.01 603.45 271.15 54770 +1947 199 24.4 18.4 22.75 0.13 650.69 266.59 54658 +1947 200 19.76 13.76 18.11 0.03 504.22 279.44 54542 +1947 201 18.24 12.24 16.59 1.3 462.8 282.69 54423 +1947 202 17.56 11.56 15.91 1.88 445.23 283.77 54301 +1947 203 19.29 13.29 17.64 0 491.09 372.57 54176 +1947 204 15.68 9.68 14.03 0.21 399.59 286.86 54047 +1947 205 18.69 12.69 17.04 0.46 474.75 280.06 53915 +1947 206 22.48 16.48 20.83 0 586.22 359.79 53780 +1947 207 20.59 14.59 18.94 0 528.14 366 53643 +1947 208 22.82 16.82 21.17 0.01 597.22 267.89 53502 +1947 209 22.51 16.51 20.86 0 587.18 357.74 53359 +1947 210 22.6 16.6 20.95 0 590.08 356.79 53213 +1947 211 23.33 17.33 21.68 0.14 614.06 264.88 53064 +1947 212 14.79 8.79 13.14 1.87 379.41 284.5 52913 +1947 213 13.57 7.57 11.92 0.25 353.17 286.05 52760 +1947 214 16.34 10.34 14.69 0 415.13 373.83 52604 +1947 215 16.79 10.79 15.14 0.56 426.03 278.94 52445 +1947 216 17.82 11.82 16.17 0 451.88 368 52285 +1947 217 23.27 17.27 21.62 0 612.06 348.64 52122 +1947 218 23.23 17.23 21.58 0 610.73 348 51958 +1947 219 25.49 19.49 23.84 0 689.89 337.57 51791 +1947 220 24.91 18.91 23.26 0 668.79 339.2 51622 +1947 221 22.99 16.99 21.34 0 602.79 346.01 51451 +1947 222 22.12 16.12 20.47 0 574.76 348.24 51279 +1947 223 22.75 16.75 21.1 0.04 594.94 258.59 51105 +1947 224 22.54 16.54 20.89 0 588.15 344.53 50929 +1947 225 22.61 16.61 20.96 0 590.41 343.15 50751 +1947 226 20.8 14.8 19.15 0 534.34 348.43 50572 +1947 227 22.45 16.45 20.8 0 585.26 341.37 50392 +1947 228 22.67 16.67 21.02 0 592.35 339.37 50210 +1947 229 25.67 19.67 24.02 0 696.55 326.09 50026 +1947 230 24.22 18.22 22.57 0 644.4 330.95 49842 +1947 231 24.89 18.89 23.24 0 668.07 326.79 49656 +1947 232 28.08 22.08 26.43 0 791.12 311.07 49469 +1947 233 28.74 22.74 27.09 0 818.83 306.46 49280 +1947 234 24.04 18.04 22.39 0 638.16 326.2 49091 +1947 235 29.22 23.22 27.57 0 839.5 301.34 48900 +1947 236 27.71 21.71 26.06 0 775.93 307.54 48709 +1947 237 26.52 20.52 24.87 0 728.75 311.48 48516 +1947 238 27.68 21.68 26.03 0 774.71 304.6 48323 +1947 239 27.73 21.73 26.08 0 776.75 302.97 48128 +1947 240 24.96 18.96 23.31 0.78 670.58 235.07 47933 +1947 241 22.66 16.66 21.01 0 592.02 320.49 47737 +1947 242 19.13 13.13 17.48 0 486.69 330.12 47541 +1947 243 21.38 15.38 19.73 0 551.79 321.34 47343 +1947 244 18.96 12.96 17.31 0 482.04 326.93 47145 +1947 245 16.93 10.93 15.28 0 429.47 330.52 46947 +1947 246 17.22 11.22 15.57 0 436.66 327.8 46747 +1947 247 19.89 13.89 18.24 0 507.9 318.61 46547 +1947 248 20.32 14.32 18.67 0.83 520.25 236.56 46347 +1947 249 22.53 16.53 20.88 0 587.83 306.31 46146 +1947 250 23.14 17.14 21.49 0 607.74 302.33 45945 +1947 251 19.41 13.41 17.76 0 494.41 312.03 45743 +1947 252 22.32 16.32 20.67 0 581.1 301 45541 +1947 253 26.17 20.17 24.52 0 715.34 284.81 45339 +1947 254 24.11 18.11 22.46 0 640.58 290.72 45136 +1947 255 21.54 15.54 19.89 0 556.69 297.2 44933 +1947 256 18.81 12.81 17.16 0 477.98 302.85 44730 +1947 257 24.58 18.58 22.93 0 657.03 282.68 44527 +1947 258 24.94 18.94 23.29 0 669.86 279.15 44323 +1947 259 25.96 19.96 24.31 0 707.39 273 44119 +1947 260 23.2 17.2 21.55 0 609.73 280.7 43915 +1947 261 20.49 14.49 18.84 0 525.2 286.68 43711 +1947 262 20.45 14.45 18.8 0 524.04 284.48 43507 +1947 263 19.82 13.82 18.17 0 505.92 283.82 43303 +1947 264 21.85 15.85 20.2 0 566.28 275.53 43099 +1947 265 25.65 19.65 24 0 695.8 260.6 42894 +1947 266 23.35 17.35 21.7 0 614.73 266.23 42690 +1947 267 21.12 15.12 19.47 0 543.91 270.42 42486 +1947 268 23.69 17.69 22.04 0 626.18 260.17 42282 +1947 269 26.37 20.37 24.72 0 722.97 248.49 42078 +1947 270 24.89 18.89 23.24 0 668.07 251.34 41875 +1947 271 26.72 20.72 25.07 0.04 736.5 181.77 41671 +1947 272 24.04 18.04 22.39 0 638.16 249.16 41468 +1947 273 25.16 19.16 23.51 0 677.81 243.11 41265 +1947 274 15.22 9.22 13.57 0 389.05 266.34 41062 +1947 275 13.32 7.32 11.67 0 347.99 267 40860 +1947 276 15.28 9.28 13.63 0 390.41 260.79 40658 +1947 277 15.78 9.78 14.13 0 401.91 257.19 40456 +1947 278 20.25 14.25 18.6 0 518.22 244.54 40255 +1947 279 19.14 13.14 17.49 0.05 486.96 183.37 40054 +1947 280 13.35 7.35 11.7 0 348.61 253.23 39854 +1947 281 18.63 12.63 16.98 0 473.14 240.45 39654 +1947 282 17.58 11.58 15.93 0 445.74 240.03 39455 +1947 283 13.14 7.14 11.49 0.01 344.3 183.96 39256 +1947 284 8.92 2.92 7.27 0 266.88 248.07 39058 +1947 285 10.58 4.58 8.93 0 295.33 243.3 38861 +1947 286 9.8 3.8 8.15 0 281.65 241.51 38664 +1947 287 5.11 -0.89 3.46 0 210.31 243.58 38468 +1947 288 7.64 1.64 5.99 0 246.57 238.21 38273 +1947 289 7.05 1.05 5.4 0 237.67 236.15 38079 +1947 290 5.38 -0.62 3.73 0.11 213.95 176.13 37885 +1947 291 7.05 1.05 5.4 0 237.67 230.48 37693 +1947 292 8.2 2.2 6.55 0 255.28 226.55 37501 +1947 293 11.56 5.56 9.91 0.33 313.32 164.84 37311 +1947 294 7.62 1.62 5.97 0.24 246.26 166.09 37121 +1947 295 11.97 5.97 10.32 0 321.12 213.54 36933 +1947 296 13.55 7.55 11.9 0 352.75 208.78 36745 +1947 297 14.55 8.55 12.9 0.01 374.12 153.46 36560 +1947 298 15.68 9.68 14.03 0.01 399.59 150.22 36375 +1947 299 14.95 8.95 13.3 0 382.97 198.71 36191 +1947 300 11.74 5.74 10.09 0.08 316.72 150.39 36009 +1947 301 9.6 3.6 7.95 0 278.23 200.48 35829 +1947 302 8.42 2.42 6.77 0.71 258.78 149.31 35650 +1947 303 8.77 2.77 7.12 0.17 264.42 147.1 35472 +1947 304 12.39 6.39 10.74 0 329.28 189.61 35296 +1947 305 9.82 3.82 8.17 0.74 282 142.38 35122 +1947 306 10.05 4.05 8.4 0 285.98 187.35 34950 +1947 307 7.06 1.06 5.41 0 237.82 187.71 34779 +1947 308 8.18 2.18 6.53 0.01 254.97 138.07 34610 +1947 309 8.13 2.13 6.48 0 254.18 181.81 34444 +1947 310 6.46 0.46 4.81 0 229.04 180.8 34279 +1947 311 7.03 1.03 5.38 0.36 237.37 133.6 34116 +1947 312 6.97 0.97 5.32 0.23 236.48 131.65 33956 +1947 313 8.28 2.28 6.63 0 256.55 172.28 33797 +1947 314 8.43 2.43 6.78 0 258.94 170.2 33641 +1947 315 8.34 2.34 6.69 0 257.5 167.75 33488 +1947 316 6.79 0.79 5.14 0 233.83 166.86 33337 +1947 317 9.13 3.13 7.48 0 270.34 162.68 33188 +1947 318 6.25 0.25 4.6 0 226.04 162.73 33042 +1947 319 4.18 -1.82 2.53 0 198.19 162.47 32899 +1947 320 6.89 0.89 5.24 0 235.3 158.67 32758 +1947 321 8.49 2.49 6.84 0 259.9 155.27 32620 +1947 322 9.39 3.39 7.74 0 274.68 152.69 32486 +1947 323 9.47 3.47 7.82 0 276.03 151.02 32354 +1947 324 9.54 3.54 7.89 0 277.21 148.92 32225 +1947 325 11.12 5.12 9.47 0 305.13 145.77 32100 +1947 326 14.85 8.85 13.2 0 380.74 140.34 31977 +1947 327 16.92 10.92 15.27 0 429.22 135.93 31858 +1947 328 14.99 8.99 13.34 0 383.87 136.47 31743 +1947 329 13.56 7.56 11.91 0 352.96 136.66 31631 +1947 330 17.19 11.19 15.54 0 435.91 130.89 31522 +1947 331 15.21 9.21 13.56 0.61 388.82 99.09 31417 +1947 332 12.38 6.38 10.73 0.62 329.09 100.2 31316 +1947 333 7.93 1.93 6.28 0 251.05 136.38 31218 +1947 334 6.18 0.18 4.53 0.01 225.05 102.39 31125 +1947 335 2.55 -3.45 0.9 0 178.39 137.49 31035 +1947 336 2.08 -3.92 0.43 0.06 173.01 102.48 30949 +1947 337 3.48 -2.52 1.83 0 189.47 134.24 30867 +1947 338 2.62 -3.38 0.97 0 179.21 133.75 30790 +1947 339 2.05 -3.95 0.4 0 172.67 133.24 30716 +1947 340 1.89 -4.11 0.24 0 170.88 132.58 30647 +1947 341 0.81 -5.19 -0.84 0 159.17 132.16 30582 +1947 342 1.35 -4.65 -0.3 0 164.93 131.15 30521 +1947 343 0.75 -5.25 -0.9 0.09 158.54 97.94 30465 +1947 344 5.57 -0.43 3.92 0.38 216.54 95.2 30413 +1947 345 6.3 0.3 4.65 0.3 226.75 94.54 30366 +1947 346 3.7 -2.3 2.05 0.52 192.17 95.27 30323 +1947 347 1.4 -4.6 -0.25 0.01 165.48 95.68 30284 +1947 348 5.59 -0.41 3.94 0 216.82 125 30251 +1947 349 5.92 -0.08 4.27 0.6 221.39 93.32 30221 +1947 350 2.74 -3.26 1.09 0.58 180.61 94.39 30197 +1947 351 4.51 -1.49 2.86 0.02 202.42 93.52 30177 +1947 352 5.83 -0.17 4.18 0.17 220.13 92.88 30162 +1947 353 7.21 1.21 5.56 0.18 240.06 92.17 30151 +1947 354 7.59 1.59 5.94 0.06 245.81 91.95 30145 +1947 355 6.82 0.82 5.17 0.71 234.27 92.33 30144 +1947 356 0.8 -5.2 -0.85 0.45 159.06 94.78 30147 +1947 357 6.65 0.65 5 0 231.79 123.31 30156 +1947 358 6.81 0.81 5.16 0.15 234.13 92.47 30169 +1947 359 2.6 -3.4 0.95 0 178.98 125.8 30186 +1947 360 3.64 -2.36 1.99 0.02 191.43 94.23 30208 +1947 361 7.03 1.03 5.38 0 237.37 123.95 30235 +1947 362 9.33 3.33 7.68 0 273.67 122.74 30267 +1947 363 9.77 3.77 8.12 0.98 281.14 92.23 30303 +1947 364 6.66 0.66 5.01 1.23 231.94 94.2 30343 +1947 365 8.94 2.94 7.29 0.22 267.2 93.42 30388 +1948 1 9.51 3.51 7.86 0.23 276.71 93.75 30438 +1948 2 12.8 6.8 11.15 1.95 337.42 92.13 30492 +1948 3 13.57 7.57 11.92 0.08 353.17 92.25 30551 +1948 4 11.16 5.16 9.51 1.47 305.87 94.62 30614 +1948 5 10.36 4.36 8.71 0.23 291.42 95.61 30681 +1948 6 13.42 7.42 11.77 0.18 350.05 94.13 30752 +1948 7 11.82 5.82 10.17 0.04 318.25 95.86 30828 +1948 8 12.51 6.51 10.86 0 331.65 128.62 30907 +1948 9 13.91 7.91 12.26 0.05 360.32 96.3 30991 +1948 10 11.95 5.95 10.3 1.76 320.74 98.73 31079 +1948 11 7.3 1.3 5.65 0.57 241.41 102.35 31171 +1948 12 2.48 -3.52 0.83 0.34 177.58 105.34 31266 +1948 13 -1.29 -7.29 -2.94 0 138.37 143.84 31366 +1948 14 -0.58 -6.58 -2.23 0 145.12 145.03 31469 +1948 15 0.23 -5.77 -1.42 0.51 153.17 109.6 31575 +1948 16 3.33 -2.67 1.68 0 187.64 145.82 31686 +1948 17 1.17 -4.83 -0.48 0 162.99 148.67 31800 +1948 18 6.81 0.81 5.16 0 234.13 147.13 31917 +1948 19 5.08 -0.92 3.43 0 209.91 150.25 32038 +1948 20 2.95 -3.05 1.3 0 183.09 153.15 32161 +1948 21 1.98 -4.02 0.33 0.11 171.89 116.78 32289 +1948 22 4.82 -1.18 3.17 0.04 206.47 116.81 32419 +1948 23 0.27 -5.73 -1.38 0 153.58 160.14 32552 +1948 24 3.82 -2.18 2.17 0 193.66 160.23 32688 +1948 25 2.57 -3.43 0.92 0.01 178.63 122.16 32827 +1948 26 3.28 -2.72 1.63 0 187.04 164.38 32969 +1948 27 2.22 -3.78 0.57 0.05 174.6 125.29 33114 +1948 28 2.35 -3.65 0.7 0 176.09 169.19 33261 +1948 29 9.6 3.6 7.95 0 278.23 166.06 33411 +1948 30 7.86 1.86 6.21 0.03 249.96 127.38 33564 +1948 31 8.26 2.26 6.61 0.04 256.23 128.88 33718 +1948 32 3.89 -2.11 2.24 0 194.54 177.34 33875 +1948 33 8.25 2.25 6.6 0 256.08 176.53 34035 +1948 34 7.27 1.27 5.62 0.01 240.96 134.68 34196 +1948 35 6.25 0.25 4.6 0.87 226.04 136.92 34360 +1948 36 10.85 4.85 9.2 0.76 300.2 135.51 34526 +1948 37 11.44 5.44 9.79 0.04 311.07 136.79 34694 +1948 38 8.41 2.41 6.76 0.18 258.62 141.2 34863 +1948 39 5.81 -0.19 4.16 0.1 219.85 144.87 35035 +1948 40 4.14 -1.86 2.49 0.13 197.68 147.8 35208 +1948 41 1.74 -4.26 0.09 0.04 169.21 151.02 35383 +1948 42 2.38 -3.62 0.73 0 176.43 203.51 35560 +1948 43 1.75 -4.25 0.1 0.01 169.32 154.99 35738 +1948 44 1.44 -4.56 -0.21 0.12 165.91 157.08 35918 +1948 45 -1.88 -7.88 -3.53 0.19 132.96 197.58 36099 +1948 46 0.47 -5.53 -1.18 0.02 155.63 198.39 36282 +1948 47 1.89 -4.11 0.24 0.16 170.88 199.44 36466 +1948 48 4.6 -1.4 2.95 0 203.59 218.13 36652 +1948 49 1.57 -4.43 -0.08 0 167.33 223.19 36838 +1948 50 3.3 -2.7 1.65 0 187.28 224.62 37026 +1948 51 2.16 -3.84 0.51 0 173.92 228.46 37215 +1948 52 3.34 -2.66 1.69 0 187.77 230.42 37405 +1948 53 5.43 -0.57 3.78 0 214.63 231.62 37596 +1948 54 7.86 1.86 6.21 0.43 249.96 173.98 37788 +1948 55 2.9 -3.1 1.25 0.52 182.5 179.65 37981 +1948 56 2.63 -3.37 0.98 0 179.33 242.45 38175 +1948 57 1.94 -4.06 0.29 0 171.44 245.89 38370 +1948 58 2.19 -3.81 0.54 0.82 174.26 186.5 38565 +1948 59 -2.08 -8.08 -3.73 0.03 131.17 224.83 38761 +1948 60 5.53 -0.47 3.88 0 215.99 251.4 38958 +1948 61 7.54 1.54 5.89 0 245.04 252.24 39156 +1948 62 10.63 4.63 8.98 0 296.23 251.19 39355 +1948 63 10.9 4.9 9.25 0.04 301.11 190.34 39553 +1948 64 8.67 2.67 7.02 0 262.8 259.58 39753 +1948 65 7.6 1.6 5.95 0 245.96 263.73 39953 +1948 66 4.35 -1.65 2.7 0 200.36 269.88 40154 +1948 67 7.17 1.17 5.52 0 239.46 269.86 40355 +1948 68 7.75 1.75 6.1 0 248.26 272.05 40556 +1948 69 7.72 1.72 6.07 0.08 247.8 206.03 40758 +1948 70 8.52 2.52 6.87 0.01 260.38 207.42 40960 +1948 71 12.3 6.3 10.65 0 327.52 273.99 41163 +1948 72 8.57 2.57 6.92 0 261.19 282.21 41366 +1948 73 5.97 -0.03 4.32 0 222.09 288 41569 +1948 74 10.89 4.89 9.24 0 300.92 284.33 41772 +1948 75 12.01 6.01 10.36 0.04 321.89 213.94 41976 +1948 76 11.4 5.4 9.75 0 310.32 288.84 42179 +1948 77 10.98 4.98 9.33 0 302.56 292.07 42383 +1948 78 7.77 1.77 6.12 0 248.57 299.28 42587 +1948 79 12.7 6.7 11.05 0 335.42 294.54 42791 +1948 80 14.19 8.19 12.54 0 366.3 294.28 42996 +1948 81 7.99 1.99 6.34 0 251.99 306.85 43200 +1948 82 5 -1 3.35 0 208.85 313.15 43404 +1948 83 6.9 0.9 5.25 0 235.45 313.42 43608 +1948 84 5.53 -0.47 3.88 0 215.99 317.63 43812 +1948 85 9.78 3.78 8.13 0 281.31 314.48 44016 +1948 86 13.11 7.11 11.46 0.06 343.69 233.41 44220 +1948 87 12.32 6.32 10.67 0 327.91 315.17 44424 +1948 88 10.56 4.56 8.91 0 294.97 320.52 44627 +1948 89 9.46 3.46 7.81 0 275.86 324.53 44831 +1948 90 11.31 5.31 9.66 0 308.64 323.88 45034 +1948 91 15.45 9.45 13.8 0 394.29 317.98 45237 +1948 92 15.22 9.22 13.57 0.14 389.05 240.51 45439 +1948 93 14.65 8.65 13 0.51 376.32 243.06 45642 +1948 94 11.25 5.25 9.6 0.54 307.53 249.61 45843 +1948 95 11.01 5.01 9.36 0.01 303.11 251.53 46045 +1948 96 16.28 10.28 14.63 0.41 413.7 245 46246 +1948 97 13.22 7.22 11.57 0.6 345.94 251.54 46446 +1948 98 11.45 5.45 9.8 0.27 311.26 255.54 46647 +1948 99 9.5 3.5 7.85 0.17 276.54 259.55 46846 +1948 100 10.51 4.51 8.86 0.42 294.08 259.75 47045 +1948 101 10.06 4.06 8.41 0 286.15 349.04 47243 +1948 102 14.14 8.14 12.49 0 365.23 343.13 47441 +1948 103 16.03 10.03 14.38 0 407.77 340.61 47638 +1948 104 18.06 12.06 16.41 0 458.09 337.13 47834 +1948 105 16.19 10.19 14.54 0.01 411.56 257.82 48030 +1948 106 15.24 9.24 13.59 0 389.5 347.67 48225 +1948 107 17.57 11.57 15.92 0 445.49 343.43 48419 +1948 108 19.33 13.33 17.68 0.1 492.19 255.08 48612 +1948 109 17.38 11.38 15.73 0.08 440.68 260.41 48804 +1948 110 16.82 10.82 15.17 1.42 426.76 262.56 48995 +1948 111 16.56 10.56 14.91 0.13 420.43 264.21 49185 +1948 112 17.88 11.88 16.23 0 453.43 350.21 49374 +1948 113 14.19 8.19 12.54 0.07 366.3 270.62 49561 +1948 114 14.5 8.5 12.85 0.18 373.03 271.21 49748 +1948 115 11.31 5.31 9.66 0 308.64 369.74 49933 +1948 116 12.11 6.11 10.46 0 323.82 369.41 50117 +1948 117 9.81 3.81 8.16 0.21 281.82 281.28 50300 +1948 118 15.64 9.64 13.99 0.02 398.66 273.08 50481 +1948 119 18.19 12.19 16.54 0 461.49 358.41 50661 +1948 120 18.74 12.74 17.09 0 476.09 357.93 50840 +1948 121 23.26 17.26 21.61 0 611.72 343.5 51016 +1948 122 23.36 17.36 21.71 0 615.06 344.24 51191 +1948 123 20.86 14.86 19.21 0.01 536.12 265.78 51365 +1948 124 17.1 11.1 15.45 0.28 433.67 275.25 51536 +1948 125 15.73 9.73 14.08 0 400.75 371.61 51706 +1948 126 21.01 15.01 19.36 0 540.6 356.81 51874 +1948 127 24.92 18.92 23.27 0 669.14 342.49 52039 +1948 128 21.88 15.88 20.23 0.12 567.22 266.65 52203 +1948 129 20.31 14.31 18.66 0.54 519.96 271.38 52365 +1948 130 24.09 18.09 22.44 0.06 639.89 261.36 52524 +1948 131 19.44 13.44 17.79 0.12 495.25 274.68 52681 +1948 132 18.23 12.23 16.58 0 462.54 370.79 52836 +1948 133 18.55 12.55 16.9 0.29 471 277.89 52989 +1948 134 17.8 11.8 16.15 0 451.37 373.46 53138 +1948 135 17.07 11.07 15.42 0 432.93 376.24 53286 +1948 136 17.25 11.25 15.6 0 437.41 376.37 53430 +1948 137 16.55 10.55 14.9 0 420.19 379.02 53572 +1948 138 16.91 10.91 15.26 0 428.97 378.63 53711 +1948 139 15.61 9.61 13.96 0 397.97 382.81 53848 +1948 140 16.93 10.93 15.28 0 429.47 379.75 53981 +1948 141 18.22 12.22 16.57 0 462.28 376.43 54111 +1948 142 14.86 8.86 13.21 0 380.96 386.15 54238 +1948 143 15.79 9.79 14.14 0.19 402.14 288.23 54362 +1948 144 18.52 12.52 16.87 0 470.21 377.01 54483 +1948 145 19.8 13.8 18.15 0 505.35 373.39 54600 +1948 146 20.3 14.3 18.65 0.02 519.67 279.05 54714 +1948 147 23.37 17.37 21.72 0 615.39 361.08 54824 +1948 148 23.6 17.6 21.95 0.16 623.13 270.38 54931 +1948 149 21.65 15.65 20 0 560.08 368.42 55034 +1948 150 20.02 14.02 18.37 0.26 511.61 280.88 55134 +1948 151 18.51 12.51 16.86 1.92 469.94 284.83 55229 +1948 152 16.43 10.43 14.78 0.61 417.29 289.46 55321 +1948 153 19.62 13.62 17.97 0.58 500.28 282.43 55409 +1948 154 17.58 11.58 15.93 0 445.74 383.25 55492 +1948 155 16.38 10.38 14.73 0 416.09 386.85 55572 +1948 156 20.3 14.3 18.65 0.27 519.67 281.33 55648 +1948 157 21.63 15.63 19.98 0.27 559.46 277.89 55719 +1948 158 23.14 17.14 21.49 0 607.74 364.86 55786 +1948 159 24.56 18.56 22.91 0.01 656.32 269.35 55849 +1948 160 23.39 17.39 21.74 0.04 616.06 273.19 55908 +1948 161 21 15 19.35 0 540.3 373.48 55962 +1948 162 22.75 16.75 21.1 0.29 594.94 275.21 56011 +1948 163 20.2 14.2 18.55 1.01 516.78 282.41 56056 +1948 164 23.16 17.16 21.51 0.08 608.4 274.17 56097 +1948 165 25.91 19.91 24.26 0.01 705.51 265.23 56133 +1948 166 20.48 14.48 18.83 0.18 524.91 281.85 56165 +1948 167 23.21 17.21 21.56 0 610.06 365.48 56192 +1948 168 20.53 14.53 18.88 0 526.38 375.65 56214 +1948 169 18.89 12.89 17.24 0 480.14 381.13 56231 +1948 170 20.57 14.57 18.92 0 527.55 375.53 56244 +1948 171 20.56 14.56 18.91 0.65 527.26 281.71 56252 +1948 172 18.3 12.3 16.65 1.28 464.38 287.27 56256 +1948 173 18.43 12.43 16.78 0.05 467.81 286.96 56255 +1948 174 21.72 15.72 20.07 0.11 562.24 278.49 56249 +1948 175 19.76 13.76 18.11 0.13 504.22 283.66 56238 +1948 176 20.84 14.84 19.19 0.82 535.53 280.84 56223 +1948 177 18.09 12.09 16.44 1.01 458.88 287.55 56203 +1948 178 20.91 14.91 19.26 2.54 537.61 280.6 56179 +1948 179 17.27 11.27 15.62 1.55 437.91 289.31 56150 +1948 180 13.5 7.5 11.85 1.57 351.71 296.55 56116 +1948 181 12.35 6.35 10.7 0.07 328.5 298.42 56078 +1948 182 14.12 8.12 12.47 0.06 364.8 295.28 56035 +1948 183 13.45 7.45 11.8 1.45 350.68 296.33 55987 +1948 184 16.54 10.54 14.89 1.31 419.95 290.35 55935 +1948 185 14.07 8.07 12.42 1.32 363.73 295.05 55879 +1948 186 19.53 13.53 17.88 0 497.76 377.74 55818 +1948 187 21.52 15.52 19.87 0 556.07 370.63 55753 +1948 188 25.02 19.02 23.37 0 672.74 356.15 55684 +1948 189 24.72 18.72 23.07 0.06 661.99 267.98 55611 +1948 190 24.98 18.98 23.33 0.77 671.3 266.85 55533 +1948 191 26.08 20.08 24.43 0 711.92 350.49 55451 +1948 192 26.24 20.24 24.59 0.04 718 262.08 55366 +1948 193 24.57 18.57 22.92 0 656.67 356.79 55276 +1948 194 21.54 15.54 19.89 0.31 556.69 276.52 55182 +1948 195 22.64 16.64 20.99 0.25 591.38 273.19 55085 +1948 196 21.62 15.62 19.97 0.5 559.15 275.79 54984 +1948 197 21.21 15.21 19.56 0 546.63 368.76 54879 +1948 198 19.36 13.36 17.71 0.67 493.03 280.99 54770 +1948 199 20.43 14.43 18.78 0.28 523.45 278.05 54658 +1948 200 22.73 16.73 21.08 0.62 594.29 271.42 54542 +1948 201 18.43 12.43 16.78 0.24 467.81 282.25 54423 +1948 202 17.34 11.34 15.69 0.06 439.67 284.25 54301 +1948 203 16.26 10.26 14.61 0.2 413.22 286.11 54176 +1948 204 13.98 7.98 12.33 0.11 361.81 290.01 54047 +1948 205 15.89 9.89 14.24 1.26 404.48 286.05 53915 +1948 206 16.06 10.06 14.41 0.48 408.48 285.28 53780 +1948 207 17.34 11.34 15.69 0.65 439.67 282.14 53643 +1948 208 20.62 14.62 18.97 0.13 529.02 273.93 53502 +1948 209 23.08 17.08 21.43 0.05 605.76 266.65 53359 +1948 210 27.12 21.12 25.47 0 752.22 337.12 53213 +1948 211 27.29 21.29 25.64 0.92 758.99 251.66 53064 +1948 212 26.25 20.25 24.6 0.31 718.38 254.84 52913 +1948 213 31 25 29.35 0 920.02 313.87 52760 +1948 214 30.7 24.7 29.05 0 906.01 314.98 52604 +1948 215 29.71 23.71 28.06 0 861.05 320.06 52445 +1948 216 29.78 23.78 28.13 0 864.16 318.73 52285 +1948 217 27.23 21.23 25.58 0.74 756.6 248.44 52122 +1948 218 21.44 15.44 19.79 0 553.62 354.67 51958 +1948 219 22.53 16.53 20.88 0 587.83 349.66 51791 +1948 220 21.2 15.2 19.55 0.01 546.32 265.16 51622 +1948 221 17.14 11.14 15.49 0 434.67 365.14 51451 +1948 222 16.92 10.92 15.27 0.25 429.22 273.51 51279 +1948 223 16.27 10.27 14.62 0 413.46 365.24 51105 +1948 224 16.96 10.96 15.31 0 430.2 362.33 50929 +1948 225 17.81 11.81 16.16 0 451.62 358.81 50751 +1948 226 22.37 16.37 20.72 0 582.7 342.92 50572 +1948 227 23.58 17.58 21.93 0.12 622.45 252.81 50392 +1948 228 18.61 12.61 16.96 0.06 472.61 264.62 50210 +1948 229 23.19 17.19 21.54 0.2 609.4 252.15 50026 +1948 230 22.32 16.32 20.67 0.08 581.1 253.64 49842 +1948 231 22.54 16.54 20.89 0 588.15 335.95 49656 +1948 232 23.27 17.27 21.62 0.97 612.06 248.94 49469 +1948 233 24.18 18.18 22.53 0.24 643.01 245.26 49280 +1948 234 21.87 15.87 20.22 0.46 566.91 250.68 49091 +1948 235 20.87 14.87 19.22 0 536.42 336.15 48900 +1948 236 26.6 20.6 24.95 0.98 731.84 234.5 48709 +1948 237 26.57 20.57 24.92 0.11 730.68 233.44 48516 +1948 238 27.78 21.78 26.13 2.24 778.79 228.09 48323 +1948 239 22.58 16.58 20.93 0.72 589.44 243.12 48128 +1948 240 19.18 13.18 17.53 0 488.06 333.43 47933 +1948 241 16.7 10.7 15.05 0 423.83 338.44 47737 +1948 242 20.97 14.97 19.32 0 539.4 324.5 47541 +1948 243 22.47 16.47 20.82 0 585.9 317.66 47343 +1948 244 17.49 11.49 15.84 0 443.46 330.94 47145 +1948 245 16.27 10.27 14.62 0.27 413.46 249.11 46947 +1948 246 18.23 12.23 16.58 0.59 462.54 243.87 46747 +1948 247 16.8 10.8 15.15 0 426.27 326.99 46547 +1948 248 16.92 10.92 15.27 0.26 429.22 243.55 46347 +1948 249 16.03 10.03 14.38 0 407.77 324.8 46146 +1948 250 18.85 12.85 17.2 0 479.06 315.68 45945 +1948 251 23.14 17.14 21.49 0 607.74 300.3 45743 +1948 252 24.19 18.19 22.54 0 643.35 294.47 45541 +1948 253 21.53 15.53 19.88 0 556.38 301.5 45339 +1948 254 23.53 17.53 21.88 0 620.77 292.79 45136 +1948 255 22.33 16.33 20.68 0 581.42 294.68 44933 +1948 256 26.86 20.86 25.21 0 741.97 275.8 44730 +1948 257 26.83 20.83 25.18 0 740.8 273.94 44527 +1948 258 28.37 22.37 26.72 0.17 803.2 198.89 44323 +1948 259 22.88 16.88 21.23 0.45 599.18 213.03 44119 +1948 260 20.29 14.29 18.64 0.02 519.38 217.23 43915 +1948 261 20.46 14.46 18.81 0 524.33 286.77 43711 +1948 262 20.51 14.51 18.86 0 525.79 284.32 43507 +1948 263 19.22 13.22 17.57 0.59 489.16 214.06 43303 +1948 264 22.32 16.32 20.67 0 581.1 274.1 43099 +1948 265 19.31 13.31 17.66 0 491.64 280.34 42894 +1948 266 14.78 8.78 13.13 0.13 379.19 216.12 42690 +1948 267 14.43 8.43 12.78 0.18 371.5 214.61 42486 +1948 268 16.01 10.01 14.36 0.17 407.3 210.31 42282 +1948 269 15.94 9.94 14.29 1.43 405.65 208.54 42078 +1948 270 14.05 8.05 12.4 0.13 363.3 209.33 41875 +1948 271 16.42 10.42 14.77 0 417.05 271.82 41671 +1948 272 13.29 7.29 11.64 0.05 347.37 206.31 41468 +1948 273 16.15 10.15 14.5 0 410.61 267.16 41265 +1948 274 10.53 4.53 8.88 0.16 294.44 205.63 41062 +1948 275 12.21 6.21 10.56 0 325.76 268.83 40860 +1948 276 11.03 5.03 9.38 1.15 303.48 200.92 40658 +1948 277 12.59 6.59 10.94 0 333.23 262.82 40456 +1948 278 13.07 7.07 11.42 0 342.87 259.16 40255 +1948 279 9.99 3.99 8.34 0 284.93 260.89 40054 +1948 280 13.11 7.11 11.46 0.07 343.69 190.21 39854 +1948 281 11.77 5.77 10.12 0.08 317.3 189.71 39654 +1948 282 14.51 8.51 12.86 0 373.25 245.83 39455 +1948 283 8.56 2.56 6.91 0 261.02 251.57 39256 +1948 284 11.15 5.15 9.5 0 305.68 245.19 39058 +1948 285 8.25 2.25 6.6 0 256.08 246.17 38861 +1948 286 8.24 2.24 6.59 0.5 255.92 182.53 38664 +1948 287 11.56 5.56 9.91 0.02 313.32 177.17 38468 +1948 288 13.93 7.93 12.28 0 360.75 229.94 38273 +1948 289 14.72 8.72 13.07 0.26 377.86 169.54 38079 +1948 290 15.86 9.86 14.21 1.2 403.78 165.98 37885 +1948 291 15.84 9.84 14.19 0.37 403.31 164.02 37693 +1948 292 16.69 10.69 15.04 0.04 423.59 160.92 37501 +1948 293 18.34 12.34 16.69 0 465.43 208.81 37311 +1948 294 18.26 12.26 16.61 0 463.33 206.17 37121 +1948 295 19.5 13.5 17.85 0 496.92 200.96 36933 +1948 296 17.58 11.58 15.93 0.06 445.74 151.66 36745 +1948 297 17.9 11.9 16.25 0.58 453.94 149.24 36560 +1948 298 18.49 12.49 16.84 0 469.41 195.38 36375 +1948 299 18.17 12.17 16.52 0.09 460.97 144.98 36191 +1948 300 14.75 8.75 13.1 0.58 378.52 147.3 36009 +1948 301 16.94 10.94 15.29 0.06 429.71 142.85 35829 +1948 302 13.44 7.44 11.79 0.15 350.47 144.92 35650 +1948 303 13.1 7.1 11.45 0 343.48 191.13 35472 +1948 304 16.29 10.29 14.64 0.61 413.94 138.09 35296 +1948 305 8.63 2.63 6.98 0 262.15 191.05 35122 +1948 306 8.72 2.72 7.07 0 263.61 188.7 34950 +1948 307 8.15 2.15 6.5 0.33 254.5 140.05 34779 +1948 308 7.22 1.22 5.57 0 240.2 184.95 34610 +1948 309 8.52 2.52 6.87 0 260.38 181.45 34444 +1948 310 9.17 3.17 7.52 0 271 178.39 34279 +1948 311 11.91 5.91 10.26 0.62 319.97 130.01 34116 +1948 312 6.75 0.75 5.1 0 233.25 175.72 33956 +1948 313 8.61 2.61 6.96 0 261.83 171.99 33797 +1948 314 10.37 4.37 8.72 0 291.59 168.36 33641 +1948 315 11.49 5.49 9.84 0 312.01 164.69 33488 +1948 316 9.1 3.1 7.45 0 269.84 164.89 33337 +1948 317 7.53 1.53 5.88 0 244.89 164.06 33188 +1948 318 7.18 1.18 5.53 0 239.61 162.01 33042 +1948 319 10.62 4.62 8.97 0 296.05 157.28 32899 +1948 320 10.34 4.34 8.69 0 291.06 155.7 32758 +1948 321 10.89 4.89 9.24 0 300.92 153.09 32620 +1948 322 6.78 0.78 5.13 0 233.69 154.82 32486 +1948 323 6.47 0.47 4.82 0.24 229.19 115.07 32354 +1948 324 4.68 -1.32 3.03 0 204.63 152.61 32225 +1948 325 4.12 -1.88 2.47 0 197.43 151.23 32100 +1948 326 3.55 -2.45 1.9 0 190.33 150.1 31977 +1948 327 2.93 -3.07 1.28 0.26 182.85 111.45 31858 +1948 328 0.11 -5.89 -1.54 0 151.95 148.05 31743 +1948 329 0.14 -5.86 -1.51 0 152.26 146.52 31631 +1948 330 -0.19 -6.19 -1.84 0.01 148.95 150.81 31522 +1948 331 5.01 -0.99 3.36 1.02 208.98 105.83 31417 +1948 332 5.23 -0.77 3.58 0 211.92 139.32 31316 +1948 333 9.86 3.86 8.21 0.02 282.68 101.13 31218 +1948 334 7.49 1.49 5.84 0 244.28 135.61 31125 +1948 335 0.15 -5.85 -1.5 0 152.36 138.64 31035 +1948 336 1.76 -4.24 0.11 0 169.43 136.8 30949 +1948 337 -2.25 -8.25 -3.9 0 129.67 136.85 30867 +1948 338 0.36 -5.64 -1.29 0 154.5 134.83 30790 +1948 339 -1.02 -7.02 -2.67 0.02 140.9 144 30716 +1948 340 -0.26 -6.26 -1.91 0.32 148.25 144.3 30647 +1948 341 2.54 -3.46 0.89 0 178.28 175.23 30582 +1948 342 4.72 -1.28 3.07 0 205.16 172.75 30521 +1948 343 4.89 -1.11 3.24 0 207.39 128.47 30465 +1948 344 5.91 -0.09 4.26 0 221.25 126.72 30413 +1948 345 5.49 -0.51 3.84 0 215.45 126.55 30366 +1948 346 3.48 -2.52 1.83 0 189.47 127.14 30323 +1948 347 3.16 -2.84 1.51 0 185.59 126.71 30284 +1948 348 5.55 -0.45 3.9 0 216.27 125.03 30251 +1948 349 6.05 0.05 4.4 0 223.21 124.34 30221 +1948 350 4.92 -1.08 3.27 0.03 207.79 93.51 30197 +1948 351 -0.78 -6.78 -2.43 0 143.19 127.2 30177 +1948 352 1.32 -4.68 -0.33 0 164.61 126.22 30162 +1948 353 2.1 -3.9 0.45 0 173.24 125.79 30151 +1948 354 5.18 -0.82 3.53 0 211.25 124.13 30145 +1948 355 -0.06 -6.06 -1.71 0 150.24 126.71 30144 +1948 356 -5.7 -11.7 -7.35 0 102.2 128.67 30147 +1948 357 -3.26 -9.26 -4.91 0 121.03 127.99 30156 +1948 358 -2.28 -8.28 -3.93 0.18 129.41 140.13 30169 +1948 359 -4.62 -10.62 -6.27 0.33 110.2 141.82 30186 +1948 360 -3.16 -9.16 -4.81 0.07 121.87 141.94 30208 +1948 361 -4.76 -10.76 -6.41 0 109.13 174.88 30235 +1948 362 -2.3 -8.3 -3.95 0.11 129.23 142.57 30267 +1948 363 1.29 -4.71 -0.36 0.21 164.28 141.69 30303 +1948 364 0.47 -5.53 -1.18 0.05 155.63 142.14 30343 +1948 365 0.48 -5.52 -1.17 0 155.73 174.81 30388 +1949 1 6.84 0.84 5.19 0 234.57 171.27 30438 +1949 2 8.79 2.79 7.14 0 264.75 126.28 30492 +1949 3 5.65 -0.35 4 0 217.64 129.36 30551 +1949 4 4.58 -1.42 2.93 0 203.33 130.91 30614 +1949 5 6.23 0.23 4.58 0 225.75 130.54 30681 +1949 6 10.82 4.82 9.17 0 299.65 127.95 30752 +1949 7 10.11 4.11 8.46 0.08 287.02 97 30828 +1949 8 8.05 2.05 6.4 0.31 252.93 99.31 30907 +1949 9 4.17 -1.83 2.52 0 198.07 136.21 30991 +1949 10 -0.32 -6.32 -1.97 0 147.66 139.77 31079 +1949 11 5.55 -0.45 3.9 0 216.27 137.65 31171 +1949 12 4.23 -1.77 2.58 0 198.83 139.47 31266 +1949 13 6.19 0.19 4.54 0 225.19 139.84 31366 +1949 14 4.28 -1.72 2.63 0 199.47 142.53 31469 +1949 15 5 -1 3.35 0 208.85 143.53 31575 +1949 16 2.66 -3.34 1.01 0 179.67 146.2 31686 +1949 17 -2.11 -8.11 -3.76 0.09 130.91 154.38 31800 +1949 18 -4.11 -10.11 -5.76 0.27 114.16 157.05 31917 +1949 19 -3.15 -9.15 -4.8 0 121.95 196.7 32038 +1949 20 -2.13 -8.13 -3.78 0 130.73 197.75 32161 +1949 21 0.1 -5.9 -1.55 0 151.85 198.6 32289 +1949 22 1.8 -4.2 0.15 0 169.87 199.11 32419 +1949 23 2.8 -3.2 1.15 0.01 181.32 160.11 32552 +1949 24 2.46 -3.54 0.81 0 177.35 201.6 32688 +1949 25 3.83 -2.17 2.18 0 193.79 162.11 32827 +1949 26 2.85 -3.15 1.2 0.48 181.9 123.48 32969 +1949 27 4.17 -1.83 2.52 0.21 198.07 124.38 33114 +1949 28 6.66 0.66 5.01 0.05 231.94 124.68 33261 +1949 29 8.67 2.67 7.02 0 262.8 166.91 33411 +1949 30 8.62 2.62 6.97 0 261.99 169.17 33564 +1949 31 5.32 -0.68 3.67 0.01 213.14 130.67 33718 +1949 32 3.25 -2.75 1.6 0 186.68 177.77 33875 +1949 33 3.76 -2.24 2.11 0 192.92 180.06 34035 +1949 34 0.72 -5.28 -0.93 0 158.22 184.16 34196 +1949 35 3.4 -2.6 1.75 0 188.49 184.67 34360 +1949 36 10.87 4.87 9.22 0 300.56 180.66 34526 +1949 37 13.06 7.06 11.41 0 342.67 180.44 34694 +1949 38 11.21 5.21 9.56 0 306.79 185.33 34863 +1949 39 6.7 0.7 5.05 0 232.52 192.41 35035 +1949 40 8.88 2.88 7.23 0 266.22 192.96 35208 +1949 41 10.89 4.89 9.24 0 300.92 193.38 35383 +1949 42 6.63 0.63 4.98 0 231.5 200.21 35560 +1949 43 7.2 1.2 5.55 0 239.91 202.38 35738 +1949 44 8.06 2.06 6.41 0 253.08 204.1 35918 +1949 45 4.01 -1.99 2.36 0 196.04 210.26 36099 +1949 46 3.55 -2.45 1.9 0 190.33 213.31 36282 +1949 47 2.69 -3.31 1.04 0 180.03 216.78 36466 +1949 48 3.53 -2.47 1.88 0 190.08 218.98 36652 +1949 49 6.47 0.47 4.82 0 229.19 219.26 36838 +1949 50 5.44 -0.56 3.79 0 214.77 222.86 37026 +1949 51 3.94 -2.06 2.29 0 195.16 227.1 37215 +1949 52 -0.59 -6.59 -2.24 0 145.02 233.13 37405 +1949 53 2.95 -3.05 1.3 0 183.09 233.7 37596 +1949 54 8.48 2.48 6.83 0 259.74 231.29 37788 +1949 55 7.42 1.42 5.77 0 243.22 235.41 37981 +1949 56 5.85 -0.15 4.2 0 220.41 239.67 38175 +1949 57 4.32 -1.68 2.67 0 199.98 243.96 38370 +1949 58 2.29 -3.71 0.64 0 175.4 248.59 38565 +1949 59 -0.1 -6.1 -1.75 0 149.84 253.04 38761 +1949 60 2.22 -3.78 0.57 0 174.6 254.29 38958 +1949 61 6.36 0.36 4.71 0 227.61 253.5 39156 +1949 62 6.26 0.26 4.61 0 226.18 256.4 39355 +1949 63 3.81 -2.19 2.16 0 193.54 261.78 39553 +1949 64 2.29 -3.71 0.64 0 175.4 266 39753 +1949 65 3.17 -2.83 1.52 0 185.71 268.19 39953 +1949 66 5.44 -0.56 3.79 0 214.77 268.81 40154 +1949 67 9.36 3.36 7.71 0 274.18 267.18 40355 +1949 68 8.54 2.54 6.89 0 260.7 271.08 40556 +1949 69 10.91 4.91 9.26 0 301.29 270.47 40758 +1949 70 14.76 8.76 13.11 0 378.75 266.87 40960 +1949 71 15.98 9.98 14.33 0 406.59 267.32 41163 +1949 72 11.5 5.5 9.85 0 312.19 278.04 41366 +1949 73 10.75 4.75 9.1 0 298.39 281.82 41569 +1949 74 1.84 -4.16 0.19 0 170.32 294.79 41772 +1949 75 4.45 -1.55 2.8 0 201.65 295.13 41976 +1949 76 9.82 3.82 8.17 0 282 291.23 42179 +1949 77 11.02 5.02 9.37 0.14 303.3 219 42383 +1949 78 8.67 2.67 7.02 0.04 262.8 223.56 42587 +1949 79 6.49 0.49 4.84 0 229.48 303.6 42791 +1949 80 5.57 -0.43 3.92 0 216.54 307.22 42996 +1949 81 1.9 -4.1 0.25 0 170.99 313.54 43200 +1949 82 1.15 -4.85 -0.5 0 162.78 316.9 43404 +1949 83 2.56 -3.44 0.91 0.01 178.51 238.63 43608 +1949 84 5.17 -0.83 3.52 0 211.12 318.04 43812 +1949 85 5.83 -0.17 4.18 0 220.13 319.81 44016 +1949 86 6.47 0.47 4.82 0.01 229.19 241.09 44220 +1949 87 5.69 -0.31 4.04 0 218.19 324.97 44424 +1949 88 2.38 -3.62 0.73 0 176.43 330.91 44627 +1949 89 -0.96 -6.96 -2.61 0 141.47 336.13 44831 +1949 90 0.08 -5.92 -1.57 0.01 151.65 253.3 45034 +1949 91 8.26 2.26 6.61 0.11 256.23 248.21 45237 +1949 92 8.68 2.68 7.03 0 262.96 332.59 45439 +1949 93 11.52 5.52 9.87 0 312.57 330.19 45642 +1949 94 16.54 10.54 14.89 0.09 419.95 241.42 45843 +1949 95 17.59 11.59 15.94 0.17 446 241.02 46045 +1949 96 21.07 15.07 19.42 0.3 542.4 235.08 46246 +1949 97 18.1 12.1 16.45 0 459.14 324.04 46446 +1949 98 18.85 12.85 17.2 0 479.06 323.88 46647 +1949 99 18.78 12.78 17.13 0.01 477.17 244.51 46846 +1949 100 18.72 12.72 17.07 0.13 475.56 246.04 47045 +1949 101 19.08 13.08 17.43 1.33 485.32 246.66 47243 +1949 102 18 12 16.35 0.08 456.53 250.31 47441 +1949 103 17.81 11.81 16.16 0.56 451.62 252.03 47638 +1949 104 14.14 8.14 12.49 0.24 365.23 260.07 47834 +1949 105 13.72 7.72 12.07 0 356.31 349.45 48030 +1949 106 16.73 10.73 15.08 0 424.56 344.01 48225 +1949 107 16.44 10.44 14.79 0 417.53 346.39 48419 +1949 108 15.16 9.16 13.51 0 387.69 351.23 48612 +1949 109 13.16 7.16 11.51 0 344.71 357.27 48804 +1949 110 14.4 8.4 12.75 0 370.85 355.97 48995 +1949 111 12.16 6.16 10.51 0.01 324.79 271.7 49185 +1949 112 15.25 9.25 13.6 0 389.73 357.03 49374 +1949 113 13.43 7.43 11.78 0 350.26 362.51 49561 +1949 114 12.17 6.17 10.52 0 324.99 366.62 49748 +1949 115 16.23 10.23 14.58 0 412.51 358.82 49933 +1949 116 12.7 6.7 11.05 0 335.42 368.2 50117 +1949 117 13.17 7.17 11.52 0.03 344.91 276.39 50300 +1949 118 12.04 6.04 10.39 0.04 322.47 279.14 50481 +1949 119 12.53 6.53 10.88 0 332.04 372.39 50661 +1949 120 16.27 10.27 14.62 0.24 413.46 273.63 50840 +1949 121 19.82 13.82 18.17 1.15 505.92 266.75 51016 +1949 122 23.88 17.88 22.23 1.25 632.66 256.63 51191 +1949 123 24.61 18.61 22.96 0.98 658.09 255.09 51365 +1949 124 21.83 15.83 20.18 3.26 565.66 264.01 51536 +1949 125 17.93 11.93 16.28 0.85 454.72 274.22 51706 +1949 126 12.2 6.2 10.55 0.77 325.57 285.55 51874 +1949 127 13.13 7.13 11.48 0.36 344.1 284.74 52039 +1949 128 16.05 10.05 14.4 0.03 408.24 280.24 52203 +1949 129 15.02 9.02 13.37 0 384.54 377.12 52365 +1949 130 16.43 10.43 14.78 0 417.29 374.29 52524 +1949 131 15.71 9.71 14.06 0.24 400.28 282.73 52681 +1949 132 12.73 6.73 11.08 0.9 336.02 288.62 52836 +1949 133 13.27 7.27 11.62 1.29 346.96 288.27 52989 +1949 134 15.49 9.49 13.84 0.31 395.2 284.83 53138 +1949 135 16.5 10.5 14.85 1.37 418.98 283.36 53286 +1949 136 15.91 9.91 14.26 0.24 404.95 285.02 53430 +1949 137 15.36 9.36 13.71 0.12 392.23 286.62 53572 +1949 138 17.74 11.74 16.09 0.24 449.83 282.19 53711 +1949 139 17.59 11.59 15.94 0 446 377.38 53848 +1949 140 19.51 13.51 17.86 0 497.2 371.96 53981 +1949 141 18.38 12.38 16.73 0 466.49 375.94 54111 +1949 142 18.58 12.58 16.93 0 471.8 375.83 54238 +1949 143 20.13 14.13 18.48 0.01 514.76 278.51 54362 +1949 144 15.48 9.48 13.83 0.01 394.97 289.2 54483 +1949 145 16.95 10.95 15.3 0 429.96 382.11 54600 +1949 146 16.87 10.87 15.22 0 427.99 382.71 54714 +1949 147 21 15 19.35 0 540.3 370.1 54824 +1949 148 20.68 14.68 19.03 0.18 530.79 278.7 54931 +1949 149 18.89 12.89 17.24 0 480.14 377.87 55034 +1949 150 19.81 13.81 18.16 0 505.63 375.21 55134 +1949 151 16.88 10.88 15.23 0 428.23 384.59 55229 +1949 152 18.18 12.18 16.53 0 461.23 380.9 55321 +1949 153 15.94 9.94 14.29 0 405.65 387.53 55409 +1949 154 18.19 12.19 16.54 0.1 461.49 286.07 55492 +1949 155 18.25 12.25 16.6 0 463.06 381.44 55572 +1949 156 17.09 11.09 15.44 0.67 433.42 288.89 55648 +1949 157 15.22 9.22 13.57 0.02 389.05 292.81 55719 +1949 158 12.98 6.98 11.33 0.04 341.05 296.97 55786 +1949 159 13.93 7.93 12.28 0.04 360.75 295.52 55849 +1949 160 16.81 10.81 15.16 0.11 426.52 290.07 55908 +1949 161 15.84 9.84 14.19 0 403.31 389.48 55962 +1949 162 16.74 10.74 15.09 0 424.8 387.08 56011 +1949 163 18.96 12.96 17.31 0 482.04 380.65 56056 +1949 164 23.08 17.08 21.43 0 605.76 365.89 56097 +1949 165 26.02 20.02 24.37 0 709.66 353.12 56133 +1949 166 24.31 18.31 22.66 0.02 647.54 270.7 56165 +1949 167 19.11 13.11 17.46 0.52 486.14 285.25 56192 +1949 168 20.8 14.8 19.15 0.06 534.34 281.03 56214 +1949 169 21.96 15.96 20.31 0.92 569.72 277.85 56231 +1949 170 20.82 14.82 19.17 0 534.93 374.65 56244 +1949 171 22.04 16.04 20.39 2.28 572.24 277.67 56252 +1949 172 22.65 16.65 21 0.02 591.7 275.89 56256 +1949 173 19.47 13.47 17.82 0.51 496.08 284.47 56255 +1949 174 21.64 15.64 19.99 0.37 559.77 278.71 56249 +1949 175 22.09 16.09 20.44 0.81 573.81 277.42 56238 +1949 176 21.97 15.97 20.32 0.39 570.04 277.73 56223 +1949 177 19.62 13.62 17.97 0 500.28 378.54 56203 +1949 178 18.36 12.36 16.71 0.08 465.96 286.95 56179 +1949 179 17.77 11.77 16.12 0 450.6 384.28 56150 +1949 180 17.94 11.94 16.29 0 454.98 383.65 56116 +1949 181 12.77 6.77 11.12 0.02 336.82 297.73 56078 +1949 182 19.63 13.63 17.98 0.14 500.56 283.57 56035 +1949 183 25.11 19.11 23.46 0.81 676 267.49 55987 +1949 184 26.23 20.23 24.58 0.05 717.62 263.49 55935 +1949 185 20.88 14.88 19.23 0 536.72 373.39 55879 +1949 186 21.79 15.79 20.14 0 564.42 369.81 55818 +1949 187 21.02 15.02 19.37 0.07 540.9 279.34 55753 +1949 188 21.04 15.04 19.39 0 541.5 372.11 55684 +1949 189 20.51 14.51 18.86 0.03 525.79 280.35 55611 +1949 190 20.3 14.3 18.65 0.42 519.67 280.61 55533 +1949 191 20.6 14.6 18.95 0 528.43 372.85 55451 +1949 192 20.56 14.56 18.91 0 527.26 372.69 55366 +1949 193 22.39 16.39 20.74 0 583.34 365.72 55276 +1949 194 21.71 15.71 20.06 0 561.93 368.06 55182 +1949 195 20.01 14.01 18.36 0.19 511.32 280.35 55085 +1949 196 20.62 14.62 18.97 0 529.02 371.3 54984 +1949 197 20.07 14.07 18.42 0 513.04 372.73 54879 +1949 198 21.26 15.26 19.61 0 548.14 368.16 54770 +1949 199 23.69 17.69 22.04 0 626.18 358.44 54658 +1949 200 23.49 17.49 21.84 0.26 619.42 269.15 54542 +1949 201 21.05 15.05 19.4 0.16 541.8 275.77 54423 +1949 202 20.48 14.48 18.83 0 524.91 369.12 54301 +1949 203 20.5 14.5 18.85 0 525.5 368.55 54176 +1949 204 22.65 16.65 21 0 591.7 360.2 54047 +1949 205 22.9 16.9 21.25 0 599.84 358.71 53915 +1949 206 22.69 16.69 21.04 0.26 593 269.24 53780 +1949 207 24.15 18.15 22.5 0.25 641.97 264.34 53643 +1949 208 25.39 19.39 23.74 0.24 686.21 259.83 53502 +1949 209 25.45 19.45 23.8 0 688.41 345.55 53359 +1949 210 28.24 22.24 26.59 0.23 797.76 248.59 53213 +1949 211 30.29 24.29 28.64 0 887.15 319.46 53064 +1949 212 24.58 18.58 22.93 0.04 657.03 260.43 52913 +1949 213 23.23 17.23 21.58 0.05 610.73 264.04 52760 +1949 214 22.34 16.34 20.69 0.22 581.74 266.06 52604 +1949 215 23.85 17.85 22.2 0 631.63 348.18 52445 +1949 216 22.34 16.34 20.69 0 581.74 353.08 52285 +1949 217 22.88 16.88 21.23 0.01 599.18 262.62 52122 +1949 218 22.74 16.74 21.09 0 594.62 349.89 51958 +1949 219 26.9 20.9 25.25 0.02 743.54 248.32 51791 +1949 220 26.92 20.92 25.27 0.09 744.33 247.58 51622 +1949 221 23.5 17.5 21.85 0.57 619.76 258.02 51451 +1949 222 22.59 16.59 20.94 0.72 589.76 259.88 51279 +1949 223 25.19 19.19 23.54 0.19 678.9 251.2 51105 +1949 224 20.18 14.18 18.53 0 516.2 352.75 50929 +1949 225 17.4 11.4 15.75 0.01 441.18 269.97 50751 +1949 226 20 14 18.35 0.37 511.04 263.29 50572 +1949 227 17.99 11.99 16.34 0 456.27 355.85 50392 +1949 228 20.18 14.18 18.53 0.31 516.2 260.99 50210 +1949 229 17.96 11.96 16.31 0.78 455.5 265.09 50026 +1949 230 20.27 14.27 18.62 1.21 518.8 258.89 49842 +1949 231 18.63 12.63 16.98 1.55 473.14 261.57 49656 +1949 232 18.82 12.82 17.17 1.25 478.25 260.13 49469 +1949 233 16.21 10.21 14.56 0.03 412.03 264.4 49280 +1949 234 17.81 11.81 16.16 0 451.62 346.86 49091 +1949 235 18.35 12.35 16.7 0 465.7 343.85 48900 +1949 236 22.68 16.68 21.03 0.28 592.67 246.38 48709 +1949 237 20.07 14.07 18.42 0.03 513.04 251.74 48516 +1949 238 23.57 17.57 21.92 0.02 622.12 241.5 48323 +1949 239 25.07 19.07 23.42 0.1 674.55 235.99 48128 +1949 240 25.55 19.55 23.9 1.34 692.1 233.25 47933 +1949 241 23.68 17.68 22.03 0.3 625.84 237.58 47737 +1949 242 22.75 16.75 21.1 0.01 594.94 238.86 47541 +1949 243 23.99 17.99 22.34 0.16 636.44 234.1 47343 +1949 244 20.61 14.61 18.96 0 528.72 322.01 47145 +1949 245 24 18 22.35 0 636.78 308.58 46947 +1949 246 23.17 17.17 21.52 0 608.73 309.74 46747 +1949 247 24.13 18.13 22.48 0 641.27 304.44 46547 +1949 248 25.35 19.35 23.7 0.07 684.74 223.41 46347 +1949 249 25.77 19.77 24.12 0 700.27 294.24 46146 +1949 250 24.44 18.44 22.79 0 652.09 297.61 45945 +1949 251 20.58 14.58 18.93 0 527.84 308.61 45743 +1949 252 21.9 15.9 20.25 0 567.85 302.37 45541 +1949 253 17.82 11.82 16.17 0 451.88 312.05 45339 +1949 254 16.54 10.54 14.89 0 419.95 313.05 45136 +1949 255 18.56 12.56 16.91 0.02 471.27 229.32 44933 +1949 256 18.01 12.01 16.36 0 456.79 304.93 44730 +1949 257 12.42 6.42 10.77 0.59 329.87 236.1 44527 +1949 258 11.61 5.61 9.96 0 314.26 313.83 44323 +1949 259 12.29 6.29 10.64 0 327.32 310.16 44119 +1949 260 15.32 9.32 13.67 0 391.32 301.85 43915 +1949 261 15.14 9.14 13.49 0 387.24 299.76 43711 +1949 262 21.1 15.1 19.45 0 543.31 282.62 43507 +1949 263 28.45 22.45 26.8 0 806.56 253.89 43303 +1949 264 26.78 20.78 25.13 0 738.84 258.47 43099 +1949 265 24.45 18.45 22.8 0.04 652.44 198.67 42894 +1949 266 25.73 19.73 24.08 0.58 698.78 193.51 42690 +1949 267 21.75 15.75 20.1 0.02 563.17 201.45 42486 +1949 268 20.48 14.48 18.83 0 524.91 269.72 42282 +1949 269 21.46 15.46 19.81 0 554.23 264.57 42078 +1949 270 20.87 14.87 19.22 0 536.42 263.68 41875 +1949 271 21.55 15.55 19.9 0 557 259.27 41671 +1949 272 17.59 11.59 15.94 0 446 266.59 41468 +1949 273 18.07 12.07 16.42 0 458.35 263.02 41265 +1949 274 9.84 3.84 8.19 0 282.34 275.15 41062 +1949 275 11.71 5.71 10.06 0 316.16 269.61 40860 +1949 276 12.27 6.27 10.62 0 326.93 266.01 40658 +1949 277 14.28 8.28 12.63 0 368.25 259.97 40456 +1949 278 16.83 10.83 15.18 0 427.01 252.27 40255 +1949 279 15.53 9.53 13.88 0 396.12 252.04 40054 +1949 280 12.02 6.02 10.37 0 322.08 255.32 39854 +1949 281 14.47 8.47 12.82 0 372.37 248.63 39654 +1949 282 12.02 6.02 10.37 0 322.08 249.82 39455 +1949 283 17.48 11.48 15.83 0 443.2 237.47 39256 +1949 284 18.35 12.35 16.7 0 465.7 232.72 39058 +1949 285 17.17 11.17 15.52 0 435.41 232.56 38861 +1949 286 17.31 11.31 15.66 0 438.92 229.59 38664 +1949 287 16.71 10.71 15.06 0 424.07 227.87 38468 +1949 288 13.08 7.08 11.43 0.01 343.08 173.44 38273 +1949 289 15.8 9.8 14.15 0 402.38 224.22 38079 +1949 290 15.39 9.39 13.74 0.06 392.91 166.59 37885 +1949 291 12.93 6.93 11.28 0 340.04 223.31 37693 +1949 292 10.36 4.36 8.71 0.09 291.42 168.04 37501 +1949 293 10.05 4.05 8.4 0.76 285.98 166.26 37311 +1949 294 11.89 5.89 10.24 0 319.59 216.47 37121 +1949 295 10.31 4.31 8.66 0 290.53 215.62 36933 +1949 296 14.88 8.88 13.23 0 381.41 206.79 36745 +1949 297 17.65 11.65 16 0 447.52 199.45 36560 +1949 298 19.71 13.71 18.06 0 502.81 192.99 36375 +1949 299 20.91 14.91 19.26 0 537.61 187.83 36191 +1949 300 20.79 14.79 19.14 0.07 534.04 139.18 36009 +1949 301 18.47 12.47 16.82 0.5 468.88 140.83 35829 +1949 302 13 7 11.35 0.19 341.45 145.36 35650 +1949 303 10.79 4.79 9.14 0.06 299.11 145.48 35472 +1949 304 8.95 2.95 7.3 0.04 267.37 145.11 35296 +1949 305 5.89 -0.11 4.24 0.04 220.97 145.14 35122 +1949 306 8.31 2.31 6.66 0 257.03 189.1 34950 +1949 307 11.03 5.03 9.38 0.73 303.48 137.84 34779 +1949 308 9.99 3.99 8.34 0 284.93 182.31 34610 +1949 309 10.96 4.96 9.31 0 302.2 178.97 34444 +1949 310 7.34 1.34 5.69 0.11 242.01 135.05 34279 +1949 311 6.29 0.29 4.64 0.01 226.61 134.06 34116 +1949 312 6.31 0.31 4.66 0.05 226.89 132.05 33956 +1949 313 7.82 1.82 6.17 0 249.34 172.69 33797 +1949 314 6.48 0.48 4.83 0 229.33 171.84 33641 +1949 315 7.57 1.57 5.92 0 245.5 168.41 33488 +1949 316 6.37 0.37 4.72 0.25 227.75 125.39 33337 +1949 317 6.11 0.11 4.46 0.56 224.06 123.89 33188 +1949 318 9.15 3.15 7.5 0.84 270.67 120.25 33042 +1949 319 9.6 3.6 7.95 0.22 278.23 118.68 32899 +1949 320 13.14 7.14 11.49 0 344.3 152.78 32758 +1949 321 12.47 6.47 10.82 0 330.86 151.46 32620 +1949 322 16.95 10.95 15.3 0.55 429.96 108.13 32486 +1949 323 12.98 6.98 11.33 2.88 341.05 110.67 32354 +1949 324 9.75 3.75 8.1 0.35 280.79 111.55 32225 +1949 325 10.08 4.08 8.43 0 286.5 146.74 32100 +1949 326 9.43 3.43 7.78 0.97 275.36 109.41 31977 +1949 327 9.07 3.07 7.42 1.18 269.35 108.27 31858 +1949 328 9.7 3.7 8.05 0.76 279.94 106.4 31743 +1949 329 8.71 2.71 7.06 0.73 263.45 105.91 31631 +1949 330 9.76 3.76 8.11 1.21 280.97 104.19 31522 +1949 331 6.77 0.77 5.12 0.26 233.54 104.95 31417 +1949 332 6.93 0.93 5.28 0.29 235.89 103.64 31316 +1949 333 8.26 2.26 6.61 0.02 256.23 102.1 31218 +1949 334 7.53 1.53 5.88 0 244.89 135.58 31125 +1949 335 5.78 -0.22 4.13 0.12 219.44 101.71 31035 +1949 336 1.86 -4.14 0.21 0 170.54 136.75 30949 +1949 337 1.44 -4.56 -0.21 0.23 165.91 101.47 30867 +1949 338 4.12 -1.88 2.47 0.01 197.43 99.7 30790 +1949 339 6.52 0.52 4.87 0 229.91 130.68 30716 +1949 340 3.8 -2.2 2.15 2.4 193.42 98.69 30647 +1949 341 1.96 -4.04 0.31 0.35 171.66 98.72 30582 +1949 342 3.07 -2.93 1.42 0 184.52 130.3 30521 +1949 343 8.38 2.38 6.73 0 258.14 126.17 30465 +1949 344 9.57 3.57 7.92 0 277.72 124.15 30413 +1949 345 10.03 4.03 8.38 0 285.63 123.37 30366 +1949 346 8.54 2.54 6.89 0.17 260.7 92.98 30323 +1949 347 8.04 2.04 6.39 0 252.77 123.74 30284 +1949 348 9.02 3.02 7.37 0 268.52 122.68 30251 +1949 349 9.49 3.49 7.84 0 276.37 121.95 30221 +1949 350 11.43 5.43 9.78 0 310.88 120.03 30197 +1949 351 6.57 0.57 4.92 0 230.63 123.46 30177 +1949 352 1.64 -4.36 -0.01 0 168.1 126.07 30162 +1949 353 2.71 -3.29 1.06 0 180.26 125.49 30151 +1949 354 -2.79 -8.79 -4.44 0.08 124.99 139.85 30145 +1949 355 -2.89 -8.89 -4.54 0 124.14 171.82 30144 +1949 356 0.47 -5.53 -1.18 0 155.63 170.49 30147 +1949 357 0.19 -5.81 -1.46 0 152.76 170.63 30156 +1949 358 4.66 -1.34 3.01 0 204.37 124.59 30169 +1949 359 2.62 -3.38 0.97 0 179.21 125.79 30186 +1949 360 3.15 -2.85 1.5 0 185.47 125.89 30208 +1949 361 4.93 -1.07 3.28 0 207.92 125.25 30235 +1949 362 10.26 4.26 8.61 0 289.65 122.01 30267 +1949 363 13.28 7.28 11.63 0 347.17 119.88 30303 +1949 364 11.41 5.41 9.76 0 310.51 121.99 30343 +1949 365 12.31 6.31 10.66 0 327.71 121.73 30388 +1950 1 6.04 0.04 4.39 0.24 223.07 95.59 30438 +1950 2 5.16 -0.84 3.51 0.01 210.98 96.54 30492 +1950 3 2.23 -3.77 0.58 0 174.72 131.26 30551 +1950 4 1.57 -4.43 -0.08 0 167.33 132.49 30614 +1950 5 1.54 -4.46 -0.11 0 167 133.16 30681 +1950 6 -0.33 -6.33 -1.98 0 147.56 134.9 30752 +1950 7 0.91 -5.09 -0.74 0.01 160.22 101.36 30828 +1950 8 -3.57 -9.57 -5.22 0 118.49 138.44 30907 +1950 9 -1.59 -7.59 -3.24 0 135.6 138.98 30991 +1950 10 1.01 -4.99 -0.64 0.38 161.28 104.38 31079 +1950 11 -2.92 -8.92 -4.57 0.18 123.88 149.26 31171 +1950 12 -0.42 -6.42 -2.07 0.06 146.68 149.33 31266 +1950 13 -3.75 -9.75 -5.4 0.21 117.03 152.04 31366 +1950 14 -3.77 -9.77 -5.42 0 116.87 189.6 31469 +1950 15 -3.8 -9.8 -5.45 0.67 116.63 156.03 31575 +1950 16 -3.05 -9.05 -4.7 0.44 122.79 157.98 31686 +1950 17 -2.53 -8.53 -4.18 0.38 127.22 160.09 31800 +1950 18 -2.91 -8.91 -4.56 1.85 123.97 167.03 31917 +1950 19 -4.87 -10.87 -6.52 0 108.3 207.59 32038 +1950 20 -1.4 -7.4 -3.05 0 137.34 207.68 32161 +1950 21 1.93 -4.07 0.28 0 171.33 207.64 32289 +1950 22 -1.05 -7.05 -2.7 0 140.62 210.67 32419 +1950 23 0.09 -5.91 -1.56 0.46 151.75 171.65 32552 +1950 24 -0.25 -6.25 -1.9 0.3 148.35 174 32688 +1950 25 -1.16 -7.16 -2.81 1.26 139.58 179.21 32827 +1950 26 -1.31 -7.31 -2.96 0.1 138.18 180.78 32969 +1950 27 0.49 -5.51 -1.16 0 155.83 223.35 33114 +1950 28 2.9 -3.1 1.25 0 182.5 223.62 33261 +1950 29 3.84 -2.16 2.19 0 193.91 224.69 33411 +1950 30 5.19 -0.81 3.54 0 211.39 225.13 33564 +1950 31 1.23 -4.77 -0.42 0 163.64 229.66 33718 +1950 32 4.66 -1.34 3.01 0 204.37 228.8 33875 +1950 33 4.66 -1.34 3.01 0.41 204.37 185.77 34035 +1950 34 2.82 -3.18 1.17 0.02 181.55 187.79 34196 +1950 35 6.67 0.67 5.02 0.81 232.08 186.25 34360 +1950 36 4.41 -1.59 2.76 0 201.13 235.32 34526 +1950 37 1.87 -4.13 0.22 0 170.65 239.01 34694 +1950 38 2.3 -3.7 0.65 0.36 175.51 192.72 34863 +1950 39 5.44 -0.56 3.79 0 214.77 240.49 35035 +1950 40 5.1 -0.9 3.45 0 210.18 242.55 35208 +1950 41 6.49 0.49 4.84 0 229.48 243.04 35383 +1950 42 4.74 -1.26 3.09 0 205.42 246.28 35560 +1950 43 5.16 -0.84 3.51 0 210.98 247.84 35738 +1950 44 6.42 0.42 4.77 0 228.47 248.39 35918 +1950 45 9.91 3.91 8.26 0 283.55 246.16 36099 +1950 46 8.81 2.81 7.16 0.02 265.08 196.67 36282 +1950 47 10.8 4.8 9.15 0.13 299.29 195.67 36466 +1950 48 11.23 5.23 9.58 0 307.16 248.74 36652 +1950 49 10.03 4.03 8.38 0 285.63 251.63 36838 +1950 50 9.06 3.06 7.41 0.4 269.18 164.44 37026 +1950 51 7.89 1.89 6.24 0 250.43 223.45 37215 +1950 52 5.1 -0.9 3.45 0 210.18 228.95 37405 +1950 53 3.96 -2.04 2.31 0.22 195.41 174.67 37596 +1950 54 4.08 -1.92 2.43 0 196.93 235.56 37788 +1950 55 2.66 -3.34 1.01 0.04 179.67 179.79 37981 +1950 56 0.67 -5.33 -0.98 0 157.7 243.88 38175 +1950 57 0.11 -5.89 -1.54 0.08 151.95 185.38 38370 +1950 58 -2.77 -8.77 -4.42 0 125.16 251.89 38565 +1950 59 0.4 -5.6 -1.25 0 154.91 252.7 38761 +1950 60 12.43 6.43 10.78 0 330.07 243 38958 +1950 61 11.49 5.49 9.84 0.1 312.01 185.43 39156 +1950 62 7.68 1.68 6.03 0 247.19 254.86 39355 +1950 63 10.87 4.87 9.22 0.39 300.56 190.37 39553 +1950 64 10.87 4.87 9.22 0.02 300.56 192.52 39753 +1950 65 10.51 4.51 8.86 0.01 294.08 195.03 39953 +1950 66 11.85 5.85 10.2 0 318.82 260.79 40154 +1950 67 11.77 5.77 10.12 0 317.3 263.77 40355 +1950 68 10.97 4.97 9.32 0.05 302.38 200.84 40556 +1950 69 9.2 3.2 7.55 0.42 271.5 204.63 40758 +1950 70 9.32 3.32 7.67 0 273.51 275.51 40960 +1950 71 11.15 5.15 9.5 0 305.68 275.79 41163 +1950 72 9.56 3.56 7.91 0 277.55 280.89 41366 +1950 73 11.86 5.86 10.21 0 319.01 280.1 41569 +1950 74 8.23 2.23 6.58 0 255.76 288.05 41772 +1950 75 12.66 6.66 11.01 0 334.62 284.16 41976 +1950 76 12 6 10.35 0 321.7 287.86 42179 +1950 77 10.1 4.1 8.45 0 286.85 293.4 42383 +1950 78 4.5 -1.5 2.85 0 202.29 303.07 42587 +1950 79 4.05 -1.95 2.4 0.08 196.55 229.72 42791 +1950 80 4.73 -1.27 3.08 0.07 205.29 231.11 42996 +1950 81 9.07 3.07 7.42 0.06 269.35 229.02 43200 +1950 82 4.18 -1.82 2.53 0 198.19 314.03 43404 +1950 83 6.45 0.45 4.8 0 228.9 313.98 43608 +1950 84 11.02 5.02 9.37 0 303.3 310.03 43812 +1950 85 11.69 5.69 10.04 0 315.78 311.39 44016 +1950 86 13.45 7.45 11.8 0 350.68 310.57 44220 +1950 87 12.99 6.99 11.34 0 341.25 313.94 44424 +1950 88 12.66 6.66 11.01 0 334.62 316.87 44627 +1950 89 12.29 6.29 10.64 0 327.32 319.8 44831 +1950 90 11.23 5.23 9.58 0 307.16 324.02 45034 +1950 91 12.16 6.16 10.51 0 324.79 324.62 45237 +1950 92 15.97 9.97 14.32 0.06 406.36 239.24 45439 +1950 93 12.35 6.35 10.7 0 328.5 328.68 45642 +1950 94 8.98 2.98 7.33 0 267.86 336.53 45843 +1950 95 5.96 -0.04 4.31 0 221.95 342.89 46045 +1950 96 8.95 2.95 7.3 1.53 267.37 255.64 46246 +1950 97 7.07 1.07 5.42 0 237.97 345.66 46446 +1950 98 6.91 0.91 5.26 0 235.6 347.87 46647 +1950 99 10.58 4.58 8.93 0 295.33 344.26 46846 +1950 100 15.07 9.07 13.42 0 385.66 337.29 47045 +1950 101 16.35 10.35 14.7 0 415.37 336.16 47243 +1950 102 12.29 6.29 10.64 0 327.32 346.92 47441 +1950 103 11.57 5.57 9.92 0 313.51 350.13 47638 +1950 104 11.99 5.99 10.34 0.33 321.51 263.37 47834 +1950 105 11 5 9.35 0.06 302.93 266.1 48030 +1950 106 10.49 4.49 8.84 0 293.72 357.37 48225 +1950 107 8.58 2.58 6.93 0.98 261.35 271.68 48419 +1950 108 14.87 8.87 13.22 0.56 381.19 263.93 48612 +1950 109 16.94 10.94 15.29 0.1 429.71 261.29 48804 +1950 110 16.37 10.37 14.72 1.74 415.85 263.43 48995 +1950 111 13.33 7.33 11.68 0 348.2 359.87 49185 +1950 112 11.77 5.77 10.12 0.02 317.3 273.42 49374 +1950 113 13.57 7.57 11.92 0.57 353.17 271.65 49561 +1950 114 17.71 11.71 16.06 1.09 449.06 265.09 49748 +1950 115 17.35 11.35 15.7 0.02 439.92 266.89 49933 +1950 116 16.09 10.09 14.44 0.04 409.18 270.28 50117 +1950 117 18.9 12.9 17.25 0.36 480.41 265.4 50300 +1950 118 20.44 14.44 18.79 0.01 523.74 262.71 50481 +1950 119 18.23 12.23 16.58 0 462.54 358.29 50661 +1950 120 18.41 12.41 16.76 0 467.28 358.91 50840 +1950 121 24.46 18.46 22.81 0.37 652.79 254.01 51016 +1950 122 20.86 14.86 19.21 0 536.12 353.39 51191 +1950 123 17.44 11.44 15.79 0 442.19 364.99 51365 +1950 124 19.61 13.61 17.96 0 500 359.55 51536 +1950 125 15.54 9.54 13.89 0 396.35 372.09 51706 +1950 126 15.83 9.83 14.18 0 403.08 372.35 51874 +1950 127 18.81 12.81 17.16 0.23 477.98 273.64 52039 +1950 128 17.3 11.3 15.65 0.01 438.67 277.7 52203 +1950 129 17.01 11.01 15.36 0 431.44 371.92 52365 +1950 130 17.25 11.25 15.6 0.19 437.41 279.02 52524 +1950 131 17.93 11.93 16.28 0.76 454.72 278.15 52681 +1950 132 20.12 14.12 18.47 0 514.48 364.83 52836 +1950 133 14.04 8.04 12.39 0.32 363.09 286.95 52989 +1950 134 19.02 13.02 17.37 0.09 483.68 277.32 53138 +1950 135 16.9 10.9 15.25 0.15 428.73 282.54 53286 +1950 136 17.74 11.74 16.09 0.61 449.83 281.22 53430 +1950 137 19.24 13.24 17.59 0 489.71 371.08 53572 +1950 138 18.15 12.15 16.5 0.38 460.44 281.28 53711 +1950 139 18.61 12.61 16.96 0.7 472.61 280.75 53848 +1950 140 19.22 13.22 17.57 0 489.16 372.89 53981 +1950 141 17.88 11.88 16.23 0 453.43 377.45 54111 +1950 142 22.48 16.48 20.83 0 586.22 362.34 54238 +1950 143 22.35 16.35 20.7 0 582.06 363.36 54362 +1950 144 20.48 14.48 18.83 0 524.91 370.62 54483 +1950 145 21.28 15.28 19.63 0.56 548.75 276.2 54600 +1950 146 22.15 16.15 20.5 0 575.7 365.41 54714 +1950 147 23.44 17.44 21.79 0.48 617.74 270.6 54824 +1950 148 25.94 19.94 24.29 0.17 706.64 262.67 54931 +1950 149 25.78 19.78 24.13 0.02 700.65 263.45 55034 +1950 150 24.68 18.68 23.03 0 660.57 356.54 55134 +1950 151 22.46 16.46 20.81 0 585.58 366.06 55229 +1950 152 22.22 16.22 20.57 0 577.92 367.09 55321 +1950 153 21.94 15.94 20.29 0 569.1 368.39 55409 +1950 154 23.17 17.17 21.52 0.53 608.73 272.93 55492 +1950 155 27.27 21.27 25.62 0.01 758.19 259.14 55572 +1950 156 27.16 21.16 25.51 0.07 753.81 259.79 55648 +1950 157 25.18 19.18 23.53 0 678.54 355.98 55719 +1950 158 24.89 18.89 23.24 0 668.07 357.44 55786 +1950 159 27.97 21.97 26.32 0 786.58 342.78 55849 +1950 160 23.29 17.29 21.64 0.41 612.72 273.5 55908 +1950 161 23.04 17.04 21.39 0 604.44 365.74 55962 +1950 162 21.09 15.09 19.44 0 543 373.21 56011 +1950 163 22.95 16.95 21.3 0 601.48 366.36 56056 +1950 164 21.87 15.87 20.22 0.13 566.91 277.95 56097 +1950 165 21.09 15.09 19.44 0.08 543 280.17 56133 +1950 166 22.49 16.49 20.84 0 586.54 368.39 56165 +1950 167 24.88 18.88 23.23 0 667.71 358.38 56192 +1950 168 21.59 15.59 19.94 0 558.23 371.84 56214 +1950 169 18.02 12.02 16.37 0.01 457.05 287.87 56231 +1950 170 20.69 14.69 19.04 0 531.08 375.11 56244 +1950 171 21.27 15.27 19.62 0 548.44 373.09 56252 +1950 172 25.41 19.41 23.76 0 686.94 356.12 56256 +1950 173 25.27 19.27 23.62 0.04 681.82 267.56 56255 +1950 174 23.28 17.28 21.63 0.47 612.39 273.92 56249 +1950 175 21.01 15.01 19.36 0 540.6 373.89 56238 +1950 176 19.41 13.41 17.76 0 494.41 379.34 56223 +1950 177 22.34 16.34 20.69 0 581.74 368.79 56203 +1950 178 20.65 14.65 19 0.17 529.9 281.29 56179 +1950 179 25.77 19.77 24.12 0 700.27 354.13 56150 +1950 180 26.47 20.47 24.82 0 726.82 350.68 56116 +1950 181 24.41 18.41 22.76 0.02 651.04 270.05 56078 +1950 182 22.55 16.55 20.9 0 588.47 367.57 56035 +1950 183 24.94 18.94 23.29 0 669.86 357.42 55987 +1950 184 24.55 18.55 22.9 0.05 655.97 269.24 55935 +1950 185 24.84 18.84 23.19 0 666.28 357.64 55879 +1950 186 24.5 18.5 22.85 0.25 654.2 269.16 55818 +1950 187 23 17 21.35 0 603.12 364.95 55753 +1950 188 25.33 19.33 23.68 0 684.01 354.75 55684 +1950 189 30.55 24.55 28.9 0 899.07 327.22 55611 +1950 190 29.8 23.8 28.15 0.39 865.05 248.46 55533 +1950 191 25.71 19.71 24.06 3.5 698.04 264.17 55451 +1950 192 26.57 20.57 24.92 0 730.68 347.86 55366 +1950 193 23.29 17.29 21.64 0.2 612.72 271.62 55276 +1950 194 21.8 15.8 20.15 0.02 564.73 275.8 55182 +1950 195 20.69 14.69 19.04 0 531.08 371.46 55085 +1950 196 21.36 15.36 19.71 0 551.18 368.67 54984 +1950 197 25.18 19.18 23.53 0 678.54 352.78 54879 +1950 198 27.41 21.41 25.76 0 763.8 341.76 54770 +1950 199 28.43 22.43 26.78 0 805.71 336.14 54658 +1950 200 27.12 21.12 25.47 0.09 752.22 256.88 54542 +1950 201 25.34 19.34 23.69 0 684.38 350.48 54423 +1950 202 23.98 17.98 22.33 0.52 636.09 266.88 54301 +1950 203 21.6 15.6 19.95 0 558.54 364.65 54176 +1950 204 24.75 18.75 23.1 0.17 663.06 263.68 54047 +1950 205 28.11 22.11 26.46 0.05 792.36 251.3 53915 +1950 206 28.1 22.1 26.45 0 791.95 334.59 53780 +1950 207 27.75 21.75 26.1 0 777.56 335.78 53643 +1950 208 27.87 21.87 26.22 0.17 782.47 250.91 53502 +1950 209 25.95 19.95 24.3 0.23 707.02 257.46 53359 +1950 210 24.93 18.93 23.28 0.29 669.5 260.44 53213 +1950 211 21.27 15.27 19.62 0.25 548.44 270.7 53064 +1950 212 20.01 14.01 18.36 0 511.32 364.45 52913 +1950 213 22.15 16.15 20.5 0.24 575.7 267.14 52760 +1950 214 20.52 14.52 18.87 0.05 526.08 270.93 52604 +1950 215 18.66 12.66 17.01 0.25 473.94 274.9 52445 +1950 216 17.64 11.64 15.99 0 447.27 368.51 52285 +1950 217 20.36 14.36 18.71 0 521.41 359.2 52122 +1950 218 24.59 18.59 22.94 0.29 657.38 256.85 51958 +1950 219 21.03 15.03 19.38 0 541.2 355.07 51791 +1950 220 23.7 17.7 22.05 0 626.52 344.21 51622 +1950 221 27.04 21.04 25.39 0 749.06 328.59 51451 +1950 222 29.14 23.14 27.49 0 836.02 316.98 51279 +1950 223 29.33 23.33 27.68 0.02 844.3 236.18 51105 +1950 224 26.78 20.78 25.13 0.15 738.84 245.08 50929 +1950 225 26.96 20.96 25.31 0 745.9 324.84 50751 +1950 226 24.32 18.32 22.67 0 647.88 335.37 50572 +1950 227 27.49 21.49 25.84 0 767.02 320.04 50392 +1950 228 26.09 20.09 24.44 0 712.3 325.41 50210 +1950 229 24.4 18.4 22.75 0 650.69 331.44 50026 +1950 230 25.28 19.28 23.63 0 682.18 326.56 49842 +1950 231 26.18 20.18 24.53 0 715.72 321.24 49656 +1950 232 24.73 18.73 23.08 0.71 662.35 244.62 49469 +1950 233 25.73 19.73 24.08 0.01 698.78 240.44 49280 +1950 234 26.05 20.05 24.4 0 710.79 317.85 49091 +1950 235 25.22 19.22 23.57 0 679.99 319.99 48900 +1950 236 25.44 19.44 23.79 0 688.04 317.72 48709 +1950 237 26.57 20.57 24.92 0.28 730.68 233.44 48516 +1950 238 25.36 19.36 23.71 0.75 685.11 236.17 48323 +1950 239 18.99 12.99 17.34 0.11 482.86 251.8 48128 +1950 240 21.6 15.6 19.95 0.16 558.54 244.37 47933 +1950 241 18.98 12.98 17.33 1.51 482.59 249.22 47737 +1950 242 21.17 15.17 19.52 0.76 545.42 242.89 47541 +1950 243 21.57 15.57 19.92 0.51 557.61 240.54 47343 +1950 244 15 9 13.35 0.66 384.09 252.74 47145 +1950 245 18.87 12.87 17.22 3.03 479.6 244.01 46947 +1950 246 19.61 13.61 17.96 2.81 500 240.95 46747 +1950 247 17.42 11.42 15.77 0.69 441.69 244.07 46547 +1950 248 11.9 5.9 10.25 0 319.78 335.51 46347 +1950 249 11.99 5.99 10.34 0 321.51 333.22 46146 +1950 250 8.6 2.6 6.95 0 261.67 336.8 45945 +1950 251 10.28 4.28 8.63 0.03 290 248.99 45743 +1950 252 15.49 9.49 13.84 0 395.2 319.74 45541 +1950 253 20.11 14.11 18.46 0.66 514.19 229.35 45339 +1950 254 22.68 16.68 21.03 0.02 592.67 221.78 45136 +1950 255 20.93 14.93 19.28 0 538.21 299.08 44933 +1950 256 20.9 14.9 19.25 0.2 537.31 222.72 44730 +1950 257 20.46 14.46 18.81 0.18 524.33 222.11 44527 +1950 258 17.02 11.02 15.37 1.35 431.69 227.15 44323 +1950 259 18.89 12.89 17.24 0.01 480.14 221.84 44119 +1950 260 19.91 13.91 18.26 0 508.47 290.7 43915 +1950 261 23.92 17.92 22.27 0 634.03 275.93 43711 +1950 262 18.27 12.27 16.62 0 463.59 290.26 43507 +1950 263 20.69 14.69 19.04 0 531.08 281.41 43303 +1950 264 21.96 15.96 20.31 0.01 569.72 206.4 43099 +1950 265 20.69 14.69 19.04 0 531.08 276.62 42894 +1950 266 21.92 15.92 20.27 0.26 568.47 203 42690 +1950 267 21.29 15.29 19.64 0.16 549.05 202.45 42486 +1950 268 19.99 13.99 18.34 0.11 510.75 203.27 42282 +1950 269 20.48 14.48 18.83 0 524.91 267.28 42078 +1950 270 20.91 14.91 19.26 0 537.61 263.57 41875 +1950 271 23.95 17.95 22.3 0 635.06 252.01 41671 +1950 272 24.18 18.18 22.53 0.98 643.01 186.53 41468 +1950 273 27.93 21.93 26.28 0.35 784.93 174.71 41265 +1950 274 18.93 12.93 17.28 0 481.23 258.4 41062 +1950 275 16.28 10.28 14.63 0.62 413.7 196.13 40860 +1950 276 14.3 8.3 12.65 0.81 368.68 196.94 40658 +1950 277 9.3 3.3 7.65 0.25 273.17 200.69 40456 +1950 278 11.81 5.81 10.16 0.21 318.06 195.86 40255 +1950 279 8.05 2.05 6.4 0.03 252.93 197.51 40054 +1950 280 11.66 5.66 10.01 0.32 315.21 191.89 39854 +1950 281 10 4 8.35 0 285.11 255.42 39654 +1950 282 8.54 2.54 6.89 0.1 260.7 190.85 39455 +1950 283 4.78 -1.22 3.13 0.45 205.94 191.67 39256 +1950 284 5 -1 3.35 0.5 208.85 189.19 39058 +1950 285 4.2 -1.8 2.55 1.34 198.45 187.69 38861 +1950 286 2.1 -3.9 0.45 0.65 173.24 186.85 38664 +1950 287 4.7 -1.3 3.05 0.13 204.89 182.96 38468 +1950 288 9.02 3.02 7.37 1.47 268.52 177.5 38273 +1950 289 11.06 5.06 9.41 0.03 304.03 173.6 38079 +1950 290 8.5 2.5 6.85 0.15 260.06 173.76 37885 +1950 291 9.33 3.33 7.68 0.1 273.67 171 37693 +1950 292 10.95 4.95 9.3 0 302.02 223.32 37501 +1950 293 10.03 4.03 8.38 0 285.63 221.71 37311 +1950 294 11.14 5.14 9.49 0.03 305.5 163.08 37121 +1950 295 10.71 4.71 9.06 0 297.67 215.14 36933 +1950 296 15.88 9.88 14.23 0 404.24 205.18 36745 +1950 297 15.13 9.13 13.48 0.07 387.01 152.79 36560 +1950 298 15.22 9.22 13.57 0 389.05 201.02 36375 +1950 299 17.26 11.26 15.61 0 437.66 194.93 36191 +1950 300 17.32 11.32 15.67 0.26 439.17 144.19 36009 +1950 301 19.11 13.11 17.46 0 486.14 186.57 35829 +1950 302 23.05 17.05 21.4 1.8 604.77 131.79 35650 +1950 303 15.86 9.86 14.21 0.52 403.78 140.38 35472 +1950 304 14.01 8.01 12.36 0.2 362.45 140.61 35296 +1950 305 10.07 4.07 8.42 0 286.32 189.57 35122 +1950 306 12.56 6.56 10.91 0.01 332.64 138.35 34950 +1950 307 7.17 1.17 5.52 0 239.46 187.62 34779 +1950 308 7.88 1.88 6.23 0 250.27 184.36 34610 +1950 309 8.8 2.8 7.15 0 264.91 181.18 34444 +1950 310 9.36 3.36 7.71 0.07 274.18 133.65 34279 +1950 311 10.46 4.46 8.81 0 293.19 174.92 34116 +1950 312 11.14 5.14 9.49 0 305.5 171.58 33956 +1950 313 12.3 6.3 10.65 0.68 327.52 126.16 33797 +1950 314 14.23 8.23 12.58 0.02 367.17 122.98 33641 +1950 315 15.04 9.04 13.39 0.02 384.99 120.33 33488 +1950 316 13.66 7.66 12.01 0.91 355.05 120.05 33337 +1950 317 10.54 4.54 8.89 2 294.62 121.01 33188 +1950 318 8.08 2.08 6.43 0 253.4 161.27 33042 +1950 319 6.44 0.44 4.79 0.41 228.76 120.66 32899 +1950 320 5.64 -0.36 3.99 1.13 217.5 119.69 32758 +1950 321 2.79 -3.21 1.14 2.32 181.2 119.48 32620 +1950 322 1.55 -4.45 -0.1 0.28 167.11 118.62 32486 +1950 323 1.26 -4.74 -0.39 0.28 163.96 117.5 32354 +1950 324 4.89 -1.11 3.24 0.18 207.39 114.35 32225 +1950 325 4.7 -1.3 3.05 0.01 204.89 113.15 32100 +1950 326 9.31 3.31 7.66 0 273.34 145.98 31977 +1950 327 8.67 2.67 7.02 0.4 262.8 108.51 31858 +1950 328 7.65 1.65 6 0.7 246.72 107.65 31743 +1950 329 7.96 1.96 6.31 0.39 251.52 106.35 31631 +1950 330 7.99 1.99 6.34 0.16 251.99 105.26 31522 +1950 331 6.08 0.08 4.43 0.38 223.63 105.3 31417 +1950 332 5.22 -0.78 3.57 0 211.79 139.33 31316 +1950 333 7.56 1.56 5.91 0 245.35 136.65 31218 +1950 334 11.08 5.08 9.43 0.1 304.4 99.53 31125 +1950 335 5.39 -0.61 3.74 0 214.09 135.86 31035 +1950 336 7.6 1.6 5.95 0.02 245.96 99.98 30949 +1950 337 5.72 -0.28 4.07 0.12 218.61 99.69 30867 +1950 338 5.13 -0.87 3.48 0.13 210.58 99.26 30790 +1950 339 4.18 -1.82 2.53 0 198.19 132.11 30716 +1950 340 0.15 -5.85 -1.5 0.01 152.36 100.04 30647 +1950 341 4.92 -1.08 3.27 0 207.79 130.03 30582 +1950 342 5.17 -0.83 3.52 0 211.12 129.12 30521 +1950 343 7.13 1.13 5.48 0 238.86 127.05 30465 +1950 344 7.46 1.46 5.81 0 243.83 125.7 30413 +1950 345 5.27 -0.73 3.62 0 212.46 126.68 30366 +1950 346 5.94 -0.06 4.29 0.05 221.67 94.3 30323 +1950 347 6.56 0.56 4.91 2.74 230.49 93.56 30284 +1950 348 7.67 1.67 6.02 0.43 247.03 92.74 30251 +1950 349 4.71 -1.29 3.06 0 205.02 125.14 30221 +1950 350 2.33 -3.67 0.68 0 175.86 126.06 30197 +1950 351 0.91 -5.09 -0.74 0.08 160.22 94.87 30177 +1950 352 -0.15 -6.15 -1.8 0.27 149.35 139.76 30162 +1950 353 1.17 -4.83 -0.48 0.54 162.99 139.15 30151 +1950 354 2.68 -3.32 1.03 0.67 179.91 138.24 30145 +1950 355 -1.58 -7.58 -3.23 0.68 135.69 141.78 30144 +1950 356 -1.55 -7.55 -3.2 0.07 135.96 142.01 30147 +1950 357 1.52 -4.48 -0.13 0 166.78 172.41 30156 +1950 358 4.44 -1.56 2.79 0 201.52 170.41 30169 +1950 359 5.3 -0.7 3.65 0 212.87 169.3 30186 +1950 360 7.4 1.4 5.75 2.01 242.92 136.47 30208 +1950 361 4.1 -1.9 2.45 0.11 197.18 94.29 30235 +1950 362 2.46 -3.54 0.81 0 177.35 127.01 30267 +1950 363 -0.38 -6.38 -2.03 0.38 147.07 141.42 30303 +1950 364 1 -5 -0.65 0.14 161.18 141.09 30343 +1950 365 1.14 -4.86 -0.51 0.95 162.67 141.25 30388 +1951 1 2.08 -3.92 0.43 1.6 173.01 141.24 30438 +1951 2 -2.95 -8.95 -4.6 0.56 123.63 145.04 30492 +1951 3 -0.1 -6.1 -1.75 0 149.84 177.93 30551 +1951 4 -0.02 -6.02 -1.67 0 150.64 178.72 30614 +1951 5 -0.16 -6.16 -1.81 0 149.25 179.34 30681 +1951 6 4.75 -1.25 3.1 0.08 205.55 143.94 30752 +1951 7 5.14 -0.86 3.49 0.29 210.72 143.57 30828 +1951 8 7.28 1.28 5.63 0.19 241.11 142.57 30907 +1951 9 9.04 3.04 7.39 0.75 268.85 99.67 30991 +1951 10 6.06 0.06 4.41 0.09 223.35 102.25 31079 +1951 11 3.47 -2.53 1.82 0 189.35 138.9 31171 +1951 12 -0.57 -6.57 -2.22 0 145.22 141.9 31266 +1951 13 -0.68 -6.68 -2.33 0.01 144.15 149.8 31366 +1951 14 -1.42 -7.42 -3.07 0 137.16 187.37 31469 +1951 15 2.01 -3.99 0.36 0 172.22 145.25 31575 +1951 16 4.09 -1.91 2.44 0.69 197.05 109.03 31686 +1951 17 5.92 -0.08 4.27 0 221.39 145.88 31800 +1951 18 5.19 -0.81 3.54 0 211.39 148.26 31917 +1951 19 2.51 -3.49 0.86 0 177.93 151.81 32038 +1951 20 8.5 2.5 6.85 0 260.06 149.3 32161 +1951 21 8.71 2.71 7.06 0 263.45 151.11 32289 +1951 22 12.36 6.36 10.71 0.04 328.69 112.02 32419 +1951 23 6.73 0.73 5.08 0.19 232.96 117.12 32552 +1951 24 7.05 1.05 5.4 0.01 237.67 118.48 32688 +1951 25 2.02 -3.98 0.37 0 172.34 163.19 32827 +1951 26 5.98 -0.02 4.33 0.07 222.23 121.92 32969 +1951 27 4.94 -1.06 3.29 0 208.05 165.32 33114 +1951 28 5.62 -0.38 3.97 0 217.23 167.03 33261 +1951 29 7.38 1.38 5.73 0.7 242.61 126.02 33411 +1951 30 8.87 2.87 7.22 0.17 266.06 126.71 33564 +1951 31 7.72 1.72 6.07 0 247.8 172.31 33718 +1951 32 6.27 0.27 4.62 0 226.32 175.6 33875 +1951 33 8.66 2.66 7.01 0 262.64 176.15 34035 +1951 34 9.38 3.38 7.73 0 274.51 177.64 34196 +1951 35 8.38 2.38 6.73 0 258.14 180.7 34360 +1951 36 9.01 3.01 7.36 0 268.36 182.58 34526 +1951 37 5.63 -0.37 3.98 0.17 217.37 140.98 34694 +1951 38 2.61 -3.39 0.96 0.75 179.09 144.68 34863 +1951 39 5.4 -0.6 3.75 0.01 214.22 145.12 35035 +1951 40 6.95 0.95 5.3 0 236.19 194.79 35208 +1951 41 5.89 -0.11 4.24 0.13 220.97 148.73 35383 +1951 42 5.81 -0.19 4.16 0 219.85 200.92 35560 +1951 43 7.24 1.24 5.59 0 240.5 202.35 35738 +1951 44 8 2 6.35 0 252.14 204.16 35918 +1951 45 6.45 0.45 4.8 0.1 228.9 156.17 36099 +1951 46 5.24 -0.76 3.59 0.02 212.06 158.97 36282 +1951 47 7.15 1.15 5.5 0.03 239.16 159.79 36466 +1951 48 10.12 4.12 8.47 0.25 287.2 159.51 36652 +1951 49 11.49 5.49 9.84 0 312.01 213.73 36838 +1951 50 13.32 7.32 11.67 0.08 347.99 160.37 37026 +1951 51 10.6 4.6 8.95 0.6 295.69 165.28 37215 +1951 52 9.68 3.68 8.03 0.25 279.6 168.2 37405 +1951 53 5.31 -0.69 3.66 0.04 213 173.8 37596 +1951 54 8.84 2.84 7.19 1.18 265.57 173.16 37788 +1951 55 7.44 1.44 5.79 0 243.52 235.39 37981 +1951 56 6.26 0.26 4.61 0 226.18 239.27 38175 +1951 57 5.83 -0.17 4.18 0.14 220.13 181.93 38370 +1951 58 3.99 -2.01 2.34 0.88 195.79 185.4 38565 +1951 59 2.21 -3.79 0.56 0.15 174.49 188.54 38761 +1951 60 2.45 -3.55 0.8 0.8 177.24 190.58 38958 +1951 61 6.81 0.81 5.16 2.01 234.13 189.77 39156 +1951 62 5.64 -0.36 3.99 0.17 217.5 192.77 39355 +1951 63 1.49 -4.51 -0.16 0 166.46 263.69 39553 +1951 64 0.17 -5.83 -1.48 0.03 152.56 200.71 39753 +1951 65 1.09 -4.91 -0.56 0 162.13 269.87 39953 +1951 66 5.53 -0.47 3.88 0 215.99 268.72 40154 +1951 67 5.92 -0.08 4.27 0.29 221.39 203.42 40355 +1951 68 5 -1 3.35 0 208.85 275.06 40556 +1951 69 8.82 2.82 7.17 0 265.24 273.34 40758 +1951 70 6.96 0.96 5.31 0.15 236.34 208.83 40960 +1951 71 5.83 -0.17 4.18 0.25 220.13 211.97 41163 +1951 72 5.76 -0.24 4.11 0.08 219.16 214.16 41366 +1951 73 6.44 0.44 4.79 0 228.76 287.47 41569 +1951 74 8.68 2.68 7.03 0 262.96 287.46 41772 +1951 75 12.33 6.33 10.68 0 328.11 284.72 41976 +1951 76 16.38 10.38 14.73 0 416.09 279.6 42179 +1951 77 12.86 6.86 11.21 0.72 338.63 216.72 42383 +1951 78 9.23 3.23 7.58 0.6 272 222.98 42587 +1951 79 7.5 1.5 5.85 0 244.43 302.35 42791 +1951 80 6.63 0.63 4.98 0 231.5 305.98 42996 +1951 81 7.93 1.93 6.28 0.06 251.05 230.19 43200 +1951 82 9.79 3.79 8.14 0.06 281.48 230.22 43404 +1951 83 12.31 6.31 10.66 0.28 327.71 229 43608 +1951 84 13.02 7.02 11.37 0.28 341.86 229.92 43812 +1951 85 8.48 2.48 6.83 0.19 259.74 237.28 44016 +1951 86 9.27 3.27 7.62 0.04 272.67 238.24 44220 +1951 87 13.43 7.43 11.78 0.48 350.26 234.82 44424 +1951 88 7.85 1.85 6.2 0.81 249.81 243.43 44627 +1951 89 5.4 -0.6 3.75 0.04 214.22 247.5 44831 +1951 90 9.7 3.7 8.05 0.23 279.94 244.89 45034 +1951 91 9.35 3.35 7.7 0 274.01 329.32 45237 +1951 92 8.99 2.99 7.34 0 268.03 332.12 45439 +1951 93 9.67 3.67 8.02 0 279.43 333.29 45642 +1951 94 8.97 2.97 7.32 0 267.7 336.54 45843 +1951 95 11.11 5.11 9.46 0 304.95 335.2 46045 +1951 96 16.27 10.27 14.62 0.06 413.46 245.01 46246 +1951 97 12.89 6.89 11.24 0 339.23 336.05 46446 +1951 98 14.07 8.07 12.42 0.45 363.73 251.69 46647 +1951 99 12.38 6.38 10.73 1.59 329.09 255.74 46846 +1951 100 10.67 4.67 9.02 0.11 296.95 259.55 47045 +1951 101 13.57 7.57 11.92 0 353.17 342.46 47243 +1951 102 14.9 8.9 13.25 0 381.86 341.45 47441 +1951 103 15.64 9.64 13.99 0 398.66 341.54 47638 +1951 104 17.03 11.03 15.38 0.07 431.94 254.91 47834 +1951 105 19.5 13.5 17.85 0 496.92 334.73 48030 +1951 106 17.26 11.26 15.61 0 437.66 342.63 48225 +1951 107 14.95 8.95 13.3 0 382.97 350 48419 +1951 108 11.68 5.68 10.03 0 315.59 358.62 48612 +1951 109 10.82 4.82 9.17 0 299.65 361.84 48804 +1951 110 10.81 4.81 9.16 0.11 299.47 272.46 48995 +1951 111 14.87 8.87 13.22 0 381.19 356.43 49185 +1951 112 11.72 5.72 10.07 0 316.34 364.66 49374 +1951 113 11.03 5.03 9.38 0 303.48 367.33 49561 +1951 114 13.04 7.04 11.39 0 342.26 364.83 49748 +1951 115 13.7 7.7 12.05 0 355.89 364.84 49933 +1951 116 11.63 5.63 9.98 0 314.64 370.36 50117 +1951 117 14.86 8.86 13.21 0 380.96 364.7 50300 +1951 118 15.35 9.35 13.7 0 392 364.82 50481 +1951 119 16.1 10.1 14.45 0 409.42 364.12 50661 +1951 120 14.77 8.77 13.12 0.09 378.97 276.43 50840 +1951 121 17.01 11.01 15.36 0.24 431.44 272.99 51016 +1951 122 16.14 10.14 14.49 0.02 410.37 275.61 51191 +1951 123 19.19 13.19 17.54 0 488.33 359.82 51365 +1951 124 19.59 13.59 17.94 0.11 499.44 269.71 51536 +1951 125 17.12 11.12 15.47 0 434.17 367.92 51706 +1951 126 21.86 15.86 20.21 0 566.6 353.79 51874 +1951 127 16.42 10.42 14.77 0.75 417.05 278.76 52039 +1951 128 19.23 13.23 17.58 0 489.43 364.52 52203 +1951 129 19.3 13.3 17.65 0.25 491.36 273.85 52365 +1951 130 21.02 15.02 19.37 0.01 540.9 270.14 52524 +1951 131 18.73 12.73 17.08 0.01 475.82 276.35 52681 +1951 132 22.18 16.18 20.53 0.24 576.65 268.16 52836 +1951 133 20.39 14.39 18.74 1.05 522.29 273.45 52989 +1951 134 21.29 15.29 19.64 0.52 549.05 271.62 53138 +1951 135 15.73 9.73 14.08 1.75 400.75 284.89 53286 +1951 136 16.34 10.34 14.69 2.16 415.13 284.16 53430 +1951 137 13.73 7.73 12.08 1.83 356.52 289.58 53572 +1951 138 14.73 8.73 13.08 0.19 378.08 288.25 53711 +1951 139 15.07 9.07 13.42 0.21 385.66 288.14 53848 +1951 140 12.57 6.57 10.92 0.46 332.83 292.87 53981 +1951 141 12.64 6.64 10.99 0.09 334.22 293.1 54111 +1951 142 13.5 7.5 11.85 0.62 351.71 292.04 54238 +1951 143 14.06 8.06 12.41 0.3 363.52 291.47 54362 +1951 144 10.81 4.81 9.16 0 299.47 396.1 54483 +1951 145 10.51 4.51 8.86 0 294.08 397.17 54600 +1951 146 11.35 5.35 9.7 0 309.39 395.91 54714 +1951 147 17.53 11.53 15.88 0.02 444.47 285.98 54824 +1951 148 16.71 10.71 15.06 0.47 424.07 288.02 54931 +1951 149 20.1 14.1 18.45 1.2 513.9 280.43 55034 +1951 150 20.71 14.71 19.06 0 531.67 372.13 55134 +1951 151 21.12 15.12 19.47 0 543.91 371.06 55229 +1951 152 24.04 18.04 22.39 0 638.16 359.77 55321 +1951 153 18.51 12.51 16.86 0.08 469.94 285.1 55409 +1951 154 18 12 16.35 0.04 456.53 286.5 55492 +1951 155 19.99 13.99 18.34 0.52 510.75 281.88 55572 +1951 156 22.79 16.79 21.14 0.49 596.25 274.44 55648 +1951 157 25.1 19.1 23.45 1.03 675.64 267.25 55719 +1951 158 24.83 18.83 23.18 0.71 665.92 268.28 55786 +1951 159 21.51 15.51 19.86 3.15 555.77 278.53 55849 +1951 160 22.04 16.04 20.39 1.14 572.24 277.18 55908 +1951 161 17.71 11.71 16.06 2.24 449.06 288.17 55962 +1951 162 15.77 9.77 14.12 0.4 401.68 292.3 56011 +1951 163 17.73 11.73 16.08 0.15 449.57 288.33 56056 +1951 164 17.21 11.21 15.56 0.56 436.41 289.51 56097 +1951 165 14.6 8.6 12.95 0 375.22 393.08 56133 +1951 166 15.81 9.81 14.16 0 402.61 390.06 56165 +1951 167 15.09 9.09 13.44 0 386.11 391.88 56192 +1951 168 17.21 11.21 15.56 0 436.41 386.21 56214 +1951 169 18.55 12.55 16.9 0.74 471 286.65 56231 +1951 170 19.12 13.12 17.47 0 486.41 380.4 56244 +1951 171 21.88 15.88 20.23 0 567.22 370.83 56252 +1951 172 25.47 19.47 23.82 0.04 689.15 266.88 56256 +1951 173 25.15 19.15 23.5 0 677.45 357.29 56255 +1951 174 25.72 19.72 24.07 0.32 698.41 265.94 56249 +1951 175 25.31 19.31 23.66 0 683.28 356.45 56238 +1951 176 25.2 19.2 23.55 0.2 679.27 267.69 56223 +1951 177 26.24 20.24 24.59 0.05 718 263.98 56203 +1951 178 25.19 19.19 23.54 0.92 678.9 267.67 56179 +1951 179 22.67 16.67 21.02 0.24 592.35 275.57 56150 +1951 180 24.19 18.19 22.54 0.12 643.35 270.81 56116 +1951 181 22.39 16.39 20.74 0.26 583.34 276.25 56078 +1951 182 26.93 20.93 25.28 1.13 744.72 261.17 56035 +1951 183 26.91 20.91 25.26 0.1 743.94 261.12 55987 +1951 184 25.65 19.65 24 0 695.8 354.05 55935 +1951 185 24.82 18.82 23.17 0.01 665.56 268.29 55879 +1951 186 25.54 19.54 23.89 0.4 691.73 265.67 55818 +1951 187 24.67 18.67 23.02 0.32 660.22 268.47 55753 +1951 188 26.85 20.85 25.2 0.05 741.58 260.67 55684 +1951 189 26.58 20.58 24.93 0.03 731.07 261.53 55611 +1951 190 27.51 21.51 25.86 0 767.83 343.72 55533 +1951 191 25.89 19.89 24.24 0 704.76 351.39 55451 +1951 192 31.53 25.53 29.88 0 945.21 320.34 55366 +1951 193 29.45 23.45 27.8 0 849.56 332.51 55276 +1951 194 25.31 19.31 23.66 0.17 683.28 264.97 55182 +1951 195 26.52 20.52 24.87 0 728.75 347.38 55085 +1951 196 21.39 15.39 19.74 0 552.1 368.56 54984 +1951 197 22.9 16.9 21.25 0 599.84 362.39 54879 +1951 198 20.59 14.59 18.94 1.08 528.14 277.9 54770 +1951 199 17.88 11.88 16.23 2.34 453.43 284.16 54658 +1951 200 17.41 11.41 15.76 0.59 441.43 284.88 54542 +1951 201 17.75 11.75 16.1 1.23 450.08 283.78 54423 +1951 202 15.79 9.79 14.14 1.42 402.14 287.43 54301 +1951 203 14.49 8.49 12.84 1.23 372.81 289.5 54176 +1951 204 15.42 9.42 13.77 0.73 393.6 287.37 54047 +1951 205 12.06 6.06 10.41 0 322.85 390.39 53915 +1951 206 13.53 7.53 11.88 0.01 352.34 289.95 53780 +1951 207 18.83 12.83 17.18 0 478.52 371.75 53643 +1951 208 18.03 12.03 16.38 0.01 457.31 280.14 53502 +1951 209 19.94 13.94 18.29 0 509.33 366.88 53359 +1951 210 18.73 12.73 17.08 0.35 475.82 277.58 53213 +1951 211 20.6 14.6 18.95 0.05 528.43 272.45 53064 +1951 212 25.84 19.84 24.19 0.23 702.89 256.26 52913 +1951 213 24.78 18.78 23.13 0.04 664.13 259.24 52760 +1951 214 21.07 15.07 19.42 0 542.4 359.35 52604 +1951 215 16.17 10.17 14.52 0 411.08 373.58 52445 +1951 216 16.42 10.42 14.77 0 417.05 371.88 52285 +1951 217 15.65 9.65 14 0 398.89 372.98 52122 +1951 218 22.01 16.01 20.36 0.05 571.29 264.46 51958 +1951 219 22.35 16.35 20.7 0 582.06 350.33 51791 +1951 220 18.98 12.98 17.33 0 482.59 360.81 51622 +1951 221 19.69 13.69 18.04 0.72 502.24 268.19 51451 +1951 222 19.06 13.06 17.41 0.05 484.77 268.88 51279 +1951 223 21.95 15.95 20.3 0.08 569.41 260.8 51105 +1951 224 21.63 15.63 19.98 0 559.46 347.83 50929 +1951 225 21.96 15.96 20.31 0 569.72 345.53 50751 +1951 226 21.84 15.84 20.19 0 565.97 344.83 50572 +1951 227 22.62 16.62 20.97 0 590.73 340.74 50392 +1951 228 24.62 18.62 22.97 0 658.44 331.73 50210 +1951 229 24.43 18.43 22.78 0 651.74 331.32 50026 +1951 230 28.23 22.23 26.58 0 797.35 312.94 49842 +1951 231 25.26 19.26 23.61 0.5 681.45 243.93 49656 +1951 232 25.55 19.55 23.9 0 692.1 322.71 49469 +1951 233 26.91 20.91 25.26 0 743.94 315.32 49280 +1951 234 26.85 20.85 25.2 0 741.58 314.27 49091 +1951 235 26.62 20.62 24.97 1.19 732.62 235.44 48900 +1951 236 27.16 21.16 25.51 0.3 753.81 232.59 48709 +1951 237 23.75 17.75 22.1 0 628.22 322.93 48516 +1951 238 20.71 14.71 19.06 0 531.67 331.98 48323 +1951 239 23.95 17.95 22.3 0.02 635.06 239.32 48128 +1951 240 24.99 18.99 23.34 0.2 671.66 234.98 47933 +1951 241 25.28 19.28 23.63 0.3 682.18 232.86 47737 +1951 242 26.35 20.35 24.7 0 722.21 304.34 47541 +1951 243 25.48 19.48 23.83 0 689.52 306.25 47343 +1951 244 22.25 16.25 20.6 0.02 578.87 237.48 47145 +1951 245 20.95 14.95 19.3 0.05 538.81 239.35 46947 +1951 246 22.53 16.53 20.88 0 587.83 311.98 46747 +1951 247 20.19 14.19 18.54 0.8 516.49 238.29 46547 +1951 248 18.82 12.82 17.17 0 478.25 319.75 46347 +1951 249 20.35 14.35 18.7 0.11 521.12 234.97 46146 +1951 250 21.63 15.63 19.98 0.76 559.46 230.55 45945 +1951 251 20.55 14.55 18.9 1.94 526.96 231.53 45743 +1951 252 17.48 11.48 15.83 0 443.2 315.02 45541 +1951 253 13.63 7.63 11.98 0 354.42 321.52 45339 +1951 254 18.46 12.46 16.81 0 468.61 308.26 45136 +1951 255 18.49 12.49 16.84 0 469.41 305.95 44933 +1951 256 23.06 17.06 21.41 0.21 605.1 217.56 44730 +1951 257 21.67 15.67 20.02 1.53 560.7 219.38 44527 +1951 258 21.35 15.35 19.7 0 550.88 291.22 44323 +1951 259 24.56 18.56 22.91 0 656.32 278.25 44119 +1951 260 21.79 15.79 20.14 0.02 564.42 213.91 43915 +1951 261 24.36 18.36 22.71 0.07 649.28 205.8 43711 +1951 262 26.16 20.16 24.51 0 714.96 265.54 43507 +1951 263 26.9 20.9 25.25 0 743.54 260.36 43303 +1951 264 19.7 13.7 18.05 0 502.53 281.63 43099 +1951 265 16.46 10.46 14.81 0 418.01 287.14 42894 +1951 266 17.44 11.44 15.79 0 442.19 282.47 42690 +1951 267 17.46 11.46 15.81 0 442.7 279.78 42486 +1951 268 16.34 10.34 14.69 0.18 415.13 209.79 42282 +1951 269 18.69 12.69 17.04 1.37 474.75 203.9 42078 +1951 270 18.95 12.95 17.3 0.01 481.77 201.49 41875 +1951 271 20.35 14.35 18.7 1.27 521.12 196.91 41671 +1951 272 19.73 13.73 18.08 0 503.37 261.5 41468 +1951 273 17.55 11.55 15.9 0 444.98 264.19 41265 +1951 274 11.86 5.86 10.21 0 319.01 272.17 41062 +1951 275 14.19 8.19 12.54 0 366.3 265.49 40860 +1951 276 12.98 6.98 11.33 0 341.05 264.86 40658 +1951 277 12.21 6.21 10.56 0 325.76 263.42 40456 +1951 278 12.3 6.3 10.65 0 327.52 260.39 40255 +1951 279 16.25 10.25 14.6 0 412.98 250.66 40054 +1951 280 11.81 5.81 10.16 0 318.06 255.63 39854 +1951 281 10.79 4.79 9.14 0 299.11 254.35 39654 +1951 282 14.91 8.91 13.26 0 382.08 245.13 39455 +1951 283 12.84 6.84 11.19 0 338.22 245.75 39256 +1951 284 10.66 4.66 9.01 0 296.77 245.86 39058 +1951 285 7.34 1.34 5.69 0 242.01 247.18 38861 +1951 286 9.53 3.53 7.88 0 277.05 241.85 38664 +1951 287 8.75 2.75 7.1 0 264.1 239.8 38468 +1951 288 16.43 10.43 14.78 0 417.29 225.67 38273 +1951 289 12.17 6.17 10.52 0 324.99 229.95 38079 +1951 290 7.93 1.93 6.28 0 251.05 232.31 37885 +1951 291 8.16 2.16 6.51 0 254.65 229.32 37693 +1951 292 5.38 -0.62 3.73 0 213.95 229.32 37501 +1951 293 6.6 0.6 4.95 0 231.07 225.4 37311 +1951 294 3.51 -2.49 1.86 0.01 189.84 168.85 37121 +1951 295 2.76 -3.24 1.11 0 180.85 222.79 36933 +1951 296 3.31 -2.69 1.66 0 187.4 219.72 36745 +1951 297 8.51 2.51 6.86 0 260.22 212.29 36560 +1951 298 15.81 9.81 14.16 0.06 402.61 150.06 36375 +1951 299 17.32 11.32 15.67 0 439.17 194.83 36191 +1951 300 15.23 9.23 13.58 0 389.27 195.67 36009 +1951 301 16.75 10.75 15.1 0 425.05 190.79 35829 +1951 302 17.86 11.86 16.21 0.37 452.91 139.77 35650 +1951 303 20.99 14.99 19.34 0.01 540 133.43 35472 +1951 304 22.16 16.16 20.51 0 576.02 173.09 35296 +1951 305 19.71 13.71 18.06 0 502.81 175.54 35122 +1951 306 16.1 10.1 14.45 0 409.42 179.57 34950 +1951 307 18 12 16.35 0 456.53 174.09 34779 +1951 308 18.77 12.77 17.12 0 476.9 170.27 34610 +1951 309 16.93 10.93 15.28 0.26 429.47 128.33 34444 +1951 310 13.05 7.05 11.4 0.06 342.47 130.6 34279 +1951 311 13.14 7.14 11.49 0 344.3 171.89 34116 +1951 312 10.32 4.32 8.67 0.1 290.71 129.33 33956 +1951 313 7.97 1.97 6.32 0.27 251.67 129.42 33797 +1951 314 6.04 0.04 4.39 1.96 223.07 129.13 33641 +1951 315 5.29 -0.71 3.64 0.04 212.73 127.64 33488 +1951 316 3.52 -2.48 1.87 1.17 189.96 126.89 33337 +1951 317 4.59 -1.41 2.94 0 203.46 166.27 33188 +1951 318 9.83 3.83 8.18 0 282.17 159.71 33042 +1951 319 10.87 4.87 9.22 0.88 300.56 117.77 32899 +1951 320 9.78 3.78 8.13 0.23 281.31 117.17 32758 +1951 321 7.38 1.38 5.73 0.34 242.61 117.13 32620 +1951 322 7.9 1.9 6.25 0.06 250.58 115.46 32486 +1951 323 10.34 4.34 8.69 0 291.06 150.23 32354 +1951 324 12.7 6.7 11.05 0.51 335.42 109.39 32225 +1951 325 9.73 3.73 8.08 0.57 280.45 110.29 32100 +1951 326 9.21 3.21 7.56 0 271.67 146.07 31977 +1951 327 9.82 3.82 8.17 0 282 143.71 31858 +1951 328 11.11 5.11 9.46 0 304.95 140.6 31743 +1951 329 14.7 8.7 13.05 0.22 377.42 101.53 31631 +1951 330 9.61 3.61 7.96 0 278.4 139.04 31522 +1951 331 3.81 -2.19 2.16 0.09 193.54 106.37 31417 +1951 332 6.62 0.62 4.97 0.01 231.36 103.8 31316 +1951 333 7.84 1.84 6.19 0.16 249.65 102.33 31218 +1951 334 9.2 3.2 7.55 0 271.5 134.31 31125 +1951 335 5.15 -0.85 3.5 0 210.85 136.01 31035 +1951 336 0.62 -5.38 -1.03 0 157.18 137.34 30949 +1951 337 -0.49 -6.49 -2.14 0 145.99 136.15 30867 +1951 338 1.23 -4.77 -0.42 0 163.64 134.44 30790 +1951 339 4.18 -1.82 2.53 0 198.19 132.11 30716 +1951 340 3.61 -2.39 1.96 0 191.06 131.7 30647 +1951 341 1.5 -4.5 -0.15 0.07 166.57 98.88 30582 +1951 342 -0.34 -6.34 -1.99 0 147.46 131.89 30521 +1951 343 -3.41 -9.41 -5.06 0 119.8 132.2 30465 +1951 344 -0.42 -6.42 -2.07 0 146.68 129.95 30413 +1951 345 3.08 -2.92 1.43 0 184.64 127.9 30366 +1951 346 6.32 0.32 4.67 0 227.04 125.49 30323 +1951 347 7.51 1.51 5.86 0 244.59 124.11 30284 +1951 348 9.98 3.98 8.33 0 284.76 121.94 30251 +1951 349 6.49 0.49 4.84 0.07 229.48 93.05 30221 +1951 350 10.09 4.09 8.44 0.2 286.67 90.86 30197 +1951 351 9.86 3.86 8.21 0.55 282.68 90.84 30177 +1951 352 4.45 -1.55 2.8 0.06 201.65 93.48 30162 +1951 353 5.25 -0.75 3.6 0 212.19 124.12 30151 +1951 354 6.63 0.63 4.98 0.01 231.5 92.43 30145 +1951 355 10.44 4.44 8.79 0 292.83 120.47 30144 +1951 356 7.45 1.45 5.8 0 243.67 122.72 30147 +1951 357 7.83 1.83 6.18 0 249.5 122.52 30156 +1951 358 3.7 -2.3 2.05 0.1 192.17 93.84 30169 +1951 359 7.49 1.49 5.84 0 244.28 122.95 30186 +1951 360 4.97 -1.03 3.32 0 208.45 124.9 30208 +1951 361 6.19 0.19 4.54 0 225.19 124.49 30235 +1951 362 3.48 -2.52 1.83 0 189.47 126.49 30267 +1951 363 2.87 -3.13 1.22 0.99 182.14 95.55 30303 +1951 364 4.9 -1.1 3.25 0.43 207.52 95.01 30343 +1951 365 1.96 -4.04 0.31 1.24 171.66 96.61 30388 +1952 1 -1.12 -7.12 -2.77 0.3 139.96 142.6 30438 +1952 2 1.45 -4.55 -0.2 2.1 166.02 142.06 30492 +1952 3 -1.28 -7.28 -2.93 0 138.46 176.76 30551 +1952 4 4.35 -1.65 2.7 0 200.36 174.34 30614 +1952 5 8.14 2.14 6.49 0 254.34 129.22 30681 +1952 6 7.29 1.29 5.64 0 241.26 130.71 30752 +1952 7 6.31 0.31 4.66 0.02 226.89 99.12 30828 +1952 8 4.67 -1.33 3.02 0 204.5 134.66 30907 +1952 9 1.27 -4.73 -0.38 0 164.07 137.74 30991 +1952 10 1.79 -4.21 0.14 0.09 169.76 104.1 31079 +1952 11 0.71 -5.29 -0.94 0 158.12 140.31 31171 +1952 12 2.57 -3.43 0.92 0.01 178.63 105.3 31266 +1952 13 -0.31 -6.31 -1.96 0.71 147.76 151.83 31366 +1952 14 1.3 -4.7 -0.35 0.21 164.39 152.07 31469 +1952 15 4.79 -1.21 3.14 0 206.07 186.85 31575 +1952 16 5.97 -0.03 4.32 0.05 222.09 150.4 31686 +1952 17 0.79 -5.21 -0.86 0.35 158.96 153.67 31800 +1952 18 -0.15 -6.15 -1.8 0 149.35 193.08 31917 +1952 19 -1.63 -7.63 -3.28 0 135.23 195.52 32038 +1952 20 -1.78 -7.78 -3.43 0 133.87 197.03 32161 +1952 21 -1.1 -7.1 -2.75 0 140.15 198.61 32289 +1952 22 2.91 -3.09 1.26 0 182.61 197.8 32419 +1952 23 5.52 -0.48 3.87 0 215.86 157.04 32552 +1952 24 6.3 0.3 4.65 0.73 226.75 118.9 32688 +1952 25 -1 -7 -2.65 0.88 141.09 166.33 32827 +1952 26 3.29 -2.71 1.64 0.65 187.16 165.48 32969 +1952 27 1.27 -4.73 -0.38 0.31 164.07 167.54 33114 +1952 28 5.6 -0.4 3.95 0.06 216.95 166.28 33261 +1952 29 8.02 2.02 6.37 0.03 252.46 165.46 33411 +1952 30 4.54 -1.46 2.89 0 202.81 172.41 33564 +1952 31 5.72 -0.28 4.07 0 218.61 173.92 33718 +1952 32 10.95 4.95 9.3 0 302.02 171.29 33875 +1952 33 12.38 6.38 10.73 0.07 329.09 129.2 34035 +1952 34 10.65 4.65 9 0.12 296.59 132.26 34196 +1952 35 7.7 1.7 6.05 1.09 247.49 135.99 34360 +1952 36 3.78 -2.22 2.13 0 193.17 186.93 34526 +1952 37 3.93 -2.07 2.28 0 195.04 189.25 34694 +1952 38 3.25 -2.75 1.6 0 186.68 192.47 34863 +1952 39 0.38 -5.62 -1.27 1.09 154.7 147.67 35035 +1952 40 4.27 -1.73 2.62 0 199.34 196.98 35208 +1952 41 2.72 -3.28 1.07 0 180.38 200.71 35383 +1952 42 3.36 -2.64 1.71 0 188.01 202.83 35560 +1952 43 0.84 -5.16 -0.81 0 159.48 207.22 35738 +1952 44 1.91 -4.09 0.26 0 171.1 209.13 35918 +1952 45 5.01 -0.99 3.36 0 208.98 209.47 36099 +1952 46 6.13 0.13 4.48 0 224.34 211.19 36282 +1952 47 6.59 0.59 4.94 0.64 230.92 160.19 36466 +1952 48 5.66 -0.34 4.01 0.75 217.78 162.92 36652 +1952 49 1.29 -4.71 -0.36 2.07 164.28 167.53 36838 +1952 50 4.14 -1.86 2.49 0.03 197.68 167.97 37026 +1952 51 3.03 -2.97 1.38 0.51 184.04 170.86 37215 +1952 52 1.29 -4.71 -0.36 0.22 164.28 173.94 37405 +1952 53 -0.01 -6.01 -1.66 0.17 150.74 212.37 37596 +1952 54 0.9 -5.1 -0.75 0.5 160.12 213.74 37788 +1952 55 0.28 -5.72 -1.37 0 153.68 276.47 37981 +1952 56 1.43 -4.57 -0.22 0 165.8 278.08 38175 +1952 57 2.24 -3.76 0.59 0.02 174.83 184.25 38370 +1952 58 2.95 -3.05 1.3 0.13 183.09 186.05 38565 +1952 59 -0.15 -6.15 -1.8 0 149.35 253.07 38761 +1952 60 0.27 -5.73 -1.38 0 153.58 255.72 38958 +1952 61 0.08 -5.92 -1.57 0 151.65 258.83 39156 +1952 62 2.57 -3.43 0.92 0 178.63 259.8 39355 +1952 63 4.11 -1.89 2.46 0 197.3 261.51 39553 +1952 64 0.41 -5.59 -1.24 0.02 155.01 200.58 39753 +1952 65 4.71 -1.29 3.06 0.46 205.02 200.09 39953 +1952 66 10.22 4.22 8.57 0 288.95 263.15 40154 +1952 67 13.48 7.48 11.83 0 351.3 261.03 40355 +1952 68 17 11 15.35 1.03 431.19 192.87 40556 +1952 69 12.02 6.02 10.37 0.73 322.08 201.59 40758 +1952 70 4.12 -1.88 2.47 0.08 197.43 211.08 40960 +1952 71 3.19 -2.81 1.54 0 185.95 285.25 41163 +1952 72 4.31 -1.69 2.66 0.11 199.85 215.28 41366 +1952 73 3.79 -2.21 2.14 0.23 193.29 217.69 41569 +1952 74 5.15 -0.85 3.5 0 210.85 291.65 41772 +1952 75 3.46 -2.54 1.81 0 189.23 296.1 41976 +1952 76 4.93 -1.07 3.28 0 207.92 297.29 42179 +1952 77 3.64 -2.36 1.99 0 191.43 301.24 42383 +1952 78 7.17 1.17 5.52 0 239.46 300.03 42587 +1952 79 5.78 -0.22 4.13 0 219.44 304.43 42791 +1952 80 4.46 -1.54 2.81 0.15 201.78 231.33 42996 +1952 81 2.37 -3.63 0.72 0 176.32 313.11 43200 +1952 82 5.19 -0.81 3.54 0.02 211.39 234.7 43404 +1952 83 6.74 0.74 5.09 0 233.1 313.62 43608 +1952 84 3.95 -2.05 2.3 0 195.29 319.37 43812 +1952 85 7.42 1.42 5.77 0 243.22 317.82 44016 +1952 86 7.72 1.72 6.07 0 247.8 319.84 44220 +1952 87 7.32 1.32 5.67 0 241.71 322.92 44424 +1952 88 9 3 7.35 0 268.19 322.94 44627 +1952 89 7.81 1.81 6.16 0 249.19 326.92 44831 +1952 90 7.13 1.13 5.48 0 238.86 330.23 45034 +1952 91 20.3 14.3 18.65 0 519.67 305.51 45237 +1952 92 15.64 9.64 13.99 0 398.66 319.74 45439 +1952 93 15.99 9.99 14.34 0 406.83 321.1 45642 +1952 94 15.01 9.01 13.36 0 384.31 325.42 45843 +1952 95 13.74 7.74 12.09 0 356.73 330.22 46045 +1952 96 9.93 3.93 8.28 0 283.89 339.31 46246 +1952 97 12.7 6.7 11.05 0 335.42 336.42 46446 +1952 98 10.63 4.63 8.98 0 296.23 342.16 46647 +1952 99 9.6 3.6 7.95 0 278.23 345.9 46846 +1952 100 12.87 6.87 11.22 0.13 338.83 256.47 47045 +1952 101 15.1 9.1 13.45 0.03 386.34 254.34 47243 +1952 102 13.43 7.43 11.78 0 350.26 344.64 47441 +1952 103 11.46 5.46 9.81 0 311.44 350.33 47638 +1952 104 14.06 8.06 12.41 0 363.52 346.94 47834 +1952 105 12.84 6.84 11.19 0 338.22 351.28 48030 +1952 106 15.61 9.61 13.96 0 397.97 346.79 48225 +1952 107 19.3 13.3 17.65 0 491.36 338.52 48419 +1952 108 22.05 16.05 20.4 0 572.55 331.28 48612 +1952 109 19.07 13.07 17.42 0 485.04 342.44 48804 +1952 110 19.53 13.53 17.88 0 497.76 342.41 48995 +1952 111 17.88 11.88 16.23 0 453.43 348.73 49185 +1952 112 15.99 9.99 14.34 0 406.83 355.22 49374 +1952 113 13.54 7.54 11.89 0 352.55 362.27 49561 +1952 114 15.87 9.87 14.22 0 404.01 358.32 49748 +1952 115 17.64 11.64 15.99 0 447.27 355.05 49933 +1952 116 18.62 12.62 16.97 0 472.87 353.42 50117 +1952 117 19.75 13.75 18.1 0 503.94 351.24 50300 +1952 118 21.66 15.66 20.01 0 560.39 346.12 50481 +1952 119 19.04 13.04 17.39 0 484.22 355.88 50661 +1952 120 20.95 14.95 19.3 0 538.81 350.85 50840 +1952 121 23.22 17.22 21.57 0 610.39 343.65 51016 +1952 122 24.52 18.52 22.87 0.41 654.91 254.66 51191 +1952 123 24.09 18.09 22.44 3.19 639.89 256.71 51365 +1952 124 24.33 18.33 22.68 0.35 648.23 256.73 51536 +1952 125 22.88 16.88 21.23 0.31 599.18 261.77 51706 +1952 126 23.54 17.54 21.89 0.15 621.1 260.54 51874 +1952 127 21.72 15.72 20.07 0 562.24 355.15 52039 +1952 128 19.13 13.13 17.48 0 486.69 364.84 52203 +1952 129 16.31 10.31 14.66 0.34 414.42 280.36 52365 +1952 130 19.75 13.75 18.1 0 503.94 364.46 52524 +1952 131 19.59 13.59 17.94 0 499.44 365.76 52681 +1952 132 19.36 13.36 17.71 0 493.03 367.3 52836 +1952 133 17.93 11.93 16.28 0 454.72 372.38 52989 +1952 134 17.31 11.31 15.66 0 438.92 374.87 53138 +1952 135 10.64 4.64 8.99 0 296.41 391.23 53286 +1952 136 11.72 5.72 10.07 0 316.34 389.75 53430 +1952 137 14.94 8.94 13.29 0.09 382.75 287.41 53572 +1952 138 12.92 6.92 11.27 0 339.83 388.54 53711 +1952 139 16.5 10.5 14.85 0 418.98 380.45 53848 +1952 140 16.65 10.65 15 0.28 422.61 285.39 53981 +1952 141 14.34 8.34 12.69 0 369.54 386.91 54111 +1952 142 13.68 7.68 12.03 0.32 355.47 291.73 54238 +1952 143 15.27 9.27 13.62 0.05 390.18 289.24 54362 +1952 144 13.19 7.19 11.54 1.27 345.32 293.34 54483 +1952 145 12.92 6.92 11.27 0.06 339.83 294.15 54600 +1952 146 11.38 5.38 9.73 0.07 309.95 296.88 54714 +1952 147 11.18 5.18 9.53 0.04 306.24 297.55 54824 +1952 148 13.38 7.38 11.73 0.15 349.23 294.32 54931 +1952 149 12.18 6.18 10.53 0.04 325.18 296.55 55034 +1952 150 14.48 8.48 12.83 0 372.59 390.49 55134 +1952 151 14.21 8.21 12.56 0 366.73 391.54 55229 +1952 152 21.9 15.9 20.25 0 567.85 368.3 55321 +1952 153 18.66 12.66 17.01 0.15 473.94 284.75 55409 +1952 154 19.34 13.34 17.69 0 492.47 377.81 55492 +1952 155 21.41 15.41 19.76 0 552.71 370.85 55572 +1952 156 21.63 15.63 19.98 0 559.46 370.36 55648 +1952 157 22.11 16.11 20.46 0.16 574.44 276.54 55719 +1952 158 23.81 17.81 22.16 0 630.27 362.1 55786 +1952 159 22.55 16.55 20.9 0 588.47 367.43 55849 +1952 160 24.26 18.26 22.61 0.04 645.79 270.45 55908 +1952 161 23.3 17.3 21.65 1.17 613.06 273.51 55962 +1952 162 23.11 17.11 21.46 0 606.75 365.51 56011 +1952 163 19.71 13.71 18.06 0 502.81 378.21 56056 +1952 164 19.08 13.08 17.43 0 485.32 380.31 56097 +1952 165 18.95 12.95 17.3 0 481.77 380.83 56133 +1952 166 22.92 16.92 21.27 0.13 600.49 275.02 56165 +1952 167 18.89 12.89 17.24 0 480.14 381.04 56192 +1952 168 19.89 13.89 18.24 1.25 507.9 283.39 56214 +1952 169 20.85 14.85 19.2 0 535.82 374.54 56231 +1952 170 20.31 14.31 18.66 0.45 519.96 282.32 56244 +1952 171 21.17 15.17 19.52 0.11 545.42 280.09 56252 +1952 172 20.11 14.11 18.46 0.31 514.19 282.87 56256 +1952 173 18.18 12.18 16.53 0.13 461.23 287.53 56255 +1952 174 18.45 12.45 16.8 0 468.34 382.46 56249 +1952 175 21.51 15.51 19.86 0 555.77 372.07 56238 +1952 176 21.13 15.13 19.48 0.36 544.21 280.06 56223 +1952 177 23.28 17.28 21.63 0 612.39 365.06 56203 +1952 178 21.42 15.42 19.77 0 553.01 372.29 56179 +1952 179 25.3 19.3 23.65 0.01 682.91 267.22 56150 +1952 180 24.83 18.83 23.18 1.05 665.92 268.71 56116 +1952 181 25.36 19.36 23.71 0.45 685.11 266.88 56078 +1952 182 25.79 19.79 24.14 0 701.02 353.71 56035 +1952 183 28.6 22.6 26.95 0 812.89 339.38 55987 +1952 184 26.43 20.43 24.78 0 725.28 350.36 55935 +1952 185 25.48 19.48 23.83 0.06 689.52 266.06 55879 +1952 186 28.52 22.52 26.87 0.28 809.5 254.52 55818 +1952 187 26.64 20.64 24.99 0.01 733.39 261.63 55753 +1952 188 24.59 18.59 22.94 0 657.38 358.05 55684 +1952 189 24.69 18.69 23.04 0.04 660.93 268.08 55611 +1952 190 27.99 21.99 26.34 0 787.4 341.24 55533 +1952 191 32.14 26.14 30.49 0 974.93 316.7 55451 +1952 192 30.61 24.61 28.96 0.29 901.84 244.5 55366 +1952 193 30.01 24.01 28.36 0 874.47 329.3 55276 +1952 194 30.28 24.28 28.63 0 886.7 327.53 55182 +1952 195 24.79 18.79 23.14 0 664.49 355.35 55085 +1952 196 24.24 18.24 22.59 0.17 645.09 268 54984 +1952 197 19.36 13.36 17.71 0.03 493.03 281.31 54879 +1952 198 23.7 17.7 22.05 0 626.52 358.74 54770 +1952 199 26.02 20.02 24.37 0 709.66 348.19 54658 +1952 200 22.19 16.19 20.54 1.22 576.97 272.98 54542 +1952 201 24.55 18.55 22.9 0.06 655.97 265.47 54423 +1952 202 22.01 16.01 20.36 0 571.29 363.63 54301 +1952 203 18.87 12.87 17.22 0 479.6 373.9 54176 +1952 204 19.34 13.34 17.69 0 492.47 371.89 54047 +1952 205 21.03 15.03 19.38 0 541.2 365.68 53915 +1952 206 17.02 11.02 15.37 0 431.69 377.76 53780 +1952 207 18.74 12.74 17.09 0 476.09 372.03 53643 +1952 208 19.64 13.64 17.99 0 500.84 368.52 53502 +1952 209 23.72 17.72 22.07 0.22 627.2 264.72 53359 +1952 210 26.57 20.57 24.92 0 730.68 339.78 53213 +1952 211 25.18 19.18 23.53 0.85 678.54 259.06 53064 +1952 212 23.53 17.53 21.88 0.35 620.77 263.7 52913 +1952 213 21.83 15.83 20.18 0.61 565.66 268.03 52760 +1952 214 22.58 16.58 20.93 0 589.44 353.84 52604 +1952 215 21.48 15.48 19.83 0.01 554.85 267.92 52445 +1952 216 24.38 18.38 22.73 0.06 649.98 258.75 52285 +1952 217 20.59 14.59 18.94 1.38 528.14 268.82 52122 +1952 218 21.24 15.24 19.59 0 547.53 355.38 51958 +1952 219 20.2 14.2 18.55 0 516.78 357.87 51791 +1952 220 21.69 15.69 20.04 0 561.31 351.82 51622 +1952 221 20.47 14.47 18.82 0 524.62 355.04 51451 +1952 222 24.45 18.45 22.8 0 652.44 339.16 51279 +1952 223 23.83 17.83 22.18 0 630.95 340.58 51105 +1952 224 27.86 21.86 26.21 0 782.06 321.55 50929 +1952 225 30.34 24.34 28.69 0.8 889.44 230.5 50751 +1952 226 30.12 24.12 28.47 0.38 879.43 230.66 50572 +1952 227 26.39 20.39 24.74 0.06 723.74 243.9 50392 +1952 228 27.8 21.8 26.15 0 779.6 317.39 50210 +1952 229 24.89 18.89 23.24 0 668.07 329.42 50026 +1952 230 26.61 20.61 24.96 0.28 732.23 240.52 49842 +1952 231 26.85 20.85 25.2 0.24 741.58 238.65 49656 +1952 232 22.73 16.73 21.08 0.02 594.29 250.45 49469 +1952 233 24.08 18.08 22.43 0 639.54 327.41 49280 +1952 234 25.13 19.13 23.48 0.03 676.72 241.34 49091 +1952 235 27.15 21.15 25.5 0 753.41 311.49 48900 +1952 236 25.04 19.04 23.39 0.07 673.47 239.54 48709 +1952 237 23.29 17.29 21.64 0 612.72 324.67 48516 +1952 238 26 20 24.35 0.02 708.9 234.14 48323 +1952 239 22.31 16.31 20.66 0 580.78 325.12 48128 +1952 240 23.26 17.26 21.61 0 611.72 319.99 47933 +1952 241 24.82 18.82 23.17 0.05 665.56 234.26 47737 +1952 242 26.05 20.05 24.4 0 710.79 305.62 47541 +1952 243 29.25 23.25 27.6 0.1 840.8 216.8 47343 +1952 244 18.29 12.29 16.64 0.84 464.12 246.6 47145 +1952 245 17.45 11.45 15.8 0.04 442.44 246.89 46947 +1952 246 16.03 10.03 14.38 0 407.77 330.73 46747 +1952 247 14.99 8.99 13.34 0 383.87 331.24 46547 +1952 248 19.19 13.19 17.54 0 488.33 318.72 46347 +1952 249 16.72 10.72 15.07 0.01 424.32 242.36 46146 +1952 250 17.86 11.86 16.21 0.21 452.91 238.74 45945 +1952 251 19.48 13.48 17.83 0.36 496.36 233.87 45743 +1952 252 21.87 15.87 20.22 0.17 566.91 226.85 45541 +1952 253 19.96 13.96 18.31 0.03 509.9 229.68 45339 +1952 254 18.69 12.69 17.04 0.08 474.75 230.74 45136 +1952 255 16.23 10.23 14.58 0.86 412.51 233.63 44933 +1952 256 17.8 11.8 16.15 0.09 451.37 229.1 44730 +1952 257 15.08 9.08 13.43 0.95 385.89 232.18 44527 +1952 258 13.35 7.35 11.7 0.38 348.61 233.01 44323 +1952 259 11.49 5.49 9.84 0.15 312.01 233.66 44119 +1952 260 11.54 5.54 9.89 0.01 312.94 231.76 43915 +1952 261 11.26 5.26 9.61 0 307.72 306.97 43711 +1952 262 13.19 7.19 11.54 0.07 345.32 225.89 43507 +1952 263 17.16 11.16 15.51 0.34 435.17 217.86 43303 +1952 264 13.13 7.13 11.48 0.22 344.1 222.14 43099 +1952 265 12.98 6.98 11.33 0 341.05 294.05 42894 +1952 266 15.04 9.04 13.39 0 384.99 287.64 42690 +1952 267 15.4 9.4 13.75 0 393.14 284.23 42486 +1952 268 16.58 10.58 14.93 0 420.91 279.2 42282 +1952 269 19.52 13.52 17.87 0.02 497.48 202.35 42078 +1952 270 21.65 15.65 20 0 560.08 261.49 41875 +1952 271 21.43 15.43 19.78 1.68 553.32 194.7 41671 +1952 272 18.83 12.83 17.18 0.54 478.52 197.79 41468 +1952 273 15.88 9.88 14.23 0.09 404.24 200.78 41265 +1952 274 8.17 2.17 6.52 0.73 254.81 208 41062 +1952 275 12.35 6.35 10.7 0 328.5 268.6 40860 +1952 276 13.36 7.36 11.71 0.2 348.81 198.17 40658 +1952 277 14.82 8.82 13.17 0.84 380.08 194.25 40456 +1952 278 20.65 14.65 19 0.06 529.9 182.65 40255 +1952 279 19.03 13.03 17.38 0.19 483.95 183.56 40054 +1952 280 18.63 12.63 16.98 0.08 473.14 182.31 39854 +1952 281 17 11 15.35 0 431.19 243.89 39654 +1952 282 18.2 12.2 16.55 0 461.75 238.72 39455 +1952 283 17.55 11.55 15.9 1.99 444.98 178 39256 +1952 284 13.99 7.99 12.34 0.57 362.02 180.67 39058 +1952 285 11.23 5.23 9.58 0 307.16 242.42 38861 +1952 286 9.59 3.59 7.94 0 278.06 241.77 38664 +1952 287 9.1 3.1 7.45 0 269.84 239.39 38468 +1952 288 3.68 -2.32 2.03 0 191.93 241.97 38273 +1952 289 10.03 4.03 8.38 1.07 285.63 174.59 38079 +1952 290 12.14 6.14 10.49 0.75 324.4 170.35 37885 +1952 291 13.41 7.41 11.76 0.07 349.85 166.95 37693 +1952 292 13.11 7.11 11.46 0.45 343.69 165.28 37501 +1952 293 12.39 6.39 10.74 0.88 329.28 164.01 37311 +1952 294 13.16 7.16 11.51 0.51 344.71 161.04 37121 +1952 295 16.34 10.34 14.69 0.24 415.13 155.19 36933 +1952 296 10.85 4.85 9.2 0.21 300.2 159.28 36745 +1952 297 9.72 3.72 8.07 0.08 280.28 158.23 36560 +1952 298 11.78 5.78 10.13 0.23 317.49 154.42 36375 +1952 299 11.53 5.53 9.88 0.2 312.76 152.57 36191 +1952 300 7.58 1.58 5.93 1.27 245.65 153.81 36009 +1952 301 9.85 3.85 8.2 0 282.51 200.21 35829 +1952 302 11.33 5.33 9.68 0.09 309.02 146.93 35650 +1952 303 13.23 7.23 11.58 0 346.14 190.96 35472 +1952 304 12.37 6.37 10.72 0 328.89 189.63 35296 +1952 305 6.81 0.81 5.16 0 234.13 192.74 35122 +1952 306 9.16 3.16 7.51 0 270.84 188.27 34950 +1952 307 8.27 2.27 6.62 0.72 256.39 139.96 34779 +1952 308 5.43 -0.57 3.78 0 214.63 186.43 34610 +1952 309 5.45 -0.55 3.8 0 214.9 184.07 34444 +1952 310 7.8 1.8 6.15 0 249.03 179.66 34279 +1952 311 1.9 -4.1 0.25 0.15 170.99 136.35 34116 +1952 312 1.83 -4.17 0.18 0.03 170.21 134.37 33956 +1952 313 1.67 -4.33 0.02 0.41 168.43 132.82 33797 +1952 314 5.1 -0.9 3.45 0 210.18 172.88 33641 +1952 315 7.16 1.16 5.51 0 239.31 168.75 33488 +1952 316 6.7 0.7 5.05 0 232.52 166.93 33337 +1952 317 6.45 0.45 4.8 0 228.9 164.92 33188 +1952 318 8.49 2.49 6.84 0 259.9 160.92 33042 +1952 319 10.64 4.64 8.99 0 296.41 157.26 32899 +1952 320 8.95 2.95 7.3 0 267.37 156.97 32758 +1952 321 13.54 7.54 11.89 0.02 352.55 112.7 32620 +1952 322 12.74 6.74 11.09 0.91 336.22 112.04 32486 +1952 323 12.07 6.07 10.42 0.13 323.05 111.39 32354 +1952 324 15.88 9.88 14.23 0.01 404.24 106.58 32225 +1952 325 13.43 7.43 11.78 0 350.26 143.38 32100 +1952 326 6.27 0.27 4.62 0 226.32 148.35 31977 +1952 327 2.95 -3.05 1.3 0 183.09 148.59 31858 +1952 328 1.59 -4.41 -0.06 0 167.55 147.33 31743 +1952 329 1.34 -4.66 -0.31 0 164.82 145.95 31631 +1952 330 1.53 -4.47 -0.12 0 166.89 144.39 31522 +1952 331 3.35 -2.65 1.7 0 187.89 142.09 31417 +1952 332 3.71 -2.29 2.06 0 192.3 140.24 31316 +1952 333 3.61 -2.39 1.96 0.15 191.06 104.4 31218 +1952 334 3.97 -2.03 2.32 0.44 195.54 103.42 31125 +1952 335 0.24 -5.76 -1.41 1.09 153.27 103.95 31035 +1952 336 -2.34 -8.34 -3.99 0 128.88 138.56 30949 +1952 337 -0.02 -6.02 -1.67 0 150.64 135.95 30867 +1952 338 5.46 -0.54 3.81 0.61 215.04 99.11 30790 +1952 339 -0.26 -6.26 -1.91 0.1 148.25 144.01 30716 +1952 340 -2.84 -8.84 -4.49 0.15 124.56 144.77 30647 +1952 341 -2.06 -8.06 -3.71 0 131.35 177.28 30582 +1952 342 0.71 -5.29 -0.94 0 158.12 175.38 30521 +1952 343 1.25 -4.75 -0.4 0 163.85 174.22 30465 +1952 344 6.07 0.07 4.42 0 223.49 126.62 30413 +1952 345 4.33 -1.67 2.68 0 200.11 127.23 30366 +1952 346 5.74 -0.26 4.09 0 218.88 125.85 30323 +1952 347 5.17 -0.83 3.52 0.14 211.12 94.2 30284 +1952 348 5.02 -0.98 3.37 1.22 209.11 94 30251 +1952 349 2.07 -3.93 0.42 0.63 172.9 94.89 30221 +1952 350 2.41 -3.59 0.76 0.39 176.78 94.51 30197 +1952 351 0.37 -5.63 -1.28 0.02 154.6 95.05 30177 +1952 352 -1.18 -7.18 -2.83 0.11 139.39 139.56 30162 +1952 353 1.27 -4.73 -0.38 0.05 164.07 138.59 30151 +1952 354 2.38 -3.62 0.73 0.12 176.43 94.22 30145 +1952 355 1.22 -4.78 -0.43 1.68 163.53 94.62 30144 +1952 356 0.43 -5.57 -1.22 0.27 155.21 94.9 30147 +1952 357 -1.2 -7.2 -2.85 0.02 139.21 139.28 30156 +1952 358 0.59 -5.41 -1.06 0 156.87 126.61 30169 +1952 359 3.09 -2.91 1.44 0 184.76 125.56 30186 +1952 360 2.17 -3.83 0.52 0 174.03 126.38 30208 +1952 361 4.53 -1.47 2.88 0 202.68 125.48 30235 +1952 362 5.39 -0.61 3.74 0 214.09 125.42 30267 +1952 363 10.72 4.72 9.07 0 297.85 122.2 30303 +1952 364 9.07 3.07 7.42 0 269.35 123.91 30343 +1952 365 7.49 1.49 5.84 0.01 244.28 94.21 30388 +1953 1 6.68 0.68 5.03 0 232.23 127.04 30438 +1953 2 1.18 -4.82 -0.47 0.4 163.1 98.11 30492 +1953 3 -1.98 -7.98 -3.63 0 132.07 133.07 30551 +1953 4 -0.94 -6.94 -2.59 0.57 141.66 145.1 30614 +1953 5 -0.83 -6.83 -2.48 0 142.71 179.01 30681 +1953 6 -2.3 -8.3 -3.95 0.04 129.23 146.58 30752 +1953 7 -0.8 -6.8 -2.45 0.01 143 146.67 30828 +1953 8 1.07 -4.93 -0.58 0 161.92 181.07 30907 +1953 9 -1.08 -7.08 -2.73 0 140.33 183.15 30991 +1953 10 1.23 -4.77 -0.42 0 163.64 183.16 31079 +1953 11 -2.24 -8.24 -3.89 0 129.76 185.51 31171 +1953 12 -2.64 -8.64 -4.29 1 126.27 153.94 31266 +1953 13 0.96 -5.04 -0.69 0 160.75 189.46 31366 +1953 14 2.56 -3.44 0.91 0.19 178.51 153.78 31469 +1953 15 6.45 0.45 4.8 0.01 228.9 152.09 31575 +1953 16 1.4 -4.6 -0.25 0 165.48 191.69 31686 +1953 17 0.13 -5.87 -1.52 0 152.15 193.82 31800 +1953 18 -2.42 -8.42 -4.07 0 128.18 196.67 31917 +1953 19 -5.35 -11.35 -7 0 104.73 199.5 32038 +1953 20 -4.12 -10.12 -5.77 0 114.08 200.53 32161 +1953 21 0.81 -5.19 -0.84 0.01 159.17 161.11 32289 +1953 22 0.89 -5.11 -0.76 0 160.01 201.63 32419 +1953 23 2.08 -3.92 0.43 0 173.01 202.34 32552 +1953 24 5.42 -0.58 3.77 0.02 214.49 161.68 32688 +1953 25 9.47 3.47 7.82 0.61 276.03 159.3 32827 +1953 26 6.15 0.15 4.5 0.02 224.62 121.82 32969 +1953 27 7.5 1.5 5.85 0 244.43 163.38 33114 +1953 28 5.23 -0.77 3.58 0 211.92 167.31 33261 +1953 29 9.15 3.15 7.5 0 270.67 166.48 33411 +1953 30 9.69 3.69 8.04 0 279.77 168.17 33564 +1953 31 8.88 2.88 7.23 0.04 266.22 128.46 33718 +1953 32 8.19 2.19 6.54 0 255.13 173.98 33875 +1953 33 6.78 0.78 5.13 0.02 233.69 133.35 34035 +1953 34 4.54 -1.46 2.89 0 202.81 181.72 34196 +1953 35 4.28 -1.72 2.63 0 199.47 184.06 34360 +1953 36 3.52 -2.48 1.87 0 189.96 187.11 34526 +1953 37 4.18 -1.82 2.53 0 198.19 189.07 34694 +1953 38 2.73 -3.27 1.08 0 180.49 192.82 34863 +1953 39 3.57 -2.43 1.92 0 190.57 194.86 35035 +1953 40 2.79 -3.21 1.14 0.2 181.2 148.52 35208 +1953 41 -1.18 -7.18 -2.83 0 139.39 203.05 35383 +1953 42 2.23 -3.77 0.58 0.24 174.72 152.71 35560 +1953 43 -3.34 -9.34 -4.99 0.51 120.37 195.39 35738 +1953 44 -0.82 -6.82 -2.47 0.45 142.8 197.41 35918 +1953 45 -0.53 -6.53 -2.18 0.04 145.6 199.19 36099 +1953 46 -0.12 -6.12 -1.77 0 149.64 254.79 36282 +1953 47 0.87 -5.13 -0.78 0 159.8 256.75 36466 +1953 48 1.6 -4.4 -0.05 0 167.66 258.73 36652 +1953 49 6.36 0.36 4.71 0 227.61 256.83 36838 +1953 50 8.66 2.66 7.01 0.02 262.64 201.11 37026 +1953 51 9.37 3.37 7.72 0 274.35 221.84 37215 +1953 52 10.12 4.12 8.47 0 287.2 223.74 37405 +1953 53 3.14 -2.86 1.49 0 185.35 233.55 37596 +1953 54 6.62 0.62 4.97 0.05 231.36 174.93 37788 +1953 55 6.88 0.88 5.23 0 235.16 235.97 37981 +1953 56 6.17 0.17 4.52 0 224.9 239.36 38175 +1953 57 6.24 0.24 4.59 0 225.9 242.18 38370 +1953 58 5.07 -0.93 3.42 0 209.78 246.23 38565 +1953 59 6.23 0.23 4.58 0 225.75 247.82 38761 +1953 60 14 8 12.35 0 362.24 240.53 38958 +1953 61 17.78 11.78 16.13 0 450.85 236.35 39156 +1953 62 12.8 6.8 11.15 0 337.42 248.03 39355 +1953 63 16.38 10.38 14.73 0 416.09 244.7 39553 +1953 64 11.45 5.45 9.8 0 311.26 255.86 39753 +1953 65 10.25 4.25 8.6 0 289.48 260.4 39953 +1953 66 11.92 5.92 10.27 0 320.16 260.69 40154 +1953 67 12.39 6.39 10.74 0 329.28 262.81 40355 +1953 68 11.09 5.09 9.44 0 304.58 267.61 40556 +1953 69 13.24 7.24 11.59 0.49 346.35 200.1 40758 +1953 70 10.59 4.59 8.94 0.01 295.51 205.31 40960 +1953 71 6.67 0.67 5.02 0.03 232.08 211.27 41163 +1953 72 7.66 1.66 6.01 0 246.88 283.35 41366 +1953 73 7.39 1.39 5.74 0 242.76 286.35 41569 +1953 74 6.45 0.45 4.8 0 228.9 290.22 41772 +1953 75 7.18 1.18 5.53 0 239.61 292.09 41976 +1953 76 5.31 -0.69 3.66 0 213 296.89 42179 +1953 77 7.1 1.1 5.45 0 238.41 297.44 42383 +1953 78 5.06 -0.94 3.41 0 209.65 302.47 42587 +1953 79 5.7 -0.3 4.05 0 218.33 304.52 42791 +1953 80 4.94 -1.06 3.29 0 208.05 307.92 42996 +1953 81 3.83 -2.17 2.18 0 193.79 311.7 43200 +1953 82 2.22 -3.78 0.57 0 174.6 315.95 43404 +1953 83 8.24 2.24 6.59 0 255.92 311.67 43608 +1953 84 10.96 4.96 9.31 0 302.2 310.13 43812 +1953 85 9.55 3.55 7.9 0 277.38 314.82 44016 +1953 86 7.55 1.55 5.9 0.01 245.19 240.05 44220 +1953 87 6.09 0.09 4.44 0 223.77 324.48 44424 +1953 88 5.12 -0.88 3.47 0 210.45 328.01 44627 +1953 89 -0.61 -6.61 -2.26 0 144.83 335.86 44831 +1953 90 0.95 -5.05 -0.7 0.01 160.64 252.73 45034 +1953 91 9.38 3.38 7.73 0.11 274.51 246.96 45237 +1953 92 13.99 7.99 12.34 0 362.02 323.29 45439 +1953 93 18.22 12.22 16.57 0 462.28 315.57 45642 +1953 94 19.23 13.23 17.58 0 489.43 314.88 45843 +1953 95 18.63 12.63 16.98 0 473.14 318.6 46045 +1953 96 19.69 13.69 18.04 0 502.24 317.63 46246 +1953 97 17.99 11.99 16.34 0 456.27 324.34 46446 +1953 98 12.84 6.84 11.19 0 338.22 338.09 46647 +1953 99 12.2 6.2 10.55 0 325.57 341.33 46846 +1953 100 14 8 12.35 0.35 362.24 254.73 47045 +1953 101 16.82 10.82 15.17 0 426.76 334.99 47243 +1953 102 13.88 7.88 12.23 0 359.69 343.69 47441 +1953 103 15.36 9.36 13.71 0 392.23 342.2 47638 +1953 104 13.14 7.14 11.49 0.04 344.3 261.66 47834 +1953 105 13.97 7.97 12.32 0.2 361.6 261.68 48030 +1953 106 10.04 4.04 8.39 0 285.8 358.15 48225 +1953 107 10.27 4.27 8.62 0 289.83 359.44 48419 +1953 108 9.84 3.84 8.19 0 282.34 361.94 48612 +1953 109 11.06 5.06 9.41 0 304.03 361.4 48804 +1953 110 12.08 6.08 10.43 0 323.24 360.88 48995 +1953 111 14.09 8.09 12.44 0 364.16 358.21 49185 +1953 112 16.41 10.41 14.76 0 416.81 354.16 49374 +1953 113 13.54 7.54 11.89 0 352.55 362.27 49561 +1953 114 15.36 9.36 13.71 0 392.23 359.57 49748 +1953 115 11.43 5.43 9.78 0.09 310.88 277.14 49933 +1953 116 18.14 12.14 16.49 0.34 460.18 266.12 50117 +1953 117 14.4 8.4 12.75 1.55 370.85 274.33 50300 +1953 118 14.02 8.02 12.37 0 362.66 367.96 50481 +1953 119 14.27 8.27 12.62 0.23 368.03 276.44 50661 +1953 120 9.08 3.08 7.43 0 269.51 380.04 50840 +1953 121 13.01 7.01 11.36 0.14 341.66 280.27 51016 +1953 122 10.53 4.53 8.88 0.11 294.44 284.89 51191 +1953 123 14.56 8.56 12.91 1.5 374.34 279.32 51365 +1953 124 14.59 8.59 12.94 0.85 375 280.08 51536 +1953 125 15.62 9.62 13.97 0.72 398.2 278.92 51706 +1953 126 15.15 9.15 13.5 0.5 387.46 280.54 51874 +1953 127 17.3 11.3 15.65 0.44 438.67 276.96 52039 +1953 128 19.59 13.59 17.94 1.03 499.44 272.53 52203 +1953 129 16.85 10.85 15.2 0.36 427.5 279.27 52365 +1953 130 13.91 7.91 12.26 0 360.32 380.56 52524 +1953 131 14.54 8.54 12.89 0.32 373.9 284.91 52681 +1953 132 14 8 12.35 0.22 362.24 286.49 52836 +1953 133 15.99 9.99 14.34 0 406.83 377.77 52989 +1953 134 14.42 8.42 12.77 0.17 371.28 286.82 53138 +1953 135 16.48 10.48 14.83 0 418.5 377.87 53286 +1953 136 20.98 14.98 19.33 0 539.7 364.56 53430 +1953 137 24.04 18.04 22.39 0 638.16 353.49 53572 +1953 138 17.17 11.17 15.52 0 435.41 377.9 53711 +1953 139 17.3 11.3 15.65 0 438.67 378.22 53848 +1953 140 15.12 9.12 13.47 0 386.79 384.55 53981 +1953 141 18.89 12.89 17.24 0 480.14 374.37 54111 +1953 142 16.48 10.48 14.83 0 418.5 381.93 54238 +1953 143 16.3 10.3 14.65 0 414.18 382.95 54362 +1953 144 19.86 13.86 18.21 0.68 507.05 279.54 54483 +1953 145 21.99 15.99 20.34 0.88 570.66 274.24 54600 +1953 146 19.69 13.69 18.04 0.23 502.24 280.59 54714 +1953 147 19.58 13.58 17.93 0 499.16 374.95 54824 +1953 148 18.85 12.85 17.2 0 479.06 377.68 54931 +1953 149 18.9 12.9 17.25 0 480.41 377.83 55034 +1953 150 17.11 11.11 15.46 0 433.92 383.54 55134 +1953 151 17.45 11.45 15.8 0 442.44 382.96 55229 +1953 152 19.9 13.9 18.25 0.59 508.19 281.55 55321 +1953 153 18.46 12.46 16.81 0 468.61 380.28 55409 +1953 154 18.18 12.18 16.53 1.1 461.23 286.09 55492 +1953 155 16.77 10.77 15.12 0 425.54 385.77 55572 +1953 156 17.82 11.82 16.17 0 451.88 383.06 55648 +1953 157 22.28 16.28 20.63 0 579.83 368.07 55719 +1953 158 25.54 19.54 23.89 0.04 691.73 265.88 55786 +1953 159 23.7 17.7 22.05 0.63 626.52 272.1 55849 +1953 160 22.8 16.8 21.15 2.38 596.57 274.97 55908 +1953 161 20.5 14.5 18.85 0.67 525.5 281.43 55962 +1953 162 22.23 16.23 20.58 0.23 578.24 276.73 56011 +1953 163 25.44 19.44 23.79 0 688.04 355.69 56056 +1953 164 22.41 16.41 20.76 0.13 583.98 276.4 56097 +1953 165 22.72 16.72 21.07 0.15 593.97 275.56 56133 +1953 166 19.46 13.46 17.81 0.08 495.8 284.44 56165 +1953 167 20.34 14.34 18.69 0.67 520.83 282.18 56192 +1953 168 16.97 10.97 15.32 0.1 430.45 290.17 56214 +1953 169 18.61 12.61 16.96 0.38 472.61 286.51 56231 +1953 170 16.84 10.84 15.19 0.25 427.25 290.46 56244 +1953 171 20.48 14.48 18.83 0 524.91 375.9 56252 +1953 172 21.43 15.43 19.78 0.01 553.32 279.37 56256 +1953 173 15.74 9.74 14.09 0.17 400.98 292.74 56255 +1953 174 21.49 15.49 19.84 0.06 555.15 279.13 56249 +1953 175 20.22 14.22 18.57 1 517.36 282.49 56238 +1953 176 21.96 15.96 20.31 0.74 569.72 277.76 56223 +1953 177 23.4 17.4 21.75 0.96 616.4 273.43 56203 +1953 178 25.66 19.66 24.01 0.77 696.18 266.05 56179 +1953 179 24.14 18.14 22.49 2.98 641.62 271.05 56150 +1953 180 24.82 18.82 23.17 0.21 665.56 268.75 56116 +1953 181 22.06 16.06 20.41 0 572.86 369.61 56078 +1953 182 20.42 14.42 18.77 0.13 523.16 281.56 56035 +1953 183 23.62 17.62 21.97 0 623.81 363.09 55987 +1953 184 26.16 20.16 24.51 0.01 714.96 263.74 55935 +1953 185 24.6 18.6 22.95 0.63 657.73 269.02 55879 +1953 186 20.46 14.46 18.81 0.17 524.33 280.95 55818 +1953 187 26.46 20.46 24.81 1.62 726.43 262.29 55753 +1953 188 28.23 22.23 26.58 0.45 797.35 255.37 55684 +1953 189 29.49 23.49 27.84 0.51 851.31 250.05 55611 +1953 190 27.13 21.13 25.48 0.5 752.62 259.23 55533 +1953 191 29.05 23.05 27.4 0.13 832.13 251.46 55451 +1953 192 21.46 15.46 19.81 0 554.23 369.48 55366 +1953 193 22.74 16.74 21.09 0.99 594.62 273.27 55276 +1953 194 21.86 15.86 20.21 0.49 566.6 275.63 55182 +1953 195 25.29 19.29 23.64 0.59 682.55 264.84 55085 +1953 196 24.08 18.08 22.43 0 639.54 358.01 54984 +1953 197 16.27 10.27 14.62 0.39 413.46 288.18 54879 +1953 198 12.99 6.99 11.34 0 341.25 391.86 54770 +1953 199 15.7 9.7 14.05 0 400.05 384.95 54658 +1953 200 16.66 10.66 15.01 0 422.85 381.96 54542 +1953 201 21.2 15.2 19.55 0 546.32 367.16 54423 +1953 202 22.77 16.77 21.12 0 595.59 360.73 54301 +1953 203 20.28 14.28 18.63 0 519.09 369.3 54176 +1953 204 22.55 16.55 20.9 0 588.47 360.58 54047 +1953 205 27.6 21.6 25.95 0 771.46 337.69 53915 +1953 206 28.45 22.45 26.8 0 806.56 332.76 53780 +1953 207 25.37 19.37 23.72 0 685.47 347.16 53643 +1953 208 25.09 19.09 23.44 0.23 675.27 260.83 53502 +1953 209 25.35 19.35 23.7 0.59 684.74 259.5 53359 +1953 210 21.87 15.87 20.22 0 566.91 359.53 53213 +1953 211 22.95 16.95 21.3 0.01 601.48 266 53064 +1953 212 24.81 18.81 23.16 0.22 665.2 259.69 52913 +1953 213 22.88 16.88 21.23 0 599.18 353.42 52760 +1953 214 19.69 13.69 18.04 0.56 502.24 272.99 52604 +1953 215 23.73 17.73 22.08 0.17 627.54 261.5 52445 +1953 216 23.94 17.94 22.29 1.49 634.72 260.11 52285 +1953 217 21.66 15.66 20.01 0.62 560.39 266.02 52122 +1953 218 20.47 14.47 18.82 0.31 524.62 268.51 51958 +1953 219 21.58 15.58 19.93 0.4 557.92 264.85 51791 +1953 220 21.08 15.08 19.43 0 542.7 353.96 51622 +1953 221 22.39 16.39 20.74 0.01 583.34 261.21 51451 +1953 222 24.29 18.29 22.64 0 646.84 339.82 51279 +1953 223 22.79 16.79 21.14 0.97 596.25 258.47 51105 +1953 224 21.5 15.5 19.85 0.66 555.46 261.22 50929 +1953 225 18.87 12.87 17.22 1.51 479.6 266.79 50751 +1953 226 19.61 13.61 17.96 0 500 352.29 50572 +1953 227 20.24 14.24 18.59 0 517.94 349 50392 +1953 228 27.65 21.65 26 0 773.49 318.13 50210 +1953 229 23.46 17.46 21.81 0.18 618.41 251.38 50026 +1953 230 22.33 16.33 20.68 0 581.42 338.15 49842 +1953 231 19.45 13.45 17.8 0.06 495.53 259.73 49656 +1953 232 19.86 13.86 18.21 0 507.05 343.68 49469 +1953 233 18.38 12.38 16.73 0.11 466.49 260.02 49280 +1953 234 19.11 13.11 17.46 0 486.14 343.13 49091 +1953 235 16.07 10.07 14.42 0 408.71 349.91 48900 +1953 236 15.13 9.13 13.48 0.62 387.01 263.04 48709 +1953 237 16.62 10.62 14.97 0.52 421.88 259.05 48516 +1953 238 16.8 10.8 15.15 0 426.27 343.25 48323 +1953 239 20.13 14.13 18.48 0.03 514.76 249.23 48128 +1953 240 23.82 17.82 22.17 0.12 630.61 238.42 47933 +1953 241 23.96 17.96 22.31 0 635.41 315.71 47737 +1953 242 25.53 19.53 23.88 0 691.36 307.81 47541 +1953 243 21.68 15.68 20.03 0.02 561.01 240.26 47343 +1953 244 19.36 13.36 17.71 0 493.03 325.78 47145 +1953 245 18.65 12.65 17 0 473.68 325.96 46947 +1953 246 22.36 16.36 20.71 0.01 582.38 234.43 46747 +1953 247 22.56 16.56 20.91 0.63 588.79 232.56 46547 +1953 248 21.14 15.14 19.49 0.31 544.51 234.66 46347 +1953 249 22.03 16.03 20.38 0 571.92 307.99 46146 +1953 250 24.85 18.85 23.2 0 666.63 296.05 45945 +1953 251 23.46 17.46 21.81 0.08 618.41 224.38 45743 +1953 252 21.95 15.95 20.3 0 569.41 302.21 45541 +1953 253 22.59 16.59 20.94 0.3 589.76 223.54 45339 +1953 254 22.45 16.45 20.8 0 585.26 296.47 45136 +1953 255 22.61 16.61 20.96 0 590.41 293.76 44933 +1953 256 19.27 13.27 17.62 0.05 490.54 226.21 44730 +1953 257 20.62 14.62 18.97 1.48 529.02 221.76 44527 +1953 258 14.46 8.46 12.81 3.06 372.15 231.37 44323 +1953 259 18.38 12.38 16.73 0.28 466.49 222.83 44119 +1953 260 18.87 12.87 17.22 0.3 479.6 220.12 43915 +1953 261 17.72 11.72 16.07 0.13 449.31 220.47 43711 +1953 262 17.4 11.4 15.75 0.28 441.18 219.28 43507 +1953 263 18.25 12.25 16.6 0 463.06 287.88 43303 +1953 264 18.61 12.61 16.96 0.06 472.61 213.33 43099 +1953 265 21.44 15.44 19.79 0 553.62 274.47 42894 +1953 266 23.25 17.25 21.6 0 611.39 266.55 42690 +1953 267 16.57 10.57 14.92 0 420.67 281.77 42486 +1953 268 13.07 7.07 11.42 0 342.87 286.07 42282 +1953 269 13.05 7.05 11.4 0 342.47 283.56 42078 +1953 270 14.71 8.71 13.06 0 377.64 277.87 41875 +1953 271 17.34 11.34 15.69 0.42 439.67 202.38 41671 +1953 272 17.66 11.66 16.01 1.67 447.78 199.82 41468 +1953 273 14.6 8.6 12.95 0.09 375.22 202.64 41265 +1953 274 8.99 2.99 7.34 0 268.03 276.29 41062 +1953 275 11.31 5.31 9.66 0 308.64 270.21 40860 +1953 276 9.92 3.92 8.27 0 283.72 269.46 40658 +1953 277 11.6 5.6 9.95 0 314.07 264.35 40456 +1953 278 10.74 4.74 9.09 0 298.21 262.71 40255 +1953 279 16.3 10.3 14.65 0 414.18 250.56 40054 +1953 280 14.12 8.12 12.47 0.28 364.8 188.95 39854 +1953 281 16.37 10.37 14.72 0.07 415.85 183.85 39654 +1953 282 17.14 11.14 15.49 0.12 434.67 180.69 39455 +1953 283 18.27 12.27 16.62 0 463.59 235.83 39256 +1953 284 17.57 11.57 15.92 0.07 445.49 175.75 39058 +1953 285 12.57 6.57 10.92 0 332.83 240.49 38861 +1953 286 14.21 8.21 12.56 0.36 366.73 176.38 38664 +1953 287 14.88 8.88 13.23 0.24 381.41 173.36 38468 +1953 288 15.29 9.29 13.64 0.3 390.64 170.77 38273 +1953 289 11.66 5.66 10.01 0.8 315.21 172.99 38079 +1953 290 15.53 9.53 13.88 1.9 396.12 166.41 37885 +1953 291 15.4 9.4 13.75 0.27 393.14 164.58 37693 +1953 292 14.94 8.94 13.29 0.22 382.75 163.17 37501 +1953 293 12.64 6.64 10.99 0 334.22 218.33 37311 +1953 294 11.34 5.34 9.69 0 309.2 217.19 37121 +1953 295 15.13 9.13 13.48 0 387.01 208.93 36933 +1953 296 17.07 11.07 15.42 0 432.93 203.14 36745 +1953 297 17.96 11.96 16.31 0 455.5 198.88 36560 +1953 298 19.9 13.9 18.25 0 508.19 192.6 36375 +1953 299 20.68 14.68 19.03 0 530.79 188.32 36191 +1953 300 14.86 8.86 13.21 0 380.96 196.24 36009 +1953 301 22.04 16.04 20.39 0 572.24 180.48 35829 +1953 302 14.04 8.04 12.39 0.01 363.09 144.29 35650 +1953 303 11.61 5.61 9.96 0 314.26 193.01 35472 +1953 304 9.25 3.25 7.6 0 272.34 193.18 35296 +1953 305 0.64 -5.36 -1.01 0 157.39 197.18 35122 +1953 306 -1.38 -7.38 -3.03 0 137.53 195.95 34950 +1953 307 2.96 -3.04 1.31 0 183.21 190.85 34779 +1953 308 4.05 -1.95 2.4 0 196.55 187.46 34610 +1953 309 3.16 -2.84 1.51 0 185.59 185.71 34444 +1953 310 5.81 -0.19 4.16 0 219.85 181.32 34279 +1953 311 5.82 -0.18 4.17 0 219.99 179.12 34116 +1953 312 4.73 -1.27 3.08 0 205.29 177.26 33956 +1953 313 8.95 2.95 7.3 0 267.37 171.67 33797 +1953 314 5.9 -0.1 4.25 0 221.11 172.29 33641 +1953 315 6.88 0.88 5.23 0 235.16 168.98 33488 +1953 316 5.99 -0.01 4.34 0 222.37 167.47 33337 +1953 317 4.55 -1.45 2.9 0 202.94 166.29 33188 +1953 318 4.91 -1.09 3.26 0.04 207.65 122.77 33042 +1953 319 4.88 -1.12 3.23 0 207.26 162 32899 +1953 320 5.09 -0.91 3.44 0 210.05 159.98 32758 +1953 321 9.69 3.69 8.04 0 279.77 154.22 32620 +1953 322 6.9 0.9 5.25 0 235.45 154.73 32486 +1953 323 9.44 3.44 7.79 0 275.52 151.04 32354 +1953 324 9.81 3.81 8.16 0.03 281.82 111.51 32225 +1953 325 5.66 -0.34 4.01 0 217.78 150.23 32100 +1953 326 8.02 2.02 6.37 0 252.46 147.04 31977 +1953 327 6.59 0.59 4.94 0 230.92 146.27 31858 +1953 328 8.19 2.19 6.54 0 255.13 143.11 31743 +1953 329 8.34 2.34 6.69 0 257.5 141.51 31631 +1953 330 8.86 2.86 7.21 0 265.89 139.66 31522 +1953 331 11.54 5.54 9.89 0 312.94 136.02 31417 +1953 332 6.27 0.27 4.62 0 226.32 138.64 31316 +1953 333 6.05 0.05 4.4 0 223.21 137.7 31218 +1953 334 6.31 0.31 4.66 0.5 226.89 102.32 31125 +1953 335 4.06 -1.94 2.41 0.07 196.67 102.49 31035 +1953 336 0.31 -5.69 -1.34 0 153.98 137.48 30949 +1953 337 1.7 -4.3 0.05 0 168.77 135.16 30867 +1953 338 3.11 -2.89 1.46 0 184.99 133.49 30790 +1953 339 2.79 -3.21 1.14 0 181.2 132.87 30716 +1953 340 1.8 -4.2 0.15 0 169.87 132.63 30647 +1953 341 0.11 -5.89 -1.54 0 151.95 132.47 30582 +1953 342 -1.18 -7.18 -2.83 0.03 139.39 142.51 30521 +1953 343 -0.17 -6.17 -1.82 0 149.15 174.41 30465 +1953 344 -1.31 -7.31 -2.96 0 138.18 173.8 30413 +1953 345 -1.98 -7.98 -3.63 0 132.07 173.68 30366 +1953 346 -5.78 -11.78 -7.43 0 101.63 174.41 30323 +1953 347 1 -5 -0.65 0 161.18 127.75 30284 +1953 348 4.62 -1.38 2.97 0 203.85 125.57 30251 +1953 349 8.36 2.36 6.71 0 257.82 122.8 30221 +1953 350 9.29 3.29 7.64 0 273.01 121.78 30197 +1953 351 5.33 -0.67 3.68 0 213.27 124.23 30177 +1953 352 3.28 -2.72 1.63 0.12 187.04 93.95 30162 +1953 353 3.31 -2.69 1.66 0 187.4 125.19 30151 +1953 354 0.08 -5.92 -1.57 0 151.65 126.66 30145 +1953 355 6.14 0.14 4.49 0 224.48 123.54 30144 +1953 356 10.35 4.35 8.7 0 291.24 120.57 30147 +1953 357 7.69 1.69 6.04 0 247.34 122.61 30156 +1953 358 5.08 -0.92 3.43 0 209.91 124.35 30169 +1953 359 5.54 -0.46 3.89 0 216.13 124.2 30186 +1953 360 5.61 -0.39 3.96 0 217.09 124.52 30208 +1953 361 5.37 -0.63 3.72 0 213.82 125 30235 +1953 362 4.27 -1.73 2.62 0 199.34 126.06 30267 +1953 363 2.93 -3.07 1.28 0 182.85 127.36 30303 +1953 364 2.26 -3.74 0.61 0 175.06 128.1 30343 +1953 365 0.16 -5.84 -1.49 0 152.46 129.63 30388 +1954 1 -2.55 -8.55 -4.2 0.12 127.05 142.43 30438 +1954 2 -3.84 -9.84 -5.49 0.27 116.3 144.09 30492 +1954 3 -5.92 -11.92 -7.57 0.53 100.63 146.86 30551 +1954 4 -6.55 -12.55 -8.2 0.15 96.27 148.06 30614 +1954 5 -2.95 -8.95 -4.6 0 123.63 181.38 30681 +1954 6 -5.19 -11.19 -6.84 0 105.91 182.9 30752 +1954 7 1.26 -4.74 -0.39 0 163.96 180.97 30828 +1954 8 -2.6 -8.6 -4.25 0.01 126.62 149.47 30907 +1954 9 -4.58 -10.58 -6.23 0 110.5 185.82 30991 +1954 10 -5.63 -11.63 -7.28 0 102.7 187.33 31079 +1954 11 -4.42 -10.42 -6.07 0 111.74 187.83 31171 +1954 12 -3.13 -9.13 -4.78 0.05 122.12 152.71 31266 +1954 13 -4.13 -10.13 -5.78 0.09 114 154.33 31366 +1954 14 -5.58 -11.58 -7.23 0.1 103.06 155.96 31469 +1954 15 0.66 -5.34 -0.99 0 157.6 191.5 31575 +1954 16 -1.29 -7.29 -2.94 0.17 138.37 157 31686 +1954 17 -1.36 -7.36 -3.01 2.16 137.72 164.66 31800 +1954 18 -4.18 -10.18 -5.83 0.45 113.61 168.07 31917 +1954 19 -6.42 -12.42 -8.07 0 97.15 208.76 32038 +1954 20 -6.92 -12.92 -8.57 0 93.78 210.33 32161 +1954 21 -6.62 -12.62 -8.27 0 95.79 212.07 32289 +1954 22 -2.12 -8.12 -3.77 0 130.82 212.05 32419 +1954 23 -0.53 -6.53 -2.18 0 145.6 212.92 32552 +1954 24 3.7 -2.3 2.05 0 192.17 212.03 32688 +1954 25 6.03 0.03 4.38 0.06 222.93 171.23 32827 +1954 26 7.47 1.47 5.82 0 243.98 211.04 32969 +1954 27 2.24 -3.76 0.59 0 174.83 216.18 33114 +1954 28 1.95 -4.05 0.3 0 171.55 218.12 33261 +1954 29 0 -6 -1.65 0 150.84 221.35 33411 +1954 30 -0.63 -6.63 -2.28 0 144.63 223.71 33564 +1954 31 -1.88 -7.88 -3.53 0 132.96 226.48 33718 +1954 32 0.38 -5.62 -1.27 0.74 154.7 182.37 33875 +1954 33 -1.59 -7.59 -3.24 0 135.6 230.66 34035 +1954 34 0.36 -5.64 -1.29 0 154.5 231.63 34196 +1954 35 -3.35 -9.35 -5 0.03 120.29 188.38 34360 +1954 36 -2.07 -8.07 -3.72 0 131.26 237.21 34526 +1954 37 -0.55 -6.55 -2.2 0 145.41 238.69 34694 +1954 38 1.82 -4.18 0.17 0 170.1 239.65 34863 +1954 39 0.96 -5.04 -0.69 0.07 160.75 193.33 35035 +1954 40 1.67 -4.33 0.02 0 168.43 244.25 35208 +1954 41 2 -4 0.35 0 172.11 246.22 35383 +1954 42 0.16 -5.84 -1.49 0 152.46 249.69 35560 +1954 43 -3.14 -9.14 -4.79 0 122.03 253.93 35738 +1954 44 -9.75 -15.75 -11.4 0 76.52 258.8 35918 +1954 45 -6.77 -12.77 -8.42 0 94.78 260.28 36099 +1954 46 -8.6 -14.6 -10.25 0.31 83.17 209.38 36282 +1954 47 -6.46 -12.46 -8.11 0 96.88 266.17 36466 +1954 48 -5.47 -11.47 -7.12 0 103.86 268.42 36652 +1954 49 -9.36 -15.36 -11.01 0 78.72 272.45 36838 +1954 50 -11.08 -17.08 -12.73 0.01 69.42 217.59 37026 +1954 51 -10.14 -16.14 -11.79 0 74.38 278.05 37215 +1954 52 -6.52 -12.52 -8.17 0 96.47 279.47 37405 +1954 53 -5.38 -11.38 -7.03 0 104.52 281.8 37596 +1954 54 -1.19 -7.19 -2.84 0 139.3 282.26 37788 +1954 55 1.62 -4.38 -0.03 0 167.88 283.07 37981 +1954 56 2.34 -3.66 0.69 0 175.97 284.79 38175 +1954 57 5.19 -0.81 3.54 0 211.39 284.53 38370 +1954 58 3.89 -2.11 2.24 0 194.54 288.02 38565 +1954 59 5 -1 3.35 0 208.85 289.02 38761 +1954 60 15.04 9.04 13.39 0.13 384.99 217.33 38958 +1954 61 11.4 5.4 9.75 0.58 310.32 222.41 39156 +1954 62 10.36 4.36 8.71 0.9 291.42 224.3 39355 +1954 63 7.76 1.76 6.11 0.54 248.42 227.99 39553 +1954 64 9.55 3.55 7.9 0.01 277.38 227.38 39753 +1954 65 8.68 2.68 7.03 0.12 262.96 196.83 39953 +1954 66 5.75 -0.25 4.1 0.88 219.02 201.37 40154 +1954 67 7.7 1.7 6.05 0 247.49 269.24 40355 +1954 68 7.14 1.14 5.49 0.43 239.01 204.57 40556 +1954 69 6.56 0.56 4.91 0 230.49 276.05 40758 +1954 70 5.65 -0.35 4 0 217.64 279.89 40960 +1954 71 1.65 -4.35 0 0.03 168.21 214.94 41163 +1954 72 4.85 -1.15 3.2 0 206.86 286.5 41366 +1954 73 3.39 -2.61 1.74 0 188.37 290.63 41569 +1954 74 7.76 1.76 6.11 0 248.42 288.65 41772 +1954 75 8.83 2.83 7.18 0 265.4 289.98 41976 +1954 76 8.55 2.55 6.9 0 260.86 292.99 42179 +1954 77 14.37 8.37 12.72 0 370.19 286.19 42383 +1954 78 17.31 11.31 15.66 0 438.92 282.6 42587 +1954 79 15.92 9.92 14.27 0 405.18 288.3 42791 +1954 80 12.03 6.03 10.38 0 322.28 298.19 42996 +1954 81 13.18 7.18 11.53 0 345.12 298.71 43200 +1954 82 10.57 4.57 8.92 0.08 295.15 229.32 43404 +1954 83 11.27 5.27 9.62 0 307.9 307.11 43608 +1954 84 10.88 4.88 9.23 0 300.74 310.26 43812 +1954 85 9.63 3.63 7.98 0 278.74 314.7 44016 +1954 86 9.51 3.51 7.86 0.01 276.71 237.97 44220 +1954 87 8.98 2.98 7.33 0 267.86 320.61 44424 +1954 88 3.94 -2.06 2.29 0 195.16 329.32 44627 +1954 89 5.01 -0.99 3.36 0.24 208.98 247.84 44831 +1954 90 0.13 -5.87 -1.52 0.35 152.15 253.26 45034 +1954 91 2.58 -3.42 0.93 0 178.74 337.76 45237 +1954 92 3.36 -2.64 1.71 0.01 188.01 254.44 45439 +1954 93 6.62 0.62 4.97 0.3 231.36 253.26 45642 +1954 94 9.86 3.86 8.21 0.14 282.68 251.36 45843 +1954 95 15.07 9.07 13.42 0 385.66 327.38 46045 +1954 96 12.15 6.15 10.5 0.34 324.6 251.57 46246 +1954 97 13 7 11.35 0.03 341.45 251.87 46446 +1954 98 13.18 7.18 11.53 0 345.12 337.42 46647 +1954 99 9.39 3.39 7.74 0 274.68 346.24 46846 +1954 100 13.53 7.53 11.88 0 352.34 340.63 47045 +1954 101 12.01 6.01 10.36 0 321.89 345.56 47243 +1954 102 10.69 4.69 9.04 0 297.3 349.87 47441 +1954 103 12.43 6.43 10.78 0 330.07 348.49 47638 +1954 104 12.56 6.56 10.91 1.59 332.64 262.54 47834 +1954 105 9.16 3.16 7.51 0.55 270.84 268.46 48030 +1954 106 10.59 4.59 8.94 0.03 295.51 267.89 48225 +1954 107 7.84 1.84 6.19 0 249.65 363.37 48419 +1954 108 7.4 1.4 5.75 0 242.92 365.79 48612 +1954 109 4.32 -1.68 2.67 0 199.98 371.53 48804 +1954 110 7.91 1.91 6.26 0 250.74 368.11 48995 +1954 111 11.1 5.1 9.45 0 304.76 364.31 49185 +1954 112 10.38 4.38 8.73 0 291.77 367.16 49374 +1954 113 9.68 3.68 8.03 0 279.6 369.74 49561 +1954 114 11.03 5.03 9.38 0 303.48 368.83 49748 +1954 115 12.6 6.6 10.95 0 333.43 367.18 49933 +1954 116 13.99 7.99 12.34 0 362.02 365.41 50117 +1954 117 17.69 11.69 16.04 0 448.55 357.38 50300 +1954 118 19.23 13.23 17.58 0 489.43 354.14 50481 +1954 119 16.31 10.31 14.66 0.58 414.42 272.68 50661 +1954 120 13.8 7.8 12.15 2.34 357.99 278.12 50840 +1954 121 19.4 13.4 17.75 0.35 494.14 267.75 51016 +1954 122 17.55 11.55 15.9 0.13 444.98 272.75 51191 +1954 123 13.79 7.79 12.14 0.34 357.78 280.66 51365 +1954 124 15.54 9.54 13.89 0.53 396.35 278.33 51536 +1954 125 16.06 10.06 14.41 0.28 408.48 278.07 51706 +1954 126 12.78 6.78 11.13 2.01 337.02 284.63 51874 +1954 127 11.91 5.91 10.26 0.36 319.97 286.67 52039 +1954 128 15.47 9.47 13.82 0.53 394.74 281.36 52203 +1954 129 19.8 13.8 18.15 0.71 505.35 272.65 52365 +1954 130 19.19 13.19 17.54 0.01 488.33 274.69 52524 +1954 131 15.51 9.51 13.86 0.4 395.66 283.11 52681 +1954 132 16.84 10.84 15.19 1.11 427.25 281.09 52836 +1954 133 16.84 10.84 15.19 0 427.25 375.48 52989 +1954 134 19.03 13.03 17.38 0.68 483.95 277.3 53138 +1954 135 18.32 12.32 16.67 0.41 464.91 279.46 53286 +1954 136 21.3 15.3 19.65 0.42 549.35 272.57 53430 +1954 137 23.4 17.4 21.75 0.61 616.4 267.09 53572 +1954 138 17.39 11.39 15.74 0 440.93 377.27 53711 +1954 139 13.19 7.19 11.54 0.28 345.32 291.48 53848 +1954 140 11.43 5.43 9.78 1.39 310.88 294.66 53981 +1954 141 11.98 5.98 10.33 0.87 321.31 294.15 54111 +1954 142 8.33 2.33 6.68 0.34 257.34 299.65 54238 +1954 143 8.56 2.56 6.91 0 261.02 399.7 54362 +1954 144 14.7 8.7 13.05 0 377.42 387.56 54483 +1954 145 11.95 5.95 10.3 0.11 320.74 295.72 54600 +1954 146 15.8 9.8 14.15 0.15 402.38 289.21 54714 +1954 147 21.16 15.16 19.51 0 545.11 369.53 54824 +1954 148 22.03 16.03 20.38 0 571.92 366.7 54931 +1954 149 21.18 15.18 19.53 0 545.72 370.14 55034 +1954 150 21.49 15.49 19.84 0 555.15 369.34 55134 +1954 151 20.81 14.81 19.16 0 534.64 372.17 55229 +1954 152 28.02 22.02 26.37 0 788.64 340.97 55321 +1954 153 23.82 17.82 22.17 0 630.61 360.93 55409 +1954 154 21.38 15.38 19.73 0 551.79 370.78 55492 +1954 155 18.5 12.5 16.85 0 469.67 380.67 55572 +1954 156 16.22 10.22 14.57 1.44 412.27 290.71 55648 +1954 157 15.91 9.91 14.26 1.2 404.95 291.46 55719 +1954 158 15.74 9.74 14.09 0 400.98 389.24 55786 +1954 159 18.51 12.51 16.86 0.37 469.94 286.16 55849 +1954 160 18.8 12.8 17.15 1.76 477.71 285.61 55908 +1954 161 19.33 13.33 17.68 0.55 492.19 284.39 55962 +1954 162 22.62 16.62 20.97 0.23 590.73 275.6 56011 +1954 163 22.8 16.8 21.15 0.03 596.57 275.22 56056 +1954 164 23.04 17.04 21.39 0.74 604.44 274.53 56097 +1954 165 24.65 18.65 23 0.17 659.51 269.53 56133 +1954 166 26.45 20.45 24.8 0.02 726.05 263.36 56165 +1954 167 22.99 16.99 21.34 0.01 602.79 274.77 56192 +1954 168 22.34 16.34 20.69 0.28 581.74 276.75 56214 +1954 169 22.81 16.81 21.16 0.07 596.9 275.38 56231 +1954 170 24.28 18.28 22.63 0.86 646.49 270.82 56244 +1954 171 23.85 17.85 22.2 0 631.63 362.98 56252 +1954 172 23.28 17.28 21.63 0.16 612.39 274 56256 +1954 173 22.65 16.65 21 0.01 591.7 275.88 56255 +1954 174 21.37 15.37 19.72 0 551.49 372.61 56249 +1954 175 21.5 15.5 19.85 0.24 555.46 279.08 56238 +1954 176 18.63 12.63 16.98 0.03 473.14 286.38 56223 +1954 177 22.95 16.95 21.3 0.31 601.48 274.8 56203 +1954 178 21.25 15.25 19.6 0.01 547.84 279.68 56179 +1954 179 24.95 18.95 23.3 0 670.22 357.87 56150 +1954 180 21.51 15.51 19.86 0 555.77 371.73 56116 +1954 181 24.08 18.08 22.43 0.01 639.54 271.11 56078 +1954 182 23.82 17.82 22.17 0 630.61 362.43 56035 +1954 183 23.69 17.69 22.04 0.78 626.18 272.1 55987 +1954 184 21.21 15.21 19.56 0.69 546.63 279.22 55935 +1954 185 20.56 14.56 18.91 0 527.26 374.51 55879 +1954 186 23.32 17.32 21.67 0.62 613.72 272.88 55818 +1954 187 19.89 13.89 18.24 0 507.9 376.36 55753 +1954 188 18.81 12.81 17.16 0 477.98 379.61 55684 +1954 189 18.13 12.13 16.48 0 459.92 381.53 55611 +1954 190 17.93 11.93 16.28 0 454.72 381.76 55533 +1954 191 21.62 15.62 19.97 0 559.15 369.19 55451 +1954 192 19.07 13.07 17.42 0 485.04 377.66 55366 +1954 193 17.28 11.28 15.63 0 438.16 382.81 55276 +1954 194 21.94 15.94 20.29 0.48 569.1 275.4 55182 +1954 195 23.47 17.47 21.82 0.71 618.75 270.71 55085 +1954 196 21.88 15.88 20.23 0.1 567.22 275.07 54984 +1954 197 17.02 11.02 15.37 0.03 431.69 286.62 54879 +1954 198 19.81 13.81 18.16 0.8 505.63 279.88 54770 +1954 199 20.21 14.21 18.56 1.8 517.07 278.61 54658 +1954 200 20.36 14.36 18.71 1.3 521.41 277.92 54542 +1954 201 20.58 14.58 18.93 0.74 527.84 277.01 54423 +1954 202 23.29 17.29 21.64 0 612.72 358.67 54301 +1954 203 22.16 16.16 20.51 0 576.02 362.57 54176 +1954 204 21.92 15.92 20.27 0.02 568.47 272.23 54047 +1954 205 24.23 18.23 22.58 0.42 644.75 264.98 53915 +1954 206 20.88 14.88 19.23 0 536.72 365.65 53780 +1954 207 20.73 14.73 19.08 0.9 532.26 274.14 53643 +1954 208 16.66 10.66 15.01 0.43 422.85 283.06 53502 +1954 209 22.52 16.52 20.87 0 587.51 357.7 53359 +1954 210 21.88 15.88 20.23 0.4 567.22 269.62 53213 +1954 211 17.05 11.05 15.4 0 432.43 374.25 53064 +1954 212 14.51 8.51 12.86 0 373.25 380.01 52913 +1954 213 18.35 12.35 16.7 0.42 465.7 276.68 52760 +1954 214 20.03 14.03 18.38 0 511.9 362.88 52604 +1954 215 20.09 14.09 18.44 0 513.62 362 52445 +1954 216 19.2 13.2 17.55 0 488.61 363.84 52285 +1954 217 23.01 17.01 21.36 0.36 603.45 262.24 52122 +1954 218 23.62 17.62 21.97 0 623.81 346.46 51958 +1954 219 22.8 16.8 21.15 0 596.57 348.64 51791 +1954 220 24.52 18.52 22.87 0.07 654.91 255.64 51622 +1954 221 28.22 22.22 26.57 0.38 796.93 242.07 51451 +1954 222 25.47 19.47 23.82 0.15 689.15 251.1 51279 +1954 223 22.17 16.17 20.52 0.6 576.34 260.2 51105 +1954 224 23.22 17.22 21.57 0 610.39 341.96 50929 +1954 225 22.67 16.67 21.02 0 592.35 342.93 50751 +1954 226 24.94 18.94 23.29 0 669.86 332.79 50572 +1954 227 23.4 17.4 21.75 0.51 616.4 253.34 50392 +1954 228 27.39 21.39 25.74 0.23 763 239.54 50210 +1954 229 25.25 19.25 23.6 0 681.09 327.9 50026 +1954 230 23.13 17.13 21.48 0.43 607.41 251.4 49842 +1954 231 17.25 11.25 15.6 0.21 437.41 264.48 49656 +1954 232 19.22 13.22 17.57 0.05 489.16 259.24 49469 +1954 233 16.79 10.79 15.14 0.52 426.03 263.28 49280 +1954 234 16.76 10.76 15.11 0 425.29 349.68 49091 +1954 235 17.38 11.38 15.73 0.92 440.68 259.9 48900 +1954 236 17.47 11.47 15.82 0.19 442.95 258.63 48709 +1954 237 18.44 12.44 16.79 0 468.08 340.5 48516 +1954 238 19.97 13.97 18.32 0 510.18 334.31 48323 +1954 239 23.48 17.48 21.83 0 619.08 320.88 48128 +1954 240 20.85 14.85 19.2 1.88 535.82 246.22 47933 +1954 241 21.52 15.52 19.87 0 556.07 324.41 47737 +1954 242 19.96 13.96 18.31 0 509.9 327.66 47541 +1954 243 21.43 15.43 19.78 0 553.32 321.18 47343 +1954 244 18.31 12.31 16.66 0.01 464.64 246.56 47145 +1954 245 15.63 9.63 13.98 0 398.43 333.66 46947 +1954 246 16.5 10.5 14.85 0 418.98 329.6 46747 +1954 247 20.39 14.39 18.74 1.19 522.29 237.84 46547 +1954 248 19.39 13.39 17.74 0.78 493.86 238.61 46347 +1954 249 17.28 11.28 15.63 0 438.16 321.76 46146 +1954 250 17.22 11.22 15.57 1.22 436.66 239.97 45945 +1954 251 19.36 13.36 17.71 0.2 493.03 234.13 45743 +1954 252 16.88 10.88 15.23 0.4 428.23 237.38 45541 +1954 253 19.95 13.95 18.3 0.44 509.61 229.7 45339 +1954 254 20.06 14.06 18.41 1.46 512.76 227.89 45136 +1954 255 20.13 14.13 18.48 1.42 514.76 226.08 44933 +1954 256 20.79 14.79 19.14 0.3 534.04 222.96 44730 +1954 257 16.97 10.97 15.32 0 430.45 305.33 44527 +1954 258 18.31 12.31 16.66 0.33 464.64 224.77 44323 +1954 259 20.05 14.05 18.4 0.63 512.47 219.48 44119 +1954 260 17.3 11.3 15.65 0.25 438.67 223.05 43915 +1954 261 21.39 15.39 19.74 0 552.1 284.06 43711 +1954 262 21.63 15.63 19.98 0.18 559.46 210.79 43507 +1954 263 25.19 19.19 23.54 0 678.9 266.89 43303 +1954 264 23.93 17.93 22.28 0.23 634.38 201.67 43099 +1954 265 22.85 16.85 21.2 0 598.2 270.18 42894 +1954 266 20.62 14.62 18.97 0 529.02 274.41 42690 +1954 267 21.7 15.7 20.05 0.02 561.62 201.56 42486 +1954 268 20.89 14.89 19.24 0 537.02 268.59 42282 +1954 269 21.46 15.46 19.81 1.02 554.23 198.43 42078 +1954 270 19.46 13.46 17.81 0.06 495.8 200.54 41875 +1954 271 19.93 13.93 18.28 0.03 509.04 197.73 41671 +1954 272 20.99 14.99 19.34 0 540 258.19 41468 +1954 273 22.43 16.43 20.78 0 584.62 251.72 41265 +1954 274 16.72 10.72 15.07 0 424.32 263.34 41062 +1954 275 12.09 6.09 10.44 0 323.43 269.02 40860 +1954 276 11.31 5.31 9.66 0 308.64 267.48 40658 +1954 277 9.8 3.8 8.15 1.2 281.65 200.19 40456 +1954 278 10.94 4.94 9.29 0.27 301.83 196.82 40255 +1954 279 13.52 7.52 11.87 0.89 352.13 191.7 40054 +1954 280 14.35 8.35 12.7 0.07 369.76 188.66 39854 +1954 281 14.4 8.4 12.75 0 370.85 248.75 39654 +1954 282 13.44 7.44 11.79 0 350.47 247.62 39455 +1954 283 13.94 7.94 12.29 0 360.96 243.99 39256 +1954 284 15.25 9.25 13.6 0.11 389.73 179.06 39058 +1954 285 14.25 8.25 12.6 0 367.6 237.84 38861 +1954 286 16.29 10.29 14.64 0.05 413.94 173.66 38664 +1954 287 12.36 6.36 10.71 0.02 328.69 176.32 38468 +1954 288 10.36 4.36 8.71 0 291.42 235.03 38273 +1954 289 16.17 10.17 14.52 0 411.08 223.56 38079 +1954 290 11.67 5.67 10.02 0 315.4 227.78 37885 +1954 291 12.1 6.1 10.45 0 323.63 224.49 37693 +1954 292 15.52 9.52 13.87 0 395.89 216.6 37501 +1954 293 10.98 4.98 9.33 0 302.56 220.54 37311 +1954 294 10.22 4.22 8.57 0 288.95 218.58 37121 +1954 295 12.29 6.29 10.64 0 327.32 213.11 36933 +1954 296 12.56 6.56 10.91 0.03 332.64 157.63 36745 +1954 297 10.74 4.74 9.09 0.15 298.21 157.33 36560 +1954 298 16.48 10.48 14.83 0.44 418.5 149.23 36375 +1954 299 13.98 7.98 12.33 0 361.81 200.15 36191 +1954 300 13.56 7.56 11.91 0 352.96 198.12 36009 +1954 301 11.02 5.02 9.37 0.18 303.3 149.16 35829 +1954 302 10.7 4.7 9.05 0 297.48 196.64 35650 +1954 303 7.88 1.88 6.23 0 250.27 197.01 35472 +1954 304 5.28 -0.72 3.63 0.05 212.6 147.59 35296 +1954 305 4.98 -1.02 3.33 0.36 208.58 145.68 35122 +1954 306 7.31 1.31 5.66 0.04 241.56 142.52 34950 +1954 307 9.9 3.9 8.25 0 283.37 185 34779 +1954 308 9.01 3.01 7.36 0.48 268.36 137.47 34610 +1954 309 4.59 -1.41 2.94 0.22 203.46 138.54 34444 +1954 310 4.7 -1.3 3.05 0.02 204.89 136.62 34279 +1954 311 2.05 -3.95 0.4 0.01 172.67 136.28 34116 +1954 312 1.11 -4.89 -0.54 0 162.35 179.58 33956 +1954 313 4.32 -1.68 2.67 0.01 199.98 131.56 33797 +1954 314 4.35 -1.65 2.7 0 200.36 173.41 33641 +1954 315 6.53 0.53 4.88 0.05 230.05 126.94 33488 +1954 316 10.32 4.32 8.67 0.08 290.71 122.8 33337 +1954 317 11.89 5.89 10.24 0 319.59 159.94 33188 +1954 318 11.99 5.99 10.34 0 321.51 157.54 33042 +1954 319 9.5 3.5 7.85 0 276.54 158.34 32899 +1954 320 9.23 3.23 7.58 0 272 156.73 32758 +1954 321 3.67 -2.33 2.02 0.03 191.8 119.08 32620 +1954 322 3.67 -2.33 2.02 0.01 191.8 117.7 32486 +1954 323 8.99 2.99 7.34 0.14 268.03 113.58 32354 +1954 324 6.14 0.14 4.49 0 224.48 151.62 32225 +1954 325 2.44 -3.56 0.79 0 177.12 152.21 32100 +1954 326 4.72 -1.28 3.07 0 205.16 149.39 31977 +1954 327 7.49 1.49 5.84 0.18 244.28 109.21 31858 +1954 328 10.72 4.72 9.07 0 297.85 140.96 31743 +1954 329 7.2 1.2 5.55 2.84 239.91 106.78 31631 +1954 330 9.37 3.37 7.72 0.12 274.35 104.43 31522 +1954 331 8.4 2.4 6.75 0.81 258.46 104.04 31417 +1954 332 9.69 3.69 8.04 0.92 279.77 102.04 31316 +1954 333 8.56 2.56 6.91 0.12 261.02 101.92 31218 +1954 334 6.36 0.36 4.71 0 227.61 136.4 31125 +1954 335 9.75 3.75 8.1 0 280.79 132.7 31035 +1954 336 10.95 4.95 9.3 0.14 302.02 97.97 30949 +1954 337 8.05 2.05 6.4 0 252.93 131.32 30867 +1954 338 10.28 4.28 8.63 0.97 290 96.48 30790 +1954 339 5.53 -0.47 3.88 1.09 215.99 98.48 30716 +1954 340 5.41 -0.59 3.76 0.28 214.36 97.99 30647 +1954 341 11.01 5.01 9.36 0.12 303.11 94.22 30582 +1954 342 12.1 6.1 10.45 0 323.63 123.91 30521 +1954 343 9.61 3.61 7.96 0.29 278.4 93.93 30465 +1954 344 6.32 0.32 4.67 0 227.04 126.46 30413 +1954 345 2.12 -3.88 0.47 0 173.47 128.38 30366 +1954 346 5.99 -0.01 4.34 0.12 222.37 94.27 30323 +1954 347 4.8 -1.2 3.15 0 206.2 125.82 30284 +1954 348 2.48 -3.52 0.83 1.02 177.58 95.03 30251 +1954 349 3.82 -2.18 2.17 0.02 193.66 94.22 30221 +1954 350 4.16 -1.84 2.51 0 197.94 125.11 30197 +1954 351 2.72 -3.28 1.07 0 180.38 125.65 30177 +1954 352 5.18 -0.82 3.53 0.01 211.25 93.17 30162 +1954 353 3.7 -2.3 2.05 0 192.17 124.98 30151 +1954 354 4.6 -1.4 2.95 0 203.59 124.46 30145 +1954 355 8.1 2.1 6.45 0 253.71 122.25 30144 +1954 356 9.6 3.6 7.95 0.05 278.23 90.87 30147 +1954 357 4.97 -1.03 3.32 0.95 208.45 93.25 30156 +1954 358 5.87 -0.13 4.22 0.63 220.69 92.91 30169 +1954 359 3.63 -2.37 1.98 0 191.31 125.28 30186 +1954 360 2.01 -3.99 0.36 0 172.22 126.46 30208 +1954 361 1.71 -4.29 0.06 0 168.88 126.93 30235 +1954 362 5.72 -0.28 4.07 0.09 218.61 93.92 30267 +1954 363 9.18 3.18 7.53 0 271.17 123.44 30303 +1954 364 3.34 -2.66 1.69 0.12 187.77 95.66 30343 +1954 365 4.61 -1.39 2.96 0.01 203.72 95.57 30388 +1955 1 1.32 -4.68 -0.33 0.01 164.61 97.51 30438 +1955 2 0.65 -5.35 -1 0 157.49 131.05 30492 +1955 3 -0.83 -6.83 -2.48 0 142.71 132.63 30551 +1955 4 -2.08 -8.08 -3.73 0 131.17 134.03 30614 +1955 5 -0.01 -6.01 -1.66 0 150.74 133.86 30681 +1955 6 3.25 -2.75 1.6 0.14 186.68 99.89 30752 +1955 7 1.85 -4.15 0.2 0.31 170.43 101.03 30828 +1955 8 1.43 -4.57 -0.22 0 165.8 136.4 30907 +1955 9 -1.42 -7.42 -3.07 0 137.16 138.92 30991 +1955 10 -1.17 -7.17 -2.82 0 139.49 140.13 31079 +1955 11 3 -3 1.35 0 183.68 139.16 31171 +1955 12 6.14 0.14 4.49 0.19 224.48 103.7 31266 +1955 13 1.83 -4.17 0.18 0 170.21 142.41 31366 +1955 14 5.37 -0.63 3.72 0 213.82 141.86 31469 +1955 15 5.2 -0.8 3.55 0 211.52 143.4 31575 +1955 16 4.31 -1.69 2.66 0 199.85 145.24 31686 +1955 17 6.36 0.36 4.71 0 227.61 145.57 31800 +1955 18 9.17 3.17 7.52 0 271 145.28 31917 +1955 19 7.24 1.24 5.59 0 240.5 148.73 32038 +1955 20 4.56 -1.44 2.91 0.07 203.07 114.13 32161 +1955 21 2.91 -3.09 1.26 0 182.61 155.18 32289 +1955 22 0.01 -5.99 -1.64 0 150.94 158.47 32419 +1955 23 0.09 -5.91 -1.56 0.04 151.75 120.17 32552 +1955 24 -1.02 -7.02 -2.67 1.19 140.9 166 32688 +1955 25 -3.2 -9.2 -4.85 0 121.53 209.36 32827 +1955 26 -1.87 -7.87 -3.52 0 133.05 210.58 32969 +1955 27 2.49 -3.51 0.84 0 177.7 209.9 33114 +1955 28 2.7 -3.3 1.05 0 180.14 211.47 33261 +1955 29 3.7 -2.3 2.05 0 192.17 212.59 33411 +1955 30 5.28 -0.72 3.63 0.14 212.6 169.94 33564 +1955 31 1.3 -4.7 -0.35 0 164.39 217.51 33718 +1955 32 2.72 -3.28 1.07 0.29 180.38 173.75 33875 +1955 33 2.27 -3.73 0.62 1.44 175.17 175.49 34035 +1955 34 2.17 -3.83 0.52 0.91 174.03 176.75 34196 +1955 35 2.45 -3.55 0.8 0.06 177.24 177.76 34360 +1955 36 3.06 -2.94 1.41 0.15 184.4 178.82 34526 +1955 37 3.9 -2.1 2.25 0 194.66 189.27 34694 +1955 38 5.35 -0.65 3.7 0 213.54 190.93 34863 +1955 39 6.55 0.55 4.9 0 230.34 192.54 35035 +1955 40 5.54 -0.46 3.89 0 216.13 195.99 35208 +1955 41 7.06 1.06 5.41 0 237.82 197.29 35383 +1955 42 9.61 3.61 7.96 0.45 278.4 147.98 35560 +1955 43 7.26 1.26 5.61 0.98 240.81 151.75 35738 +1955 44 5.95 -0.05 4.3 0.57 221.81 154.54 35918 +1955 45 1.82 -4.18 0.17 0 170.1 211.83 36099 +1955 46 1.03 -4.97 -0.62 0.19 161.49 161.3 36282 +1955 47 -0.34 -6.34 -1.99 0 147.46 218.75 36466 +1955 48 1.66 -4.34 0.01 0 168.32 220.32 36652 +1955 49 1.88 -4.12 0.23 0.31 170.77 167.23 36838 +1955 50 4.08 -1.92 2.43 0.38 196.93 168.01 37026 +1955 51 2.89 -3.11 1.24 0.3 182.38 170.94 37215 +1955 52 4.34 -1.66 2.69 0 200.23 229.61 37405 +1955 53 4.81 -1.19 3.16 0 206.34 232.17 37596 +1955 54 5.62 -0.38 3.97 0 217.23 234.2 37788 +1955 55 7.37 1.37 5.72 0.08 242.46 176.6 37981 +1955 56 4.8 -1.2 3.15 0.76 206.2 180.48 38175 +1955 57 7.4 1.4 5.75 0.03 242.92 180.74 38370 +1955 58 4.01 -1.99 2.36 0.14 196.04 185.38 38565 +1955 59 2.51 -3.49 0.86 0.59 177.93 188.36 38761 +1955 60 1.82 -4.18 0.17 0.26 170.1 190.95 38958 +1955 61 4.06 -1.94 2.41 0.12 196.67 191.78 39156 +1955 62 3.68 -2.32 2.03 0.15 191.93 194.15 39355 +1955 63 6.32 0.32 4.67 0 227.04 259.35 39553 +1955 64 9.18 3.18 7.53 0 271.17 258.95 39753 +1955 65 9.15 3.15 7.5 0 270.67 261.85 39953 +1955 66 6.55 0.55 4.9 0.25 230.34 200.74 40154 +1955 67 3.61 -2.39 1.96 0.21 191.06 205.12 40355 +1955 68 3.18 -2.82 1.53 0 185.83 276.78 40556 +1955 69 6.51 0.51 4.86 0 229.76 276.1 40758 +1955 70 9.63 3.63 7.98 0 278.74 275.09 40960 +1955 71 9.65 3.65 8 0 279.08 277.96 41163 +1955 72 4.17 -1.83 2.52 0 198.07 287.18 41366 +1955 73 6.59 0.59 4.94 0 230.92 287.3 41569 +1955 74 4.88 -1.12 3.23 0.1 207.26 218.95 41772 +1955 75 3.8 -2.2 2.15 0.42 193.42 221.83 41976 +1955 76 6.96 0.96 5.31 0.8 236.34 221.25 42179 +1955 77 3.46 -2.54 1.81 0.95 189.23 226.06 42383 +1955 78 5.2 -0.8 3.55 0.01 211.52 226.74 42587 +1955 79 3.14 -2.86 1.49 0.06 185.35 230.39 42791 +1955 80 7.65 1.65 6 0.12 246.72 228.53 42996 +1955 81 3.71 -2.29 2.06 0.28 192.3 233.86 43200 +1955 82 3.72 -2.28 2.07 0 192.42 314.5 43404 +1955 83 1.4 -4.6 -0.25 0.08 165.48 239.42 43608 +1955 84 2.17 -3.83 0.52 0 174.03 321.12 43812 +1955 85 6.77 0.77 5.12 0 233.54 318.66 44016 +1955 86 6.75 0.75 5.1 0.01 233.25 240.83 44220 +1955 87 5.12 -0.88 3.47 0.01 210.45 244.22 44424 +1955 88 1.38 -4.62 -0.27 0.25 165.26 248.88 44627 +1955 89 1 -5 -0.65 0 161.18 334.51 44831 +1955 90 4.52 -1.48 2.87 0 202.55 333.41 45034 +1955 91 8.91 2.91 7.26 0 266.71 329.99 45237 +1955 92 9.51 3.51 7.86 0.44 276.71 248.49 45439 +1955 93 9.26 3.26 7.61 0 272.5 333.93 45642 +1955 94 9.22 3.22 7.57 0.24 271.84 252.12 45843 +1955 95 10.32 4.32 8.67 0 290.71 336.54 46045 +1955 96 9.52 3.52 7.87 0 276.88 339.97 46246 +1955 97 10.61 4.61 8.96 0 295.87 340.23 46446 +1955 98 9.52 3.52 7.87 0.3 276.88 258 46647 +1955 99 8.39 2.39 6.74 0 258.3 347.79 46846 +1955 100 3.09 -2.91 1.44 0 184.76 356.53 47045 +1955 101 4.09 -1.91 2.44 0 197.05 357.4 47243 +1955 102 8.4 2.4 6.75 0 258.46 353.62 47441 +1955 103 12.45 6.45 10.8 0 330.46 348.45 47638 +1955 104 14.31 8.31 12.66 0.03 368.89 259.79 47834 +1955 105 11.28 5.28 9.63 0.13 308.09 265.72 48030 +1955 106 9.61 3.61 7.96 0.22 278.4 269.16 48225 +1955 107 11.15 5.15 9.5 0 305.68 357.86 48419 +1955 108 9.31 3.31 7.66 0 273.34 362.83 48612 +1955 109 14.62 8.62 12.97 0 375.66 354.07 48804 +1955 110 15.64 9.64 13.99 0 398.66 353.06 48995 +1955 111 12.43 6.43 10.78 0 330.07 361.73 49185 +1955 112 13.62 7.62 11.97 0 354.21 360.76 49374 +1955 113 13.49 7.49 11.84 0 351.51 362.38 49561 +1955 114 13.14 7.14 11.49 0 344.3 364.62 49748 +1955 115 16.45 10.45 14.8 0 417.77 358.25 49933 +1955 116 14.61 8.61 12.96 0.05 375.44 272.99 50117 +1955 117 10.8 4.8 9.15 0 299.29 373.26 50300 +1955 118 9.8 3.8 8.15 1.46 281.65 282.3 50481 +1955 119 11.21 5.21 9.56 0.09 306.79 281.27 50661 +1955 120 14.07 8.07 12.42 0.43 363.73 277.66 50840 +1955 121 20.38 14.38 18.73 0.28 522 265.38 51016 +1955 122 21.2 15.2 19.55 0 546.32 352.22 51191 +1955 123 21.29 15.29 19.64 0.13 549.05 264.67 51365 +1955 124 20.53 14.53 18.88 0.27 526.38 267.4 51536 +1955 125 15.35 9.35 13.7 0 392 372.57 51706 +1955 126 16.02 10.02 14.37 0 407.53 371.85 51874 +1955 127 12.71 6.71 11.06 0 335.62 380.56 52039 +1955 128 13.67 7.67 12.02 0.8 355.26 284.59 52203 +1955 129 10.01 4.01 8.36 0 285.28 387.77 52365 +1955 130 8.65 2.65 7 0 262.48 390.95 52524 +1955 131 11.22 5.22 9.57 0.68 306.98 290.33 52681 +1955 132 7.76 1.76 6.11 0.29 248.42 295.55 52836 +1955 133 13.18 7.18 11.53 0 345.12 384.56 52989 +1955 134 17.53 11.53 15.88 0.02 444.47 280.68 53138 +1955 135 20.52 14.52 18.87 0.25 526.08 274.15 53286 +1955 136 16.72 10.72 15.07 0 424.32 377.85 53430 +1955 137 17.15 11.15 15.5 0 434.92 377.35 53572 +1955 138 19.3 13.3 17.65 0.22 491.36 278.61 53711 +1955 139 19.07 13.07 17.42 0 485.04 372.89 53848 +1955 140 21.36 15.36 19.71 0 551.18 365.62 53981 +1955 141 21.59 15.59 19.94 0.01 558.23 273.9 54111 +1955 142 19.61 13.61 17.96 0 500 372.55 54238 +1955 143 22.99 16.99 21.34 0.12 602.79 270.65 54362 +1955 144 20.7 14.7 19.05 0 531.38 369.86 54483 +1955 145 21.92 15.92 20.27 0 568.47 365.91 54600 +1955 146 17.47 11.47 15.82 1.23 442.95 285.75 54714 +1955 147 15.21 9.21 13.56 1.91 388.82 290.72 54824 +1955 148 15.33 9.33 13.68 1.1 391.55 290.78 54931 +1955 149 11.59 5.59 9.94 0.67 313.89 297.47 55034 +1955 150 7.5 1.5 5.85 0.97 244.43 303.28 55134 +1955 151 10.07 4.07 8.42 0.24 286.32 300.26 55229 +1955 152 13.89 7.89 12.24 0.29 359.9 294.32 55321 +1955 153 15.72 9.72 14.07 0 400.51 388.11 55409 +1955 154 19.48 13.48 17.83 0 496.36 377.35 55492 +1955 155 19.54 13.54 17.89 0 498.04 377.34 55572 +1955 156 19.57 13.57 17.92 0 498.88 377.57 55648 +1955 157 17.76 11.76 16.11 0 450.34 383.4 55719 +1955 158 23.76 17.76 22.11 0 628.56 362.31 55786 +1955 159 23.74 17.74 22.09 0 627.88 362.63 55849 +1955 160 22.35 16.35 20.7 0 582.06 368.39 55908 +1955 161 14.74 8.74 13.09 0 378.3 392.31 55962 +1955 162 17.48 11.48 15.83 0 443.2 384.96 56011 +1955 163 22.07 16.07 20.42 0.01 573.18 277.35 56056 +1955 164 18.69 12.69 17.04 0.11 474.75 286.16 56097 +1955 165 21.87 15.87 20.22 0 566.91 370.69 56133 +1955 166 21.11 15.11 19.46 0.6 543.61 280.18 56165 +1955 167 20.89 14.89 19.24 1.18 537.02 280.73 56192 +1955 168 21.19 15.19 19.54 0 546.02 373.31 56214 +1955 169 24.31 18.31 22.66 0.07 647.54 270.72 56231 +1955 170 22.9 16.9 21.25 0 599.84 366.81 56244 +1955 171 24.33 18.33 22.68 0.06 648.23 270.7 56252 +1955 172 21.41 15.41 19.76 0 552.71 372.56 56256 +1955 173 23.35 17.35 21.7 0 614.73 365.03 56255 +1955 174 18.79 12.79 17.14 0.01 477.44 286.05 56249 +1955 175 16.92 10.92 15.27 0.42 429.22 290.23 56238 +1955 176 17.69 11.69 16.04 0.03 448.55 288.53 56223 +1955 177 15.09 9.09 13.44 0 386.11 391.75 56203 +1955 178 21.05 15.05 19.4 0 541.8 373.63 56179 +1955 179 19.23 13.23 17.58 0.19 489.43 284.81 56150 +1955 180 18.34 12.34 16.69 0.11 465.43 286.82 56116 +1955 181 17.92 11.92 16.27 1.05 454.46 287.73 56078 +1955 182 17.94 11.94 16.29 1.99 454.98 287.57 56035 +1955 183 15.92 9.92 14.27 0.14 405.18 291.73 55987 +1955 184 21.86 15.86 20.21 0.05 566.6 277.42 55935 +1955 185 21.94 15.94 20.29 1.81 569.1 277.13 55879 +1955 186 18.37 12.37 16.72 0.43 466.23 286.08 55818 +1955 187 21.23 15.23 19.58 0 547.23 371.69 55753 +1955 188 25.33 19.33 23.68 0 684.01 354.75 55684 +1955 189 28.65 22.65 27 0.54 815.01 253.55 55611 +1955 190 25.75 19.75 24.1 0.92 699.53 264.22 55533 +1955 191 24.89 18.89 23.24 0 668.07 355.94 55451 +1955 192 27.77 21.77 26.12 0 778.38 341.85 55366 +1955 193 28.84 22.84 27.19 0.04 823.1 251.93 55276 +1955 194 24.8 18.8 23.15 0 664.85 355.57 55182 +1955 195 23.9 17.9 22.25 1.08 633.35 269.37 55085 +1955 196 19.77 13.77 18.12 0.94 504.5 280.64 54984 +1955 197 18.87 12.87 17.22 0.63 479.6 282.48 54879 +1955 198 16.49 10.49 14.84 0.15 418.74 287.4 54770 +1955 199 15.84 9.84 14.19 0 403.31 384.58 54658 +1955 200 23.43 17.43 21.78 0 617.4 359.11 54542 +1955 201 23.27 17.27 21.62 0.47 612.06 269.47 54423 +1955 202 19.94 13.94 18.29 0.19 509.33 278.21 54301 +1955 203 20.38 14.38 18.73 0.92 522 276.72 54176 +1955 204 20.67 14.67 19.02 0.44 530.49 275.59 54047 +1955 205 20.46 14.46 18.81 0 524.33 367.66 53915 +1955 206 21.86 15.86 20.21 0 566.6 362.12 53780 +1955 207 23.77 17.77 22.12 0.07 628.9 265.52 53643 +1955 208 23.34 17.34 21.69 0.59 614.39 266.35 53502 +1955 209 22.16 16.16 20.51 0.02 576.02 269.3 53359 +1955 210 18.83 12.83 17.18 0 478.52 369.8 53213 +1955 211 19.14 13.14 17.49 0 486.96 368.05 53064 +1955 212 21.6 15.6 19.95 0.76 558.54 269.22 52913 +1955 213 17.71 11.71 16.06 0.95 449.06 278.1 52760 +1955 214 19.47 13.47 17.82 0.75 496.08 273.52 52604 +1955 215 19.69 13.69 18.04 0 502.24 363.3 52445 +1955 216 20.74 14.74 19.09 1.05 532.56 269.1 52285 +1955 217 21.1 15.1 19.45 0.65 543.31 267.51 52122 +1955 218 20.99 14.99 19.34 0.96 540 267.18 51958 +1955 219 18.17 12.17 16.52 0.19 460.97 273.14 51791 +1955 220 21.08 15.08 19.43 1.29 542.7 265.47 51622 +1955 221 25.25 19.25 23.6 0.97 681.09 252.58 51451 +1955 222 24.47 18.47 22.82 1.16 653.15 254.31 51279 +1955 223 22.36 16.36 20.71 0.54 582.38 259.68 51105 +1955 224 22.33 16.33 20.68 0.89 581.42 258.98 50929 +1955 225 21.36 15.36 19.71 0.51 551.18 260.74 50751 +1955 226 21.6 15.6 19.95 0 558.54 345.68 50572 +1955 227 23.41 17.41 21.76 0.32 616.73 253.31 50392 +1955 228 26.22 20.22 24.57 0.51 717.24 243.62 50210 +1955 229 23.04 17.04 21.39 0.52 604.44 252.58 50026 +1955 230 23.9 17.9 22.25 1.11 633.35 249.16 49842 +1955 231 22.63 16.63 20.98 0.58 591.05 251.72 49656 +1955 232 24.18 18.18 22.53 0.01 643.01 246.29 49469 +1955 233 22.5 16.5 20.85 0 586.86 333.39 49280 +1955 234 18.85 12.85 17.2 0.37 479.06 257.93 49091 +1955 235 20.31 14.31 18.66 0.16 519.96 253.47 48900 +1955 236 20.18 14.18 18.53 0 516.2 336.95 48709 +1955 237 18.61 12.61 16.96 0.55 472.61 255.01 48516 +1955 238 15.68 9.68 14.03 0.88 399.59 259.52 48323 +1955 239 14.65 8.65 13 0.35 376.32 260.16 48128 +1955 240 14.53 8.53 12.88 0 373.68 345.35 47933 +1955 241 17.61 11.61 15.96 0 446.5 336.08 47737 +1955 242 19.1 13.1 17.45 0 485.86 330.2 47541 +1955 243 21.12 15.12 19.47 0 543.91 322.19 47343 +1955 244 18.65 12.65 17 0.19 473.68 245.85 47145 +1955 245 17.18 11.18 15.53 0 435.66 329.88 46947 +1955 246 15.97 9.97 14.32 0.01 406.36 248.16 46747 +1955 247 18.67 12.67 17.02 0.21 474.21 241.58 46547 +1955 248 17.46 11.46 15.81 0 442.7 323.38 46347 +1955 249 15.17 9.17 13.52 0 387.92 326.77 46146 +1955 250 16.63 10.63 14.98 0 422.13 321.41 45945 +1955 251 20.21 14.21 18.56 0 517.07 309.71 45743 +1955 252 18.73 12.73 17.08 0.04 475.82 233.82 45541 +1955 253 19.46 13.46 17.81 0.57 495.8 230.74 45339 +1955 254 24.75 18.75 23.1 0 663.06 288.37 45136 +1955 255 24.97 18.97 23.32 0 670.94 285.41 44933 +1955 256 23.16 17.16 21.51 0.05 608.4 217.3 44730 +1955 257 14.56 8.56 12.91 0.01 374.34 233 44527 +1955 258 14.06 8.06 12.41 0 363.52 309.3 44323 +1955 259 19.54 13.54 17.89 0 498.04 294.05 44119 +1955 260 21.37 15.37 19.72 0.04 551.49 214.87 43915 +1955 261 18.76 12.76 17.11 0.96 476.63 218.52 43711 +1955 262 18.16 12.16 16.51 0.38 460.7 217.9 43507 +1955 263 20.14 14.14 18.49 0.09 515.05 212.21 43303 +1955 264 17.54 11.54 15.89 0.81 444.72 215.28 43099 +1955 265 18.04 12.04 16.39 0 457.57 283.51 42894 +1955 266 13.36 7.36 11.71 0.19 348.81 218.14 42690 +1955 267 12.63 6.63 10.98 0.12 334.03 217.07 42486 +1955 268 16.45 10.45 14.8 0.39 417.77 209.61 42282 +1955 269 15.99 9.99 14.34 0 406.83 277.95 42078 +1955 270 17.92 11.92 16.27 0 454.46 271.11 41875 +1955 271 21.88 15.88 20.23 0.45 567.22 193.74 41671 +1955 272 20.4 14.4 18.75 0.11 522.58 194.83 41468 +1955 273 18.55 12.55 16.9 0 471 261.91 41265 +1955 274 16.73 10.73 15.08 0.04 424.56 197.49 41062 +1955 275 15.82 9.82 14.17 1.24 402.84 196.82 40860 +1955 276 13.91 7.91 12.26 0.8 360.32 197.46 40658 +1955 277 14.54 8.54 12.89 0.6 373.9 194.63 40456 +1955 278 17.72 11.72 16.07 0.16 449.31 187.8 40255 +1955 279 15.13 9.13 13.48 0.22 387.01 189.59 40054 +1955 280 10.47 4.47 8.82 0.02 293.37 193.16 39854 +1955 281 6.89 0.89 5.24 0.3 235.3 194.37 39654 +1955 282 8.53 2.53 6.88 0.28 260.54 190.86 39455 +1955 283 9.92 3.92 8.27 0.11 283.72 187.41 39256 +1955 284 11.39 5.39 9.74 0.14 310.13 183.64 39058 +1955 285 14.91 8.91 13.26 0.77 382.08 177.55 38861 +1955 286 9.51 3.51 7.86 0.69 276.71 181.4 38664 +1955 287 10.08 4.08 8.43 0.27 286.5 178.64 38468 +1955 288 12.01 6.01 10.36 0.12 321.89 174.61 38273 +1955 289 12.56 6.56 10.91 0.1 332.64 172.04 38079 +1955 290 14.52 8.52 12.87 0.04 373.46 167.67 37885 +1955 291 12.88 6.88 11.23 0 339.03 223.38 37693 +1955 292 14.09 8.09 12.44 0 364.16 218.9 37501 +1955 293 9.98 3.98 8.33 0.06 284.76 166.33 37311 +1955 294 9.79 3.79 8.14 1.54 281.48 164.32 37121 +1955 295 10.12 4.12 8.47 0.11 287.2 161.89 36933 +1955 296 12.54 6.54 10.89 1.45 332.24 157.65 36745 +1955 297 10.38 4.38 8.73 0.46 291.77 157.65 36560 +1955 298 9.69 3.69 8.04 0.16 279.77 156.29 36375 +1955 299 9.26 3.26 7.61 0.28 272.5 154.54 36191 +1955 300 12.37 6.37 10.72 0.66 328.89 149.79 36009 +1955 301 11.85 5.85 10.2 0.16 318.82 148.4 35829 +1955 302 15.25 9.25 13.6 0 389.73 190.63 35650 +1955 303 19.36 13.36 17.71 0 493.03 181.15 35472 +1955 304 21.77 15.77 20.12 0.01 563.79 130.46 35296 +1955 305 13.61 7.61 11.96 0.13 354.01 139 35122 +1955 306 14.35 8.35 12.7 0.1 369.76 136.59 34950 +1955 307 7.59 1.59 5.94 0.3 245.81 140.43 34779 +1955 308 3.74 -2.26 2.09 0 192.67 187.67 34610 +1955 309 2.49 -3.51 0.84 0 177.7 186.15 34444 +1955 310 1.12 -4.88 -0.53 0 162.45 184.49 34279 +1955 311 1.2 -4.8 -0.45 0.07 163.31 136.66 34116 +1955 312 4.13 -1.87 2.48 0 197.56 177.69 33956 +1955 313 3.39 -2.61 1.74 0 188.37 176.03 33797 +1955 314 4.44 -1.56 2.79 0 201.52 173.35 33641 +1955 315 4.49 -1.51 2.84 0 202.16 170.75 33488 +1955 316 7.38 1.38 5.73 0.44 242.61 124.79 33337 +1955 317 8.64 2.64 6.99 0 262.32 163.12 33188 +1955 318 7.19 1.19 5.54 0 239.76 162 33042 +1955 319 9.24 3.24 7.59 0.38 272.17 118.93 32899 +1955 320 9.76 3.76 8.11 0.95 280.97 117.19 32758 +1955 321 13.99 7.99 12.34 0.06 362.02 112.31 32620 +1955 322 12.89 6.89 11.24 0.11 339.23 111.92 32486 +1955 323 14.75 8.75 13.1 0.11 378.52 109.13 32354 +1955 324 10.55 4.55 8.9 0 294.79 148.01 32225 +1955 325 9.73 3.73 8.08 0.12 280.45 110.29 32100 +1955 326 9.33 3.33 7.68 0.02 273.67 109.47 31977 +1955 327 8.63 2.63 6.98 0 262.15 144.72 31858 +1955 328 8.9 2.9 7.25 0 266.55 142.54 31743 +1955 329 6.58 0.58 4.93 0.04 230.78 107.11 31631 +1955 330 1.04 -4.96 -0.61 0.47 161.6 108.47 31522 +1955 331 0.54 -5.46 -1.11 0.19 156.35 107.65 31417 +1955 332 1.92 -4.08 0.27 0.18 171.21 105.9 31316 +1955 333 5.13 -0.87 3.48 0.22 210.58 103.72 31218 +1955 334 4.58 -1.42 2.93 0 203.33 137.53 31125 +1955 335 2.7 -3.3 1.05 0.76 180.14 103.06 31035 +1955 336 -1.79 -7.79 -3.44 0 133.78 138.36 30949 +1955 337 -0.41 -6.41 -2.06 0.04 146.78 144.98 30867 +1955 338 0.42 -5.58 -1.23 0 155.11 177.75 30790 +1955 339 4.44 -1.56 2.79 0 201.52 131.97 30716 +1955 340 4.18 -1.82 2.53 0 198.19 131.38 30647 +1955 341 7.36 1.36 5.71 0 242.31 128.47 30582 +1955 342 10.84 4.84 9.19 0 300.02 125.04 30521 +1955 343 10.1 4.1 8.45 0.01 286.85 93.63 30465 +1955 344 8.86 2.86 7.21 0 265.89 124.7 30413 +1955 345 7.35 1.35 5.7 0.41 242.16 94.02 30366 +1955 346 6.31 0.31 4.66 0.24 226.89 94.12 30323 +1955 347 3.39 -2.61 1.74 0 188.37 126.59 30284 +1955 348 5.28 -0.72 3.63 0 212.6 125.19 30251 +1955 349 3.75 -2.25 2.1 0 192.79 125.67 30221 +1955 350 3.41 -2.59 1.76 0 188.62 125.51 30197 +1955 351 4.93 -1.07 3.28 0 207.92 124.46 30177 +1955 352 5.83 -0.17 4.18 0.3 220.13 92.88 30162 +1955 353 0.35 -5.65 -1.3 0 154.39 126.58 30151 +1955 354 4.05 -1.95 2.4 0 196.55 124.76 30145 +1955 355 6.57 0.57 4.92 0 230.63 123.27 30144 +1955 356 6.6 0.6 4.95 0 231.07 123.28 30147 +1955 357 7.63 1.63 5.98 0 246.42 122.66 30156 +1955 358 6.87 0.87 5.22 0 235.01 123.25 30169 +1955 359 8.5 2.5 6.85 0 260.06 122.24 30186 +1955 360 10.91 4.91 9.26 0 301.29 120.72 30208 +1955 361 9.14 3.14 7.49 0 270.51 122.46 30235 +1955 362 9.81 3.81 8.16 0 281.82 122.37 30267 +1955 363 5.8 -0.2 4.15 0 219.72 125.75 30303 +1955 364 8.34 2.34 6.69 0 257.5 124.45 30343 +1955 365 8.07 2.07 6.42 0 253.24 125.2 30388 +1956 1 3.29 -2.71 1.64 0.12 187.16 96.78 30438 +1956 2 3.8 -2.2 2.15 0 193.42 129.5 30492 +1956 3 4.57 -1.43 2.92 0 203.2 130 30551 +1956 4 7.13 1.13 5.48 0 238.86 129.3 30614 +1956 5 10.11 4.11 8.46 0.05 287.02 95.77 30681 +1956 6 6 0 4.35 0 222.51 131.57 30752 +1956 7 6.04 0.04 4.39 0 223.07 132.33 30828 +1956 8 7.35 1.35 5.7 0 242.16 132.92 30907 +1956 9 1.66 -4.34 0.01 0.2 168.32 103.16 30991 +1956 10 -0.28 -6.28 -1.93 0.39 148.06 148.49 31079 +1956 11 -1.01 -7.01 -2.66 0 141 184.61 31171 +1956 12 -2.35 -8.35 -4 0 128.79 186.04 31266 +1956 13 2.53 -3.47 0.88 0 178.16 185 31366 +1956 14 3.85 -2.15 2.2 0 194.04 185.11 31469 +1956 15 2.84 -3.16 1.19 0 181.79 186.62 31575 +1956 16 3.65 -2.35 2 0 191.56 145.64 31686 +1956 17 -0.14 -6.14 -1.79 0 149.44 149.29 31800 +1956 18 -0.28 -6.28 -1.93 0.01 148.06 154.84 31917 +1956 19 -4.31 -10.31 -5.96 0 112.59 196.07 32038 +1956 20 0.88 -5.12 -0.77 0 159.9 154.26 32161 +1956 21 6.89 0.89 5.24 0 235.3 152.55 32289 +1956 22 7.25 1.25 5.6 0 240.65 154.01 32419 +1956 23 6.77 0.77 5.12 0.02 233.54 117.1 32552 +1956 24 2.04 -3.96 0.39 0.14 172.56 120.96 32688 +1956 25 4.96 -1.04 3.31 0.06 208.32 121.02 32827 +1956 26 6.93 0.93 5.28 0.07 235.89 121.38 32969 +1956 27 5.94 -0.06 4.29 0 221.67 164.6 33114 +1956 28 9.22 3.22 7.57 0 271.84 164.07 33261 +1956 29 7.2 1.2 5.55 0 239.91 168.17 33411 +1956 30 8.17 2.17 6.52 0 254.81 169.57 33564 +1956 31 9.52 3.52 7.87 0 276.88 170.67 33718 +1956 32 -5.4 -11.4 -7.05 0 104.37 182.03 33875 +1956 33 -5.4 -11.4 -7.05 0.43 104.37 178.52 34035 +1956 34 -5.4 -11.4 -7.05 0.19 104.37 180.55 34196 +1956 35 -5.4 -11.4 -7.05 0.07 104.37 182.2 34360 +1956 36 -5.4 -11.4 -7.05 0 104.37 231.85 34526 +1956 37 -5.4 -11.4 -7.05 0 104.37 234.13 34694 +1956 38 -5.4 -11.4 -7.05 0 104.37 236.73 34863 +1956 39 -5.4 -11.4 -7.05 0.38 104.37 190.33 35035 +1956 40 -5.4 -11.4 -7.05 0 104.37 242.7 35208 +1956 41 -5.4 -11.4 -7.05 0.07 104.37 194.12 35383 +1956 42 -5.4 -11.4 -7.05 0 104.37 247.77 35560 +1956 43 -5.4 -11.4 -7.05 0 104.37 250.33 35738 +1956 44 -5.4 -11.4 -7.05 0.05 104.37 199.65 35918 +1956 45 -5.4 -11.4 -7.05 0 104.37 255.36 36099 +1956 46 -5.4 -11.4 -7.05 0 104.37 257.91 36282 +1956 47 -5.4 -11.4 -7.05 0.02 104.37 205.32 36466 +1956 48 -5.4 -11.4 -7.05 0 104.37 263.3 36652 +1956 49 -5.4 -11.4 -7.05 0.15 104.37 209.59 36838 +1956 50 -5.4 -11.4 -7.05 0 104.37 268.86 37026 +1956 51 -5.4 -11.4 -7.05 0 104.37 271.69 37215 +1956 52 -5.4 -11.4 -7.05 0.32 104.37 216.3 37405 +1956 53 -5.4 -11.4 -7.05 0.18 104.37 218.83 37596 +1956 54 -5.4 -11.4 -7.05 0 104.37 281.1 37788 +1956 55 -5.4 -11.4 -7.05 0 104.37 283.96 37981 +1956 56 -5.4 -11.4 -7.05 0.49 104.37 225.93 38175 +1956 57 -5.4 -11.4 -7.05 0.66 104.37 229.59 38370 +1956 58 -5.4 -11.4 -7.05 0.76 104.37 233.52 38565 +1956 59 -5.4 -11.4 -7.05 0 104.37 299.38 38761 +1956 60 3.97 -2.03 2.32 0 195.54 295.6 38958 +1956 61 4.74 -1.26 3.09 0 205.42 297.15 39156 +1956 62 6.46 0.46 4.81 0 229.04 297.38 39355 +1956 63 5.16 -0.84 3.51 0 210.98 300.97 39553 +1956 64 4.07 -1.93 2.42 0.03 196.8 238.19 39753 +1956 65 0.95 -5.05 -0.7 0.83 160.64 242.02 39953 +1956 66 -1.76 -7.76 -3.41 0 134.05 313.96 40154 +1956 67 4.1 -1.9 2.45 0.07 197.18 243.52 40355 +1956 68 4.99 -1.01 3.34 0.02 208.72 244.35 40556 +1956 69 0.99 -5.01 -0.66 0 161.07 319.02 40758 +1956 70 2.27 -3.73 0.62 0 175.17 320.46 40960 +1956 71 2.98 -3.02 1.33 0 183.44 322.32 41163 +1956 72 2.25 -3.75 0.6 0 174.94 325.42 41366 +1956 73 4.96 -1.04 3.31 0 208.32 324.9 41569 +1956 74 6.28 0.28 4.63 0 226.47 325.45 41772 +1956 75 8.59 2.59 6.94 0 261.51 324.34 41976 +1956 76 10.92 4.92 9.27 0 301.47 322.42 42179 +1956 77 8.93 2.93 7.28 0.25 267.04 253.13 42383 +1956 78 9.64 3.64 7.99 0.13 278.91 222.54 42587 +1956 79 6.73 0.73 5.08 0.04 232.96 227.48 42791 +1956 80 5.71 -0.29 4.06 0 218.47 307.06 42996 +1956 81 3.62 -2.38 1.97 0.31 191.19 233.93 43200 +1956 82 4.34 -1.66 2.69 0 200.23 313.86 43404 +1956 83 6.57 0.57 4.92 0 230.63 313.83 43608 +1956 84 6.47 0.47 4.82 0 229.19 316.51 43812 +1956 85 2.11 -3.89 0.46 0.08 173.35 242.79 44016 +1956 86 0.16 -5.84 -1.49 0 152.46 327.89 44220 +1956 87 4.83 -1.17 3.18 0 206.6 325.96 44424 +1956 88 3.28 -2.72 1.63 0.31 187.04 247.51 44627 +1956 89 2.58 -3.42 0.93 0.08 178.74 249.78 44831 +1956 90 5.37 -0.63 3.72 0 213.82 332.43 45034 +1956 91 14.32 8.32 12.67 0.03 369.11 240.3 45237 +1956 92 12.53 6.53 10.88 0 332.04 326.15 45439 +1956 93 14.89 8.89 13.24 0.27 381.63 242.67 45642 +1956 94 16.1 10.1 14.45 0.01 409.42 242.2 45843 +1956 95 16.62 10.62 14.97 0.41 421.88 242.84 46045 +1956 96 16.48 10.48 14.83 0.21 418.5 244.63 46246 +1956 97 18.04 12.04 16.39 0.27 457.57 243.15 46446 +1956 98 16.12 10.12 14.47 0 409.89 330.96 46647 +1956 99 15.61 9.61 13.96 0 397.97 334.13 46846 +1956 100 11.57 5.57 9.92 0 313.51 344.45 47045 +1956 101 15.2 9.2 13.55 0 388.59 338.89 47243 +1956 102 14.8 8.8 13.15 0.35 379.63 256.26 47441 +1956 103 12.33 6.33 10.68 0.18 328.11 261.51 47638 +1956 104 11.15 5.15 9.5 0.26 305.68 264.55 47834 +1956 105 10.79 4.79 9.14 1.5 299.11 266.39 48030 +1956 106 9.56 3.56 7.91 0.67 277.55 269.22 48225 +1956 107 8.01 2.01 6.36 1.13 252.3 272.34 48419 +1956 108 9.19 3.19 7.54 0 271.34 363.02 48612 +1956 109 8.28 2.28 6.63 0.11 256.55 274.58 48804 +1956 110 6.61 0.61 4.96 0.01 231.21 277.51 48995 +1956 111 6.47 0.47 4.82 0 229.19 371.79 49185 +1956 112 4.84 -1.16 3.19 0 206.73 375.5 49374 +1956 113 3.98 -2.02 2.33 0.12 195.67 283.46 49561 +1956 114 7.15 1.15 5.5 0 239.16 375.27 49748 +1956 115 12.13 6.13 10.48 0 324.21 368.14 49933 +1956 116 11.9 5.9 10.25 0 319.78 369.83 50117 +1956 117 13.65 7.65 12 0 354.84 367.47 50300 +1956 118 13.92 7.92 12.27 0 360.53 368.19 50481 +1956 119 15.26 9.26 13.61 0.14 389.95 274.67 50661 +1956 120 17.5 11.5 15.85 0 443.71 361.52 50840 +1956 121 23.29 17.29 21.64 1 612.72 257.54 51016 +1956 122 21.6 15.6 19.95 1.76 558.54 263.11 51191 +1956 123 20.95 14.95 19.3 0.65 538.81 265.55 51365 +1956 124 18.11 12.11 16.46 0.03 459.4 273.1 51536 +1956 125 18.3 12.3 16.65 0.44 464.38 273.4 51706 +1956 126 13.79 7.79 12.14 0 357.78 377.28 51874 +1956 127 16.43 10.43 14.78 0 417.29 371.66 52039 +1956 128 17.62 11.62 15.97 0 446.76 369.36 52203 +1956 129 17.64 11.64 15.99 0 447.27 370.14 52365 +1956 130 12.34 6.34 10.69 0 328.3 384.02 52524 +1956 131 16.07 10.07 14.42 0 408.71 376.03 52681 +1956 132 14.14 8.14 12.49 0.25 365.23 286.24 52836 +1956 133 16.02 10.02 14.37 0.04 407.53 283.27 52989 +1956 134 16.15 10.15 14.5 0 410.61 378.06 53138 +1956 135 19.51 13.51 17.86 0 497.2 368.89 53286 +1956 136 17.2 11.2 15.55 0.01 436.16 282.38 53430 +1956 137 16.31 10.31 14.66 0.05 414.42 284.75 53572 +1956 138 17.59 11.59 15.94 0 446 376.7 53711 +1956 139 19.62 13.62 17.97 0 500.28 371.12 53848 +1956 140 19.94 13.94 18.29 0.09 509.33 277.91 53981 +1956 141 16.43 10.43 14.78 0.38 417.29 286.17 54111 +1956 142 17.25 11.25 15.6 0 437.41 379.78 54238 +1956 143 18.18 12.18 16.53 0 461.23 377.58 54362 +1956 144 19.16 13.16 17.51 0.14 487.51 281.25 54483 +1956 145 19.19 13.19 17.54 0.48 488.33 281.53 54600 +1956 146 19.26 13.26 17.61 0 490.26 375.52 54714 +1956 147 15.31 9.31 13.66 0.07 391.09 290.53 54824 +1956 148 15.41 9.41 13.76 1.58 393.37 290.63 54931 +1956 149 18.48 12.48 16.83 0.35 469.14 284.36 55034 +1956 150 15.15 9.15 13.5 0.06 387.46 291.62 55134 +1956 151 12.27 6.27 10.62 0 326.93 395.94 55229 +1956 152 10.53 4.53 8.88 0.04 294.44 299.7 55321 +1956 153 13.59 7.59 11.94 0.57 353.59 295.03 55409 +1956 154 15.69 9.69 14.04 0.34 399.82 291.38 55492 +1956 155 18.1 12.1 16.45 0 459.14 381.89 55572 +1956 156 19.07 13.07 17.42 0 485.04 379.19 55648 +1956 157 18.43 12.43 16.78 0.23 467.81 286.03 55719 +1956 158 16.17 10.17 14.52 1.5 411.08 291.07 55786 +1956 159 18.62 12.62 16.97 0.02 472.87 285.9 55849 +1956 160 17.26 11.26 15.61 1.42 437.66 289.1 55908 +1956 161 17.94 11.94 16.29 0.09 454.98 287.65 55962 +1956 162 17.5 11.5 15.85 0.08 443.71 288.68 56011 +1956 163 17.39 11.39 15.74 0 440.93 385.44 56056 +1956 164 19.88 13.88 18.23 0 507.62 377.68 56097 +1956 165 23.41 17.41 21.76 0.03 616.73 273.48 56133 +1956 166 26.7 20.7 25.05 0.1 735.72 262.44 56165 +1956 167 25.3 19.3 23.65 1.91 682.91 267.37 56192 +1956 168 24.56 18.56 22.91 0.63 656.32 269.9 56214 +1956 169 23.64 17.64 21.99 0.84 624.48 272.85 56231 +1956 170 22.99 16.99 21.34 1.11 602.79 274.84 56244 +1956 171 23.32 17.32 21.67 0.49 613.72 273.88 56252 +1956 172 21.77 15.77 20.12 1.05 563.79 278.42 56256 +1956 173 18.41 12.41 16.76 0.05 467.28 287 56255 +1956 174 16.17 10.17 14.52 0.43 411.08 291.81 56249 +1956 175 17.94 11.94 16.29 0.98 454.98 287.99 56238 +1956 176 16.53 10.53 14.88 0.06 419.7 291.02 56223 +1956 177 20.78 14.78 19.13 0.15 533.75 280.93 56203 +1956 178 20.09 14.09 18.44 1.11 513.62 282.74 56179 +1956 179 20 14 18.35 0.54 511.04 282.89 56150 +1956 180 20.53 14.53 18.88 0.02 526.38 281.44 56116 +1956 181 21.23 15.23 19.58 1.06 547.23 279.52 56078 +1956 182 24.11 18.11 22.46 0.12 640.58 270.91 56035 +1956 183 21.21 15.21 19.56 0 546.63 372.44 55987 +1956 184 25.14 19.14 23.49 0.33 677.09 267.28 55935 +1956 185 24.3 18.3 22.65 0.02 647.19 269.99 55879 +1956 186 22.1 16.1 20.45 0.94 574.13 276.48 55818 +1956 187 25.8 19.8 24.15 0.05 701.39 264.64 55753 +1956 188 23.73 17.73 22.08 0 627.54 361.71 55684 +1956 189 23.22 17.22 21.57 0 610.39 363.63 55611 +1956 190 26.11 20.11 24.46 0 713.06 350.6 55533 +1956 191 27.1 21.1 25.45 0.04 751.43 259.15 55451 +1956 192 21.46 15.46 19.81 0 554.23 369.48 55366 +1956 193 24.53 18.53 22.88 0 655.26 356.96 55276 +1956 194 22.44 16.44 20.79 0 584.94 365.3 55182 +1956 195 19.76 13.76 18.11 0 504.22 374.63 55085 +1956 196 19.9 13.9 18.25 0.02 508.19 280.32 54984 +1956 197 22.54 16.54 20.89 0 588.15 363.8 54879 +1956 198 24.61 18.61 22.96 0 658.09 354.89 54770 +1956 199 21.95 15.95 20.3 0.97 569.41 273.96 54658 +1956 200 22.89 16.89 21.24 0.54 599.51 270.95 54542 +1956 201 26.55 20.55 24.9 0.03 729.9 258.64 54423 +1956 202 26.83 20.83 25.18 0 740.8 342.95 54301 +1956 203 25.76 19.76 24.11 1.4 699.9 260.66 54176 +1956 204 22.27 16.27 20.62 0 579.51 361.65 54047 +1956 205 22.38 16.38 20.73 0 583.02 360.73 53915 +1956 206 23.68 17.68 22.03 0.29 625.84 266.28 53780 +1956 207 22.8 16.8 21.15 1.32 596.57 268.43 53643 +1956 208 18.91 12.91 17.26 0 480.69 370.84 53502 +1956 209 19.07 13.07 17.42 0 485.04 369.68 53359 +1956 210 21.27 15.27 19.62 0 548.44 361.7 53213 +1956 211 19.19 13.19 17.54 0 488.33 367.9 53064 +1956 212 21.63 15.63 19.98 0 559.46 358.85 52913 +1956 213 20.49 14.49 18.84 0 525.2 362.09 52760 +1956 214 20.57 14.57 18.92 0 527.55 361.07 52604 +1956 215 21.67 15.67 20.02 0 560.7 356.54 52445 +1956 216 28.35 22.35 26.7 0 802.36 326.44 52285 +1956 217 27.01 21.01 25.36 0 747.87 332.32 52122 +1956 218 26.64 20.64 24.99 0.67 733.39 249.99 51958 +1956 219 24.01 18.01 22.36 0.37 637.13 257.9 51791 +1956 220 22.08 16.08 20.43 0 573.49 350.41 51622 +1956 221 18.74 12.74 17.09 1.4 476.09 270.4 51451 +1956 222 17.26 11.26 15.61 1.75 437.66 272.81 51279 +1956 223 15.98 9.98 14.33 0.02 406.59 274.49 51105 +1956 224 17.69 11.69 16.04 1.3 448.55 270.23 50929 +1956 225 20.21 14.21 18.56 0.18 517.07 263.64 50751 +1956 226 19.83 13.83 18.18 0.01 506.2 263.7 50572 +1956 227 19.24 13.24 17.59 0 489.71 352.15 50392 +1956 228 17.65 11.65 16 0.45 447.52 266.68 50210 +1956 229 18.74 12.74 17.09 0.06 476.09 263.39 50026 +1956 230 21.11 15.11 19.46 0 543.61 342.42 49842 +1956 231 23.72 17.72 22.07 0.01 627.2 248.63 49656 +1956 232 26.69 20.69 25.04 0 735.33 317.66 49469 +1956 233 24.68 18.68 23.03 0.12 660.57 243.75 49280 +1956 234 24.29 18.29 22.64 0 646.84 325.21 49091 +1956 235 27.22 21.22 25.57 0.52 756.2 233.38 48900 +1956 236 21.46 15.46 19.81 0.31 554.23 249.58 48709 +1956 237 17.15 11.15 15.5 0.09 434.92 258.02 48516 +1956 238 22.26 16.26 20.61 0.26 579.19 245.07 48323 +1956 239 24.45 18.45 22.8 0.02 652.44 237.86 48128 +1956 240 21.37 15.37 19.72 0.3 551.49 244.95 47933 +1956 241 20.45 14.45 18.8 0.15 524.04 245.9 47737 +1956 242 20.32 14.32 18.67 0.72 520.25 244.91 47541 +1956 243 22 16 20.35 0.12 570.98 239.46 47343 +1956 244 15.93 9.93 14.28 0 405.42 334.83 47145 +1956 245 11.62 5.62 9.97 0.08 314.45 256.48 46947 +1956 246 13.41 7.41 11.76 0 349.85 336.5 46747 +1956 247 12.34 6.34 10.69 0 328.3 336.69 46547 +1956 248 10.53 4.53 8.88 0 294.44 337.92 46347 +1956 249 11.69 5.69 10.04 0 315.78 333.76 46146 +1956 250 13.66 7.66 12.01 0 355.05 327.99 45945 +1956 251 19.01 13.01 17.36 0 483.41 313.14 45743 +1956 252 19.84 13.84 18.19 0 506.48 308.67 45541 +1956 253 21.52 15.52 19.87 0.04 556.07 226.15 45339 +1956 254 21.92 15.92 20.27 0 568.47 298.19 45136 +1956 255 22.38 16.38 20.73 0 583.02 294.52 44933 +1956 256 24.92 18.92 23.27 0 669.14 283.46 44730 +1956 257 19.09 13.09 17.44 0 485.59 299.97 44527 +1956 258 20.98 14.98 19.33 0.13 539.7 219.25 44323 +1956 259 17.48 11.48 15.83 0 443.2 299.34 44119 +1956 260 21.99 15.99 20.34 0 570.66 284.59 43915 +1956 261 20.89 14.89 19.24 0 537.02 285.53 43711 +1956 262 18.79 12.79 17.14 0 477.44 288.95 43507 +1956 263 21.55 15.55 19.9 0 557 278.91 43303 +1956 264 27.33 21.33 25.68 0 760.59 256.26 43099 +1956 265 23.99 17.99 22.34 0 636.44 266.46 42894 +1956 266 25.02 19.02 23.37 0 672.74 260.58 42690 +1956 267 23.81 17.81 22.16 0.91 630.27 196.64 42486 +1956 268 21.27 15.27 19.62 0 548.44 267.52 42282 +1956 269 19.84 13.84 18.19 0 506.48 268.98 42078 +1956 270 19.55 13.55 17.9 0 498.32 267.16 41875 +1956 271 18.12 12.12 16.47 0 459.66 268.06 41671 +1956 272 23.82 17.82 22.17 0 630.61 249.87 41468 +1956 273 19.46 13.46 17.81 0 495.8 259.72 41265 +1956 274 12.15 6.15 10.5 0.88 324.6 203.79 41062 +1956 275 11.83 5.83 10.18 0.86 318.44 202.07 40860 +1956 276 12.32 6.32 10.67 0 327.91 265.93 40658 +1956 277 13.22 7.22 11.57 0.24 345.94 196.34 40456 +1956 278 13.18 7.18 11.53 0.33 345.12 194.23 40255 +1956 279 13.69 7.69 12.04 0 355.68 255.31 40054 +1956 280 12.98 6.98 11.33 0.03 341.05 190.37 39854 +1956 281 11.66 5.66 10.01 0.33 315.21 189.83 39654 +1956 282 14.03 8.03 12.38 0 362.88 246.65 39455 +1956 283 14.99 8.99 13.34 0 383.87 242.2 39256 +1956 284 15.8 9.8 14.15 0 402.38 237.76 39058 +1956 285 11.52 5.52 9.87 0 312.57 242.01 38861 +1956 286 13.23 7.23 11.58 1.03 346.14 177.55 38664 +1956 287 12.57 6.57 10.92 0 332.83 234.79 38468 +1956 288 10.64 4.64 8.99 0.02 296.41 176 38273 +1956 289 11.93 5.93 10.28 0.23 320.35 172.71 38079 +1956 290 10.33 4.33 8.68 0 290.89 229.52 37885 +1956 291 14.62 8.62 12.97 0 375.66 220.72 37693 +1956 292 20.23 14.23 18.58 0 517.65 207.48 37501 +1956 293 18.74 12.74 17.09 0 476.09 208.01 37311 +1956 294 11.85 5.85 10.2 0 318.82 216.53 37121 +1956 295 8.76 2.76 7.11 0 264.26 217.39 36933 +1956 296 9.67 3.67 8.02 0 279.43 213.77 36745 +1956 297 12.6 6.6 10.95 0 333.43 207.41 36560 +1956 298 9.06 3.06 7.41 0 269.18 209.07 36375 +1956 299 12.84 6.84 11.19 0 338.22 201.74 36191 +1956 300 13.17 7.17 11.52 0 344.91 198.65 36009 +1956 301 11.29 5.29 9.64 0 308.27 198.56 35829 +1956 302 12.3 6.3 10.65 1.94 327.52 146.04 35650 +1956 303 11.27 5.27 9.62 0 307.9 193.41 35472 +1956 304 13.24 7.24 11.59 0.11 346.35 141.39 35296 +1956 305 5.4 -0.6 3.75 0.03 214.22 145.44 35122 +1956 306 9.22 3.22 7.57 0.01 271.84 141.15 34950 +1956 307 4.87 -1.13 3.22 0.04 207.13 142.12 34779 +1956 308 1.25 -4.75 -0.4 0.47 163.85 141.96 34610 +1956 309 3.94 -2.06 2.29 0.02 195.16 138.89 34444 +1956 310 4.92 -1.08 3.27 0 207.79 182 34279 +1956 311 4.03 -1.97 2.38 0 196.29 180.43 34116 +1956 312 5.8 -0.2 4.15 0 219.72 176.47 33956 +1956 313 5.75 -0.25 4.1 0.08 219.02 130.78 33797 +1956 314 4.19 -1.81 2.54 0.05 198.32 130.14 33641 +1956 315 1.17 -4.83 -0.48 0.74 162.99 129.6 33488 +1956 316 -0.92 -6.92 -2.57 0 141.85 171.65 33337 +1956 317 0.34 -5.66 -1.31 0 154.29 168.79 33188 +1956 318 3.4 -2.6 1.75 0.01 188.49 123.51 33042 +1956 319 5.57 -0.43 3.92 1 216.54 121.14 32899 +1956 320 3.72 -2.28 2.07 0.34 192.42 120.65 32758 +1956 321 1.72 -4.28 0.07 0 168.99 159.91 32620 +1956 322 3.97 -2.03 2.32 0.01 195.54 117.56 32486 +1956 323 2.73 -3.27 1.08 0 180.49 155.86 32354 +1956 324 2.8 -3.2 1.15 0.24 181.32 115.31 32225 +1956 325 7.26 1.26 5.61 0 240.81 149.08 32100 +1956 326 10.55 4.55 8.9 0.39 294.79 108.66 31977 +1956 327 7.49 1.49 5.84 0.43 244.28 109.21 31858 +1956 328 2.36 -3.64 0.71 0.86 176.2 110.2 31743 +1956 329 3.79 -2.21 2.14 0.07 193.29 108.46 31631 +1956 330 4.98 -1.02 3.33 0.65 208.58 106.83 31522 +1956 331 3.81 -2.19 2.16 0.65 193.54 106.37 31417 +1956 332 6.49 0.49 4.84 0.55 229.48 103.87 31316 +1956 333 11.95 5.95 10.3 0 320.74 132.96 31218 +1956 334 6.28 0.28 4.63 0 226.47 136.45 31125 +1956 335 6 0 4.35 0 222.51 135.47 31035 +1956 336 3.71 -2.29 2.06 0.35 192.3 101.84 30949 +1956 337 6.6 0.6 4.95 0.16 231.07 99.26 30867 +1956 338 3.44 -2.56 1.79 0 188.98 133.32 30790 +1956 339 -1.93 -7.93 -3.58 0 132.51 134.97 30716 +1956 340 3.63 -2.37 1.98 0 191.31 131.69 30647 +1956 341 4.52 -1.48 2.87 0 202.55 130.27 30582 +1956 342 5.03 -0.97 3.38 0 209.25 129.21 30521 +1956 343 2.87 -3.13 1.22 0 182.14 129.57 30465 +1956 344 -1.59 -7.59 -3.24 0 135.6 130.41 30413 +1956 345 -1.33 -7.33 -2.98 0 137.99 129.87 30366 +1956 346 0.99 -5.01 -0.66 0 161.07 128.35 30323 +1956 347 1.06 -4.94 -0.59 0 161.81 127.72 30284 +1956 348 4.87 -1.13 3.22 0 207.13 125.43 30251 +1956 349 7.36 1.36 5.71 0 242.31 123.49 30221 +1956 350 3.32 -2.68 1.67 0 187.52 125.56 30197 +1956 351 6.22 0.22 4.57 0.03 225.61 92.76 30177 +1956 352 7 1 5.35 0 236.93 123.09 30162 +1956 353 5.28 -0.72 3.63 0 212.6 124.1 30151 +1956 354 8.87 2.87 7.22 0 266.06 121.69 30145 +1956 355 12.66 6.66 11.01 0 334.62 118.53 30144 +1956 356 10.09 4.09 8.44 0 286.67 120.78 30147 +1956 357 7.38 1.38 5.73 0.13 242.61 92.12 30156 +1956 358 6.1 0.1 4.45 0.37 223.91 92.81 30169 +1956 359 1.23 -4.77 -0.42 0.15 163.64 94.84 30186 +1956 360 0.73 -5.27 -0.92 0.06 158.33 95.28 30208 +1956 361 -0.96 -6.96 -2.61 0 141.47 128.08 30235 +1956 362 -3.32 -9.32 -4.97 0.94 120.54 143.62 30267 +1956 363 -8.27 -14.27 -9.92 0.02 85.17 145.12 30303 +1956 364 -5.93 -11.93 -7.58 0 100.56 177.71 30343 +1956 365 -4.98 -10.98 -6.63 0.28 107.47 145.96 30388 +1957 1 -8.6 -14.6 -10.25 0 83.17 180.61 30438 +1957 2 -6.19 -12.19 -7.84 0 98.74 180.66 30492 +1957 3 -6.74 -12.74 -8.39 0.02 94.98 148.1 30551 +1957 4 -5.01 -11.01 -6.66 0 107.25 182.08 30614 +1957 5 -1.85 -7.85 -3.5 0 133.23 181.57 30681 +1957 6 0.75 -5.25 -0.9 0.06 158.54 147.58 30752 +1957 7 0.85 -5.15 -0.8 0 159.59 181.71 30828 +1957 8 0.83 -5.17 -0.82 0 159.38 182.99 30907 +1957 9 -0.94 -6.94 -2.59 0 141.66 184.9 30991 +1957 10 1 -5 -0.65 0.19 161.18 150.3 31079 +1957 11 -0.37 -6.37 -2.02 0 147.17 186.58 31171 +1957 12 1.5 -4.5 -0.15 0 166.57 186.4 31266 +1957 13 6.81 0.81 5.16 0 234.13 183.85 31366 +1957 14 2.36 -3.64 0.71 0 176.2 187.6 31469 +1957 15 2.63 -3.37 0.98 0 179.33 188.42 31575 +1957 16 1.99 -4.01 0.34 0.04 172 153.01 31686 +1957 17 2.85 -3.15 1.2 0 181.9 190.36 31800 +1957 18 0.04 -5.96 -1.61 0.07 151.25 155.76 31917 +1957 19 1.54 -4.46 -0.11 0 167 194.39 32038 +1957 20 0.02 -5.98 -1.63 0.13 151.05 157.91 32161 +1957 21 2.26 -3.74 0.61 0.02 175.06 158.12 32289 +1957 22 2.14 -3.86 0.49 0.01 173.69 159.05 32419 +1957 23 2.61 -3.39 0.96 0 179.09 158.89 32552 +1957 24 2.39 -3.61 0.74 1.54 176.55 120.82 32688 +1957 25 -0.71 -6.71 -2.36 0 143.86 164.6 32827 +1957 26 3.15 -2.85 1.5 0 185.47 164.46 32969 +1957 27 0.64 -5.36 -1.01 0 157.39 167.92 33114 +1957 28 0.74 -5.26 -0.91 0 158.43 170.09 33261 +1957 29 -1.19 -7.19 -2.84 0.08 139.3 169.83 33411 +1957 30 2.72 -3.28 1.07 0 180.38 173.61 33564 +1957 31 -1.15 -7.15 -2.8 0 139.68 178.11 33718 +1957 32 10.48 4.48 8.83 0 293.55 171.78 33875 +1957 33 10.31 4.31 8.66 0 290.53 174.54 34035 +1957 34 14.22 8.22 12.57 0.85 366.95 129.08 34196 +1957 35 12.22 6.22 10.57 0 325.96 176.67 34360 +1957 36 11.93 5.93 10.28 0.22 320.35 134.59 34526 +1957 37 6.47 0.47 4.82 0 229.19 187.29 34694 +1957 38 8.8 2.8 7.15 0.03 264.91 140.91 34863 +1957 39 5.22 -0.78 3.57 0 211.79 193.63 35035 +1957 40 2.62 -3.38 0.97 0 179.21 198.15 35208 +1957 41 2.62 -3.38 0.97 0 179.21 200.78 35383 +1957 42 3.91 -2.09 2.26 0 194.79 202.43 35560 +1957 43 5.13 -0.87 3.48 0 210.58 204.18 35738 +1957 44 6.89 0.89 5.24 0 235.3 205.22 35918 +1957 45 8.92 2.92 7.27 0.03 266.88 154.36 36099 +1957 46 7.15 1.15 5.5 2.44 239.16 157.69 36282 +1957 47 5.51 -0.49 3.86 0.69 215.72 160.91 36466 +1957 48 6.86 0.86 5.21 0 234.86 216.12 36652 +1957 49 7.52 1.52 5.87 0 244.74 218.24 36838 +1957 50 8.55 2.55 6.9 0.05 260.86 164.86 37026 +1957 51 9.33 3.33 7.68 0 273.67 221.88 37215 +1957 52 9.05 3.05 7.4 0 269.02 224.99 37405 +1957 53 7.94 1.94 6.29 0 251.21 229.15 37596 +1957 54 8.6 2.6 6.95 0.15 261.67 173.37 37788 +1957 55 8.14 2.14 6.49 0.11 254.34 175.98 37981 +1957 56 9.03 3.03 7.38 0.45 268.69 177.22 38175 +1957 57 2.79 -3.21 1.14 0.77 181.2 183.93 38370 +1957 58 4.08 -1.92 2.43 0.88 196.93 185.34 38565 +1957 59 4.51 -1.49 2.86 0.08 202.42 187.09 38761 +1957 60 6.49 0.49 4.84 0 229.48 250.44 38958 +1957 61 9.36 3.36 7.71 0.07 274.18 187.57 39156 +1957 62 5.24 -0.76 3.59 0.01 212.06 193.07 39355 +1957 63 3.66 -2.34 2.01 0.21 191.68 196.43 39553 +1957 64 1.72 -4.28 0.07 0 168.99 266.46 39753 +1957 65 0.76 -5.24 -0.89 1.04 158.64 202.59 39953 +1957 66 0.57 -5.43 -1.08 0 156.66 273.04 40154 +1957 67 5.98 -0.02 4.33 0 222.23 271.17 40355 +1957 68 8.22 2.22 6.57 0 255.6 271.48 40556 +1957 69 8.71 2.71 7.06 0 263.45 273.48 40758 +1957 70 16.26 10.26 14.61 0 413.22 263.94 40960 +1957 71 15.43 9.43 13.78 0 393.83 268.41 41163 +1957 72 14.69 8.69 13.04 0 377.2 272.57 41366 +1957 73 15.16 9.16 13.51 0 387.69 274.26 41569 +1957 74 15.37 9.37 13.72 0 392.46 276.5 41772 +1957 75 14.23 8.23 12.58 0 367.17 281.36 41976 +1957 76 13.84 7.84 12.19 0 358.84 284.65 42179 +1957 77 14.55 8.55 12.9 0 374.12 285.85 42383 +1957 78 9.27 3.27 7.62 0 272.67 297.25 42587 +1957 79 9.84 3.84 8.19 0.16 282.34 224.36 42791 +1957 80 10.54 4.54 8.89 0 294.62 300.61 42996 +1957 81 14.01 8.01 12.36 0 362.45 297.15 43200 +1957 82 14.92 8.92 13.27 0 382.3 297.93 43404 +1957 83 11.11 5.11 9.46 0 304.95 307.37 43608 +1957 84 11.93 5.93 10.28 0 320.35 308.5 43812 +1957 85 10.28 4.28 8.63 0 290 313.7 44016 +1957 86 11.8 5.8 10.15 0 317.87 313.58 44220 +1957 87 9.06 3.06 7.41 0 269.18 320.49 44424 +1957 88 10.65 4.65 9 0 296.59 320.37 44627 +1957 89 10.67 4.67 9.02 0 296.95 322.61 44831 +1957 90 11.32 5.32 9.67 0 308.83 323.87 45034 +1957 91 16.15 10.15 14.5 0 410.61 316.39 45237 +1957 92 15.8 9.8 14.15 0 402.38 319.37 45439 +1957 93 15.78 9.78 14.13 0.21 401.91 241.18 45642 +1957 94 14.17 8.17 12.52 0 365.87 327.22 45843 +1957 95 14.23 8.23 12.58 0.08 367.17 246.9 46045 +1957 96 15.24 9.24 13.59 0.25 389.5 246.81 46246 +1957 97 11.21 5.21 9.56 1.08 306.79 254.39 46446 +1957 98 6.99 0.99 5.34 0.57 236.78 260.82 46647 +1957 99 8.27 2.27 6.62 0.14 256.39 260.97 46846 +1957 100 6.3 0.3 4.65 0 226.75 352.71 47045 +1957 101 8.21 2.21 6.56 0 255.44 351.98 47243 +1957 102 10.37 4.37 8.72 0 291.59 350.43 47441 +1957 103 11.96 5.96 10.31 0 320.93 349.39 47638 +1957 104 13.96 7.96 12.31 0.01 361.38 260.36 47834 +1957 105 12.99 6.99 11.34 0.02 341.25 263.23 48030 +1957 106 13.38 7.38 11.73 0 349.23 351.8 48225 +1957 107 13.95 7.95 12.3 0 361.17 352.25 48419 +1957 108 16.67 10.67 15.02 0.03 423.1 260.63 48612 +1957 109 14.79 8.79 13.14 0.64 379.41 265.26 48804 +1957 110 16.83 10.83 15.18 0.99 427.01 262.54 48995 +1957 111 11.73 5.73 10.08 0.77 316.53 272.34 49185 +1957 112 10.01 4.01 8.36 0.12 285.28 275.86 49374 +1957 113 8.87 2.87 7.22 0 266.06 371.09 49561 +1957 114 11.48 5.48 9.83 0.05 311.82 275.98 49748 +1957 115 12.17 6.17 10.52 0.34 324.99 276.04 49933 +1957 116 14.47 8.47 12.82 0.08 372.37 273.23 50117 +1957 117 15.82 9.82 14.17 0 402.84 362.35 50300 +1957 118 16.03 10.03 14.38 0 407.77 363.12 50481 +1957 119 14.47 8.47 12.82 0.05 372.37 276.09 50661 +1957 120 13.36 7.36 11.71 0 348.81 371.8 50840 +1957 121 11.83 5.83 10.18 0 318.44 376.14 51016 +1957 122 12.87 6.87 11.22 0 338.83 375.19 51191 +1957 123 14.5 8.5 12.85 2.42 373.03 279.43 51365 +1957 124 14.41 8.41 12.76 0.34 371.06 280.39 51536 +1957 125 13.66 7.66 12.01 0.84 355.05 282.43 51706 +1957 126 11.28 5.28 9.63 0.29 308.09 286.94 51874 +1957 127 15.78 9.78 14.13 0.24 401.91 280.02 52039 +1957 128 16.91 10.91 15.26 0 428.97 371.35 52203 +1957 129 15.77 9.77 14.12 0 401.68 375.23 52365 +1957 130 14.39 8.39 12.74 0.23 370.63 284.58 52524 +1957 131 12.52 6.52 10.87 0.72 331.84 288.34 52681 +1957 132 15.71 9.71 14.06 0.1 400.28 283.35 52836 +1957 133 14.94 8.94 13.29 0.04 382.75 285.33 52989 +1957 134 15.31 9.31 13.66 0 391.09 380.23 53138 +1957 135 16.98 10.98 15.33 0 430.7 376.5 53286 +1957 136 16.76 10.76 15.11 0 425.29 377.74 53430 +1957 137 14.77 8.77 13.12 0 378.97 383.63 53572 +1957 138 9.64 3.64 7.99 0 278.91 395.08 53711 +1957 139 13.72 7.72 12.07 0 356.31 387.44 53848 +1957 140 11.59 5.59 9.94 0.65 313.89 294.41 53981 +1957 141 10.26 4.26 8.61 0.16 289.65 296.7 54111 +1957 142 12.66 6.66 11.01 0.43 334.62 293.45 54238 +1957 143 14.69 8.69 13.04 0 377.2 387.11 54362 +1957 144 17.32 11.32 15.67 0.02 439.17 285.44 54483 +1957 145 17.56 11.56 15.91 0.66 445.23 285.27 54600 +1957 146 19.03 13.03 17.38 0.02 483.95 282.19 54714 +1957 147 17.29 11.29 15.64 0 438.42 382 54824 +1957 148 16.12 10.12 14.47 0 409.89 385.63 54931 +1957 149 15.72 9.72 14.07 0.28 400.51 290.26 55034 +1957 150 17.19 11.19 15.54 0 435.91 383.32 55134 +1957 151 16.28 10.28 14.63 0.4 413.7 289.69 55229 +1957 152 23.55 17.55 21.9 0.05 621.44 271.36 55321 +1957 153 25.77 19.77 24.12 0 700.27 352.32 55409 +1957 154 22.38 16.38 20.73 0 583.02 367.02 55492 +1957 155 21.71 15.71 20.06 0 561.93 369.75 55572 +1957 156 23.4 17.4 21.75 0.14 616.4 272.6 55648 +1957 157 23.02 17.02 21.37 0 603.78 365.17 55719 +1957 158 22.12 16.12 20.47 0 574.76 368.86 55786 +1957 159 19.42 13.42 17.77 0 494.69 378.64 55849 +1957 160 19.87 13.87 18.22 0.15 507.33 283 55908 +1957 161 20.62 14.62 18.97 0.17 529.02 281.12 55962 +1957 162 22.35 16.35 20.7 0.4 582.06 276.38 56011 +1957 163 22.62 16.62 20.97 0.08 590.73 275.75 56056 +1957 164 19.65 13.65 18 0 501.12 378.45 56097 +1957 165 20.41 14.41 18.76 0 522.87 375.97 56133 +1957 166 19.92 13.92 18.27 0.05 508.76 283.29 56165 +1957 167 20.6 14.6 18.95 0.04 528.43 281.5 56192 +1957 168 24.38 18.38 22.73 0.01 649.98 270.49 56214 +1957 169 25.11 19.11 23.46 0 676 357.43 56231 +1957 170 25.4 19.4 23.75 0 686.58 356.12 56244 +1957 171 25.99 19.99 24.34 0.67 708.52 265.07 56252 +1957 172 21.32 15.32 19.67 0.17 549.96 279.67 56256 +1957 173 21.31 15.31 19.66 0.83 549.66 279.69 56255 +1957 174 23.33 17.33 21.68 0.02 614.06 273.77 56249 +1957 175 25.96 19.96 24.31 0.06 707.39 265.08 56238 +1957 176 29.36 23.36 27.71 0 845.61 335.81 56223 +1957 177 25.06 19.06 23.41 0 674.19 357.45 56203 +1957 178 23.49 17.49 21.84 0.65 619.42 273.17 56179 +1957 179 26.74 20.74 25.09 0.49 737.28 262.11 56150 +1957 180 23.72 17.72 22.07 0.09 627.2 272.29 56116 +1957 181 23.01 17.01 21.36 0.18 603.45 274.42 56078 +1957 182 21.04 15.04 19.39 2.4 541.5 279.92 56035 +1957 183 17.09 11.09 15.44 0.29 433.42 289.3 55987 +1957 184 19.3 13.3 17.65 1.39 491.36 284.13 55935 +1957 185 22.99 16.99 21.34 0.14 602.79 274.07 55879 +1957 186 20.89 14.89 19.24 1.3 537.02 279.82 55818 +1957 187 21.08 15.08 19.43 2.85 542.7 279.17 55753 +1957 188 23.58 17.58 21.93 1.2 622.45 271.75 55684 +1957 189 26.31 20.31 24.66 0.05 720.68 262.51 55611 +1957 190 27.73 21.73 26.08 0.79 776.75 256.94 55533 +1957 191 28.11 22.11 26.46 0 792.36 340.36 55451 +1957 192 24.15 18.15 22.5 0.3 641.97 269.14 55366 +1957 193 21.92 15.92 20.27 0.31 568.47 275.63 55276 +1957 194 24.11 18.11 22.46 1.36 640.58 268.91 55182 +1957 195 23.15 17.15 21.5 0.27 608.07 271.68 55085 +1957 196 22.71 16.71 21.06 0.8 593.64 272.69 54984 +1957 197 24.67 18.67 23.02 0.81 660.22 266.28 54879 +1957 198 24.14 18.14 22.49 0.6 641.62 267.68 54770 +1957 199 24.18 18.18 22.53 0.51 643.01 267.29 54658 +1957 200 22.97 16.97 21.32 0.91 602.13 270.72 54542 +1957 201 18.83 12.83 17.18 0.12 478.52 281.32 54423 +1957 202 18.99 12.99 17.34 0.63 482.86 280.52 54301 +1957 203 20.34 14.34 18.69 0.09 520.83 276.82 54176 +1957 204 25.24 19.24 23.59 0.02 680.72 262.06 54047 +1957 205 23.95 17.95 22.3 0 635.06 354.47 53915 +1957 206 29.79 23.79 28.14 0 864.61 325.4 53780 +1957 207 31.3 25.3 29.65 0.06 934.21 236.9 53643 +1957 208 27.59 21.59 25.94 0.01 771.06 251.98 53502 +1957 209 23.82 17.82 22.17 0 630.61 352.55 53359 +1957 210 25.52 19.52 23.87 0.17 690.99 258.48 53213 +1957 211 22.48 16.48 20.83 0.25 586.22 267.36 53064 +1957 212 23.14 17.14 21.49 0 607.74 353.15 52913 +1957 213 20.04 14.04 18.39 0.38 512.18 272.69 52760 +1957 214 21.7 15.7 20.05 0 561.62 357.1 52604 +1957 215 23.97 17.97 22.32 0 635.75 347.69 52445 +1957 216 21.26 15.26 19.61 0.22 548.14 267.75 52285 +1957 217 20.02 14.02 18.37 0 511.61 360.32 52122 +1957 218 20.31 14.31 18.66 0.01 519.96 268.91 51958 +1957 219 22.89 16.89 21.24 0 599.51 348.29 51791 +1957 220 19.78 13.78 18.13 0 504.78 358.3 51622 +1957 221 24.18 18.18 22.53 1.03 643.01 255.97 51451 +1957 222 22.95 16.95 21.3 0.09 601.48 258.86 51279 +1957 223 22.51 16.51 20.86 0.16 587.18 259.26 51105 +1957 224 22.02 16.02 20.37 0.05 571.61 259.83 50929 +1957 225 19.75 13.75 18.1 1.05 503.94 264.74 50751 +1957 226 18.79 12.79 17.14 0.49 477.44 266.1 50572 +1957 227 21.31 15.31 19.66 0 549.66 345.43 50392 +1957 228 24.43 18.43 22.78 0 651.74 332.51 50210 +1957 229 17.45 11.45 15.8 0 442.44 354.87 50026 +1957 230 17.97 11.97 16.32 0 455.76 352.13 49842 +1957 231 22.88 16.88 21.23 0.01 599.18 251.02 49656 +1957 232 20.26 14.26 18.61 0 518.51 342.42 49469 +1957 233 16.97 10.97 15.32 0.66 430.45 262.93 49280 +1957 234 15.71 9.71 14.06 0 400.28 352.32 49091 +1957 235 14.33 8.33 12.68 0 369.33 354.03 48900 +1957 236 15.3 9.3 13.65 0 390.86 350.32 48709 +1957 237 19.86 13.86 18.21 0 507.05 336.31 48516 +1957 238 20.87 14.87 19.22 0 536.42 331.46 48323 +1957 239 21.28 15.28 19.63 0.2 548.75 246.47 48128 +1957 240 23.53 17.53 21.88 0.81 620.77 239.24 47933 +1957 241 22.95 16.95 21.3 0 601.48 319.45 47737 +1957 242 23.65 17.65 22 0.12 624.82 236.4 47541 +1957 243 23.33 17.33 21.68 0 614.06 314.59 47343 +1957 244 21.05 15.05 19.4 0.11 541.8 240.46 47145 +1957 245 19.73 13.73 18.08 0.32 503.37 242.15 46947 +1957 246 16.57 10.57 14.92 0.12 420.67 247.07 46747 +1957 247 16.72 10.72 15.07 0.19 424.32 245.39 46547 +1957 248 14.6 8.6 12.95 0 375.22 330.12 46347 +1957 249 11.72 5.72 10.07 0 316.34 333.71 46146 +1957 250 14.25 8.25 12.6 0 367.6 326.77 45945 +1957 251 19.71 13.71 18.06 0.02 502.81 233.38 45743 +1957 252 20.11 14.11 18.46 0.05 514.19 230.91 45541 +1957 253 20.18 14.18 18.53 1.57 516.2 229.2 45339 +1957 254 17.67 11.67 16.02 0.44 448.04 232.72 45136 +1957 255 19.35 13.35 17.7 0 492.75 303.63 44933 +1957 256 19.37 13.37 17.72 0 493.3 301.34 44730 +1957 257 22.15 16.15 20.5 0 575.7 290.99 44527 +1957 258 15.58 9.58 13.93 0 397.27 306.14 44323 +1957 259 13.6 7.6 11.95 0 353.8 307.73 44119 +1957 260 16.4 10.4 14.75 0 416.57 299.49 43915 +1957 261 20.04 14.04 18.39 0.07 512.18 215.96 43711 +1957 262 20.7 14.7 19.05 0 531.38 283.78 43507 +1957 263 19.6 13.6 17.95 0.21 499.72 213.31 43303 +1957 264 21.62 15.62 19.97 0.76 559.15 207.17 43099 +1957 265 15.85 9.85 14.2 0.48 403.54 216.34 42894 +1957 266 14.54 8.54 12.89 0.28 373.9 216.47 42690 +1957 267 18.31 12.31 16.66 0.03 464.64 208.33 42486 +1957 268 18.98 12.98 17.33 0.05 482.59 205.21 42282 +1957 269 18.95 12.95 17.3 0.41 481.77 203.42 42078 +1957 270 15.12 9.12 13.47 0 386.79 277.07 41875 +1957 271 17.26 11.26 15.61 0 437.66 270.01 41671 +1957 272 16.66 10.66 15.01 0 422.85 268.61 41468 +1957 273 16.26 10.26 14.61 0 413.22 266.94 41265 +1957 274 14.04 8.04 12.39 0 363.09 268.53 41062 +1957 275 13.11 7.11 11.46 0 343.69 267.36 40860 +1957 276 15.56 9.56 13.91 0 396.81 260.25 40658 +1957 277 12.83 6.83 11.18 0 338.02 262.43 40456 +1957 278 14.45 8.45 12.8 0 371.94 256.81 40255 +1957 279 14.83 8.83 13.18 0.07 380.3 190 40054 +1957 280 12.32 6.32 10.67 0.3 327.91 191.14 39854 +1957 281 9.43 3.43 7.78 0.15 275.36 192.12 39654 +1957 282 13.2 7.2 11.55 0 345.53 248.01 39455 +1957 283 15.26 9.26 13.61 0 389.95 241.72 39256 +1957 284 15.33 9.33 13.68 0 391.55 238.6 39058 +1957 285 13.87 7.87 12.22 0 359.47 238.47 38861 +1957 286 19.27 13.27 17.62 0 490.54 225.51 38664 +1957 287 14.56 8.56 12.91 0 374.34 231.68 38468 +1957 288 7.26 1.26 5.61 0.03 240.81 178.96 38273 +1957 289 10.54 4.54 8.89 0 294.62 232.14 38079 +1957 290 11.82 5.82 10.17 0 318.25 227.57 37885 +1957 291 11.63 5.63 9.98 0 314.64 225.13 37693 +1957 292 12.53 6.53 10.88 0 332.04 221.2 37501 +1957 293 13.3 7.3 11.65 0 347.58 217.38 37311 +1957 294 13.36 7.36 11.71 0.01 348.81 160.82 37121 +1957 295 12.32 6.32 10.67 0.22 327.91 159.8 36933 +1957 296 11.95 5.95 10.3 1.21 320.74 158.24 36745 +1957 297 10.18 4.18 8.53 0.07 288.25 157.83 36560 +1957 298 6.36 0.36 4.71 0 227.61 211.74 36375 +1957 299 7.38 1.38 5.73 0.02 242.61 155.98 36191 +1957 300 9.39 3.39 7.74 0 274.68 203.24 36009 +1957 301 10.43 4.43 8.78 0 292.66 199.56 35829 +1957 302 13.27 7.27 11.62 0 346.96 193.45 35650 +1957 303 13.92 7.92 12.27 0 360.53 190.02 35472 +1957 304 14.78 8.78 13.13 0.27 379.19 139.8 35296 +1957 305 11.34 5.34 9.69 0.42 309.2 141.12 35122 +1957 306 11.34 5.34 9.69 0 309.2 185.92 34950 +1957 307 11.01 5.01 9.36 0 303.11 183.8 34779 +1957 308 6.61 0.61 4.96 0 231.21 185.47 34610 +1957 309 7.54 1.54 5.89 0.57 245.04 136.76 34444 +1957 310 6 0 4.35 0 222.51 181.17 34279 +1957 311 6.76 0.76 5.11 0 233.39 178.36 34116 +1957 312 4.76 -1.24 3.11 0 205.68 177.24 33956 +1957 313 6.04 0.04 4.39 0.25 223.07 130.61 33797 +1957 314 5.64 -0.36 3.99 0 217.5 172.48 33641 +1957 315 4.44 -1.56 2.79 0.13 201.52 128.09 33488 +1957 316 2.46 -3.54 0.81 0.19 177.35 127.38 33337 +1957 317 4.81 -1.19 3.16 0.03 206.34 124.59 33188 +1957 318 3.35 -2.65 1.7 0 187.89 164.71 33042 +1957 319 6.08 0.08 4.43 0 223.63 161.15 32899 +1957 320 9.34 3.34 7.69 0 273.84 156.63 32758 +1957 321 10.96 4.96 9.31 0 302.2 153.02 32620 +1957 322 10.71 4.71 9.06 0 297.67 151.47 32486 +1957 323 15.09 9.09 13.44 0.01 386.11 108.82 32354 +1957 324 10.19 4.19 8.54 0.01 288.42 111.25 32225 +1957 325 14 8 12.35 0 362.24 142.74 32100 +1957 326 14.67 8.67 13.02 0.02 376.76 105.42 31977 +1957 327 14.29 8.29 12.64 1.04 368.46 104.41 31858 +1957 328 13.12 7.12 11.47 0 343.89 138.58 31743 +1957 329 11.53 5.53 9.88 0.09 312.76 104.05 31631 +1957 330 7.25 1.25 5.6 0 240.65 140.9 31522 +1957 331 6.31 0.31 4.66 0 226.89 140.25 31417 +1957 332 6.63 0.63 4.98 0 231.5 138.39 31316 +1957 333 9.07 3.07 7.42 0 269.35 135.5 31218 +1957 334 8.24 2.24 6.59 0 255.92 135.06 31125 +1957 335 5.95 -0.05 4.3 0 221.81 135.5 31035 +1957 336 3.06 -2.94 1.41 0 184.4 136.14 30949 +1957 337 2.18 -3.82 0.53 0 174.15 134.92 30867 +1957 338 1.92 -4.08 0.27 0 171.21 134.1 30790 +1957 339 5.56 -0.44 3.91 0 216.41 131.29 30716 +1957 340 5.43 -0.57 3.78 0 214.63 130.64 30647 +1957 341 5.03 -0.97 3.38 0 209.25 129.97 30582 +1957 342 8.09 2.09 6.44 0 253.55 127.2 30521 +1957 343 6.6 0.6 4.95 0 231.07 127.41 30465 +1957 344 3.37 -2.63 1.72 0 188.13 128.18 30413 +1957 345 3.68 -2.32 2.03 0 191.93 127.58 30366 +1957 346 1.48 -4.52 -0.17 0 166.35 128.13 30323 +1957 347 -0.31 -6.31 -1.96 0 147.76 128.31 30284 +1957 348 0.11 -5.89 -1.54 0 151.95 127.78 30251 +1957 349 -0.6 -6.6 -2.25 0 144.92 127.69 30221 +1957 350 -0.43 -6.43 -2.08 0 146.58 127.28 30197 +1957 351 -0.06 -6.06 -1.71 0 150.24 126.91 30177 +1957 352 2.43 -3.57 0.78 1.88 177.01 94.27 30162 +1957 353 3 -3 1.35 0 183.68 125.35 30151 +1957 354 2.15 -3.85 0.5 0.04 173.81 94.3 30145 +1957 355 7.15 1.15 5.5 0 239.16 122.9 30144 +1957 356 6.81 0.81 5.16 0 234.13 123.15 30147 +1957 357 7.63 1.63 5.98 0 246.42 122.66 30156 +1957 358 4.74 -1.26 3.09 0 205.42 124.55 30169 +1957 359 4.67 -1.33 3.02 0 204.5 124.71 30186 +1957 360 2.42 -3.58 0.77 0 176.89 126.26 30208 +1957 361 3.52 -2.48 1.87 0 189.96 126.03 30235 +1957 362 4.46 -1.54 2.81 0.12 201.78 94.47 30267 +1957 363 5.6 -0.4 3.95 0.2 216.95 94.41 30303 +1957 364 2.86 -3.14 1.21 0 182.02 127.8 30343 +1957 365 2.94 -3.06 1.29 0.01 182.97 96.24 30388 +1958 1 0.5 -5.5 -1.15 0 155.94 130.38 30438 +1958 2 0.49 -5.51 -1.16 0 155.83 131.12 30492 +1958 3 0.62 -5.38 -1.03 0 157.18 132.01 30551 +1958 4 -1.35 -7.35 -3 0 137.81 133.75 30614 +1958 5 -0.48 -6.48 -2.13 0 146.09 134.06 30681 +1958 6 0.92 -5.08 -0.73 0 160.33 134.35 30752 +1958 7 -0.23 -6.23 -1.88 0 148.55 135.66 30828 +1958 8 0.51 -5.49 -1.14 0.06 156.04 102.62 30907 +1958 9 2.73 -3.27 1.08 0.05 180.49 102.76 30991 +1958 10 1.99 -4.01 0.34 0 172 138.69 31079 +1958 11 7.18 1.18 5.53 0 239.61 136.55 31171 +1958 12 9.76 3.76 8.11 0 280.97 135.54 31266 +1958 13 12.65 6.65 11 0 334.42 134.45 31366 +1958 14 8.35 2.35 6.7 0 257.66 139.73 31469 +1958 15 5.75 -0.25 4.1 0 219.02 143.04 31575 +1958 16 4.46 -1.54 2.81 0.22 201.78 108.86 31686 +1958 17 6.17 0.17 4.52 0 224.9 145.71 31800 +1958 18 6.77 0.77 5.12 0 233.54 147.16 31917 +1958 19 2.9 -3.1 1.25 0.15 182.5 113.69 32038 +1958 20 -2.08 -8.08 -3.73 0 131.17 155.61 32161 +1958 21 -2.8 -8.8 -4.45 0 124.9 157.93 32289 +1958 22 -2.42 -8.42 -4.07 0.07 128.18 160.59 32419 +1958 23 -3.08 -9.08 -4.73 0.52 122.54 163.5 32552 +1958 24 -2.68 -8.68 -4.33 0.44 125.93 166.07 32688 +1958 25 0.2 -5.8 -1.45 0 152.86 207.36 32827 +1958 26 2.62 -3.38 0.97 0 179.21 207.47 32969 +1958 27 0.5 -5.5 -1.15 1.04 155.94 168.44 33114 +1958 28 -4.18 -10.18 -5.83 0.45 113.61 172.78 33261 +1958 29 -0.23 -6.23 -1.88 1.15 148.55 176.41 33411 +1958 30 0.24 -5.76 -1.41 0.34 153.27 177.68 33564 +1958 31 0.74 -5.26 -0.91 0 158.43 223.26 33718 +1958 32 8.11 2.11 6.46 0 253.87 219 33875 +1958 33 8.86 2.86 7.21 0.04 265.89 175.66 34035 +1958 34 7.39 1.39 5.74 0 242.76 222.08 34196 +1958 35 5.75 -0.25 4.1 0.51 219.02 178.94 34360 +1958 36 2.26 -3.74 0.61 0 175.06 229.2 34526 +1958 37 4.25 -1.75 2.6 0.01 199.08 182.33 34694 +1958 38 7.29 1.29 5.64 0 241.26 228.83 34863 +1958 39 9.26 3.26 7.61 0.13 272.5 180.77 35035 +1958 40 10.58 4.58 8.93 0.22 295.33 143.37 35208 +1958 41 9 3 7.35 0 268.19 195.43 35383 +1958 42 11.5 5.5 9.85 0 312.19 195.16 35560 +1958 43 7 1 5.35 0 236.93 202.57 35738 +1958 44 4.31 -1.69 2.66 0 199.85 207.4 35918 +1958 45 8.78 2.78 7.13 0 264.59 205.96 36099 +1958 46 6.71 0.71 5.06 0.44 232.66 158 36282 +1958 47 9.14 3.14 7.49 0.11 270.51 158.27 36466 +1958 48 3.55 -2.45 1.9 0.28 190.33 164.22 36652 +1958 49 5.18 -0.82 3.53 0.73 211.25 165.31 36838 +1958 50 3.5 -2.5 1.85 0.3 189.71 168.35 37026 +1958 51 3.7 -2.3 2.05 1.34 192.17 170.47 37215 +1958 52 1.26 -4.74 -0.39 0.45 163.96 173.96 37405 +1958 53 4.96 -1.04 3.31 0.01 208.32 174.03 37596 +1958 54 3.18 -2.82 1.53 0 185.83 236.29 37788 +1958 55 5.17 -0.83 3.52 0 211.12 237.61 37981 +1958 56 8.35 2.35 6.7 0 257.66 237.07 38175 +1958 57 10.78 4.78 9.13 0.02 298.93 177.72 38370 +1958 58 12.56 6.56 10.91 0 332.64 237.35 38565 +1958 59 9.78 3.78 8.13 0.06 281.31 182.86 38761 +1958 60 5.47 -0.53 3.82 0 215.17 251.46 38958 +1958 61 1.99 -4.01 0.34 0 172 257.43 39156 +1958 62 1.44 -4.56 -0.21 0 165.91 260.68 39355 +1958 63 -1.75 -7.75 -3.4 0 134.14 265.91 39553 +1958 64 0.38 -5.62 -1.27 0 154.7 267.46 39753 +1958 65 2.28 -3.72 0.63 0 175.29 268.94 39953 +1958 66 -0.69 -6.69 -2.34 0.21 144.05 238.82 40154 +1958 67 -0.44 -6.44 -2.09 0 146.48 309.92 40355 +1958 68 2.29 -3.71 0.64 0 175.4 310.36 40556 +1958 69 3.76 -2.24 2.11 0.24 192.92 209.18 40758 +1958 70 4.91 -1.09 3.26 0.67 207.65 210.5 40960 +1958 71 5.97 -0.03 4.32 0.16 222.09 211.86 41163 +1958 72 7.57 1.57 5.92 0.37 245.5 212.6 41366 +1958 73 9.07 3.07 7.42 0 269.35 284.21 41569 +1958 74 9.81 3.81 8.16 0 281.82 285.91 41772 +1958 75 5.27 -0.73 3.62 0 212.46 294.27 41976 +1958 76 4.65 -1.35 3 0 204.24 297.59 42179 +1958 77 3.55 -2.45 1.9 0 190.33 301.33 42383 +1958 78 4.27 -1.73 2.62 0 199.34 303.31 42587 +1958 79 6.01 0.01 4.36 0 222.65 304.16 42791 +1958 80 7.42 1.42 5.77 0 243.22 305 42996 +1958 81 2.91 -3.09 1.26 0 182.61 312.61 43200 +1958 82 6.42 0.42 4.77 0 228.47 311.5 43404 +1958 83 4.17 -1.83 2.52 0 198.07 316.57 43608 +1958 84 3.18 -2.82 1.53 0 185.83 320.15 43812 +1958 85 4.38 -1.62 2.73 0.52 200.75 241.09 44016 +1958 86 3.59 -2.41 1.94 0 190.82 324.73 44220 +1958 87 3.4 -2.6 1.75 0 188.49 327.5 44424 +1958 88 4.79 -1.21 3.14 0.06 206.07 246.29 44627 +1958 89 6.81 0.81 5.16 1.1 234.13 246.19 44831 +1958 90 2.62 -3.38 0.97 0.79 179.21 251.56 45034 +1958 91 16.3 10.3 14.65 0 414.18 316.04 45237 +1958 92 9.41 3.41 7.76 0.71 275.02 248.61 45439 +1958 93 8 2 6.35 0 252.14 335.8 45642 +1958 94 11.17 5.17 9.52 0 306.05 332.96 45843 +1958 95 14.42 8.42 12.77 0 371.28 328.8 46045 +1958 96 12.8 6.8 11.15 0 337.42 334.19 46246 +1958 97 10.07 4.07 8.42 0 286.32 341.14 46446 +1958 98 9.61 3.61 7.96 0 278.4 343.86 46647 +1958 99 8.3 2.3 6.65 0.02 256.87 260.94 46846 +1958 100 5.43 -0.57 3.78 0 214.63 353.82 47045 +1958 101 8.45 2.45 6.8 0.05 259.26 263.71 47243 +1958 102 9.36 3.36 7.71 0.68 274.18 264.09 47441 +1958 103 8.88 2.88 7.23 0.27 266.22 266.05 47638 +1958 104 13.27 7.27 11.62 0 346.96 348.61 47834 +1958 105 13.53 7.53 11.88 0 352.34 349.85 48030 +1958 106 12.59 6.59 10.94 0 333.23 353.42 48225 +1958 107 8.62 2.62 6.97 0 261.99 362.17 48419 +1958 108 7.91 1.91 6.26 0 250.74 365.04 48612 +1958 109 9.48 3.48 7.83 0 276.2 364.18 48804 +1958 110 10.66 4.66 9.01 0.54 296.77 272.67 48995 +1958 111 9.58 3.58 7.93 0.38 277.89 275.26 49185 +1958 112 10.75 4.75 9.1 0 298.39 366.49 49374 +1958 113 4.59 -1.41 2.94 0 203.46 377.2 49561 +1958 114 12.3 6.3 10.65 0 327.52 366.36 49748 +1958 115 11.34 5.34 9.69 0 309.2 369.69 49933 +1958 116 12.09 6.09 10.44 0 323.43 369.45 50117 +1958 117 13.49 7.49 11.84 0 351.51 367.83 50300 +1958 118 15.24 9.24 13.59 0 389.5 365.09 50481 +1958 119 11.81 5.81 10.16 0.45 318.06 280.39 50661 +1958 120 9.72 3.72 8.07 0 280.28 378.94 50840 +1958 121 19.45 13.45 17.8 0.15 495.53 267.63 51016 +1958 122 20.49 14.49 18.84 0.27 525.2 265.98 51191 +1958 123 18.27 12.27 16.62 0.18 463.59 271.95 51365 +1958 124 18.76 12.76 17.11 0 476.63 362.19 51536 +1958 125 22.46 16.46 20.81 0 585.58 350.63 51706 +1958 126 21.59 15.59 19.94 0 558.23 354.77 51874 +1958 127 20.07 14.07 18.42 0 513.04 360.85 52039 +1958 128 22.42 16.42 20.77 0 584.3 353.53 52203 +1958 129 24.05 18.05 22.4 0 638.51 347.9 52365 +1958 130 23.35 17.35 21.7 0.48 614.73 263.62 52524 +1958 131 17.78 11.78 16.13 0 450.85 371.31 52681 +1958 132 17.46 11.46 15.81 0 442.7 373.04 52836 +1958 133 16.52 10.52 14.87 0 419.46 376.36 52989 +1958 134 19.42 13.42 17.77 0 494.69 368.5 53138 +1958 135 17.89 11.89 16.24 0.02 453.69 280.42 53286 +1958 136 18.44 12.44 16.79 0 468.08 372.87 53430 +1958 137 21.66 15.66 20.01 0.17 560.39 272.1 53572 +1958 138 24.49 18.49 22.84 0.27 653.85 264.12 53711 +1958 139 25.02 19.02 23.37 0.02 672.74 262.89 53848 +1958 140 22.67 16.67 21.02 0 592.35 360.71 53981 +1958 141 20.22 14.22 18.57 0 517.36 370.03 54111 +1958 142 17.44 11.44 15.79 0.03 442.19 284.42 54238 +1958 143 18.45 12.45 16.8 0 468.34 376.76 54362 +1958 144 19.92 13.92 18.27 0 508.76 372.52 54483 +1958 145 19.76 13.76 18.11 0 504.22 373.52 54600 +1958 146 19.84 13.84 18.19 0 506.48 373.62 54714 +1958 147 21.25 15.25 19.6 0.05 547.84 276.9 54824 +1958 148 23.43 17.43 21.78 0 617.4 361.2 54931 +1958 149 22.77 16.77 21.12 0 595.59 364.15 55034 +1958 150 26.53 20.53 24.88 0 729.13 348.02 55134 +1958 151 27.26 21.26 25.61 0.05 757.79 258.59 55229 +1958 152 22.3 16.3 20.65 0.6 580.46 275.09 55321 +1958 153 15.24 9.24 13.59 0.77 389.5 292.02 55409 +1958 154 17.33 11.33 15.68 1.35 439.42 287.99 55492 +1958 155 17.5 11.5 15.85 2.21 443.71 287.76 55572 +1958 156 20.25 14.25 18.6 0.21 518.22 281.46 55648 +1958 157 20.25 14.25 18.6 0.71 518.22 281.59 55719 +1958 158 21.21 15.21 19.56 2.49 546.63 279.18 55786 +1958 159 20.28 14.28 18.63 0.82 519.09 281.82 55849 +1958 160 19.27 13.27 17.62 0.13 490.54 284.48 55908 +1958 161 21.99 15.99 20.34 0.38 570.66 277.37 55962 +1958 162 23.38 17.38 21.73 0.31 615.73 273.31 56011 +1958 163 20.15 14.15 18.5 1.75 515.34 282.54 56056 +1958 164 23.22 17.22 21.57 0.34 610.39 273.99 56097 +1958 165 18.63 12.63 16.98 0.19 473.14 286.38 56133 +1958 166 18.33 12.33 16.68 0.3 465.17 287.14 56165 +1958 167 19.26 13.26 17.61 0 490.26 379.85 56192 +1958 168 19.97 13.97 18.32 0.14 510.18 283.18 56214 +1958 169 18.39 12.39 16.74 0.84 466.76 287.02 56231 +1958 170 20.86 14.86 19.21 0.32 536.12 280.88 56244 +1958 171 23.68 17.68 22.03 0 625.84 363.69 56252 +1958 172 21.27 15.27 19.62 0.05 548.44 279.81 56256 +1958 173 26.91 20.91 25.26 0.34 743.94 261.71 56255 +1958 174 24.87 18.87 23.22 0.02 667.35 268.84 56249 +1958 175 23.09 17.09 21.44 0.33 606.09 274.48 56238 +1958 176 20.14 14.14 18.49 0.73 515.05 282.67 56223 +1958 177 18.5 12.5 16.85 0.09 469.67 286.6 56203 +1958 178 16.68 10.68 15.03 0.03 423.34 290.65 56179 +1958 179 17.77 11.77 16.12 1 450.6 288.21 56150 +1958 180 19.69 13.69 18.04 0 502.24 378.11 56116 +1958 181 13.5 7.5 11.85 0 351.71 395.32 56078 +1958 182 21.75 15.75 20.1 0 563.17 370.63 56035 +1958 183 23.21 17.21 21.56 0.24 610.06 273.58 55987 +1958 184 24.27 18.27 22.62 0.07 646.14 270.15 55935 +1958 185 23.91 17.91 22.26 0.58 633.69 271.24 55879 +1958 186 24.88 18.88 23.23 0.33 667.71 267.91 55818 +1958 187 26 20 24.35 0.02 708.9 263.93 55753 +1958 188 26.74 20.74 25.09 0.75 737.28 261.07 55684 +1958 189 27.03 21.03 25.38 0.2 748.66 259.87 55611 +1958 190 25.62 19.62 23.97 0.1 694.69 264.67 55533 +1958 191 24.02 18.02 22.37 0.11 637.47 269.78 55451 +1958 192 22.89 16.89 21.24 1.1 599.51 273.02 55366 +1958 193 26.13 20.13 24.48 0.95 713.82 262.28 55276 +1958 194 27.41 21.41 25.76 0.36 763.8 257.43 55182 +1958 195 26.89 20.89 25.24 0.17 743.15 259.18 55085 +1958 196 21.06 15.06 19.41 0 542.1 369.75 54984 +1958 197 14.04 8.04 12.39 0.01 363.09 292.41 54879 +1958 198 15.48 9.48 13.83 0 394.97 385.89 54770 +1958 199 15.02 9.02 13.37 0 384.54 386.69 54658 +1958 200 16.62 10.62 14.97 0 421.88 382.07 54542 +1958 201 16.96 10.96 15.31 0 430.2 380.64 54423 +1958 202 19.99 13.99 18.34 0 510.75 370.78 54301 +1958 203 22.04 16.04 20.39 0 572.24 363.02 54176 +1958 204 23.69 17.69 22.04 0 626.18 356.05 54047 +1958 205 25.12 19.12 23.47 0.31 676.36 262.09 53915 +1958 206 23.68 17.68 22.03 0.64 625.84 266.28 53780 +1958 207 22.82 16.82 21.17 0 597.22 357.83 53643 +1958 208 24.01 18.01 22.36 0.08 637.13 264.3 53502 +1958 209 26.24 20.24 24.59 0 718 341.93 53359 +1958 210 25.93 19.93 24.28 0 706.27 342.78 53213 +1958 211 30.18 24.18 28.53 0.02 882.15 240.07 53064 +1958 212 34.17 28.17 32.52 0.12 1079.54 220.4 52913 +1958 213 33 27 31.35 0 1018.16 301.23 52760 +1958 214 29.59 23.59 27.94 0 855.73 321.34 52604 +1958 215 27.86 21.86 26.21 0 782.06 329.91 52445 +1958 216 21.92 15.92 20.27 0.09 568.47 265.97 52285 +1958 217 20.05 14.05 18.4 0 512.47 360.23 52122 +1958 218 20.86 14.86 19.21 0 536.12 356.69 51958 +1958 219 23.34 17.34 21.69 0 614.39 346.55 51791 +1958 220 23.22 17.22 21.57 0.32 610.39 259.58 51622 +1958 221 22.7 16.7 21.05 0 593.32 347.12 51451 +1958 222 24.71 18.71 23.06 0 661.64 338.08 51279 +1958 223 20.82 14.82 19.17 0.3 534.93 263.76 51105 +1958 224 20.93 14.93 19.28 1.16 538.21 262.69 50929 +1958 225 18.81 12.81 17.16 0.01 477.98 266.92 50751 +1958 226 17.42 11.42 15.77 1.83 441.69 269.06 50572 +1958 227 19.15 13.15 17.5 0.22 487.23 264.32 50392 +1958 228 20.44 14.44 18.79 0 523.74 347.14 50210 +1958 229 21.37 15.37 19.72 0.14 551.49 257.09 50026 +1958 230 24.58 18.58 22.93 0 657.03 329.48 49842 +1958 231 24.87 18.87 23.22 0.06 667.35 245.16 49656 +1958 232 27.09 21.09 25.44 0.82 751.04 236.86 49469 +1958 233 23.8 17.8 22.15 0 629.93 328.51 49280 +1958 234 23.7 17.7 22.05 0.3 626.52 245.64 49091 +1958 235 23.24 17.24 21.59 0 611.06 327.83 48900 +1958 236 21.56 15.56 19.91 0.35 557.3 249.33 48709 +1958 237 21.21 15.21 19.56 0 546.63 331.99 48516 +1958 238 23.29 17.29 21.64 0.02 612.72 242.28 48323 +1958 239 24.13 18.13 22.48 0 641.27 318.4 48128 +1958 240 23.22 17.22 21.57 0 610.39 320.14 47933 +1958 241 20.59 14.59 18.94 0 528.14 327.43 47737 +1958 242 21.81 15.81 20.16 0.55 565.04 241.3 47541 +1958 243 23.16 17.16 21.51 0.02 608.4 236.41 47343 +1958 244 17.13 11.13 15.48 0.1 434.42 248.9 47145 +1958 245 18.56 12.56 16.91 0 471.27 326.21 46947 +1958 246 18.94 12.94 17.29 0 481.5 323.2 46747 +1958 247 16.21 10.21 14.56 0.4 412.03 246.32 46547 +1958 248 15.83 9.83 14.18 0.05 403.08 245.52 46347 +1958 249 23.75 17.75 22.1 0 628.22 302.02 46146 +1958 250 26.66 20.66 25.01 0 734.17 288.73 45945 +1958 251 30.17 24.17 28.52 0 881.7 270.45 45743 +1958 252 26.56 20.56 24.91 0.01 730.29 213.88 45541 +1958 253 26.01 20.01 24.36 0.39 709.28 214.1 45339 +1958 254 21.61 15.61 19.96 0.31 558.84 224.38 45136 +1958 255 18.12 12.12 16.47 0.07 459.66 230.18 44933 +1958 256 16.57 10.57 14.92 0.14 420.67 231.33 44730 +1958 257 17.17 11.17 15.52 0.6 435.41 228.64 44527 +1958 258 15.97 9.97 14.32 1.24 406.36 228.96 44323 +1958 259 13.62 7.62 11.97 0.01 354.21 230.77 44119 +1958 260 15.03 9.03 13.38 0 384.76 302.46 43915 +1958 261 19.42 13.42 17.77 0 494.69 289.63 43711 +1958 262 19.62 13.62 17.97 0.33 500.28 215.08 43507 +1958 263 21.04 15.04 19.39 0 541.5 280.41 43303 +1958 264 19.11 13.11 17.46 0.73 486.14 212.38 43099 +1958 265 18.14 12.14 16.49 0.09 460.18 212.45 42894 +1958 266 17.19 11.19 15.54 0.1 435.91 212.29 42690 +1958 267 18.07 12.07 16.42 0 458.35 278.35 42486 +1958 268 16.84 10.84 15.19 0 427.25 278.63 42282 +1958 269 17.53 11.53 15.88 0 444.47 274.6 42078 +1958 270 15.77 9.77 14.12 0 401.68 275.77 41875 +1958 271 18.26 12.26 16.61 0 463.33 267.74 41671 +1958 272 17.48 11.48 15.83 0 443.2 266.83 41468 +1958 273 15.64 9.64 13.99 0.35 398.66 201.14 41265 +1958 274 8.86 2.86 7.21 0 265.89 276.46 41062 +1958 275 14.09 8.09 12.44 0.32 364.16 199.25 40860 +1958 276 14.05 8.05 12.4 0.69 363.3 197.28 40658 +1958 277 11.82 5.82 10.17 0 318.25 264.02 40456 +1958 278 15.21 9.21 13.56 0 388.82 255.43 40255 +1958 279 16.64 10.64 14.99 0.03 422.37 187.42 40054 +1958 280 18.61 12.61 16.96 0.03 472.61 182.35 39854 +1958 281 15.11 9.11 13.46 0 386.56 247.49 39654 +1958 282 18.97 12.97 17.32 0 482.32 237.03 39455 +1958 283 19.23 13.23 17.58 0 489.43 233.72 39256 +1958 284 14.62 8.62 12.97 0.16 375.66 179.88 39058 +1958 285 14.03 8.03 12.38 0.02 362.88 178.65 38861 +1958 286 9.75 3.75 8.1 0 280.79 241.57 38664 +1958 287 10.99 4.99 9.34 1.56 302.75 177.76 38468 +1958 288 12.39 6.39 10.74 0.39 329.28 174.2 38273 +1958 289 10.86 4.86 9.21 0.02 300.38 173.8 38079 +1958 290 11.85 5.85 10.2 0 318.82 227.53 37885 +1958 291 15.93 9.93 14.28 0 405.42 218.53 37693 +1958 292 15.33 9.33 13.68 0 391.55 216.92 37501 +1958 293 15.59 9.59 13.94 0.89 397.51 160.35 37311 +1958 294 15.04 9.04 13.39 0.42 384.99 158.9 37121 +1958 295 16.58 10.58 14.93 0.32 420.91 154.88 36933 +1958 296 13.82 7.82 12.17 1.08 358.42 156.29 36745 +1958 297 14.05 8.05 12.4 0.27 363.3 154.02 36560 +1958 298 11.75 5.75 10.1 0.1 316.91 154.45 36375 +1958 299 11.49 5.49 9.84 0.19 312.01 152.61 36191 +1958 300 12.19 6.19 10.54 0.31 325.37 149.96 36009 +1958 301 13.62 7.62 11.97 0 354.21 195.55 35829 +1958 302 14.17 8.17 12.52 0.72 365.87 144.16 35650 +1958 303 12.33 6.33 10.68 0 328.11 192.12 35472 +1958 304 16.46 10.46 14.81 0 418.01 183.85 35296 +1958 305 10.93 4.93 9.28 0 301.65 188.62 35122 +1958 306 9.73 3.73 8.08 0.04 280.45 140.76 34950 +1958 307 10.57 4.57 8.92 0 295.15 184.29 34779 +1958 308 10.44 4.44 8.79 0.5 292.83 136.38 34610 +1958 309 8.41 2.41 6.76 0.34 258.62 136.16 34444 +1958 310 8.3 2.3 6.65 0.24 256.87 134.41 34279 +1958 311 8.57 2.57 6.92 0.62 261.19 132.59 34116 +1958 312 6.95 0.95 5.3 0.32 236.19 131.66 33956 +1958 313 9.73 3.73 8.08 1.01 280.45 128.2 33797 +1958 314 8.33 2.33 6.68 0.99 257.34 127.72 33641 +1958 315 7.46 1.46 5.81 0.46 243.83 126.38 33488 +1958 316 8.19 2.19 6.54 0 255.13 165.7 33337 +1958 317 5.93 -0.07 4.28 0 221.53 165.31 33188 +1958 318 11.03 5.03 9.38 0 303.48 158.54 33042 +1958 319 12.09 6.09 10.44 0 323.43 155.77 32899 +1958 320 7.25 1.25 5.6 0.04 240.65 118.79 32758 +1958 321 7.55 1.55 5.9 0.47 245.19 117.03 32620 +1958 322 3.56 -2.44 1.91 0.33 190.45 117.75 32486 +1958 323 4.21 -1.79 2.56 0.28 198.57 116.23 32354 +1958 324 2.18 -3.82 0.53 0.11 174.15 115.57 32225 +1958 325 5.64 -0.36 3.99 0 217.5 150.24 32100 +1958 326 6.95 0.95 5.3 0 236.19 147.86 31977 +1958 327 8.91 2.91 7.26 0.88 266.71 108.37 31858 +1958 328 7.62 1.62 5.97 0.24 246.26 107.66 31743 +1958 329 11 5 9.35 0.01 302.93 104.42 31631 +1958 330 12.29 6.29 10.64 0 327.32 136.57 31522 +1958 331 10.79 4.79 9.14 0 299.11 136.71 31417 +1958 332 10.78 4.78 9.13 0 298.93 135.11 31316 +1958 333 9.47 3.47 7.82 0.04 276.03 101.38 31218 +1958 334 9.97 3.97 8.32 0 284.59 133.67 31125 +1958 335 6.05 0.05 4.4 0 223.21 135.43 31035 +1958 336 4.78 -1.22 3.13 0.3 205.94 101.37 30949 +1958 337 7.04 1.04 5.39 0 237.52 132.04 30867 +1958 338 9.65 3.65 8 0 279.08 129.16 30790 +1958 339 8.74 2.74 7.09 0 263.94 129.1 30716 +1958 340 4.23 -1.77 2.58 0 198.83 131.35 30647 +1958 341 6.2 0.2 4.55 0.15 225.33 96.93 30582 +1958 342 0.2 -5.8 -1.45 0.47 152.86 98.75 30521 +1958 343 1.56 -4.44 -0.09 0 167.22 130.22 30465 +1958 344 2.62 -3.38 0.97 0 179.21 128.57 30413 +1958 345 5.22 -0.78 3.57 0 211.79 126.71 30366 +1958 346 10.57 4.57 8.92 0 295.15 122.39 30323 +1958 347 9.52 3.52 7.87 0 276.88 122.64 30284 +1958 348 10.24 4.24 8.59 0 289.3 121.73 30251 +1958 349 7.64 1.64 5.99 0.28 246.57 92.48 30221 +1958 350 4.25 -1.75 2.6 0 199.08 125.06 30197 +1958 351 2.69 -3.31 1.04 0 180.03 125.66 30177 +1958 352 0.48 -5.52 -1.17 0 155.73 126.59 30162 +1958 353 1.31 -4.69 -0.34 0 164.5 126.16 30151 +1958 354 3.56 -2.44 1.91 0.39 190.45 93.77 30145 +1958 355 5.66 -0.34 4.01 2.15 217.78 92.88 30144 +1958 356 4.46 -1.54 2.81 0.1 201.78 93.42 30147 +1958 357 4.7 -1.3 3.05 0.2 204.89 93.36 30156 +1958 358 7.73 1.73 6.08 0 247.95 122.67 30169 +1958 359 11.08 5.08 9.43 0 304.4 120.22 30186 +1958 360 9.39 3.39 7.74 0 274.68 121.94 30208 +1958 361 3.2 -2.8 1.55 0.13 186.07 94.65 30235 +1958 362 3.25 -2.75 1.6 0 186.68 126.61 30267 +1958 363 5.75 -0.25 4.1 0 219.02 125.79 30303 +1958 364 8.49 2.49 6.84 0.05 259.9 93.25 30343 +1958 365 8.55 2.55 6.9 0 260.86 124.85 30388 +1959 1 10.11 4.11 8.46 0 287.02 124.52 30438 +1959 2 8.82 2.82 7.17 0 265.24 126.25 30492 +1959 3 6.07 0.07 4.42 0.02 223.49 96.82 30551 +1959 4 1.72 -4.28 0.07 0 168.99 132.42 30614 +1959 5 -2.57 -8.57 -4.22 0 126.88 134.87 30681 +1959 6 -1.89 -7.89 -3.54 0 132.87 135.52 30752 +1959 7 -1.05 -7.05 -2.7 0 140.62 136 30828 +1959 8 1.67 -4.33 0.02 0 168.43 136.28 30907 +1959 9 5.34 -0.66 3.69 0 213.41 135.51 30991 +1959 10 4.78 -1.22 3.13 0 205.94 137.15 31079 +1959 11 6.45 0.45 4.8 0 228.9 137.06 31171 +1959 12 3.07 -2.93 1.42 0.08 184.52 105.1 31266 +1959 13 2.88 -3.12 1.23 0.46 182.26 106.39 31366 +1959 14 4.56 -1.44 2.91 0.21 203.07 106.77 31469 +1959 15 2.56 -3.44 0.91 0 178.51 144.96 31575 +1959 16 1.3 -4.7 -0.35 0 164.39 146.91 31686 +1959 17 0.03 -5.97 -1.62 0 151.15 149.22 31800 +1959 18 0.31 -5.69 -1.34 0 153.98 151 31917 +1959 19 2.13 -3.87 0.48 0 173.58 152.02 32038 +1959 20 2.55 -3.45 0.9 0 178.39 153.38 32161 +1959 21 0.13 -5.87 -1.52 0 152.15 156.65 32289 +1959 22 0.79 -5.21 -0.86 0 158.96 158.09 32419 +1959 23 3.33 -2.67 1.68 0 187.64 158.46 32552 +1959 24 2.23 -3.77 0.58 0 174.72 161.18 32688 +1959 25 7.69 1.69 6.04 0 247.34 159.32 32827 +1959 26 7.25 1.25 5.6 0 240.65 161.58 32969 +1959 27 8.97 2.97 7.32 0 267.7 162.12 33114 +1959 28 5.18 -0.82 3.53 0 211.25 167.35 33261 +1959 29 3.37 -2.63 1.72 0 188.13 170.95 33411 +1959 30 0.53 -5.47 -1.12 0 156.25 174.86 33564 +1959 31 1.92 -4.08 0.27 0 171.21 176.47 33718 +1959 32 3.24 -2.76 1.59 0 186.56 177.78 33875 +1959 33 0.98 -5.02 -0.67 0 160.96 181.79 34035 +1959 34 2.97 -3.03 1.32 0 183.33 182.8 34196 +1959 35 7.64 1.64 5.99 0 246.57 181.37 34360 +1959 36 6.74 0.74 5.09 0 233.1 184.65 34526 +1959 37 4.96 -1.04 3.31 0 208.32 188.49 34694 +1959 38 4.49 -1.51 2.84 0 202.16 191.58 34863 +1959 39 3.05 -2.95 1.4 0 184.28 195.23 35035 +1959 40 6.59 0.59 4.94 0 230.92 195.1 35208 +1959 41 4.76 -1.24 3.11 0 205.68 199.22 35383 +1959 42 1.02 -4.98 -0.63 0 161.39 204.38 35560 +1959 43 2.36 -3.64 0.71 0 176.2 206.24 35738 +1959 44 -1.12 -7.12 -2.77 0 139.96 210.95 35918 +1959 45 -0.88 -6.88 -2.53 0 142.23 213.48 36099 +1959 46 4.26 -1.74 2.61 0 199.21 212.76 36282 +1959 47 3.84 -2.16 2.19 0 193.91 215.92 36466 +1959 48 1.75 -4.25 0.1 0 169.32 220.26 36652 +1959 49 4.21 -1.79 2.56 0 198.57 221.23 36838 +1959 50 1.73 -4.27 0.08 0 169.1 225.77 37026 +1959 51 0.2 -5.8 -1.45 0.03 152.86 172.33 37215 +1959 52 -1.6 -7.6 -3.25 0 135.5 233.72 37405 +1959 53 -5 -11 -6.65 0 107.32 238.45 37596 +1959 54 0.98 -5.02 -0.67 0 160.96 237.91 37788 +1959 55 2.92 -3.08 1.27 0 182.73 239.51 37981 +1959 56 3.53 -2.47 1.88 0 190.08 241.73 38175 +1959 57 6.11 0.11 4.46 0.1 224.06 181.73 38370 +1959 58 3.37 -2.63 1.72 0 188.13 247.72 38565 +1959 59 8.25 2.25 6.6 0 256.08 245.65 38761 +1959 60 13.58 7.58 11.93 0 353.38 241.22 38958 +1959 61 15.15 9.15 13.5 0 387.46 241.41 39156 +1959 62 14.86 8.86 13.21 0 380.96 244.61 39355 +1959 63 10.53 4.53 8.88 0 294.44 254.3 39553 +1959 64 8.11 2.11 6.46 0.26 253.87 195.19 39753 +1959 65 7.98 1.98 6.33 0.14 251.83 197.47 39953 +1959 66 8.27 2.27 6.62 0 256.39 265.67 40154 +1959 67 8.28 2.28 6.63 0 256.55 268.55 40355 +1959 68 10.38 4.38 8.73 0 291.77 268.64 40556 +1959 69 15.6 9.6 13.95 0 397.74 262.51 40758 +1959 70 16.34 10.34 14.69 0.3 415.13 197.83 40960 +1959 71 18.36 12.36 16.71 0.37 465.96 196.62 41163 +1959 72 16.28 10.28 14.63 0.3 413.7 202.07 41366 +1959 73 17.53 11.53 15.88 0 444.47 269.29 41569 +1959 74 14.52 8.52 12.87 0 373.46 278.15 41772 +1959 75 15.86 9.86 14.21 0 403.78 278.15 41976 +1959 76 14.66 8.66 13.01 0 376.54 283.1 42179 +1959 77 11.55 5.55 9.9 0.02 313.13 218.37 42383 +1959 78 8.82 2.82 7.17 0.26 265.24 223.41 42587 +1959 79 7.91 1.91 6.26 0.29 250.74 226.37 42791 +1959 80 10.14 4.14 8.49 0 287.55 301.22 42996 +1959 81 9.6 3.6 7.95 0.03 278.23 228.45 43200 +1959 82 6.22 0.22 4.57 0.34 225.61 233.81 43404 +1959 83 4.25 -1.75 2.6 0 199.08 316.48 43608 +1959 84 2.36 -3.64 0.71 0.15 176.2 240.71 43812 +1959 85 4.87 -1.13 3.22 0 207.13 320.91 44016 +1959 86 5.97 -0.03 4.32 0 222.09 322.07 44220 +1959 87 7.47 1.47 5.82 0 243.98 322.72 44424 +1959 88 11.52 5.52 9.87 0 312.57 318.91 44627 +1959 89 9.85 3.85 8.2 0 282.51 323.92 44831 +1959 90 8.85 2.85 7.2 0.07 265.73 245.86 45034 +1959 91 13.72 7.72 12.07 0.67 356.31 241.22 45237 +1959 92 11.82 5.82 10.17 0 318.25 327.46 45439 +1959 93 9.77 3.77 8.12 0.09 281.14 249.85 45642 +1959 94 11.55 5.55 9.9 0.65 313.13 249.21 45843 +1959 95 7.74 1.74 6.09 1.48 248.11 255.38 46045 +1959 96 5.36 -0.64 3.71 0.36 213.68 259.34 46246 +1959 97 5.26 -0.74 3.61 0.27 212.33 261 46446 +1959 98 9.77 3.77 8.12 0 281.14 343.6 46647 +1959 99 8.44 2.44 6.79 0.84 259.1 260.78 46846 +1959 100 7.61 1.61 5.96 0.2 246.11 263.18 47045 +1959 101 10.49 4.49 8.84 0 293.72 348.31 47243 +1959 102 16.27 10.27 14.62 0 413.46 338.22 47441 +1959 103 16.41 10.41 14.76 0.04 416.81 254.75 47638 +1959 104 11.55 5.55 9.9 0.17 313.13 264 47834 +1959 105 16.73 10.73 15.08 0 424.56 342.4 48030 +1959 106 19.27 13.27 17.62 0 490.54 337 48225 +1959 107 19.63 13.63 17.98 0 500.56 337.52 48419 +1959 108 14.79 8.79 13.14 0 379.41 352.09 48612 +1959 109 16.98 10.98 15.33 0.03 430.7 261.21 48804 +1959 110 15.75 9.75 14.1 1.88 401.21 264.59 48995 +1959 111 17.32 11.32 15.67 0.04 439.17 262.7 49185 +1959 112 19.59 13.59 17.94 0.39 499.44 258.89 49374 +1959 113 15.77 9.77 14.12 0 401.68 357.09 49561 +1959 114 20.25 14.25 18.6 0 518.22 345.83 49748 +1959 115 20.43 14.43 18.78 0 523.45 346.62 49933 +1959 116 18.28 12.28 16.63 0 463.85 354.42 50117 +1959 117 16.96 10.96 15.31 0 430.2 359.39 50300 +1959 118 13.78 7.78 12.13 0 357.57 368.5 50481 +1959 119 13.79 7.79 12.14 0 357.78 369.67 50661 +1959 120 13.78 7.78 12.13 0 357.57 370.87 50840 +1959 121 19.43 13.43 17.78 0 494.97 356.91 51016 +1959 122 16.28 10.28 14.63 0.09 413.7 275.34 51191 +1959 123 15.24 9.24 13.59 0.02 389.5 278.09 51365 +1959 124 15.08 9.08 13.43 0.19 385.89 279.19 51536 +1959 125 17.64 11.64 15.99 0 447.27 366.46 51706 +1959 126 16.25 10.25 14.6 0 412.98 371.25 51874 +1959 127 20.68 14.68 19.03 0 530.79 358.8 52039 +1959 128 18.17 12.17 16.52 0.17 460.97 275.82 52203 +1959 129 12.27 6.27 10.62 0.02 326.93 287.52 52365 +1959 130 15.49 9.49 13.84 0 395.2 376.74 52524 +1959 131 15.17 9.17 13.52 0.23 387.92 283.75 52681 +1959 132 17.54 11.54 15.89 0.16 444.72 279.61 52836 +1959 133 17.06 11.06 15.41 0 432.68 374.87 52989 +1959 134 20.1 14.1 18.45 0 513.9 366.27 53138 +1959 135 20.99 14.99 19.34 0 540 363.91 53286 +1959 136 20.23 14.23 18.58 0 517.65 367.14 53430 +1959 137 21.23 15.23 19.58 0 547.23 364.36 53572 +1959 138 17.04 11.04 15.39 0 432.18 378.27 53711 +1959 139 15.91 9.91 14.26 0 404.95 382.03 53848 +1959 140 14.68 8.68 13.03 1.12 376.98 289.23 53981 +1959 141 12.33 6.33 10.68 2.33 328.11 293.6 54111 +1959 142 10.86 4.86 9.21 0.72 300.38 296.23 54238 +1959 143 14.43 8.43 12.78 0.72 371.5 290.81 54362 +1959 144 11.25 5.25 9.6 1.39 307.53 296.43 54483 +1959 145 17.83 11.83 16.18 0.28 452.14 284.68 54600 +1959 146 20.66 14.66 19.01 1.41 530.2 278.12 54714 +1959 147 20.61 14.61 18.96 0 528.72 371.47 54824 +1959 148 22.6 16.6 20.95 0 590.08 364.51 54931 +1959 149 18.95 12.95 17.3 0 481.77 377.68 55034 +1959 150 19.65 13.65 18 0.03 501.12 281.81 55134 +1959 151 22.37 16.37 20.72 0.29 582.7 274.81 55229 +1959 152 26 20 24.35 1.45 708.9 263.26 55321 +1959 153 25.9 19.9 24.25 1.05 705.14 263.79 55409 +1959 154 23.71 17.71 22.06 0.48 626.86 271.27 55492 +1959 155 22.61 16.61 20.96 0.76 590.41 274.73 55572 +1959 156 23.14 17.14 21.49 0.56 607.74 273.39 55648 +1959 157 19.25 13.25 17.6 0.48 489.98 284.08 55719 +1959 158 17.63 11.63 15.98 0 447.01 383.97 55786 +1959 159 20.54 14.54 18.89 0.67 526.67 281.14 55849 +1959 160 21.43 15.43 19.78 0.92 553.32 278.89 55908 +1959 161 22.94 16.94 21.29 0.96 601.15 274.6 55962 +1959 162 18.24 12.24 16.59 0.17 462.8 287.02 56011 +1959 163 11.79 5.79 10.14 0.51 317.68 299.5 56056 +1959 164 13.74 7.74 12.09 0.29 356.73 296.29 56097 +1959 165 17.59 11.59 15.94 0 446 385 56133 +1959 166 13.49 7.49 11.84 0.29 351.51 296.86 56165 +1959 167 13.92 7.92 12.27 0 360.53 394.76 56192 +1959 168 15.69 9.69 14.04 0 399.82 390.41 56214 +1959 169 17.84 11.84 16.19 0.03 452.4 288.28 56231 +1959 170 19.99 13.99 18.34 0 510.75 377.52 56244 +1959 171 23.12 17.12 21.47 0.4 607.08 274.49 56252 +1959 172 17.56 11.56 15.91 0.03 445.23 288.94 56256 +1959 173 21.04 15.04 19.39 1.4 541.5 280.42 56255 +1959 174 23.92 17.92 22.27 1.71 634.03 271.93 56249 +1959 175 25.42 19.42 23.77 0.68 687.31 266.96 56238 +1959 176 24.92 18.92 23.27 0.57 669.14 268.63 56223 +1959 177 22 16 20.35 0.52 570.98 277.57 56203 +1959 178 20.23 14.23 18.58 0.2 517.65 282.38 56179 +1959 179 20.29 14.29 18.64 0.43 519.38 282.15 56150 +1959 180 22.46 16.46 20.81 0.05 585.58 276.1 56116 +1959 181 22.02 16.02 20.37 1.08 571.61 277.32 56078 +1959 182 28.92 22.92 27.27 0.7 826.53 253.35 56035 +1959 183 28.29 22.29 26.64 2.4 799.85 255.79 55987 +1959 184 24.36 18.36 22.71 0.01 649.28 269.86 55935 +1959 185 23.97 17.97 22.32 0 635.75 361.4 55879 +1959 186 22.22 16.22 20.57 0.06 577.92 276.14 55818 +1959 187 18.92 12.92 17.27 0 480.96 379.53 55753 +1959 188 20.07 14.07 18.42 0 513.04 375.49 55684 +1959 189 17.55 11.55 15.9 0.05 444.98 287.44 55611 +1959 190 20.73 14.73 19.08 0 532.26 372.66 55533 +1959 191 16.05 10.05 14.4 0.46 408.24 290.11 55451 +1959 192 21.63 15.63 19.98 0.38 559.46 276.64 55366 +1959 193 20.54 14.54 18.89 2.08 526.67 279.36 55276 +1959 194 22.03 16.03 20.38 0.14 571.92 275.15 55182 +1959 195 22.62 16.62 20.97 0.04 590.73 273.25 55085 +1959 196 26.07 20.07 24.42 0.02 711.55 261.85 54984 +1959 197 25.48 19.48 23.83 1.25 689.52 263.57 54879 +1959 198 27.71 21.71 26.06 0.08 775.93 255.17 54770 +1959 199 29.52 23.52 27.87 0.13 852.64 247.62 54658 +1959 200 32.12 26.12 30.47 0 973.94 314.09 54542 +1959 201 32.09 26.09 30.44 0.01 972.46 235.4 54423 +1959 202 29.51 23.51 27.86 0.03 852.2 246.67 54301 +1959 203 21.97 15.97 20.32 0 570.04 363.28 54176 +1959 204 21.27 15.27 19.62 0.7 548.44 274.01 54047 +1959 205 23 17 21.35 0.09 603.12 268.74 53915 +1959 206 21.9 15.9 20.25 0 567.85 361.97 53780 +1959 207 19.07 13.07 17.42 1.08 485.04 278.25 53643 +1959 208 16.95 10.95 15.3 0.74 429.96 282.46 53502 +1959 209 22.96 16.96 21.31 0 601.8 356 53359 +1959 210 23.44 17.44 21.79 0.28 617.74 265.12 53213 +1959 211 21.31 15.31 19.66 0.43 549.66 270.59 53064 +1959 212 17.25 11.25 15.6 0.28 437.41 279.66 52913 +1959 213 18.26 12.26 16.61 0.24 463.33 276.88 52760 +1959 214 16.36 10.36 14.71 0 415.61 373.78 52604 +1959 215 19.19 13.19 17.54 0 488.33 364.9 52445 +1959 216 23.72 17.72 22.07 0 627.2 347.71 52285 +1959 217 18.52 12.52 16.87 0.14 470.21 273.77 52122 +1959 218 20.63 14.63 18.98 0 529.31 357.48 51958 +1959 219 19.83 13.83 18.18 0 506.2 359.08 51791 +1959 220 20.15 14.15 18.5 0 515.34 357.1 51622 +1959 221 18.01 12.01 16.36 0.27 456.79 272.02 51451 +1959 222 16.84 10.84 15.19 0.1 427.25 273.67 51279 +1959 223 19.12 13.12 17.47 0.63 486.41 267.88 51105 +1959 224 17.98 11.98 16.33 0 456.02 359.49 50929 +1959 225 22.56 16.56 20.91 0.02 588.79 257.5 50751 +1959 226 20.87 14.87 19.22 0.33 536.42 261.14 50572 +1959 227 22.64 16.64 20.99 0 591.38 340.67 50392 +1959 228 23.75 17.75 22.1 0 628.22 335.24 50210 +1959 229 22.84 16.84 21.19 0.41 597.88 253.14 50026 +1959 230 21.52 15.52 19.87 0.73 556.07 255.76 49842 +1959 231 22.76 16.76 21.11 0.03 595.27 251.36 49656 +1959 232 21.95 15.95 20.3 0 569.41 336.74 49469 +1959 233 23.43 17.43 21.78 0 617.4 329.93 49280 +1959 234 24.12 18.12 22.47 0 640.93 325.89 49091 +1959 235 24.92 18.92 23.27 0 669.14 321.24 48900 +1959 236 22.66 16.66 21.01 1.05 592.02 246.44 48709 +1959 237 22.08 16.08 20.43 0 573.49 329.03 48516 +1959 238 24.84 18.84 23.19 0 666.28 317.03 48323 +1959 239 24.49 18.49 22.84 0 653.85 316.99 48128 +1959 240 21.26 15.26 19.61 0 548.14 326.96 47933 +1959 241 23.33 17.33 21.68 0.24 614.06 238.55 47737 +1959 242 21.2 15.2 19.55 0.46 546.32 242.82 47541 +1959 243 23.96 17.96 22.31 0 635.41 312.25 47343 +1959 244 19.27 13.27 17.62 0 490.54 326.04 47145 +1959 245 18.37 12.37 16.72 0 466.23 326.74 46947 +1959 246 18.51 12.51 16.86 0 469.94 324.39 46747 +1959 247 20.21 14.21 18.56 0 517.07 317.66 46547 +1959 248 19.97 13.97 18.32 0 510.18 316.46 46347 +1959 249 20.24 14.24 18.59 0 517.94 313.62 46146 +1959 250 16.01 10.01 14.36 0.17 407.3 242.16 45945 +1959 251 13.09 7.09 11.44 0.27 343.28 245.22 45743 +1959 252 11.86 5.86 10.21 0 319.01 327.04 45541 +1959 253 11.54 5.54 9.89 0 312.94 325.43 45339 +1959 254 12.27 6.27 10.62 0 326.93 321.93 45136 +1959 255 12.39 6.39 10.74 0.01 329.28 239.55 44933 +1959 256 17.56 11.56 15.91 0 445.23 306.06 44730 +1959 257 19.82 13.82 18.17 0 505.92 297.97 44527 +1959 258 19.35 13.35 17.7 0 492.75 296.96 44323 +1959 259 20.01 14.01 18.36 0 511.32 292.75 44119 +1959 260 21.42 15.42 19.77 0.34 553.01 214.75 43915 +1959 261 19.78 13.78 18.13 0.4 504.78 216.49 43711 +1959 262 23.22 17.22 21.57 0.01 610.39 207.03 43507 +1959 263 20.91 14.91 19.26 0.09 537.61 210.59 43303 +1959 264 18.02 12.02 16.37 0.14 457.05 214.42 43099 +1959 265 15.28 9.28 13.63 0.01 390.41 217.23 42894 +1959 266 14.42 8.42 12.77 0.4 371.28 216.65 42690 +1959 267 14.55 8.55 12.9 0 374.12 285.92 42486 +1959 268 13.42 7.42 11.77 0 350.05 285.44 42282 +1959 269 15.92 9.92 14.27 0 405.18 278.09 42078 +1959 270 15.61 9.61 13.96 0 397.97 276.1 41875 +1959 271 14.76 8.76 13.11 0 378.75 275.15 41671 +1959 272 16.26 10.26 14.61 0 413.22 269.45 41468 +1959 273 18.22 12.22 16.57 0 462.28 262.67 41265 +1959 274 15.75 9.75 14.1 0 401.21 265.31 41062 +1959 275 16.21 10.21 14.56 0 412.03 261.65 40860 +1959 276 13.99 7.99 12.34 0 362.02 263.14 40658 +1959 277 12.44 6.44 10.79 0 330.27 263.06 40456 +1959 278 17.66 11.66 16.01 0.1 447.78 187.9 40255 +1959 279 17.86 11.86 16.21 0 452.91 247.35 40054 +1959 280 19.6 13.6 17.95 0 499.72 240.86 39854 +1959 281 18.49 12.49 16.84 0 469.41 240.75 39654 +1959 282 18.63 12.63 16.98 0 473.14 237.79 39455 +1959 283 12.03 6.03 10.38 0 322.28 246.97 39256 +1959 284 9.12 3.12 7.47 0 270.17 247.83 39058 +1959 285 11.82 5.82 10.17 0.28 318.25 181.19 38861 +1959 286 10.69 4.69 9.04 0.03 297.3 180.27 38664 +1959 287 9.46 3.46 7.81 0 275.86 238.96 38468 +1959 288 10.17 4.17 8.52 0.17 288.07 176.45 38273 +1959 289 7.09 1.09 5.44 0 238.26 236.1 38079 +1959 290 7.15 1.15 5.5 0 239.16 233.13 37885 +1959 291 7.13 1.13 5.48 0 238.86 230.4 37693 +1959 292 7.65 1.65 6 0 246.72 227.13 37501 +1959 293 11.23 5.23 9.58 0 307.16 220.22 37311 +1959 294 14.42 8.42 12.77 0 371.28 212.84 37121 +1959 295 13.8 7.8 12.15 0 357.99 210.98 36933 +1959 296 11.71 5.71 10.06 0 316.16 211.29 36745 +1959 297 11.43 5.43 9.78 0 310.88 208.93 36560 +1959 298 10.61 4.61 8.96 0 295.87 207.32 36375 +1959 299 11.28 5.28 9.63 0 308.09 203.74 36191 +1959 300 10.92 4.92 9.27 0 301.47 201.51 36009 +1959 301 5.34 -0.66 3.69 0.35 213.41 153.39 35829 +1959 302 9.03 3.03 7.38 0 268.69 198.46 35650 +1959 303 9.77 3.77 8.12 0 281.14 195.1 35472 +1959 304 13.85 7.85 12.2 0.02 359.05 140.78 35296 +1959 305 8.24 2.24 6.59 0.03 255.92 143.57 35122 +1959 306 13.87 7.87 12.22 0 359.47 182.77 34950 +1959 307 10.92 4.92 9.27 0 301.47 183.9 34779 +1959 308 9.97 3.97 8.32 0.25 284.59 136.75 34610 +1959 309 9.79 3.79 8.14 0.67 281.48 135.16 34444 +1959 310 11.13 5.13 9.48 0 305.31 176.37 34279 +1959 311 12.38 6.38 10.73 0 329.09 172.8 34116 +1959 312 14.35 8.35 12.7 0.01 369.76 125.83 33956 +1959 313 13.81 7.81 12.16 0.35 358.21 124.8 33797 +1959 314 13.37 7.37 11.72 0.02 349.02 123.78 33641 +1959 315 14.04 8.04 12.39 0.1 363.09 121.3 33488 +1959 316 9.64 3.64 7.99 0.17 278.91 123.29 33337 +1959 317 4.99 -1.01 3.34 0.32 208.72 124.49 33188 +1959 318 3.5 -2.5 1.85 0 189.71 164.62 33042 +1959 319 5.1 -0.9 3.45 0 210.18 161.85 32899 +1959 320 1.96 -4.04 0.31 0.15 171.66 121.44 32758 +1959 321 -2.78 -8.78 -4.43 0 125.07 162.02 32620 +1959 322 1.55 -4.45 -0.1 0 167.11 158.15 32486 +1959 323 4.45 -1.55 2.8 0 201.65 154.82 32354 +1959 324 4.71 -1.29 3.06 0 205.02 152.59 32225 +1959 325 3.27 -2.73 1.62 0 186.92 151.74 32100 +1959 326 7.07 1.07 5.42 0 237.97 147.77 31977 +1959 327 11.05 5.05 9.4 0 303.84 142.59 31858 +1959 328 7.15 1.15 5.5 0 239.16 143.9 31743 +1959 329 5.37 -0.63 3.72 0.53 213.82 107.73 31631 +1959 330 6.96 0.96 5.31 0.03 236.34 105.83 31522 +1959 331 7.73 1.73 6.08 0 247.95 139.24 31417 +1959 332 7.93 1.93 6.28 0.45 251.05 103.09 31316 +1959 333 7.17 1.17 5.52 0 239.46 136.93 31218 +1959 334 11.23 5.23 9.58 0 307.16 132.57 31125 +1959 335 11.5 5.5 9.85 0.32 312.19 98.38 31035 +1959 336 9.48 3.48 7.83 0.13 276.2 98.9 30949 +1959 337 10.06 4.06 8.41 0 286.15 129.75 30867 +1959 338 9.06 3.06 7.41 0 269.18 129.63 30790 +1959 339 10.94 4.94 9.29 0 301.83 127.31 30716 +1959 340 8.27 2.27 6.62 0 256.39 128.73 30647 +1959 341 10.67 4.67 9.02 0.08 296.95 94.44 30582 +1959 342 6 0 4.35 1.81 222.51 96.46 30521 +1959 343 7.26 1.26 5.61 1.65 240.81 95.22 30465 +1959 344 5.77 -0.23 4.12 0.25 219.3 95.11 30413 +1959 345 6.63 0.63 4.98 0 231.5 125.84 30366 +1959 346 6.52 0.52 4.87 0.08 229.91 94.02 30323 +1959 347 6.63 0.63 4.98 0.36 231.5 93.52 30284 +1959 348 1.27 -4.73 -0.38 0 164.07 127.28 30251 +1959 349 0.02 -5.98 -1.63 0.34 151.05 95.58 30221 +1959 350 -1.09 -7.09 -2.74 0 140.24 127.54 30197 +1959 351 1.5 -4.5 -0.15 0 166.57 126.23 30177 +1959 352 5.07 -0.93 3.42 0 209.78 124.29 30162 +1959 353 4.87 -1.13 3.22 0 207.13 124.34 30151 +1959 354 6.47 0.47 4.82 0.06 229.19 92.5 30145 +1959 355 2.31 -3.69 0.66 3.83 175.63 94.24 30144 +1959 356 3 -3 1.35 1.24 183.68 94 30147 +1959 357 7.38 1.38 5.73 0.08 242.61 92.12 30156 +1959 358 2.73 -3.27 1.08 0 180.49 125.62 30169 +1959 359 6.82 0.82 5.17 0 234.27 123.4 30186 +1959 360 8.68 2.68 7.03 0.01 262.96 91.85 30208 +1959 361 7.14 1.14 5.49 0 239.01 123.88 30235 +1959 362 9.76 3.76 8.11 0.03 280.97 91.81 30267 +1959 363 4.56 -1.44 2.91 0.16 203.07 94.87 30303 +1959 364 6.49 0.49 4.84 0.04 229.48 94.28 30343 +1959 365 4.26 -1.74 2.61 0.42 199.21 95.71 30388 +1960 1 0.56 -5.44 -1.09 0.02 156.56 97.76 30438 +1960 2 -1.14 -7.14 -2.79 0.14 139.77 142.58 30492 +1960 3 -3.07 -9.07 -4.72 0 122.62 177.11 30551 +1960 4 -4.9 -10.9 -6.55 0 108.07 178.54 30614 +1960 5 -3.14 -9.14 -4.79 0 122.03 178.53 30681 +1960 6 -1.9 -7.9 -3.55 0.2 132.78 145.63 30752 +1960 7 1.89 -4.11 0.24 0 170.88 178.31 30828 +1960 8 4.28 -1.72 2.63 0 199.47 177.85 30907 +1960 9 3 -3 1.35 0 183.68 136.86 30991 +1960 10 0.17 -5.83 -1.48 0 152.56 139.56 31079 +1960 11 -0.53 -6.53 -2.18 0 145.6 140.86 31171 +1960 12 1.97 -4.03 0.32 0.32 171.77 105.53 31266 +1960 13 3.18 -2.82 1.53 0.09 185.83 106.27 31366 +1960 14 -0.63 -6.63 -2.28 0 144.63 145.06 31469 +1960 15 3.48 -2.52 1.83 0 189.47 144.45 31575 +1960 16 4.29 -1.71 2.64 0 199.59 145.25 31686 +1960 17 2.61 -3.39 0.96 0 179.09 147.91 31800 +1960 18 5.16 -0.84 3.51 0 210.98 148.28 31917 +1960 19 -1.08 -7.08 -2.73 0.05 140.33 156.53 32038 +1960 20 -1.35 -7.35 -3 0.05 137.81 157.82 32161 +1960 21 -0.68 -6.68 -2.33 0 144.15 198.21 32289 +1960 22 -0.9 -6.9 -2.55 1.9 142.04 165.81 32419 +1960 23 3.42 -2.58 1.77 0 188.74 204.43 32552 +1960 24 0.21 -5.79 -1.44 0 152.96 208.06 32688 +1960 25 1.47 -4.53 -0.18 0 166.24 208.93 32827 +1960 26 6.31 0.31 4.66 0 226.89 206.78 32969 +1960 27 5.05 -0.95 3.4 0 209.51 208.9 33114 +1960 28 2.9 -3.1 1.25 0.15 182.5 169.75 33261 +1960 29 2.84 -3.16 1.19 0.41 181.79 171.04 33411 +1960 30 8.32 2.32 6.67 0.03 257.19 168.46 33564 +1960 31 9.55 3.55 7.9 0 277.38 210.69 33718 +1960 32 8.46 2.46 6.81 0.36 259.42 130.31 33875 +1960 33 4.95 -1.05 3.3 0 208.18 179.22 34035 +1960 34 4.08 -1.92 2.43 0 196.93 182.05 34196 +1960 35 2.84 -3.16 1.19 0.35 181.79 138.78 34360 +1960 36 -1.67 -7.67 -3.32 0 134.87 190.12 34526 +1960 37 -0.21 -6.21 -1.86 0 148.75 191.82 34694 +1960 38 1.73 -4.27 0.08 0 169.1 193.46 34863 +1960 39 0.06 -5.94 -1.59 0 151.45 197.08 35035 +1960 40 1.27 -4.73 -0.38 0 164.07 199.01 35208 +1960 41 4.06 -1.94 2.41 1.15 196.67 149.82 35383 +1960 42 0.82 -5.18 -0.83 0 159.27 204.51 35560 +1960 43 6.28 0.28 4.63 0 226.47 203.21 35738 +1960 44 0.09 -5.91 -1.56 0 151.75 210.27 35918 +1960 45 -4.83 -10.83 -6.48 0 108.6 215.4 36099 +1960 46 0.26 -5.74 -1.39 0.42 153.47 161.65 36282 +1960 47 4.36 -1.64 2.71 0 200.49 215.51 36466 +1960 48 6.72 0.72 5.07 0.67 232.81 162.19 36652 +1960 49 9.64 3.64 7.99 0 278.91 215.97 36838 +1960 50 7.05 1.05 5.4 0 237.67 221.36 37026 +1960 51 4.72 -1.28 3.07 0 205.16 226.45 37215 +1960 52 0.3 -5.7 -1.35 0 153.88 232.58 37405 +1960 53 3.37 -2.63 1.72 0 188.13 233.37 37596 +1960 54 5 -1 3.35 0 208.85 234.77 37788 +1960 55 10.94 4.94 9.29 0 301.83 231.27 37981 +1960 56 11.15 5.15 9.5 0 305.68 233.64 38175 +1960 57 8.05 2.05 6.4 0 252.93 240.27 38370 +1960 58 6.59 0.59 4.94 0 230.92 244.75 38565 +1960 59 5.1 -0.9 3.45 0 210.18 248.92 38761 +1960 60 11.62 5.62 9.97 0.02 314.45 183.14 38958 +1960 61 7.81 1.81 6.16 0.24 249.19 188.95 39156 +1960 62 8.85 2.85 7.2 0 265.73 253.49 39355 +1960 63 7.4 1.4 5.75 0 242.92 258.18 39553 +1960 64 8.29 2.29 6.64 0.01 256.71 195.03 39753 +1960 65 10.28 4.28 8.63 0 290 260.36 39953 +1960 66 11.63 5.63 9.98 1.55 314.64 195.84 40154 +1960 67 7.45 1.45 5.8 1.42 243.67 202.15 40355 +1960 68 4.23 -1.77 2.58 0.78 198.83 206.86 40556 +1960 69 1.3 -4.7 -0.35 0.63 164.39 210.76 40758 +1960 70 -0.47 -6.47 -2.12 0.22 146.19 246.67 40960 +1960 71 5.54 -0.46 3.89 0 216.13 282.94 41163 +1960 72 9.54 3.54 7.89 0.21 277.21 210.68 41366 +1960 73 12.69 6.69 11.04 0 335.22 278.74 41569 +1960 74 9.5 3.5 7.85 0 276.54 286.35 41772 +1960 75 10.7 4.7 9.05 0 297.48 287.31 41976 +1960 76 9.3 3.3 7.65 0 273.17 291.97 42179 +1960 77 8.38 2.38 6.73 0.01 258.14 221.86 42383 +1960 78 7.28 1.28 5.63 0 241.11 299.9 42587 +1960 79 7.11 1.11 5.46 0 238.56 302.84 42791 +1960 80 8.34 2.34 6.69 0.01 257.5 227.85 42996 +1960 81 12.55 6.55 10.9 0 332.44 299.84 43200 +1960 82 9.5 3.5 7.85 0 276.54 307.39 43404 +1960 83 12.82 6.82 11.17 0 337.82 304.42 43608 +1960 84 11.92 5.92 10.27 0.07 320.16 231.39 43812 +1960 85 10.2 4.2 8.55 0 288.6 313.83 44016 +1960 86 8.76 2.76 7.11 0.03 264.26 238.8 44220 +1960 87 7.77 1.77 6.12 0.23 248.57 241.74 44424 +1960 88 8.17 2.17 6.52 0 254.81 324.13 44627 +1960 89 6.05 0.05 4.4 0 223.21 329.21 44831 +1960 90 8.6 2.6 6.95 0 261.67 328.18 45034 +1960 91 10.25 4.25 8.6 0 289.48 327.9 45237 +1960 92 9.11 3.11 7.46 0.56 270.01 248.96 45439 +1960 93 10.67 4.67 9.02 0.21 296.95 248.75 45642 +1960 94 12.2 6.2 10.55 0 325.57 331.1 45843 +1960 95 11.4 5.4 9.75 0.01 310.32 251.02 46045 +1960 96 10.73 4.73 9.08 0 298.03 337.97 46246 +1960 97 13.15 7.15 11.5 0.01 344.5 251.65 46446 +1960 98 14.91 8.91 13.26 0 382.08 333.76 46647 +1960 99 14.97 8.97 13.32 0 383.42 335.6 46846 +1960 100 11.87 5.87 10.22 0 319.2 343.9 47045 +1960 101 6.07 0.07 4.42 1.01 223.49 266.23 47243 +1960 102 9.11 3.11 7.46 0 270.01 352.52 47441 +1960 103 5.62 -0.38 3.97 0 217.23 359.38 47638 +1960 104 6.66 0.66 5.01 0 231.94 359.86 47834 +1960 105 13.42 7.42 11.77 0 350.05 350.08 48030 +1960 106 13.88 7.88 12.23 0 359.69 350.74 48225 +1960 107 17.95 11.95 16.3 0 455.24 342.4 48419 +1960 108 18.13 12.13 16.48 0 459.92 343.59 48612 +1960 109 15.56 9.56 13.91 0 396.81 351.86 48804 +1960 110 14.95 8.95 13.3 0 382.97 354.71 48995 +1960 111 17.45 11.45 15.8 0 442.44 349.92 49185 +1960 112 15.62 9.62 13.97 0 398.2 356.14 49374 +1960 113 19.08 13.08 17.43 0 485.32 348.03 49561 +1960 114 13.24 7.24 11.59 0 346.35 364.41 49748 +1960 115 13.12 7.12 11.47 0 343.89 366.09 49933 +1960 116 15.49 9.49 13.84 0.07 395.2 271.41 50117 +1960 117 12.75 6.75 11.1 0 336.42 369.41 50300 +1960 118 11.45 5.45 9.8 0 311.26 373.36 50481 +1960 119 11.55 5.55 9.9 0 313.13 374.37 50661 +1960 120 13.14 7.14 11.49 0 344.3 372.28 50840 +1960 121 19.78 13.78 18.13 0.16 504.78 266.85 51016 +1960 122 17.47 11.47 15.82 0 442.95 363.89 51191 +1960 123 21.22 15.22 19.57 0 546.93 353.13 51365 +1960 124 21.87 15.87 20.22 0.01 566.91 263.9 51536 +1960 125 18.93 12.93 17.28 0.09 481.23 271.98 51706 +1960 126 17.05 11.05 15.4 0 432.43 369.09 51874 +1960 127 18.23 12.23 16.58 0.07 462.54 274.95 52039 +1960 128 18.7 12.7 17.05 0.15 475.02 274.62 52203 +1960 129 18.37 12.37 16.72 0 466.23 368 52365 +1960 130 18.15 12.15 16.5 0.04 460.44 277.07 52524 +1960 131 18.64 12.64 16.99 0 473.41 368.74 52681 +1960 132 19.68 13.68 18.03 0 501.96 366.27 52836 +1960 133 17.31 11.31 15.66 0.3 438.92 280.63 52989 +1960 134 15.2 9.2 13.55 0 388.59 380.51 53138 +1960 135 12.55 6.55 10.9 0 332.44 387.37 53286 +1960 136 13.34 7.34 11.69 0.65 348.4 289.71 53430 +1960 137 12.39 6.39 10.74 0.06 329.28 291.8 53572 +1960 138 14.01 8.01 12.36 0 362.45 386.06 53711 +1960 139 11.49 5.49 9.84 0.12 312.01 294.19 53848 +1960 140 10.42 4.42 8.77 0 292.48 394.85 53981 +1960 141 9.88 3.88 8.23 0.01 283.03 297.23 54111 +1960 142 14.11 8.11 12.46 0.05 364.59 290.98 54238 +1960 143 16.14 10.14 14.49 0.05 410.37 287.54 54362 +1960 144 14.87 8.87 13.22 0.83 381.19 290.36 54483 +1960 145 15.07 9.07 13.42 0.19 385.66 290.34 54600 +1960 146 16.59 10.59 14.94 0.03 421.16 287.62 54714 +1960 147 15.54 9.54 13.89 0.83 396.35 290.09 54824 +1960 148 17.06 11.06 15.41 0 432.68 383.04 54931 +1960 149 20.8 14.8 19.15 0 534.34 371.49 55034 +1960 150 18.05 12.05 16.4 0 457.83 380.79 55134 +1960 151 20.97 14.97 19.32 0 539.4 371.6 55229 +1960 152 24.36 18.36 22.71 1.48 649.28 268.8 55321 +1960 153 24.53 18.53 22.88 0 655.26 357.9 55409 +1960 154 24.49 18.49 22.84 0.43 653.85 268.78 55492 +1960 155 20.12 14.12 18.47 0.38 514.48 281.55 55572 +1960 156 20.79 14.79 19.14 0.16 534.04 280.05 55648 +1960 157 22.13 16.13 20.48 0 575.07 368.65 55719 +1960 158 24.84 18.84 23.19 0 666.28 357.66 55786 +1960 159 27.52 21.52 25.87 0 768.23 345.11 55849 +1960 160 28.02 22.02 26.37 0 788.64 342.69 55908 +1960 161 25.43 19.43 23.78 0.66 687.68 266.61 55962 +1960 162 24.07 18.07 22.42 0.08 639.2 271.15 56011 +1960 163 21.63 15.63 19.98 0 559.46 371.45 56056 +1960 164 22.1 16.1 20.45 0 574.13 369.73 56097 +1960 165 25.65 19.65 24 0 695.8 354.86 56133 +1960 166 21.52 15.52 19.87 0 556.07 372.07 56165 +1960 167 17.41 11.41 15.76 0 441.43 385.55 56192 +1960 168 17.27 11.27 15.62 0.16 437.91 289.53 56214 +1960 169 15.19 9.19 13.54 0.37 388.37 293.79 56231 +1960 170 17.77 11.77 16.12 0.28 450.6 288.44 56244 +1960 171 19.01 13.01 17.36 0.76 483.41 285.61 56252 +1960 172 23.39 17.39 21.74 0.24 616.06 273.66 56256 +1960 173 21.85 15.85 20.2 1.11 566.28 278.18 56255 +1960 174 21.02 15.02 19.37 0.41 540.9 280.41 56249 +1960 175 20.32 14.32 18.67 0.08 520.25 282.24 56238 +1960 176 16.56 10.56 14.91 0 420.43 387.94 56223 +1960 177 19.19 13.19 17.54 0 488.33 379.95 56203 +1960 178 21.23 15.23 19.58 0.17 547.23 279.74 56179 +1960 179 21.67 15.67 20.02 0.24 560.7 278.45 56150 +1960 180 18.29 12.29 16.64 0.34 464.12 286.94 56116 +1960 181 16.41 10.41 14.76 0.01 416.81 290.98 56078 +1960 182 15.64 9.64 13.99 0 398.66 389.9 56035 +1960 183 19.6 13.6 17.95 0 499.72 378.01 55987 +1960 184 22.87 16.87 21.22 0.47 598.86 274.49 55935 +1960 185 22.09 16.09 20.44 0 573.81 368.94 55879 +1960 186 24.52 18.52 22.87 0.28 654.91 269.09 55818 +1960 187 21.9 15.9 20.25 0.13 567.85 276.91 55753 +1960 188 21.24 15.24 19.59 0.51 547.53 278.54 55684 +1960 189 18.69 12.69 17.04 0.83 474.75 284.85 55611 +1960 190 17.42 11.42 15.77 1.11 441.69 287.45 55533 +1960 191 18.81 12.81 17.16 2.15 477.98 284.09 55451 +1960 192 19.2 13.2 17.55 1.66 488.61 282.93 55366 +1960 193 15.88 9.88 14.23 0.26 404.24 290.01 55276 +1960 194 20.75 14.75 19.1 0.62 532.86 278.65 55182 +1960 195 24.08 18.08 22.43 0.26 639.54 268.81 55085 +1960 196 25.73 19.73 24.08 0.2 698.78 263.04 54984 +1960 197 27.48 21.48 25.83 0.39 766.62 256.35 54879 +1960 198 24.93 18.93 23.28 0.02 669.5 265.11 54770 +1960 199 27.32 21.32 25.67 0.05 760.19 256.41 54658 +1960 200 22.53 16.53 20.88 0 587.83 362.68 54542 +1960 201 21.81 15.81 20.16 0.09 565.04 273.7 54423 +1960 202 22.34 16.34 20.69 0.32 581.74 271.79 54301 +1960 203 20.41 14.41 18.76 0.45 522.87 276.64 54176 +1960 204 19.29 13.29 17.64 0.4 491.09 279.04 54047 +1960 205 18.46 12.46 16.81 0.18 468.61 280.59 53915 +1960 206 18.2 12.2 16.55 0.56 461.75 280.76 53780 +1960 207 17.78 11.78 16.13 0.03 450.85 281.19 53643 +1960 208 19.47 13.47 17.82 0 496.08 369.07 53502 +1960 209 18.64 12.64 16.99 0 473.41 371.02 53359 +1960 210 19.27 13.27 17.62 0 490.54 368.42 53213 +1960 211 21.49 15.49 19.84 0.11 555.15 270.11 53064 +1960 212 21.12 15.12 19.47 1.31 543.91 270.5 52913 +1960 213 22.75 16.75 21.1 0.46 594.94 265.44 52760 +1960 214 19.91 13.91 18.26 0 508.47 363.27 52604 +1960 215 21.06 15.06 19.41 0 542.1 358.71 52445 +1960 216 19.6 13.6 17.95 0.08 499.72 271.93 52285 +1960 217 17.59 11.59 15.94 0.05 446 275.81 52122 +1960 218 17.51 11.51 15.86 0.01 443.96 275.36 51958 +1960 219 15.97 9.97 14.32 0 406.36 370.25 51791 +1960 220 17.71 11.71 16.06 0 449.06 364.56 51622 +1960 221 20.67 14.67 19.02 0.08 530.49 265.78 51451 +1960 222 21.9 15.9 20.25 1.18 567.85 261.78 51279 +1960 223 20.5 14.5 18.85 0 525.5 352.76 51105 +1960 224 20.6 14.6 18.95 0 528.43 351.37 50929 +1960 225 24.48 18.48 22.83 0.1 653.5 251.86 50751 +1960 226 27.82 21.82 26.17 1.69 780.42 239.71 50572 +1960 227 27.09 21.09 25.44 0.58 751.04 241.46 50392 +1960 228 23.9 17.9 22.25 0.02 633.35 250.99 50210 +1960 229 24.8 18.8 23.15 0 664.85 329.8 50026 +1960 230 26.47 20.47 24.82 0.22 726.82 241 49842 +1960 231 26.04 20.04 24.39 0 710.41 321.86 49656 +1960 232 24.02 18.02 22.37 0.18 637.47 246.76 49469 +1960 233 27.02 21.02 25.37 0.35 748.27 236.11 49280 +1960 234 25.72 19.72 24.07 0.9 698.41 239.47 49091 +1960 235 24.9 18.9 23.25 0.73 668.43 240.99 48900 +1960 236 21.32 15.32 19.67 0.82 549.96 249.94 48709 +1960 237 18.06 12.06 16.41 0 458.09 341.57 48516 +1960 238 19.11 13.11 17.46 0 486.14 336.9 48323 +1960 239 22.05 16.05 20.4 0 572.55 326.02 48128 +1960 240 18.49 12.49 16.84 0 469.41 335.4 47933 +1960 241 19.61 13.61 17.96 0.01 500 247.83 47737 +1960 242 20.47 14.47 18.82 0.06 524.62 244.56 47541 +1960 243 24.67 18.67 23.02 0.09 660.22 232.13 47343 +1960 244 20.14 14.14 18.49 1.11 515.05 242.59 47145 +1960 245 15.33 9.33 13.68 0.85 391.55 250.77 46947 +1960 246 14.97 8.97 13.32 0.18 383.42 249.88 46747 +1960 247 13.65 7.65 12 0.69 354.84 250.58 46547 +1960 248 14.99 8.99 13.34 1.28 383.87 246.95 46347 +1960 249 17.04 11.04 15.39 0.32 432.18 241.77 46146 +1960 250 17.44 11.44 15.79 0.04 442.19 239.55 45945 +1960 251 18.06 12.06 16.41 0 458.09 315.69 45743 +1960 252 20.52 14.52 18.87 0.66 526.08 230 45541 +1960 253 21.25 15.25 19.6 1.71 547.84 226.78 45339 +1960 254 15.82 9.82 14.17 0.19 402.84 236.03 45136 +1960 255 20.16 14.16 18.51 0 515.63 301.35 44933 +1960 256 18.39 12.39 16.74 0 466.76 303.96 44730 +1960 257 14.71 8.71 13.06 0 377.64 310.35 44527 +1960 258 15.38 9.38 13.73 0.25 392.69 229.93 44323 +1960 259 13.5 7.5 11.85 0.51 351.71 230.94 44119 +1960 260 10.46 4.46 8.81 0 293.19 310.78 43915 +1960 261 13.03 7.03 11.38 0 342.06 303.89 43711 +1960 262 14.89 8.89 13.24 0 381.63 297.89 43507 +1960 263 15.85 9.85 14.2 0.21 403.54 220.05 43303 +1960 264 17.52 11.52 15.87 0.64 444.22 215.32 43099 +1960 265 14.1 8.1 12.45 0 364.37 291.98 42894 +1960 266 10.76 4.76 9.11 0.04 298.57 221.41 42690 +1960 267 14.96 8.96 13.31 0 383.2 285.12 42486 +1960 268 17.7 11.7 16.05 0 448.8 276.69 42282 +1960 269 22.6 16.6 20.95 0 590.08 261.21 42078 +1960 270 26.09 20.09 24.44 0 712.3 247.1 41875 +1960 271 25.48 19.48 23.83 0 689.52 246.86 41671 +1960 272 22.76 16.76 21.11 0 595.27 253.14 41468 +1960 273 26.43 20.43 24.78 1 725.28 178.98 41265 +1960 274 21.6 15.6 19.95 0.41 558.54 188.65 41062 +1960 275 20.06 14.06 18.41 0.01 512.76 189.71 40860 +1960 276 17.36 11.36 15.71 0 440.17 256.6 40658 +1960 277 13.92 7.92 12.27 0 360.53 260.6 40456 +1960 278 16.19 10.19 14.54 0 411.56 253.55 40255 +1960 279 18.12 12.12 16.47 0 459.66 246.79 40054 +1960 280 19.64 13.64 17.99 0.09 500.84 180.57 39854 +1960 281 19.66 13.66 18.01 1.6 501.4 178.57 39654 +1960 282 18.01 12.01 16.36 0.94 456.79 179.34 39455 +1960 283 14.02 8.02 12.37 0.04 362.66 182.89 39256 +1960 284 14.25 8.25 12.6 0.32 367.6 180.35 39058 +1960 285 12.26 6.26 10.61 0.85 326.74 180.71 38861 +1960 286 9.76 3.76 8.11 0.21 280.97 181.17 38664 +1960 287 3.48 -2.52 1.83 0 189.47 245 38468 +1960 288 5.06 -0.94 3.41 0 209.65 240.77 38273 +1960 289 7.99 1.99 6.34 0 251.99 235.15 38079 +1960 290 7.48 1.48 5.83 0.06 244.13 174.59 37885 +1960 291 9.97 3.97 8.32 1.03 284.59 170.43 37693 +1960 292 10.44 4.44 8.79 0.15 292.83 167.97 37501 +1960 293 12.14 6.14 10.49 0.25 324.4 164.26 37311 +1960 294 15.04 9.04 13.39 0.19 384.99 158.9 37121 +1960 295 16.22 10.22 14.57 0 412.27 207.13 36933 +1960 296 19.87 13.87 18.22 0.1 507.33 148.3 36745 +1960 297 16.85 10.85 15.2 0 427.5 200.87 36560 +1960 298 18.25 12.25 16.6 0 463.06 195.83 36375 +1960 299 19.25 13.25 17.6 0 489.98 191.25 36191 +1960 300 20.05 14.05 18.4 0 512.47 187.11 36009 +1960 301 17.91 11.91 16.26 0.25 454.2 141.59 35829 +1960 302 14.43 8.43 12.78 1.17 371.5 143.88 35650 +1960 303 10.46 4.46 8.81 0 293.19 194.34 35472 +1960 304 11.77 5.77 10.12 0 317.3 190.37 35296 +1960 305 7.89 1.89 6.24 0 250.43 191.76 35122 +1960 306 11.46 5.46 9.81 0.58 311.44 139.34 34950 +1960 307 9.72 3.72 8.07 0.43 280.28 138.89 34779 +1960 308 7.81 1.81 6.16 0.05 249.19 138.32 34610 +1960 309 10.21 4.21 8.56 0 288.77 179.78 34444 +1960 310 12.08 6.08 10.43 0 323.24 175.3 34279 +1960 311 15.59 9.59 13.94 0 397.51 168.66 34116 +1960 312 18.3 12.3 16.65 0 464.38 161.95 33956 +1960 313 21.78 15.78 20.13 0.11 564.11 115.24 33797 +1960 314 21.08 15.08 19.43 0 542.7 153.22 33641 +1960 315 19.11 13.11 17.46 0 486.14 154.35 33488 +1960 316 16.21 10.21 14.56 0.64 412.03 117.55 33337 +1960 317 14.56 8.56 12.91 0.19 374.34 117.62 33188 +1960 318 10.98 4.98 9.33 0.73 302.56 118.94 33042 +1960 319 9.31 3.31 7.66 1.03 273.34 118.88 32899 +1960 320 5.52 -0.48 3.87 0 215.86 159.68 32758 +1960 321 6.48 0.48 4.83 0 229.33 156.87 32620 +1960 322 0.2 -5.8 -1.45 0 152.86 158.84 32486 +1960 323 3.69 -2.31 2.04 0.02 192.05 116.47 32354 +1960 324 5.61 -0.39 3.96 1.83 217.09 113.99 32225 +1960 325 0.35 -5.65 -1.3 1.12 154.39 114.97 32100 +1960 326 2.96 -3.04 1.31 0.57 183.21 112.83 31977 +1960 327 3.91 -2.09 2.26 0.04 194.79 111.02 31858 +1960 328 6.15 0.15 4.5 0.3 224.62 108.46 31743 +1960 329 6.35 0.35 4.7 0.02 227.47 107.24 31631 +1960 330 9.91 3.91 8.26 0.02 283.55 104.09 31522 +1960 331 10.24 4.24 8.59 0 289.3 137.2 31417 +1960 332 9.59 3.59 7.94 0.48 278.06 102.1 31316 +1960 333 8.67 2.67 7.02 0 262.8 135.81 31218 +1960 334 7.67 1.67 6.02 0 247.03 135.48 31125 +1960 335 6.87 0.87 5.22 0 235.01 134.88 31035 +1960 336 5.99 -0.01 4.34 0 222.37 134.4 30949 +1960 337 0.54 -5.46 -1.11 0.97 156.35 101.78 30867 +1960 338 2.14 -3.86 0.49 1.31 173.69 100.5 30790 +1960 339 1.41 -4.59 -0.24 0.46 165.58 100.17 30716 +1960 340 4.39 -1.61 2.74 0.21 200.88 98.45 30647 +1960 341 7.7 1.7 6.05 0.09 247.49 96.17 30582 +1960 342 5.26 -0.74 3.61 0 212.33 129.07 30521 +1960 343 5.78 -0.22 4.13 0.03 219.44 95.95 30465 +1960 344 5.35 -0.65 3.7 0.03 213.54 95.3 30413 +1960 345 3.08 -2.92 1.43 0 184.64 127.9 30366 +1960 346 0.94 -5.06 -0.71 0 160.54 128.38 30323 +1960 347 6.1 0.1 4.45 0 223.91 125.04 30284 +1960 348 6.87 0.87 5.22 0.11 235.01 93.15 30251 +1960 349 7.48 1.48 5.83 0 244.13 123.41 30221 +1960 350 11.09 5.09 9.44 0 304.58 120.33 30197 +1960 351 9.71 3.71 8.06 0 280.11 121.24 30177 +1960 352 5.13 -0.87 3.48 0.03 210.58 93.19 30162 +1960 353 6.9 0.9 5.25 0 235.45 123.1 30151 +1960 354 4.81 -1.19 3.16 0.2 206.34 93.25 30145 +1960 355 5.99 -0.01 4.34 0 222.37 123.64 30144 +1960 356 6.87 0.87 5.22 0.07 235.01 92.33 30147 +1960 357 8.68 2.68 7.03 0 262.96 121.91 30156 +1960 358 5.7 -0.3 4.05 0.83 218.33 92.99 30169 +1960 359 6.61 0.61 4.96 0 231.21 123.53 30186 +1960 360 6.32 0.32 4.67 0 227.04 124.08 30208 +1960 361 8.65 2.65 7 0 262.48 122.82 30235 +1960 362 7.89 1.89 6.24 0 250.43 123.8 30267 +1960 363 6.09 0.09 4.44 0.21 223.77 94.18 30303 +1960 364 8.08 2.08 6.43 0.25 253.4 93.48 30343 +1960 365 8.2 2.2 6.55 0 255.28 125.11 30388 +1961 1 -1.98 -7.98 -3.63 0 132.07 131.38 30438 +1961 2 1.23 -4.77 -0.42 0 163.64 130.79 30492 +1961 3 -0.8 -6.8 -2.45 0.01 143 142.7 30551 +1961 4 0.47 -5.53 -1.18 0.06 155.63 99.75 30614 +1961 5 0.99 -5.01 -0.66 0 161.07 133.42 30681 +1961 6 2.85 -3.15 1.2 0 181.9 133.4 30752 +1961 7 6.12 0.12 4.47 0 224.2 132.28 30828 +1961 8 5.28 -0.72 3.63 0 212.6 134.29 30907 +1961 9 3.76 -2.24 2.11 0 192.92 136.45 30991 +1961 10 3.71 -2.29 2.06 0 192.3 137.77 31079 +1961 11 5.17 -0.83 3.52 0 211.12 137.89 31171 +1961 12 4.25 -1.75 2.6 0 199.08 139.46 31266 +1961 13 2.75 -3.25 1.1 0 180.73 141.93 31366 +1961 14 -1.77 -7.77 -3.42 0 133.96 145.53 31469 +1961 15 -3.29 -9.29 -4.94 1.58 120.79 157.29 31575 +1961 16 -3.32 -9.32 -4.97 0 120.54 195.34 31686 +1961 17 -1.37 -7.37 -3.02 0 137.62 196.11 31800 +1961 18 1.63 -4.37 -0.02 0.05 167.99 158.66 31917 +1961 19 2.64 -3.36 0.99 0 179.44 197.13 32038 +1961 20 2.04 -3.96 0.39 0 172.56 198.63 32161 +1961 21 0.16 -5.84 -1.49 0 152.46 201.41 32289 +1961 22 0.58 -5.42 -1.07 0 156.76 202.71 32419 +1961 23 1.55 -4.45 -0.1 0 167.11 203.62 32552 +1961 24 -1.88 -7.88 -3.53 0.01 132.96 166.4 32688 +1961 25 -2.96 -8.96 -4.61 0.19 123.55 168.54 32827 +1961 26 1.15 -4.85 -0.5 0.28 162.78 168.23 32969 +1961 27 -3.42 -9.42 -5.07 0.2 119.71 171.74 33114 +1961 28 -2.31 -8.31 -3.96 0.55 129.14 174.47 33261 +1961 29 -4.67 -10.67 -6.32 0 109.82 220.51 33411 +1961 30 -0.57 -6.57 -2.22 0 145.22 220.82 33564 +1961 31 5.33 -0.67 3.68 0 213.27 218.76 33718 +1961 32 9.18 3.18 7.53 0 271.17 216.32 33875 +1961 33 8.84 2.84 7.19 0 265.57 217.98 34035 +1961 34 7.55 1.55 5.9 0 245.19 220.24 34196 +1961 35 5.96 -0.04 4.31 0 221.95 222.8 34360 +1961 36 9.12 3.12 7.47 0.37 270.17 175.62 34526 +1961 37 6.47 0.47 4.82 0.77 229.19 140.46 34694 +1961 38 1.06 -4.94 -0.59 0.51 161.81 145.4 34863 +1961 39 3.95 -2.05 2.3 0 195.29 194.59 35035 +1961 40 0.7 -5.3 -0.95 0 158.01 199.35 35208 +1961 41 1.24 -4.76 -0.41 0 163.74 201.67 35383 +1961 42 0.77 -5.23 -0.88 0.72 158.75 153.4 35560 +1961 43 2.47 -3.53 0.82 0.64 177.47 154.63 35738 +1961 44 0.11 -5.89 -1.54 0 151.95 210.26 35918 +1961 45 5.33 -0.67 3.68 0 213.27 209.2 36099 +1961 46 7.44 1.44 5.79 0 243.52 209.97 36282 +1961 47 4.12 -1.88 2.47 0 197.43 215.7 36466 +1961 48 4.29 -1.71 2.64 0.02 199.59 163.78 36652 +1961 49 8.09 2.09 6.44 0 253.55 217.66 36838 +1961 50 10.01 4.01 8.36 0 285.28 218.16 37026 +1961 51 11.59 5.59 9.94 0.03 313.89 164.33 37215 +1961 52 11.93 5.93 10.28 0 320.35 221.42 37405 +1961 53 13.09 7.09 11.44 0.02 343.28 167.01 37596 +1961 54 7.18 1.18 5.53 0 239.61 232.68 37788 +1961 55 7.9 1.9 6.25 0 250.58 234.9 37981 +1961 56 11.96 5.96 10.31 0 320.93 232.53 38175 +1961 57 8.67 2.67 7.02 0 262.8 239.57 38370 +1961 58 5.28 -0.72 3.63 0.05 212.6 184.53 38565 +1961 59 7.61 1.61 5.96 0 246.11 246.37 38761 +1961 60 10.91 4.91 9.26 0 301.29 245.17 38958 +1961 61 9.86 3.86 8.21 0.19 282.68 187.09 39156 +1961 62 8.4 2.4 6.75 0.26 258.46 190.52 39355 +1961 63 6.92 0.92 5.27 0.13 235.74 194.03 39553 +1961 64 10.64 4.64 8.99 0.23 296.41 192.76 39753 +1961 65 8.45 2.45 6.8 0 259.26 262.72 39953 +1961 66 7.37 1.37 5.72 0 242.46 266.73 40154 +1961 67 12.29 6.29 10.64 0.01 327.32 197.22 40355 +1961 68 8.82 2.82 7.17 0.65 265.24 203.05 40556 +1961 69 8.42 2.42 6.77 0.05 258.78 205.39 40758 +1961 70 11.47 5.47 9.82 0.3 311.63 204.32 40960 +1961 71 8.87 2.87 7.22 0 266.06 279.01 41163 +1961 72 6.99 0.99 5.34 0 236.78 284.16 41366 +1961 73 6.12 0.12 4.47 0.05 224.2 215.87 41569 +1961 74 7.07 1.07 5.42 0 237.97 289.49 41772 +1961 75 10.59 4.59 8.94 0.06 295.51 215.61 41976 +1961 76 8.18 2.18 6.53 0 254.97 293.48 42179 +1961 77 10.21 4.21 8.56 0 288.77 293.24 42383 +1961 78 11.35 5.35 9.7 0 309.39 294.12 42587 +1961 79 13.98 7.98 12.33 0 361.81 292.2 42791 +1961 80 12.9 6.9 11.25 0.08 339.43 222.51 42996 +1961 81 10.45 4.45 8.8 0 293.01 303.31 43200 +1961 82 11.75 5.75 10.1 0 316.91 303.84 43404 +1961 83 15.34 9.34 13.69 0 391.77 299.49 43608 +1961 84 14.94 8.94 13.29 0 382.75 302.79 43812 +1961 85 16.04 10.04 14.39 0 408 302.86 44016 +1961 86 17.2 11.2 15.55 0 436.16 302.5 44220 +1961 87 19.84 13.84 18.19 0 506.48 298.07 44424 +1961 88 18.32 12.32 16.67 0 464.91 304.41 44627 +1961 89 15.12 9.12 13.47 0 386.79 314.18 44831 +1961 90 15.85 9.85 14.2 0 403.54 314.88 45034 +1961 91 16.7 10.7 15.05 0.1 423.83 236.32 45237 +1961 92 19.76 13.76 18.11 1.49 504.22 231.91 45439 +1961 93 17.97 11.97 16.32 0 455.76 316.23 45642 +1961 94 17.51 11.51 15.86 0.04 443.96 239.62 45843 +1961 95 15.85 9.85 14.2 0 403.54 325.61 46045 +1961 96 15.11 9.11 13.46 0 386.56 329.37 46246 +1961 97 17.58 11.58 15.93 0 445.74 325.41 46446 +1961 98 17.23 11.23 15.58 0 436.91 328.22 46647 +1961 99 19.68 13.68 18.03 1.04 501.96 242.56 46846 +1961 100 18.56 12.56 16.91 0.02 471.27 246.37 47045 +1961 101 19.02 13.02 17.37 0 483.68 329.06 47243 +1961 102 19.1 13.1 17.45 0 485.86 330.66 47441 +1961 103 18.58 12.58 16.93 0 471.8 333.92 47638 +1961 104 17.81 11.81 16.16 0.06 451.62 253.36 47834 +1961 105 16.17 10.17 14.52 0.16 411.08 257.86 48030 +1961 106 13.61 7.61 11.96 0 354.01 351.32 48225 +1961 107 14.48 8.48 12.83 0 372.59 351.07 48419 +1961 108 14.29 8.29 12.64 0 368.46 353.22 48612 +1961 109 15.22 9.22 13.57 0 389.05 352.68 48804 +1961 110 17.17 11.17 15.52 0 435.41 349.16 48995 +1961 111 12.29 6.29 10.64 0 327.32 362.01 49185 +1961 112 12.25 6.25 10.6 0 326.54 363.62 49374 +1961 113 11.91 5.91 10.26 0 319.97 365.64 49561 +1961 114 10.37 4.37 8.72 0 291.59 370.04 49748 +1961 115 13.5 7.5 11.85 1.69 351.71 273.96 49933 +1961 116 16.13 10.13 14.48 0 410.13 360.27 50117 +1961 117 13.81 7.81 12.16 0 358.21 367.12 50300 +1961 118 13.27 7.27 11.62 0.02 346.96 277.22 50481 +1961 119 13.81 7.81 12.16 0.01 358.21 277.22 50661 +1961 120 17.6 11.6 15.95 0.15 446.25 270.93 50840 +1961 121 19.03 13.03 17.38 0.17 483.95 268.61 51016 +1961 122 16.62 10.62 14.97 0 421.88 366.22 51191 +1961 123 14.78 8.78 13.13 0.07 379.19 278.93 51365 +1961 124 17 11 15.35 1.34 431.19 275.46 51536 +1961 125 19.68 13.68 18.03 0 501.96 360.28 51706 +1961 126 25.5 19.5 23.85 0 690.25 339.13 51874 +1961 127 22.6 16.6 20.95 0 590.08 351.89 52039 +1961 128 25.86 19.86 24.21 0.52 703.64 254.45 52203 +1961 129 19.43 13.43 17.78 0 494.97 364.72 52365 +1961 130 17.58 11.58 15.93 0.59 445.74 278.32 52524 +1961 131 17.39 11.39 15.74 0.94 440.93 279.32 52681 +1961 132 19.68 13.68 18.03 0.18 501.96 274.71 52836 +1961 133 20.88 14.88 19.23 0.33 536.72 272.19 52989 +1961 134 17.92 11.92 16.27 0.69 454.46 279.83 53138 +1961 135 17.45 11.45 15.8 0.35 442.44 281.37 53286 +1961 136 18.04 12.04 16.39 0.69 457.57 280.56 53430 +1961 137 14.93 8.93 13.28 0.01 382.52 287.42 53572 +1961 138 12.3 6.3 10.65 0.02 327.52 292.41 53711 +1961 139 11.75 5.75 10.1 0.29 316.91 293.8 53848 +1961 140 12.22 6.22 10.57 0 325.96 391.25 53981 +1961 141 10.26 4.26 8.61 0 289.65 395.6 54111 +1961 142 9.48 3.48 7.83 0.03 276.2 298.16 54238 +1961 143 10.15 4.15 8.5 0.12 287.72 297.65 54362 +1961 144 11.84 5.84 10.19 0 318.63 394.04 54483 +1961 145 13.3 7.3 11.65 0 347.58 391.35 54600 +1961 146 12.44 6.44 10.79 0.16 330.27 295.23 54714 +1961 147 14.83 8.83 13.18 0.36 380.3 291.44 54824 +1961 148 12.27 6.27 10.62 0.06 326.93 296.16 54931 +1961 149 7.77 1.77 6.12 0.57 248.57 302.7 55034 +1961 150 15.62 9.62 13.97 0 398.2 387.61 55134 +1961 151 20.09 14.09 18.44 0 513.62 374.66 55229 +1961 152 25.25 19.25 23.6 0 681.09 354.48 55321 +1961 153 25.6 19.6 23.95 0.12 693.95 264.83 55409 +1961 154 24.77 18.77 23.12 0.25 663.78 267.87 55492 +1961 155 25.75 19.75 24.1 0 699.53 352.89 55572 +1961 156 26.65 20.65 25 0 733.78 348.91 55648 +1961 157 29.78 23.78 28.13 0.12 864.16 249.32 55719 +1961 158 28.44 22.44 26.79 0 806.14 340.05 55786 +1961 159 23.41 17.41 21.76 0 616.73 363.99 55849 +1961 160 23.41 17.41 21.76 0.06 616.73 273.13 55908 +1961 161 23.45 17.45 21.8 0.07 618.08 273.05 55962 +1961 162 22.91 16.91 21.26 0.71 600.17 274.73 56011 +1961 163 21.46 15.46 19.81 0.96 554.23 279.06 56056 +1961 164 13.32 7.32 11.67 0.09 347.99 297.02 56097 +1961 165 15.63 9.63 13.98 0 398.43 390.46 56133 +1961 166 18.14 12.14 16.49 0 460.18 383.43 56165 +1961 167 16.23 10.23 14.58 0.08 412.51 291.66 56192 +1961 168 16.61 10.61 14.96 0.58 421.64 290.93 56214 +1961 169 15.28 9.28 13.63 0.92 390.41 293.62 56231 +1961 170 15.66 9.66 14.01 0.3 399.12 292.87 56244 +1961 171 18.9 12.9 17.25 0.23 480.41 285.87 56252 +1961 172 18.91 12.91 17.26 0 480.69 381.12 56256 +1961 173 25.42 19.42 23.77 0.7 687.31 267.04 56255 +1961 174 23.8 17.8 22.15 0 629.93 363.08 56249 +1961 175 26.7 20.7 25.05 0.37 735.72 262.41 56238 +1961 176 25.03 19.03 23.38 0 673.11 357.68 56223 +1961 177 26.12 20.12 24.47 1.92 713.44 264.41 56203 +1961 178 25.25 19.25 23.6 0.25 681.09 267.46 56179 +1961 179 18.77 12.77 17.12 0 476.9 381.21 56150 +1961 180 19.38 13.38 17.73 0 493.58 379.13 56116 +1961 181 20.41 14.41 18.76 0 522.87 375.6 56078 +1961 182 20.01 14.01 18.36 0 511.32 376.82 56035 +1961 183 20.43 14.43 18.78 0.01 523.45 281.4 55987 +1961 184 26.73 20.73 25.08 0.22 736.89 261.67 55935 +1961 185 24.81 18.81 23.16 0 665.2 357.77 55879 +1961 186 26.36 20.36 24.71 0 722.59 350.37 55818 +1961 187 24.55 18.55 22.9 0.03 655.97 268.86 55753 +1961 188 22.72 16.72 21.07 0.01 593.97 274.35 55684 +1961 189 19.79 13.79 18.14 0 505.07 376.25 55611 +1961 190 19.97 13.97 18.32 0 510.18 375.27 55533 +1961 191 24.19 18.19 22.54 0 643.35 358.98 55451 +1961 192 22.15 16.15 20.5 0.25 575.7 275.18 55366 +1961 193 23.94 17.94 22.29 0.65 634.72 269.61 55276 +1961 194 25.7 19.7 24.05 0 697.66 351.51 55182 +1961 195 24.24 18.24 22.59 0.14 645.09 268.3 55085 +1961 196 25.1 19.1 23.45 0.09 675.64 265.19 54984 +1961 197 26.34 20.34 24.69 0.09 721.82 260.56 54879 +1961 198 25.8 19.8 24.15 0.22 701.39 262.16 54770 +1961 199 19.79 13.79 18.14 0.01 505.07 279.66 54658 +1961 200 18.64 12.64 16.99 0.58 473.41 282.12 54542 +1961 201 18.67 12.67 17.02 0 474.21 375.6 54423 +1961 202 17.55 11.55 15.9 0.05 444.98 283.79 54301 +1961 203 18.73 12.73 17.08 0 475.82 374.33 54176 +1961 204 19.33 13.33 17.68 0.07 492.19 278.94 54047 +1961 205 21.16 15.16 19.51 0 545.11 365.22 53915 +1961 206 18.74 12.74 17.09 0 476.09 372.7 53780 +1961 207 17.78 11.78 16.13 1.57 450.85 281.19 53643 +1961 208 21.58 15.58 19.93 2.28 557.92 271.39 53502 +1961 209 17.8 11.8 16.15 0.17 451.37 280.15 53359 +1961 210 20.5 14.5 18.85 0.7 525.5 273.28 53213 +1961 211 16.49 10.49 14.84 0.78 418.74 281.84 53064 +1961 212 15.4 9.4 13.75 0.08 393.14 283.36 52913 +1961 213 21.19 15.19 19.54 0 546.02 359.67 52760 +1961 214 24.01 18.01 22.36 0 637.13 348.18 52604 +1961 215 22.84 16.84 21.19 0 597.88 352.18 52445 +1961 216 25.95 19.95 24.3 0.02 707.02 253.6 52285 +1961 217 23.01 17.01 21.36 0 603.45 349.65 52122 +1961 218 24.73 18.73 23.08 0 662.35 341.88 51958 +1961 219 21.6 15.6 19.95 0 558.54 353.07 51791 +1961 220 22.57 16.57 20.92 0.02 589.12 261.44 51622 +1961 221 19.4 13.4 17.75 0 494.14 358.5 51451 +1961 222 18.68 12.68 17.03 0.59 474.48 269.74 51279 +1961 223 17.96 11.96 16.31 0.71 455.5 270.46 51105 +1961 224 14.58 8.58 12.93 0 374.78 368.33 50929 +1961 225 18.48 12.48 16.83 0 469.14 356.88 50751 +1961 226 20.57 14.57 18.92 0 527.55 349.19 50572 +1961 227 18.79 12.79 17.14 0 477.44 353.51 50392 +1961 228 21.4 15.4 19.75 0 552.4 343.91 50210 +1961 229 17.02 11.02 15.37 0.12 431.69 267.03 50026 +1961 230 15.03 9.03 13.38 0.3 384.76 269.82 49842 +1961 231 18.73 12.73 17.08 0.31 475.82 261.35 49656 +1961 232 22.16 16.16 20.51 0.39 576.02 252 49469 +1961 233 24.17 18.17 22.52 0 642.66 327.05 49280 +1961 234 27.59 21.59 25.94 0 771.06 310.81 49091 +1961 235 25.48 19.48 23.83 0.14 689.52 239.17 48900 +1961 236 25.35 19.35 23.7 0 684.74 318.09 48709 +1961 237 25.26 19.26 23.61 0.25 681.45 237.68 48516 +1961 238 27.14 21.14 25.49 0 753.02 307.11 48323 +1961 239 25.57 19.57 23.92 0.39 692.84 234.44 48128 +1961 240 22.44 16.44 20.79 0 584.94 322.94 47933 +1961 241 24.14 18.14 22.49 0.64 641.62 236.26 47737 +1961 242 28.68 22.68 27.03 0.21 816.28 220.2 47541 +1961 243 28.6 22.6 26.95 0 812.89 292.28 47343 +1961 244 27.63 21.63 25.98 0 772.68 295.19 47145 +1961 245 28.14 22.14 26.49 0 793.6 291.13 46947 +1961 246 25.86 19.86 24.21 0 703.64 299.37 46747 +1961 247 21.8 15.8 20.15 0 564.73 312.65 46547 +1961 248 25.36 19.36 23.71 0 685.11 297.84 46347 +1961 249 21.96 15.96 20.31 0 569.72 308.22 46146 +1961 250 26.47 20.47 24.82 0 726.82 289.53 45945 +1961 251 26.67 20.67 25.02 0 734.56 286.72 45743 +1961 252 23.73 17.73 22.08 0.3 627.54 222.11 45541 +1961 253 23.54 17.54 21.89 0 621.1 294.79 45339 +1961 254 23.63 17.63 21.98 0 624.15 292.44 45136 +1961 255 20.15 14.15 18.5 0.08 515.34 226.03 44933 +1961 256 23.12 17.12 21.47 0 607.08 289.87 44730 +1961 257 18.5 12.5 16.85 0 469.67 301.53 44527 +1961 258 19.46 13.46 17.81 0 495.8 296.66 44323 +1961 259 18.69 12.69 17.04 0 474.75 296.31 44119 +1961 260 19.83 13.83 18.18 0 506.2 290.92 43915 +1961 261 18.12 12.12 16.47 0.05 459.66 219.74 43711 +1961 262 19.77 13.77 18.12 0 504.5 286.36 43507 +1961 263 20.17 14.17 18.52 0 515.92 282.87 43303 +1961 264 14.42 8.42 12.77 0 371.28 293.75 43099 +1961 265 10.67 4.67 9.02 0 296.95 297.89 42894 +1961 266 14.36 8.36 12.71 0 369.98 288.98 42690 +1961 267 17.23 11.23 15.58 0 436.91 280.3 42486 +1961 268 20 14 18.35 0 511.04 271 42282 +1961 269 19.9 13.9 18.25 0 508.19 268.82 42078 +1961 270 20.47 14.47 18.82 0 524.62 264.76 41875 +1961 271 18.8 12.8 17.15 0.57 477.71 199.84 41671 +1961 272 17.44 11.44 15.79 0.66 442.19 200.19 41468 +1961 273 12.91 6.91 11.26 0 339.63 273.17 41265 +1961 274 8.31 2.31 6.66 0.03 257.03 207.87 41062 +1961 275 10.32 4.32 8.67 0.04 290.71 203.74 40860 +1961 276 9.42 3.42 7.77 0.58 275.19 202.6 40658 +1961 277 7.79 1.79 6.14 0.03 248.88 202.1 40456 +1961 278 13.23 7.23 11.58 0.34 346.14 194.17 40255 +1961 279 9.42 3.42 7.77 0.93 275.19 196.23 40054 +1961 280 11.45 5.45 9.8 0 311.26 256.16 39854 +1961 281 14.84 8.84 13.19 0.25 380.52 185.98 39654 +1961 282 12.42 6.42 10.77 0.01 329.87 186.92 39455 +1961 283 10.77 4.77 9.12 0 298.75 248.76 39256 +1961 284 13.28 7.28 11.63 0 347.17 242.04 39058 +1961 285 12.28 6.28 10.63 0.07 327.13 180.69 38861 +1961 286 10.71 4.71 9.06 0.04 297.67 180.25 38664 +1961 287 15.58 9.58 13.93 0 397.27 229.93 38468 +1961 288 14.92 8.92 13.27 0.04 382.3 171.24 38273 +1961 289 13.95 7.95 12.3 0.09 361.17 170.47 38079 +1961 290 19.12 13.12 17.47 0 486.41 215.03 37885 +1961 291 17.16 11.16 15.51 0.09 435.17 162.24 37693 +1961 292 20.14 14.14 18.49 0.02 515.05 155.76 37501 +1961 293 15.77 9.77 14.12 0.4 401.68 160.12 37311 +1961 294 18.57 12.57 16.92 0.97 471.54 154.18 37121 +1961 295 18.08 12.08 16.43 1.25 458.62 152.83 36933 +1961 296 18.89 12.89 17.24 0.01 480.14 149.79 36745 +1961 297 18.98 12.98 17.33 1.46 482.59 147.7 36560 +1961 298 18 12 16.35 0.83 456.53 147.22 36375 +1961 299 15.58 9.58 13.93 0.05 397.27 148.3 36191 +1961 300 18.26 12.26 16.61 0 463.33 190.58 36009 +1961 301 20.6 14.6 18.95 0.01 528.43 137.7 35829 +1961 302 18.76 12.76 17.11 0.18 476.63 138.55 35650 +1961 303 18.49 12.49 16.84 0.95 469.41 137.07 35472 +1961 304 17.98 11.98 16.33 0 456.02 181.32 35296 +1961 305 12.76 6.76 11.11 1.03 336.62 139.82 35122 +1961 306 9.86 3.86 8.21 0 282.68 187.55 34950 +1961 307 12.17 6.17 10.52 0.18 324.99 136.84 34779 +1961 308 10.77 4.77 9.12 0.73 298.75 136.11 34610 +1961 309 3.83 -2.17 2.18 0.28 193.79 138.94 34444 +1961 310 0.71 -5.29 -0.94 0.22 158.12 138.54 34279 +1961 311 4.07 -1.93 2.42 0.05 196.8 135.3 34116 +1961 312 5.77 -0.23 4.12 0.33 219.3 132.37 33956 +1961 313 5.53 -0.47 3.88 0.13 215.99 130.9 33797 +1961 314 8.84 2.84 7.19 0.03 265.57 127.37 33641 +1961 315 7.37 1.37 5.72 0 242.46 168.58 33488 +1961 316 10.01 4.01 8.36 0 285.28 164.03 33337 +1961 317 6.22 0.22 4.57 1.01 225.61 123.82 33188 +1961 318 5.56 -0.44 3.91 0.38 216.41 122.43 33042 +1961 319 8.01 2.01 6.36 0.15 252.3 119.73 32899 +1961 320 10.44 4.44 8.79 0.37 292.83 116.71 32758 +1961 321 11.84 5.84 10.19 0.1 318.63 114.1 32620 +1961 322 11.98 5.98 10.33 0.42 321.31 112.65 32486 +1961 323 12.58 6.58 10.93 0.07 333.03 110.99 32354 +1961 324 6.42 0.42 4.77 0.02 228.47 113.56 32225 +1961 325 4.24 -1.76 2.59 0 198.96 151.15 32100 +1961 326 2.69 -3.31 1.04 0.32 180.03 112.95 31977 +1961 327 5.97 -0.03 4.32 0 222.09 146.71 31858 +1961 328 6.95 0.95 5.3 0 236.19 144.05 31743 +1961 329 7.7 1.7 6.05 0.7 247.49 106.5 31631 +1961 330 6.55 0.55 4.9 0.52 230.34 106.05 31522 +1961 331 8.17 2.17 6.52 0.71 254.81 104.18 31417 +1961 332 10.47 4.47 8.82 0.85 293.37 101.54 31316 +1961 333 7.59 1.59 5.94 0.04 245.81 102.47 31218 +1961 334 8.24 2.24 6.59 0 255.92 135.06 31125 +1961 335 -1.43 -7.43 -3.08 0 137.07 139.31 31035 +1961 336 1.2 -4.8 -0.45 0 163.31 137.07 30949 +1961 337 7.55 1.55 5.9 0.02 245.19 98.76 30867 +1961 338 6.04 0.04 4.39 0.25 223.07 98.83 30790 +1961 339 9.06 3.06 7.41 0 269.18 128.86 30716 +1961 340 8.71 2.71 7.06 0.31 263.45 96.3 30647 +1961 341 6.07 0.07 4.42 0.11 223.49 97 30582 +1961 342 2.23 -3.77 0.58 0.06 174.72 98.04 30521 +1961 343 3.83 -2.17 2.18 0 193.79 129.07 30465 +1961 344 5.88 -0.12 4.23 0 220.83 126.74 30413 +1961 345 6.16 0.16 4.51 0 224.76 126.14 30366 +1961 346 6.19 0.19 4.54 0.02 225.19 94.18 30323 +1961 347 7.03 1.03 5.38 0 237.37 124.44 30284 +1961 348 2.04 -3.96 0.39 0.04 172.56 95.19 30251 +1961 349 1.22 -4.78 -0.43 0 163.53 126.92 30221 +1961 350 -1.34 -7.34 -2.99 0 137.9 127.64 30197 +1961 351 0.92 -5.08 -0.73 0.56 160.33 94.87 30177 +1961 352 1.37 -4.63 -0.28 0.14 165.15 94.65 30162 +1961 353 1.69 -4.31 0.04 0.14 168.65 94.49 30151 +1961 354 2.83 -3.17 1.18 0.1 181.67 94.05 30145 +1961 355 -1.76 -7.76 -3.41 0 134.05 127.37 30144 +1961 356 -0.86 -6.86 -2.51 0 142.42 127.06 30147 +1961 357 -3.81 -9.81 -5.46 0 116.55 128.16 30156 +1961 358 -7.64 -13.64 -9.29 0.58 89.1 142.59 30169 +1961 359 -9.37 -15.37 -11.02 0 78.67 175.42 30186 +1961 360 -5.25 -11.25 -6.9 0 105.47 174.73 30208 +1961 361 -1.47 -7.47 -3.12 0 136.7 173.77 30235 +1961 362 4.73 -1.27 3.08 0 205.29 170.63 30267 +1961 363 2.17 -3.83 0.52 0 174.03 172.22 30303 +1961 364 0.86 -5.14 -0.79 1.15 159.69 140.87 30343 +1961 365 -2.89 -8.89 -4.54 0.91 124.14 145.22 30388 +1962 1 -1.18 -7.18 -2.83 0.53 139.39 147.01 30438 +1962 2 2.85 -3.15 1.2 0.13 181.9 145.75 30492 +1962 3 3.74 -2.26 2.09 1.41 192.67 145.51 30551 +1962 4 -0.11 -6.11 -1.76 0.08 149.74 147.75 30614 +1962 5 -0.35 -6.35 -2 0 147.37 181.71 30681 +1962 6 2.44 -3.56 0.79 0.13 177.12 147.49 30752 +1962 7 6.46 0.46 4.81 0 229.04 178.37 30828 +1962 8 5.74 -0.26 4.09 0 218.88 179.45 30907 +1962 9 2.25 -3.75 0.6 0 174.94 182.29 30991 +1962 10 0.88 -5.12 -0.77 0 159.9 184.03 31079 +1962 11 0.23 -5.77 -1.42 1.46 153.17 150.03 31171 +1962 12 2.5 -3.5 0.85 0.36 177.82 149.5 31266 +1962 13 3.98 -2.02 2.33 0 195.67 184.76 31366 +1962 14 3.49 -2.51 1.84 0.14 189.59 150.18 31469 +1962 15 1.67 -4.33 0.02 0 168.43 188 31575 +1962 16 2.32 -3.68 0.67 0 175.74 188.51 31686 +1962 17 7.94 1.94 6.29 0 251.21 144.41 31800 +1962 18 6.06 0.06 4.41 0 223.35 147.67 31917 +1962 19 5.03 -0.97 3.38 0 209.25 150.29 32038 +1962 20 3.64 -2.36 1.99 0 191.43 152.74 32161 +1962 21 2.34 -3.66 0.69 0.03 175.97 116.63 32289 +1962 22 3.56 -2.44 1.91 0 190.45 156.55 32419 +1962 23 1.77 -4.23 0.12 0.02 169.54 119.52 32552 +1962 24 2.47 -3.53 0.82 0 177.47 161.04 32688 +1962 25 2.88 -3.12 1.23 0 182.26 162.7 32827 +1962 26 3.28 -2.72 1.63 0 187.04 164.38 32969 +1962 27 3.52 -2.48 1.87 0 189.96 166.26 33114 +1962 28 2.2 -3.8 0.55 0 174.37 169.28 33261 +1962 29 2.52 -3.48 0.87 0.02 178.05 128.61 33411 +1962 30 4.11 -1.89 2.46 0 197.3 172.71 33564 +1962 31 2.93 -3.07 1.28 0 182.85 175.85 33718 +1962 32 0.64 -5.36 -1.01 0 157.39 179.33 33875 +1962 33 -0.18 -6.18 -1.83 0 149.05 182.41 34035 +1962 34 2.46 -3.54 0.81 0 177.35 183.12 34196 +1962 35 0.99 -5.01 -0.66 0 161.07 186.17 34360 +1962 36 -1.39 -7.39 -3.04 0.16 137.44 181.16 34526 +1962 37 0.76 -5.24 -0.89 0 158.64 229.69 34694 +1962 38 4.72 -1.28 3.07 0 205.16 191.41 34863 +1962 39 3.94 -2.06 2.29 0 195.16 194.6 35035 +1962 40 4.43 -1.57 2.78 0 201.39 196.86 35208 +1962 41 6.93 0.93 5.28 0 235.89 197.41 35383 +1962 42 5.49 -0.51 3.84 0 215.45 201.19 35560 +1962 43 3.5 -2.5 1.85 0 189.71 205.44 35738 +1962 44 4.29 -1.71 2.64 0 199.59 207.42 35918 +1962 45 3.72 -2.28 2.07 0 192.42 210.49 36099 +1962 46 7.17 1.17 5.52 0 239.46 210.23 36282 +1962 47 2.66 -3.34 1.01 0.53 179.67 162.6 36466 +1962 48 3.15 -2.85 1.5 0.5 185.47 164.45 36652 +1962 49 2.2 -3.8 0.55 0 174.37 222.75 36838 +1962 50 3.77 -2.23 2.12 0 193.04 224.26 37026 +1962 51 7.9 1.9 6.25 0 250.58 223.44 37215 +1962 52 9.91 3.91 8.26 0.22 283.55 167.99 37405 +1962 53 9.83 3.83 8.18 0.01 282.17 170.26 37596 +1962 54 9.86 3.86 8.21 0.5 282.68 172.27 37788 +1962 55 5.49 -0.51 3.84 0.24 215.45 177.99 37981 +1962 56 -1.99 -7.99 -3.64 0 131.98 245.54 38175 +1962 57 -3.94 -9.94 -5.59 0 115.51 249.52 38370 +1962 58 -1.28 -7.28 -2.93 0 138.46 251.04 38565 +1962 59 -0.89 -6.89 -2.54 0 142.14 253.55 38761 +1962 60 2.76 -3.24 1.11 0 180.85 253.86 38958 +1962 61 3.77 -2.23 2.12 0 193.04 255.97 39156 +1962 62 0 -6 -1.65 0 150.84 261.72 39355 +1962 63 1.31 -4.69 -0.34 0 164.5 263.83 39553 +1962 64 5.07 -0.93 3.42 0 209.78 263.53 39753 +1962 65 4.03 -1.97 2.38 0 196.29 267.42 39953 +1962 66 2.77 -3.23 1.12 0 180.96 271.3 40154 +1962 67 4.51 -1.49 2.86 0 202.42 272.65 40355 +1962 68 4.49 -1.51 2.84 0 202.16 275.56 40556 +1962 69 4.55 -1.45 2.9 0 202.94 278.15 40758 +1962 70 5.33 -0.67 3.68 0 213.27 280.23 40960 +1962 71 4.86 -1.14 3.21 0.4 206.99 212.73 41163 +1962 72 3.66 -2.34 2.01 0.06 191.68 215.75 41366 +1962 73 5.87 -0.13 4.22 0 220.69 288.11 41569 +1962 74 7.09 1.09 5.44 0 238.26 289.47 41772 +1962 75 9.3 3.3 7.65 0.33 273.17 217.01 41976 +1962 76 8.82 2.82 7.17 0.21 265.24 219.47 42179 +1962 77 4.04 -1.96 2.39 0.08 196.42 225.63 42383 +1962 78 4.89 -1.11 3.24 1.18 207.39 226.99 42587 +1962 79 3.87 -2.13 2.22 1.87 194.29 229.85 42791 +1962 80 2.93 -3.07 1.28 0.05 182.85 232.47 42996 +1962 81 1.31 -4.69 -0.34 0.3 164.5 235.54 43200 +1962 82 0.1 -5.9 -1.55 0.11 151.85 238.33 43404 +1962 83 1.4 -4.6 -0.25 0 165.48 319.23 43608 +1962 84 4.47 -1.53 2.82 0.76 201.91 239.11 43812 +1962 85 3.59 -2.41 1.94 0 190.82 322.28 44016 +1962 86 3.78 -2.22 2.13 0 193.17 324.53 44220 +1962 87 6.1 0.1 4.45 0 223.91 324.47 44424 +1962 88 5.47 -0.53 3.82 0.12 215.17 245.7 44627 +1962 89 9.33 3.33 7.68 0 273.67 324.72 44831 +1962 90 10.23 4.23 8.58 0 289.12 325.68 45034 +1962 91 19.24 13.24 17.59 0 489.71 308.54 45237 +1962 92 15.99 9.99 14.34 0 406.83 318.94 45439 +1962 93 15.15 9.15 13.5 0 387.46 323 45642 +1962 94 16.15 10.15 14.5 0 410.61 322.82 45843 +1962 95 18.42 12.42 16.77 0 467.55 319.17 46045 +1962 96 20.72 14.72 19.07 0 531.97 314.54 46246 +1962 97 26.74 20.74 25.09 0 737.28 294.25 46446 +1962 98 22.51 16.51 20.86 0 587.18 312.46 46647 +1962 99 20.57 14.57 18.92 0.42 527.55 240.54 46846 +1962 100 16.56 10.56 14.91 2.18 420.43 250.32 47045 +1962 101 14.7 8.7 13.05 0.26 377.42 255.02 47243 +1962 102 13.06 7.06 11.41 0 342.67 345.4 47441 +1962 103 10.77 4.77 9.12 0.02 298.75 263.69 47638 +1962 104 10 4 8.35 0.39 285.11 266.06 47834 +1962 105 8.75 2.75 7.1 0.03 264.1 268.95 48030 +1962 106 7.68 1.68 6.03 0.22 247.19 271.43 48225 +1962 107 4.8 -1.2 3.15 0 206.2 367.51 48419 +1962 108 0.59 -5.41 -1.06 0 156.87 373.84 48612 +1962 109 3.96 -2.04 2.31 0.12 195.41 278.97 48804 +1962 110 6.74 0.74 5.09 0.32 233.1 277.37 48995 +1962 111 8.45 2.45 6.8 0 259.26 368.85 49185 +1962 112 11.76 5.76 10.11 0 317.1 364.58 49374 +1962 113 9.72 3.72 8.07 0 280.28 369.67 49561 +1962 114 13.27 7.27 11.62 0 346.96 364.34 49748 +1962 115 13.12 7.12 11.47 0 343.89 366.09 49933 +1962 116 16.79 10.79 15.14 0.02 426.03 268.91 50117 +1962 117 18.46 12.46 16.81 0.18 468.61 266.38 50300 +1962 118 19.25 13.25 17.6 0.06 489.98 265.56 50481 +1962 119 14.66 8.66 13.01 0 376.54 367.67 50661 +1962 120 15.8 9.8 14.15 0 402.38 366.05 50840 +1962 121 19.15 13.15 17.5 0 487.23 357.78 51016 +1962 122 17.96 11.96 16.31 0.45 455.5 271.87 51191 +1962 123 16.08 10.08 14.43 0.21 408.95 276.49 51365 +1962 124 17.55 11.55 15.9 0.13 444.98 274.31 51536 +1962 125 17.39 11.39 15.74 0 440.93 367.17 51706 +1962 126 19.16 13.16 17.51 0.11 487.51 272.17 51874 +1962 127 21.25 15.25 19.6 0.01 547.84 267.62 52039 +1962 128 19.02 13.02 17.37 0.15 483.68 273.88 52203 +1962 129 17.42 11.42 15.77 0 441.69 370.77 52365 +1962 130 18.03 12.03 16.38 1.85 457.31 277.34 52524 +1962 131 14.27 8.27 12.62 0.91 368.03 285.39 52681 +1962 132 12.64 6.64 10.99 0 334.22 385.03 52836 +1962 133 15.35 9.35 13.7 0 392 379.42 52989 +1962 134 16.06 10.06 14.41 0 408.48 378.3 53138 +1962 135 16.85 10.85 15.2 0.27 427.5 282.64 53286 +1962 136 13.63 7.63 11.98 0.29 354.42 289.22 53430 +1962 137 16.24 10.24 14.59 1 412.74 284.89 53572 +1962 138 12.01 6.01 10.36 0.74 321.89 292.87 53711 +1962 139 13.81 7.81 12.16 0.01 358.21 290.42 53848 +1962 140 15.25 9.25 13.6 0.72 389.73 288.17 53981 +1962 141 11.58 5.58 9.93 0.08 313.7 294.77 54111 +1962 142 16.32 10.32 14.67 0.19 414.65 286.77 54238 +1962 143 15.12 9.12 13.47 0.25 386.79 289.53 54362 +1962 144 15.01 9.01 13.36 0.18 384.31 290.1 54483 +1962 145 14.59 8.59 12.94 0 375 388.31 54600 +1962 146 12.64 6.64 10.99 0 334.22 393.2 54714 +1962 147 15.15 9.15 13.5 0 387.46 387.78 54824 +1962 148 18.38 12.38 16.73 0 466.49 379.14 54931 +1962 149 19.41 13.41 17.76 0 494.41 376.2 55034 +1962 150 19.67 13.67 18.02 0.01 501.68 281.76 55134 +1962 151 20.73 14.73 19.08 0.19 532.26 279.34 55229 +1962 152 20.27 14.27 18.62 0.49 518.8 280.61 55321 +1962 153 17.88 11.88 16.23 0 453.43 382.05 55409 +1962 154 17.49 11.49 15.84 1 443.46 287.64 55492 +1962 155 21.66 15.66 20.01 0.5 560.39 277.45 55572 +1962 156 23.38 17.38 21.73 0.1 615.73 272.66 55648 +1962 157 18.38 12.38 16.73 0 466.49 381.53 55719 +1962 158 18.12 12.12 16.47 0 459.66 382.5 55786 +1962 159 15.9 9.9 14.25 0 404.71 389.06 55849 +1962 160 15.11 9.11 13.46 0 386.56 391.31 55908 +1962 161 18.59 12.59 16.94 0 472.07 381.55 55962 +1962 162 20.53 14.53 18.88 0.04 526.38 281.4 56011 +1962 163 16.11 10.11 14.46 0.72 409.66 291.78 56056 +1962 164 17.23 11.23 15.58 0.04 436.91 289.46 56097 +1962 165 17.18 11.18 15.53 0 435.66 386.19 56133 +1962 166 15.14 9.14 13.49 0 387.24 391.81 56165 +1962 167 18.13 12.13 16.48 0 459.92 383.41 56192 +1962 168 22.56 16.56 20.91 0 588.79 368.14 56214 +1962 169 23.66 17.66 22.01 0 625.16 363.71 56231 +1962 170 26.23 20.23 24.58 0 717.62 352.23 56244 +1962 171 25.76 19.76 24.11 0 699.9 354.51 56252 +1962 172 24.66 18.66 23.01 0.35 659.86 269.61 56256 +1962 173 24.71 18.71 23.06 0 661.64 359.25 56255 +1962 174 19.09 13.09 17.44 0 485.59 380.44 56249 +1962 175 21.5 15.5 19.85 0.76 555.46 279.08 56238 +1962 176 18.73 12.73 17.08 0.05 475.82 286.14 56223 +1962 177 18.61 12.61 16.96 0.78 472.61 286.34 56203 +1962 178 17.63 11.63 15.98 0.3 447.01 288.6 56179 +1962 179 16.72 10.72 15.07 0.02 424.32 290.48 56150 +1962 180 12.17 6.17 10.52 0 324.99 398.35 56116 +1962 181 12.41 6.41 10.76 0 329.68 397.76 56078 +1962 182 17.44 11.44 15.79 0 442.19 384.91 56035 +1962 183 19.2 13.2 17.55 0 488.61 379.32 55987 +1962 184 20.95 14.95 19.3 0 538.81 373.22 55935 +1962 185 21.63 15.63 19.98 0.23 559.46 278 55879 +1962 186 23.78 17.78 22.13 0 629.24 361.95 55818 +1962 187 23.02 17.02 21.37 0 603.78 364.87 55753 +1962 188 22.52 16.52 20.87 0.03 587.51 274.94 55684 +1962 189 22.51 16.51 20.86 0.19 587.18 274.83 55611 +1962 190 20.95 14.95 19.3 0.45 538.81 278.91 55533 +1962 191 21.14 15.14 19.49 0.16 544.51 278.2 55451 +1962 192 21.03 15.03 19.38 0 541.2 371.03 55366 +1962 193 20.91 14.91 19.26 0 537.61 371.19 55276 +1962 194 21.78 15.78 20.13 0 564.11 367.8 55182 +1962 195 20.21 14.21 18.56 0 517.07 373.12 55085 +1962 196 18.11 12.11 16.46 0.02 459.4 284.58 54984 +1962 197 19.21 13.21 17.56 0 488.88 375.56 54879 +1962 198 24.03 18.03 22.38 0.03 637.82 268.02 54770 +1962 199 23.03 17.03 21.38 0.12 604.11 270.83 54658 +1962 200 22 16 20.35 0.05 570.98 273.52 54542 +1962 201 23.1 17.1 21.45 1.43 606.42 269.98 54423 +1962 202 19.42 13.42 17.77 0.38 494.69 279.49 54301 +1962 203 18.66 12.66 17.01 2.64 473.94 280.91 54176 +1962 204 22.06 16.06 20.41 0.25 572.86 271.83 54047 +1962 205 24.29 18.29 22.64 0 646.84 353.05 53915 +1962 206 24.04 18.04 22.39 0 638.16 353.55 53780 +1962 207 26.54 20.54 24.89 0 729.52 341.75 53643 +1962 208 19.94 13.94 18.29 0.15 509.33 275.65 53502 +1962 209 21.44 15.44 19.79 1.13 553.62 271.28 53359 +1962 210 16.19 10.19 14.54 0.89 411.56 283.04 53213 +1962 211 18.75 12.75 17.1 1.58 476.36 276.95 53064 +1962 212 15.99 9.99 14.34 2.86 406.83 282.23 52913 +1962 213 16.22 10.22 14.57 0.82 412.27 281.19 52760 +1962 214 19.62 13.62 17.97 0.22 500.28 273.16 52604 +1962 215 18.82 12.82 17.17 0.89 478.25 274.53 52445 +1962 216 19.05 13.05 17.4 0.41 484.5 273.23 52285 +1962 217 20.03 14.03 18.38 0.16 511.9 270.22 52122 +1962 218 20.35 14.35 18.7 0.2 521.12 268.81 51958 +1962 219 21.36 15.36 19.71 0 551.18 353.92 51791 +1962 220 27.13 21.13 25.48 0 752.62 329.1 51622 +1962 221 25.51 19.51 23.86 0 690.62 335.63 51451 +1962 222 23.42 17.42 21.77 0.17 617.07 257.49 51279 +1962 223 22.25 16.25 20.6 0 578.87 346.64 51105 +1962 224 23.68 17.68 22.03 0 625.84 340.16 50929 +1962 225 23.37 17.37 21.72 0 615.39 340.26 50751 +1962 226 26.27 20.27 24.62 0 719.15 326.96 50572 +1962 227 23.36 17.36 21.71 0 615.06 337.94 50392 +1962 228 24.94 18.94 23.29 0 669.86 330.4 50210 +1962 229 23.18 17.18 21.53 0 609.06 336.24 50026 +1962 230 26.29 20.29 24.64 0 719.91 322.14 49842 +1962 231 23.89 17.89 22.24 0 633 330.83 49656 +1962 232 24.18 18.18 22.53 0 643.01 328.38 49469 +1962 233 27 21 25.35 0 747.48 314.9 49280 +1962 234 26.89 20.89 25.24 0.1 743.15 235.56 49091 +1962 235 28.14 22.14 26.49 0.01 793.6 230.08 48900 +1962 236 24.26 18.26 22.61 0 645.79 322.53 48709 +1962 237 23.87 17.87 22.22 0 632.32 322.47 48516 +1962 238 26.1 20.1 24.45 0 712.68 311.75 48323 +1962 239 25.17 19.17 23.52 0.37 678.18 235.69 48128 +1962 240 25.46 19.46 23.81 0.52 688.78 233.53 47933 +1962 241 22.27 16.27 20.62 0 579.51 321.86 47737 +1962 242 26.84 20.84 25.19 0 741.19 302.19 47541 +1962 243 27.15 21.15 25.5 0.01 753.41 224.3 47343 +1962 244 16.91 10.91 15.26 0 428.97 332.42 47145 +1962 245 17.46 11.46 15.81 0 442.7 329.16 46947 +1962 246 19.67 13.67 18.02 0 501.68 321.1 46747 +1962 247 18.4 12.4 16.75 0.04 467.02 242.13 46547 +1962 248 18.58 12.58 16.93 0.71 471.8 240.31 46347 +1962 249 20.31 14.31 18.66 0.1 519.96 235.06 46146 +1962 250 18.96 12.96 17.31 0 482.04 315.38 45945 +1962 251 21.75 15.75 20.1 0 563.17 304.96 45743 +1962 252 17.81 11.81 16.16 0.12 451.62 235.64 45541 +1962 253 20.28 14.28 18.63 0 519.09 305.31 45339 +1962 254 18 12 16.35 0.05 456.53 232.09 45136 +1962 255 19.46 13.46 17.81 2.98 495.8 227.5 44933 +1962 256 16.38 10.38 14.73 1.51 416.09 231.66 44730 +1962 257 14.53 8.53 12.88 0.5 373.68 233.05 44527 +1962 258 12.72 6.72 11.07 0.16 335.82 233.89 44323 +1962 259 11.01 5.01 9.36 0.05 303.11 234.26 44119 +1962 260 16.65 10.65 15 0 422.61 298.92 43915 +1962 261 18.14 12.14 16.49 0.02 460.18 219.7 43711 +1962 262 18.21 12.21 16.56 0 462.01 290.41 43507 +1962 263 18.67 12.67 17.02 0 474.21 286.83 43303 +1962 264 18.32 12.32 16.67 0.86 464.91 213.87 43099 +1962 265 17.82 11.82 16.17 0.01 451.88 213.03 42894 +1962 266 18.46 12.46 16.81 0.3 468.61 210.04 42690 +1962 267 19.5 13.5 17.85 0.13 496.92 206.1 42486 +1962 268 19.02 13.02 17.37 0.14 483.68 205.14 42282 +1962 269 19.35 13.35 17.7 0.51 492.75 202.67 42078 +1962 270 19.4 13.4 17.75 0.21 494.14 200.65 41875 +1962 271 17.92 11.92 16.27 0 454.46 268.53 41671 +1962 272 15.41 9.41 13.76 0 393.37 271.16 41468 +1962 273 15.25 9.25 13.6 0.01 389.73 201.71 41265 +1962 274 6.91 0.91 5.26 0 235.6 278.84 41062 +1962 275 9.21 3.21 7.56 0 271.67 273.17 40860 +1962 276 10.01 4.01 8.36 0 285.28 269.34 40658 +1962 277 11.29 5.29 9.64 0.48 308.27 198.61 40456 +1962 278 15.43 9.43 13.78 0 393.83 255.02 40255 +1962 279 13.85 7.85 12.2 0 359.05 255.04 40054 +1962 280 11.32 5.32 9.67 0 308.83 256.35 39854 +1962 281 9.61 3.61 7.96 0.08 278.4 191.95 39654 +1962 282 9.2 3.2 7.55 0 271.5 253.66 39455 +1962 283 11.05 5.05 9.4 0 303.84 248.37 39256 +1962 284 11.92 5.92 10.27 0 320.16 244.1 39058 +1962 285 15.08 9.08 13.43 0 385.89 236.43 38861 +1962 286 14.78 8.78 13.13 0.24 379.19 175.66 38664 +1962 287 15.01 9.01 13.36 0.04 384.31 173.19 38468 +1962 288 13.91 7.91 12.26 0.07 360.32 172.48 38273 +1962 289 11.46 5.46 9.81 1.03 311.44 173.2 38079 +1962 290 10.25 4.25 8.6 0.43 289.48 172.22 37885 +1962 291 7.76 1.76 6.11 0 248.42 229.74 37693 +1962 292 8.78 2.78 7.13 0 264.59 225.91 37501 +1962 293 13.67 7.67 12.02 0.01 355.26 162.63 37311 +1962 294 14.06 8.06 12.41 0 363.52 213.39 37121 +1962 295 15.45 9.45 13.8 0.04 394.29 156.31 36933 +1962 296 19.59 13.59 17.94 0 499.44 198.31 36745 +1962 297 14.33 8.33 12.68 0 369.33 204.95 36560 +1962 298 17.69 11.69 16.04 0 448.55 196.86 36375 +1962 299 20.41 14.41 18.76 0 522.87 188.89 36191 +1962 300 18.92 12.92 17.27 0.21 480.96 142.01 36009 +1962 301 18.23 12.23 16.58 0.58 462.54 141.16 35829 +1962 302 16.99 10.99 15.34 0 430.95 187.86 35650 +1962 303 17.49 11.49 15.84 0.15 443.46 138.39 35472 +1962 304 13.72 7.72 12.07 0 356.31 187.88 35296 +1962 305 9.79 3.79 8.14 0 281.48 189.87 35122 +1962 306 8.17 2.17 6.52 0.36 254.81 141.92 34950 +1962 307 9.33 3.33 7.68 0.68 273.67 139.19 34779 +1962 308 9.44 3.44 7.79 0 275.52 182.87 34610 +1962 309 7.39 1.39 5.74 0 242.76 182.47 34444 +1962 310 8.78 2.78 7.13 0 264.59 178.76 34279 +1962 311 8.73 2.73 7.08 0 263.77 176.63 34116 +1962 312 9.73 3.73 8.08 0.75 280.45 129.78 33956 +1962 313 8.09 2.09 6.44 0.05 253.55 129.34 33797 +1962 314 5.34 -0.66 3.69 0 213.41 172.7 33641 +1962 315 6.27 0.27 4.62 0 226.32 169.46 33488 +1962 316 3.86 -2.14 2.21 0.13 194.16 126.73 33337 +1962 317 1.21 -4.79 -0.44 0 163.42 168.33 33188 +1962 318 4.44 -1.56 2.79 0.31 201.52 123.01 33042 +1962 319 3.39 -2.61 1.74 0.08 188.37 122.23 32899 +1962 320 2.72 -3.28 1.07 0.54 180.38 121.11 32758 +1962 321 5.48 -0.52 3.83 2.44 215.31 118.19 32620 +1962 322 1.76 -4.24 0.11 2.23 169.43 118.53 32486 +1962 323 2.39 -3.61 0.74 0.19 176.55 117.04 32354 +1962 324 5.39 -0.61 3.74 0.21 214.09 114.1 32225 +1962 325 6.86 0.86 5.21 0 234.86 149.37 32100 +1962 326 9.87 3.87 8.22 0 282.86 145.49 31977 +1962 327 10.53 4.53 8.88 0.31 294.44 107.31 31858 +1962 328 7.52 1.52 5.87 0.35 244.74 107.72 31743 +1962 329 10.36 4.36 8.71 0.06 291.42 104.86 31631 +1962 330 12.15 6.15 10.5 0.79 324.6 102.54 31522 +1962 331 5.88 -0.12 4.23 3.6 220.83 105.4 31417 +1962 332 4.86 -1.14 3.21 1.47 206.99 104.66 31316 +1962 333 3.83 -2.17 2.18 1.84 193.79 104.3 31218 +1962 334 3.13 -2.87 1.48 0.49 185.23 103.77 31125 +1962 335 -3.58 -9.58 -5.23 0 118.4 140.1 31035 +1962 336 -2.55 -8.55 -4.2 0 127.05 138.64 30949 +1962 337 -2.27 -8.27 -3.92 0 129.49 136.86 30867 +1962 338 -2.63 -8.63 -4.28 0 126.36 136.03 30790 +1962 339 -0.27 -6.27 -1.92 0 148.15 134.3 30716 +1962 340 -2.76 -8.76 -4.41 0 125.24 134.52 30647 +1962 341 -2.53 -8.53 -4.18 0.2 127.22 143.92 30582 +1962 342 -3.53 -9.53 -5.18 0.06 118.81 143.87 30521 +1962 343 -4.27 -10.27 -5.92 0 112.9 176.63 30465 +1962 344 -7.43 -13.43 -9.08 0 90.44 176.45 30413 +1962 345 -3.2 -9.2 -4.85 0 121.53 174.84 30366 +1962 346 2.56 -3.44 0.91 0 178.51 171.63 30323 +1962 347 1.34 -4.66 -0.31 0.01 164.82 139.59 30284 +1962 348 1.15 -4.85 -0.5 0 162.78 171.12 30251 +1962 349 4.64 -1.36 2.99 0 204.11 125.18 30221 +1962 350 2.8 -3.2 1.15 0 181.32 125.83 30197 +1962 351 0.49 -5.51 -1.16 0 155.83 126.68 30177 +1962 352 -0.46 -6.46 -2.11 0 146.29 126.98 30162 +1962 353 -1.4 -7.4 -3.05 0 137.34 127.28 30151 +1962 354 2.07 -3.93 0.42 0 172.9 125.77 30145 +1962 355 2.22 -3.78 0.57 0 174.6 125.69 30144 +1962 356 1.5 -4.5 -0.15 0 166.57 126.06 30147 +1962 357 2.99 -3.01 1.34 0 183.56 125.4 30156 +1962 358 -1.34 -7.34 -2.99 0 137.9 127.4 30169 +1962 359 -2.81 -8.81 -4.46 0 124.82 128.05 30186 +1962 360 -3.79 -9.79 -5.44 0.96 116.71 143.3 30208 +1962 361 -0.7 -6.7 -2.35 0.41 143.96 143.99 30235 +1962 362 -3.69 -9.69 -5.34 0 117.51 177.45 30267 +1962 363 -0.49 -6.49 -2.14 0.65 145.99 146.65 30303 +1962 364 -0.19 -6.19 -1.84 0 148.95 179.09 30343 +1962 365 0.78 -5.22 -0.87 0 158.85 179.07 30388 +1963 1 -3.8 -9.8 -5.45 0 116.63 181.64 30438 +1963 2 -3.8 -9.8 -5.45 0.61 116.63 151.03 30492 +1963 3 -3.8 -9.8 -5.45 0 116.63 185.07 30551 +1963 4 -3.8 -9.8 -5.45 0.06 116.63 152.43 30614 +1963 5 -3.8 -9.8 -5.45 0.9 116.63 155.62 30681 +1963 6 -3.8 -9.8 -5.45 0.18 116.63 156.74 30752 +1963 7 -3.8 -9.8 -5.45 0 116.63 191.47 30828 +1963 8 -3.8 -9.8 -5.45 0.01 116.63 158.23 30907 +1963 9 -3.8 -9.8 -5.45 0.02 116.63 159.1 30991 +1963 10 -3.8 -9.8 -5.45 0.09 116.63 160.22 31079 +1963 11 -3.8 -9.8 -5.45 0 116.63 196.34 31171 +1963 12 -3.8 -9.8 -5.45 0 116.63 197.21 31266 +1963 13 -3.8 -9.8 -5.45 0 116.63 198.68 31366 +1963 14 -3.8 -9.8 -5.45 0 116.63 200 31469 +1963 15 -3.8 -9.8 -5.45 1.14 116.63 167.81 31575 +1963 16 -3.8 -9.8 -5.45 0.89 116.63 171.3 31686 +1963 17 -3.8 -9.8 -5.45 0.82 116.63 174.84 31800 +1963 18 -3.8 -9.8 -5.45 0.26 116.63 176.84 31917 +1963 19 -3.8 -9.8 -5.45 0.55 116.63 179.72 32038 +1963 20 -3.8 -9.8 -5.45 0 116.63 219.75 32161 +1963 21 -3.8 -9.8 -5.45 0 116.63 221.54 32289 +1963 22 -3.8 -9.8 -5.45 0 116.63 223.06 32419 +1963 23 -3.8 -9.8 -5.45 0 116.63 224.61 32552 +1963 24 -3.8 -9.8 -5.45 0.45 116.63 186.77 32688 +1963 25 -3.8 -9.8 -5.45 0.57 116.63 189.6 32827 +1963 26 -3.8 -9.8 -5.45 0 116.63 232.76 32969 +1963 27 -3.8 -9.8 -5.45 0 116.63 234.53 33114 +1963 28 -3.8 -9.8 -5.45 0 116.63 236.49 33261 +1963 29 -3.8 -9.8 -5.45 0 116.63 238.61 33411 +1963 30 -3.8 -9.8 -5.45 0.11 116.63 196.7 33564 +1963 31 -3.8 -9.8 -5.45 0.29 116.63 199.04 33718 +1963 32 -2.86 -8.86 -4.51 0 124.39 245.32 33875 +1963 33 -2.53 -8.53 -4.18 0 127.22 247.54 34035 +1963 34 -3.23 -9.23 -4.88 0.08 121.28 203.48 34196 +1963 35 -3 -9 -4.65 0.15 123.21 205.16 34360 +1963 36 -5.41 -11.41 -7.06 0.81 104.3 209.75 34526 +1963 37 -8.99 -14.99 -10.64 0 80.86 261.02 34694 +1963 38 -6.29 -12.29 -7.94 0 98.05 262.63 34863 +1963 39 -3.75 -9.75 -5.4 0 117.03 263.97 35035 +1963 40 -1.48 -7.48 -3.13 0 136.61 265.24 35208 +1963 41 3.39 -2.61 1.74 0 188.37 264.23 35383 +1963 42 4.04 -1.96 2.39 0.03 196.42 214.96 35560 +1963 43 4.39 -1.61 2.74 0.04 200.88 215.98 35738 +1963 44 4.82 -1.18 3.17 0 206.47 268.55 35918 +1963 45 1.04 -4.96 -0.61 0.7 161.6 220.38 36099 +1963 46 2.08 -3.92 0.43 0 173.01 274.95 36282 +1963 47 6.56 0.56 4.91 0.17 230.49 219.76 36466 +1963 48 5.69 -0.31 4.04 1.43 218.19 221.52 36652 +1963 49 0.67 -5.33 -0.98 0 157.7 282.04 36838 +1963 50 -1.41 -7.41 -3.06 0 137.25 285.69 37026 +1963 51 -4 -10 -5.65 0 115.03 289.75 37215 +1963 52 -3.32 -9.32 -4.97 0 120.54 292.01 37405 +1963 53 3.42 -2.58 1.77 0.39 188.74 231.71 37596 +1963 54 -3.03 -9.03 -4.68 0 122.96 296.74 37788 +1963 55 -7.25 -13.25 -8.9 0.38 91.61 241.05 37981 +1963 56 -6.38 -12.38 -8.03 0 97.43 304.49 38175 +1963 57 -5.99 -11.99 -7.64 0 100.14 306.99 38370 +1963 58 -5.91 -11.91 -7.56 0.11 100.71 246.59 38565 +1963 59 -4.96 -10.96 -6.61 0.19 107.62 248.53 38761 +1963 60 6.06 0.06 4.41 0.33 223.35 243.94 38958 +1963 61 4.57 -1.43 2.92 0.03 203.2 246.47 39156 +1963 62 5.14 -0.86 3.49 0 210.72 311.75 39355 +1963 63 5.57 -0.43 3.92 0 216.54 313.5 39553 +1963 64 7.54 1.54 5.89 0 245.04 313.27 39753 +1963 65 8.42 2.42 6.77 0.03 258.78 248.31 39953 +1963 66 8.13 2.13 6.48 1.25 254.18 249.54 40154 +1963 67 6.59 0.59 4.94 0 230.92 319.77 40355 +1963 68 5.99 -0.01 4.34 0 222.37 322.46 40556 +1963 69 5.35 -0.65 3.7 0 213.54 325 40758 +1963 70 6.59 0.59 4.94 0.55 230.92 255.92 40960 +1963 71 5.52 -0.48 3.87 0.04 215.86 258.22 41163 +1963 72 6.05 0.05 4.4 0 223.21 330.41 41366 +1963 73 7.42 1.42 5.77 0.01 243.22 258.98 41569 +1963 74 10.86 4.86 9.21 0 300.38 327.35 41772 +1963 75 6.68 0.68 5.03 0 232.23 334.81 41976 +1963 76 9.76 3.76 8.11 0.38 280.97 259.47 42179 +1963 77 4.61 -1.39 2.96 0 203.72 340.61 42383 +1963 78 6.72 0.72 5.07 0 232.81 340.1 42587 +1963 79 7.91 1.91 6.26 0 250.74 340.42 42791 +1963 80 7.77 1.77 6.12 0 248.57 342.23 42996 +1963 81 8.56 2.56 6.91 0 261.02 342.77 43200 +1963 82 4.37 -1.63 2.72 0.03 200.62 271.49 43404 +1963 83 4.94 -1.06 3.29 0 208.05 351.23 43608 +1963 84 0.62 -5.38 -1.03 0 157.18 357.76 43812 +1963 85 0.43 -5.57 -1.22 0 155.21 360.27 44016 +1963 86 4.88 -1.12 3.23 0 207.26 357.8 44220 +1963 87 3.47 -2.53 1.82 0 189.35 361.42 44424 +1963 88 4.13 -1.87 2.48 0 197.56 362.58 44627 +1963 89 9.47 3.47 7.82 0 276.03 356.97 44831 +1963 90 5.79 -0.21 4.14 0 219.58 363.72 45034 +1963 91 12.37 6.37 10.72 0 328.89 354.78 45237 +1963 92 18.35 12.35 16.7 0 465.7 313.1 45439 +1963 93 20.67 14.67 19.02 0.02 530.49 231.47 45642 +1963 94 21.13 15.13 19.48 0.11 544.21 231.93 45843 +1963 95 15.07 9.07 13.42 0 385.66 327.38 46045 +1963 96 10.26 4.26 8.61 0.18 289.65 254.07 46246 +1963 97 13.74 7.74 12.09 0.18 356.73 250.75 46446 +1963 98 17.48 11.48 15.83 0 443.2 327.57 46647 +1963 99 15.79 9.79 14.14 0.02 402.14 250.28 46846 +1963 100 11.14 5.14 9.49 0.07 305.5 258.92 47045 +1963 101 10.21 4.21 8.56 0 288.77 348.79 47243 +1963 102 16.49 10.49 14.84 0 418.74 337.67 47441 +1963 103 16.38 10.38 14.73 0 416.09 339.75 47638 +1963 104 16.25 10.25 14.6 0 412.98 341.86 47834 +1963 105 15.49 9.49 13.84 0 395.2 345.46 48030 +1963 106 14.85 8.85 13.2 0.16 380.74 261.43 48225 +1963 107 11.19 5.19 9.54 0.02 306.42 268.34 48419 +1963 108 12.42 6.42 10.77 0 329.87 357.18 48612 +1963 109 14.19 8.19 12.54 0.86 366.3 266.28 48804 +1963 110 17.17 11.17 15.52 0 435.41 349.16 48995 +1963 111 14.18 8.18 12.53 0 366.09 358.01 49185 +1963 112 10.54 4.54 8.89 0.49 294.62 275.15 49374 +1963 113 11.01 5.01 9.36 1.43 303.11 275.52 49561 +1963 114 10.78 4.78 9.13 0.08 298.93 276.97 49748 +1963 115 8.2 2.2 6.55 0 255.28 375.14 49933 +1963 116 9.84 3.84 8.19 0.31 282.34 280.25 50117 +1963 117 9.65 3.65 8 0.06 279.08 281.49 50300 +1963 118 10.69 4.69 9.04 0.11 297.3 281.1 50481 +1963 119 14.18 8.18 12.53 0.03 366.09 276.59 50661 +1963 120 17.27 11.27 15.62 0 437.91 362.16 50840 +1963 121 16.49 10.49 14.84 0.02 418.74 274.04 51016 +1963 122 15.87 9.87 14.22 0.04 404.01 276.13 51191 +1963 123 13.37 7.37 11.72 0 349.02 375.15 51365 +1963 124 10.16 4.16 8.51 0 287.9 382.67 51536 +1963 125 12.76 6.76 11.11 0 336.62 378.55 51706 +1963 126 10.12 4.12 8.47 0.01 287.2 288.58 51874 +1963 127 10.2 4.2 8.55 0 288.6 385.53 52039 +1963 128 14.17 8.17 12.52 0 365.87 378.3 52203 +1963 129 16.34 10.34 14.69 0.18 415.13 280.3 52365 +1963 130 15.41 9.41 13.76 0 393.37 376.94 52524 +1963 131 17.37 11.37 15.72 0 440.43 372.48 52681 +1963 132 25.77 19.77 24.12 0 700.27 342.7 52836 +1963 133 27.41 21.41 25.76 0.16 763.8 251.64 52989 +1963 134 26.33 20.33 24.68 1.39 721.44 256.06 53138 +1963 135 21.16 15.16 19.51 0.33 545.11 272.48 53286 +1963 136 23.77 17.77 22.12 1.18 628.9 265.46 53430 +1963 137 25.61 19.61 23.96 1.34 694.32 259.98 53572 +1963 138 21.66 15.66 20.01 0 560.39 363.39 53711 +1963 139 20.88 14.88 19.23 0 536.72 366.86 53848 +1963 140 18.15 12.15 16.5 0 460.44 376.21 53981 +1963 141 14.19 8.19 12.54 0 366.3 387.27 54111 +1963 142 16.4 10.4 14.75 0 416.57 382.15 54238 +1963 143 15.66 9.66 14.01 0 399.12 384.65 54362 +1963 144 16.09 10.09 14.44 0 409.18 384 54483 +1963 145 15.38 9.38 13.73 0 392.69 386.33 54600 +1963 146 15.95 9.95 14.3 0 405.89 385.22 54714 +1963 147 14.23 8.23 12.58 0 367.17 390.05 54824 +1963 148 16.34 10.34 14.69 0 415.13 385.04 54931 +1963 149 18.17 12.17 16.52 0.26 460.97 285.07 55034 +1963 150 16.69 10.69 15.04 0.01 423.59 288.55 55134 +1963 151 17.01 11.01 15.36 0 431.44 384.22 55229 +1963 152 23.25 17.25 21.6 0.11 611.39 272.28 55321 +1963 153 17.89 11.89 16.24 0.46 453.69 286.51 55409 +1963 154 21.43 15.43 19.78 0.25 553.32 277.95 55492 +1963 155 22.37 16.37 20.72 1.09 582.7 275.43 55572 +1963 156 25.04 19.04 23.39 0.17 673.47 267.33 55648 +1963 157 26.17 20.17 24.52 0 715.34 351.39 55719 +1963 158 26.37 20.37 24.72 0.03 722.97 262.95 55786 +1963 159 26.42 20.42 24.77 2.19 724.89 262.94 55849 +1963 160 25.25 19.25 23.6 0 681.09 356.24 55908 +1963 161 18.74 12.74 17.09 0 476.09 381.08 55962 +1963 162 17.87 11.87 16.22 0 453.17 383.81 56011 +1963 163 17.32 11.32 15.67 0.28 439.17 289.23 56056 +1963 164 19.32 13.32 17.67 0 491.92 379.54 56097 +1963 165 21.87 15.87 20.22 0 566.91 370.69 56133 +1963 166 22.39 16.39 20.74 0 583.34 368.78 56165 +1963 167 23.04 17.04 21.39 0 604.44 366.16 56192 +1963 168 23.24 17.24 21.59 0 611.06 365.43 56214 +1963 169 23.72 17.72 22.07 0 627.2 363.46 56231 +1963 170 24.19 18.19 22.54 0.49 643.35 271.11 56244 +1963 171 25.52 19.52 23.87 1.37 690.99 266.72 56252 +1963 172 25.19 19.19 23.54 0.04 678.9 267.84 56256 +1963 173 25.6 19.6 23.95 0.09 693.95 266.42 56255 +1963 174 24.17 18.17 22.52 0.04 642.66 271.13 56249 +1963 175 25.44 19.44 23.79 0 688.04 355.86 56238 +1963 176 17.78 11.78 16.13 0.78 450.85 288.32 56223 +1963 177 18.15 12.15 16.5 0.29 460.44 287.41 56203 +1963 178 16.13 10.13 14.48 0.04 410.13 291.78 56179 +1963 179 12.43 6.43 10.78 0 330.07 397.92 56150 +1963 180 15.21 9.21 13.56 0.02 388.82 293.43 56116 +1963 181 16.75 10.75 15.1 0.55 425.05 290.27 56078 +1963 182 18.55 12.55 16.9 0.4 471 286.17 56035 +1963 183 18.15 12.15 16.5 0 460.44 382.61 55987 +1963 184 23.1 17.1 21.45 0 606.42 365.07 55935 +1963 185 23.51 17.51 21.86 0 620.09 363.32 55879 +1963 186 19.19 13.19 17.54 0 488.33 378.85 55818 +1963 187 20.57 14.57 18.92 0 527.55 374.04 55753 +1963 188 24.99 18.99 23.34 0 671.66 356.28 55684 +1963 189 27.3 21.3 25.65 0 759.39 345.14 55611 +1963 190 25.89 19.89 24.24 0 704.76 351.64 55533 +1963 191 29.25 23.25 27.6 0 840.8 334.16 55451 +1963 192 27.06 21.06 25.41 0 749.85 345.45 55366 +1963 193 29.56 23.56 27.91 0 854.4 331.89 55276 +1963 194 25.47 19.47 23.82 0.03 689.15 264.42 55182 +1963 195 23.72 17.72 22.07 0.37 627.2 269.94 55085 +1963 196 21.49 15.49 19.84 0.33 555.15 276.15 54984 +1963 197 22.61 16.61 20.96 0 590.41 363.52 54879 +1963 198 24.94 18.94 23.29 0 669.86 353.44 54770 +1963 199 26.76 20.76 25.11 0 738.06 344.66 54658 +1963 200 29.25 23.25 27.6 0 840.8 331.31 54542 +1963 201 27.91 21.91 26.26 0 784.11 338.06 54423 +1963 202 27.15 21.15 25.5 0 753.41 341.38 54301 +1963 203 22.69 16.69 21.04 0 593 360.54 54176 +1963 204 18.87 12.87 17.22 0 479.6 373.38 54047 +1963 205 21.72 15.72 20.07 1.34 562.24 272.4 53915 +1963 206 25.56 19.56 23.91 0.2 692.47 260.2 53780 +1963 207 22.83 16.83 21.18 1.22 597.55 268.34 53643 +1963 208 23.53 17.53 21.88 0.54 620.77 265.78 53502 +1963 209 23.81 17.81 22.16 0.02 630.27 264.45 53359 +1963 210 23.19 17.19 21.54 0.1 609.4 265.87 53213 +1963 211 26.55 20.55 24.9 0 729.9 339.13 53064 +1963 212 24.4 18.4 22.75 0.07 650.69 261.01 52913 +1963 213 23.31 17.31 21.66 0 613.39 351.73 52760 +1963 214 23.54 17.54 21.89 0 621.1 350.09 52604 +1963 215 23.67 17.67 22.02 0.21 625.5 261.68 52445 +1963 216 23.94 17.94 22.29 0 634.72 346.82 52285 +1963 217 26.69 20.69 25.04 0.23 735.33 250.38 52122 +1963 218 24.06 18.06 22.41 0.14 638.85 258.51 51958 +1963 219 23.53 17.53 21.88 1.18 620.77 259.35 51791 +1963 220 24.36 18.36 22.71 0 649.28 341.51 51622 +1963 221 28.05 22.05 26.4 0.24 789.88 242.71 51451 +1963 222 29.83 23.83 28.18 0.07 866.39 234.92 51279 +1963 223 30.03 24.03 28.38 1.67 875.37 233.3 51105 +1963 224 32.27 26.27 30.62 0.27 981.36 222.65 50929 +1963 225 26.95 20.95 25.3 0.45 745.51 243.67 50751 +1963 226 24.24 18.24 22.59 2.27 645.09 251.77 50572 +1963 227 21.97 15.97 20.32 0.52 570.04 257.33 50392 +1963 228 21.76 15.76 20.11 0 563.48 342.66 50210 +1963 229 22.63 16.63 20.98 0 591.05 338.3 50026 +1963 230 20.75 14.75 19.1 0.44 532.86 257.72 49842 +1963 231 21.95 15.95 20.3 0.42 569.41 253.55 49656 +1963 232 21.67 15.67 20.02 0 560.7 337.72 49469 +1963 233 22.66 16.66 21.01 0.46 592.02 249.6 49280 +1963 234 19.3 13.3 17.65 0.49 491.36 256.92 49091 +1963 235 16.76 10.76 15.11 4.49 425.29 261.12 48900 +1963 236 14.99 8.99 13.34 0.82 383.87 263.29 48709 +1963 237 17.37 11.37 15.72 0.2 440.43 257.58 48516 +1963 238 19.23 13.23 17.58 0 489.43 336.54 48323 +1963 239 19.16 13.16 17.51 0.07 487.51 251.43 48128 +1963 240 20.77 14.77 19.12 0.07 533.45 246.42 47933 +1963 241 18.93 12.93 17.28 0.54 481.23 249.32 47737 +1963 242 17.53 11.53 15.88 0.27 444.47 250.91 47541 +1963 243 16.98 10.98 15.33 0.03 430.7 250.57 47343 +1963 244 13.33 7.33 11.68 0 348.2 340.57 47145 +1963 245 19.14 13.14 17.49 0.01 486.96 243.44 46947 +1963 246 17.41 11.41 15.76 0.04 441.43 245.49 46747 +1963 247 14.93 8.93 13.28 0 382.52 331.37 46547 +1963 248 12.21 6.21 10.56 0.02 325.76 251.2 46347 +1963 249 14.46 8.46 12.81 0.27 372.15 246.24 46146 +1963 250 18.95 12.95 17.3 0.01 481.77 236.55 45945 +1963 251 17.91 11.91 16.26 0.01 454.2 237.06 45743 +1963 252 18.56 12.56 16.91 0.01 471.27 234.17 45541 +1963 253 19.49 13.49 17.84 0.05 496.64 230.68 45339 +1963 254 18.02 12.02 16.37 0.61 457.05 232.06 45136 +1963 255 18.37 12.37 16.72 0.17 466.23 229.69 44933 +1963 256 21.93 15.93 20.28 0.1 568.78 220.33 44730 +1963 257 23.07 17.07 21.42 2.12 605.43 215.98 44527 +1963 258 18.26 12.26 16.61 2.58 463.33 224.87 44323 +1963 259 16.58 10.58 14.93 0 420.91 301.46 44119 +1963 260 19.98 13.98 18.33 0.6 510.47 217.88 43915 +1963 261 20.98 14.98 19.33 0.06 539.7 213.95 43711 +1963 262 18.07 12.07 16.42 0 458.35 290.75 43507 +1963 263 23.43 17.43 21.78 0 617.4 273 43303 +1963 264 23.29 17.29 21.64 0 612.72 271.02 43099 +1963 265 19.34 13.34 17.69 0 492.47 280.26 42894 +1963 266 18.79 12.79 17.14 0 477.44 279.23 42690 +1963 267 18.42 12.42 16.77 0 467.55 277.51 42486 +1963 268 20.96 14.96 19.31 0.01 539.11 201.3 42282 +1963 269 23.31 17.31 21.66 0.26 613.39 194.26 42078 +1963 270 23.43 17.43 21.78 0.2 617.4 192.11 41875 +1963 271 22.88 16.88 21.23 0.49 599.18 191.53 41671 +1963 272 17.8 11.8 16.15 0.11 451.37 199.59 41468 +1963 273 23.7 17.7 22.05 0 626.52 247.88 41265 +1963 274 15.82 9.82 14.17 0 402.84 265.17 41062 +1963 275 13.6 7.6 11.95 0 353.8 266.52 40860 +1963 276 10.66 4.66 9.01 0 296.77 268.43 40658 +1963 277 10.06 4.06 8.41 0 286.15 266.56 40456 +1963 278 12.36 6.36 10.71 0 328.69 260.29 40255 +1963 279 9.8 3.8 8.15 0 281.65 261.14 40054 +1963 280 12.79 6.79 11.14 0 337.22 254.13 39854 +1963 281 11.95 5.95 10.3 0.12 320.74 189.51 39654 +1963 282 16.14 10.14 14.49 0 410.37 242.88 39455 +1963 283 13 7 11.35 0.47 341.45 184.12 39256 +1963 284 12.86 6.86 11.21 0.02 338.63 182.02 39058 +1963 285 11.26 5.26 9.61 0 307.72 242.38 38861 +1963 286 10.85 4.85 9.2 0.89 300.2 180.11 38664 +1963 287 13.06 7.06 11.41 0.42 342.67 175.54 38468 +1963 288 12.8 6.8 11.15 0.08 337.42 173.75 38273 +1963 289 16.09 10.09 14.44 0.28 409.18 167.78 38079 +1963 290 15.41 9.41 13.76 1.17 393.37 166.56 37885 +1963 291 9.89 3.89 8.24 0.18 283.2 170.5 37693 +1963 292 9.6 3.6 7.95 0.03 278.23 168.73 37501 +1963 293 12.16 6.16 10.51 0 324.79 218.99 37311 +1963 294 11.41 5.41 9.76 0 310.51 217.1 37121 +1963 295 11.37 5.37 9.72 0.01 309.76 160.74 36933 +1963 296 14.7 8.7 13.05 0.03 377.42 155.3 36745 +1963 297 15.35 9.35 13.7 0.1 392 152.53 36560 +1963 298 18.2 12.2 16.55 0.04 461.75 146.95 36375 +1963 299 18.89 12.89 17.24 0 480.14 191.95 36191 +1963 300 14.69 8.69 13.04 0 377.2 196.49 36009 +1963 301 15.5 9.5 13.85 0.16 395.43 144.6 35829 +1963 302 13.08 7.08 11.43 0.76 343.08 145.28 35650 +1963 303 11.6 5.6 9.95 0.16 314.07 144.76 35472 +1963 304 10.92 4.92 9.27 0.01 301.47 143.52 35296 +1963 305 10.46 4.46 8.81 0 293.19 189.15 35122 +1963 306 6.61 0.61 4.96 1 231.21 142.97 34950 +1963 307 7.83 1.83 6.18 0.13 249.5 140.27 34779 +1963 308 11.57 5.57 9.92 0 313.51 180.58 34610 +1963 309 13.23 7.23 11.58 0.03 346.14 132.23 34444 +1963 310 11.4 5.4 9.75 0 310.32 176.07 34279 +1963 311 11.73 5.73 10.08 0.31 316.53 130.16 34116 +1963 312 8.52 2.52 6.87 0.5 260.38 130.64 33956 +1963 313 8.08 2.08 6.43 0.2 253.4 129.35 33797 +1963 314 10.64 4.64 8.99 0 296.41 168.08 33641 +1963 315 9.28 3.28 7.63 0.02 272.84 125.17 33488 +1963 316 11.62 5.62 9.97 0 314.45 162.39 33337 +1963 317 13.68 7.68 12.03 0 355.47 157.91 33188 +1963 318 15.69 9.69 14.04 0 399.82 153.08 33042 +1963 319 17.23 11.23 15.58 0.12 436.91 111.98 32899 +1963 320 15.2 9.2 13.55 0 388.59 150.3 32758 +1963 321 15.92 9.92 14.27 0.11 405.18 110.49 32620 +1963 322 12.97 6.97 11.32 0.5 340.85 111.85 32486 +1963 323 11.39 5.39 9.74 0 310.13 149.22 32354 +1963 324 11.15 5.15 9.5 0.2 305.68 110.57 32225 +1963 325 12.66 6.66 11.01 0.64 334.62 108.16 32100 +1963 326 11.4 5.4 9.75 0.1 310.32 108.06 31977 +1963 327 8.22 2.22 6.57 0.15 255.6 108.78 31858 +1963 328 7.02 1.02 5.37 0.54 237.22 108 31743 +1963 329 7.39 1.39 5.74 1.14 242.76 106.68 31631 +1963 330 10.26 4.26 8.61 0.37 289.65 103.86 31522 +1963 331 11.62 5.62 9.97 0 314.45 135.94 31417 +1963 332 12.48 6.48 10.83 0.01 331.05 100.12 31316 +1963 333 13.78 7.78 12.13 0 357.57 131.11 31218 +1963 334 16.9 10.9 15.25 0.19 428.73 94.8 31125 +1963 335 1.43 -4.57 -0.22 0 165.8 138.05 31035 +1963 336 -1.66 -7.66 -3.31 0.37 134.96 147.53 30949 +1963 337 -2.64 -8.64 -4.29 0.22 126.27 147.34 30867 +1963 338 -0.91 -6.91 -2.56 0.57 141.95 148.02 30790 +1963 339 1.21 -4.79 -0.44 0.15 163.42 146.68 30716 +1963 340 -0.52 -6.52 -2.17 0.04 145.7 146.92 30647 +1963 341 -2.73 -8.73 -4.38 0 125.5 180.35 30582 +1963 342 0.6 -5.4 -1.05 0 156.97 178.27 30521 +1963 343 1.05 -4.95 -0.6 0 161.71 177.18 30465 +1963 344 -2.4 -8.4 -4.05 0 128.35 177.52 30413 +1963 345 -3.74 -9.74 -5.39 0 117.11 177.61 30366 +1963 346 -4.55 -10.55 -6.2 0 110.73 177.37 30323 +1963 347 -7.19 -13.19 -8.84 0.82 92 147.52 30284 +1963 348 -3.67 -9.67 -5.32 0.14 117.67 147 30251 +1963 349 -1.91 -7.91 -3.56 0 132.69 178.35 30221 +1963 350 2.83 -3.17 1.18 0 181.67 175.63 30197 +1963 351 3 -3 1.35 0 183.68 174.96 30177 +1963 352 3.97 -2.03 2.32 0.13 195.54 142.62 30162 +1963 353 1.61 -4.39 -0.04 0.21 167.77 143.26 30151 +1963 354 -1.98 -7.98 -3.63 0 132.07 176.22 30145 +1963 355 -1.19 -7.19 -2.84 0.48 139.3 145.66 30144 +1963 356 -2.23 -8.23 -3.88 0 129.85 177.86 30147 +1963 357 1.73 -4.27 0.08 0 169.1 176.05 30156 +1963 358 0.25 -5.75 -1.4 0 153.37 176.74 30169 +1963 359 -0.97 -6.97 -2.62 0 141.38 177.33 30186 +1963 360 -1.75 -7.75 -3.4 0.03 134.14 146.04 30208 +1963 361 -1.37 -7.37 -3.02 1.06 137.62 149.51 30235 +1963 362 -6.99 -12.99 -8.64 0.01 93.31 151.14 30267 +1963 363 -11.31 -17.31 -12.96 0 68.25 185.24 30303 +1963 364 -8.91 -14.91 -10.56 0 81.33 185.09 30343 +1963 365 -5.39 -11.39 -7.04 0 104.44 184.69 30388 +1964 1 -3.4 -9.4 -5.05 0 119.88 184.88 30438 +1964 2 -3.4 -9.4 -5.05 0 119.88 185.53 30492 +1964 3 -3.4 -9.4 -5.05 0 119.88 186.39 30551 +1964 4 -3.4 -9.4 -5.05 0 119.88 187.21 30614 +1964 5 -3.4 -9.4 -5.05 0 119.88 187.75 30681 +1964 6 -3.4 -9.4 -5.05 0 119.88 188.53 30752 +1964 7 -3.4 -9.4 -5.05 0 119.88 189.21 30828 +1964 8 -3.4 -9.4 -5.05 0 119.88 190.58 30907 +1964 9 -3.4 -9.4 -5.05 0 119.88 191.72 30991 +1964 10 -3.4 -9.4 -5.05 0 119.88 192.89 31079 +1964 11 -3.4 -9.4 -5.05 0 119.88 193.74 31171 +1964 12 -3.4 -9.4 -5.05 0 119.88 194.61 31266 +1964 13 -3.4 -9.4 -5.05 0 119.88 196.09 31366 +1964 14 -3.4 -9.4 -5.05 0 119.88 197.42 31469 +1964 15 -3.4 -9.4 -5.05 0 119.88 198.71 31575 +1964 16 -3.4 -9.4 -5.05 0 119.88 199.85 31686 +1964 17 -3.4 -9.4 -5.05 0 119.88 201.37 31800 +1964 18 -3.4 -9.4 -5.05 0 119.88 203.11 31917 +1964 19 -3.4 -9.4 -5.05 0 119.88 204.87 32038 +1964 20 -3.4 -9.4 -5.05 0 119.88 206.29 32161 +1964 21 -3.4 -9.4 -5.05 0 119.88 208.13 32289 +1964 22 -3.4 -9.4 -5.05 0 119.88 209.71 32419 +1964 23 -3.4 -9.4 -5.05 0 119.88 211.3 32552 +1964 24 -3.4 -9.4 -5.05 0 119.88 213.19 32688 +1964 25 -3.4 -9.4 -5.05 0 119.88 214.9 32827 +1964 26 -3.4 -9.4 -5.05 0 119.88 216.65 32969 +1964 27 -3.4 -9.4 -5.05 0 119.88 218.49 33114 +1964 28 -3.4 -9.4 -5.05 0 119.88 220.51 33261 +1964 29 -3.4 -9.4 -5.05 0 119.88 222.71 33411 +1964 30 -3.4 -9.4 -5.05 0 119.88 224.77 33564 +1964 31 -3.4 -9.4 -5.05 0 119.88 226.96 33718 +1964 32 5.95 -0.05 4.3 0.5 221.81 178.81 33875 +1964 33 7.63 1.63 5.98 0 246.42 222.88 34035 +1964 34 4.43 -1.57 2.78 0 201.39 226.86 34196 +1964 35 5.62 -0.38 3.97 0 217.23 227.24 34360 +1964 36 7.43 1.43 5.78 0 243.37 227.16 34526 +1964 37 6.71 0.71 5.06 0 232.66 229.2 34694 +1964 38 2.01 -3.99 0.36 0 172.22 234.97 34863 +1964 39 0.98 -5.02 -0.67 0 160.96 237.91 35035 +1964 40 2.4 -3.6 0.75 0 176.66 239.18 35208 +1964 41 3.82 -2.18 2.17 0 193.66 240.18 35383 +1964 42 8.64 2.64 6.99 0 262.32 237.38 35560 +1964 43 4.52 -1.48 2.87 0 202.55 243.03 35738 +1964 44 4.22 -1.78 2.57 0 198.7 245.17 35918 +1964 45 1.91 -4.09 0.26 0.11 171.1 196.13 36099 +1964 46 0.81 -5.19 -0.84 0.39 159.17 198.42 36282 +1964 47 1.81 -4.19 0.16 0 169.99 254.02 36466 +1964 48 2.91 -3.09 1.26 0.1 182.61 200.71 36652 +1964 49 0.28 -5.72 -1.37 0 153.68 259.94 36838 +1964 50 2.34 -3.66 0.69 0 175.97 225.34 37026 +1964 51 -1.49 -7.49 -3.14 0 136.51 230.79 37215 +1964 52 -2.68 -8.68 -4.33 0 125.93 234.31 37405 +1964 53 -2.72 -8.72 -4.37 0 125.59 237.34 37596 +1964 54 0.52 -5.48 -1.13 0 156.14 238.22 37788 +1964 55 0.55 -5.45 -1.1 0 156.45 241.23 37981 +1964 56 4.22 -1.78 2.57 0 198.7 241.15 38175 +1964 57 5.98 -0.02 4.33 0 222.23 242.43 38370 +1964 58 4.68 -1.32 3.03 0 204.63 246.59 38565 +1964 59 5.02 -0.98 3.37 0 209.11 248.99 38761 +1964 60 8.04 2.04 6.39 0 252.77 248.76 38958 +1964 61 3.56 -2.44 1.91 0 190.45 256.15 39156 +1964 62 6.26 0.26 4.61 0 226.18 256.4 39355 +1964 63 8.19 2.19 6.54 0 255.13 257.27 39553 +1964 64 8.36 2.36 6.71 0 257.82 259.96 39753 +1964 65 9.87 3.87 8.22 0 282.86 260.91 39953 +1964 66 11.33 5.33 9.68 0 309.02 261.57 40154 +1964 67 7.77 1.77 6.12 2.59 248.57 201.87 40355 +1964 68 6.48 0.48 4.83 1 229.33 205.13 40556 +1964 69 7.14 1.14 5.49 0.18 239.01 206.54 40758 +1964 70 5.74 -0.26 4.09 0.32 218.88 209.85 40960 +1964 71 4.08 -1.92 2.43 0.03 196.93 213.31 41163 +1964 72 -0.68 -6.68 -2.33 0.43 144.15 251.33 41366 +1964 73 4.16 -1.84 2.51 0.62 197.94 249.76 41569 +1964 74 7 1 5.35 0.09 236.93 217.18 41772 +1964 75 2.9 -3.1 1.25 0 182.5 296.63 41976 +1964 76 -1.35 -7.35 -3 0 137.81 302.72 42179 +1964 77 0.24 -5.76 -1.41 0 153.27 304.21 42383 +1964 78 3.14 -2.86 1.49 0 185.35 304.42 42587 +1964 79 4.28 -1.72 2.63 0 199.47 306.05 42791 +1964 80 7.12 1.12 5.47 0.09 238.71 229.03 42996 +1964 81 5.82 -0.18 4.17 0 219.99 309.54 43200 +1964 82 6.86 0.86 5.21 0 234.86 310.96 43404 +1964 83 9.39 3.39 7.74 0.11 274.68 232.53 43608 +1964 84 6.81 0.81 5.16 0.3 234.13 237.07 43812 +1964 85 2.13 -3.87 0.48 0.57 173.58 242.78 44016 +1964 86 1.5 -4.5 -0.15 0 166.57 326.74 44220 +1964 87 2.27 -3.73 0.62 0 175.17 328.61 44424 +1964 88 0.25 -5.75 -1.4 0.09 153.37 249.61 44627 +1964 89 1.63 -4.37 -0.02 0 167.99 333.94 44831 +1964 90 0.15 -5.85 -1.5 0 152.36 337.67 45034 +1964 91 12.59 6.59 10.94 0.09 333.23 242.87 45237 +1964 92 12.73 6.73 11.08 0.33 336.02 244.33 45439 +1964 93 11.14 5.14 9.49 0 305.5 330.86 45642 +1964 94 11.45 5.45 9.8 0 311.26 332.46 45843 +1964 95 11.54 5.54 9.89 0.54 312.94 250.83 46045 +1964 96 16.7 10.7 15.05 1.58 423.83 244.23 46246 +1964 97 14.64 8.64 12.99 0.38 376.1 249.32 46446 +1964 98 14.23 8.23 12.58 0 367.17 335.24 46647 +1964 99 13.53 7.53 11.88 0.04 352.34 254.02 46846 +1964 100 12.35 6.35 10.7 0.14 328.5 257.24 47045 +1964 101 10 4 8.35 0 285.11 349.14 47243 +1964 102 13.85 7.85 12.2 0.3 359.05 257.82 47441 +1964 103 14.5 8.5 12.85 0.01 373.03 258.12 47638 +1964 104 16.22 10.22 14.57 0 412.27 341.93 47834 +1964 105 15.47 9.47 13.82 1.06 394.74 259.13 48030 +1964 106 13.05 7.05 11.4 0.01 342.47 264.37 48225 +1964 107 13.5 7.5 11.85 0.73 351.71 264.91 48419 +1964 108 12.51 6.51 10.86 0 331.65 357 48612 +1964 109 11.92 5.92 10.27 0.29 320.16 269.83 48804 +1964 110 19.18 13.18 17.53 0 488.06 343.47 48995 +1964 111 18.57 12.57 16.92 0.38 471.54 260.08 49185 +1964 112 18.76 12.76 17.11 0.68 476.63 260.77 49374 +1964 113 17.44 11.44 15.79 0.42 442.19 264.55 49561 +1964 114 16.04 10.04 14.39 0.05 408 268.42 49748 +1964 115 16.99 10.99 15.34 0.18 430.95 267.62 49933 +1964 116 18.04 12.04 16.39 0.56 457.57 266.33 50117 +1964 117 12.96 6.96 11.31 0 340.64 368.97 50300 +1964 118 7.47 1.47 5.82 0.15 243.98 285.15 50481 +1964 119 9.9 3.9 8.25 0 283.37 377.43 50661 +1964 120 9.11 3.11 7.46 0 270.01 379.99 50840 +1964 121 13.09 7.09 11.44 0 343.28 373.52 51016 +1964 122 13.75 7.75 12.1 0.27 356.94 279.95 51191 +1964 123 14.63 8.63 12.98 1.07 375.88 279.19 51365 +1964 124 12.65 6.65 11 0.43 334.42 283.34 51536 +1964 125 17.82 11.82 16.17 0.9 451.88 274.46 51706 +1964 126 19.44 13.44 17.79 0 495.25 362.02 51874 +1964 127 16.07 10.07 14.42 0 408.71 372.61 52039 +1964 128 19.36 13.36 17.71 0 493.03 364.11 52203 +1964 129 18.09 12.09 16.44 0 458.88 368.83 52365 +1964 130 21.76 15.76 20.11 0 563.48 357.55 52524 +1964 131 17.11 11.11 15.46 0 433.92 373.21 52681 +1964 132 19.31 13.31 17.66 0.21 491.64 275.6 52836 +1964 133 19.11 13.11 17.46 0.65 486.14 276.59 52989 +1964 134 15.51 9.51 13.86 0 395.66 379.72 53138 +1964 135 13.56 7.56 11.91 0 352.96 385.14 53286 +1964 136 14.45 8.45 12.8 0.72 371.94 287.77 53430 +1964 137 12.45 6.45 10.8 0 330.46 388.94 53572 +1964 138 17.04 11.04 15.39 1.54 432.18 283.7 53711 +1964 139 16.09 10.09 14.44 0.57 409.18 286.17 53848 +1964 140 19.93 13.93 18.28 0.27 509.04 277.93 53981 +1964 141 21.34 15.34 19.69 0.21 550.57 274.58 54111 +1964 142 21 15 19.35 0.11 540.3 275.86 54238 +1964 143 19.37 13.37 17.72 0.75 493.3 280.39 54362 +1964 144 16.31 10.31 14.66 0 414.42 383.4 54483 +1964 145 18.47 12.47 16.82 0 468.88 377.64 54600 +1964 146 18.81 12.81 17.16 0.04 477.98 282.71 54714 +1964 147 20.2 14.2 18.55 0 516.78 372.88 54824 +1964 148 21.53 15.53 19.88 0 556.38 368.56 54931 +1964 149 19.44 13.44 17.79 0.57 495.25 282.08 55034 +1964 150 17.77 11.77 16.12 0 450.6 381.63 55134 +1964 151 13.44 7.44 11.79 0.36 350.47 295.01 55229 +1964 152 20.15 14.15 18.5 0 515.34 374.56 55321 +1964 153 18.63 12.63 16.98 0.07 473.14 284.82 55409 +1964 154 15.99 9.99 14.34 0.07 406.83 290.78 55492 +1964 155 17.62 11.62 15.97 0.16 446.76 287.49 55572 +1964 156 19.66 13.66 18.01 0.16 501.4 282.95 55648 +1964 157 20.73 14.73 19.08 0.05 532.26 280.33 55719 +1964 158 23.78 17.78 22.13 3.08 629.24 271.67 55786 +1964 159 20.51 14.51 18.86 0.05 525.79 281.22 55849 +1964 160 22.5 16.5 20.85 0 586.86 367.81 55908 +1964 161 24.86 18.86 23.21 0.26 666.99 268.54 55962 +1964 162 24.63 18.63 22.98 0 658.8 359.12 56011 +1964 163 24.44 18.44 22.79 0.02 652.09 270.12 56056 +1964 164 26.62 20.62 24.97 0.01 732.62 262.61 56097 +1964 165 26.09 20.09 24.44 0.15 712.3 264.59 56133 +1964 166 26.67 20.67 25.02 1.22 734.56 262.55 56165 +1964 167 24.22 18.22 22.57 0 644.4 361.26 56192 +1964 168 19.84 13.84 18.19 0.17 506.48 283.51 56214 +1964 169 22.99 16.99 21.34 1.32 602.79 274.84 56231 +1964 170 22.86 16.86 21.21 0.01 598.53 275.23 56244 +1964 171 22.86 16.86 21.21 0 598.53 367.03 56252 +1964 172 26.68 20.68 25.03 0 734.95 350.1 56256 +1964 173 28.8 22.8 27.15 0 821.39 339.07 56255 +1964 174 26.81 20.81 25.16 0.19 740.02 262.02 56249 +1964 175 27.68 21.68 26.03 0.12 774.71 258.7 56238 +1964 176 22.18 16.18 20.53 0 576.65 369.51 56223 +1964 177 22.96 16.96 21.31 0 601.8 366.36 56203 +1964 178 24.21 18.21 22.56 0.23 644.05 270.91 56179 +1964 179 23.55 17.55 21.9 0.21 621.44 272.91 56150 +1964 180 21.43 15.43 19.78 1.23 553.32 279.02 56116 +1964 181 19.46 13.46 17.81 0.29 495.8 284.1 56078 +1964 182 18.17 12.17 16.52 0.07 460.97 287.05 56035 +1964 183 18.24 12.24 16.59 0 462.8 382.34 55987 +1964 184 17.46 11.46 15.81 0 442.7 384.51 55935 +1964 185 20.64 14.64 18.99 0 529.61 374.23 55879 +1964 186 17.72 11.72 16.07 0.03 449.31 287.55 55818 +1964 187 20.83 14.83 19.18 0.27 535.23 279.84 55753 +1964 188 18.49 12.49 16.84 0 469.41 380.61 55684 +1964 189 18.77 12.77 17.12 0 476.9 379.55 55611 +1964 190 17.11 11.11 15.46 0 433.92 384.15 55533 +1964 191 20.86 14.86 19.21 0.06 536.12 278.95 55451 +1964 192 21.41 15.41 19.76 0 552.71 369.66 55366 +1964 193 26.81 20.81 25.16 0 740.02 346.43 55276 +1964 194 24.13 18.13 22.48 0 641.27 358.46 55182 +1964 195 25.24 19.24 23.59 0.01 680.72 265.01 55085 +1964 196 22.71 16.71 21.06 0 593.64 363.58 54984 +1964 197 26.53 20.53 24.88 0 729.13 346.51 54879 +1964 198 29.34 23.34 27.69 0 844.73 331.49 54770 +1964 199 24.13 18.13 22.48 0 641.27 356.6 54658 +1964 200 26.28 20.28 24.63 0 719.53 346.59 54542 +1964 201 26.17 20.17 24.52 0 715.34 346.66 54423 +1964 202 23.54 17.54 21.89 0.91 621.1 268.24 54301 +1964 203 25.17 19.17 23.52 1.8 678.18 262.66 54176 +1964 204 24.02 18.02 22.37 0.82 637.47 266.01 54047 +1964 205 23.34 17.34 21.69 0.42 614.39 267.73 53915 +1964 206 23.95 17.95 22.3 0.09 635.06 265.45 53780 +1964 207 22.61 16.61 20.96 0.23 590.41 268.98 53643 +1964 208 25.39 19.39 23.74 0.48 686.21 259.83 53502 +1964 209 26.91 20.91 25.26 0.06 743.94 254.05 53359 +1964 210 23.28 17.28 21.63 0 612.39 354.13 53213 +1964 211 25.7 19.7 24.05 0.6 697.66 257.31 53064 +1964 212 26.73 20.73 25.08 0.07 736.89 253.14 52913 +1964 213 26.34 20.34 24.69 0.01 721.82 253.99 52760 +1964 214 25.67 19.67 24.02 0.09 696.55 255.76 52604 +1964 215 21.21 15.21 19.56 0 546.63 358.18 52445 +1964 216 22.3 16.3 20.65 0 580.46 353.23 52285 +1964 217 22.62 16.62 20.97 0 590.73 351.15 52122 +1964 218 26.83 20.83 25.18 0 740.8 332.41 51958 +1964 219 25.61 19.61 23.96 0.47 694.32 252.78 51791 +1964 220 22.55 16.55 20.9 0.08 588.47 261.5 51622 +1964 221 22.93 16.93 21.28 0.51 600.82 259.68 51451 +1964 222 20.32 14.32 18.67 0.2 520.25 265.87 51279 +1964 223 18.03 12.03 16.38 0 457.31 360.41 51105 +1964 224 15.65 9.65 14 0.63 398.89 274.3 50929 +1964 225 14.26 8.26 12.61 0.27 367.81 275.92 50751 +1964 226 16.22 10.22 14.57 0 412.27 361.95 50572 +1964 227 17.72 11.72 16.07 0.27 449.31 267.46 50392 +1964 228 14.96 8.96 13.31 0 383.2 362.51 50210 +1964 229 20.82 14.82 19.17 0 534.93 344.65 50026 +1964 230 22.28 16.28 20.63 0 579.83 338.34 49842 +1964 231 23.8 17.8 22.15 1.42 629.93 248.39 49656 +1964 232 24.67 18.67 23.02 0 660.22 326.4 49469 +1964 233 25.25 19.25 23.6 0 681.09 322.64 49280 +1964 234 23.55 17.55 21.9 1.07 621.44 246.08 49091 +1964 235 22.29 16.29 20.64 0 580.15 331.3 48900 +1964 236 17.38 11.38 15.73 0.29 440.68 258.81 48709 +1964 237 22.36 16.36 20.71 0 582.38 328.05 48516 +1964 238 16.8 10.8 15.15 0.08 426.27 257.44 48323 +1964 239 20.98 14.98 19.33 0.1 539.7 247.21 48128 +1964 240 20.85 14.85 19.2 0.19 535.82 246.22 47933 +1964 241 20.99 14.99 19.34 1.12 540 244.61 47737 +1964 242 19.68 13.68 18.03 0 501.96 328.5 47541 +1964 243 24.6 18.6 22.95 0 657.73 309.78 47343 +1964 244 22.74 16.74 21.09 0.22 594.62 236.21 47145 +1964 245 21.83 15.83 20.18 0 565.66 316.27 46947 +1964 246 17.4 11.4 15.75 0 441.18 327.34 46747 +1964 247 18.22 12.22 16.57 0.35 462.28 242.5 46547 +1964 248 15.28 9.28 13.63 0.02 390.41 246.46 46347 +1964 249 15.93 9.93 14.28 1.25 405.42 243.78 46146 +1964 250 12.36 6.36 10.71 0.79 328.69 247.89 45945 +1964 251 15.97 9.97 14.32 1.11 406.36 240.63 45743 +1964 252 17.82 11.82 16.17 0.05 451.88 235.62 45541 +1964 253 18.03 12.03 16.38 0.27 457.31 233.63 45339 +1964 254 20.54 14.54 18.89 0.06 526.67 226.84 45136 +1964 255 19.21 13.21 17.56 0 488.88 304.02 44933 +1964 256 19.72 13.72 18.07 0 503.09 300.37 44730 +1964 257 21.42 15.42 19.77 0.48 553.01 219.96 44527 +1964 258 20.29 14.29 18.64 0.98 519.38 220.76 44323 +1964 259 19.16 13.16 17.51 0 487.51 295.08 44119 +1964 260 20.18 14.18 18.53 0.4 516.2 217.46 43915 +1964 261 22.13 16.13 20.48 0.07 575.07 211.35 43711 +1964 262 17.04 11.04 15.39 0 432.18 293.21 43507 +1964 263 13.6 7.6 11.95 0 353.8 297.92 43303 +1964 264 14.84 8.84 13.19 0 380.52 292.92 43099 +1964 265 17.88 11.88 16.23 0 453.43 283.89 42894 +1964 266 21.24 15.24 19.59 0 547.53 272.66 42690 +1964 267 20.17 14.17 18.52 0 515.92 273.04 42486 +1964 268 19.68 13.68 18.03 0 501.96 271.84 42282 +1964 269 17.43 11.43 15.78 0.22 441.94 206.12 42078 +1964 270 17.37 11.37 15.72 0.02 440.43 204.27 41875 +1964 271 18.13 12.13 16.48 0.01 459.92 201.03 41671 +1964 272 16.74 10.74 15.09 0.44 424.8 201.33 41468 +1964 273 16.18 10.18 14.53 0 411.32 267.1 41265 +1964 274 5.81 -0.19 4.16 0 219.85 280.06 41062 +1964 275 7.27 1.27 5.62 0.09 240.96 206.69 40860 +1964 276 6.21 0.21 4.56 0 225.47 273.99 40658 +1964 277 13.09 7.09 11.44 0 343.28 262 40456 +1964 278 12.36 6.36 10.71 0.4 328.69 195.22 40255 +1964 279 14.99 8.99 13.34 0.02 383.87 189.78 40054 +1964 280 8.91 2.91 7.26 1.23 266.71 194.69 39854 +1964 281 9.28 3.28 7.63 1.7 272.84 192.26 39654 +1964 282 11.55 5.55 9.9 3.01 313.13 187.88 39455 +1964 283 10.24 4.24 8.59 0.75 289.3 187.1 39256 +1964 284 7.76 1.76 6.11 0.73 248.42 187.07 39058 +1964 285 12.81 6.81 11.16 0.13 337.62 180.1 38861 +1964 286 11.23 5.23 9.58 0.06 307.16 179.73 38664 +1964 287 7.9 1.9 6.25 0 250.58 240.76 38468 +1964 288 9.68 3.68 8.03 0.25 279.6 176.91 38273 +1964 289 10.18 4.18 8.53 0 288.25 232.6 38079 +1964 290 11.44 5.44 9.79 0 311.07 228.09 37885 +1964 291 10.81 4.81 9.16 0 299.47 226.2 37693 +1964 292 10.88 4.88 9.23 0 300.74 223.41 37501 +1964 293 12.63 6.63 10.98 0 334.03 218.34 37311 +1964 294 13.59 7.59 11.94 0 353.59 214.09 37121 +1964 295 16.24 10.24 14.59 0 412.74 207.1 36933 +1964 296 19.75 13.75 18.1 0 503.94 197.98 36745 +1964 297 18.95 12.95 17.3 0 481.77 196.99 36560 +1964 298 18.34 12.34 16.69 0.05 465.43 146.75 36375 +1964 299 16.08 10.08 14.43 0.3 408.95 147.7 36191 +1964 300 11.73 5.73 10.08 0.04 316.53 150.4 36009 +1964 301 14.31 8.31 12.66 0.53 368.89 145.93 35829 +1964 302 15.89 9.89 14.24 1.74 404.48 142.23 35650 +1964 303 15.9 9.9 14.25 0.68 404.71 140.34 35472 +1964 304 16.12 10.12 14.47 2.82 409.89 138.29 35296 +1964 305 8.21 2.21 6.56 0.08 255.44 143.59 35122 +1964 306 6.46 0.46 4.81 0.53 229.04 143.07 34950 +1964 307 5.82 -0.18 4.17 0 219.99 188.75 34779 +1964 308 5.07 -0.93 3.42 0 209.78 186.71 34610 +1964 309 2.23 -3.77 0.58 0.22 174.72 139.73 34444 +1964 310 5.33 -0.67 3.68 0 213.27 181.69 34279 +1964 311 7.64 1.64 5.99 0 246.57 177.62 34116 +1964 312 7.1 1.1 5.45 0 238.41 175.43 33956 +1964 313 6.52 0.52 4.87 0 229.91 173.77 33797 +1964 314 6.85 0.85 5.2 0 234.71 171.54 33641 +1964 315 9.55 3.55 7.9 0.01 277.38 124.98 33488 +1964 316 12.45 6.45 10.8 0.69 330.46 121.11 33337 +1964 317 13.87 7.87 12.22 0.01 359.47 118.26 33188 +1964 318 14.83 8.83 13.18 0 380.3 154.2 33042 +1964 319 11.62 5.62 9.97 0 314.45 156.26 32899 +1964 320 13.12 7.12 11.47 0.02 343.89 114.6 32758 +1964 321 13.26 7.26 11.61 0.01 346.76 112.94 32620 +1964 322 8.01 2.01 6.36 0.12 252.3 115.4 32486 +1964 323 8.49 2.49 6.84 0.08 259.9 113.89 32354 +1964 324 8.19 2.19 6.54 0 255.13 150.06 32225 +1964 325 9.51 3.51 7.86 0 276.71 147.25 32100 +1964 326 10.92 4.92 9.27 0.13 301.47 108.4 31977 +1964 327 13.5 7.5 11.85 0 351.71 140.1 31858 +1964 328 13.7 7.7 12.05 0.51 355.89 103.46 31743 +1964 329 8.23 2.23 6.58 0.03 255.76 106.2 31631 +1964 330 8.56 2.56 6.91 0 261.02 139.9 31522 +1964 331 6.94 0.94 5.29 0 236.04 139.81 31417 +1964 332 6.12 0.12 4.47 0.17 224.2 104.06 31316 +1964 333 10.67 4.67 9.02 0 296.95 134.15 31218 +1964 334 10.88 4.88 9.23 0.2 300.74 99.66 31125 +1964 335 3.34 -2.66 1.69 0.36 187.77 102.8 31035 +1964 336 -0.29 -6.29 -1.94 0.14 147.96 146.39 30949 +1964 337 0.73 -5.27 -0.92 0.06 158.33 144.82 30867 +1964 338 1.53 -4.47 -0.12 0.36 166.89 143.73 30790 +1964 339 -3.64 -9.64 -5.29 0.87 117.92 147.52 30716 +1964 340 -4.28 -10.28 -5.93 0.01 112.82 147.24 30647 +1964 341 -1.2 -7.2 -2.85 0 139.21 179.07 30582 +1964 342 5.08 -0.92 3.43 0.04 209.91 142.37 30521 +1964 343 6.46 0.46 4.81 0.02 229.04 140.34 30465 +1964 344 8.11 2.11 6.46 0 253.87 168.97 30413 +1964 345 6.44 0.44 4.79 0.07 228.76 94.47 30366 +1964 346 7.91 1.91 6.26 0.27 250.74 93.32 30323 +1964 347 4.14 -1.86 2.49 0.11 197.68 94.64 30284 +1964 348 3.9 -2.1 2.25 0.04 194.66 94.48 30251 +1964 349 6.37 0.37 4.72 0.45 227.75 93.11 30221 +1964 350 4.75 -1.25 3.1 0.21 205.55 93.59 30197 +1964 351 0.33 -5.67 -1.32 0 154.19 126.75 30177 +1964 352 0.09 -5.91 -1.56 0 151.75 126.75 30162 +1964 353 4.04 -1.96 2.39 0 196.42 124.8 30151 +1964 354 -0.82 -6.82 -2.47 0 142.8 127.02 30145 +1964 355 1.51 -4.49 -0.14 0 166.68 126.03 30144 +1964 356 -0.86 -6.86 -2.51 0 142.42 127.06 30147 +1964 357 0.7 -5.3 -0.95 0.15 158.01 94.86 30156 +1964 358 -0.15 -6.15 -1.8 0.09 149.35 139.24 30169 +1964 359 -2.12 -8.12 -3.77 0.25 130.82 140.66 30186 +1964 360 -0.57 -6.57 -2.22 0.24 145.22 141.23 30208 +1964 361 1.93 -4.07 0.28 0 171.33 172.07 30235 +1964 362 -0.22 -6.22 -1.87 0.09 148.65 141.65 30267 +1964 363 2.75 -3.25 1.1 0.17 180.73 140.65 30303 +1964 364 2.48 -3.52 0.83 0 177.58 172.66 30343 +1964 365 1.42 -4.58 -0.23 0.74 165.69 141.22 30388 +1965 1 1.73 -4.27 0.08 0 169.1 173.93 30438 +1965 2 0.57 -5.43 -1.08 0 156.66 175.05 30492 +1965 3 0.9 -5.1 -0.75 0 160.12 175.64 30551 +1965 4 0.82 -5.18 -0.83 0.02 159.27 143.19 30614 +1965 5 0.88 -5.12 -0.77 0 159.9 176.82 30681 +1965 6 0.23 -5.77 -1.42 0 153.17 177.87 30752 +1965 7 0.16 -5.84 -1.49 0 152.46 178.58 30828 +1965 8 3.03 -2.97 1.38 0.4 184.04 101.69 30907 +1965 9 2.75 -3.25 1.1 0.5 180.73 102.75 30991 +1965 10 3.72 -2.28 2.07 0 192.42 137.77 31079 +1965 11 1.54 -4.46 -0.11 0.59 167 104.93 31171 +1965 12 1.38 -4.62 -0.27 0 165.26 141.01 31266 +1965 13 -1.07 -7.07 -2.72 0.06 140.43 150.08 31366 +1965 14 0.6 -5.4 -1.05 0.7 156.97 150.43 31469 +1965 15 4.97 -1.03 3.32 0.27 208.45 107.66 31575 +1965 16 4.45 -1.55 2.8 0.02 201.65 108.87 31686 +1965 17 1.91 -4.09 0.26 0 171.1 148.29 31800 +1965 18 4.81 -1.19 3.16 0 206.34 148.5 31917 +1965 19 6.61 0.61 4.96 0 231.21 149.2 32038 +1965 20 6.12 0.12 4.47 0 224.2 151.12 32161 +1965 21 5.34 -0.66 3.69 0.05 213.41 115.24 32289 +1965 22 5.75 -0.25 4.1 0.03 219.02 116.34 32419 +1965 23 8.5 2.5 6.85 0.86 260.06 116.06 32552 +1965 24 7.77 1.77 6.12 0.21 248.57 118.05 32688 +1965 25 7.47 1.47 5.82 0.03 243.98 119.63 32827 +1965 26 7.04 1.04 5.39 0.26 237.52 121.31 32969 +1965 27 4.78 -1.22 3.13 0 205.94 165.43 33114 +1965 28 2.59 -3.41 0.94 0.45 178.86 126.78 33261 +1965 29 1.97 -4.03 0.32 0 171.77 171.8 33411 +1965 30 -0.48 -6.48 -2.13 0 146.09 175.38 33564 +1965 31 -1.28 -7.28 -2.93 0.21 138.46 173.37 33718 +1965 32 -2.26 -8.26 -3.91 0.11 129.58 175.45 33875 +1965 33 1.85 -4.15 0.2 0.23 170.43 175.43 34035 +1965 34 2.09 -3.91 0.44 0.57 173.13 176.55 34196 +1965 35 3.21 -2.79 1.56 0 186.2 223.27 34360 +1965 36 4.74 -1.26 3.09 0 205.42 186.24 34526 +1965 37 1.74 -4.26 0.09 0 169.21 190.7 34694 +1965 38 1.7 -4.3 0.05 0.64 168.77 145.11 34863 +1965 39 3.71 -2.29 2.06 0.02 192.3 146.07 35035 +1965 40 1.59 -4.41 -0.06 0.06 167.55 149.11 35208 +1965 41 3.22 -2.78 1.57 0 186.32 200.36 35383 +1965 42 0.32 -5.68 -1.33 0 154.09 204.8 35560 +1965 43 1.85 -4.15 0.2 0 170.43 206.58 35738 +1965 44 2.96 -3.04 1.31 0 183.21 208.41 35918 +1965 45 -1.07 -7.07 -2.72 0 140.43 213.58 36099 +1965 46 -7.28 -13.28 -8.93 0 91.41 219.09 36282 +1965 47 -6.33 -12.33 -7.98 0 97.77 221.62 36466 +1965 48 -1.46 -7.46 -3.11 0 136.79 222.23 36652 +1965 49 2.02 -3.98 0.37 0 172.34 222.88 36838 +1965 50 -0.09 -6.09 -1.74 0 149.94 226.96 37026 +1965 51 0.45 -5.55 -1.2 0 155.42 229.62 37215 +1965 52 1.89 -4.11 0.24 0 170.88 231.5 37405 +1965 53 -0.01 -6.01 -1.66 0.05 150.74 212.07 37596 +1965 54 -0.73 -6.73 -2.38 0 143.67 274.07 37788 +1965 55 1.81 -4.19 0.16 0 169.99 240.35 37981 +1965 56 2.69 -3.31 1.04 0 180.03 242.41 38175 +1965 57 1.99 -4.01 0.34 0 172 245.85 38370 +1965 58 1.81 -4.19 0.16 0 169.99 248.95 38565 +1965 59 5.23 -0.77 3.58 0 211.92 248.8 38761 +1965 60 9.79 3.79 8.14 0 281.48 246.65 38958 +1965 61 8.87 2.87 7.22 0 266.06 250.69 39156 +1965 62 11.7 5.7 10.05 0 315.97 249.68 39355 +1965 63 8.56 2.56 6.91 0 261.02 256.83 39553 +1965 64 13.11 7.11 11.46 0 343.69 253.32 39753 +1965 65 12.2 6.2 10.55 0 325.57 257.57 39953 +1965 66 9.61 3.61 7.96 0.23 278.4 197.98 40154 +1965 67 8.33 2.33 6.68 0.06 257.34 201.36 40355 +1965 68 9.78 3.78 8.13 0 281.31 269.46 40556 +1965 69 9.23 3.23 7.58 0.11 272 204.6 40758 +1965 70 7.76 1.76 6.11 0.18 248.42 208.12 40960 +1965 71 7.03 1.03 5.38 0.5 237.37 210.96 41163 +1965 72 9.87 3.87 8.22 1.6 282.86 210.34 41366 +1965 73 10.22 4.22 8.57 0.85 288.95 211.95 41569 +1965 74 5.76 -0.24 4.11 0.05 219.16 218.24 41772 +1965 75 3.7 -2.3 2.05 0 192.17 295.87 41976 +1965 76 6.75 0.75 5.1 0 233.25 295.25 42179 +1965 77 5.19 -0.81 3.54 0.02 211.39 224.73 42383 +1965 78 4.75 -1.25 3.1 0 205.55 302.81 42587 +1965 79 3.91 -2.09 2.26 0 194.79 306.43 42791 +1965 80 3.27 -2.73 1.62 0.07 186.92 232.23 42996 +1965 81 3.91 -2.09 2.26 0 194.79 311.62 43200 +1965 82 5.17 -0.83 3.52 0 211.12 312.96 43404 +1965 83 10.4 4.4 8.75 0 292.12 308.5 43608 +1965 84 10.44 4.44 8.79 0 292.83 310.96 43812 +1965 85 9 3 7.35 0 268.19 315.64 44016 +1965 86 6.23 0.23 4.58 0 225.75 321.76 44220 +1965 87 7.19 1.19 5.54 0 239.76 323.09 44424 +1965 88 9.14 3.14 7.49 0.33 270.51 242.05 44627 +1965 89 9.28 3.28 7.63 1.11 272.84 243.6 44831 +1965 90 7.02 1.02 5.37 0.36 237.22 247.78 45034 +1965 91 12.9 6.9 11.25 0 339.43 323.24 45237 +1965 92 15.05 9.05 13.4 0.49 385.21 240.79 45439 +1965 93 6.99 0.99 5.34 0.96 236.78 252.89 45642 +1965 94 4.78 -1.22 3.13 0.27 205.94 256.61 45843 +1965 95 9.28 3.28 7.63 0 272.84 338.22 46045 +1965 96 9.86 3.86 8.21 0 282.68 339.42 46246 +1965 97 15.96 9.96 14.31 0.46 406.12 247.07 46446 +1965 98 10.52 4.52 8.87 1.61 294.26 256.76 46647 +1965 99 8.09 2.09 6.44 0.02 253.55 261.17 46846 +1965 100 6.94 0.94 5.29 0.12 236.04 263.88 47045 +1965 101 6.82 0.82 5.17 0 234.27 353.97 47243 +1965 102 9.2 3.2 7.55 0 271.5 352.37 47441 +1965 103 9.71 3.71 8.06 0 280.11 353.4 47638 +1965 104 9.54 3.54 7.89 0.14 277.21 266.64 47834 +1965 105 11.45 5.45 9.8 0.2 311.26 265.48 48030 +1965 106 16.57 10.57 14.92 1.86 420.67 258.32 48225 +1965 107 16.77 10.77 15.12 1.39 425.54 259.16 48419 +1965 108 16.92 10.92 15.27 0.34 429.22 260.15 48612 +1965 109 12.95 6.95 11.3 0.02 340.44 268.28 48804 +1965 110 12.96 6.96 11.31 0 340.64 359.1 48995 +1965 111 12.5 6.5 10.85 0 331.45 361.59 49185 +1965 112 11.73 5.73 10.08 0 316.53 364.64 49374 +1965 113 9.99 3.99 8.34 0.29 284.93 276.9 49561 +1965 114 12.02 6.02 10.37 0.52 322.08 275.19 49748 +1965 115 14.73 8.73 13.08 1.05 378.08 271.87 49933 +1965 116 12.85 6.85 11.2 1.94 338.42 275.92 50117 +1965 117 14.5 8.5 12.85 0.19 373.03 274.16 50300 +1965 118 13.66 7.66 12.01 0 355.05 368.77 50481 +1965 119 14.2 8.2 12.55 0.03 366.52 276.56 50661 +1965 120 15.53 9.53 13.88 0.06 396.12 275.05 50840 +1965 121 15.59 9.59 13.94 1.81 397.51 275.77 51016 +1965 122 13.54 7.54 11.89 0.63 352.55 280.3 51191 +1965 123 13.63 7.63 11.98 1.17 354.42 280.93 51365 +1965 124 15.45 9.45 13.8 0.08 394.29 278.5 51536 +1965 125 17.74 11.74 16.09 0.37 449.83 274.63 51706 +1965 126 17.16 11.16 15.51 0.42 435.17 276.59 51874 +1965 127 15.93 9.93 14.28 0.36 405.42 279.73 52039 +1965 128 14.24 8.24 12.59 0.24 367.38 283.6 52203 +1965 129 15.58 9.58 13.93 0 397.27 375.71 52365 +1965 130 11.57 5.57 9.92 0.07 313.51 289.2 52524 +1965 131 14.63 8.63 12.98 0 375.88 379.66 52681 +1965 132 16.67 10.67 15.02 0 423.1 375.25 52836 +1965 133 17.71 11.71 16.06 0 449.06 373.02 52989 +1965 134 17.82 11.82 16.17 0 451.88 373.4 53138 +1965 135 18.79 12.79 17.14 0.16 477.44 278.38 53286 +1965 136 16.78 10.78 15.13 0.26 425.78 283.26 53430 +1965 137 15.45 9.45 13.8 0.88 394.29 286.44 53572 +1965 138 16.19 10.19 14.54 0.02 411.56 285.45 53711 +1965 139 16.8 10.8 15.15 0.07 426.27 284.72 53848 +1965 140 14.02 8.02 12.37 0.27 362.66 290.42 53981 +1965 141 11.56 5.56 9.91 0 313.32 393.06 54111 +1965 142 15.26 9.26 13.61 0 389.95 385.14 54238 +1965 143 17.41 11.41 15.76 1.76 441.43 284.89 54362 +1965 144 16.27 10.27 14.62 0.03 413.46 287.63 54483 +1965 145 21.45 15.45 19.8 0 553.93 367.65 54600 +1965 146 18.47 12.47 16.82 0.12 468.88 283.51 54714 +1965 147 18.06 12.06 16.41 0.28 458.09 284.8 54824 +1965 148 15.86 9.86 14.21 0.15 403.78 289.75 54931 +1965 149 14.27 8.27 12.62 0.73 368.03 293 55034 +1965 150 12.79 6.79 11.14 3.34 337.22 295.81 55134 +1965 151 15.04 9.04 13.39 1.58 384.99 292.12 55229 +1965 152 21.38 15.38 19.73 0.09 551.79 277.67 55321 +1965 153 19.95 13.95 18.3 0 509.61 375.48 55409 +1965 154 18.03 12.03 16.38 0 457.31 381.91 55492 +1965 155 21.22 15.22 19.57 0.02 546.93 278.66 55572 +1965 156 21.03 15.03 19.38 0 541.2 372.55 55648 +1965 157 21.4 15.4 19.75 0.18 552.4 278.53 55719 +1965 158 23.06 17.06 21.41 0.04 605.1 273.88 55786 +1965 159 23.61 17.61 21.96 0 623.47 363.17 55849 +1965 160 24.62 18.62 22.97 0 658.44 359.04 55908 +1965 161 24.22 18.22 22.57 0.1 644.4 270.63 55962 +1965 162 21.51 15.51 19.86 0.07 555.77 278.76 56011 +1965 163 19.77 13.77 18.12 0.17 504.5 283.51 56056 +1965 164 21.92 15.92 20.27 0.31 568.47 277.81 56097 +1965 165 23.33 17.33 21.68 0.34 614.06 273.72 56133 +1965 166 22.27 16.27 20.62 0.14 579.51 276.94 56165 +1965 167 20.59 14.59 18.94 0.02 528.14 281.53 56192 +1965 168 22.9 16.9 21.25 0.28 599.84 275.1 56214 +1965 169 24.51 18.51 22.86 1.9 654.55 270.07 56231 +1965 170 25.01 19.01 23.36 2.03 672.38 268.41 56244 +1965 171 25.51 19.51 23.86 1.78 690.62 266.75 56252 +1965 172 21.33 15.33 19.68 0.74 550.27 279.64 56256 +1965 173 19.98 13.98 18.33 0.8 510.47 283.19 56255 +1965 174 20.08 14.08 18.43 0.02 513.33 282.87 56249 +1965 175 17.94 11.94 16.29 1.57 454.98 287.99 56238 +1965 176 16.33 10.33 14.68 0.21 414.89 291.43 56223 +1965 177 15.93 9.93 14.28 1.35 405.42 292.17 56203 +1965 178 13.65 7.65 12 0.08 354.84 296.46 56179 +1965 179 17.49 11.49 15.84 1.32 443.46 288.83 56150 +1965 180 20.17 14.17 18.52 0 515.92 376.49 56116 +1965 181 19.43 13.43 17.78 0.24 494.97 284.17 56078 +1965 182 16.94 10.94 15.29 0.2 429.71 289.76 56035 +1965 183 20.25 14.25 18.6 0.02 518.22 281.87 55987 +1965 184 20.61 14.61 18.96 0.93 528.72 280.82 55935 +1965 185 20.3 14.3 18.65 0.57 519.67 281.56 55879 +1965 186 21.01 15.01 19.36 1.18 540.6 279.5 55818 +1965 187 26.48 20.48 24.83 0.64 727.2 262.21 55753 +1965 188 22.29 16.29 20.64 0.8 580.15 275.6 55684 +1965 189 21.15 15.15 19.5 2.56 544.81 278.65 55611 +1965 190 15.93 9.93 14.28 0.63 405.42 290.56 55533 +1965 191 17.37 11.37 15.72 0.01 440.43 287.35 55451 +1965 192 17.03 11.03 15.38 0 431.94 383.8 55366 +1965 193 23.38 17.38 21.73 0 615.73 361.79 55276 +1965 194 22.74 16.74 21.09 0.01 594.62 273.1 55182 +1965 195 21.42 15.42 19.77 0.47 553.01 276.64 55085 +1965 196 23.74 17.74 22.09 1.58 627.88 269.58 54984 +1965 197 22.31 16.31 20.66 2.14 580.78 273.51 54879 +1965 198 24.55 18.55 22.9 0 655.97 355.15 54770 +1965 199 25.24 19.24 23.59 0 680.72 351.77 54658 +1965 200 21.82 15.82 20.17 0.01 565.35 274.02 54542 +1965 201 18.84 12.84 17.19 0.62 478.79 281.3 54423 +1965 202 22.5 16.5 20.85 0.37 586.86 271.33 54301 +1965 203 24 18 22.35 0.03 636.78 266.45 54176 +1965 204 24.98 18.98 23.33 0.96 671.3 262.93 54047 +1965 205 25.88 19.88 24.23 0 704.39 346.01 53915 +1965 206 23.42 17.42 21.77 0.83 617.07 267.07 53780 +1965 207 24.53 18.53 22.88 0 655.26 350.84 53643 +1965 208 25.05 19.05 23.4 0 673.83 347.95 53502 +1965 209 23.46 17.46 21.81 0.08 618.41 265.51 53359 +1965 210 21.91 15.91 20.26 0.56 568.16 269.54 53213 +1965 211 18.32 12.32 16.67 0.16 464.91 277.93 53064 +1965 212 16.82 10.82 15.17 0.34 426.76 280.56 52913 +1965 213 17.77 11.77 16.12 0.19 450.6 277.97 52760 +1965 214 18.64 12.64 16.99 0.05 473.41 275.46 52604 +1965 215 18.94 12.94 17.29 0.61 481.5 274.25 52445 +1965 216 20.58 14.58 18.93 0.23 527.84 269.51 52285 +1965 217 20.68 14.68 19.03 0.66 530.79 268.59 52122 +1965 218 19.16 13.16 17.51 0.27 487.51 271.69 51958 +1965 219 19.4 13.4 17.75 0.41 494.14 270.34 51791 +1965 220 17.92 11.92 16.27 0 454.46 363.96 51622 +1965 221 16.86 10.86 15.21 0 427.74 365.91 51451 +1965 222 17.75 11.75 16.1 0 450.08 362.37 51279 +1965 223 19.03 13.03 17.38 0.92 483.95 268.08 51105 +1965 224 21.01 15.01 19.36 0 540.6 349.99 50929 +1965 225 19.49 13.49 17.84 0 496.64 353.81 50751 +1965 226 17.6 11.6 15.95 0.53 446.25 268.68 50572 +1965 227 16.24 10.24 14.59 0.1 412.74 270.44 50392 +1965 228 17.15 11.15 15.5 0 434.92 356.95 50210 +1965 229 20.96 14.96 19.31 0.01 539.11 258.14 50026 +1965 230 20.46 14.46 18.81 0.08 524.33 258.43 49842 +1965 231 19.38 13.38 17.73 0 493.58 346.52 49656 +1965 232 18.44 12.44 16.79 0 468.08 347.95 49469 +1965 233 26.05 20.05 24.4 0.25 710.79 239.39 49280 +1965 234 24.87 18.87 23.22 0 667.35 322.87 49091 +1965 235 23.87 17.87 22.22 0 632.32 325.43 48900 +1965 236 23.42 17.42 21.77 0 617.07 325.77 48709 +1965 237 23.41 17.41 21.76 0 616.73 324.22 48516 +1965 238 24.87 18.87 23.22 0.01 667.35 237.68 48323 +1965 239 21.2 15.2 19.55 0.1 546.32 246.67 48128 +1965 240 18.72 12.72 17.07 2.87 475.56 251.07 47933 +1965 241 19.42 13.42 17.77 0.8 494.69 248.25 47737 +1965 242 17.67 11.67 16.02 0.13 448.04 250.63 47541 +1965 243 18.01 12.01 16.36 0 456.79 331.39 47343 +1965 244 14.88 8.88 13.23 0.11 381.41 252.94 47145 +1965 245 15.53 9.53 13.88 0 396.12 333.9 46947 +1965 246 18.05 12.05 16.4 0.14 457.83 244.23 46747 +1965 247 14.27 8.27 12.62 0 368.03 332.81 46547 +1965 248 16.32 10.32 14.67 0 414.65 326.2 46347 +1965 249 17.6 11.6 15.95 0 446.25 320.95 46146 +1965 250 19.14 13.14 17.49 0 486.96 314.88 45945 +1965 251 20.96 14.96 19.31 0.27 539.11 230.59 45743 +1965 252 21.92 15.92 20.27 0 568.47 302.31 45541 +1965 253 25.07 19.07 23.42 0 674.55 289.16 45339 +1965 254 24.76 18.76 23.11 0 663.42 288.33 45136 +1965 255 28.23 22.23 26.58 0.02 797.35 203.96 44933 +1965 256 28.73 22.73 27.08 0.3 818.41 200.71 44730 +1965 257 27.39 21.39 25.74 1.65 763 203.69 44527 +1965 258 24.03 18.03 22.38 0.48 637.82 211.83 44323 +1965 259 20.2 14.2 18.55 0.13 516.78 219.16 44119 +1965 260 21.55 15.55 19.9 0.16 557 214.46 43915 +1965 261 21.01 15.01 19.36 0.88 540.6 213.89 43711 +1965 262 20.67 14.67 19.02 0 530.49 283.86 43507 +1965 263 20.09 14.09 18.44 0 513.62 283.09 43303 +1965 264 18.12 12.12 16.47 0 459.66 285.66 43099 +1965 265 11.25 5.25 9.6 0 307.53 296.98 42894 +1965 266 10.97 4.97 9.32 0 302.38 294.88 42690 +1965 267 12.47 6.47 10.82 0.01 330.86 217.28 42486 +1965 268 11.08 5.08 9.43 0.04 304.4 217.02 42282 +1965 269 13.08 7.08 11.43 0 343.08 283.5 42078 +1965 270 12.86 6.86 11.21 0 338.63 281.22 41875 +1965 271 12.48 6.48 10.83 0 331.05 279.21 41671 +1965 272 14.53 8.53 12.88 0.75 373.68 204.63 41468 +1965 273 18.6 12.6 16.95 0.34 472.34 196.34 41265 +1965 274 12.14 6.14 10.49 0 324.4 271.73 41062 +1965 275 12.85 6.85 11.2 0 338.42 267.79 40860 +1965 276 11.96 5.96 10.31 0 320.93 266.49 40658 +1965 277 10.71 4.71 9.06 0 297.67 265.66 40456 +1965 278 13.5 7.5 11.85 0 351.71 258.45 40255 +1965 279 14.48 8.48 12.83 0 372.59 253.95 40054 +1965 280 12.75 6.75 11.1 0 336.42 254.19 39854 +1965 281 15.61 9.61 13.96 0 397.97 246.58 39654 +1965 282 9.48 3.48 7.83 0 276.2 253.31 39455 +1965 283 9.81 3.81 8.16 0 281.82 250.03 39256 +1965 284 12.49 6.49 10.84 0 331.25 243.26 39058 +1965 285 12.06 6.06 10.41 0 322.85 241.24 38861 +1965 286 11.79 5.79 10.14 0 317.68 238.86 38664 +1965 287 9.18 3.18 7.53 0 271.17 239.3 38468 +1965 288 7.29 1.29 5.64 0 241.26 238.58 38273 +1965 289 9.49 3.49 7.84 0 276.37 233.44 38079 +1965 290 11.93 5.93 10.28 0 320.35 227.42 37885 +1965 291 13.32 7.32 11.67 0 347.99 222.74 37693 +1965 292 15.84 9.84 14.19 0 403.31 216.06 37501 +1965 293 14.62 8.62 12.97 0 375.66 215.38 37311 +1965 294 12.76 6.76 11.11 0 336.62 215.29 37121 +1965 295 9.06 3.06 7.41 0 269.18 217.06 36933 +1965 296 11 5 9.35 0 302.93 212.19 36745 +1965 297 12.4 6.4 10.75 0 329.48 207.67 36560 +1965 298 9.37 3.37 7.72 0 274.35 208.74 36375 +1965 299 11.88 5.88 10.23 0 319.39 202.99 36191 +1965 300 10.15 4.15 8.5 0 287.72 202.4 36009 +1965 301 11.41 5.41 9.76 0 310.51 198.41 35829 +1965 302 12.04 6.04 10.39 0 322.47 195.04 35650 +1965 303 11.96 5.96 10.31 0 320.93 192.58 35472 +1965 304 12.3 6.3 10.65 0 327.52 189.72 35296 +1965 305 5.75 -0.25 4.1 0.25 219.02 145.22 35122 +1965 306 3.82 -2.18 2.17 0.02 193.66 144.61 34950 +1965 307 3.45 -2.55 1.8 2.36 189.1 142.89 34779 +1965 308 5.95 -0.05 4.3 0.31 221.81 139.51 34610 +1965 309 7.31 1.31 5.66 0.68 241.56 136.91 34444 +1965 310 5.35 -0.65 3.7 0.17 213.54 136.26 34279 +1965 311 4.46 -1.54 2.81 0 201.78 180.13 34116 +1965 312 6.54 0.54 4.89 0.15 230.2 131.92 33956 +1965 313 7.4 1.4 5.75 0.1 242.92 129.79 33797 +1965 314 6.24 0.24 4.59 0 225.9 172.03 33641 +1965 315 5.86 -0.14 4.21 0 220.55 169.77 33488 +1965 316 1.93 -4.07 0.28 0 171.33 170.15 33337 +1965 317 3.83 -2.17 2.18 0.42 193.79 125.08 33188 +1965 318 2.75 -3.25 1.1 2.03 180.73 123.81 33042 +1965 319 6.75 0.75 5.1 0.34 233.25 120.48 32899 +1965 320 7.15 1.15 5.5 0.79 239.16 118.85 32758 +1965 321 5.6 -0.4 3.95 0 216.95 157.5 32620 +1965 322 4.93 -1.07 3.28 0 207.92 156.13 32486 +1965 323 6.48 0.48 4.83 0 229.33 153.43 32354 +1965 324 1.82 -4.18 0.17 0 170.1 154.29 32225 +1965 325 1.76 -4.24 0.11 0 169.43 152.58 32100 +1965 326 2.44 -3.56 0.79 0 177.12 150.74 31977 +1965 327 6.84 0.84 5.19 0.14 234.57 109.57 31858 +1965 328 7.8 1.8 6.15 0.34 249.03 107.56 31743 +1965 329 6.08 0.08 4.43 0.44 223.63 107.37 31631 +1965 330 4.81 -1.19 3.16 0 206.34 142.55 31522 +1965 331 4.83 -1.17 3.18 0.19 206.6 105.91 31417 +1965 332 5.88 -0.12 4.23 0.72 220.83 104.17 31316 +1965 333 5.6 -0.4 3.95 0.39 216.95 103.5 31218 +1965 334 11.22 5.22 9.57 0.01 306.98 99.43 31125 +1965 335 9.27 3.27 7.62 1.52 272.67 99.82 31035 +1965 336 8.32 2.32 6.67 0.01 257.19 99.58 30949 +1965 337 7.19 1.19 5.54 0 239.76 131.94 30867 +1965 338 7.41 1.41 5.76 0 243.07 130.85 30790 +1965 339 6.96 0.96 5.31 0 236.34 130.38 30716 +1965 340 5.77 -0.23 4.12 0 219.3 130.43 30647 +1965 341 8.09 2.09 6.44 0 253.55 127.95 30582 +1965 342 6.73 0.73 5.08 0.05 232.96 96.11 30521 +1965 343 8.04 2.04 6.39 0.53 252.77 94.82 30465 +1965 344 6.88 0.88 5.23 0 235.16 126.1 30413 +1965 345 8.84 2.84 7.19 0 265.57 124.29 30366 +1965 346 7.08 1.08 5.43 0 238.11 124.99 30323 +1965 347 4.21 -1.79 2.56 0.14 198.57 94.61 30284 +1965 348 2.18 -3.82 0.53 0 174.15 126.85 30251 +1965 349 -1.3 -7.3 -2.95 0 138.27 127.96 30221 +1965 350 -0.3 -6.3 -1.95 0.39 147.86 140.38 30197 +1965 351 -6.59 -12.59 -8.24 0.42 95.99 143.13 30177 +1965 352 -4.22 -10.22 -5.87 0 113.29 174.65 30162 +1965 353 -4.55 -10.55 -6.2 0.01 110.73 142.65 30151 +1965 354 -1.41 -7.41 -3.06 0 137.25 173.65 30145 +1965 355 1.83 -4.17 0.18 0 170.21 172.04 30144 +1965 356 3.88 -2.12 2.23 0 194.41 170.51 30147 +1965 357 3.86 -2.14 2.21 0 194.16 170.05 30156 +1965 358 9.15 3.15 7.5 0 270.67 165.51 30169 +1965 359 9.02 3.02 7.37 0.1 268.52 91.4 30186 +1965 360 7.09 1.09 5.44 1.19 238.26 92.69 30208 +1965 361 10.48 4.48 8.83 0 293.55 121.4 30235 +1965 362 10.57 4.57 8.92 0.73 295.15 91.31 30267 +1965 363 5.61 -0.39 3.96 0 217.09 125.87 30303 +1965 364 7.8 1.8 6.15 0.28 249.03 93.62 30343 +1965 365 5.84 -0.16 4.19 0.02 220.27 95.02 30388 +1966 1 2.3 -3.7 0.65 0 175.51 129.54 30438 +1966 2 -0.19 -6.19 -1.84 0 148.95 131.41 30492 +1966 3 0.98 -5.02 -0.67 0 160.96 131.85 30551 +1966 4 0 -6 -1.65 0 150.84 133.2 30614 +1966 5 4.8 -1.2 3.15 0.23 206.2 98.57 30681 +1966 6 2.63 -3.37 0.98 1.09 179.33 100.13 30752 +1966 7 1.08 -4.92 -0.57 0.17 162.03 101.3 30828 +1966 8 2.79 -3.21 1.14 1.02 181.2 101.79 30907 +1966 9 -0.26 -6.26 -1.91 0.21 148.25 147.07 30991 +1966 10 -4.38 -10.38 -6.03 0 112.05 184.42 31079 +1966 11 -2.7 -8.7 -4.35 0.01 125.76 149.32 31171 +1966 12 -5.13 -11.13 -6.78 0 106.36 186.47 31266 +1966 13 -3.81 -9.81 -5.46 0.45 116.55 152.73 31366 +1966 14 -7.41 -13.41 -9.06 0 90.57 191.39 31469 +1966 15 -7.69 -13.69 -9.34 0.01 88.78 155.58 31575 +1966 16 -3.62 -9.62 -5.27 0 118.08 192.72 31686 +1966 17 -4.4 -10.4 -6.05 0 111.89 194.54 31800 +1966 18 -0.4 -6.4 -2.05 0 146.88 194.73 31917 +1966 19 -2.31 -8.31 -3.96 0 129.14 197.33 32038 +1966 20 -2.59 -8.59 -4.24 0 126.7 198.89 32161 +1966 21 -1.21 -7.21 -2.86 0 139.11 200.17 32289 +1966 22 -0.52 -6.52 -2.17 0 145.7 201.46 32419 +1966 23 0.17 -5.83 -1.48 0.03 152.56 162.67 32552 +1966 24 -0.3 -6.3 -1.95 0.01 147.86 164.26 32688 +1966 25 -1.62 -7.62 -3.27 0 135.32 207.22 32827 +1966 26 -0.75 -6.75 -2.4 0.32 143.48 167.88 32969 +1966 27 0.48 -5.52 -1.17 0 155.73 210.71 33114 +1966 28 1.35 -4.65 -0.3 0.28 164.93 169.68 33261 +1966 29 0.41 -5.59 -1.24 0 155.01 214.78 33411 +1966 30 -0.16 -6.16 -1.81 0 149.25 217.15 33564 +1966 31 -0.56 -6.56 -2.21 0 145.31 219.55 33718 +1966 32 8.88 2.88 7.23 0 266.22 213.84 33875 +1966 33 9.25 3.25 7.6 0 272.34 214.79 34035 +1966 34 12.43 6.43 10.78 0.19 330.07 130.76 34196 +1966 35 11.96 5.96 10.31 0 320.93 176.97 34360 +1966 36 11.67 5.67 10.02 0.01 315.4 134.82 34526 +1966 37 11.87 5.87 10.22 0 319.2 181.89 34694 +1966 38 9.24 3.24 7.59 0.29 272.17 140.59 34863 +1966 39 9.72 3.72 8.07 0.03 280.28 142.14 35035 +1966 40 12.28 6.28 10.63 0.04 327.13 141.87 35208 +1966 41 13.64 7.64 11.99 0 354.63 189.94 35383 +1966 42 10.2 4.2 8.55 0.42 288.6 147.5 35560 +1966 43 7.75 1.75 6.1 1.26 248.26 151.4 35738 +1966 44 5.97 -0.03 4.32 0.7 222.09 154.53 35918 +1966 45 11.02 5.02 9.37 0 303.3 203.45 36099 +1966 46 14.07 8.07 12.42 0 363.73 202.02 36282 +1966 47 14.07 8.07 12.42 0 363.73 204.75 36466 +1966 48 11.86 5.86 10.21 0 319.01 210.53 36652 +1966 49 11.81 5.81 10.16 0 318.06 213.31 36838 +1966 50 7.88 1.88 6.23 0 250.27 220.52 37026 +1966 51 6.45 0.45 4.8 0 228.9 224.89 37215 +1966 52 5.87 -0.13 4.22 0 220.69 228.26 37405 +1966 53 4.17 -1.83 2.52 0.16 198.07 174.54 37596 +1966 54 4.81 -1.19 3.16 1.14 206.34 176.2 37788 +1966 55 6.33 0.33 4.68 0 227.18 236.52 37981 +1966 56 8.9 2.9 7.25 0 266.55 236.45 38175 +1966 57 10.39 4.39 8.74 0.57 291.95 178.1 38370 +1966 58 11.81 5.81 10.16 0.16 318.06 178.82 38565 +1966 59 10.78 4.78 9.13 0.43 298.93 181.88 38761 +1966 60 10.38 4.38 8.73 0 291.77 245.88 38958 +1966 61 10.94 4.94 9.29 0 301.83 248.02 39156 +1966 62 11.28 5.28 9.63 0 308.09 250.29 39355 +1966 63 11.56 5.56 9.91 0.38 313.32 189.63 39553 +1966 64 11.03 5.03 9.38 0.54 303.48 192.35 39753 +1966 65 10.42 4.42 8.77 0 292.48 260.17 39953 +1966 66 10.85 4.85 9.2 0 300.2 262.27 40154 +1966 67 10.41 4.41 8.76 0 292.3 265.75 40355 +1966 68 6.27 0.27 4.62 0.41 226.32 205.3 40556 +1966 69 6.67 0.67 5.02 0.01 232.08 206.94 40758 +1966 70 4.75 -1.25 3.1 0 205.55 280.82 40960 +1966 71 8.02 2.02 6.37 0 252.46 280.09 41163 +1966 72 3.25 -2.75 1.6 0 186.68 288.05 41366 +1966 73 6.84 0.84 5.19 0 234.57 287.01 41569 +1966 74 4.56 -1.44 2.91 0 203.07 292.26 41772 +1966 75 5.91 -0.09 4.26 0 221.25 293.57 41976 +1966 76 0.39 -5.61 -1.26 0 154.8 301.44 42179 +1966 77 1.05 -4.95 -0.6 0 161.71 303.57 42383 +1966 78 4 -2 2.35 0 195.92 303.58 42587 +1966 79 4.06 -1.94 2.41 0 196.67 306.28 42791 +1966 80 5.89 -0.11 4.24 0 220.97 306.86 42996 +1966 81 5.49 -0.51 3.84 0.66 215.45 232.44 43200 +1966 82 8.96 2.96 7.31 0.07 267.53 231.13 43404 +1966 83 13.59 7.59 11.94 0 353.59 302.99 43608 +1966 84 12.13 6.13 10.48 0 324.21 308.15 43812 +1966 85 11.86 5.86 10.21 0.01 319.01 233.32 44016 +1966 86 11.21 5.21 9.56 0.01 306.79 235.94 44220 +1966 87 11.33 5.33 9.68 0.02 309.02 237.68 44424 +1966 88 8.02 2.02 6.37 0.19 252.46 243.25 44627 +1966 89 8.6 2.6 6.95 0.46 261.67 244.35 44831 +1966 90 8.43 2.43 6.78 0 258.94 328.43 45034 +1966 91 9.93 3.93 8.28 0.61 283.89 246.31 45237 +1966 92 17.38 11.38 15.73 0 440.68 315.6 45439 +1966 93 14.69 8.69 13.04 0 377.2 324 45642 +1966 94 17.79 11.79 16.14 0.18 451.11 239.08 45843 +1966 95 14.54 8.54 12.89 0.14 373.9 246.4 46045 +1966 96 18.36 12.36 16.71 0 465.96 321.37 46246 +1966 97 17.71 11.71 16.06 1.73 449.06 243.8 46446 +1966 98 10.58 4.58 8.93 0.29 295.33 256.69 46647 +1966 99 12.09 6.09 10.44 0 323.43 341.54 46846 +1966 100 11.27 5.27 9.62 0 307.9 345 47045 +1966 101 13.98 7.98 12.33 0 361.81 341.59 47243 +1966 102 13.98 7.98 12.33 0.23 361.81 257.61 47441 +1966 103 18.7 12.7 17.05 1.75 475.02 250.18 47638 +1966 104 18.84 12.84 17.19 0.01 478.79 251.2 47834 +1966 105 16.02 10.02 14.37 0 407.53 344.18 48030 +1966 106 12.62 6.62 10.97 0.22 333.83 265.02 48225 +1966 107 12.05 6.05 10.4 0.63 322.66 267.12 48419 +1966 108 11.37 5.37 9.72 0.37 309.76 269.4 48612 +1966 109 13.79 7.79 12.14 0.12 357.78 266.94 48804 +1966 110 17.29 11.29 15.64 0.15 438.42 261.63 48995 +1966 111 14.59 8.59 12.94 0.64 375 267.81 49185 +1966 112 15.99 9.99 14.34 0.17 406.83 266.42 49374 +1966 113 7.93 1.93 6.28 0.24 251.05 279.44 49561 +1966 114 10.4 4.4 8.75 0 292.12 369.98 49748 +1966 115 17.73 11.73 16.08 0 449.57 354.8 49933 +1966 116 17.06 11.06 15.41 0 432.68 357.83 50117 +1966 117 14.92 8.92 13.27 0 382.3 364.56 50300 +1966 118 18.24 12.24 16.59 0 462.8 357.1 50481 +1966 119 15.81 9.81 14.16 0 402.61 364.86 50661 +1966 120 18.67 12.67 17.02 0 474.21 358.14 50840 +1966 121 16.17 10.17 14.52 0 411.08 366.22 51016 +1966 122 15.92 9.92 14.27 0.02 405.18 276.04 51191 +1966 123 12.48 6.48 10.83 0 331.05 377.06 51365 +1966 124 13.46 7.46 11.81 0 350.88 376.03 51536 +1966 125 15.72 9.72 14.07 0.52 400.51 278.73 51706 +1966 126 16.77 10.77 15.12 0.11 425.54 277.4 51874 +1966 127 16.55 10.55 14.9 0 420.19 371.34 52039 +1966 128 18.02 12.02 16.37 0.05 457.05 276.15 52203 +1966 129 19.2 13.2 17.55 0.14 488.61 274.09 52365 +1966 130 16.96 10.96 15.31 0.08 430.2 279.63 52524 +1966 131 19.7 13.7 18.05 0 502.53 365.4 52681 +1966 132 20.15 14.15 18.5 0 515.34 364.73 52836 +1966 133 19.89 13.89 18.24 0.04 507.9 274.71 52989 +1966 134 16.75 10.75 15.1 0.08 425.05 282.33 53138 +1966 135 16.31 10.31 14.66 0.01 414.42 283.75 53286 +1966 136 13.02 7.02 11.37 0.04 341.86 290.24 53430 +1966 137 15.53 9.53 13.88 0.07 396.12 286.29 53572 +1966 138 17.15 11.15 15.5 0 434.92 377.96 53711 +1966 139 18.68 12.68 17.03 0 474.48 374.11 53848 +1966 140 17.17 11.17 15.52 0.01 435.41 284.3 53981 +1966 141 15.26 9.26 13.61 0 389.95 384.64 54111 +1966 142 14.92 8.92 13.27 0 382.3 386 54238 +1966 143 16.73 10.73 15.08 0 424.56 381.78 54362 +1966 144 18.33 12.33 16.68 0.52 465.17 283.2 54483 +1966 145 21.61 15.61 19.96 0.04 558.84 275.3 54600 +1966 146 22.73 16.73 21.08 0 594.29 363.17 54714 +1966 147 17.58 11.58 15.93 3.49 445.74 285.87 54824 +1966 148 17 11 15.35 0.67 431.19 287.41 54931 +1966 149 17.8 11.8 16.15 0.17 451.37 285.9 55034 +1966 150 20.64 14.64 18.99 0.88 529.61 279.28 55134 +1966 151 23.25 17.25 21.6 1.55 611.39 272.2 55229 +1966 152 26.19 20.19 24.54 0 716.1 350.12 55321 +1966 153 25.56 19.56 23.91 0.57 692.47 264.97 55409 +1966 154 22.82 16.82 21.17 0.05 597.22 273.98 55492 +1966 155 25.33 19.33 23.68 0.81 684.01 266.12 55572 +1966 156 25.73 19.73 24.08 0.15 698.78 264.97 55648 +1966 157 21.91 15.91 20.26 0.15 568.16 277.11 55719 +1966 158 22.64 16.64 20.99 0.2 591.38 275.13 55786 +1966 159 19.09 13.09 17.44 0.26 485.59 284.78 55849 +1966 160 15.24 9.24 13.59 0.21 389.5 293.23 55908 +1966 161 18.9 12.9 17.25 0.38 480.41 285.43 55962 +1966 162 19 13 17.35 1.59 483.13 285.23 56011 +1966 163 16.95 10.95 15.3 0 429.96 386.71 56056 +1966 164 20.76 14.76 19.11 0.54 533.15 280.99 56097 +1966 165 25.76 19.76 24.11 0 699.9 354.35 56133 +1966 166 24.01 18.01 22.36 2.09 637.13 271.66 56165 +1966 167 24.27 18.27 22.62 0.01 646.14 270.79 56192 +1966 168 24.66 18.66 23.01 0 659.86 359.43 56214 +1966 169 18.07 12.07 16.42 0 458.35 383.68 56231 +1966 170 20.21 14.21 18.56 0.2 517.07 282.58 56244 +1966 171 15.39 9.39 13.74 0 392.91 391.26 56252 +1966 172 16.6 10.6 14.95 0.07 421.4 291 56256 +1966 173 14.3 8.3 12.65 0.46 368.68 295.48 56255 +1966 174 19.65 13.65 18 0.07 501.12 283.96 56249 +1966 175 21.73 15.73 20.08 0.4 562.55 278.44 56238 +1966 176 20.53 14.53 18.88 0 526.38 375.55 56223 +1966 177 21.4 15.4 19.75 0 552.4 372.33 56203 +1966 178 20.77 14.77 19.12 0 533.45 374.63 56179 +1966 179 22.43 16.43 20.78 0.05 584.62 276.28 56150 +1966 180 23 17 21.35 0.4 603.12 274.5 56116 +1966 181 26.88 20.88 25.23 0.64 742.76 261.46 56078 +1966 182 23.59 17.59 21.94 1.36 622.79 272.54 56035 +1966 183 23.94 17.94 22.29 2.74 634.72 271.32 55987 +1966 184 21.11 15.11 19.46 0.2 543.61 279.49 55935 +1966 185 24.12 18.12 22.47 0.44 640.93 270.57 55879 +1966 186 20.32 14.32 18.67 0.42 520.25 281.32 55818 +1966 187 20.14 14.14 18.49 0.04 515.05 281.64 55753 +1966 188 18.4 12.4 16.75 0.65 467.02 285.67 55684 +1966 189 21.91 15.91 20.26 0 568.16 368.74 55611 +1966 190 22.43 16.43 20.78 0.47 584.62 274.79 55533 +1966 191 23.42 17.42 21.77 0 617.07 362.19 55451 +1966 192 22.02 16.02 20.37 0 571.61 367.4 55366 +1966 193 18.36 12.36 16.71 0 465.96 379.6 55276 +1966 194 17.01 11.01 15.36 0 431.44 383.35 55182 +1966 195 15.58 9.58 13.93 1.39 397.27 290.21 55085 +1966 196 15.66 9.66 14.01 1.13 399.12 289.74 54984 +1966 197 18.87 12.87 17.22 0 479.6 376.64 54879 +1966 198 22.21 16.21 20.56 0.76 577.6 273.48 54770 +1966 199 25.6 19.6 23.95 0.11 693.95 262.6 54658 +1966 200 26.08 20.08 24.43 0.75 711.92 260.65 54542 +1966 201 24.47 18.47 22.82 2.6 653.15 265.73 54423 +1966 202 20.82 14.82 19.17 0.37 534.93 275.96 54301 +1966 203 17.81 11.81 16.16 0.15 451.62 282.84 54176 +1966 204 21.59 15.59 19.94 0 558.23 364.18 54047 +1966 205 21.11 15.11 19.46 0.24 543.61 274.05 53915 +1966 206 23.72 17.72 22.07 0.05 627.2 266.16 53780 +1966 207 24.76 18.76 23.11 0.17 663.42 262.39 53643 +1966 208 24.46 18.46 22.81 0 652.79 350.51 53502 +1966 209 24.58 18.58 22.93 0.64 657.03 262.03 53359 +1966 210 21.83 15.83 20.18 0.14 565.66 269.76 53213 +1966 211 19.7 13.7 18.05 0 502.53 366.26 53064 +1966 212 18.39 12.39 16.74 0.72 466.76 277.17 52913 +1966 213 22.16 16.16 20.51 0.18 576.02 267.11 52760 +1966 214 20.04 14.04 18.39 0 512.18 362.84 52604 +1966 215 12.98 6.98 11.33 0 341.05 381.23 52445 +1966 216 15.15 9.15 13.5 0.2 387.46 281.36 52285 +1966 217 18.12 12.12 16.47 0.16 459.66 274.67 52122 +1966 218 17.06 11.06 15.41 0.67 432.68 276.3 51958 +1966 219 15.46 9.46 13.81 0.45 394.52 278.66 51791 +1966 220 14.53 8.53 12.88 1.16 373.68 279.63 51622 +1966 221 15.77 9.77 14.12 0.09 401.68 276.57 51451 +1966 222 19.78 13.78 18.13 0 504.78 356.25 51279 +1966 223 17.69 11.69 16.04 0 448.55 361.39 51105 +1966 224 19.89 13.89 18.24 0.01 507.9 265.27 50929 +1966 225 21.04 15.04 19.39 0 541.5 348.75 50751 +1966 226 26.84 20.84 25.19 0.47 741.19 243.25 50572 +1966 227 22.46 16.46 20.81 0.57 585.58 256 50392 +1966 228 22.03 16.03 20.38 0.06 571.92 256.27 50210 +1966 229 22.01 16.01 20.36 0 571.29 340.55 50026 +1966 230 21.78 15.78 20.13 0.58 564.11 255.09 49842 +1966 231 20.58 14.58 18.93 0.7 527.84 257.04 49656 +1966 232 19.34 13.34 17.69 0 492.47 345.29 49469 +1966 233 22.43 16.43 20.78 0 584.62 333.64 49280 +1966 234 28.18 22.18 26.53 0 795.27 307.96 49091 +1966 235 26.56 20.56 24.91 0 730.29 314.19 48900 +1966 236 24.41 18.41 22.76 0.23 651.04 241.45 48709 +1966 237 22.77 16.77 21.12 0.08 595.59 244.93 48516 +1966 238 21.24 15.24 19.59 0 547.53 330.25 48323 +1966 239 22.94 16.94 21.29 3.7 601.15 242.15 48128 +1966 240 25.03 19.03 23.38 0 673.11 313.14 47933 +1966 241 20.05 14.05 18.4 0 512.47 329.11 47737 +1966 242 20.9 14.9 19.25 0.19 537.31 243.54 47541 +1966 243 24.74 18.74 23.09 0.2 662.71 231.93 47343 +1966 244 23.09 17.09 21.44 0 606.09 313.7 47145 +1966 245 24.23 18.23 22.58 0 644.75 307.71 46947 +1966 246 23.94 17.94 22.29 0 634.72 306.93 46747 +1966 247 21.2 15.2 19.55 0.03 546.32 235.94 46547 +1966 248 24.25 18.25 22.6 0 645.44 302.14 46347 +1966 249 21.55 15.55 19.9 0.01 557 232.17 46146 +1966 250 19.72 13.72 18.07 0 503.09 313.23 45945 +1966 251 18.68 12.68 17.03 0 474.48 314.05 45743 +1966 252 21.26 15.26 19.61 0 548.14 304.41 45541 +1966 253 17.38 11.38 15.73 0 440.68 313.15 45339 +1966 254 17.84 11.84 16.19 0 452.4 309.87 45136 +1966 255 16.25 10.25 14.6 0.01 412.98 233.59 44933 +1966 256 12.49 6.49 10.84 2.2 331.25 237.67 44730 +1966 257 11.88 5.88 10.23 0 319.39 315.76 44527 +1966 258 15.47 9.47 13.82 0 394.74 306.38 44323 +1966 259 14.11 8.11 12.46 1.17 364.59 230.05 44119 +1966 260 14.74 8.74 13.09 0.01 378.3 227.29 43915 +1966 261 16.48 10.48 14.83 0 418.5 296.86 43711 +1966 262 20.21 14.21 18.56 0.02 517.07 213.87 43507 +1966 263 19.45 13.45 17.8 0 495.53 284.81 43303 +1966 264 21.99 15.99 20.34 0 570.66 275.11 43099 +1966 265 19.15 13.15 17.5 0 487.23 280.75 42894 +1966 266 15.68 9.68 14.03 0.24 399.59 214.75 42690 +1966 267 14.67 8.67 13.02 0 376.76 285.69 42486 +1966 268 15.84 9.84 14.19 0 403.31 280.77 42282 +1966 269 16.21 10.21 14.56 0 412.03 277.49 42078 +1966 270 16.37 10.37 14.72 0.15 415.85 205.9 41875 +1966 271 20.01 14.01 18.36 0 511.32 263.43 41671 +1966 272 23.26 17.26 21.61 0 611.72 251.62 41468 +1966 273 18.86 12.86 17.21 0.44 479.33 195.88 41265 +1966 274 15.38 9.38 13.73 0.32 392.69 199.53 41062 +1966 275 15.28 9.28 13.63 0.14 390.41 197.61 40860 +1966 276 12.99 6.99 11.34 1.62 341.25 198.63 40658 +1966 277 12.41 6.41 10.76 0.04 329.68 197.33 40456 +1966 278 14.75 8.75 13.1 0.03 378.52 192.2 40255 +1966 279 11.01 5.01 9.36 2.08 303.11 194.61 40054 +1966 280 15.1 9.1 13.45 0.01 386.34 187.66 39854 +1966 281 16.54 10.54 14.89 0 419.95 244.8 39654 +1966 282 13.52 7.52 11.87 0 352.13 247.49 39455 +1966 283 14.26 8.26 12.61 0 367.81 243.45 39256 +1966 284 15.02 9.02 13.37 0 384.54 239.15 39058 +1966 285 13.08 7.08 11.43 0 343.08 239.72 38861 +1966 286 11.04 5.04 9.39 0 303.66 239.9 38664 +1966 287 13.53 7.53 11.88 0 352.34 233.34 38468 +1966 288 12.29 6.29 10.64 0 327.32 232.41 38273 +1966 289 14.13 8.13 12.48 0 365.02 227.01 38079 +1966 290 14.7 8.7 13.05 0.08 377.42 167.45 37885 +1966 291 22.87 16.87 21.22 0.24 598.86 152.77 37693 +1966 292 23.14 17.14 21.49 0 607.74 200.49 37501 +1966 293 21.78 15.78 20.13 0 564.11 201.33 37311 +1966 294 20.26 14.26 18.61 0.37 518.51 151.55 37121 +1966 295 19.28 13.28 17.63 0.03 490.81 151.06 36933 +1966 296 21.49 15.49 19.84 0 555.15 194.19 36745 +1966 297 20.23 14.23 18.58 0 517.65 194.38 36560 +1966 298 18.01 12.01 16.36 0 456.79 196.28 36375 +1966 299 16.9 10.9 15.25 0 428.73 195.56 36191 +1966 300 17.15 11.15 15.5 0.76 434.92 144.41 36009 +1966 301 18.27 12.27 16.62 0.08 463.59 141.11 35829 +1966 302 18.8 12.8 17.15 0.16 477.71 138.5 35650 +1966 303 15.52 9.52 13.87 0.22 395.89 140.78 35472 +1966 304 18.39 12.39 16.74 0 466.76 180.59 35296 +1966 305 6.09 0.09 4.44 0 223.77 193.35 35122 +1966 306 7.98 1.98 6.33 0.13 251.83 142.06 34950 +1966 307 8.27 2.27 6.62 0 256.39 186.62 34779 +1966 308 6.4 0.4 4.75 0 228.18 185.65 34610 +1966 309 9.98 3.98 8.33 0.03 284.76 135.01 34444 +1966 310 8.66 2.66 7.01 0 262.64 178.87 34279 +1966 311 10.58 4.58 8.93 0 295.33 174.8 34116 +1966 312 11.48 5.48 9.83 0.73 311.82 128.41 33956 +1966 313 8.77 2.77 7.12 0.63 264.42 128.88 33797 +1966 314 4.59 -1.41 2.94 0.86 203.46 129.93 33641 +1966 315 6.39 0.39 4.74 0.58 228.04 127.02 33488 +1966 316 12.55 6.55 10.9 0.67 332.44 121.03 33337 +1966 317 12.24 6.24 10.59 0 326.35 159.56 33188 +1966 318 10.54 4.54 8.89 0 294.62 159.03 33042 +1966 319 6.66 0.66 5.01 0.45 231.94 120.54 32899 +1966 320 6.23 0.23 4.58 0.83 225.75 119.37 32758 +1966 321 3.46 -2.54 1.81 1.06 189.23 119.18 32620 +1966 322 2.53 -3.47 0.88 1.59 178.16 118.21 32486 +1966 323 -0.65 -6.65 -2.3 0.45 144.44 160.33 32354 +1966 324 3.97 -2.03 2.32 0 195.54 194.86 32225 +1966 325 6.62 0.62 4.97 0.51 231.36 153.3 32100 +1966 326 6.55 0.55 4.9 0.15 230.34 111.11 31977 +1966 327 6.06 0.06 4.41 0.97 223.35 109.98 31858 +1966 328 7.12 1.12 5.47 0.41 238.71 107.94 31743 +1966 329 4.3 -1.7 2.65 0.47 199.72 108.23 31631 +1966 330 2.87 -3.13 1.22 0.1 182.14 107.76 31522 +1966 331 0.89 -5.11 -0.76 0 160.01 143.37 31417 +1966 332 2.81 -3.19 1.16 0.27 181.43 105.55 31316 +1966 333 0.21 -5.79 -1.44 0.03 152.96 105.69 31218 +1966 334 -0.1 -6.1 -1.75 0.06 149.84 147.55 31125 +1966 335 -1.52 -7.52 -3.17 0.07 136.24 147.44 31035 +1966 336 2.61 -3.39 0.96 0 179.09 179.09 30949 +1966 337 4.71 -1.29 3.06 0 205.02 133.54 30867 +1966 338 0.7 -5.3 -0.95 0 158.01 134.68 30790 +1966 339 2.69 -3.31 1.04 0 180.03 132.92 30716 +1966 340 4.87 -1.13 3.22 0 207.13 130.98 30647 +1966 341 8.15 2.15 6.5 0 254.5 127.91 30582 +1966 342 8.91 2.91 7.26 0 266.71 126.59 30521 +1966 343 4.08 -1.92 2.43 0 196.93 128.93 30465 +1966 344 7.02 1.02 5.37 0 237.22 126 30413 +1966 345 1.76 -4.24 0.11 0 169.43 128.55 30366 +1966 346 5.53 -0.47 3.88 0.04 215.99 94.48 30323 +1966 347 2.79 -3.21 1.14 0.41 181.2 95.17 30284 +1966 348 4.63 -1.37 2.98 0 203.98 125.56 30251 +1966 349 8.98 2.98 7.33 1.07 267.86 91.76 30221 +1966 350 5.78 -0.22 4.13 0 219.44 124.17 30197 +1966 351 4.51 -1.49 2.86 0.04 202.42 93.52 30177 +1966 352 4.15 -1.85 2.5 0.06 197.81 93.6 30162 +1966 353 2.68 -3.32 1.03 0.06 179.91 94.13 30151 +1966 354 2.64 -3.36 0.99 0.58 179.44 94.12 30145 +1966 355 2.25 -3.75 0.6 0 174.94 125.68 30144 +1966 356 1.18 -4.82 -0.47 0.22 163.1 94.65 30147 +1966 357 -1.85 -7.85 -3.5 0 133.23 127.5 30156 +1966 358 -0.45 -6.45 -2.1 0.75 146.39 141.43 30169 +1966 359 0.99 -5.01 -0.66 0.61 161.07 140.9 30186 +1966 360 3.23 -2.77 1.58 0.15 186.44 139.91 30208 +1966 361 3.51 -2.49 1.86 0.04 189.84 139.54 30235 +1966 362 7.21 1.21 5.56 0 240.06 168.27 30267 +1966 363 8.86 2.86 7.21 0 265.89 123.68 30303 +1966 364 5.48 -0.52 3.83 0 215.31 126.34 30343 +1966 365 5.75 -0.25 4.1 0 219.02 126.74 30388 +1967 1 4.38 -1.62 2.73 0 200.75 128.44 30438 +1967 2 1.07 -4.93 -0.58 0 161.92 130.86 30492 +1967 3 2.92 -3.08 1.27 0 182.73 130.91 30551 +1967 4 1.76 -4.24 0.11 0 169.43 132.4 30614 +1967 5 4.04 -1.96 2.39 0.04 196.42 98.9 30681 +1967 6 1.09 -4.91 -0.56 0 162.13 134.27 30752 +1967 7 0.68 -5.32 -0.97 0.14 157.8 101.44 30828 +1967 8 -2.77 -8.77 -4.42 0 125.16 138.16 30907 +1967 9 -0.72 -6.72 -2.37 0.01 143.77 146.6 30991 +1967 10 1.66 -4.34 0.01 0.64 168.32 104.14 31079 +1967 11 1.98 -4.02 0.33 0.53 171.89 104.77 31171 +1967 12 1.34 -4.66 -0.31 0.06 164.82 105.77 31266 +1967 13 0.34 -5.66 -1.31 0.1 154.29 107.35 31366 +1967 14 1.08 -4.92 -0.57 0.15 162.03 108.2 31469 +1967 15 3.25 -2.75 1.6 0.04 186.68 108.43 31575 +1967 16 2.29 -3.71 0.64 0 175.4 146.4 31686 +1967 17 3.73 -2.27 2.08 0 192.55 147.27 31800 +1967 18 -5.26 -11.26 -6.91 0 105.4 153.19 31917 +1967 19 -0.35 -6.35 -2 0 147.37 153.25 32038 +1967 20 -0.56 -6.56 -2.21 0 145.31 154.95 32161 +1967 21 0.76 -5.24 -0.89 0.5 158.64 117.26 32289 +1967 22 -0.42 -6.42 -2.07 0 146.68 158.68 32419 +1967 23 -1.52 -7.52 -3.17 0 136.24 160.97 32552 +1967 24 1.93 -4.07 0.28 0 171.33 161.35 32688 +1967 25 1.81 -4.19 0.16 0 169.99 163.31 32827 +1967 26 3.66 -2.34 2.01 0 191.68 164.14 32969 +1967 27 3.31 -2.69 1.66 0 187.4 166.39 33114 +1967 28 3.28 -2.72 1.63 0.09 187.04 126.47 33261 +1967 29 -0.58 -6.58 -2.23 0 145.12 173.16 33411 +1967 30 2.88 -3.12 1.23 0.14 182.26 130.13 33564 +1967 31 3.08 -2.92 1.43 0.33 184.64 131.82 33718 +1967 32 4.03 -1.97 2.38 0 196.29 177.25 33875 +1967 33 0.9 -5.1 -0.75 0.01 160.12 136.37 34035 +1967 34 4.73 -1.27 3.08 0 205.29 181.59 34196 +1967 35 3.74 -2.26 2.09 0 192.67 184.44 34360 +1967 36 6.83 0.83 5.18 0 234.42 184.57 34526 +1967 37 8.65 2.65 7 0.91 262.48 138.99 34694 +1967 38 7.7 1.7 6.05 0.01 247.49 141.7 34863 +1967 39 6.57 0.57 4.92 0 230.63 192.52 35035 +1967 40 7.99 1.99 6.34 0.04 251.99 145.37 35208 +1967 41 3.32 -2.68 1.67 0 187.52 200.29 35383 +1967 42 6.97 0.97 5.32 0.55 236.48 149.93 35560 +1967 43 6.66 0.66 5.01 0.35 231.94 152.16 35738 +1967 44 6.27 0.27 4.62 0.17 226.32 154.33 35918 +1967 45 5.32 -0.68 3.67 0.23 213.14 156.91 36099 +1967 46 3.5 -2.5 1.85 0 189.71 213.35 36282 +1967 47 1.37 -4.63 -0.28 0 165.15 217.69 36466 +1967 48 -0.38 -6.38 -2.03 0 147.07 221.61 36652 +1967 49 -1.46 -7.46 -3.11 0.1 136.79 204.88 36838 +1967 50 2.21 -3.79 0.56 0 174.49 261.1 37026 +1967 51 3.49 -2.51 1.84 0 189.59 227.46 37215 +1967 52 2.58 -3.42 0.93 0 178.74 231 37405 +1967 53 4.73 -1.27 3.08 0 205.29 232.24 37596 +1967 54 9.22 3.22 7.57 0.07 271.84 172.84 37788 +1967 55 7.74 1.74 6.09 0.16 248.11 176.3 37981 +1967 56 10.42 4.42 8.77 0 292.48 234.59 38175 +1967 57 8.51 2.51 6.86 0 260.22 239.76 38370 +1967 58 10.58 4.58 8.93 0 295.33 240.11 38565 +1967 59 8.6 2.6 6.95 0.11 261.67 183.93 38761 +1967 60 9.43 3.43 7.78 0.38 275.36 185.33 38958 +1967 61 10.72 4.72 9.07 0 297.85 248.32 39156 +1967 62 9.82 3.82 8.17 0 282 252.27 39355 +1967 63 10.63 4.63 8.98 0.26 296.23 190.62 39553 +1967 64 5.44 -0.56 3.79 0.01 214.77 197.37 39753 +1967 65 3.51 -2.49 1.86 1.21 189.84 200.92 39953 +1967 66 6.67 0.67 5.02 0 232.08 267.52 40154 +1967 67 6.88 0.88 5.23 0 235.16 270.19 40355 +1967 68 10.77 4.77 9.12 0.04 298.75 201.06 40556 +1967 69 10.49 4.49 8.84 0 293.72 271.07 40758 +1967 70 6.46 0.46 4.81 0 229.04 279.01 40960 +1967 71 5.37 -0.63 3.72 0.97 213.82 212.34 41163 +1967 72 5.84 -0.16 4.19 0.07 220.27 214.09 41366 +1967 73 2.12 -3.88 0.47 0 173.47 291.77 41569 +1967 74 5.95 -0.05 4.3 0 221.81 290.78 41772 +1967 75 7.12 1.12 5.47 0 238.71 292.16 41976 +1967 76 9.71 3.71 8.06 0 280.11 291.39 42179 +1967 77 12.61 6.61 10.96 0.04 333.63 217.05 42383 +1967 78 10.95 4.95 9.3 0.95 302.02 221.07 42587 +1967 79 9.3 3.3 7.65 0 273.17 299.93 42791 +1967 80 14.26 8.26 12.61 0 367.81 294.14 42996 +1967 81 12.86 6.86 11.21 0 338.63 299.29 43200 +1967 82 12.6 6.6 10.95 0 333.43 302.36 43404 +1967 83 11.11 5.11 9.46 0 304.95 307.37 43608 +1967 84 12.96 6.96 11.31 0.11 340.64 230 43812 +1967 85 17.43 11.43 15.78 0.32 441.94 224.73 44016 +1967 86 16.3 10.3 14.65 0 414.18 304.61 44220 +1967 87 14.04 8.04 12.39 0 363.09 311.9 44424 +1967 88 14.39 8.39 12.74 0 370.63 313.49 44627 +1967 89 8.94 2.94 7.29 0.01 267.2 243.98 44831 +1967 90 9.43 3.43 7.78 0.01 275.36 245.21 45034 +1967 91 12.31 6.31 10.66 0 327.71 324.34 45237 +1967 92 14.73 8.73 13.08 0 378.08 321.74 45439 +1967 93 11.93 5.93 10.28 0 320.35 329.46 45642 +1967 94 12.41 6.41 10.76 0 329.68 330.71 45843 +1967 95 10.5 4.5 8.85 0 293.9 336.24 46045 +1967 96 10.18 4.18 8.53 0 288.25 338.89 46246 +1967 97 9.41 3.41 7.76 0 275.02 342.2 46446 +1967 98 10.32 4.32 8.67 0.05 290.71 257.02 46647 +1967 99 12.75 6.75 11.1 0.52 336.42 255.2 46846 +1967 100 11.49 5.49 9.84 0.07 312.01 258.45 47045 +1967 101 11.75 5.75 10.1 0.24 316.91 259.54 47243 +1967 102 9.61 3.61 7.96 0 278.4 351.71 47441 +1967 103 13.4 7.4 11.75 0 349.64 346.53 47638 +1967 104 12.98 6.98 11.33 0 341.05 349.21 47834 +1967 105 9.22 3.22 7.57 0 271.84 357.85 48030 +1967 106 11.59 5.59 9.94 0.01 313.89 266.52 48225 +1967 107 13.78 7.78 12.13 0.53 357.57 264.46 48419 +1967 108 13.44 7.44 11.79 0.41 350.47 266.31 48612 +1967 109 10.55 4.55 8.9 0 294.79 362.33 48804 +1967 110 15.67 9.67 14.02 0.02 399.35 264.74 48995 +1967 111 11.6 5.6 9.95 0.45 314.07 272.52 49185 +1967 112 6.73 0.73 5.08 0 232.96 372.98 49374 +1967 113 9.67 3.67 8.02 0.28 279.43 277.32 49561 +1967 114 11.8 5.8 10.15 0 317.87 367.36 49748 +1967 115 14.34 8.34 12.69 0 369.54 363.4 49933 +1967 116 16.28 10.28 14.63 0.02 413.7 269.92 50117 +1967 117 16.72 10.72 15.07 0 424.32 360.03 50300 +1967 118 16.52 10.52 14.87 0 419.46 361.85 50481 +1967 119 16.89 10.89 15.24 0.44 428.48 271.53 50661 +1967 120 18.33 12.33 16.68 1.16 465.17 269.36 50840 +1967 121 19.66 13.66 18.01 1.91 501.4 267.13 51016 +1967 122 18.62 12.62 16.97 1.52 472.87 270.42 51191 +1967 123 15.73 9.73 14.08 0.04 400.75 277.17 51365 +1967 124 15.19 9.19 13.54 0.01 388.37 278.99 51536 +1967 125 16.34 10.34 14.69 0.49 415.13 277.52 51706 +1967 126 17.35 11.35 15.7 0.43 439.92 276.19 51874 +1967 127 18.6 12.6 16.95 1.27 472.34 274.12 52039 +1967 128 14.85 8.85 13.2 0.64 380.74 282.51 52203 +1967 129 17.43 11.43 15.78 0.67 441.94 278.05 52365 +1967 130 18.16 12.16 16.51 0.09 460.7 277.05 52524 +1967 131 18.79 12.79 17.14 0 477.44 368.28 52681 +1967 132 12.72 6.72 11.07 0.04 335.82 288.64 52836 +1967 133 15.57 9.57 13.92 0 397.04 378.86 52989 +1967 134 13.95 7.95 12.3 0 361.17 383.53 53138 +1967 135 16.66 10.66 15.01 0 422.85 377.38 53286 +1967 136 16.85 10.85 15.2 0 427.5 377.49 53430 +1967 137 18.74 12.74 17.09 0 476.09 372.65 53572 +1967 138 20.11 14.11 18.46 0 514.19 368.82 53711 +1967 139 21.76 15.76 20.11 0 563.48 363.69 53848 +1967 140 20.6 14.6 18.95 0.14 528.43 276.23 53981 +1967 141 19.22 13.22 17.57 0.01 489.16 279.99 54111 +1967 142 15.11 9.11 13.46 0.87 386.56 289.14 54238 +1967 143 17.3 11.3 15.65 1.35 438.67 285.13 54362 +1967 144 16.25 10.25 14.6 0.07 412.98 287.68 54483 +1967 145 17.53 11.53 15.88 0.09 444.47 285.34 54600 +1967 146 19.86 13.86 18.21 0.02 507.05 280.17 54714 +1967 147 22.05 16.05 20.4 0.04 572.55 274.69 54824 +1967 148 21.36 15.36 19.71 0.24 551.18 276.88 54931 +1967 149 21.79 15.79 20.14 0.22 564.42 275.93 55034 +1967 150 19.13 13.13 17.48 0.26 486.69 283.07 55134 +1967 151 16.3 10.3 14.65 0.91 414.18 289.65 55229 +1967 152 19.86 13.86 18.21 0.95 507.05 281.65 55321 +1967 153 12.02 6.02 10.37 0.05 322.08 297.64 55409 +1967 154 16.25 10.25 14.6 0 412.98 387.01 55492 +1967 155 14.81 8.81 13.16 0 379.85 390.96 55572 +1967 156 14.47 8.47 12.82 0 372.37 392.12 55648 +1967 157 17.47 11.47 15.82 0 442.95 384.26 55719 +1967 158 16.71 10.71 15.06 0 424.07 386.61 55786 +1967 159 17.01 11.01 15.36 0 431.44 386 55849 +1967 160 16.68 10.68 15.03 0 423.34 387.12 55908 +1967 161 16.08 10.08 14.43 0 408.95 388.84 55962 +1967 162 18.36 12.36 16.71 0 465.96 382.32 56011 +1967 163 20.55 14.55 18.9 0.1 526.96 281.51 56056 +1967 164 19.87 13.87 18.22 0 507.33 377.72 56097 +1967 165 21.67 15.67 20.02 0 560.7 371.44 56133 +1967 166 20.54 14.54 18.89 0 526.67 375.59 56165 +1967 167 22.12 16.12 20.47 0 574.76 369.77 56192 +1967 168 22.42 16.42 20.77 0.4 584.3 276.52 56214 +1967 169 21.25 15.25 19.6 0.76 547.84 279.82 56231 +1967 170 21.13 15.13 19.48 0.65 544.21 280.15 56244 +1967 171 20.52 14.52 18.87 0.47 526.08 281.82 56252 +1967 172 20.87 14.87 19.22 0.08 536.42 280.89 56256 +1967 173 21.03 15.03 19.38 0 541.2 373.93 56255 +1967 174 24.25 18.25 22.6 0 645.44 361.17 56249 +1967 175 22.97 16.97 21.32 0 602.13 366.45 56238 +1967 176 21.69 15.69 20.04 0 561.31 371.36 56223 +1967 177 23.32 17.32 21.67 0 613.72 364.9 56203 +1967 178 24.99 18.99 23.34 0 671.66 357.79 56179 +1967 179 26.98 20.98 25.33 0 746.69 348.29 56150 +1967 180 26.51 20.51 24.86 0.13 728.36 262.87 56116 +1967 181 26.54 20.54 24.89 0 729.52 350.28 56078 +1967 182 27.02 21.02 25.37 0 748.27 347.78 56035 +1967 183 28.2 22.2 26.55 0.3 796.1 256.15 55987 +1967 184 26.03 20.03 24.38 1.04 710.03 264.2 55935 +1967 185 24.67 18.67 23.02 2.07 660.22 268.79 55879 +1967 186 23.18 17.18 21.53 0 609.06 364.41 55818 +1967 187 25.54 19.54 23.89 0 691.73 354.05 55753 +1967 188 22.99 16.99 21.34 0 602.79 364.73 55684 +1967 189 23.28 17.28 21.63 0 612.39 363.39 55611 +1967 190 21.88 15.88 20.23 0.18 567.22 276.36 55533 +1967 191 21.16 15.16 19.51 0 545.11 370.87 55451 +1967 192 21.84 15.84 20.19 0 565.97 368.07 55366 +1967 193 23.82 17.82 22.17 0 630.61 359.98 55276 +1967 194 25.16 19.16 23.51 0.01 677.81 265.48 55182 +1967 195 24.51 18.51 22.86 0 654.55 356.57 55085 +1967 196 27.5 21.5 25.85 0 767.42 342.14 54984 +1967 197 32.19 26.19 30.54 0 977.4 314.67 54879 +1967 198 30.77 24.77 29.12 0 909.26 323.18 54770 +1967 199 30.34 24.34 28.69 0.69 889.44 244.07 54658 +1967 200 23.54 17.54 21.89 0.43 621.1 269 54542 +1967 201 19.16 13.16 17.51 0.52 487.51 280.54 54423 +1967 202 20.47 14.47 18.82 0.66 524.62 276.87 54301 +1967 203 26.32 20.32 24.67 0 721.06 344.93 54176 +1967 204 23.89 17.89 22.24 0 633 355.23 54047 +1967 205 25.19 19.19 23.54 0 678.9 349.14 53915 +1967 206 24.55 18.55 22.9 0.12 655.97 263.55 53780 +1967 207 22.67 16.67 21.02 0.18 592.35 268.81 53643 +1967 208 19.49 13.49 17.84 0.01 496.64 276.75 53502 +1967 209 20.32 14.32 18.67 0 520.25 365.61 53359 +1967 210 19.73 13.73 18.08 0 503.37 366.94 53213 +1967 211 21.18 15.18 19.53 0 545.72 361.25 53064 +1967 212 21.01 15.01 19.36 0 540.6 361.06 52913 +1967 213 17.15 11.15 15.5 0 434.92 372.39 52760 +1967 214 21.46 15.46 19.81 0 554.23 357.97 52604 +1967 215 22.01 16.01 20.36 0 571.29 355.3 52445 +1967 216 26.25 20.25 24.6 0 718.38 336.75 52285 +1967 217 25.16 19.16 23.51 0.04 677.81 255.6 52122 +1967 218 22.11 16.11 20.46 0 574.44 352.25 51958 +1967 219 21.1 15.1 19.45 0.88 543.31 266.12 51791 +1967 220 20.54 14.54 18.89 0.49 526.67 266.85 51622 +1967 221 19.63 13.63 17.98 0 500.56 357.77 51451 +1967 222 19.29 13.29 17.64 0.24 491.09 268.34 51279 +1967 223 17.53 11.53 15.88 0.12 444.47 271.38 51105 +1967 224 15.15 9.15 13.5 0.04 387.46 275.23 50929 +1967 225 16.84 10.84 15.19 0 427.25 361.49 50751 +1967 226 20.31 14.31 18.66 0.22 519.96 262.54 50572 +1967 227 24.45 18.45 22.8 0 652.44 333.6 50392 +1967 228 21.96 15.96 20.31 0.31 569.72 256.46 50210 +1967 229 22.3 16.3 20.65 0 580.46 339.51 50026 +1967 230 21.82 15.82 20.17 0 565.35 339.97 49842 +1967 231 22.75 16.75 21.1 0.3 594.94 251.39 49656 +1967 232 23.86 17.86 22.21 0 631.98 329.65 49469 +1967 233 20.97 14.97 19.32 0 539.4 338.69 49280 +1967 234 21.11 15.11 19.46 0 543.61 336.83 49091 +1967 235 23.33 17.33 21.68 0 614.06 327.49 48900 +1967 236 23.46 17.46 21.81 0 618.41 325.62 48709 +1967 237 26.26 20.26 24.61 0 718.77 312.63 48516 +1967 238 27.57 21.57 25.92 0 770.25 305.11 48323 +1967 239 25.65 19.65 24 0 695.8 312.25 48128 +1967 240 30.46 24.46 28.81 0 894.93 287.54 47933 +1967 241 25.18 19.18 23.53 0.29 678.54 233.17 47737 +1967 242 26.21 20.21 24.56 0.97 716.86 228.71 47541 +1967 243 22.79 16.79 21.14 0.52 596.25 237.4 47343 +1967 244 15.27 9.27 13.62 0.62 390.18 252.28 47145 +1967 245 11.75 5.75 10.1 2.7 316.91 256.3 46947 +1967 246 10.23 4.23 8.58 1.81 289.12 256.78 46747 +1967 247 11.28 5.28 9.63 0 308.09 338.64 46547 +1967 248 15.88 9.88 14.23 0 404.24 327.24 46347 +1967 249 16.89 10.89 15.24 0 428.48 322.74 46146 +1967 250 15.68 9.68 14.03 0.04 399.59 242.73 45945 +1967 251 17.73 11.73 16.08 0.27 449.57 237.41 45743 +1967 252 15.52 9.52 13.87 0.02 395.89 239.76 45541 +1967 253 18.04 12.04 16.39 1.47 457.57 233.61 45339 +1967 254 22.26 16.26 20.61 0 579.19 297.09 45136 +1967 255 21.02 15.02 19.37 0 540.9 298.8 44933 +1967 256 21.13 15.13 19.48 0 544.21 296.26 44730 +1967 257 23.05 17.05 21.4 0 604.77 288.05 44527 +1967 258 22.87 16.87 21.22 0 598.86 286.4 44323 +1967 259 21.28 15.28 19.63 0 548.75 289.07 44119 +1967 260 22.13 16.13 20.48 0.29 575.07 213.12 43915 +1967 261 22.9 16.9 21.25 0 599.84 279.35 43711 +1967 262 21.53 15.53 19.88 0 556.38 281.35 43507 +1967 263 22.23 16.23 20.58 1.18 578.24 207.63 43303 +1967 264 19.32 13.32 17.67 0 491.92 282.63 43099 +1967 265 19.36 13.36 17.71 0 493.03 280.21 42894 +1967 266 18.09 12.09 16.44 0.03 458.88 210.71 42690 +1967 267 19.05 13.05 17.4 0 484.5 275.95 42486 +1967 268 19.1 13.1 17.45 0.03 485.86 204.99 42282 +1967 269 22.97 16.97 21.32 0.64 602.13 195.06 42078 +1967 270 23.8 17.8 22.15 0.49 629.93 191.22 41875 +1967 271 25.45 19.45 23.8 0 688.41 246.97 41671 +1967 272 21.23 15.23 19.58 0 547.23 257.54 41468 +1967 273 20.29 14.29 18.64 0.16 519.38 193.21 41265 +1967 274 17.59 11.59 15.94 0 446 261.47 41062 +1967 275 13.34 7.34 11.69 0 348.4 266.97 40860 +1967 276 15.3 9.3 13.65 0 390.86 260.75 40658 +1967 277 13.85 7.85 12.2 0 359.05 260.72 40456 +1967 278 16.02 10.02 14.37 0 407.53 253.89 40255 +1967 279 14.46 8.46 12.81 0.16 372.15 190.49 40054 +1967 280 16.4 10.4 14.75 0.11 416.57 185.82 39854 +1967 281 16.98 10.98 15.33 0 430.7 243.93 39654 +1967 282 16.16 10.16 14.51 0 410.84 242.84 39455 +1967 283 12.63 6.63 10.98 0 334.03 246.07 39256 +1967 284 15.14 9.14 13.49 0 387.24 238.94 39058 +1967 285 13.33 7.33 11.68 0 348.2 239.33 38861 +1967 286 13.89 7.89 12.24 0.03 359.9 176.77 38664 +1967 287 12.99 6.99 11.34 0 341.25 234.16 38468 +1967 288 12.64 6.64 10.99 0.06 334.22 173.93 38273 +1967 289 9.27 3.27 7.62 0.02 272.67 175.28 38079 +1967 290 12.63 6.63 10.98 0.22 334.03 169.83 37885 +1967 291 13.57 7.57 11.92 0.58 353.17 166.77 37693 +1967 292 12.78 6.78 11.13 0 337.02 220.85 37501 +1967 293 15.56 9.56 13.91 0 396.81 213.85 37311 +1967 294 13.37 7.37 11.72 0 349.02 214.42 37121 +1967 295 16.33 10.33 14.68 0.22 414.89 155.21 36933 +1967 296 21.28 15.28 19.63 0.72 548.75 146 36745 +1967 297 18.63 12.63 16.98 0.06 473.14 148.21 36560 +1967 298 16.83 10.83 15.18 0.43 427.01 148.79 36375 +1967 299 19.06 13.06 17.41 0.88 484.77 143.71 36191 +1967 300 13 7 11.35 0 341.45 198.88 36009 +1967 301 12.33 6.33 10.68 0.16 328.11 147.95 35829 +1967 302 12.49 6.49 10.84 0 331.25 194.47 35650 +1967 303 13.88 7.88 12.23 0 359.69 190.08 35472 +1967 304 15.09 9.09 13.44 0 386.11 185.94 35296 +1967 305 7.28 1.28 5.63 0 241.11 192.32 35122 +1967 306 5.77 -0.23 4.12 0 219.3 191.33 34950 +1967 307 6.22 0.22 4.57 0 225.61 188.43 34779 +1967 308 7.84 1.84 6.19 0.12 249.65 138.3 34610 +1967 309 11.78 5.78 10.13 1.75 317.49 133.54 34444 +1967 310 13.11 7.11 11.46 0 343.69 174.06 34279 +1967 311 13.95 7.95 12.3 0 361.17 170.87 34116 +1967 312 10.51 4.51 8.86 1.09 294.08 129.19 33956 +1967 313 4.01 -1.99 2.36 0 196.04 175.62 33797 +1967 314 1.23 -4.77 -0.42 0 163.64 175.35 33641 +1967 315 2.22 -3.78 0.57 0 174.6 172.2 33488 +1967 316 5.39 -0.61 3.74 0.19 214.09 125.94 33337 +1967 317 9.28 3.28 7.63 0 272.84 162.54 33188 +1967 318 8.15 2.15 6.5 0.01 254.5 120.91 33042 +1967 319 11.88 5.88 10.23 0.02 319.39 116.99 32899 +1967 320 11.77 5.77 10.12 0 317.3 154.27 32758 +1967 321 5.44 -0.56 3.79 0.05 214.77 118.21 32620 +1967 322 7.4 1.4 5.75 0 242.92 154.35 32486 +1967 323 7.92 1.92 6.27 0.03 250.9 114.24 32354 +1967 324 5.9 -0.1 4.25 0 221.11 151.79 32225 +1967 325 11.35 5.35 9.7 0.3 309.39 109.16 32100 +1967 326 10.73 4.73 9.08 0.04 298.03 108.53 31977 +1967 327 13.38 7.38 11.73 0.03 349.23 105.17 31858 +1967 328 7.97 1.97 6.32 0 251.67 143.28 31743 +1967 329 6.18 0.18 4.53 0 225.05 143.1 31631 +1967 330 6.65 0.65 5 0 231.79 141.33 31522 +1967 331 9.37 3.37 7.72 0 274.35 137.94 31417 +1967 332 3.54 -2.46 1.89 0 190.2 140.33 31316 +1967 333 1.02 -4.98 -0.63 0 161.39 140.54 31218 +1967 334 4.39 -1.61 2.74 0 200.88 137.64 31125 +1967 335 5.26 -0.74 3.61 0 212.33 135.94 31035 +1967 336 2.22 -3.78 0.57 0 174.6 136.57 30949 +1967 337 1.23 -4.77 -0.42 0 163.64 135.39 30867 +1967 338 2.3 -3.7 0.65 0.1 175.51 100.44 30790 +1967 339 1.37 -4.63 -0.28 0 165.15 133.57 30716 +1967 340 -1.05 -7.05 -2.7 0 140.62 133.88 30647 +1967 341 -0.41 -6.41 -2.06 0 146.78 132.69 30582 +1967 342 -0.63 -6.63 -2.28 0.35 144.63 143.36 30521 +1967 343 -1.06 -7.06 -2.71 0.43 140.52 144.3 30465 +1967 344 2.44 -3.56 0.79 0 177.12 174.2 30413 +1967 345 1.12 -4.88 -0.53 0 162.45 174.31 30366 +1967 346 3.26 -2.74 1.61 0 186.8 172.35 30323 +1967 347 1.76 -4.24 0.11 0 169.43 172.32 30284 +1967 348 6.18 0.18 4.53 0 225.05 168.78 30251 +1967 349 8.05 2.05 6.4 0 252.93 123.02 30221 +1967 350 5.85 -0.15 4.2 0 220.41 124.13 30197 +1967 351 5.47 -0.53 3.82 0.41 215.17 93.11 30177 +1967 352 2.75 -3.25 1.1 0.01 180.73 94.15 30162 +1967 353 -2.33 -8.33 -3.98 0.15 128.97 139.97 30151 +1967 354 -1.7 -7.7 -3.35 0 134.59 171.62 30145 +1967 355 1.25 -4.75 -0.4 0 163.85 170.25 30144 +1967 356 4.42 -1.58 2.77 0 201.26 124.58 30147 +1967 357 2.59 -3.41 0.94 0 178.86 125.6 30156 +1967 358 2.59 -3.41 0.94 0 178.86 125.69 30169 +1967 359 5.63 -0.37 3.98 0 217.37 124.15 30186 +1967 360 5.69 -0.31 4.04 1.12 218.19 93.35 30208 +1967 361 6.51 0.51 4.86 0 229.76 124.29 30235 +1967 362 4.05 -1.95 2.4 0 196.55 126.19 30267 +1967 363 2.07 -3.93 0.42 0.14 172.9 95.84 30303 +1967 364 2.7 -3.3 1.05 0.62 180.14 95.91 30343 +1967 365 1.28 -4.72 -0.37 0.42 164.17 96.85 30388 +1968 1 -4.24 -10.24 -5.89 0 113.14 132.15 30438 +1968 2 -0.18 -6.18 -1.83 0.06 149.05 142.03 30492 +1968 3 -3.25 -9.25 -4.9 0 121.12 176.92 30551 +1968 4 2.03 -3.97 0.38 0 172.45 132.27 30614 +1968 5 1.02 -4.98 -0.63 0 161.39 133.4 30681 +1968 6 -1.72 -7.72 -3.37 0.33 134.41 145.55 30752 +1968 7 -3.53 -9.53 -5.18 0.26 118.81 147.34 30828 +1968 8 -5.88 -11.88 -7.53 0.06 100.92 149.1 30907 +1968 9 -4.08 -10.08 -5.73 0.34 114.39 150.57 30991 +1968 10 -4.45 -10.45 -6.1 0.12 111.5 151.89 31079 +1968 11 -3.11 -9.11 -4.76 0 122.28 187.64 31171 +1968 12 -2.15 -8.15 -3.8 0 130.55 188.17 31266 +1968 13 -0.39 -6.39 -2.04 0 146.97 188.94 31366 +1968 14 6.27 0.27 4.62 0.01 226.32 150.47 31469 +1968 15 3 -3 1.35 0 183.68 188.71 31575 +1968 16 3.79 -2.21 2.14 0.08 193.29 152.53 31686 +1968 17 0.65 -5.35 -1 0 157.49 192.05 31800 +1968 18 0.48 -5.52 -1.17 0 155.73 193.82 31917 +1968 19 2.79 -3.21 1.14 0 181.2 194.04 32038 +1968 20 4.69 -1.31 3.04 0.36 204.76 155.71 32161 +1968 21 0.64 -5.36 -1.01 0.89 157.39 158.7 32289 +1968 22 -2.98 -8.98 -4.63 0.05 123.38 161.21 32419 +1968 23 0.03 -5.97 -1.62 0 151.15 201.46 32552 +1968 24 2.73 -3.27 1.08 0 180.49 201.59 32688 +1968 25 4.84 -1.16 3.19 0 206.73 161.45 32827 +1968 26 5.04 -0.96 3.39 0 209.38 163.23 32969 +1968 27 8.46 2.46 6.81 0 259.42 162.57 33114 +1968 28 9.44 3.44 7.79 0 275.52 163.86 33261 +1968 29 6.01 0.01 4.36 0 222.65 169.11 33411 +1968 30 3.89 -2.11 2.24 0 194.54 172.86 33564 +1968 31 5.94 -0.06 4.29 0 221.67 173.76 33718 +1968 32 7.97 1.97 6.32 0 251.67 174.18 33875 +1968 33 9.32 3.32 7.67 0 273.51 175.53 34035 +1968 34 8.34 2.34 6.69 0 257.5 178.62 34196 +1968 35 8.96 2.96 7.31 0 267.53 180.15 34360 +1968 36 7.69 1.69 6.04 0 247.34 183.82 34526 +1968 37 6.88 0.88 5.23 0 235.16 186.94 34694 +1968 38 5.97 -0.03 4.32 0 222.09 190.43 34863 +1968 39 10.19 4.19 8.54 0 288.42 189.02 35035 +1968 40 6.79 0.79 5.14 0.01 233.83 146.2 35208 +1968 41 6.12 0.12 4.47 0 224.2 198.11 35383 +1968 42 2.44 -3.56 0.79 0 177.12 203.47 35560 +1968 43 0.41 -5.59 -1.24 0 155.01 207.48 35738 +1968 44 1.76 -4.24 0.11 0 169.43 209.23 35918 +1968 45 3.84 -2.16 2.19 0.24 193.91 157.8 36099 +1968 46 5.1 -0.9 3.45 0 210.18 212.08 36282 +1968 47 1.64 -4.36 -0.01 0 168.1 217.51 36466 +1968 48 1.39 -4.61 -0.26 0.09 165.37 165.38 36652 +1968 49 -0.5 -6.5 -2.15 0 145.9 224.5 36838 +1968 50 -2.64 -8.64 -4.29 0.05 126.27 207.07 37026 +1968 51 1.2 -4.8 -0.45 0 163.31 229.13 37215 +1968 52 1.84 -4.16 0.19 0 170.32 231.54 37405 +1968 53 3.78 -2.22 2.13 0 193.17 233.04 37596 +1968 54 8.29 2.29 6.64 0 256.71 231.5 37788 +1968 55 9.01 3.01 7.36 0 268.36 233.66 37981 +1968 56 9.82 3.82 8.17 0 282 235.34 38175 +1968 57 9.69 3.69 8.04 0 279.77 238.35 38370 +1968 58 5.07 -0.93 3.42 0.33 209.78 184.67 38565 +1968 59 7.99 1.99 6.34 0 251.99 245.94 38761 +1968 60 16.79 10.79 15.14 0 426.03 235.54 38958 +1968 61 14.57 8.57 12.92 0 374.56 242.42 39156 +1968 62 11.57 5.57 9.92 0 313.51 249.87 39355 +1968 63 10.62 4.62 8.97 0 296.05 254.17 39553 +1968 64 8.51 2.51 6.86 0 260.22 259.78 39753 +1968 65 8.79 2.79 7.14 0 264.75 262.3 39953 +1968 66 6.48 0.48 4.83 0 229.33 267.72 40154 +1968 67 7.68 1.68 6.03 0.14 247.19 201.95 40355 +1968 68 8.93 2.93 7.28 0 267.04 270.59 40556 +1968 69 6.66 0.66 5.01 0 231.94 275.94 40758 +1968 70 4.45 -1.55 2.8 0 201.65 281.12 40960 +1968 71 7.41 1.41 5.76 0.01 243.07 210.63 41163 +1968 72 10.06 4.06 8.41 0.37 286.15 210.14 41366 +1968 73 8.61 2.61 6.96 0 261.83 284.82 41569 +1968 74 1.67 -4.33 0.02 0 168.43 294.94 41772 +1968 75 4.7 -1.3 3.05 0 204.89 294.87 41976 +1968 76 7.85 1.85 6.2 0.08 249.81 220.43 42179 +1968 77 6.83 0.83 5.18 0 234.42 297.77 42383 +1968 78 9.03 3.03 7.38 0 268.69 297.59 42587 +1968 79 9.59 3.59 7.94 0 278.06 299.51 42791 +1968 80 9.75 3.75 8.1 0 280.79 301.8 42996 +1968 81 8.91 2.91 7.26 0 266.71 305.59 43200 +1968 82 5.47 -0.53 3.82 0.01 215.17 234.46 43404 +1968 83 5.86 -0.14 4.21 0 220.55 314.69 43608 +1968 84 13.33 7.33 11.68 0 348.2 305.98 43812 +1968 85 13.46 7.46 11.81 0 350.88 308.18 44016 +1968 86 11.01 5.01 9.36 0 303.11 314.92 44220 +1968 87 13.07 7.07 11.42 0.02 342.87 235.34 44424 +1968 88 9.33 3.33 7.68 0 273.67 322.44 44627 +1968 89 8.99 2.99 7.34 0.14 268.03 243.93 44831 +1968 90 8.41 2.41 6.76 0 258.62 328.46 45034 +1968 91 15.88 9.88 14.23 0 404.24 317.01 45237 +1968 92 19.84 13.84 18.19 0 506.48 308.98 45439 +1968 93 17.98 11.98 16.33 0 456.02 316.2 45642 +1968 94 16.03 10.03 14.38 0.3 407.77 242.33 45843 +1968 95 14.28 8.28 12.63 0 368.25 329.09 46045 +1968 96 17.12 11.12 15.47 0 434.17 324.6 46246 +1968 97 17.02 11.02 15.37 0 431.69 326.84 46446 +1968 98 13.67 7.67 12.02 0 355.26 336.42 46647 +1968 99 11.39 5.39 9.74 0 310.13 342.83 46846 +1968 100 9.7 3.7 8.05 0.03 279.94 260.77 47045 +1968 101 12.48 6.48 10.83 0 331.05 344.66 47243 +1968 102 14.1 8.1 12.45 0 364.37 343.22 47441 +1968 103 13.97 7.97 12.32 0 361.6 345.32 47638 +1968 104 13.59 7.59 11.94 0 353.59 347.94 47834 +1968 105 11.74 5.74 10.09 0 316.72 353.43 48030 +1968 106 13.35 7.35 11.7 0 348.61 351.87 48225 +1968 107 17.68 11.68 16.03 0 448.29 343.14 48419 +1968 108 13.97 7.97 12.32 0.14 361.6 265.45 48612 +1968 109 14.11 8.11 12.46 0 364.59 355.22 48804 +1968 110 15.81 9.81 14.16 0.24 402.61 264.48 48995 +1968 111 13.58 7.58 11.93 0.02 353.38 269.5 49185 +1968 112 11.24 5.24 9.59 0 307.35 365.58 49374 +1968 113 11.86 5.86 10.21 0 319.01 365.74 49561 +1968 114 14.46 8.46 12.81 0 372.15 361.7 49748 +1968 115 17.04 11.04 15.39 0.01 432.18 267.52 49933 +1968 116 12.5 6.5 10.85 0 331.45 368.61 50117 +1968 117 17.7 11.7 16.05 0 448.8 357.35 50300 +1968 118 15.09 9.09 13.44 0 386.11 365.46 50481 +1968 119 16.13 10.13 14.48 0 410.13 364.04 50661 +1968 120 19.56 13.56 17.91 0 498.6 355.4 50840 +1968 121 18.87 12.87 17.22 0 479.6 358.63 51016 +1968 122 19.95 13.95 18.3 0 509.61 356.41 51191 +1968 123 18.85 12.85 17.2 0 479.06 360.86 51365 +1968 124 18.09 12.09 16.44 0 458.88 364.19 51536 +1968 125 17.57 11.57 15.92 0.28 445.49 274.99 51706 +1968 126 17.33 11.33 15.68 0 439.42 368.32 51874 +1968 127 21.05 15.05 19.4 0 541.8 357.53 52039 +1968 128 22.53 16.53 20.88 0 587.83 353.11 52203 +1968 129 24.43 18.43 22.78 0 651.74 346.32 52365 +1968 130 27.29 21.29 25.64 0 758.99 333.99 52524 +1968 131 25.46 19.46 23.81 0.35 688.78 257.5 52681 +1968 132 21.9 15.9 20.25 0 567.85 358.59 52836 +1968 133 21.49 15.49 19.84 0 555.15 360.76 52989 +1968 134 21.41 15.41 19.76 0.01 552.71 271.3 53138 +1968 135 17.38 11.38 15.73 0.82 440.68 281.52 53286 +1968 136 14.51 8.51 12.86 0 373.25 383.55 53430 +1968 137 14.55 8.55 12.9 1.35 374.12 288.12 53572 +1968 138 14.3 8.3 12.65 0.04 368.68 289.03 53711 +1968 139 17.73 11.73 16.08 0.78 449.57 282.73 53848 +1968 140 13.77 7.77 12.12 0.68 357.36 290.86 53981 +1968 141 16.77 10.77 15.12 1.15 425.54 285.47 54111 +1968 142 14.12 8.12 12.47 0.02 364.8 290.96 54238 +1968 143 12.72 6.72 11.07 0 335.82 391.68 54362 +1968 144 11.11 5.11 9.46 0 304.95 395.52 54483 +1968 145 15.89 9.89 14.24 0 404.48 385 54600 +1968 146 19.12 13.12 17.47 0.03 486.41 281.98 54714 +1968 147 18.42 12.42 16.77 0 467.55 378.64 54824 +1968 148 15.34 9.34 13.69 0.17 391.77 290.76 54931 +1968 149 14.78 8.78 13.13 0.27 379.19 292.06 55034 +1968 150 15.77 9.77 14.12 0.12 401.68 290.41 55134 +1968 151 14.88 8.88 13.23 0.72 381.41 292.43 55229 +1968 152 17.02 11.02 15.37 0.04 431.69 288.23 55321 +1968 153 18.21 12.21 16.56 0 462.01 381.05 55409 +1968 154 19.1 13.1 17.45 0.26 485.86 283.94 55492 +1968 155 18.91 12.91 17.26 0 480.69 379.38 55572 +1968 156 24.18 18.18 22.53 0 643.01 360.21 55648 +1968 157 25.32 19.32 23.67 0.08 683.64 266.51 55719 +1968 158 25 19 23.35 0.39 672.02 267.71 55786 +1968 159 22.98 16.98 21.33 0 602.46 365.73 55849 +1968 160 25.54 19.54 23.89 0 691.73 354.91 55908 +1968 161 27.75 21.75 26.1 0.6 777.56 258.12 55962 +1968 162 21.95 15.95 20.3 0.13 569.41 277.53 56011 +1968 163 24.82 18.82 23.17 0.1 665.56 268.87 56056 +1968 164 26.62 20.62 24.97 1.06 732.62 262.61 56097 +1968 165 24.25 18.25 22.6 0.04 645.44 270.83 56133 +1968 166 24.67 18.67 23.02 0.05 660.22 269.52 56165 +1968 167 26.06 20.06 24.41 0.15 711.17 264.72 56192 +1968 168 23.83 17.83 22.18 0.77 630.95 272.25 56214 +1968 169 21.53 15.53 19.88 0.85 556.38 279.05 56231 +1968 170 23.81 17.81 22.16 0.61 630.27 272.32 56244 +1968 171 19.1 13.1 17.45 0 485.86 380.52 56252 +1968 172 21.86 15.86 20.21 0 566.6 370.89 56256 +1968 173 17.69 11.69 16.04 0 448.55 384.85 56255 +1968 174 15.81 9.81 14.16 0.02 402.61 292.54 56249 +1968 175 13.04 7.04 11.39 0 342.26 396.8 56238 +1968 176 11.81 5.81 10.16 0.07 318.06 299.57 56223 +1968 177 17.07 11.07 15.42 0.13 432.93 289.8 56203 +1968 178 15.02 9.02 13.37 0 384.54 391.95 56179 +1968 179 20.98 14.98 19.33 0 539.7 373.78 56150 +1968 180 19.3 13.3 17.65 0 491.36 379.39 56116 +1968 181 21.81 15.81 20.16 0 565.04 370.55 56078 +1968 182 19.79 13.79 18.14 0.27 505.07 283.17 56035 +1968 183 20.77 14.77 19.12 0.24 533.45 280.51 55987 +1968 184 18.11 12.11 16.46 0.59 459.4 286.93 55935 +1968 185 16.94 10.94 15.29 1.82 429.71 289.44 55879 +1968 186 16.34 10.34 14.69 0.27 415.13 290.5 55818 +1968 187 15.14 9.14 13.49 0.65 387.24 292.73 55753 +1968 188 11.97 5.97 10.32 0 321.12 397.38 55684 +1968 189 17.23 11.23 15.58 0.14 436.91 288.14 55611 +1968 190 20.42 14.42 18.77 0.11 523.16 280.3 55533 +1968 191 20.09 14.09 18.44 0 513.62 374.6 55451 +1968 192 22.04 16.04 20.39 0.58 572.24 275.49 55366 +1968 193 23.88 17.88 22.23 0 632.66 359.73 55276 +1968 194 24.98 18.98 23.33 0.1 671.3 266.08 55182 +1968 195 25.67 19.67 24.02 0.01 696.55 263.54 55085 +1968 196 24.44 18.44 22.79 0 652.09 356.48 54984 +1968 197 22.68 16.68 21.03 0.12 592.67 272.44 54879 +1968 198 20.55 14.55 18.9 0.44 526.96 278 54770 +1968 199 23.96 17.96 22.31 0 635.41 357.32 54658 +1968 200 23.55 17.55 21.9 0 621.44 358.62 54542 +1968 201 22.82 16.82 21.17 0 597.22 361.09 54423 +1968 202 25.2 19.2 23.55 0 679.27 350.57 54301 +1968 203 26.05 20.05 24.4 0 710.79 346.2 54176 +1968 204 26.41 20.41 24.76 0.57 724.51 258.01 54047 +1968 205 23.45 17.45 21.8 0.08 618.08 267.39 53915 +1968 206 20.89 14.89 19.24 0.19 537.02 274.21 53780 +1968 207 26.08 20.08 24.43 0.03 711.92 257.94 53643 +1968 208 26.11 20.11 24.46 0 713.06 343.15 53502 +1968 209 25.6 19.6 23.95 0.01 693.95 258.66 53359 +1968 210 27.77 21.77 26.12 1.16 778.38 250.4 53213 +1968 211 28.06 22.06 26.41 0 790.29 331.66 53064 +1968 212 26.07 20.07 24.42 0.02 711.55 255.47 52913 +1968 213 24.25 18.25 22.6 0.37 645.44 260.93 52760 +1968 214 25.15 19.15 23.5 0.18 677.45 257.5 52604 +1968 215 20.91 14.91 19.26 0.3 537.61 269.42 52445 +1968 216 16.9 10.9 15.25 0.48 428.73 277.94 52285 +1968 217 19.31 13.31 17.66 0.48 491.64 271.95 52122 +1968 218 19.03 13.03 17.38 0.57 483.95 271.99 51958 +1968 219 19.9 13.9 18.25 1.62 508.19 269.14 51791 +1968 220 15.92 9.92 14.27 0 405.18 369.41 51622 +1968 221 21.94 15.94 20.29 1.64 569.1 262.45 51451 +1968 222 23.09 17.09 21.44 0.91 606.09 258.45 51279 +1968 223 23.46 17.46 21.81 2.25 618.41 256.54 51105 +1968 224 20.32 14.32 18.67 0.68 520.25 264.22 50929 +1968 225 22 16 20.35 0 570.98 345.39 50751 +1968 226 23.68 17.68 22.03 1.68 625.84 253.45 50572 +1968 227 21.24 15.24 19.59 0.05 547.53 259.25 50392 +1968 228 16.73 10.73 15.08 0.09 424.56 268.55 50210 +1968 229 15.3 9.3 13.65 0.01 390.86 270.31 50026 +1968 230 18.96 12.96 17.31 0.12 482.04 261.94 49842 +1968 231 16.69 10.69 15.04 0.35 423.59 265.59 49656 +1968 232 16.6 10.6 14.95 0 421.4 352.98 49469 +1968 233 13.55 7.55 11.9 0 352.75 358.74 49280 +1968 234 17.27 11.27 15.62 0 437.91 348.33 49091 +1968 235 19.47 13.47 17.82 0 496.08 340.56 48900 +1968 236 23.99 17.99 22.34 0 636.44 323.59 48709 +1968 237 23.74 17.74 22.09 0.65 627.88 242.22 48516 +1968 238 26.82 20.82 25.17 0.79 740.41 231.42 48323 +1968 239 28.02 22.02 26.37 0.03 788.64 226.19 48128 +1968 240 22.55 16.55 20.9 0.18 588.47 241.92 47933 +1968 241 23.53 17.53 21.88 0.08 620.77 238 47737 +1968 242 22.75 16.75 21.1 0.76 594.94 238.86 47541 +1968 243 22 16 20.35 0.11 570.98 239.46 47343 +1968 244 16.85 10.85 15.2 0 427.5 332.58 47145 +1968 245 12.89 6.89 11.24 0 339.23 339.56 46947 +1968 246 13.63 7.63 11.98 0.67 354.42 252.04 46747 +1968 247 16.52 10.52 14.87 0.31 419.46 245.76 46547 +1968 248 20.78 14.78 19.13 0.37 533.75 235.51 46347 +1968 249 21.09 15.09 19.44 0.08 543 233.26 46146 +1968 250 21.92 15.92 20.27 0.61 568.47 229.84 45945 +1968 251 19.63 13.63 17.98 0 500.56 311.4 45743 +1968 252 18.52 12.52 16.87 0 470.21 312.33 45541 +1968 253 18.02 12.02 16.37 0 457.05 311.53 45339 +1968 254 18.76 12.76 17.11 0 476.63 307.47 45136 +1968 255 21.53 15.53 19.88 0 556.38 297.24 44933 +1968 256 23.53 17.53 21.88 0.48 620.77 216.35 44730 +1968 257 22.19 16.19 20.54 0 576.97 290.87 44527 +1968 258 19.34 13.34 17.69 0 492.47 296.99 44323 +1968 259 20.49 14.49 18.84 0.72 525.2 218.54 44119 +1968 260 19.13 13.13 17.48 0.43 486.69 219.61 43915 +1968 261 12.7 6.7 11.05 0.91 335.42 228.37 43711 +1968 262 14.23 8.23 12.58 0.77 367.17 224.41 43507 +1968 263 17.45 11.45 15.8 0.06 442.44 217.35 43303 +1968 264 16.47 10.47 14.82 0.13 418.26 217.11 43099 +1968 265 12.62 6.62 10.97 0.38 333.83 221.01 42894 +1968 266 15.53 9.53 13.88 0.73 396.12 214.99 42690 +1968 267 17.42 11.42 15.77 0.81 441.69 209.9 42486 +1968 268 14.5 8.5 12.85 0 373.03 283.44 42282 +1968 269 15.14 9.14 13.49 0 387.24 279.67 42078 +1968 270 16.47 10.47 14.82 0 418.26 274.32 41875 +1968 271 21.1 15.1 19.45 0.04 543.31 195.39 41671 +1968 272 19.46 13.46 17.81 0.1 495.8 196.63 41468 +1968 273 14.02 8.02 12.37 0.04 362.66 203.43 41265 +1968 274 13.88 7.88 12.23 0 359.69 268.81 41062 +1968 275 8.32 2.32 6.67 0 257.19 274.31 40860 +1968 276 9.19 3.19 7.54 0 271.34 270.44 40658 +1968 277 10.36 4.36 8.71 0.01 291.42 199.61 40456 +1968 278 8.53 2.53 6.88 0 260.54 265.63 40255 +1968 279 9.64 3.64 7.99 0 278.91 261.35 40054 +1968 280 16.28 10.28 14.63 0 413.7 247.99 39854 +1968 281 14.78 8.78 13.13 0.42 379.19 186.06 39654 +1968 282 16.79 10.79 15.14 0 426.03 241.62 39455 +1968 283 18.72 12.72 17.07 0 475.56 234.85 39256 +1968 284 16.5 10.5 14.85 0.12 418.98 177.33 39058 +1968 285 16.31 10.31 14.66 0.16 414.42 175.66 38861 +1968 286 20.12 14.12 18.47 0.09 514.48 167.69 38664 +1968 287 18.41 12.41 16.76 0.22 467.28 168.38 38468 +1968 288 16.82 10.82 15.17 0.01 426.76 168.71 38273 +1968 289 16.43 10.43 14.78 0.38 417.29 167.32 38079 +1968 290 13.14 7.14 11.49 0 344.3 225.69 37885 +1968 291 16.45 10.45 14.8 0 417.77 217.62 37693 +1968 292 14.5 8.5 12.85 0 373.03 218.26 37501 +1968 293 13.34 7.34 11.69 0 348.4 217.32 37311 +1968 294 11.5 5.5 9.85 0 312.19 216.98 37121 +1968 295 12.92 6.92 11.27 0 339.83 212.24 36933 +1968 296 12.52 6.52 10.87 0 331.84 210.22 36745 +1968 297 11.24 5.24 9.59 0 307.35 209.17 36560 +1968 298 12.81 6.81 11.16 0 337.62 204.54 36375 +1968 299 13.39 7.39 11.74 0 349.43 200.98 36191 +1968 300 14.03 8.03 12.38 0.1 362.88 148.09 36009 +1968 301 10.61 4.61 8.96 0 295.87 199.36 35829 +1968 302 10.79 4.79 9.14 0 299.11 196.54 35650 +1968 303 10.86 4.86 9.21 0 300.38 193.89 35472 +1968 304 8.17 2.17 6.52 0 254.81 194.25 35296 +1968 305 6.31 0.31 4.66 0 226.89 193.17 35122 +1968 306 6.51 0.51 4.86 0 229.76 190.72 34950 +1968 307 5.01 -0.99 3.36 0.01 208.98 142.04 34779 +1968 308 7.03 1.03 5.38 0.54 237.37 138.84 34610 +1968 309 6.36 0.36 4.71 0 227.61 183.35 34444 +1968 310 10.25 4.25 8.6 0.75 289.48 132.98 34279 +1968 311 9.7 3.7 8.05 0.32 279.94 131.77 34116 +1968 312 8.25 2.25 6.6 0 256.08 174.43 33956 +1968 313 10.01 4.01 8.36 0.05 285.28 127.99 33797 +1968 314 10.36 4.36 8.71 0 291.42 168.37 33641 +1968 315 9.04 3.04 7.39 0 268.85 167.12 33488 +1968 316 8.54 2.54 6.89 0.36 260.7 124.05 33337 +1968 317 7.1 1.1 5.45 0.01 238.41 123.31 33188 +1968 318 5.75 -0.25 4.1 0.69 219.02 122.32 33042 +1968 319 4.83 -1.17 3.18 0 206.6 162.03 32899 +1968 320 4.09 -1.91 2.44 0 197.05 160.64 32758 +1968 321 5.5 -0.5 3.85 0 215.58 157.57 32620 +1968 322 8.66 2.66 7.01 0 262.64 153.32 32486 +1968 323 7.82 1.82 6.17 0 249.34 152.4 32354 +1968 324 11.15 5.15 9.5 0 305.68 147.43 32225 +1968 325 12.94 6.94 11.29 0 340.24 143.91 32100 +1968 326 12.64 6.64 10.99 0 334.22 142.82 31977 +1968 327 9.51 3.51 7.86 0.66 276.71 107.99 31858 +1968 328 7.19 1.19 5.54 0.27 239.76 107.9 31743 +1968 329 8.31 2.31 6.66 0.14 257.03 106.15 31631 +1968 330 8.44 2.44 6.79 0.72 259.1 105 31522 +1968 331 6.92 0.92 5.27 0.27 235.74 104.87 31417 +1968 332 6.67 0.67 5.02 1.54 232.08 103.77 31316 +1968 333 5.38 -0.62 3.73 0.46 213.95 103.6 31218 +1968 334 8.34 2.34 6.69 0 257.5 134.98 31125 +1968 335 6.14 0.14 4.49 0 224.48 135.38 31035 +1968 336 1.54 -4.46 -0.11 0 167 136.91 30949 +1968 337 0.69 -5.31 -0.96 0.08 157.91 101.73 30867 +1968 338 0.09 -5.91 -1.56 0 151.75 134.95 30790 +1968 339 -0.71 -6.71 -2.36 0 143.86 134.49 30716 +1968 340 -0.06 -6.06 -1.71 0.22 150.24 143.86 30647 +1968 341 1.16 -4.84 -0.49 0.81 162.88 142.7 30582 +1968 342 0.29 -5.71 -1.36 0 153.78 175.37 30521 +1968 343 2.4 -3.6 0.75 0 176.66 173.32 30465 +1968 344 3.5 -2.5 1.85 0 189.71 128.11 30413 +1968 345 0.99 -5.01 -0.66 0 161.07 128.91 30366 +1968 346 6.44 0.44 4.79 0 228.76 125.41 30323 +1968 347 4.52 -1.48 2.87 0 202.55 125.98 30284 +1968 348 -1.1 -7.1 -2.75 0 140.15 128.27 30251 +1968 349 -2.55 -8.55 -4.2 0 127.05 128.42 30221 +1968 350 -3.06 -9.06 -4.71 0 122.7 128.25 30197 +1968 351 -3.21 -9.21 -4.86 0.29 121.45 140.73 30177 +1968 352 -1.77 -7.77 -3.42 0 133.96 172.17 30162 +1968 353 1.44 -4.56 -0.21 0 165.91 170.61 30151 +1968 354 -1.81 -7.81 -3.46 0 133.59 171.91 30145 +1968 355 1.91 -4.09 0.26 0 171.1 170.11 30144 +1968 356 3.48 -2.52 1.83 1.2 189.47 137.61 30147 +1968 357 1.07 -4.93 -0.58 0.14 161.92 94.74 30156 +1968 358 -0.34 -6.34 -1.99 0 147.46 127 30169 +1968 359 0.57 -5.43 -1.08 0.01 156.66 95.06 30186 +1968 360 1.2 -4.8 -0.45 0 163.31 126.83 30208 +1968 361 -0.79 -6.79 -2.44 0 143.09 128.01 30235 +1968 362 -1.43 -7.43 -3.08 0 137.07 128.7 30267 +1968 363 -2.05 -8.05 -3.7 0 131.44 129.52 30303 +1968 364 -5.91 -11.91 -7.56 0.77 100.71 144.31 30343 +1968 365 -2.2 -8.2 -3.85 0 130.11 176.43 30388 +1969 1 -0.58 -6.58 -2.23 1.19 145.12 147.67 30438 +1969 2 1.6 -4.4 -0.05 0 167.66 179.86 30492 +1969 3 0.32 -5.68 -1.33 0 154.09 181.26 30551 +1969 4 0.18 -5.82 -1.47 0.31 152.66 148.83 30614 +1969 5 -3.88 -9.88 -5.53 0.02 115.98 150.43 30681 +1969 6 -1.92 -7.92 -3.57 0.26 132.6 151.29 30752 +1969 7 -1.84 -7.84 -3.49 0.08 133.32 152 30828 +1969 8 -6.21 -12.21 -7.86 0.04 98.6 154.21 30907 +1969 9 -5.4 -11.4 -7.05 1.22 104.37 158.63 30991 +1969 10 -4.6 -10.6 -6.25 0.01 110.35 159.32 31079 +1969 11 -2.35 -8.35 -4 0 128.79 194.73 31171 +1969 12 -2.78 -8.78 -4.43 0 125.07 195.75 31266 +1969 13 0.54 -5.46 -1.11 0 156.35 195.77 31366 +1969 14 0.8 -5.2 -0.85 0 159.06 196.86 31469 +1969 15 3.65 -2.35 2 0 191.56 196.16 31575 +1969 16 2.87 -3.13 1.22 0.21 182.14 160.83 31686 +1969 17 4.09 -1.91 2.44 0.39 197.05 160.86 31800 +1969 18 1.91 -4.09 0.26 0.19 171.1 162.78 31917 +1969 19 -2.28 -8.28 -3.93 0 129.41 204.03 32038 +1969 20 1.11 -4.89 -0.54 0 162.35 203.77 32161 +1969 21 -2.17 -8.17 -3.82 0.57 130.38 169.37 32289 +1969 22 1.63 -4.37 -0.02 0 167.99 208.36 32419 +1969 23 1.74 -4.26 0.09 0 169.21 209.66 32552 +1969 24 3.3 -2.7 1.65 0 187.28 210.22 32688 +1969 25 3.76 -2.24 2.11 0 192.92 211.15 32827 +1969 26 2.94 -3.06 1.29 0 182.97 213.02 32969 +1969 27 2.91 -3.09 1.26 0 182.61 214.5 33114 +1969 28 2.31 -3.69 0.66 0.28 175.63 174.28 33261 +1969 29 2.89 -3.11 1.24 0.25 182.38 175.25 33411 +1969 30 1.07 -4.93 -0.58 0.93 161.92 177.39 33564 +1969 31 0.03 -5.97 -1.62 0 151.15 223.77 33718 +1969 32 4.57 -1.43 2.92 0 203.2 222.37 33875 +1969 33 5.01 -0.99 3.36 0 208.98 223.87 34035 +1969 34 7.18 1.18 5.53 1.54 239.61 178.37 34196 +1969 35 5.63 -0.37 3.98 0.06 217.37 180.05 34360 +1969 36 2.51 -3.49 0.86 0.03 177.93 183.09 34526 +1969 37 6.56 0.56 4.91 0 230.49 228.5 34694 +1969 38 5.25 -0.75 3.6 0 212.19 231.49 34863 +1969 39 6.11 0.11 4.46 0 224.06 232.49 35035 +1969 40 5.21 -0.79 3.56 0 211.65 235.04 35208 +1969 41 3.51 -2.49 1.86 0.06 189.84 188.32 35383 +1969 42 3.67 -2.33 2.02 0.57 191.8 189.55 35560 +1969 43 2.65 -3.35 1 0 179.56 243.15 35738 +1969 44 1.86 -4.14 0.21 0 170.54 209.17 35918 +1969 45 -1.34 -7.34 -2.99 0 137.9 213.73 36099 +1969 46 -0.55 -6.55 -2.2 0.47 145.41 199.64 36282 +1969 47 -3.61 -9.61 -5.26 0.79 118.16 204.87 36466 +1969 48 -5.3 -11.3 -6.95 0.7 105.1 209.21 36652 +1969 49 2.15 -3.85 0.5 0.25 173.81 207.79 36838 +1969 50 2.02 -3.98 0.37 1.23 172.34 209.45 37026 +1969 51 0.6 -5.4 -1.05 0.53 156.97 212.15 37215 +1969 52 0.8 -5.2 -0.85 0.52 159.06 213.91 37405 +1969 53 0.43 -5.57 -1.22 0 155.21 274.96 37596 +1969 54 0.39 -5.61 -1.26 0 154.8 277.54 37788 +1969 55 1.66 -4.34 0.01 0.11 168.32 219.2 37981 +1969 56 0.29 -5.71 -1.36 0 153.78 282.76 38175 +1969 57 0.92 -5.08 -0.73 1.93 160.33 223.3 38370 +1969 58 -0.92 -6.92 -2.57 0.38 141.85 227.2 38565 +1969 59 4.13 -1.87 2.48 0.1 197.56 225.81 38761 +1969 60 2.31 -3.69 0.66 1.29 175.63 228.69 38958 +1969 61 4 -2 2.35 0.58 195.92 229.24 39156 +1969 62 1.68 -4.32 0.03 1.42 168.54 232.44 39355 +1969 63 -3.22 -9.22 -4.87 0.03 121.37 237.02 39553 +1969 64 -2.77 -8.77 -4.42 0 125.16 306.24 39753 +1969 65 1.5 -4.5 -0.15 0.66 166.57 238.59 39953 +1969 66 5.08 -0.92 3.43 0.32 209.91 237.61 40154 +1969 67 7 1 5.35 0.1 236.93 237.39 40355 +1969 68 3.82 -2.18 2.17 0 193.66 310.5 40556 +1969 69 4.28 -1.72 2.63 0 199.47 312.12 40758 +1969 70 4.1 -1.9 2.45 0.03 197.18 244.23 40960 +1969 71 3.97 -2.03 2.32 0 195.54 317.11 41163 +1969 72 4.7 -1.3 3.05 0 204.89 318.62 41366 +1969 73 1.55 -4.45 -0.1 0 167.11 292.25 41569 +1969 74 1.76 -4.24 0.11 0 169.43 294.86 41772 +1969 75 0.98 -5.02 -0.67 0 160.96 298.28 41976 +1969 76 9.94 3.94 8.29 0 284.07 291.05 42179 +1969 77 7.27 1.27 5.62 0 240.96 297.24 42383 +1969 78 6.85 0.85 5.2 0 234.71 300.42 42587 +1969 79 9.65 3.65 8 0 279.08 299.43 42791 +1969 80 14.07 8.07 12.42 0 363.73 294.51 42996 +1969 81 11.37 5.37 9.72 0 309.76 301.84 43200 +1969 82 11.76 5.76 10.11 0 317.1 303.82 43404 +1969 83 14.27 8.27 12.62 0 368.03 301.67 43608 +1969 84 11.71 5.71 10.06 0 316.16 308.88 43812 +1969 85 9.33 3.33 7.68 0 273.67 315.15 44016 +1969 86 10.55 4.55 8.9 0 294.79 315.67 44220 +1969 87 10.15 4.15 8.5 0 287.72 318.83 44424 +1969 88 8.49 2.49 6.84 0 259.9 323.68 44627 +1969 89 4.54 -1.46 2.89 0 202.81 330.99 44831 +1969 90 5.7 -0.3 4.05 0 218.33 332.04 45034 +1969 91 7.82 1.82 6.17 0 249.34 331.56 45237 +1969 92 8.98 2.98 7.33 0 267.86 332.14 45439 +1969 93 12.23 6.23 10.58 0 326.15 328.91 45642 +1969 94 17.13 11.13 15.48 0.03 434.42 240.34 45843 +1969 95 16.13 10.13 14.48 0.64 410.13 243.72 46045 +1969 96 17.32 11.32 15.67 0.7 439.17 243.07 46246 +1969 97 15.26 9.26 13.61 0.21 389.95 248.28 46446 +1969 98 14.11 8.11 12.46 0.54 364.59 251.62 46647 +1969 99 14.37 8.37 12.72 0 370.19 336.92 46846 +1969 100 14.7 8.7 13.05 0.02 377.42 253.59 47045 +1969 101 15.54 9.54 13.89 0 396.35 338.1 47243 +1969 102 11.21 5.21 9.56 0 306.79 348.95 47441 +1969 103 11.43 5.43 9.78 0 310.88 350.39 47638 +1969 104 10.82 4.82 9.17 0 299.65 353.32 47834 +1969 105 15.09 9.09 13.44 0.01 386.11 259.8 48030 +1969 106 13.25 7.25 11.6 0 346.55 352.07 48225 +1969 107 11.39 5.39 9.74 0 310.13 357.42 48419 +1969 108 14.79 8.79 13.14 0 379.41 352.09 48612 +1969 109 15.41 9.41 13.76 0 393.37 352.22 48804 +1969 110 13.29 7.29 11.64 0.24 347.37 268.8 48995 +1969 111 12.81 6.81 11.16 0.04 337.62 270.72 49185 +1969 112 11.85 5.85 10.2 0.02 318.82 273.31 49374 +1969 113 13.11 7.11 11.46 0 343.69 363.19 49561 +1969 114 11 5 9.35 0 302.93 368.89 49748 +1969 115 8.78 2.78 7.13 0 264.59 374.21 49933 +1969 116 11.36 5.36 9.71 0.02 309.57 278.16 50117 +1969 117 11.53 5.53 9.88 0 312.76 371.87 50300 +1969 118 11.41 5.41 9.76 0 310.51 373.43 50481 +1969 119 7.04 1.04 5.39 0.11 237.52 286.54 50661 +1969 120 17.39 11.39 15.74 0 440.93 361.83 50840 +1969 121 23.99 17.99 22.34 1.01 636.44 255.45 51016 +1969 122 19.87 13.87 18.22 0.01 507.33 267.5 51191 +1969 123 21 15 19.35 0 540.3 353.9 51365 +1969 124 24.27 18.27 22.62 0.02 646.14 256.92 51536 +1969 125 24.23 18.23 22.58 0 644.75 343.65 51706 +1969 126 24.41 18.41 22.76 0.38 651.04 257.87 51874 +1969 127 26.52 20.52 24.87 0 728.75 335.28 52039 +1969 128 24.18 18.18 22.53 0 643.01 346.57 52203 +1969 129 21.31 15.31 19.66 0 549.66 358.4 52365 +1969 130 17.74 11.74 16.09 0 449.83 370.63 52524 +1969 131 16.82 10.82 15.17 0 426.76 374.02 52681 +1969 132 15.62 9.62 13.97 0.01 398.2 283.52 52836 +1969 133 17.3 11.3 15.65 0 438.67 374.2 52989 +1969 134 21.37 15.37 19.72 0 551.49 361.88 53138 +1969 135 22.18 16.18 20.53 0 576.65 359.58 53286 +1969 136 21.77 15.77 20.12 0.51 563.79 271.29 53430 +1969 137 21.03 15.03 19.38 0.02 541.2 273.8 53572 +1969 138 21.42 15.42 19.77 0.46 553.01 273.2 53711 +1969 139 21.87 15.87 20.22 1.09 566.91 272.46 53848 +1969 140 23.22 17.22 21.57 0.03 610.39 268.91 53981 +1969 141 23.84 17.84 22.19 0.89 631.29 267.32 54111 +1969 142 23.62 17.62 21.97 0.26 623.81 268.36 54238 +1969 143 20.39 14.39 18.74 0 522.29 370.46 54362 +1969 144 18.64 12.64 16.99 0.21 473.41 282.48 54483 +1969 145 16.54 10.54 14.89 0.01 419.95 287.44 54600 +1969 146 14.12 8.12 12.47 0 364.8 389.83 54714 +1969 147 13.25 7.25 11.6 0 346.55 392.34 54824 +1969 148 14.54 8.54 12.89 0 373.9 389.69 54931 +1969 149 15.56 9.56 13.91 0 396.81 387.43 55034 +1969 150 16.78 10.78 15.13 1.03 425.78 288.36 55134 +1969 151 16.77 10.77 15.12 1.14 425.54 288.67 55229 +1969 152 17.45 11.45 15.8 0.53 442.44 287.3 55321 +1969 153 16.61 10.61 14.96 0.62 421.64 289.28 55409 +1969 154 17.74 11.74 16.09 1.18 449.83 287.09 55492 +1969 155 13.63 7.63 11.98 0.36 354.42 295.35 55572 +1969 156 20.41 14.41 18.76 1.43 522.87 281.05 55648 +1969 157 18.74 12.74 17.09 2.41 476.09 285.31 55719 +1969 158 14.26 8.26 12.61 0 367.81 392.99 55786 +1969 159 16.78 10.78 15.13 0 425.78 386.65 55849 +1969 160 14.63 8.63 12.98 0.01 375.88 294.38 55908 +1969 161 16.24 10.24 14.59 0.57 412.74 291.3 55962 +1969 162 20.43 14.43 18.78 1.1 523.45 281.66 56011 +1969 163 21.25 15.25 19.6 1.16 547.84 279.64 56056 +1969 164 21.46 15.46 19.81 0.67 554.23 279.09 56097 +1969 165 21.28 15.28 19.63 0.1 548.75 279.66 56133 +1969 166 22.13 16.13 20.48 0.97 575.07 277.34 56165 +1969 167 23.36 17.36 21.71 0.04 615.06 273.65 56192 +1969 168 20.42 14.42 18.77 0 523.16 376.04 56214 +1969 169 19.63 13.63 17.98 0.36 500.56 284.05 56231 +1969 170 21.79 15.79 20.14 0.03 564.42 278.33 56244 +1969 171 21.96 15.96 20.31 0.67 569.72 277.89 56252 +1969 172 23.36 17.36 21.71 0.26 615.06 273.75 56256 +1969 173 24.36 18.36 22.71 0 649.28 360.78 56255 +1969 174 26.31 20.31 24.66 0.37 720.68 263.85 56249 +1969 175 29.32 23.32 27.67 0 843.86 336.07 56238 +1969 176 23.16 17.16 21.51 0 608.4 365.65 56223 +1969 177 22.38 16.38 20.73 0 583.02 368.64 56203 +1969 178 19.04 13.04 17.39 0.08 484.22 285.34 56179 +1969 179 18.24 12.24 16.59 0 462.8 382.86 56150 +1969 180 17.01 11.01 15.36 0.01 431.44 289.78 56116 +1969 181 19.28 13.28 17.63 0.05 490.81 284.54 56078 +1969 182 21.56 15.56 19.91 0 557.3 371.34 56035 +1969 183 24.57 18.57 22.92 0 656.67 359.05 55987 +1969 184 22.3 16.3 20.65 0 580.46 368.22 55935 +1969 185 24.86 18.86 23.21 0.08 666.99 268.16 55879 +1969 186 21.5 15.5 19.85 0.11 555.46 278.17 55818 +1969 187 18.91 12.91 17.26 0.1 480.69 284.67 55753 +1969 188 24.5 18.5 22.85 0.27 654.2 268.83 55684 +1969 189 25.62 19.62 23.97 0.08 694.69 264.94 55611 +1969 190 21.42 15.42 19.77 0.17 553.01 277.64 55533 +1969 191 23.28 17.28 21.63 0.02 612.39 272.07 55451 +1969 192 20.64 14.64 18.99 0 529.61 372.41 55366 +1969 193 20.79 14.79 19.14 0 534.04 371.61 55276 +1969 194 23.26 17.26 21.61 0 611.72 362.06 55182 +1969 195 19.93 13.93 18.28 0.33 509.04 280.55 55085 +1969 196 20.96 14.96 19.31 0 539.11 370.11 54984 +1969 197 17.51 11.51 15.86 0 443.96 380.76 54879 +1969 198 16.84 10.84 15.19 0.47 427.25 286.68 54770 +1969 199 18.37 12.37 16.72 0.13 466.23 283.05 54658 +1969 200 21.55 15.55 19.9 0.32 557 274.77 54542 +1969 201 22.31 16.31 20.66 0.66 580.78 272.29 54423 +1969 202 21.01 15.01 19.36 0.17 540.6 275.46 54301 +1969 203 22.77 16.77 21.12 0.13 595.59 270.17 54176 +1969 204 22.63 16.63 20.98 0 591.05 360.28 54047 +1969 205 23.82 17.82 22.17 0 630.61 355.01 53915 +1969 206 23.36 17.36 21.71 0 615.06 356.34 53780 +1969 207 24.74 18.74 23.09 0.36 662.71 262.45 53643 +1969 208 27.64 21.64 25.99 0 773.09 335.72 53502 +1969 209 23.17 17.17 21.52 0 608.73 355.18 53359 +1969 210 25.21 19.21 23.56 0.01 679.63 259.52 53213 +1969 211 27 21 25.35 0.41 747.48 252.73 53064 +1969 212 26.85 20.85 25.2 1.04 741.58 252.71 52913 +1969 213 21.18 15.18 19.53 0.35 545.72 269.78 52760 +1969 214 25.13 19.13 23.48 0.11 676.72 257.56 52604 +1969 215 24.49 18.49 22.84 0 653.85 345.52 52445 +1969 216 23.42 17.42 21.77 0 617.07 348.91 52285 +1969 217 22.76 16.76 21.11 0 595.27 350.62 52122 +1969 218 21.31 15.31 19.66 0.24 549.66 266.35 51958 +1969 219 21.88 15.88 20.23 0.36 567.22 264.05 51791 +1969 220 20.68 14.68 19.03 2.13 530.79 266.5 51622 +1969 221 19.21 13.21 17.56 0.41 488.88 269.32 51451 +1969 222 19.9 13.9 18.25 0 508.19 355.86 51279 +1969 223 17.07 11.07 15.42 0.82 432.93 272.33 51105 +1969 224 16.71 10.71 15.06 0 424.07 363 50929 +1969 225 16.24 10.24 14.59 0.77 412.74 272.3 50751 +1969 226 16.58 10.58 14.93 0.25 420.91 270.76 50572 +1969 227 19.46 13.46 17.81 0.38 495.8 263.61 50392 +1969 228 22.56 16.56 20.91 1.79 588.79 254.83 50210 +1969 229 24.12 18.12 22.47 0.46 640.93 249.43 50026 +1969 230 26.45 20.45 24.8 0.15 726.05 241.06 49842 +1969 231 23.69 17.69 22.04 0.73 626.18 248.71 49656 +1969 232 24.29 18.29 22.64 0.9 646.84 245.96 49469 +1969 233 23.03 17.03 21.38 0.94 604.11 248.58 49280 +1969 234 22.08 16.08 20.43 0 573.49 333.5 49091 +1969 235 17.81 11.81 16.16 0.33 451.62 259.02 48900 +1969 236 18.51 12.51 16.86 0 469.94 341.96 48709 +1969 237 19.14 13.14 17.49 0.2 486.96 253.86 48516 +1969 238 20.5 14.5 18.85 0 525.5 332.65 48323 +1969 239 21.46 15.46 19.81 0.14 554.23 246.02 48128 +1969 240 17.92 11.92 16.27 0.16 454.46 252.74 47933 +1969 241 15.72 9.72 14.07 0.67 400.51 255.63 47737 +1969 242 16.08 10.08 14.43 0.62 408.95 253.66 47541 +1969 243 15.64 9.64 13.99 0.56 398.66 253.03 47343 +1969 244 16.93 10.93 15.28 0 429.47 332.37 47145 +1969 245 19.5 13.5 17.85 0 496.92 323.54 46947 +1969 246 19.45 13.45 17.8 0.13 495.53 241.3 46747 +1969 247 23.12 17.12 21.47 0 607.08 308.13 46547 +1969 248 25.36 19.36 23.71 0 685.11 297.84 46347 +1969 249 27.18 21.18 25.53 0 754.61 288.29 46146 +1969 250 25.58 19.58 23.93 0 693.21 293.18 45945 +1969 251 24.17 18.17 22.52 0 642.66 296.6 45743 +1969 252 26.43 20.43 24.78 0 725.28 285.72 45541 +1969 253 21.63 15.63 19.98 0.02 559.46 225.89 45339 +1969 254 21.06 15.06 19.41 0 542.1 300.88 45136 +1969 255 17.42 11.42 15.77 0 441.69 308.67 44933 +1969 256 12.93 6.93 11.28 0 340.04 316.07 44730 +1969 257 10.99 4.99 9.34 0 302.75 317.28 44527 +1969 258 12.62 6.62 10.97 0 333.83 312.04 44323 +1969 259 15 9 13.35 0.4 384.09 228.69 44119 +1969 260 14.11 8.11 12.46 0.42 364.59 228.24 43915 +1969 261 16.78 10.78 15.13 1.08 425.78 222.13 43711 +1969 262 15.51 9.51 13.86 0 395.66 296.6 43507 +1969 263 16.32 10.32 14.67 0 414.65 292.38 43303 +1969 264 17.01 11.01 15.36 0 431.44 288.27 43099 +1969 265 14.18 8.18 12.53 0 366.09 291.83 42894 +1969 266 12.68 6.68 11.03 0 335.02 292.06 42690 +1969 267 15.65 9.65 14 0 398.89 283.72 42486 +1969 268 14.62 8.62 12.97 0.14 375.66 212.41 42282 +1969 269 15.65 9.65 14 0 398.89 278.65 42078 +1969 270 25.07 19.07 23.42 0.64 674.55 188.04 41875 +1969 271 22.83 16.83 21.18 0.29 597.55 191.64 41671 +1969 272 23.95 17.95 22.3 0.96 635.06 187.09 41468 +1969 273 18.77 12.77 17.12 0 476.9 261.39 41265 +1969 274 10.89 4.89 9.24 0 300.92 273.65 41062 +1969 275 11.21 5.21 9.56 0 306.79 270.36 40860 +1969 276 11.27 5.27 9.62 0 307.9 267.54 40658 +1969 277 13.8 7.8 12.15 0.69 357.99 195.61 40456 +1969 278 12.35 6.35 10.7 0.06 328.5 195.23 40255 +1969 279 12.67 6.67 11.02 0 334.82 256.98 40054 +1969 280 9.12 3.12 7.47 0 270.17 259.32 39854 +1969 281 6.98 0.98 5.33 0.52 236.63 194.29 39654 +1969 282 10 4 8.35 0 285.11 252.64 39455 +1969 283 12.29 6.29 10.64 0.59 327.32 184.94 39256 +1969 284 12.58 6.58 10.93 0.59 333.03 182.34 39058 +1969 285 14.18 8.18 12.53 0.01 366.09 178.47 38861 +1969 286 16.31 10.31 14.66 0 414.42 231.5 38664 +1969 287 15.86 9.86 14.21 0 403.78 229.44 38468 +1969 288 15.66 9.66 14.01 0 399.12 227.05 38273 +1969 289 14.63 8.63 12.98 0 375.88 226.21 38079 +1969 290 14.23 8.23 12.58 0 367.17 224.02 37885 +1969 291 14.93 8.93 13.28 0.02 382.52 165.17 37693 +1969 292 13.16 7.16 11.51 0 344.71 220.3 37501 +1969 293 12.27 6.27 10.62 0 326.93 218.84 37311 +1969 294 13.46 7.46 11.81 0 350.88 214.28 37121 +1969 295 14.24 8.24 12.59 0 367.38 210.32 36933 +1969 296 15.66 9.66 14.01 0 399.12 205.54 36745 +1969 297 17.05 11.05 15.4 0.01 432.43 150.39 36560 +1969 298 13.86 7.86 12.21 0 359.26 203.07 36375 +1969 299 15.07 9.07 13.42 0 385.66 198.53 36191 +1969 300 15.63 9.63 13.98 0 398.43 195.05 36009 +1969 301 17.1 11.1 15.45 0 433.67 190.2 35829 +1969 302 18.3 12.3 16.65 0 464.38 185.58 35650 +1969 303 17.11 11.11 15.46 0.38 433.92 138.87 35472 +1969 304 15.7 9.7 14.05 0.23 400.05 138.77 35296 +1969 305 11.79 5.79 10.14 0.57 317.68 140.72 35122 +1969 306 9.66 3.66 8.01 0.3 279.26 140.82 34950 +1969 307 13.21 7.21 11.56 0 345.73 181.17 34779 +1969 308 12.85 6.85 11.2 0 338.42 179.06 34610 +1969 309 13.98 7.98 12.33 0.58 361.81 131.51 34444 +1969 310 11.42 5.42 9.77 0.04 310.69 132.04 34279 +1969 311 10.15 4.15 8.5 0.44 287.72 131.43 34116 +1969 312 6.92 0.92 5.27 0 235.74 175.58 33956 +1969 313 7.91 1.91 6.26 0 250.74 172.61 33797 +1969 314 8.24 2.24 6.59 0.25 255.92 127.78 33641 +1969 315 7.35 1.35 5.7 0 242.16 168.59 33488 +1969 316 10.54 4.54 8.89 0 294.62 163.51 33337 +1969 317 10.51 4.51 8.86 0 294.08 161.37 33188 +1969 318 13.82 7.82 12.17 2.07 358.42 116.59 33042 +1969 319 13 7 11.35 0 341.45 154.76 32899 +1969 320 14.37 8.37 12.72 0 370.19 151.34 32758 +1969 321 8.88 2.88 7.23 0 266.22 154.94 32620 +1969 322 5.48 -0.52 3.83 0.08 215.31 116.82 32486 +1969 323 6.08 0.08 4.43 0 223.63 153.71 32354 +1969 324 7.51 1.51 5.86 0 244.59 150.6 32225 +1969 325 8.66 2.66 7.01 0 262.64 147.97 32100 +1969 326 11.48 5.48 9.83 0.01 311.82 108 31977 +1969 327 11.32 5.32 9.67 0 308.83 142.34 31858 +1969 328 12.19 6.19 10.54 0 325.37 139.54 31743 +1969 329 9.41 3.41 7.76 0.01 275.02 105.48 31631 +1969 330 15.41 9.41 13.76 0 393.37 133.15 31522 +1969 331 13.83 7.83 12.18 0.18 358.63 100.27 31417 +1969 332 7.85 1.85 6.2 0.08 249.81 103.14 31316 +1969 333 7.84 1.84 6.19 0.38 249.65 102.33 31218 +1969 334 6.89 0.89 5.24 0.17 235.3 102.03 31125 +1969 335 -4.45 -10.45 -6.1 1.41 111.5 152.19 31035 +1969 336 -0.91 -6.91 -2.56 0.11 141.95 150.87 30949 +1969 337 1.06 -4.94 -0.59 0 161.81 182.82 30867 +1969 338 2.98 -3.02 1.33 0 183.44 180.64 30790 +1969 339 2.95 -3.05 1.3 0.32 183.09 146.4 30716 +1969 340 2.25 -3.75 0.6 0.19 174.94 145.92 30647 +1969 341 0.69 -5.31 -0.96 0.28 157.91 145.79 30582 +1969 342 -1.72 -7.72 -3.37 1.29 134.41 150.1 30521 +1969 343 -4.07 -10.07 -5.72 0.84 114.47 152.83 30465 +1969 344 -8.33 -14.33 -9.98 0.21 84.8 153.6 30413 +1969 345 -4.78 -10.78 -6.43 0 108.98 185.41 30366 +1969 346 -2.18 -8.18 -3.83 0 130.29 184.06 30323 +1969 347 -1.25 -7.25 -2.9 0.4 138.74 152.28 30284 +1969 348 -2.16 -8.16 -3.81 0.07 130.46 152.55 30251 +1969 349 -1.88 -7.88 -3.53 0.31 132.96 153.23 30221 +1969 350 -0.38 -6.38 -2.03 0 147.07 184.4 30197 +1969 351 1.38 -4.62 -0.27 0.01 165.26 151.71 30177 +1969 352 -0.9 -6.9 -2.55 0 142.04 184.17 30162 +1969 353 1.65 -4.35 0 0 168.21 182.82 30151 +1969 354 0.14 -5.86 -1.51 0 152.26 183.44 30145 +1969 355 -1.87 -7.87 -3.52 0 133.05 184.23 30144 +1969 356 -1.24 -7.24 -2.89 0 138.83 184.02 30147 +1969 357 -4.02 -10.02 -5.67 0 114.87 185.02 30156 +1969 358 -3.39 -9.39 -5.04 0.96 119.96 155.91 30169 +1969 359 -1.69 -7.69 -3.34 0.01 134.68 155.56 30186 +1969 360 -1.11 -7.11 -2.76 0 140.05 187.57 30208 +1969 361 0.13 -5.87 -1.52 0 152.15 187.34 30235 +1969 362 0.28 -5.72 -1.37 0 153.68 187.62 30267 +1969 363 2.23 -3.77 0.58 0 174.72 186.95 30303 +1969 364 4.14 -1.86 2.49 0 197.68 185.73 30343 +1969 365 0.31 -5.69 -1.34 0 153.98 188.05 30388 +1970 1 3.44 -2.56 1.79 0 188.98 186.89 30438 +1970 2 3.48 -2.52 1.83 0 189.47 187.04 30492 +1970 3 -0.99 -6.99 -2.64 0 141.19 189.95 30551 +1970 4 0.03 -5.97 -1.62 0 151.15 190.33 30614 +1970 5 -0.37 -6.37 -2.02 0 147.17 191.03 30681 +1970 6 -2.88 -8.88 -4.53 0 124.22 192.76 30752 +1970 7 -3.5 -9.5 -5.15 0 119.06 193.65 30828 +1970 8 -1.42 -7.42 -3.07 0.04 137.16 159.95 30907 +1970 9 2.47 -3.53 0.82 0 177.47 193.39 30991 +1970 10 -0.73 -6.73 -2.38 0.41 143.67 162.31 31079 +1970 11 0.12 -5.88 -1.53 0.21 152.05 162.6 31171 +1970 12 4.87 -1.13 3.22 0 207.13 195.45 31266 +1970 13 5.46 -0.54 3.81 0.28 215.04 160.73 31366 +1970 14 2.51 -3.49 0.86 0 177.93 198.52 31469 +1970 15 5.29 -0.71 3.64 0.07 212.73 161.63 31575 +1970 16 2.06 -3.94 0.41 0.12 172.79 163.56 31686 +1970 17 0.51 -5.49 -1.14 0.35 156.04 165.15 31800 +1970 18 -1.14 -7.14 -2.79 0.42 139.77 168.22 31917 +1970 19 -1.47 -7.47 -3.12 0 136.7 208.02 32038 +1970 20 1.13 -4.87 -0.52 0 162.56 208.06 32161 +1970 21 -0.96 -6.96 -2.61 0.04 141.47 171.69 32289 +1970 22 -2.74 -8.74 -4.39 0.02 125.42 173.43 32419 +1970 23 -6.18 -12.18 -7.83 0.01 98.81 175.51 32552 +1970 24 -0.09 -6.09 -1.74 0 149.94 215.66 32688 +1970 25 -1.18 -7.18 -2.83 0 139.39 217.85 32827 +1970 26 0.35 -5.65 -1.3 0 154.39 218.79 32969 +1970 27 3.79 -2.21 2.14 0 193.29 218.15 33114 +1970 28 6.84 0.84 5.19 0 234.57 217.11 33261 +1970 29 3.89 -2.11 2.24 0 194.54 220.92 33411 +1970 30 1.31 -4.69 -0.34 0 164.5 224.36 33564 +1970 31 6.01 0.01 4.36 0 222.65 222.68 33718 +1970 32 11.04 5.04 9.39 0.06 303.66 175.83 33875 +1970 33 9.4 3.4 7.75 1.48 274.85 177.69 34035 +1970 34 8.52 2.52 6.87 0.89 260.38 178.72 34196 +1970 35 3.14 -2.86 1.49 0 185.35 229.14 34360 +1970 36 2.92 -3.08 1.27 0.1 182.73 184.37 34526 +1970 37 1.01 -4.99 -0.64 0 161.28 234.55 34694 +1970 38 -0.71 -6.71 -2.36 0 143.86 238.06 34863 +1970 39 -2.34 -8.34 -3.99 0 128.88 241.31 35035 +1970 40 0.39 -5.61 -1.26 0 154.8 242.27 35208 +1970 41 3.01 -2.99 1.36 0 183.8 242.69 35383 +1970 42 4.4 -1.6 2.75 0 201 243.53 35560 +1970 43 4.33 -1.67 2.68 0.2 200.11 194.39 35738 +1970 44 6.56 0.56 4.91 0.19 230.49 193.98 35918 +1970 45 7.98 1.98 6.33 0.72 251.83 193.83 36099 +1970 46 5.73 -0.27 4.08 0.01 218.75 196.57 36282 +1970 47 5.36 -0.64 3.71 0 213.68 251.81 36466 +1970 48 5.2 -0.8 3.55 0.06 211.52 199.58 36652 +1970 49 4.22 -1.78 2.57 0.24 198.7 165.91 36838 +1970 50 -0.27 -6.27 -1.92 0.09 148.15 206.18 37026 +1970 51 -0.72 -6.72 -2.37 0 143.77 266.04 37215 +1970 52 -1.55 -7.55 -3.2 0 135.96 269.21 37405 +1970 53 0.96 -5.04 -0.69 0 160.75 270.38 37596 +1970 54 -2.46 -8.46 -4.11 0 127.83 275.07 37788 +1970 55 -2.28 -8.28 -3.93 0 129.41 277.84 37981 +1970 56 3.53 -2.47 1.88 0 190.08 241.73 38175 +1970 57 3.14 -2.86 1.49 0.01 185.35 183.72 38370 +1970 58 3.49 -2.51 1.84 0 189.59 247.62 38565 +1970 59 3.56 -2.44 1.91 0.25 190.45 187.72 38761 +1970 60 1.95 -4.05 0.3 0.09 171.55 190.88 38958 +1970 61 4.03 -1.97 2.38 1.62 196.29 191.8 39156 +1970 62 5.09 -0.91 3.44 0 210.05 257.57 39355 +1970 63 7.37 1.37 5.72 1.35 242.46 193.66 39553 +1970 64 5.17 -0.83 3.52 0.1 211.12 197.57 39753 +1970 65 8.72 2.72 7.07 0 263.61 262.39 39953 +1970 66 11.84 5.84 10.19 0.01 318.63 195.61 40154 +1970 67 8.88 2.88 7.23 0.02 266.22 200.85 40355 +1970 68 6.79 0.79 5.14 0 233.83 273.16 40556 +1970 69 7.82 1.82 6.17 0.11 249.34 205.94 40758 +1970 70 9.98 3.98 8.33 0 284.76 274.61 40960 +1970 71 9.01 3.01 7.36 0 268.36 278.82 41163 +1970 72 8.76 2.76 7.11 0 264.26 281.96 41366 +1970 73 11.08 5.08 9.43 0.69 304.4 210.99 41569 +1970 74 11.36 5.36 9.71 0.5 309.57 212.7 41772 +1970 75 4.29 -1.71 2.64 0.48 199.59 221.47 41976 +1970 76 7.79 1.79 6.14 0 248.88 293.98 42179 +1970 77 9.01 3.01 7.36 0 268.36 294.96 42383 +1970 78 8.99 2.99 7.34 0.03 268.03 223.24 42587 +1970 79 7.25 1.25 5.6 0.8 240.65 227 42791 +1970 80 7.71 1.71 6.06 0.31 247.65 228.47 42996 +1970 81 1.18 -4.82 -0.47 0.3 163.1 235.63 43200 +1970 82 6.87 0.87 5.22 0.63 235.01 233.21 43404 +1970 83 4.3 -1.7 2.65 0.24 199.72 237.32 43608 +1970 84 3.69 -2.31 2.04 0 192.05 319.64 43812 +1970 85 5.5 -0.5 3.85 0.22 215.58 240.14 44016 +1970 86 4.71 -1.29 3.06 0.15 205.02 242.65 44220 +1970 87 2.96 -3.04 1.31 0 183.21 327.94 44424 +1970 88 1.21 -4.79 -0.44 1.9 163.42 248.99 44627 +1970 89 2.48 -3.52 0.83 0.04 177.58 249.85 44831 +1970 90 6.53 0.53 4.88 0.03 230.05 248.26 45034 +1970 91 9.69 3.69 8.04 0 279.77 328.8 45237 +1970 92 8.55 2.55 6.9 0 260.86 332.78 45439 +1970 93 14.23 8.23 12.58 0.35 367.17 243.73 45642 +1970 94 12.3 6.3 10.65 0.05 327.52 248.19 45843 +1970 95 10.73 4.73 9.08 0 298.03 335.85 46045 +1970 96 10.92 4.92 9.27 0.93 301.47 253.23 46246 +1970 97 11.49 5.49 9.84 0.16 312.01 254.01 46446 +1970 98 11.47 5.47 9.82 0.05 311.63 255.51 46647 +1970 99 9.55 3.55 7.9 0 277.38 345.98 46846 +1970 100 11.72 5.72 10.07 0.11 316.34 258.13 47045 +1970 101 13.97 7.97 12.32 1.14 361.6 256.21 47243 +1970 102 15.97 9.97 14.32 1 406.36 254.21 47441 +1970 103 16.68 10.68 15.03 0.1 423.34 254.25 47638 +1970 104 15.3 9.3 13.65 0.13 390.86 258.11 47834 +1970 105 15.37 9.37 13.72 1.22 392.46 259.31 48030 +1970 106 15.51 9.51 13.86 0.03 395.66 260.27 48225 +1970 107 14.27 8.27 12.62 0.53 368.03 263.66 48419 +1970 108 7.53 1.53 5.88 0.09 244.89 274.2 48612 +1970 109 4.47 -1.53 2.82 0 201.91 371.35 48804 +1970 110 4.02 -1.98 2.37 0.42 196.17 280.01 48995 +1970 111 8.17 2.17 6.52 0.48 254.81 276.97 49185 +1970 112 10 4 8.35 0 285.11 367.83 49374 +1970 113 12.18 6.18 10.53 0 325.18 365.11 49561 +1970 114 10.31 4.31 8.66 0.21 290.53 277.61 49748 +1970 115 9.27 3.27 7.62 0.1 272.67 280.05 49933 +1970 116 13.25 7.25 11.6 0 346.55 367.04 50117 +1970 117 16.58 10.58 14.93 0 420.91 360.4 50300 +1970 118 16.54 10.54 14.89 0.74 419.95 271.35 50481 +1970 119 17.05 11.05 15.4 0 432.43 361.61 50661 +1970 120 12.61 6.61 10.96 0 333.63 373.4 50840 +1970 121 13.2 7.2 11.55 0 345.53 373.28 51016 +1970 122 14.65 8.65 13 0 376.32 371.18 51191 +1970 123 12.7 6.7 11.05 0 335.42 376.59 51365 +1970 124 13.08 7.08 11.43 0.17 343.08 282.65 51536 +1970 125 14.19 8.19 12.54 0 366.3 375.36 51706 +1970 126 12.33 6.33 10.68 0 328.11 380.46 51874 +1970 127 11.57 5.57 9.92 0.69 313.51 287.19 52039 +1970 128 11.1 5.1 9.45 0.46 304.76 288.64 52203 +1970 129 9.22 3.22 7.57 0.18 271.84 291.87 52365 +1970 130 8.12 2.12 6.47 0.01 254.02 293.87 52524 +1970 131 13.25 7.25 11.6 0 346.55 382.86 52681 +1970 132 9.79 3.79 8.14 0 281.48 390.64 52836 +1970 133 16.2 10.2 14.55 0.06 411.79 282.91 52989 +1970 134 14.91 8.91 13.26 0 382.08 381.23 53138 +1970 135 14.68 8.68 13.03 0.01 376.98 286.87 53286 +1970 136 13.03 7.03 11.38 0.04 342.06 290.23 53430 +1970 137 16.28 10.28 14.63 0 413.7 379.75 53572 +1970 138 21.93 15.93 20.28 0.01 568.78 271.79 53711 +1970 139 22.78 16.78 21.13 0.82 595.92 269.87 53848 +1970 140 21.99 15.99 20.34 0 570.66 363.3 53981 +1970 141 20.75 14.75 19.1 0 532.86 368.21 54111 +1970 142 19.38 13.38 17.73 0 493.58 373.3 54238 +1970 143 23.06 17.06 21.41 0.4 605.1 270.44 54362 +1970 144 18.88 12.88 17.23 0 479.87 375.89 54483 +1970 145 19.39 13.39 17.74 0 493.86 374.73 54600 +1970 146 19.36 13.36 17.71 0 493.03 375.2 54714 +1970 147 17.28 11.28 15.63 0.34 438.16 286.52 54824 +1970 148 16.07 10.07 14.42 0 408.71 385.77 54931 +1970 149 19.06 13.06 17.41 0.79 484.77 283 55034 +1970 150 18.24 12.24 16.59 0.06 462.8 285.16 55134 +1970 151 15.49 9.49 13.84 0.04 395.2 291.26 55229 +1970 152 23.85 17.85 22.2 0.67 631.63 270.42 55321 +1970 153 24.76 18.76 23.11 0.01 663.42 267.67 55409 +1970 154 24.76 18.76 23.11 1.28 663.42 267.9 55492 +1970 155 21.95 15.95 20.3 0.03 569.41 276.64 55572 +1970 156 26.3 20.3 24.65 0 720.29 350.61 55648 +1970 157 27.93 21.93 26.28 0.04 784.93 256.95 55719 +1970 158 25.7 19.7 24.05 0 697.66 353.76 55786 +1970 159 25.37 19.37 23.72 0 685.47 355.51 55849 +1970 160 27.66 21.66 26.01 0 773.9 344.56 55908 +1970 161 31.32 25.32 29.67 0 935.16 323.76 55962 +1970 162 32.14 26.14 30.49 0 974.93 318.56 56011 +1970 163 30.19 24.19 28.54 0 882.61 330.89 56056 +1970 164 30.57 24.57 28.92 0.79 899.99 246.49 56097 +1970 165 29.07 23.07 27.42 0 832.99 337.44 56133 +1970 166 24.37 18.37 22.72 0.11 649.63 270.5 56165 +1970 167 22.26 16.26 20.61 0 579.19 369.23 56192 +1970 168 22.27 16.27 20.62 1.93 579.51 276.95 56214 +1970 169 15.13 9.13 13.48 0 387.01 391.87 56231 +1970 170 15.59 9.59 13.94 0 397.51 390.68 56244 +1970 171 14.57 8.57 12.92 0.46 374.56 295 56252 +1970 172 11.46 5.46 9.81 0.01 311.44 300.25 56256 +1970 173 15.18 9.18 13.53 0 388.14 391.78 56255 +1970 174 13.46 7.46 11.81 0 350.88 395.88 56249 +1970 175 13.42 7.42 11.77 0.18 350.05 296.95 56238 +1970 176 17.12 11.12 15.47 0 434.17 386.36 56223 +1970 177 17.85 11.85 16.2 0 452.65 384.12 56203 +1970 178 15.03 9.03 13.38 0.05 384.76 293.94 56179 +1970 179 20.09 14.09 18.44 0 513.62 376.88 56150 +1970 180 21.22 15.22 19.57 0.04 546.93 279.6 56116 +1970 181 21.5 15.5 19.85 0 555.46 371.7 56078 +1970 182 24.54 18.54 22.89 0 655.61 359.35 56035 +1970 183 25.65 19.65 24 0 695.8 354.19 55987 +1970 184 21.58 15.58 19.93 0.68 557.92 278.2 55935 +1970 185 18.34 12.34 16.69 0 465.43 381.79 55879 +1970 186 18.09 12.09 16.44 0.1 458.88 286.72 55818 +1970 187 16.39 10.39 14.74 0 416.33 387 55753 +1970 188 18.19 12.19 16.54 0.28 461.49 286.15 55684 +1970 189 23.37 17.37 21.72 0 615.39 363.02 55611 +1970 190 21.85 15.85 20.2 0 566.28 368.6 55533 +1970 191 26.09 20.09 24.44 0.01 712.3 262.83 55451 +1970 192 25.38 19.38 23.73 0.16 685.84 265.09 55366 +1970 193 21.84 15.84 20.19 0.11 565.97 275.85 55276 +1970 194 18.34 12.34 16.69 0 465.43 379.43 55182 +1970 195 20.49 14.49 18.84 0 525.2 372.16 55085 +1970 196 23.93 17.93 22.28 0.08 634.38 268.98 54984 +1970 197 25.49 19.49 23.84 0.01 689.89 263.54 54879 +1970 198 24.32 18.32 22.67 0.73 647.88 267.1 54770 +1970 199 23.43 17.43 21.78 0 617.4 359.5 54658 +1970 200 26.71 20.71 25.06 0.73 736.11 258.39 54542 +1970 201 23.36 17.36 21.71 0.65 615.06 269.2 54423 +1970 202 21.87 15.87 20.22 0.5 566.91 273.12 54301 +1970 203 20.04 14.04 18.39 1.81 512.18 277.58 54176 +1970 204 18.6 12.6 16.95 0.45 472.34 280.67 54047 +1970 205 17.95 11.95 16.3 0.05 455.24 281.74 53915 +1970 206 16.53 10.53 14.88 0.01 419.7 284.34 53780 +1970 207 18.28 12.28 16.63 0 463.85 373.44 53643 +1970 208 20.54 14.54 18.89 0.14 526.67 274.14 53502 +1970 209 20.98 14.98 19.33 0 539.7 363.34 53359 +1970 210 25 19 23.35 0.13 672.02 260.21 53213 +1970 211 28.21 22.21 26.56 0.99 796.51 248.16 53064 +1970 212 30.5 24.5 28.85 0.22 896.77 238.14 52913 +1970 213 26.56 20.56 24.91 1.38 730.29 253.21 52760 +1970 214 27.06 21.06 25.41 0.67 749.85 250.88 52604 +1970 215 23.81 17.81 22.16 1.4 630.27 261.25 52445 +1970 216 23.79 17.79 22.14 0.04 629.58 260.57 52285 +1970 217 24.22 18.22 22.57 0.15 644.4 258.6 52122 +1970 218 22.87 16.87 21.22 0.07 598.86 262.05 51958 +1970 219 23.72 17.72 22.07 1.12 627.2 258.78 51791 +1970 220 22.59 16.59 20.94 0 589.76 348.51 51622 +1970 221 18.89 12.89 17.24 0 480.14 360.07 51451 +1970 222 16.36 10.36 14.71 0.23 415.61 274.63 51279 +1970 223 18.29 12.29 16.64 0.24 464.12 269.74 51105 +1970 224 19.49 13.49 17.84 0.57 496.64 266.22 50929 +1970 225 20.97 14.97 19.32 1.31 539.4 261.74 50751 +1970 226 17.14 11.14 15.49 0.08 434.67 269.63 50572 +1970 227 18.11 12.11 16.46 0.3 459.4 266.63 50392 +1970 228 20.38 14.38 18.73 0.31 522 260.5 50210 +1970 229 24.5 18.5 22.85 0.11 654.2 248.28 50026 +1970 230 23.5 17.5 21.85 1.09 619.76 250.34 49842 +1970 231 28.13 22.13 26.48 0.76 793.19 234.05 49656 +1970 232 24.86 18.86 23.21 0.05 666.99 244.22 49469 +1970 233 26.91 20.91 25.26 0 743.94 315.32 49280 +1970 234 24.95 18.95 23.3 0.55 670.22 241.9 49091 +1970 235 23.27 17.27 21.62 0.1 612.06 245.79 48900 +1970 236 22.57 16.57 20.92 0 589.12 328.9 48709 +1970 237 20 14 18.35 0 511.04 335.88 48516 +1970 238 21.28 15.28 19.63 0 548.75 330.11 48323 +1970 239 18.35 12.35 16.7 0 465.7 337.56 48128 +1970 240 18.85 12.85 17.2 0.05 479.06 250.79 47933 +1970 241 19.15 13.15 17.5 0.38 487.23 248.85 47737 +1970 242 19.9 13.9 18.25 0.74 508.19 245.88 47541 +1970 243 24.15 18.15 22.5 0.38 641.97 233.64 47343 +1970 244 19.85 13.85 18.2 0.05 506.77 243.25 47145 +1970 245 17.34 11.34 15.69 0 439.67 329.47 46947 +1970 246 15.31 9.31 13.66 0 391.09 332.41 46747 +1970 247 15.41 9.41 13.76 0 393.37 330.29 46547 +1970 248 16.96 10.96 15.31 0.26 430.2 243.48 46347 +1970 249 16.98 10.98 15.33 0.15 430.7 241.88 46146 +1970 250 17.39 11.39 15.74 0 440.93 319.53 45945 +1970 251 20.79 14.79 19.14 0.18 534.04 230.98 45743 +1970 252 16.89 10.89 15.24 0.17 428.48 237.36 45541 +1970 253 12.16 6.16 10.51 0 324.79 324.32 45339 +1970 254 12.78 6.78 11.13 0 337.02 320.98 45136 +1970 255 11.74 5.74 10.09 0 316.72 320.56 44933 +1970 256 11.19 5.19 9.54 0 306.42 319.18 44730 +1970 257 13.2 7.2 11.55 0 345.53 313.36 44527 +1970 258 15.33 9.33 13.68 0 391.55 306.68 44323 +1970 259 18.97 12.97 17.32 1.04 482.32 221.68 44119 +1970 260 21.99 15.99 20.34 0 570.66 284.59 43915 +1970 261 20.81 14.81 19.16 0.33 534.64 214.32 43711 +1970 262 22.93 16.93 21.28 0.08 600.82 207.74 43507 +1970 263 21.19 15.19 19.54 0 546.02 279.97 43303 +1970 264 18.27 12.27 16.62 0 463.59 285.29 43099 +1970 265 19.49 13.49 17.84 0 496.64 279.87 42894 +1970 266 22.65 16.65 21 0 591.7 268.45 42690 +1970 267 23.41 17.41 21.76 0 616.73 263.5 42486 +1970 268 20.94 14.94 19.29 0 538.51 268.45 42282 +1970 269 23.71 17.71 22.06 0 626.86 257.74 42078 +1970 270 21.45 15.45 19.8 0 553.93 262.06 41875 +1970 271 21.79 15.79 20.14 0 564.42 258.58 41671 +1970 272 17.72 11.72 16.07 0 449.31 266.3 41468 +1970 273 21.71 15.71 20.06 0 561.93 253.79 41265 +1970 274 19.44 13.44 17.79 0.03 495.25 192.88 41062 +1970 275 15.15 9.15 13.5 0 387.46 263.72 40860 +1970 276 16.41 10.41 14.76 0.27 416.81 193.93 40658 +1970 277 13.46 7.46 11.81 0.57 350.88 196.04 40456 +1970 278 12.71 6.71 11.06 0 335.62 259.74 40255 +1970 279 12.09 6.09 10.44 0 323.43 257.88 40054 +1970 280 12.03 6.03 10.38 0 322.28 255.3 39854 +1970 281 9.14 3.14 7.49 0.03 270.51 192.4 39654 +1970 282 8.84 2.84 7.19 0 265.57 254.11 39455 +1970 283 8.02 2.02 6.37 0 252.46 252.2 39256 +1970 284 6.91 0.91 5.26 0 235.6 250.35 39058 +1970 285 8.69 2.69 7.04 0.12 263.12 184.24 38861 +1970 286 10.02 4.02 8.37 0.02 285.45 180.93 38664 +1970 287 15.18 9.18 13.53 0.14 388.14 172.97 38468 +1970 288 14.12 8.12 12.47 0 364.8 229.64 38273 +1970 289 15.42 9.42 13.77 0.18 393.6 168.66 38079 +1970 290 18.77 12.77 17.12 0.35 476.9 161.82 37885 +1970 291 16.58 10.58 14.93 0 420.91 217.38 37693 +1970 292 17.69 11.69 16.04 0 448.55 212.71 37501 +1970 293 16.83 10.83 15.18 0 427.01 211.65 37311 +1970 294 17.11 11.11 15.46 0 433.92 208.33 37121 +1970 295 17.53 11.53 15.88 0 444.47 204.81 36933 +1970 296 16.09 10.09 14.44 0 409.18 204.83 36745 +1970 297 13.5 7.5 11.85 0 351.71 206.16 36560 +1970 298 11.57 5.57 9.92 0.36 313.51 154.62 36375 +1970 299 9.41 3.41 7.76 0.38 275.02 154.42 36191 +1970 300 4.15 -1.85 2.5 1.05 197.81 156.03 36009 +1970 301 5.64 -0.36 3.99 0.45 217.5 153.2 35829 +1970 302 8.95 2.95 7.3 0 267.37 198.55 35650 +1970 303 12.25 6.25 10.6 0 326.54 192.22 35472 +1970 304 7.68 1.68 6.03 0 247.19 194.72 35296 +1970 305 3.37 -2.63 1.72 0.17 188.13 146.58 35122 +1970 306 5.04 -0.96 3.39 0.01 209.38 143.93 34950 +1970 307 8.66 2.66 7.01 0 262.64 186.24 34779 +1970 308 8.47 2.47 6.82 0 259.58 183.82 34610 +1970 309 6.1 0.1 4.45 0 223.91 183.56 34444 +1970 310 7.66 1.66 6.01 0.03 246.88 134.84 34279 +1970 311 9.31 3.31 7.66 0.06 273.34 132.06 34116 +1970 312 10.59 4.59 8.94 0 295.51 172.17 33956 +1970 313 15.2 9.2 13.55 0.67 388.59 123.43 33797 +1970 314 12.59 6.59 10.94 0.41 333.23 124.47 33641 +1970 315 16.74 10.74 15.09 0.82 424.8 118.56 33488 +1970 316 15.78 9.78 14.13 1.44 401.91 118 33337 +1970 317 9.16 3.16 7.51 0.14 270.84 121.99 33188 +1970 318 12.61 6.61 10.96 0.76 333.63 117.64 33042 +1970 319 9.09 3.09 7.44 0.48 269.68 119.03 32899 +1970 320 10.36 4.36 8.71 0.01 291.42 116.76 32758 +1970 321 10.61 4.61 8.96 0 295.87 153.36 32620 +1970 322 8.03 2.03 6.38 0 252.61 153.84 32486 +1970 323 9.85 3.85 8.2 0 282.51 150.68 32354 +1970 324 10.63 4.63 8.98 0.62 296.23 110.95 32225 +1970 325 7.66 1.66 6.01 0 246.88 148.77 32100 +1970 326 7.63 1.63 5.98 0 246.42 147.34 31977 +1970 327 8.25 2.25 6.6 0 256.08 145.02 31858 +1970 328 8.45 2.45 6.8 0 259.26 142.9 31743 +1970 329 8.23 2.23 6.58 0.13 255.76 106.2 31631 +1970 330 11.42 5.42 9.77 0 310.69 137.42 31522 +1970 331 9.91 3.91 8.26 0 283.55 137.49 31417 +1970 332 13.3 7.3 11.65 0 347.58 132.66 31316 +1970 333 12.96 6.96 11.31 0 340.64 131.97 31218 +1970 334 13.52 7.52 11.87 0.07 352.13 97.74 31125 +1970 335 3.04 -2.96 1.39 0.42 184.16 102.92 31035 +1970 336 5.59 -0.41 3.94 0 216.82 134.66 30949 +1970 337 2.74 -3.26 1.09 0 180.61 134.64 30867 +1970 338 -2.94 -8.94 -4.59 0 123.71 136.14 30790 +1970 339 0.48 -5.52 -1.17 0.03 155.73 100.48 30716 +1970 340 -1.2 -7.2 -2.85 0 139.21 133.94 30647 +1970 341 2.81 -3.19 1.16 0 181.43 131.2 30582 +1970 342 4.19 -1.81 2.54 0.23 198.32 97.27 30521 +1970 343 5.52 -0.48 3.87 0.02 215.86 96.07 30465 +1970 344 3.39 -2.61 1.74 0 188.37 128.17 30413 +1970 345 2.88 -3.12 1.23 0.01 182.26 96 30366 +1970 346 1.23 -4.77 -0.42 0.47 163.64 96.18 30323 +1970 347 -2.54 -8.54 -4.19 0.83 127.14 143.09 30284 +1970 348 2.45 -3.55 0.8 0 177.24 172.66 30251 +1970 349 2.28 -3.72 0.63 0 175.29 172.1 30221 +1970 350 1.33 -4.67 -0.32 0 164.72 172.07 30197 +1970 351 4.71 -1.29 3.06 0 205.02 169.53 30177 +1970 352 7.08 1.08 5.43 0 238.11 167.06 30162 +1970 353 8.68 2.68 7.03 0 262.96 121.86 30151 +1970 354 9.54 3.54 7.89 0 277.21 121.19 30145 +1970 355 8.84 2.84 7.19 0 265.57 121.71 30144 +1970 356 6.96 0.96 5.31 0 236.34 123.05 30147 +1970 357 6.52 0.52 4.87 0 229.91 123.39 30156 +1970 358 0.55 -5.45 -1.1 0 156.45 126.63 30169 +1970 359 1.3 -4.7 -0.35 0 164.39 126.42 30186 +1970 360 2.18 -3.82 0.53 0.11 174.15 94.78 30208 +1970 361 -0.84 -6.84 -2.49 0 142.61 128.03 30235 +1970 362 0.81 -5.19 -0.84 0 159.17 127.78 30267 +1970 363 0.3 -5.7 -1.35 0 153.88 128.59 30303 +1970 364 0.96 -5.04 -0.69 0.01 160.75 96.53 30343 +1970 365 0.38 -5.62 -1.27 0.09 154.7 97.15 30388 +1971 1 0.32 -5.68 -1.33 0 154.09 130.46 30438 +1971 2 -1.02 -7.02 -2.67 0 140.9 131.75 30492 +1971 3 1.26 -4.74 -0.39 0 163.96 131.72 30551 +1971 4 -2.09 -8.09 -3.74 0 131.09 134.04 30614 +1971 5 1.51 -4.49 -0.14 0 166.68 133.17 30681 +1971 6 -1.73 -7.73 -3.38 0 134.32 135.46 30752 +1971 7 -4.5 -10.5 -6.15 0.03 111.12 145.84 30828 +1971 8 -4.63 -10.63 -6.28 0 110.12 181.59 30907 +1971 9 -4.01 -10.01 -5.66 0 114.95 182.54 30991 +1971 10 -5.33 -11.33 -6.98 0.01 104.88 148.8 31079 +1971 11 -1.24 -7.24 -2.89 0.12 138.83 148.71 31171 +1971 12 -2.04 -8.04 -3.69 0 131.53 185.21 31266 +1971 13 1.78 -4.22 0.13 0 169.65 184.78 31366 +1971 14 1.45 -4.55 -0.2 0.69 166.02 150.09 31469 +1971 15 -2.73 -8.73 -4.38 0 125.5 189.24 31575 +1971 16 0.39 -5.61 -1.26 0 154.8 189.04 31686 +1971 17 2.08 -3.92 0.43 0 173.01 148.2 31800 +1971 18 -0.39 -6.39 -2.04 0 146.97 151.32 31917 +1971 19 0.24 -5.76 -1.41 0 153.27 152.98 32038 +1971 20 3.21 -2.79 1.56 0 186.2 153 32161 +1971 21 0.28 -5.72 -1.37 0 153.68 156.58 32289 +1971 22 3.93 -2.07 2.28 0 195.04 156.32 32419 +1971 23 5.23 -0.77 3.58 0.01 211.92 117.93 32552 +1971 24 6.66 0.66 5.01 0.22 231.94 118.7 32688 +1971 25 6.15 0.15 4.5 0 224.62 160.52 32827 +1971 26 6.26 0.26 4.61 0 226.18 162.35 32969 +1971 27 4.76 -1.24 3.11 0 205.68 165.44 33114 +1971 28 5.94 -0.06 4.29 1.28 221.67 125.1 33261 +1971 29 4.2 -1.8 2.55 0.03 198.45 127.8 33411 +1971 30 1.87 -4.13 0.22 0.22 170.65 130.59 33564 +1971 31 2.23 -3.77 0.58 0 174.72 176.29 33718 +1971 32 5.93 -0.07 4.28 0 221.53 175.87 33875 +1971 33 8.51 2.51 6.86 0.08 260.22 132.22 34035 +1971 34 6.48 0.48 4.83 0 229.33 180.24 34196 +1971 35 1.37 -4.63 -0.28 0.01 165.15 139.46 34360 +1971 36 0.89 -5.11 -0.76 0 160.01 188.76 34526 +1971 37 1.84 -4.16 0.19 0 170.32 190.64 34694 +1971 38 5.38 -0.62 3.73 0 213.95 190.9 34863 +1971 39 7.97 1.97 6.32 0.26 251.67 143.45 35035 +1971 40 9.64 3.64 7.99 0 278.91 192.18 35208 +1971 41 11.28 5.28 9.63 0.11 308.09 144.69 35383 +1971 42 11 5 9.35 0.07 302.93 146.81 35560 +1971 43 10.93 4.93 9.28 0.02 301.65 148.86 35738 +1971 44 5.23 -0.77 3.58 0 211.92 206.67 35918 +1971 45 5.61 -0.39 3.96 0 217.09 208.97 36099 +1971 46 3.73 -2.27 2.08 0.19 192.55 159.88 36282 +1971 47 7.57 1.57 5.92 0 245.5 212.65 36466 +1971 48 9.39 3.39 7.74 0 274.68 213.51 36652 +1971 49 8.06 2.06 6.41 0.12 253.08 163.27 36838 +1971 50 6.13 0.13 4.48 0.1 224.34 166.67 37026 +1971 51 5.08 -0.92 3.43 0 209.91 226.14 37215 +1971 52 2.64 -3.36 0.99 0 179.44 230.96 37405 +1971 53 1.95 -4.05 0.3 0 171.55 234.45 37596 +1971 54 3.78 -2.22 2.13 0 193.17 235.81 37788 +1971 55 5.39 -0.61 3.74 0.01 214.09 178.06 37981 +1971 56 5.45 -0.55 3.8 0 214.9 240.05 38175 +1971 57 2.7 -3.3 1.05 0.34 180.14 183.98 38370 +1971 58 2.23 -3.77 0.58 0 174.72 248.63 38565 +1971 59 1.98 -4.02 0.33 0 171.89 251.56 38761 +1971 60 1 -5 -0.65 0 161.18 255.21 38958 +1971 61 -1.68 -7.68 -3.33 0 134.77 259.96 39156 +1971 62 1.31 -4.69 -0.34 0 164.5 260.78 39355 +1971 63 2.45 -3.55 0.8 0.04 177.24 197.2 39553 +1971 64 1.73 -4.27 0.08 0 169.1 266.45 39753 +1971 65 -1.26 -7.26 -2.91 0.03 138.65 236.74 39953 +1971 66 -0.87 -6.87 -2.52 0.14 142.33 238.82 40154 +1971 67 0.42 -5.58 -1.23 0 155.11 309.17 40355 +1971 68 3.81 -2.19 2.16 0 193.54 276.21 40556 +1971 69 4.59 -1.41 2.94 0 203.46 278.11 40758 +1971 70 8.07 2.07 6.42 0 253.24 277.12 40960 +1971 71 9.53 3.53 7.88 0 277.05 278.12 41163 +1971 72 8.66 2.66 7.01 0 262.64 282.09 41366 +1971 73 8.01 2.01 6.36 0 252.3 285.59 41569 +1971 74 6.67 0.67 5.02 0.38 232.08 217.47 41772 +1971 75 5.75 -0.25 4.1 1.89 219.02 220.31 41976 +1971 76 4.19 -1.81 2.54 0 198.32 298.06 42179 +1971 77 9.15 3.15 7.5 0.56 270.67 221.07 42383 +1971 78 3.94 -2.06 2.29 0 195.16 303.64 42587 +1971 79 4.96 -1.04 3.31 0.53 208.32 229 42791 +1971 80 5.92 -0.08 4.27 0.16 221.39 230.12 42996 +1971 81 8.46 2.46 6.81 0 259.42 306.21 43200 +1971 82 9.07 3.07 7.42 0.16 269.35 231.01 43404 +1971 83 1.06 -4.94 -0.59 0 161.81 319.53 43608 +1971 84 6.6 0.6 4.95 0 231.07 316.35 43812 +1971 85 7.27 1.27 5.62 0 240.96 318.02 44016 +1971 86 8.2 2.2 6.55 0 255.28 319.19 44220 +1971 87 7.74 1.74 6.09 0 248.11 322.36 44424 +1971 88 10.28 4.28 8.63 0 290 320.97 44627 +1971 89 7.58 1.58 5.93 0.02 245.65 245.43 44831 +1971 90 6.58 0.58 4.93 0 230.78 330.94 45034 +1971 91 14.57 8.57 12.92 0 374.56 319.88 45237 +1971 92 11.59 5.59 9.94 0 313.89 327.87 45439 +1971 93 15.16 9.16 13.51 0 387.69 322.97 45642 +1971 94 15.24 9.24 13.59 0.14 389.5 243.68 45843 +1971 95 18.45 12.45 16.8 0 468.34 319.09 46045 +1971 96 22.33 16.33 20.68 0.01 581.42 231.99 46246 +1971 97 16.91 10.91 15.26 0 428.97 327.12 46446 +1971 98 19.58 13.58 17.93 0.11 499.16 241.34 46647 +1971 99 14.88 8.88 13.23 0 381.41 335.8 46846 +1971 100 12.18 6.18 10.53 0 325.18 343.31 47045 +1971 101 11.36 5.36 9.71 0 309.57 346.77 47243 +1971 102 10.05 4.05 8.4 0 285.98 350.98 47441 +1971 103 12.36 6.36 10.71 0 328.69 348.62 47638 +1971 104 13.2 7.2 11.55 0 345.53 348.76 47834 +1971 105 16.43 10.43 14.78 0.53 417.29 257.37 48030 +1971 106 17.44 11.44 15.79 0.04 442.19 256.62 48225 +1971 107 14.39 8.39 12.74 0 370.63 351.27 48419 +1971 108 15.54 9.54 13.89 0.04 396.35 262.74 48612 +1971 109 16.35 10.35 14.7 0 415.37 349.91 48804 +1971 110 17.47 11.47 15.82 0 442.95 348.35 48995 +1971 111 16.14 10.14 14.49 0 410.37 353.35 49185 +1971 112 15.06 9.06 13.41 0 385.44 357.49 49374 +1971 113 8.52 2.52 6.87 0.95 260.38 278.74 49561 +1971 114 11.32 5.32 9.67 0.55 308.83 276.21 49748 +1971 115 9.12 3.12 7.47 0.52 270.17 280.24 49933 +1971 116 10.22 4.22 8.57 0.81 288.95 279.74 50117 +1971 117 9.83 3.83 8.18 0.03 282.17 281.26 50300 +1971 118 10.32 4.32 8.67 0 290.71 375.47 50481 +1971 119 12.03 6.03 10.38 0 322.28 373.41 50661 +1971 120 7.26 1.26 5.61 0 240.81 382.94 50840 +1971 121 16.82 10.82 15.17 0 426.76 364.5 51016 +1971 122 14.7 8.7 13.05 0 377.42 371.06 51191 +1971 123 13.58 7.58 11.93 0 353.38 374.68 51365 +1971 124 14.45 8.45 12.8 0 371.94 373.77 51536 +1971 125 16.37 10.37 14.72 0 415.85 369.95 51706 +1971 126 13.21 7.21 11.56 0 345.73 378.58 51874 +1971 127 19.45 13.45 17.8 0 495.53 362.85 52039 +1971 128 19.81 13.81 18.16 0 505.63 362.67 52203 +1971 129 19.45 13.45 17.8 0.13 495.53 273.49 52365 +1971 130 21.28 15.28 19.63 0 548.75 359.27 52524 +1971 131 23.94 17.94 22.29 0.41 634.72 262.39 52681 +1971 132 23.75 17.75 22.1 0.08 628.22 263.56 52836 +1971 133 22.64 16.64 20.99 0 591.38 356.48 52989 +1971 134 21 15 19.35 0 540.3 363.19 53138 +1971 135 22.21 16.21 20.56 0 577.6 359.47 53286 +1971 136 23.55 17.55 21.9 0.03 621.44 266.13 53430 +1971 137 20.91 14.91 19.26 0.44 537.61 274.12 53572 +1971 138 15.65 9.65 14 0 398.89 382.02 53711 +1971 139 17.31 11.31 15.66 0 438.92 378.19 53848 +1971 140 18.54 12.54 16.89 0 470.74 375.02 53981 +1971 141 21.57 15.57 19.92 0 557.61 365.28 54111 +1971 142 20.17 14.17 18.52 0 515.92 370.69 54238 +1971 143 18.09 12.09 16.44 0 458.88 377.85 54362 +1971 144 19.27 13.27 17.62 0.72 490.54 280.99 54483 +1971 145 20.35 14.35 18.7 0.45 521.12 278.65 54600 +1971 146 21.68 15.68 20.03 0.74 561.01 275.37 54714 +1971 147 21.05 15.05 19.4 0 541.8 369.92 54824 +1971 148 18.53 12.53 16.88 0 470.47 378.68 54931 +1971 149 18.75 12.75 17.1 0.04 476.36 283.73 55034 +1971 150 17.58 11.58 15.93 0.02 445.74 286.64 55134 +1971 151 18.69 12.69 17.04 0 474.75 379.22 55229 +1971 152 20.72 14.72 19.07 0.37 531.97 279.44 55321 +1971 153 21.78 15.78 20.13 0.59 564.11 276.74 55409 +1971 154 23.48 17.48 21.83 0.93 619.08 271.98 55492 +1971 155 19.32 13.32 17.67 0 491.92 378.06 55572 +1971 156 16.58 10.58 14.93 0.14 420.91 289.97 55648 +1971 157 19.39 13.39 17.74 1.59 493.86 283.74 55719 +1971 158 19.14 13.14 17.49 2.31 486.96 284.48 55786 +1971 159 19.14 13.14 17.49 0.42 486.96 284.66 55849 +1971 160 19.32 13.32 17.67 0.3 491.92 284.36 55908 +1971 161 18.16 12.16 16.51 0.02 460.7 287.15 55962 +1971 162 17.17 11.17 15.52 0 435.41 385.86 56011 +1971 163 22.03 16.03 20.38 0 571.92 369.95 56056 +1971 164 20.93 14.93 19.28 0 538.21 374.04 56097 +1971 165 21.5 15.5 19.85 0 555.46 372.07 56133 +1971 166 21.32 15.32 19.67 0 549.96 372.81 56165 +1971 167 21.36 15.36 19.71 0 551.18 372.61 56192 +1971 168 20.98 14.98 19.33 0.04 539.7 280.55 56214 +1971 169 17.43 11.43 15.78 0 441.94 385.58 56231 +1971 170 19.21 13.21 17.56 0.41 488.88 285.08 56244 +1971 171 19.68 13.68 18.03 0.01 501.96 283.97 56252 +1971 172 19.2 13.2 17.55 0.18 488.61 285.14 56256 +1971 173 14.38 8.38 12.73 0 370.41 393.78 56255 +1971 174 19.87 13.87 18.22 0 507.33 377.88 56249 +1971 175 19.54 13.54 17.89 0 498.04 378.95 56238 +1971 176 21.76 15.76 20.11 0.24 563.48 278.33 56223 +1971 177 21.79 15.79 20.14 0 564.42 370.89 56203 +1971 178 19.69 13.69 18.04 0.57 502.24 283.75 56179 +1971 179 19.23 13.23 17.58 0 489.43 379.74 56150 +1971 180 20.18 14.18 18.53 0 516.2 376.46 56116 +1971 181 21.9 15.9 20.25 0 567.85 370.21 56078 +1971 182 23.93 17.93 22.28 0.18 634.38 271.48 56035 +1971 183 26.69 20.69 25.04 0 735.33 349.24 55987 +1971 184 21.88 15.88 20.23 0 567.22 369.81 55935 +1971 185 21.68 15.68 20.03 0.09 561.01 277.86 55879 +1971 186 21.04 15.04 19.39 0 541.5 372.56 55818 +1971 187 19.65 13.65 18 0 501.12 377.16 55753 +1971 188 21.95 15.95 20.3 0 569.41 368.77 55684 +1971 189 23.02 17.02 21.37 0 603.78 364.43 55611 +1971 190 23.6 17.6 21.95 0.14 623.13 271.28 55533 +1971 191 24.53 18.53 22.88 0 655.26 357.52 55451 +1971 192 20.8 14.8 19.15 0 534.34 371.85 55366 +1971 193 20.36 14.36 18.71 0.12 521.41 279.83 55276 +1971 194 17.18 11.18 15.53 0 435.66 382.86 55182 +1971 195 18.53 12.53 16.88 0.05 470.47 283.93 55085 +1971 196 18.39 12.39 16.74 0.07 466.76 283.94 54984 +1971 197 22.27 16.27 20.62 0 579.51 364.83 54879 +1971 198 25.79 19.79 24.14 2.01 701.02 262.2 54770 +1971 199 27.89 21.89 26.24 0.96 783.29 254.23 54658 +1971 200 24.88 18.88 23.23 0.14 667.71 264.74 54542 +1971 201 24.72 18.72 23.07 0.21 661.99 264.92 54423 +1971 202 25.79 19.79 24.14 0 701.02 347.89 54301 +1971 203 21.97 15.97 20.32 0.29 570.04 272.46 54176 +1971 204 24.66 18.66 23.01 0.73 659.86 263.97 54047 +1971 205 25.37 19.37 23.72 0.19 685.47 261.25 53915 +1971 206 24.94 18.94 23.29 0.9 669.86 262.28 53780 +1971 207 26.02 20.02 24.37 0.16 709.66 258.15 53643 +1971 208 27.39 21.39 25.74 0.14 763 252.73 53502 +1971 209 27 21 25.35 0.17 747.48 253.72 53359 +1971 210 25.2 19.2 23.55 0.97 679.27 259.55 53213 +1971 211 24.5 18.5 22.85 0 654.2 348.35 53064 +1971 212 24.55 18.55 22.9 0.11 655.97 260.53 52913 +1971 213 24.44 18.44 22.79 0 652.09 347.11 52760 +1971 214 26.98 20.98 25.33 0 746.69 334.9 52604 +1971 215 26.24 20.24 24.59 0.01 718 253.33 52445 +1971 216 20.9 14.9 19.25 0.27 537.31 268.69 52285 +1971 217 24.52 18.52 22.87 0.73 654.91 257.66 52122 +1971 218 20.37 14.37 18.72 0.7 521.7 268.76 51958 +1971 219 18.67 12.67 17.02 0.21 474.21 272.02 51791 +1971 220 19.94 13.94 18.29 0 509.33 357.78 51622 +1971 221 22.09 16.09 20.44 0.07 573.81 262.04 51451 +1971 222 24.32 18.32 22.67 0 647.88 339.7 51279 +1971 223 23.39 17.39 21.74 0 616.06 342.33 51105 +1971 224 24.71 18.71 23.06 0 661.64 335.96 50929 +1971 225 24.5 18.5 22.85 0.11 654.2 251.8 50751 +1971 226 26.45 20.45 24.8 0.04 726.05 244.61 50572 +1971 227 24.71 18.71 23.06 0.08 661.64 249.4 50392 +1971 228 26.3 20.3 24.65 0.13 720.29 243.35 50210 +1971 229 21.99 15.99 20.34 0.57 570.66 255.47 50026 +1971 230 23.53 17.53 21.88 0 620.77 333.67 49842 +1971 231 24.05 18.05 22.4 0 638.51 330.2 49656 +1971 232 26.62 20.62 24.97 0 732.62 317.98 49469 +1971 233 29.83 23.83 28.18 0 866.39 300.76 49280 +1971 234 27.73 21.73 26.08 0 776.75 310.14 49091 +1971 235 23.69 17.69 22.04 0.44 626.18 244.59 48900 +1971 236 22.85 16.85 21.2 0 598.2 327.89 48709 +1971 237 25.72 19.72 24.07 0 698.41 314.96 48516 +1971 238 25.29 19.29 23.64 0 682.55 315.18 48323 +1971 239 24.66 18.66 23.01 0 659.86 316.31 48128 +1971 240 21.11 15.11 19.46 0.56 543.61 245.59 47933 +1971 241 21.87 15.87 20.22 0.27 566.91 242.43 47737 +1971 242 19.24 13.24 17.59 0 489.71 329.8 47541 +1971 243 21.17 15.17 19.52 0 545.42 322.03 47343 +1971 244 13.69 7.69 12.04 0 355.68 339.83 47145 +1971 245 14.49 8.49 12.84 0 372.81 336.23 46947 +1971 246 19.18 13.18 17.53 0 488.06 322.52 46747 +1971 247 24.26 18.26 22.61 0.3 645.79 227.97 46547 +1971 248 21.05 15.05 19.4 0 541.8 313.17 46347 +1971 249 16.39 10.39 14.74 0 416.33 323.95 46146 +1971 250 14.93 8.93 13.28 0 382.52 325.31 45945 +1971 251 17.01 11.01 15.36 0.2 431.44 238.77 45743 +1971 252 20.7 14.7 19.05 0 531.38 306.13 45541 +1971 253 21.9 15.9 20.25 0.08 567.85 225.24 45339 +1971 254 19.84 13.84 18.19 0.36 506.48 228.36 45136 +1971 255 20.86 14.86 19.21 0.29 536.12 224.46 44933 +1971 256 21.43 15.43 19.78 0 553.32 295.34 44730 +1971 257 16.13 10.13 14.48 0.67 410.13 230.46 44527 +1971 258 13.25 7.25 11.6 0 346.55 310.87 44323 +1971 259 14.56 8.56 12.91 0 374.34 305.83 44119 +1971 260 16.94 10.94 15.29 0.22 429.71 223.69 43915 +1971 261 16.71 10.71 15.06 0 424.07 296.34 43711 +1971 262 13.85 7.85 12.2 0 359.05 299.94 43507 +1971 263 10.12 4.12 8.47 0 287.2 303.81 43303 +1971 264 12.69 6.69 11.04 0 335.22 296.97 43099 +1971 265 15.77 9.77 14.12 0 401.68 288.63 42894 +1971 266 17.09 11.09 15.44 1.01 433.42 212.46 42690 +1971 267 15.71 9.71 14.06 0.04 400.28 212.7 42486 +1971 268 11.62 5.62 9.97 0.83 314.45 216.38 42282 +1971 269 11.88 5.88 10.23 0 319.39 285.52 42078 +1971 270 14.01 8.01 12.36 0.49 362.45 209.38 41875 +1971 271 15.08 9.08 13.43 0.27 385.89 205.9 41671 +1971 272 16.5 10.5 14.85 0 418.98 268.95 41468 +1971 273 17.87 11.87 16.22 0 453.17 263.47 41265 +1971 274 16.17 10.17 14.52 0 411.08 264.47 41062 +1971 275 14.63 8.63 12.98 0 375.88 264.69 40860 +1971 276 16.81 10.81 15.16 0 426.52 257.76 40658 +1971 277 14.3 8.3 12.65 0.02 368.68 194.95 40456 +1971 278 15.05 9.05 13.4 0.01 385.21 191.79 40255 +1971 279 13.93 7.93 12.28 0 360.75 254.91 40054 +1971 280 12.06 6.06 10.41 0.1 322.85 191.44 39854 +1971 281 11.87 5.87 10.22 0.71 319.2 189.6 39654 +1971 282 8.69 2.69 7.04 0 263.12 254.29 39455 +1971 283 6.66 0.66 5.01 0 231.94 253.7 39256 +1971 284 9.26 3.26 7.61 0 272.5 247.66 39058 +1971 285 9.65 3.65 8 0 279.08 244.49 38861 +1971 286 10.89 4.89 9.24 0 300.92 240.1 38664 +1971 287 14.69 8.69 13.04 0 377.2 231.46 38468 +1971 288 11.77 5.77 10.12 0 317.3 233.15 38273 +1971 289 14.22 8.22 12.57 0 366.95 226.87 38079 +1971 290 13.48 7.48 11.83 0 351.3 225.18 37885 +1971 291 12.76 6.76 11.11 0 336.62 223.56 37693 +1971 292 14.01 8.01 12.36 0 362.45 219.03 37501 +1971 293 11 5 9.35 0 302.93 220.52 37311 +1971 294 11.83 5.83 10.18 0.08 318.44 162.41 37121 +1971 295 12.63 6.63 10.98 0 334.03 212.65 36933 +1971 296 12.23 6.23 10.58 0 326.15 210.61 36745 +1971 297 12.85 6.85 11.2 0 338.42 207.07 36560 +1971 298 10.87 4.87 9.22 0 300.56 207.01 36375 +1971 299 16.45 10.45 14.8 0.21 417.77 147.24 36191 +1971 300 17 11 15.35 0.72 431.19 144.6 36009 +1971 301 14.13 8.13 12.48 0 365.02 194.83 35829 +1971 302 14.22 8.22 12.57 0.09 366.95 144.1 35650 +1971 303 14.89 8.89 13.24 0 381.63 188.64 35472 +1971 304 10.03 4.03 8.38 0 285.63 192.35 35296 +1971 305 3.29 -2.71 1.64 0 187.16 195.49 35122 +1971 306 3.93 -2.07 2.28 0.68 195.04 144.55 34950 +1971 307 7.26 1.26 5.61 0 240.81 187.54 34779 +1971 308 6.46 0.46 4.81 0.03 229.04 139.2 34610 +1971 309 1.2 -4.8 -0.45 0.04 163.31 140.2 34444 +1971 310 6.19 0.19 4.54 0 225.19 181.02 34279 +1971 311 9.57 3.57 7.92 0 277.72 175.83 34116 +1971 312 9.15 3.15 7.5 0 270.67 173.6 33956 +1971 313 13.08 7.08 11.43 0.36 343.08 125.47 33797 +1971 314 10.15 4.15 8.5 0 287.72 168.58 33641 +1971 315 8.17 2.17 6.52 0.03 254.81 125.92 33488 +1971 316 8.39 2.39 6.74 0 258.3 165.53 33337 +1971 317 5.19 -0.81 3.54 0.13 211.39 124.39 33188 +1971 318 5.32 -0.68 3.67 0 213.14 163.41 33042 +1971 319 7.1 1.1 5.45 0.32 238.41 120.28 32899 +1971 320 10.31 4.31 8.66 0.43 290.53 116.8 32758 +1971 321 7.14 1.14 5.49 0 239.01 156.37 32620 +1971 322 6.26 0.26 4.61 0.19 226.18 116.4 32486 +1971 323 5.23 -0.77 3.58 0 211.92 154.3 32354 +1971 324 7.14 1.14 5.49 0.08 239.01 113.16 32225 +1971 325 10.7 4.7 9.05 0.05 297.48 109.63 32100 +1971 326 10.01 4.01 8.36 0 285.28 145.37 31977 +1971 327 9.27 3.27 7.62 0.02 272.67 108.14 31858 +1971 328 8.87 2.87 7.22 1.77 266.06 106.92 31743 +1971 329 9.36 3.36 7.71 0.36 274.18 105.51 31631 +1971 330 4.59 -1.41 2.94 0 203.46 142.68 31522 +1971 331 2.13 -3.87 0.48 0 173.58 142.75 31417 +1971 332 7.01 1.01 5.36 0 237.08 138.13 31316 +1971 333 9.04 3.04 7.39 0 268.85 135.52 31218 +1971 334 10.06 4.06 8.41 0 286.15 133.6 31125 +1971 335 7.52 1.52 5.87 0 244.74 134.43 31035 +1971 336 7.53 1.53 5.88 0.01 244.89 100.02 30949 +1971 337 9.93 3.93 8.28 0 283.89 129.86 30867 +1971 338 11.82 5.82 10.17 0 318.25 127.28 30790 +1971 339 13.8 7.8 12.15 0 357.99 124.58 30716 +1971 340 7.95 1.95 6.3 0 251.36 128.96 30647 +1971 341 5.82 -0.18 4.17 0 219.99 129.48 30582 +1971 342 4.8 -1.2 3.15 0.41 206.2 97.01 30521 +1971 343 7.06 1.06 5.41 0.09 237.82 95.33 30465 +1971 344 7.09 1.09 5.44 0 238.26 125.96 30413 +1971 345 3.8 -2.2 2.15 0.71 193.42 95.64 30366 +1971 346 10.53 4.53 8.88 0 294.44 122.42 30323 +1971 347 9.34 3.34 7.69 0 273.84 122.78 30284 +1971 348 4.52 -1.48 2.87 0 202.55 125.63 30251 +1971 349 6.23 0.23 4.58 0 225.75 124.23 30221 +1971 350 1.59 -4.41 -0.06 0.61 167.55 94.81 30197 +1971 351 3.42 -2.58 1.77 0.07 188.74 93.97 30177 +1971 352 2.85 -3.15 1.2 0.14 181.9 94.11 30162 +1971 353 -3.68 -9.68 -5.33 0 117.59 128.07 30151 +1971 354 -2.27 -8.27 -3.92 0 129.49 127.56 30145 +1971 355 -1.16 -7.16 -2.81 0 139.58 127.15 30144 +1971 356 -1.85 -7.85 -3.5 0.52 133.23 141.02 30147 +1971 357 -1.36 -7.36 -3.01 0 137.72 172.74 30156 +1971 358 1.68 -4.32 0.03 0 168.54 171.31 30169 +1971 359 5.43 -0.57 3.78 0 214.63 168.7 30186 +1971 360 7.19 1.19 5.54 0.25 239.76 92.64 30208 +1971 361 5.89 -0.11 4.24 0.3 220.97 93.51 30235 +1971 362 2.01 -3.99 0.36 0.49 172.22 95.42 30267 +1971 363 4 -2 2.35 0.03 195.92 95.1 30303 +1971 364 2.27 -3.73 0.62 0.31 175.17 96.07 30343 +1971 365 1.65 -4.35 0 0 168.21 128.96 30388 +1972 1 -2.3 -8.3 -3.95 0.02 129.23 142.05 30438 +1972 2 -1.85 -7.85 -3.5 0.06 133.23 142.59 30492 +1972 3 -3.55 -9.55 -5.2 0 118.65 177.08 30551 +1972 4 -3.35 -9.35 -5 0 120.29 177.85 30614 +1972 5 -4.69 -10.69 -6.34 0 109.66 178.85 30681 +1972 6 -4.57 -10.57 -6.22 0 110.58 179.62 30752 +1972 7 -5.47 -11.47 -7.12 0.02 103.86 146.28 30828 +1972 8 -3.35 -9.35 -5 0 120.29 181.38 30907 +1972 9 -2.6 -8.6 -4.25 0.4 126.62 148.67 30991 +1972 10 -2.24 -8.24 -3.89 0.31 129.76 150.39 31079 +1972 11 -3.03 -9.03 -4.68 0.47 122.96 152.67 31171 +1972 12 0.65 -5.35 -1 0 157.49 187.42 31266 +1972 13 -0.6 -6.6 -2.25 0 144.92 189.47 31366 +1972 14 -2.71 -8.71 -4.36 0 125.67 191.66 31469 +1972 15 -1.15 -7.15 -2.8 0.31 139.68 156.61 31575 +1972 16 0.39 -5.61 -1.26 0.01 154.8 156.86 31686 +1972 17 2.46 -3.54 0.81 0 177.35 193.86 31800 +1972 18 -0.42 -6.42 -2.07 0 146.68 197.03 31917 +1972 19 -0.73 -6.73 -2.38 0.23 143.67 161.28 32038 +1972 20 0.83 -5.17 -0.82 0.18 159.38 161.65 32161 +1972 21 3.11 -2.89 1.46 0.1 184.99 161.66 32289 +1972 22 4.34 -1.66 2.69 0 200.23 200.7 32419 +1972 23 6.26 0.26 4.61 0 226.18 200.19 32552 +1972 24 7.34 1.34 5.69 0 242.01 200.34 32688 +1972 25 7.97 1.97 6.32 0 251.67 200.53 32827 +1972 26 1.59 -4.41 -0.06 1.98 167.55 165.09 32969 +1972 27 0.47 -5.53 -1.18 0.54 155.63 166.83 33114 +1972 28 1.82 -4.18 0.17 0 170.1 209.92 33261 +1972 29 4.39 -1.61 2.74 0.04 200.88 167.42 33411 +1972 30 7.05 1.05 5.4 0.03 237.67 127.89 33564 +1972 31 5.97 -0.03 4.32 0 222.09 173.73 33718 +1972 32 10.91 4.91 9.26 0 301.29 171.33 33875 +1972 33 11.94 5.94 10.29 0 320.54 172.77 34035 +1972 34 10.65 4.65 9 0 296.59 176.34 34196 +1972 35 6.55 0.55 4.9 0.1 230.34 136.73 34360 +1972 36 6.4 0.4 4.75 0 228.18 184.93 34526 +1972 37 4.83 -1.17 3.18 0.16 206.6 141.44 34694 +1972 38 2.96 -3.04 1.31 0 183.21 192.67 34863 +1972 39 3.98 -2.02 2.33 0.24 195.67 145.93 35035 +1972 40 1.2 -4.8 -0.45 0.77 163.31 149.29 35208 +1972 41 2.67 -3.33 1.02 0.14 179.79 150.56 35383 +1972 42 7.04 1.04 5.39 0.98 237.52 149.88 35560 +1972 43 4.28 -1.72 2.63 0.49 199.47 153.64 35738 +1972 44 4.29 -1.71 2.64 0.39 199.59 155.57 35918 +1972 45 6.83 0.83 5.18 0.04 234.42 155.91 36099 +1972 46 4.19 -1.81 2.54 0 198.32 212.82 36282 +1972 47 4.15 -1.85 2.5 0.01 197.81 161.76 36466 +1972 48 5.69 -0.31 4.04 0.9 218.19 162.9 36652 +1972 49 2.27 -3.73 0.62 0 175.17 222.7 36838 +1972 50 3.37 -2.63 1.72 0 188.13 224.57 37026 +1972 51 7.79 1.79 6.14 0.14 248.88 167.67 37215 +1972 52 7.36 1.36 5.71 0.88 242.31 170.11 37405 +1972 53 4.72 -1.28 3.07 0 205.16 232.25 37596 +1972 54 4.77 -1.23 3.12 0.02 205.81 176.23 37788 +1972 55 5.23 -0.77 3.58 0.1 211.92 178.17 37981 +1972 56 7.76 1.76 6.11 0 248.42 237.73 38175 +1972 57 6.92 0.92 5.27 0.08 235.74 181.12 38370 +1972 58 5.45 -0.55 3.8 0.62 214.9 184.41 38565 +1972 59 4.47 -1.53 2.82 0.02 201.91 187.12 38761 +1972 60 8.78 2.78 7.13 0 264.59 247.89 38958 +1972 61 8.69 2.69 7.04 0 263.12 250.91 39156 +1972 62 12.51 6.51 10.86 0.19 331.65 186.36 39355 +1972 63 6.97 0.97 5.32 0.07 236.48 193.99 39553 +1972 64 6.43 0.43 4.78 0 228.61 262.14 39753 +1972 65 11.01 5.01 9.36 0.2 303.11 194.5 39953 +1972 66 13.27 7.27 11.62 1.32 346.96 193.91 40154 +1972 67 7.61 1.61 5.96 0 246.11 269.35 40355 +1972 68 9.94 3.94 8.29 0.44 284.07 201.94 40556 +1972 69 14.09 8.09 12.44 0 364.16 265.32 40758 +1972 70 16.16 10.16 14.51 0 410.84 264.14 40960 +1972 71 13.82 7.82 12.17 0 358.42 271.41 41163 +1972 72 12.94 6.94 11.29 0 340.24 275.7 41366 +1972 73 13.55 7.55 11.9 0 352.75 277.25 41569 +1972 74 13.68 7.68 12.03 0 355.47 279.7 41772 +1972 75 14.93 8.93 13.28 0 382.52 280.02 41976 +1972 76 12.61 6.61 10.96 0.01 333.63 215.13 42179 +1972 77 12.64 6.64 10.99 0 334.22 289.34 42383 +1972 78 10.42 4.42 8.77 0 292.48 295.57 42587 +1972 79 6.78 0.78 5.13 0 233.69 303.25 42791 +1972 80 4.72 -1.28 3.07 0 205.16 308.16 42996 +1972 81 8.58 2.58 6.93 0.44 261.35 229.54 43200 +1972 82 8.82 2.82 7.17 0.1 265.24 231.28 43404 +1972 83 6.62 0.62 4.97 0 231.36 313.77 43608 +1972 84 9 3 7.35 0 268.19 313.14 43812 +1972 85 9.58 3.58 7.93 0.01 277.89 236.08 44016 +1972 86 13.46 7.46 11.81 0.23 350.88 232.91 44220 +1972 87 8.76 2.76 7.11 0 264.26 320.93 44424 +1972 88 8.46 2.46 6.81 0 259.42 323.72 44627 +1972 89 11.77 5.77 10.12 0 317.3 320.73 44831 +1972 90 12.64 6.64 10.99 0 334.22 321.5 45034 +1972 91 18.51 12.51 16.86 0 469.94 310.52 45237 +1972 92 17.18 11.18 15.53 0 435.66 316.09 45439 +1972 93 16.77 10.77 15.12 0 425.54 319.24 45642 +1972 94 14.05 8.05 12.4 0 363.3 327.47 45843 +1972 95 17.57 11.57 15.92 0 445.49 321.41 46045 +1972 96 17.46 11.46 15.81 0 442.7 323.74 46246 +1972 97 13.16 7.16 11.51 0.01 344.71 251.63 46446 +1972 98 14.39 8.39 12.74 0.03 370.63 251.17 46647 +1972 99 13.26 7.26 11.61 0.34 346.76 254.44 46846 +1972 100 8.64 2.64 6.99 0.2 262.32 262.03 47045 +1972 101 11.15 5.15 9.5 0.05 305.68 260.36 47243 +1972 102 11.29 5.29 9.64 0.22 308.27 261.6 47441 +1972 103 10.77 4.77 9.12 0.4 298.75 263.69 47638 +1972 104 11.14 5.14 9.49 0 305.5 352.75 47834 +1972 105 13.07 7.07 11.42 0 342.87 350.81 48030 +1972 106 11.29 5.29 9.64 0.7 308.27 266.94 48225 +1972 107 8.67 2.67 7.02 0 262.8 362.1 48419 +1972 108 9.42 3.42 7.77 0.53 275.19 271.98 48612 +1972 109 12.64 6.64 10.99 0.83 334.22 268.76 48804 +1972 110 10.42 4.42 8.77 3.13 292.48 272.99 48995 +1972 111 8.39 2.39 6.74 0.06 258.3 276.71 49185 +1972 112 11.81 5.81 10.16 0 318.06 364.49 49374 +1972 113 6.84 0.84 5.19 0.14 234.57 280.65 49561 +1972 114 9.68 3.68 8.03 0 279.6 371.25 49748 +1972 115 11.12 5.12 9.47 0.01 305.13 277.58 49933 +1972 116 14.58 8.58 12.93 0.13 374.78 273.04 50117 +1972 117 15.01 9.01 13.36 0 384.31 364.34 50300 +1972 118 14.96 8.96 13.31 0.04 383.2 274.33 50481 +1972 119 18.35 12.35 16.7 0.07 465.7 268.45 50661 +1972 120 15.05 9.05 13.4 0.04 385.21 275.93 50840 +1972 121 21.15 15.15 19.5 1.27 544.81 263.43 51016 +1972 122 18.73 12.73 17.08 0.55 475.82 270.17 51191 +1972 123 15.33 9.33 13.68 0.27 391.55 277.92 51365 +1972 124 17.88 11.88 16.23 0.48 453.43 273.6 51536 +1972 125 20.1 14.1 18.45 0 513.9 358.92 51706 +1972 126 18.69 12.69 17.04 0.03 474.75 273.26 51874 +1972 127 18.63 12.63 16.98 0 473.14 365.4 52039 +1972 128 19.03 13.03 17.38 0 483.95 365.15 52203 +1972 129 15.89 9.89 14.24 0.47 404.48 281.19 52365 +1972 130 14.38 8.38 12.73 0.41 370.41 284.6 52524 +1972 131 17.44 11.44 15.79 0.59 442.19 279.21 52681 +1972 132 20.77 14.77 19.12 0 533.45 362.62 52836 +1972 133 18.37 12.37 16.72 0.01 466.23 278.3 52989 +1972 134 17.76 11.76 16.11 0.16 450.34 280.18 53138 +1972 135 14.26 8.26 12.61 0.07 367.81 287.63 53286 +1972 136 17.76 11.76 16.11 0.03 450.34 281.18 53430 +1972 137 19.66 13.66 18.01 0.09 501.4 277.29 53572 +1972 138 19.89 13.89 18.24 0.03 507.9 277.17 53711 +1972 139 20.63 14.63 18.98 1.11 529.31 275.8 53848 +1972 140 18.04 12.04 16.39 1.65 457.57 282.4 53981 +1972 141 16.51 10.51 14.86 0.67 419.22 286.01 54111 +1972 142 12.59 6.59 10.94 0.77 333.23 293.56 54238 +1972 143 10.86 4.86 9.21 1 300.38 296.64 54362 +1972 144 16.48 10.48 14.83 0.21 418.5 287.21 54483 +1972 145 12.64 6.64 10.99 1.15 334.22 294.61 54600 +1972 146 13.88 7.88 12.23 0.62 359.69 292.8 54714 +1972 147 14.96 8.96 13.31 0 383.2 388.26 54824 +1972 148 17.68 11.68 16.03 0 448.29 381.25 54931 +1972 149 17.46 11.46 15.81 0.12 442.7 286.65 55034 +1972 150 16.03 10.03 14.38 0.02 407.77 289.9 55134 +1972 151 15.17 9.17 13.52 0.28 387.92 291.88 55229 +1972 152 20.19 14.19 18.54 0.35 516.49 280.82 55321 +1972 153 21.76 15.76 20.11 0.02 563.48 276.8 55409 +1972 154 22.99 16.99 21.34 0.01 602.79 273.47 55492 +1972 155 20.46 14.46 18.81 0 524.33 374.24 55572 +1972 156 18.02 12.02 16.37 0 457.05 382.46 55648 +1972 157 18.83 12.83 17.18 0 478.52 380.12 55719 +1972 158 19.24 13.24 17.59 0.35 489.71 284.24 55786 +1972 159 23.12 17.12 21.47 0 607.08 365.17 55849 +1972 160 21.24 15.24 19.59 0 547.53 372.55 55908 +1972 161 24.39 18.39 22.74 0.2 650.34 270.08 55962 +1972 162 24.81 18.81 23.16 1.68 665.2 268.74 56011 +1972 163 22.66 16.66 21.01 1.05 592.02 275.64 56056 +1972 164 20.78 14.78 19.13 1.32 533.75 280.93 56097 +1972 165 19.59 13.59 17.94 0 499.44 378.75 56133 +1972 166 23.79 17.79 22.14 0 629.58 363.14 56165 +1972 167 22.27 16.27 20.62 0.9 579.51 276.9 56192 +1972 168 22.16 16.16 20.51 0 576.02 369.69 56214 +1972 169 26.39 20.39 24.74 0 723.74 351.46 56231 +1972 170 21.87 15.87 20.22 0.03 566.91 278.1 56244 +1972 171 20.5 14.5 18.85 0 525.5 375.83 56252 +1972 172 24.75 18.75 23.1 0 663.06 359.09 56256 +1972 173 23.42 17.42 21.77 0 617.07 364.74 56255 +1972 174 24.22 18.22 22.57 0 644.4 361.3 56249 +1972 175 23.51 17.51 21.86 0.01 620.09 273.19 56238 +1972 176 22.48 16.48 20.83 0.37 586.22 276.27 56223 +1972 177 20.62 14.62 18.97 0 529.02 375.13 56203 +1972 178 16.89 10.89 15.24 0.84 428.48 290.2 56179 +1972 179 17.23 11.23 15.58 0 436.91 385.86 56150 +1972 180 19.11 13.11 17.46 0.03 486.14 285 56116 +1972 181 24.06 18.06 22.41 0.02 638.85 271.17 56078 +1972 182 27.52 21.52 25.87 1.33 768.23 258.94 56035 +1972 183 19.03 13.03 17.38 1.67 483.95 284.9 55987 +1972 184 15.97 9.97 14.32 3.92 406.36 291.51 55935 +1972 185 16.79 10.79 15.14 2.58 426.03 289.76 55879 +1972 186 13.64 7.64 11.99 0.47 354.63 295.61 55818 +1972 187 17.3 11.3 15.65 0.63 438.67 288.33 55753 +1972 188 16.39 10.39 14.74 0.8 416.33 290.05 55684 +1972 189 18.42 12.42 16.77 0.58 467.55 285.48 55611 +1972 190 16.27 10.27 14.62 1.23 413.46 289.87 55533 +1972 191 19.74 13.74 18.09 0.15 503.65 281.83 55451 +1972 192 24.12 18.12 22.47 0.15 640.93 269.24 55366 +1972 193 27.17 21.17 25.52 0 754.21 344.65 55276 +1972 194 26.71 20.71 25.06 0 736.11 346.71 55182 +1972 195 26.4 20.4 24.75 0 724.13 347.96 55085 +1972 196 26.61 20.61 24.96 0.05 732.23 259.92 54984 +1972 197 25.67 19.67 24.02 0 696.55 350.56 54879 +1972 198 24.18 18.18 22.53 0.23 643.01 267.55 54770 +1972 199 24.78 18.78 23.13 0.49 664.13 265.36 54658 +1972 200 24.14 18.14 22.49 0.46 641.62 267.13 54542 +1972 201 25.09 19.09 23.44 0.75 675.27 263.7 54423 +1972 202 22.13 16.13 20.48 0.38 575.07 272.39 54301 +1972 203 19.54 13.54 17.89 0.08 498.04 278.82 54176 +1972 204 19.99 13.99 18.34 0.16 510.75 277.32 54047 +1972 205 19.44 13.44 17.79 0.17 495.25 278.29 53915 +1972 206 21.57 15.57 19.92 0 557.61 363.19 53780 +1972 207 24.25 18.25 22.6 0.16 645.44 264.03 53643 +1972 208 24.2 18.2 22.55 0 643.7 351.61 53502 +1972 209 25.92 19.92 24.27 0.57 705.89 257.56 53359 +1972 210 25.98 19.98 24.33 0.7 708.15 256.91 53213 +1972 211 28.15 22.15 26.5 0.24 794.02 248.39 53064 +1972 212 30.26 24.26 28.61 0.47 885.79 239.18 52913 +1972 213 27.58 21.58 25.93 0 770.65 332.64 52760 +1972 214 23.99 17.99 22.34 0 636.44 348.26 52604 +1972 215 20.86 14.86 19.21 0.43 536.12 269.55 52445 +1972 216 18.93 12.93 17.28 0.32 481.23 273.51 52285 +1972 217 21 15 19.35 0 540.3 357.02 52122 +1972 218 20.16 14.16 18.51 0.21 515.63 269.28 51958 +1972 219 22.99 16.99 21.34 0 602.79 347.91 51791 +1972 220 25.54 19.54 23.89 0.64 691.73 252.34 51622 +1972 221 24.05 18.05 22.4 0 638.51 341.82 51451 +1972 222 20.5 14.5 18.85 0 525.5 353.9 51279 +1972 223 17.11 11.11 15.46 0.16 433.92 272.25 51105 +1972 224 18.62 12.62 16.97 0.21 472.87 268.21 50929 +1972 225 18.48 12.48 16.83 1.21 469.14 267.66 50751 +1972 226 17.16 11.16 15.51 0.08 435.17 269.59 50572 +1972 227 18.34 12.34 16.69 0.02 465.43 266.13 50392 +1972 228 24.53 18.53 22.88 0.39 655.26 249.08 50210 +1972 229 22.79 16.79 21.14 0.28 596.25 253.28 50026 +1972 230 19.88 13.88 18.23 0 507.62 346.43 49842 +1972 231 23.9 17.9 22.25 0 633.35 330.8 49656 +1972 232 25.53 19.53 23.88 0.65 691.36 242.1 49469 +1972 233 25.32 19.32 23.67 0.36 683.64 241.76 49280 +1972 234 19.71 13.71 18.06 3.27 502.81 255.99 49091 +1972 235 12.87 6.87 11.22 1.72 338.83 267.87 48900 +1972 236 15.88 9.88 14.23 0.2 404.24 261.69 48709 +1972 237 20.48 14.48 18.83 0 524.91 334.37 48516 +1972 238 18.49 12.49 16.84 0 469.41 338.69 48323 +1972 239 21.67 15.67 20.02 0 560.7 327.32 48128 +1972 240 22.02 16.02 20.37 0 571.61 324.41 47933 +1972 241 27.5 21.5 25.85 0 767.42 300.81 47737 +1972 242 27.44 21.44 25.79 0 765.01 299.48 47541 +1972 243 25.29 19.29 23.64 0 682.55 307.03 47343 +1972 244 18.94 12.94 17.29 0 481.5 326.99 47145 +1972 245 16.73 10.73 15.08 0 424.56 331.02 46947 +1972 246 18.54 12.54 16.89 0 470.74 324.31 46747 +1972 247 18.68 12.68 17.03 0 474.48 322.07 46547 +1972 248 19.77 13.77 18.12 0 504.5 317.05 46347 +1972 249 19.73 13.73 18.08 0.07 503.37 236.34 46146 +1972 250 18.01 12.01 16.36 0 456.79 317.93 45945 +1972 251 16.62 10.62 14.97 0.57 421.88 239.48 45743 +1972 252 14.8 8.8 13.15 0.36 379.63 240.94 45541 +1972 253 14.15 8.15 12.5 0.15 365.44 240.35 45339 +1972 254 14.21 8.21 12.56 0.05 366.73 238.63 45136 +1972 255 15.55 9.55 13.9 0 396.58 313.03 44933 +1972 256 14.26 8.26 12.61 0 367.81 313.47 44730 +1972 257 12.18 6.18 10.53 0 325.18 315.23 44527 +1972 258 11.3 5.3 9.65 0 308.46 314.35 44323 +1972 259 18.31 12.31 16.66 0 464.64 297.29 44119 +1972 260 17.13 11.13 15.48 0 434.42 297.81 43915 +1972 261 20.71 14.71 19.06 0 531.67 286.05 43711 +1972 262 17.55 11.55 15.9 0 444.98 292.01 43507 +1972 263 14.69 8.69 13.04 0.16 377.2 221.86 43303 +1972 264 14.05 8.05 12.4 0.82 363.3 220.85 43099 +1972 265 13.01 7.01 11.36 0.14 341.66 220.49 42894 +1972 266 16.45 10.45 14.8 0 417.77 284.7 42690 +1972 267 18.16 12.16 16.51 0 460.7 278.14 42486 +1972 268 17.3 11.3 15.65 0 438.67 277.61 42282 +1972 269 16.68 10.68 15.03 0.45 423.34 207.36 42078 +1972 270 12.61 6.61 10.96 0 333.63 281.64 41875 +1972 271 13.59 7.59 11.94 0 353.59 277.3 41671 +1972 272 13.43 7.43 11.78 0 350.26 274.83 41468 +1972 273 14.75 8.75 13.1 0 378.52 269.9 41265 +1972 274 14.4 8.4 12.75 0 370.85 267.88 41062 +1972 275 16.14 10.14 14.49 0 410.37 261.79 40860 +1972 276 16.95 10.95 15.3 0 429.96 257.47 40658 +1972 277 16.02 10.02 14.37 0 407.53 256.72 40456 +1972 278 15.64 9.64 13.99 0.53 398.66 190.96 40255 +1972 279 14.18 8.18 12.53 0.03 366.09 190.86 40054 +1972 280 10.37 4.37 8.72 0.16 291.59 193.26 39854 +1972 281 10.87 4.87 9.22 0.1 300.56 190.68 39654 +1972 282 8.82 2.82 7.17 0.38 265.24 190.6 39455 +1972 283 8.3 2.3 6.65 0.03 256.87 188.91 39256 +1972 284 10.87 4.87 9.22 0.36 300.56 184.18 39058 +1972 285 9.39 3.39 7.74 0.01 274.68 183.61 38861 +1972 286 10.51 4.51 8.86 0 294.08 240.6 38664 +1972 287 7.77 1.77 6.12 0.06 248.57 180.68 38468 +1972 288 6.28 0.28 4.63 0 226.47 239.61 38273 +1972 289 6.73 0.73 5.08 0 232.96 236.47 38079 +1972 290 8.25 2.25 6.6 0 256.08 231.96 37885 +1972 291 9.18 3.18 7.53 0 271.17 228.18 37693 +1972 292 12.14 6.14 10.49 0 324.4 221.74 37501 +1972 293 11.4 5.4 9.75 0 310.32 220 37311 +1972 294 10.07 4.07 8.42 0 286.32 218.76 37121 +1972 295 10.96 4.96 9.31 0 302.2 214.83 36933 +1972 296 10.06 4.06 8.41 0 286.15 213.32 36745 +1972 297 10.05 4.05 8.4 0 285.98 210.59 36560 +1972 298 8.29 2.29 6.64 0 256.71 209.88 36375 +1972 299 11.78 5.78 10.13 0.02 317.49 152.34 36191 +1972 300 11.5 5.5 9.85 0 312.19 200.81 36009 +1972 301 15.33 9.33 13.68 0 391.55 193.06 35829 +1972 302 15.29 9.29 13.64 0.01 390.64 142.93 35650 +1972 303 15.64 9.64 13.99 0.36 398.66 140.64 35472 +1972 304 17.87 11.87 16.22 0.25 453.17 136.13 35296 +1972 305 12.13 6.13 10.48 0.46 324.21 140.41 35122 +1972 306 8.79 2.79 7.14 0 264.75 188.63 34950 +1972 307 7.38 1.38 5.73 0 242.61 187.43 34779 +1972 308 10.62 4.62 8.97 0 296.05 181.64 34610 +1972 309 9.2 3.2 7.55 0 271.5 180.8 34444 +1972 310 10.67 4.67 9.02 0.12 296.95 132.65 34279 +1972 311 11.21 5.21 9.56 0.13 306.79 130.59 34116 +1972 312 14.39 8.39 12.74 0 370.63 167.72 33956 +1972 313 14.89 8.89 13.24 0.12 381.63 123.75 33797 +1972 314 11.23 5.23 9.58 0 307.16 167.47 33641 +1972 315 10.76 4.76 9.11 0.02 298.57 124.09 33488 +1972 316 7.89 1.89 6.24 0.66 250.43 124.47 33337 +1972 317 4.62 -1.38 2.97 0.13 203.85 124.68 33188 +1972 318 6.06 0.06 4.41 0 223.35 162.87 33042 +1972 319 3.77 -2.23 2.12 0.44 193.04 122.05 32899 +1972 320 4.31 -1.69 2.66 0.48 199.85 120.37 32758 +1972 321 8.64 2.64 6.99 0 262.32 155.15 32620 +1972 322 7.47 1.47 5.82 0.23 243.98 115.72 32486 +1972 323 8.96 2.96 7.31 1.24 267.53 113.6 32354 +1972 324 9.65 3.65 8 0.21 279.08 111.62 32225 +1972 325 6.41 0.41 4.76 0.42 228.32 112.28 32100 +1972 326 1.67 -4.33 0.02 0.6 168.43 113.36 31977 +1972 327 2.8 -3.2 1.15 0.06 181.32 111.51 31858 +1972 328 7.62 1.62 5.97 0.04 246.26 107.66 31743 +1972 329 6.35 0.35 4.7 0.09 227.47 107.24 31631 +1972 330 8.79 2.79 7.14 1.31 264.75 104.79 31522 +1972 331 5.32 -0.68 3.67 0.73 213.14 105.68 31417 +1972 332 5.73 -0.27 4.08 0.46 218.75 104.25 31316 +1972 333 5.67 -0.33 4.02 0.03 217.92 103.46 31218 +1972 334 5.77 -0.23 4.12 0 219.3 136.79 31125 +1972 335 0 -6 -1.65 0 150.84 138.71 31035 +1972 336 -2.39 -8.39 -4.04 0 128.44 138.58 30949 +1972 337 0.26 -5.74 -1.39 0 153.47 135.83 30867 +1972 338 -2.43 -8.43 -4.08 0 128.09 135.96 30790 +1972 339 -0.75 -6.75 -2.4 0 143.48 134.5 30716 +1972 340 -1.79 -7.79 -3.44 0 133.78 134.17 30647 +1972 341 1.47 -4.53 -0.18 0 166.24 131.86 30582 +1972 342 4.94 -1.06 3.29 0 208.05 129.26 30521 +1972 343 5.09 -0.91 3.44 0 210.05 128.35 30465 +1972 344 6.65 0.65 5 0 231.79 126.25 30413 +1972 345 5.97 -0.03 4.32 0 222.09 126.26 30366 +1972 346 5.81 -0.19 4.16 0 219.85 125.81 30323 +1972 347 5.68 -0.32 4.03 0 218.05 125.3 30284 +1972 348 0.66 -5.34 -0.99 0 157.6 127.55 30251 +1972 349 -1.85 -7.85 -3.5 0 133.23 128.17 30221 +1972 350 1.34 -4.66 -0.31 0 164.82 126.52 30197 +1972 351 0.86 -5.14 -0.79 0 159.69 126.52 30177 +1972 352 1.11 -4.89 -0.54 0 162.35 126.31 30162 +1972 353 4.03 -1.97 2.38 0 196.29 124.81 30151 +1972 354 3.1 -2.9 1.45 0 184.88 125.26 30145 +1972 355 3.02 -2.98 1.37 0 183.92 125.3 30144 +1972 356 1.49 -4.51 -0.16 0 166.46 126.07 30147 +1972 357 1.41 -4.59 -0.24 0 165.58 126.16 30156 +1972 358 1.58 -4.42 -0.07 0 167.44 126.17 30169 +1972 359 4.63 -1.37 2.98 0 203.98 124.73 30186 +1972 360 6.97 0.97 5.32 0.07 236.48 92.75 30208 +1972 361 7.89 1.89 6.24 0.65 250.43 92.53 30235 +1972 362 6.08 0.08 4.43 0 223.63 125 30267 +1972 363 10.94 4.94 9.29 0.01 301.83 91.51 30303 +1972 364 6.19 0.19 4.54 0 225.19 125.9 30343 +1972 365 3.25 -2.75 1.6 0.2 186.68 96.12 30388 +1973 1 5.8 -0.2 4.15 0 219.72 127.6 30438 +1973 2 -0.91 -6.91 -2.56 0 141.95 131.71 30492 +1973 3 -3.42 -9.42 -5.07 0 119.71 133.58 30551 +1973 4 -0.82 -6.82 -2.47 0 142.8 133.54 30614 +1973 5 1.88 -4.12 0.23 0 170.77 133 30681 +1973 6 -1.72 -7.72 -3.37 0.05 134.41 144.67 30752 +1973 7 -0.32 -6.32 -1.97 0 147.66 178.67 30828 +1973 8 1.28 -4.72 -0.37 0 164.17 136.47 30907 +1973 9 4.48 -1.52 2.83 0 202.04 136.03 30991 +1973 10 0.65 -5.35 -1 0.77 157.49 104.5 31079 +1973 11 0.65 -5.35 -1 0.14 157.49 105.25 31171 +1973 12 2.89 -3.11 1.24 0.18 182.38 105.17 31266 +1973 13 3.74 -2.26 2.09 0 192.67 141.38 31366 +1973 14 3.18 -2.82 1.53 0.09 185.83 107.38 31469 +1973 15 2 -4 0.35 0.18 172.11 108.94 31575 +1973 16 -2.01 -8.01 -3.66 0.39 131.8 154.14 31686 +1973 17 1.73 -4.27 0.08 0 169.1 190.85 31800 +1973 18 4.41 -1.59 2.76 1.09 201.13 153.32 31917 +1973 19 0.64 -5.36 -1.01 0 157.39 194.3 32038 +1973 20 -1.5 -7.5 -3.15 0 136.42 196.72 32161 +1973 21 -6.43 -12.43 -8.08 0 97.09 200.38 32289 +1973 22 -1.61 -7.61 -3.26 0.35 135.41 161.47 32419 +1973 23 -1.42 -7.42 -3.07 0 137.16 202.82 32552 +1973 24 0.8 -5.2 -0.85 0.1 159.06 163.08 32688 +1973 25 -0.1 -6.1 -1.75 0.05 149.84 164.82 32827 +1973 26 3.17 -2.83 1.52 0 185.71 205.47 32969 +1973 27 2.41 -3.59 0.76 0 176.78 207.49 33114 +1973 28 7.64 1.64 5.99 0 246.57 165.45 33261 +1973 29 11.39 5.39 9.74 0 310.13 164.26 33411 +1973 30 12.95 6.95 11.3 0 340.44 164.69 33564 +1973 31 10.89 4.89 9.24 0 300.92 169.29 33718 +1973 32 11.12 5.12 9.47 0 305.13 171.11 33875 +1973 33 9.03 3.03 7.38 0.01 268.69 131.85 34035 +1973 34 8.63 2.63 6.98 0 262.15 178.36 34196 +1973 35 4.8 -1.2 3.15 0.01 206.2 137.76 34360 +1973 36 1.19 -4.81 -0.46 0.45 163.21 141.44 34526 +1973 37 1.86 -4.14 0.21 0.1 170.54 142.97 34694 +1973 38 1.87 -4.13 0.22 0 170.65 193.38 34863 +1973 39 3.83 -2.17 2.18 0 193.79 194.68 35035 +1973 40 5.88 -0.12 4.23 0 220.83 195.71 35208 +1973 41 5.28 -0.72 3.63 0 212.6 198.81 35383 +1973 42 4.71 -1.29 3.06 0 205.02 201.82 35560 +1973 43 7.87 1.87 6.22 0.82 250.12 151.31 35738 +1973 44 10.15 4.15 8.5 0 287.72 201.89 35918 +1973 45 9.77 3.77 8.12 0.02 281.14 153.67 36099 +1973 46 8.83 2.83 7.18 0 265.4 208.57 36282 +1973 47 4.59 -1.41 2.94 0 203.46 215.32 36466 +1973 48 3.57 -2.43 1.92 0 190.57 218.94 36652 +1973 49 0.79 -5.21 -0.86 0 158.96 223.7 36838 +1973 50 -0.06 -6.06 -1.71 0 150.24 226.94 37026 +1973 51 2.03 -3.97 0.38 0 172.45 228.55 37215 +1973 52 1.42 -4.58 -0.23 0.2 165.69 173.88 37405 +1973 53 3.8 -2.2 2.15 0.16 193.42 174.77 37596 +1973 54 0.67 -5.33 -0.98 0.01 157.7 178.59 37788 +1973 55 3.35 -2.65 1.7 0 187.89 239.17 37981 +1973 56 3.97 -2.03 2.32 0 195.54 241.37 38175 +1973 57 5.69 -0.31 4.04 0 218.19 242.71 38370 +1973 58 5.08 -0.92 3.43 0 209.91 246.22 38565 +1973 59 6.76 0.76 5.11 0 233.39 247.28 38761 +1973 60 6.82 0.82 5.17 0.02 234.27 187.57 38958 +1973 61 7.21 1.21 5.56 0 240.06 252.6 39156 +1973 62 8.04 2.04 6.39 0 252.77 254.45 39355 +1973 63 10.42 4.42 8.77 0.07 292.48 190.83 39553 +1973 64 12.65 6.65 11 0 334.42 254.05 39753 +1973 65 12.35 6.35 10.7 0 328.5 257.34 39953 +1973 66 11.71 5.71 10.06 0 316.16 261.01 40154 +1973 67 11.49 5.49 9.84 0 312.01 264.19 40355 +1973 68 11.8 5.8 10.15 0 317.87 266.55 40556 +1973 69 10.24 4.24 8.59 0 289.3 271.43 40758 +1973 70 7 1 5.35 0 236.93 278.4 40960 +1973 71 7.88 1.88 6.23 0.75 250.27 210.2 41163 +1973 72 5.22 -0.78 3.57 0 211.79 286.12 41366 +1973 73 7.26 1.26 5.61 0.1 240.81 214.88 41569 +1973 74 3.9 -2.1 2.25 0 194.66 292.92 41772 +1973 75 2.35 -3.65 0.7 0 176.09 297.12 41976 +1973 76 0.89 -5.11 -0.76 0 160.01 301.04 42179 +1973 77 3.22 -2.78 1.57 0 186.32 301.64 42383 +1973 78 1.77 -4.23 0.12 0 169.54 305.67 42587 +1973 79 4.16 -1.84 2.51 0 197.94 306.18 42791 +1973 80 4.51 -1.49 2.86 0 202.42 308.38 42996 +1973 81 11.2 5.2 9.55 0 306.61 302.12 43200 +1973 82 11.8 5.8 10.15 0 317.87 303.75 43404 +1973 83 12.82 6.82 11.17 0.28 337.82 228.32 43608 +1973 84 10.58 4.58 8.93 0.01 295.33 233.06 43812 +1973 85 11.59 5.59 9.94 0 313.89 311.56 44016 +1973 86 9.31 3.31 7.66 0 273.34 317.59 44220 +1973 87 8.25 2.25 6.6 0.01 256.08 241.24 44424 +1973 88 13.34 7.34 11.69 0.08 348.4 236.69 44627 +1973 89 12.09 6.09 10.44 0.22 323.43 240.12 44831 +1973 90 10.06 4.06 8.41 0 286.15 325.96 45034 +1973 91 12.57 6.57 10.92 0 332.83 323.86 45237 +1973 92 11.22 5.22 9.57 0 306.98 328.52 45439 +1973 93 12.17 6.17 10.52 0.2 324.99 246.76 45642 +1973 94 13 7 11.35 0.13 341.45 247.19 45843 +1973 95 9.12 3.12 7.47 0.43 270.17 253.85 46045 +1973 96 11.66 5.66 10.01 0.51 315.21 252.25 46246 +1973 97 14.14 8.14 12.49 0 365.23 333.5 46446 +1973 98 13.09 7.09 11.44 0.02 343.28 253.2 46647 +1973 99 11.88 5.88 10.23 0.08 319.39 256.45 46846 +1973 100 11.22 5.22 9.57 0.05 306.98 258.82 47045 +1973 101 10.38 4.38 8.73 0.04 291.77 261.38 47243 +1973 102 13.11 7.11 11.46 0 343.69 345.3 47441 +1973 103 13.04 7.04 11.39 0 342.26 347.27 47638 +1973 104 10.4 4.4 8.75 0.46 292.12 265.55 47834 +1973 105 11.52 5.52 9.87 0.06 312.57 265.38 48030 +1973 106 14.6 8.6 12.95 0 375.22 349.14 48225 +1973 107 13.52 7.52 11.87 0.87 352.13 264.88 48419 +1973 108 11.89 5.89 10.24 1.97 319.59 268.66 48612 +1973 109 10.65 4.65 9 2.07 296.59 271.61 48804 +1973 110 9.43 3.43 7.78 1.6 275.36 274.27 48995 +1973 111 10.77 4.77 9.12 0.03 298.75 273.69 49185 +1973 112 7.18 1.18 5.53 0 239.61 372.33 49374 +1973 113 5.42 -0.58 3.77 0.32 214.49 282.11 49561 +1973 114 7.82 1.82 6.17 0.47 249.34 280.7 49748 +1973 115 11.23 5.23 9.58 0.27 307.16 277.42 49933 +1973 116 6.36 0.36 4.71 0 227.61 379.12 50117 +1973 117 9.83 3.83 8.18 0 282.17 375.01 50300 +1973 118 8.62 2.62 6.97 0.04 261.99 283.79 50481 +1973 119 11.43 5.43 9.78 0.01 310.88 280.95 50661 +1973 120 14.91 8.91 13.26 0.38 382.08 276.18 50840 +1973 121 21.44 15.44 19.79 0.13 553.62 262.67 51016 +1973 122 19.55 13.55 17.9 0 498.32 357.69 51191 +1973 123 17.29 11.29 15.64 0 438.42 365.41 51365 +1973 124 14.51 8.51 12.86 0 373.25 373.62 51536 +1973 125 18.12 12.12 16.47 0 459.66 365.07 51706 +1973 126 22.7 16.7 21.05 0 593.32 350.67 51874 +1973 127 22.21 16.21 20.56 0.66 577.6 265.02 52039 +1973 128 18.83 12.83 17.18 0.3 478.52 274.32 52203 +1973 129 18.11 12.11 16.46 0.04 459.4 276.58 52365 +1973 130 19.62 13.62 17.97 0 500.28 364.89 52524 +1973 131 16.89 10.89 15.24 0 428.48 373.83 52681 +1973 132 20.07 14.07 18.42 0 513.04 364.99 52836 +1973 133 20.26 14.26 18.61 0 518.51 365.05 52989 +1973 134 21.24 15.24 19.59 0 547.53 362.34 53138 +1973 135 19.81 13.81 18.16 0 505.63 367.92 53286 +1973 136 20.48 14.48 18.83 0 524.91 366.29 53430 +1973 137 16.87 10.87 15.22 0 427.99 378.14 53572 +1973 138 13.47 7.47 11.82 0 351.09 387.31 53711 +1973 139 16.4 10.4 14.75 0 416.57 380.72 53848 +1973 140 17.92 11.92 16.27 0 454.46 376.89 53981 +1973 141 19.13 13.13 17.48 0 486.69 373.61 54111 +1973 142 18.09 12.09 16.44 0 458.88 377.32 54238 +1973 143 15.28 9.28 13.63 0.02 390.41 289.22 54362 +1973 144 17.14 11.14 15.49 0 434.67 381.1 54483 +1973 145 16.19 10.19 14.54 0 411.56 384.2 54600 +1973 146 16.24 10.24 14.59 0 412.74 384.45 54714 +1973 147 19.97 13.97 18.32 0 510.18 373.66 54824 +1973 148 13.16 7.16 11.51 0 344.71 392.93 54931 +1973 149 19.7 13.7 18.05 0.11 502.53 281.44 55034 +1973 150 17.74 11.74 16.09 0.13 449.83 286.29 55134 +1973 151 15.99 9.99 14.34 0 406.83 387.03 55229 +1973 152 18.82 12.82 17.17 0.87 478.25 284.19 55321 +1973 153 16.41 10.41 14.76 0.18 416.81 289.69 55409 +1973 154 20.59 14.59 18.94 0 528.14 373.6 55492 +1973 155 18 12 16.35 0 456.53 382.19 55572 +1973 156 19.81 13.81 18.16 0 505.63 376.77 55648 +1973 157 20.7 14.7 19.05 0 531.38 373.88 55719 +1973 158 24.98 18.98 23.33 0 671.3 357.04 55786 +1973 159 24.38 18.38 22.73 0.71 649.98 269.93 55849 +1973 160 24.63 18.63 22.98 0.11 658.8 269.25 55908 +1973 161 25.35 19.35 23.7 0.1 684.74 266.88 55962 +1973 162 25.48 19.48 23.83 1.24 689.52 266.48 56011 +1973 163 24.17 18.17 22.52 0.28 642.66 270.99 56056 +1973 164 23.15 17.15 21.5 0.01 608.07 274.2 56097 +1973 165 23.64 17.64 21.99 0 624.48 363.69 56133 +1973 166 21.07 15.07 19.42 0.38 542.4 280.29 56165 +1973 167 20.64 14.64 18.99 0.83 529.61 281.39 56192 +1973 168 19.88 13.88 18.23 0.01 507.62 283.41 56214 +1973 169 17.21 11.21 15.56 0 436.41 386.22 56231 +1973 170 21.13 15.13 19.48 0.02 544.21 280.15 56244 +1973 171 25.48 19.48 23.83 0.51 689.52 266.86 56252 +1973 172 27.24 21.24 25.59 0.15 757 260.48 56256 +1973 173 22.76 16.76 21.11 0 595.27 367.4 56255 +1973 174 22.31 16.31 20.66 0.81 580.78 276.81 56249 +1973 175 21.81 15.81 20.16 0.76 565.04 278.21 56238 +1973 176 21.28 15.28 19.63 0 548.75 372.87 56223 +1973 177 15.36 9.36 13.71 1.98 392.23 293.29 56203 +1973 178 14.98 8.98 13.33 0.13 383.64 294.04 56179 +1973 179 14.13 8.13 12.48 1.31 365.02 295.53 56150 +1973 180 14.75 8.75 13.1 0 378.52 392.4 56116 +1973 181 14.4 8.4 12.75 0 370.85 393.19 56078 +1973 182 20.91 14.91 19.26 0 537.61 373.69 56035 +1973 183 21.99 15.99 20.34 0 570.66 369.55 55987 +1973 184 22.1 16.1 20.45 0 574.13 368.98 55935 +1973 185 17.58 11.58 15.93 0.05 445.74 288.05 55879 +1973 186 21.15 15.15 19.5 0 544.81 372.16 55818 +1973 187 22.98 16.98 21.33 0 602.46 365.03 55753 +1973 188 27.92 21.92 26.27 0.31 784.52 256.59 55684 +1973 189 24.7 18.7 23.05 0.26 661.28 268.05 55611 +1973 190 26.41 20.41 24.76 0.17 724.51 261.88 55533 +1973 191 20.59 14.59 18.94 0.02 528.14 279.66 55451 +1973 192 21.97 15.97 20.32 0.61 570.04 275.69 55366 +1973 193 21.9 15.9 20.25 0.61 567.85 275.68 55276 +1973 194 22.07 16.07 20.42 0.19 573.18 275.04 55182 +1973 195 21.32 15.32 19.67 0.48 549.96 276.92 55085 +1973 196 21.31 15.31 19.66 0.43 549.66 276.64 54984 +1973 197 20.96 14.96 19.31 0.39 539.11 277.24 54879 +1973 198 22.71 16.71 21.06 0 593.64 362.72 54770 +1973 199 23.04 17.04 21.39 0 604.44 361.07 54658 +1973 200 26.97 20.97 25.32 0 746.3 343.25 54542 +1973 201 23.79 17.79 22.14 0 629.58 357.18 54423 +1973 202 22.81 16.81 21.16 0.6 596.9 270.43 54301 +1973 203 20.18 14.18 18.53 0.3 516.2 277.23 54176 +1973 204 23.08 17.08 21.43 1.67 605.76 268.89 54047 +1973 205 22 16 20.35 0 570.98 362.16 53915 +1973 206 22.2 16.2 20.55 0 577.29 360.85 53780 +1973 207 23.03 17.03 21.38 0 604.11 357.01 53643 +1973 208 21.02 15.02 19.37 0.94 540.9 272.89 53502 +1973 209 21.34 15.34 19.69 0.29 550.57 271.55 53359 +1973 210 23.3 17.3 21.65 0.11 613.06 265.54 53213 +1973 211 24.94 18.94 23.29 0.41 669.86 259.85 53064 +1973 212 26.09 20.09 24.44 0 712.3 340.54 52913 +1973 213 25.65 19.65 24 0.2 695.8 256.37 52760 +1973 214 21.82 15.82 20.17 0.02 565.35 267.5 52604 +1973 215 17.44 11.44 15.79 0.53 442.19 277.59 52445 +1973 216 20.49 14.49 18.84 0.1 525.2 269.74 52285 +1973 217 24.49 18.49 22.84 0 653.85 343.68 52122 +1973 218 26.2 20.2 24.55 0 716.48 335.37 51958 +1973 219 23.82 17.82 22.17 0 630.61 344.63 51791 +1973 220 27.78 21.78 26.13 0.2 778.79 244.43 51622 +1973 221 24.4 18.4 22.75 0 650.69 340.38 51451 +1973 222 24.4 18.4 22.75 0 650.69 339.37 51279 +1973 223 22.96 16.96 21.31 0.03 601.8 257.99 51105 +1973 224 23.25 17.25 21.6 0 611.39 341.84 50929 +1973 225 23.05 17.05 21.4 0 604.77 341.49 50751 +1973 226 24.5 18.5 22.85 0 654.2 334.63 50572 +1973 227 22.35 16.35 20.7 0.02 582.06 256.3 50392 +1973 228 24.04 18.04 22.39 0 638.16 334.09 50210 +1973 229 27.05 21.05 25.4 0.66 749.45 239.88 50026 +1973 230 23.49 17.49 21.84 0.64 619.42 250.36 49842 +1973 231 22.78 16.78 21.13 0 595.92 335.07 49656 +1973 232 23.17 17.17 21.52 0 608.73 332.3 49469 +1973 233 22.2 16.2 20.55 0.15 577.29 250.85 49280 +1973 234 24.61 18.61 22.96 0 658.09 323.93 49091 +1973 235 22.93 16.93 21.28 0 600.82 328.98 48900 +1973 236 25.54 19.54 23.89 0 691.73 317.29 48709 +1973 237 26.87 20.87 25.22 0 742.37 309.91 48516 +1973 238 27.07 21.07 25.42 0 750.24 307.43 48323 +1973 239 20.74 14.74 19.09 0 532.56 330.39 48128 +1973 240 20.5 14.5 18.85 0.04 525.5 247.06 47933 +1973 241 20.17 14.17 18.52 0.84 515.92 246.55 47737 +1973 242 17.91 11.91 16.26 0 454.2 333.53 47541 +1973 243 14.39 8.39 12.74 1.4 370.63 255.15 47343 +1973 244 14.1 8.1 12.45 0.02 364.37 254.22 47145 +1973 245 18.66 12.66 17.01 0.08 473.94 244.45 46947 +1973 246 16.67 10.67 15.02 0 423.1 329.18 46747 +1973 247 20.52 14.52 18.87 0 526.08 316.72 46547 +1973 248 21.38 15.38 19.73 0 551.79 312.12 46347 +1973 249 26.22 20.22 24.57 0 717.24 292.39 46146 +1973 250 23.59 17.59 21.94 0 622.79 300.73 45945 +1973 251 24.17 18.17 22.52 0.02 642.66 222.45 45743 +1973 252 23.65 17.65 22 0 624.82 296.43 45541 +1973 253 24.85 18.85 23.2 0 666.63 290 45339 +1973 254 23.94 17.94 22.29 0 634.72 291.34 45136 +1973 255 20.63 14.63 18.98 0.67 529.31 224.98 44933 +1973 256 21.57 15.57 19.92 1.83 557.61 221.18 44730 +1973 257 22.77 16.77 21.12 0.09 595.59 216.73 44527 +1973 258 18.58 12.58 16.93 0 471.8 299 44323 +1973 259 13.63 7.63 11.98 0 354.42 307.68 44119 +1973 260 16.66 10.66 15.01 0 422.85 298.9 43915 +1973 261 15.54 9.54 13.89 0 396.35 298.92 43711 +1973 262 13.72 7.72 12.07 0.08 356.31 225.14 43507 +1973 263 14.79 8.79 13.14 0 379.41 295.61 43303 +1973 264 12.53 6.53 10.88 0 332.04 297.25 43099 +1973 265 16.12 10.12 14.47 0.28 409.89 215.91 42894 +1973 266 20.64 14.64 18.99 1.19 529.61 205.77 42690 +1973 267 19.29 13.29 17.64 0.18 491.09 206.51 42486 +1973 268 18.94 12.94 17.29 1.58 481.5 205.29 42282 +1973 269 22.23 16.23 20.58 2.19 578.24 196.74 42078 +1973 270 17.75 11.75 16.1 1.87 450.08 203.62 41875 +1973 271 17.2 11.2 15.55 0 436.16 270.14 41671 +1973 272 18.41 12.41 16.76 0.24 467.28 198.53 41468 +1973 273 16.4 10.4 14.75 0.61 416.57 199.99 41265 +1973 274 11.33 5.33 9.68 0 309.02 272.99 41062 +1973 275 8.56 2.56 6.91 0 261.02 274.01 40860 +1973 276 9.53 3.53 7.88 0 277.05 269.99 40658 +1973 277 10.05 4.05 8.4 0.59 285.98 199.93 40456 +1973 278 7.24 1.24 5.59 0 240.5 267.16 40255 +1973 279 7.35 1.35 5.7 0 242.16 264.15 40054 +1973 280 6.58 0.58 4.93 0 230.78 262.28 39854 +1973 281 10.76 4.76 9.11 0 298.57 254.39 39654 +1973 282 11.97 5.97 10.32 0 321.12 249.9 39455 +1973 283 17.35 11.35 15.7 0 439.92 237.74 39256 +1973 284 13.65 7.65 12 0.05 354.84 181.09 39058 +1973 285 15.45 9.45 13.8 0.04 394.29 176.84 38861 +1973 286 11.35 5.35 9.7 0 309.39 239.47 38664 +1973 287 11.86 5.86 10.21 0 319.01 235.81 38468 +1973 288 12.89 6.89 11.24 0.01 339.23 173.65 38273 +1973 289 12.31 6.31 10.66 1.19 327.71 172.31 38079 +1973 290 12.14 6.14 10.49 0.6 324.4 170.35 37885 +1973 291 9.46 3.46 7.81 0 275.86 227.85 37693 +1973 292 9.36 3.36 7.71 0.03 274.18 168.94 37501 +1973 293 10.97 4.97 9.32 1.1 302.38 165.42 37311 +1973 294 11.56 5.56 9.91 0.02 313.32 162.68 37121 +1973 295 10.18 4.18 8.53 0 288.25 215.78 36933 +1973 296 10.5 4.5 8.85 0.02 293.9 159.6 36745 +1973 297 14.95 8.95 13.3 0 382.97 204 36560 +1973 298 15.38 9.38 13.73 0.31 392.69 150.58 36375 +1973 299 14.72 8.72 13.07 0 377.86 199.06 36191 +1973 300 14.09 8.09 12.44 0 364.16 197.37 36009 +1973 301 14.95 8.95 13.3 0 382.97 193.63 35829 +1973 302 14.4 8.4 12.75 0 370.85 191.88 35650 +1973 303 15.42 9.42 13.77 0.12 393.6 140.89 35472 +1973 304 15.93 9.93 14.28 0 405.42 184.68 35296 +1973 305 9.05 3.05 7.4 0.43 269.02 142.97 35122 +1973 306 8.39 2.39 6.74 1.05 258.3 141.77 34950 +1973 307 6.26 0.26 4.61 0.08 226.18 141.29 34779 +1973 308 3.85 -2.15 2.2 0.32 194.04 140.7 34610 +1973 309 4.76 -1.24 3.11 0.5 205.68 138.44 34444 +1973 310 3.88 -2.12 2.23 0 194.41 182.74 34279 +1973 311 6.08 0.08 4.43 0 223.63 178.91 34116 +1973 312 4.79 -1.21 3.14 0 206.07 177.22 33956 +1973 313 5.11 -0.89 3.46 0.06 210.31 131.13 33797 +1973 314 3.4 -2.6 1.75 0 188.49 174.04 33641 +1973 315 5.74 -0.26 4.09 0 218.88 169.86 33488 +1973 316 12.24 6.24 10.59 0 326.35 161.72 33337 +1973 317 10.16 4.16 8.51 0 287.9 161.71 33188 +1973 318 8.05 2.05 6.4 0 252.93 161.3 33042 +1973 319 5.14 -0.86 3.49 0 210.72 161.82 32899 +1973 320 6.18 0.18 4.53 0 225.05 159.2 32758 +1973 321 -0.07 -6.07 -1.72 0 150.14 160.83 32620 +1973 322 -3.34 -9.34 -4.99 0 120.37 160.37 32486 +1973 323 -1.63 -7.63 -3.28 0 135.23 158.02 32354 +1973 324 4.98 -1.02 3.33 1.25 208.58 114.31 32225 +1973 325 5.62 -0.38 3.97 0 217.23 150.25 32100 +1973 326 5.95 -0.05 4.3 0.05 221.81 111.43 31977 +1973 327 6.46 0.46 4.81 0.05 229.04 109.77 31858 +1973 328 10.44 4.44 8.79 0.04 292.83 105.91 31743 +1973 329 10.32 4.32 8.67 0 290.71 139.85 31631 +1973 330 12.09 6.09 10.44 0 323.43 136.77 31522 +1973 331 13.51 7.51 11.86 0 351.92 134.04 31417 +1973 332 8.69 2.69 7.04 0.08 263.12 102.65 31316 +1973 333 4.64 -1.36 2.99 0 204.11 138.6 31218 +1973 334 5.43 -0.57 3.78 0.01 214.63 102.75 31125 +1973 335 4.96 -1.04 3.31 0 208.32 136.12 31035 +1973 336 2.4 -3.6 0.75 0 176.66 136.48 30949 +1973 337 6.03 0.03 4.38 0 222.93 132.72 30867 +1973 338 10.26 4.26 8.61 0 289.65 128.66 30790 +1973 339 7.33 1.33 5.68 0 241.86 130.13 30716 +1973 340 1.68 -4.32 0.03 0.66 168.54 99.51 30647 +1973 341 -3.06 -9.06 -4.71 0.1 122.7 143.75 30582 +1973 342 -3.92 -9.92 -5.57 0 115.67 176.77 30521 +1973 343 -3.6 -9.6 -5.25 0.03 118.24 142.94 30465 +1973 344 -2.65 -8.65 -4.3 0.09 126.19 142.19 30413 +1973 345 -3.03 -9.03 -4.68 0.04 122.96 142.16 30366 +1973 346 -0.01 -6.01 -1.66 0 150.74 173.14 30323 +1973 347 3.72 -2.28 2.07 0 192.42 170.33 30284 +1973 348 2.5 -3.5 0.85 0 177.82 126.69 30251 +1973 349 3.09 -2.91 1.44 0 184.76 126.01 30221 +1973 350 4.81 -1.19 3.16 0 206.34 124.75 30197 +1973 351 -0.26 -6.26 -1.91 0.13 148.25 139.4 30177 +1973 352 0.94 -5.06 -0.71 0.13 160.54 138.84 30162 +1973 353 3.31 -2.69 1.66 0 187.4 125.19 30151 +1973 354 2.87 -3.13 1.22 0 182.14 125.38 30145 +1973 355 3.56 -2.44 1.91 0 190.45 125.02 30144 +1973 356 6.46 0.46 4.81 0 229.04 123.37 30147 +1973 357 9.18 3.18 7.53 0 271.17 121.54 30156 +1973 358 7.22 1.22 5.57 0 240.2 123.02 30169 +1973 359 9.55 3.55 7.9 0 277.38 121.46 30186 +1973 360 6.05 0.05 4.4 0.73 223.21 93.19 30208 +1973 361 4.22 -1.78 2.57 0 198.7 125.66 30235 +1973 362 5.88 -0.12 4.23 0 220.83 125.12 30267 +1973 363 7.54 1.54 5.89 0.26 245.04 93.47 30303 +1973 364 2.79 -3.21 1.14 0 181.2 127.83 30343 +1973 365 4.88 -1.12 3.23 0 207.26 127.26 30388 +1974 1 2.64 -3.36 0.99 0 179.44 129.37 30438 +1974 2 2.95 -3.05 1.3 0 183.09 129.95 30492 +1974 3 5.84 -0.16 4.19 0.03 220.27 96.93 30551 +1974 4 4.66 -1.34 3.01 0 204.37 130.86 30614 +1974 5 6.62 0.62 4.97 0 231.36 130.28 30681 +1974 6 5.53 -0.47 3.88 0.71 215.99 98.9 30752 +1974 7 3.69 -2.31 2.04 0.05 192.05 100.31 30828 +1974 8 1.59 -4.41 -0.06 0 167.55 136.32 30907 +1974 9 0.65 -5.35 -1 0.02 157.49 103.52 30991 +1974 10 4.21 -1.79 2.56 0.02 198.57 103.12 31079 +1974 11 3.85 -2.15 2.2 0 194.04 138.68 31171 +1974 12 -0.64 -6.64 -2.29 0 144.54 141.93 31266 +1974 13 1.2 -4.8 -0.45 0.04 163.31 107.04 31366 +1974 14 -0.47 -6.47 -2.12 0 146.19 144.99 31469 +1974 15 2.41 -3.59 0.76 0 176.78 145.04 31575 +1974 16 3.69 -2.31 2.04 0.2 192.05 109.21 31686 +1974 17 3.98 -2.02 2.33 0 195.67 147.12 31800 +1974 18 5.42 -0.58 3.77 0 214.49 148.1 31917 +1974 19 6.8 0.8 5.15 0 233.98 149.06 32038 +1974 20 8.68 2.68 7.03 0 262.96 149.15 32161 +1974 21 10.88 4.88 9.23 0 300.74 149.15 32289 +1974 22 6.05 0.05 4.4 0 223.21 154.9 32419 +1974 23 6.96 0.96 5.31 0.07 236.34 116.99 32552 +1974 24 6.95 0.95 5.3 0.05 236.19 118.53 32688 +1974 25 8.84 2.84 7.19 1.01 265.57 118.76 32827 +1974 26 5.61 -0.39 3.96 1.13 217.09 122.12 32969 +1974 27 0.57 -5.43 -1.08 0.99 156.66 125.97 33114 +1974 28 3.62 -2.38 1.97 0 191.19 168.41 33261 +1974 29 0.62 -5.38 -1.03 0 157.18 172.55 33411 +1974 30 -1.74 -7.74 -3.39 0 134.23 175.98 33564 +1974 31 3.34 -2.66 1.69 0.01 187.77 131.69 33718 +1974 32 7.8 1.8 6.15 0 249.03 174.33 33875 +1974 33 10.63 4.63 8.98 0 296.23 174.21 34035 +1974 34 10.7 4.7 9.05 0 297.48 176.29 34196 +1974 35 10.22 4.22 8.57 0.03 288.95 134.17 34360 +1974 36 6.27 0.27 4.62 0.18 226.32 138.78 34526 +1974 37 8.75 2.75 7.1 0 264.1 185.23 34694 +1974 38 6.08 0.08 4.43 0 223.63 190.34 34863 +1974 39 10.47 4.47 8.82 0.22 293.37 141.54 35035 +1974 40 10.42 4.42 8.77 0 292.48 191.34 35208 +1974 41 11.39 5.39 9.74 0 310.13 192.79 35383 +1974 42 14.26 8.26 12.61 0 367.81 191.54 35560 +1974 43 12.67 6.67 11.02 0.01 334.82 147.24 35738 +1974 44 5.16 -0.84 3.51 0.09 210.98 155.04 35918 +1974 45 7.65 1.65 6 0.37 246.72 155.33 36099 +1974 46 4.25 -1.75 2.6 0.48 199.08 159.58 36282 +1974 47 6.25 0.25 4.6 0.06 226.04 160.42 36466 +1974 48 6.44 0.44 4.79 0.07 228.76 162.39 36652 +1974 49 10.6 4.6 8.95 0.13 295.69 161.13 36838 +1974 50 10.58 4.58 8.93 0 295.33 217.48 37026 +1974 51 8.25 2.25 6.6 0.18 256.08 167.31 37215 +1974 52 10.26 4.26 8.61 0.32 289.65 167.68 37405 +1974 53 5.52 -0.48 3.87 0.43 215.86 173.65 37596 +1974 54 2.98 -3.02 1.33 0 183.44 236.45 37788 +1974 55 0.62 -5.38 -1.03 0.27 157.18 180.89 37981 +1974 56 3.31 -2.69 1.66 0 187.4 241.91 38175 +1974 57 5.71 -0.29 4.06 0.15 218.47 182.02 38370 +1974 58 5.99 -0.01 4.34 0 222.37 245.35 38565 +1974 59 4.2 -1.8 2.55 0 198.45 249.74 38761 +1974 60 9.06 3.06 7.41 0 269.18 247.56 38958 +1974 61 10.79 4.79 9.14 0.24 299.11 186.17 39156 +1974 62 12.63 6.63 10.98 0.65 334.03 186.22 39355 +1974 63 10.26 4.26 8.61 0.04 289.65 191 39553 +1974 64 11.93 5.93 10.28 0.02 320.35 191.36 39753 +1974 65 9.81 3.81 8.16 0 281.82 260.99 39953 +1974 66 8.83 2.83 7.18 0.45 265.4 198.73 40154 +1974 67 10.31 4.31 8.66 0 290.53 265.89 40355 +1974 68 14.45 8.45 12.8 0 371.94 262.13 40556 +1974 69 14.15 8.15 12.5 0.01 365.44 198.91 40758 +1974 70 7.84 1.84 6.19 0.17 249.65 208.05 40960 +1974 71 2.87 -3.13 1.22 0 182.14 285.54 41163 +1974 72 5.3 -0.7 3.65 0 212.87 286.03 41366 +1974 73 5.79 -0.21 4.14 0 219.58 288.2 41569 +1974 74 8.89 2.89 7.24 0 266.38 287.18 41772 +1974 75 6.89 0.89 5.24 0 235.3 292.44 41976 +1974 76 6.77 0.77 5.12 0.01 233.54 221.42 42179 +1974 77 8.69 2.69 7.04 0.34 263.12 221.55 42383 +1974 78 13.56 7.56 11.91 0.24 352.96 217.74 42587 +1974 79 12.77 6.77 11.12 0.01 336.82 220.81 42791 +1974 80 11.86 5.86 10.21 0 319.01 298.48 42996 +1974 81 12.75 6.75 11.1 0 336.42 299.48 43200 +1974 82 11.42 5.42 9.77 0.18 310.69 228.29 43404 +1974 83 14.65 8.65 13 0.33 376.32 225.68 43608 +1974 84 13.23 7.23 11.58 0 346.14 306.16 43812 +1974 85 14.71 8.71 13.06 0 377.64 305.71 44016 +1974 86 10.25 4.25 8.6 0 289.48 316.15 44220 +1974 87 7.68 1.68 6.03 0 247.19 322.44 44424 +1974 88 10.1 4.1 8.45 0.02 286.85 240.94 44627 +1974 89 13.95 7.95 12.3 0.07 361.17 237.47 44831 +1974 90 12.84 6.84 11.19 0.71 338.22 240.84 45034 +1974 91 18.59 12.59 16.94 0.44 472.07 232.73 45237 +1974 92 15.01 9.01 13.36 0 384.31 321.14 45439 +1974 93 14.57 8.57 12.92 0 374.56 324.25 45642 +1974 94 15.33 9.33 13.68 1.47 391.55 243.53 45843 +1974 95 10.54 4.54 8.89 0 294.62 336.18 46045 +1974 96 13.31 7.31 11.66 0 347.78 333.18 46246 +1974 97 11.12 5.12 9.47 0 305.13 339.34 46446 +1974 98 7.36 1.36 5.71 0 242.31 347.25 46647 +1974 99 10.02 4.02 8.37 0 285.45 345.21 46846 +1974 100 7.13 1.13 5.48 0 238.86 351.58 47045 +1974 101 5.81 -0.19 4.16 0 219.85 355.31 47243 +1974 102 7.45 1.45 5.8 0 243.67 355.02 47441 +1974 103 7.01 1.01 5.36 0 237.08 357.52 47638 +1974 104 8.72 2.72 7.07 0 263.61 356.84 47834 +1974 105 10.13 4.13 8.48 0 287.37 356.34 48030 +1974 106 18.01 12.01 16.36 0 456.79 340.61 48225 +1974 107 18.43 12.43 16.78 0 467.81 341.05 48419 +1974 108 15.22 9.22 13.57 0 389.05 351.09 48612 +1974 109 16.62 10.62 14.97 0 421.88 349.22 48804 +1974 110 14.24 8.24 12.59 0 367.38 356.33 48995 +1974 111 13.68 7.68 12.03 0 355.47 359.11 49185 +1974 112 16.89 10.89 15.24 0 428.48 352.91 49374 +1974 113 17.78 11.78 16.13 0 450.85 351.8 49561 +1974 114 15.51 9.51 13.86 0 395.66 359.21 49748 +1974 115 15.79 9.79 14.14 0.24 402.14 269.95 49933 +1974 116 13.58 7.58 11.93 0 353.38 366.32 50117 +1974 117 10.77 4.77 9.12 0 298.75 373.32 50300 +1974 118 9.26 3.26 7.61 0 272.5 377.33 50481 +1974 119 11.38 5.38 9.73 0.54 309.95 281.02 50661 +1974 120 11.43 5.43 9.78 0 310.88 375.79 50840 +1974 121 12.26 6.26 10.61 0.09 326.74 281.45 51016 +1974 122 13.15 7.15 11.5 0.2 344.5 280.94 51191 +1974 123 14.88 8.88 13.23 1.33 381.41 278.75 51365 +1974 124 17.36 11.36 15.71 0.21 440.17 274.71 51536 +1974 125 14.36 8.36 12.71 0 369.98 374.97 51706 +1974 126 15.15 9.15 13.5 0 387.46 374.06 51874 +1974 127 16.13 10.13 14.48 0.01 410.13 279.34 52039 +1974 128 12.58 6.58 10.93 0 333.03 381.85 52203 +1974 129 17.17 11.17 15.52 0 435.41 371.47 52365 +1974 130 12.91 6.91 11.26 0.02 339.63 287.1 52524 +1974 131 11.83 5.83 10.18 0.2 318.44 289.41 52681 +1974 132 12.48 6.48 10.83 0 331.05 385.37 52836 +1974 133 17.97 11.97 16.32 0 455.76 372.26 52989 +1974 134 15.88 9.88 14.23 0.03 404.24 284.08 53138 +1974 135 14.42 8.42 12.77 0.39 371.28 287.34 53286 +1974 136 16.53 10.53 14.88 0 419.7 378.37 53430 +1974 137 17.67 11.67 16.02 0.34 448.04 281.9 53572 +1974 138 17.84 11.84 16.19 0.02 452.4 281.97 53711 +1974 139 18.98 12.98 17.33 0 482.59 373.18 53848 +1974 140 20.56 14.56 18.91 0 527.26 368.44 53981 +1974 141 20.82 14.82 19.17 0 534.93 367.96 54111 +1974 142 20.16 14.16 18.51 0 515.63 370.72 54238 +1974 143 24.33 18.33 22.68 0.06 648.23 266.52 54362 +1974 144 22.61 16.61 20.96 1.55 590.41 272.12 54483 +1974 145 19.92 13.92 18.27 0.01 508.76 279.74 54600 +1974 146 18.97 12.97 17.32 0 482.32 376.45 54714 +1974 147 15.1 9.1 13.45 1.02 386.34 290.93 54824 +1974 148 15 9 13.35 2.22 384.09 291.41 54931 +1974 149 16.27 10.27 14.62 0.13 413.46 289.16 55034 +1974 150 16.17 10.17 14.52 0.05 411.08 289.61 55134 +1974 151 17.21 11.21 15.56 0 436.41 383.65 55229 +1974 152 25.25 19.25 23.6 0 681.09 354.48 55321 +1974 153 23.83 17.83 22.18 0.03 630.95 270.66 55409 +1974 154 26.87 20.87 25.22 1.04 742.37 260.51 55492 +1974 155 25.46 19.46 23.81 1.46 688.78 265.67 55572 +1974 156 25.48 19.48 23.83 0 689.52 354.45 55648 +1974 157 27.73 21.73 26.08 2.02 776.75 257.73 55719 +1974 158 25.55 19.55 23.9 0.89 692.1 265.84 55786 +1974 159 20.96 14.96 19.31 0 539.11 373.37 55849 +1974 160 17.82 11.82 16.17 0 451.88 383.83 55908 +1974 161 17.85 11.85 16.2 0.41 452.65 287.86 55962 +1974 162 16.44 10.44 14.79 1.13 417.53 290.94 56011 +1974 163 16.61 10.61 14.96 0.2 421.64 290.75 56056 +1974 164 17.02 11.02 15.37 0.07 431.69 289.92 56097 +1974 165 13.04 7.04 11.39 0.76 342.26 297.57 56133 +1974 166 10.95 4.95 9.3 0 302.02 401.26 56165 +1974 167 15.71 9.71 14.06 0 400.28 390.28 56192 +1974 168 17.48 11.48 15.83 0.13 443.2 289.07 56214 +1974 169 16.83 10.83 15.18 0.28 427.01 290.48 56231 +1974 170 11.53 5.53 9.88 0 312.76 400.14 56244 +1974 171 9.25 3.25 7.6 0.04 272.34 303.42 56252 +1974 172 13.68 7.68 12.03 0 355.47 395.47 56256 +1974 173 15.48 9.48 13.83 0.54 394.97 293.25 56255 +1974 174 16.11 10.11 14.46 0 409.66 389.24 56249 +1974 175 16.97 10.97 15.32 0 430.45 386.83 56238 +1974 176 19.09 13.09 17.44 0 485.59 380.38 56223 +1974 177 20.72 14.72 19.07 0 531.97 374.78 56203 +1974 178 20.4 14.4 18.75 0 522.58 375.92 56179 +1974 179 21.34 15.34 19.69 0.14 550.57 279.36 56150 +1974 180 23.59 17.59 21.94 0 622.79 363.6 56116 +1974 181 23.07 17.07 21.42 0 605.43 365.66 56078 +1974 182 23.06 17.06 21.41 0 605.1 365.55 56035 +1974 183 23.12 17.12 21.47 0 607.08 365.14 55987 +1974 184 25.81 19.81 24.16 0 701.77 353.3 55935 +1974 185 24.78 18.78 23.13 0 664.13 357.9 55879 +1974 186 23.98 17.98 22.33 0.3 636.09 270.83 55818 +1974 187 23.13 17.13 21.48 0.09 607.41 273.32 55753 +1974 188 25.9 19.9 24.25 1.03 705.14 264.09 55684 +1974 189 23 17 21.35 0 603.12 364.51 55611 +1974 190 19.04 13.04 17.39 0 484.22 378.32 55533 +1974 191 21.97 15.97 20.32 0.48 570.04 275.91 55451 +1974 192 21.05 15.05 19.4 0 541.8 370.96 55366 +1974 193 21.3 15.3 19.65 0.03 549.35 277.34 55276 +1974 194 24.1 18.1 22.45 0 640.23 358.59 55182 +1974 195 22.32 16.32 20.67 0.1 581.1 274.12 55085 +1974 196 17.73 11.73 16.08 0.08 449.57 285.43 54984 +1974 197 20.81 14.81 19.16 1.27 534.64 277.64 54879 +1974 198 22.03 16.03 20.38 0 571.92 365.32 54770 +1974 199 21.26 15.26 19.61 0 548.14 367.81 54658 +1974 200 22.91 16.91 21.26 0.06 600.17 270.89 54542 +1974 201 17.34 11.34 15.69 0.08 439.67 284.67 54423 +1974 202 17.22 11.22 15.57 0.21 436.66 284.5 54301 +1974 203 16.08 10.08 14.43 0 408.95 381.96 54176 +1974 204 17.42 11.42 15.77 0 441.69 377.73 54047 +1974 205 23.45 17.45 21.8 0.03 618.08 267.39 53915 +1974 206 24.49 18.49 22.84 0.45 653.85 263.74 53780 +1974 207 24.01 18.01 22.36 0.7 637.13 264.78 53643 +1974 208 24.23 18.23 22.58 0.61 644.75 263.61 53502 +1974 209 21.44 15.44 19.79 0 553.62 361.71 53359 +1974 210 19.75 13.75 18.1 0 503.94 366.88 53213 +1974 211 23.31 17.31 21.66 0 613.39 353.25 53064 +1974 212 25.23 19.23 23.58 0.11 680.36 258.32 52913 +1974 213 23.73 17.73 22.08 2.45 627.54 262.53 52760 +1974 214 24.44 18.44 22.79 0.01 652.09 259.79 52604 +1974 215 18.86 12.86 17.21 0.48 479.33 274.44 52445 +1974 216 21.5 15.5 19.85 0.17 555.46 267.11 52285 +1974 217 23.27 17.27 21.62 0.07 612.06 261.48 52122 +1974 218 23.73 17.73 22.08 0.09 627.54 259.51 51958 +1974 219 23.75 17.75 22.1 0.05 628.22 258.69 51791 +1974 220 27.43 21.43 25.78 0 764.6 327.64 51622 +1974 221 25.54 19.54 23.89 1.17 691.73 251.62 51451 +1974 222 24.9 18.9 23.25 0.65 668.43 252.95 51279 +1974 223 25.61 19.61 23.96 0.29 694.32 249.82 51105 +1974 224 27.56 21.56 25.91 0.45 769.85 242.27 50929 +1974 225 27.91 21.91 26.26 0.2 784.11 240.18 50751 +1974 226 26.07 20.07 24.42 1.64 711.55 245.9 50572 +1974 227 28.64 22.64 26.99 0.07 814.58 235.73 50392 +1974 228 24.75 18.75 23.1 0.45 663.06 248.39 50210 +1974 229 24.51 18.51 22.86 0 654.55 330.99 50026 +1974 230 21.91 15.91 20.26 0 568.16 339.66 49842 +1974 231 21.99 15.99 20.34 0.08 570.66 253.45 49656 +1974 232 22.68 16.68 21.03 0.17 592.67 250.59 49469 +1974 233 24.15 18.15 22.5 1.01 641.97 245.35 49280 +1974 234 22.65 16.65 21 0 591.7 331.46 49091 +1974 235 20.98 14.98 19.33 0.27 539.7 251.84 48900 +1974 236 22.27 16.27 20.62 0.02 579.51 247.48 48709 +1974 237 26.73 20.73 25.08 0 736.89 310.54 48516 +1974 238 25.49 19.49 23.84 0.12 689.89 235.76 48323 +1974 239 23.82 17.82 22.17 0.26 630.61 239.69 48128 +1974 240 20.73 14.73 19.08 0.97 532.26 246.51 47933 +1974 241 20.84 14.84 19.19 2.25 535.53 244.97 47737 +1974 242 20.48 14.48 18.83 0.84 524.91 244.54 47541 +1974 243 19.28 13.28 17.63 0.52 490.81 245.87 47343 +1974 244 15.35 9.35 13.7 0.02 392 252.14 47145 +1974 245 21.21 15.21 19.56 0.1 546.63 238.72 46947 +1974 246 18.04 12.04 16.39 0 457.57 325.66 46747 +1974 247 17.42 11.42 15.77 0 441.69 325.43 46547 +1974 248 15.18 9.18 13.53 0 388.14 328.84 46347 +1974 249 22.97 16.97 21.32 0 602.13 304.8 46146 +1974 250 22.32 16.32 20.67 0 581.1 305.14 45945 +1974 251 20.71 14.71 19.06 0 531.67 308.22 45743 +1974 252 20.87 14.87 19.22 0 536.42 305.61 45541 +1974 253 23.01 17.01 21.36 0 603.45 296.63 45339 +1974 254 19.06 13.06 17.41 0.2 484.77 229.99 45136 +1974 255 15.4 9.4 13.75 0 393.14 313.36 44933 +1974 256 14.13 8.13 12.48 0 365.02 313.74 44730 +1974 257 14.68 8.68 13.03 1.12 376.98 232.81 44527 +1974 258 17.35 11.35 15.7 0.08 439.92 226.56 44323 +1974 259 17.47 11.47 15.82 0.06 442.95 224.53 44119 +1974 260 22.04 16.04 20.39 0 572.24 284.44 43915 +1974 261 18.99 12.99 17.34 0 482.86 290.77 43711 +1974 262 18.63 12.63 16.98 0.14 473.14 217.02 43507 +1974 263 22.53 16.53 20.88 0.92 587.83 206.93 43303 +1974 264 22.11 16.11 20.46 0.06 574.44 206.06 43099 +1974 265 18.56 12.56 16.91 0 471.27 282.24 42894 +1974 266 22.4 16.4 20.75 0 583.66 269.22 42690 +1974 267 18.3 12.3 16.65 0 464.38 277.8 42486 +1974 268 18.2 12.2 16.55 0 461.75 275.52 42282 +1974 269 17.72 11.72 16.07 1.24 449.31 205.62 42078 +1974 270 18.12 12.12 16.47 0.18 459.66 202.98 41875 +1974 271 13.55 7.55 11.9 0.73 352.75 208.03 41671 +1974 272 17.33 11.33 15.68 1.43 439.42 200.37 41468 +1974 273 16.94 10.94 15.29 0.82 429.71 199.14 41265 +1974 274 5.21 -0.79 3.56 0.02 211.65 210.52 41062 +1974 275 8.19 2.19 6.54 0 255.13 274.47 40860 +1974 276 13.05 7.05 11.4 0 342.47 264.74 40658 +1974 277 13.09 7.09 11.44 0.02 343.28 196.5 40456 +1974 278 12.33 6.33 10.68 0.67 328.11 195.26 40255 +1974 279 15.66 9.66 14.01 0.93 399.12 188.85 40054 +1974 280 15.13 9.13 13.48 0.43 387.01 187.62 39854 +1974 281 15.34 9.34 13.69 0 391.77 247.08 39654 +1974 282 14.46 8.46 12.81 1.3 372.15 184.44 39455 +1974 283 11.08 5.08 9.43 0.17 304.4 186.25 39256 +1974 284 11.26 5.26 9.61 0.55 307.72 183.78 39058 +1974 285 12.12 6.12 10.47 1.82 324.02 180.87 38861 +1974 286 9.83 3.83 8.18 1.19 282.17 181.11 38664 +1974 287 11.7 5.7 10.05 0.83 315.97 177.03 38468 +1974 288 3.71 -2.29 2.06 0 192.3 241.95 38273 +1974 289 -0.01 -6.01 -1.66 0.08 150.74 216.33 38079 +1974 290 6.63 0.63 4.98 0.14 231.5 175.24 37885 +1974 291 5.61 -0.39 3.96 0.35 217.09 173.9 37693 +1974 292 6.19 0.19 4.54 0.93 225.19 171.43 37501 +1974 293 5.82 -0.18 4.17 0.83 219.99 169.6 37311 +1974 294 10.61 4.61 8.96 0.15 295.87 163.58 37121 +1974 295 12.25 6.25 10.6 0 326.54 213.16 36933 +1974 296 9.02 3.02 7.37 0.27 268.52 160.87 36745 +1974 297 8.21 2.21 6.56 0.32 255.44 159.45 36560 +1974 298 5.5 -0.5 3.85 0.58 215.58 159.38 36375 +1974 299 7.52 1.52 5.87 0.69 244.74 155.88 36191 +1974 300 7.69 1.69 6.04 0.14 247.34 153.73 36009 +1974 301 9.8 3.8 8.15 0.03 281.65 150.2 35829 +1974 302 11.21 5.21 9.56 1.09 306.79 147.04 35650 +1974 303 10.72 4.72 9.07 0.14 297.85 145.54 35472 +1974 304 10.41 4.41 8.76 0.05 292.3 143.95 35296 +1974 305 9.2 3.2 7.55 0.03 271.5 142.86 35122 +1974 306 10.01 4.01 8.36 0.21 285.28 140.54 34950 +1974 307 12.44 6.44 10.79 0.02 330.27 136.6 34779 +1974 308 12.13 6.13 10.48 0 324.21 179.93 34610 +1974 309 13.93 7.93 12.28 0 360.75 175.41 34444 +1974 310 11.9 5.9 10.25 0 319.78 175.5 34279 +1974 311 11.48 5.48 9.83 0.01 311.82 130.37 34116 +1974 312 9.85 3.85 8.2 0 282.51 172.92 33956 +1974 313 10.11 4.11 8.46 0 287.02 170.55 33797 +1974 314 10.26 4.26 8.61 0 289.65 168.47 33641 +1974 315 8.64 2.64 6.99 0 262.32 167.48 33488 +1974 316 11 5 9.35 0 302.93 163.05 33337 +1974 317 9.22 3.22 7.57 0 271.84 162.6 33188 +1974 318 7.62 1.62 5.97 0 246.26 161.65 33042 +1974 319 7.25 1.25 5.6 0.18 240.65 120.19 32899 +1974 320 5.36 -0.64 3.71 0.02 213.68 119.84 32758 +1974 321 2.82 -3.18 1.17 1.81 181.55 119.47 32620 +1974 322 0.68 -5.32 -0.97 0.08 157.8 118.95 32486 +1974 323 -1.27 -7.27 -2.92 0.16 138.55 159.67 32354 +1974 324 -1.68 -7.68 -3.33 0 134.77 197.4 32225 +1974 325 6.76 0.76 5.11 0.16 233.39 112.09 32100 +1974 326 12.07 6.07 10.42 0 323.05 143.41 31977 +1974 327 11.39 5.39 9.74 0 310.13 142.27 31858 +1974 328 11.46 5.46 9.81 0 311.44 140.26 31743 +1974 329 9.85 3.85 8.2 0 282.51 140.26 31631 +1974 330 5.81 -0.19 4.16 0.01 219.85 106.43 31522 +1974 331 5.35 -0.65 3.7 0 213.54 140.89 31417 +1974 332 3.59 -2.41 1.94 0.15 190.82 105.23 31316 +1974 333 3.8 -2.2 2.15 0.41 193.42 104.32 31218 +1974 334 5.6 -0.4 3.95 0 216.95 136.9 31125 +1974 335 3.87 -2.13 2.22 0.69 194.29 102.57 31035 +1974 336 0.3 -5.7 -1.35 0.14 153.88 103.12 30949 +1974 337 4.24 -1.76 2.59 0 198.96 133.81 30867 +1974 338 4.09 -1.91 2.44 0 197.05 132.96 30790 +1974 339 3.44 -2.56 1.79 0 188.98 132.53 30716 +1974 340 3.25 -2.75 1.6 0 186.68 131.89 30647 +1974 341 3.07 -2.93 1.42 0.01 184.52 98.3 30582 +1974 342 3.79 -2.21 2.14 0.87 193.29 97.44 30521 +1974 343 3.05 -2.95 1.4 0.1 184.28 97.11 30465 +1974 344 4.72 -1.28 3.07 0 205.16 127.43 30413 +1974 345 7.16 1.16 5.51 0 239.31 125.49 30366 +1974 346 10.15 4.15 8.5 0 287.72 122.73 30323 +1974 347 9.31 3.31 7.66 0 273.34 122.81 30284 +1974 348 9.02 3.02 7.37 0 268.52 122.68 30251 +1974 349 4.72 -1.28 3.07 0.59 205.16 93.85 30221 +1974 350 0.73 -5.27 -0.92 0 158.33 126.8 30197 +1974 351 0.6 -5.4 -1.05 0.21 156.97 94.97 30177 +1974 352 5.59 -0.41 3.94 0 216.82 123.98 30162 +1974 353 8.48 2.48 6.83 0 259.74 122.01 30151 +1974 354 9.85 3.85 8.2 0 282.51 120.95 30145 +1974 355 7.15 1.15 5.5 0 239.16 122.9 30144 +1974 356 9.36 3.36 7.71 0 274.18 121.35 30147 +1974 357 12.51 6.51 10.86 0 331.65 118.75 30156 +1974 358 12.34 6.34 10.69 0 328.3 118.99 30169 +1974 359 16.67 10.67 15.02 0.09 423.1 85.92 30186 +1974 360 7.58 1.58 5.93 0 245.65 123.25 30208 +1974 361 10.76 4.76 9.11 0 298.57 121.17 30235 +1974 362 6.6 0.6 4.95 0 231.07 124.67 30267 +1974 363 6.78 0.78 5.13 0.1 233.69 93.85 30303 +1974 364 7.49 1.49 5.84 0.01 244.28 93.79 30343 +1974 365 4.96 -1.04 3.31 0 208.32 127.22 30388 +1975 1 3.2 -2.8 1.55 0 186.07 129.08 30438 +1975 2 2.06 -3.94 0.41 0.3 172.79 97.8 30492 +1975 3 -1.47 -7.47 -3.12 0.08 136.7 143.12 30551 +1975 4 1.08 -4.92 -0.57 0 162.03 175.95 30614 +1975 5 -0.59 -6.59 -2.24 0 145.02 177.24 30681 +1975 6 -0.62 -6.62 -2.27 0 144.73 178.05 30752 +1975 7 -1.6 -7.6 -3.25 0 135.5 179.14 30828 +1975 8 0.91 -5.09 -0.74 0 160.22 136.65 30907 +1975 9 4.08 -1.92 2.43 0 196.93 136.26 30991 +1975 10 4.48 -1.52 2.83 0 202.04 137.33 31079 +1975 11 8.1 2.1 6.45 0.04 253.71 101.91 31171 +1975 12 9.91 3.91 8.26 0 283.55 135.41 31266 +1975 13 4.55 -1.45 2.9 0 202.94 140.9 31366 +1975 14 9.32 3.32 7.67 0.18 273.51 104.22 31469 +1975 15 7.71 1.71 6.06 0 247.65 141.65 31575 +1975 16 7.6 1.6 5.95 0 245.96 143 31686 +1975 17 8.87 2.87 7.22 0 266.06 143.66 31800 +1975 18 7.99 1.99 6.34 0 251.99 146.24 31917 +1975 19 8.46 2.46 6.81 0 259.42 147.77 32038 +1975 20 5.79 -0.21 4.14 0 219.58 151.35 32161 +1975 21 4.97 -1.03 3.32 0 208.45 153.91 32289 +1975 22 5.86 -0.14 4.21 0 220.55 155.04 32419 +1975 23 7.05 1.05 5.4 0 237.67 155.92 32552 +1975 24 3.95 -2.05 2.3 0 195.29 160.15 32688 +1975 25 6.53 0.53 4.88 0 230.05 160.24 32827 +1975 26 8.2 2.2 6.55 0 255.28 160.8 32969 +1975 27 12.06 6.06 10.41 0 322.85 159.06 33114 +1975 28 11.89 5.89 10.24 0 319.59 161.4 33261 +1975 29 16.35 10.35 14.7 0 415.37 158.11 33411 +1975 30 13.63 7.63 11.98 0 354.42 163.87 33564 +1975 31 15.05 9.05 13.4 0 385.21 164.33 33718 +1975 32 15.62 9.62 13.97 0 398.2 165.56 33875 +1975 33 15.75 9.75 14.1 0 401.21 167.9 34035 +1975 34 14.14 8.14 12.49 0 365.23 172.21 34196 +1975 35 11.01 5.01 9.36 0 303.11 178.05 34360 +1975 36 11.1 5.1 9.45 0 304.76 180.41 34526 +1975 37 10.57 4.57 8.92 0 295.15 183.36 34694 +1975 38 8.88 2.88 7.23 0 266.22 187.81 34863 +1975 39 3.03 -2.97 1.38 0 184.04 195.24 35035 +1975 40 3.67 -2.33 2.02 0 191.8 197.42 35208 +1975 41 4.73 -1.27 3.08 0 205.29 199.25 35383 +1975 42 6.13 0.13 4.48 0 224.34 200.65 35560 +1975 43 6.26 0.26 4.61 0 226.18 203.23 35738 +1975 44 3.88 -2.12 2.23 0 194.41 207.73 35918 +1975 45 1.14 -4.86 -0.51 0 162.67 212.28 36099 +1975 46 3.14 -2.86 1.49 0 185.35 213.62 36282 +1975 47 4.21 -1.79 2.56 0 198.57 215.63 36466 +1975 48 -1.22 -7.22 -2.87 0 139.02 222.1 36652 +1975 49 -3.12 -9.12 -4.77 0 122.2 225.92 36838 +1975 50 -4.77 -10.77 -6.42 0 109.06 229.41 37026 +1975 51 -5.96 -11.96 -7.61 0 100.35 232.94 37215 +1975 52 1.42 -4.58 -0.23 0 165.69 231.83 37405 +1975 53 -1.66 -7.66 -3.31 0 134.96 236.76 37596 +1975 54 -3.03 -9.03 -4.68 0 122.96 240.31 37788 +1975 55 0.25 -5.75 -1.4 0 153.37 241.43 37981 +1975 56 2.19 -3.81 0.54 0 174.26 242.79 38175 +1975 57 4.54 -1.46 2.89 0 202.81 243.77 38370 +1975 58 5.02 -0.98 3.37 0 209.11 246.28 38565 +1975 59 3.93 -2.07 2.28 0 195.04 249.97 38761 +1975 60 8.39 2.39 6.74 0 258.3 248.35 38958 +1975 61 11.32 5.32 9.67 0 308.83 247.49 39156 +1975 62 13.42 7.42 11.77 0.15 350.05 185.28 39355 +1975 63 13.59 7.59 11.94 0.26 353.59 187.28 39553 +1975 64 12.01 6.01 10.36 1.22 321.89 191.27 39753 +1975 65 11.52 5.52 9.87 0.11 312.57 193.95 39953 +1975 66 13.19 7.19 11.54 0 345.32 258.68 40154 +1975 67 11.58 5.58 9.93 0.13 313.7 198.04 40355 +1975 68 11.28 5.28 9.63 0.51 308.09 200.5 40556 +1975 69 11.25 5.25 9.6 1.3 307.53 202.47 40758 +1975 70 9.8 3.8 8.15 0.04 281.65 206.14 40960 +1975 71 7.71 1.71 6.06 0.5 247.65 210.35 41163 +1975 72 6.01 0.01 4.36 0.55 222.65 213.95 41366 +1975 73 5.33 -0.67 3.68 0.02 213.27 216.52 41569 +1975 74 5.21 -0.79 3.56 0 211.65 291.59 41772 +1975 75 7.38 1.38 5.73 0 242.61 291.85 41976 +1975 76 8.59 2.59 6.94 0.01 261.51 219.7 42179 +1975 77 7.76 1.76 6.11 0 248.42 296.62 42383 +1975 78 9.04 3.04 7.39 0 268.85 297.58 42587 +1975 79 7.95 1.95 6.3 0 251.36 301.77 42791 +1975 80 7.57 1.57 5.92 0 245.5 304.81 42996 +1975 81 11.74 5.74 10.09 0 316.72 301.23 43200 +1975 82 8.55 2.55 6.9 0 260.86 308.74 43404 +1975 83 9.94 3.94 8.29 0 284.07 309.21 43608 +1975 84 7.06 1.06 5.41 0.03 237.82 236.83 43812 +1975 85 10 4 8.35 0 285.11 314.14 44016 +1975 86 8.67 2.67 7.02 0 262.8 318.52 44220 +1975 87 9.93 3.93 8.28 0 283.89 319.18 44424 +1975 88 10.12 4.12 8.47 0.75 287.2 240.92 44627 +1975 89 7.36 1.36 5.71 0.86 242.31 245.65 44831 +1975 90 12.27 6.27 10.62 0 326.93 322.18 45034 +1975 91 16.27 10.27 14.62 0 413.46 316.11 45237 +1975 92 14.89 8.89 13.24 0.24 381.63 241.05 45439 +1975 93 13.93 7.93 12.28 0 360.75 325.59 45642 +1975 94 13.28 7.28 11.63 0 347.17 329.03 45843 +1975 95 13.12 7.12 11.47 0.04 343.89 248.6 46045 +1975 96 13.06 7.06 11.41 0.99 342.67 250.26 46246 +1975 97 6.75 0.75 5.1 0.53 233.25 259.57 46446 +1975 98 8.47 2.47 6.82 0 259.58 345.64 46647 +1975 99 7.85 1.85 6.2 0 249.81 348.58 46846 +1975 100 11.82 5.82 10.17 0 318.25 343.99 47045 +1975 101 17.98 11.98 16.33 0 456.02 331.96 47243 +1975 102 15.9 9.9 14.25 0 404.71 339.12 47441 +1975 103 15.62 9.62 13.97 0 398.2 341.59 47638 +1975 104 15.23 9.23 13.58 0.06 389.27 258.23 47834 +1975 105 15.04 9.04 13.39 0.02 384.99 259.88 48030 +1975 106 12.87 6.87 11.22 0 338.83 352.86 48225 +1975 107 11.62 5.62 9.97 0 314.45 356.99 48419 +1975 108 9.75 3.75 8.1 0 280.79 362.09 48612 +1975 109 12.85 6.85 11.2 0 338.42 357.91 48804 +1975 110 6.96 0.96 5.31 0.07 236.34 277.14 48995 +1975 111 9.98 3.98 8.33 0 284.76 366.32 49185 +1975 112 11.27 5.27 9.62 0.18 307.9 274.14 49374 +1975 113 13.27 7.27 11.62 1.44 346.96 272.14 49561 +1975 114 16.11 10.11 14.46 0 409.66 357.71 49748 +1975 115 17.07 11.07 15.42 0.01 432.93 267.46 49933 +1975 116 15.34 9.34 13.69 0 391.77 362.24 50117 +1975 117 12.35 6.35 10.7 0 328.5 370.24 50300 +1975 118 8.8 2.8 7.15 0 264.91 378.09 50481 +1975 119 11.03 5.03 9.38 0 303.48 375.37 50661 +1975 120 13.06 7.06 11.41 0 342.67 372.45 50840 +1975 121 16.04 10.04 14.39 0 408 366.55 51016 +1975 122 17.29 11.29 15.64 0.02 438.42 273.29 51191 +1975 123 18.48 12.48 16.83 1.84 469.14 271.48 51365 +1975 124 15.71 9.71 14.06 0 400.28 370.68 51536 +1975 125 16.86 10.86 15.21 0.38 427.74 276.47 51706 +1975 126 24.32 18.32 22.67 0 647.88 344.21 51874 +1975 127 19.69 13.69 18.04 0.2 502.24 271.56 52039 +1975 128 19.1 13.1 17.45 0.24 485.86 273.7 52203 +1975 129 19.3 13.3 17.65 0.04 491.36 273.85 52365 +1975 130 19.55 13.55 17.9 0.11 498.32 273.83 52524 +1975 131 19.64 13.64 17.99 1.15 500.84 274.2 52681 +1975 132 21.7 15.7 20.05 0 561.62 359.32 52836 +1975 133 19.7 13.7 18.05 0 502.53 366.9 52989 +1975 134 18.69 12.69 17.04 0.5 474.75 278.09 53138 +1975 135 16.21 10.21 14.56 0.32 412.03 283.95 53286 +1975 136 13.57 7.57 11.92 0.4 353.17 289.32 53430 +1975 137 10.68 4.68 9.03 2.4 297.12 294.4 53572 +1975 138 8.49 2.49 6.84 0 259.9 397.08 53711 +1975 139 8.05 2.05 6.4 0 252.93 398.51 53848 +1975 140 11.89 5.89 10.24 0 319.59 391.94 53981 +1975 141 16.29 10.29 14.64 0.04 413.94 286.46 54111 +1975 142 16.2 10.2 14.55 0.09 411.79 287.01 54238 +1975 143 17.7 11.7 16.05 0 448.8 379.01 54362 +1975 144 23.77 17.77 22.12 0 628.9 358.16 54483 +1975 145 25.51 19.51 23.86 0 690.62 351.05 54600 +1975 146 25.6 19.6 23.95 0 693.95 350.98 54714 +1975 147 22.76 16.76 21.11 0 595.27 363.52 54824 +1975 148 24.59 18.59 22.94 0 657.38 356.32 54931 +1975 149 22.29 16.29 20.64 0 580.15 366.01 55034 +1975 150 24.31 18.31 22.66 0 647.54 358.14 55134 +1975 151 20.13 14.13 18.48 0 514.76 374.52 55229 +1975 152 19.07 13.07 17.42 0 485.04 378.12 55321 +1975 153 22.36 16.36 20.71 0.82 582.38 275.09 55409 +1975 154 21.97 15.97 20.32 0 570.04 368.59 55492 +1975 155 22.72 16.72 21.07 0.04 593.97 274.41 55572 +1975 156 20.94 14.94 19.29 0.18 538.51 279.65 55648 +1975 157 20.48 14.48 18.83 0.09 524.91 280.99 55719 +1975 158 19.43 13.43 17.78 0 494.97 378.37 55786 +1975 159 20.06 14.06 18.41 0.05 512.76 282.38 55849 +1975 160 23.8 17.8 22.15 0 629.93 362.56 55908 +1975 161 21.62 15.62 19.97 0 559.15 371.22 55962 +1975 162 20.61 14.61 18.96 0 528.72 374.92 56011 +1975 163 22.5 16.5 20.85 0 586.86 368.14 56056 +1975 164 24.5 18.5 22.85 0 654.2 359.94 56097 +1975 165 24.52 18.52 22.87 0 654.91 359.94 56133 +1975 166 26.2 20.2 24.55 0 716.48 352.34 56165 +1975 167 27.08 21.08 25.43 0.23 750.64 260.99 56192 +1975 168 21.64 15.64 19.99 0.77 559.77 278.74 56214 +1975 169 23.23 17.23 21.58 0.69 610.73 274.11 56231 +1975 170 21.31 15.31 19.66 0.4 549.66 279.66 56244 +1975 171 19.22 13.22 17.57 0.64 489.16 285.1 56252 +1975 172 17.95 11.95 16.3 0.12 455.24 288.07 56256 +1975 173 15.53 9.53 13.88 1.88 396.12 293.15 56255 +1975 174 15.71 9.71 14.06 1.64 400.28 292.73 56249 +1975 175 13.6 7.6 11.95 0.59 353.8 296.64 56238 +1975 176 14.16 8.16 12.51 0.35 365.66 295.62 56223 +1975 177 14.91 8.91 13.26 1.39 382.08 294.15 56203 +1975 178 15.52 9.52 13.87 3.05 395.89 293 56179 +1975 179 16.35 10.35 14.7 0.15 415.37 291.25 56150 +1975 180 12.72 6.72 11.07 0 335.82 397.16 56116 +1975 181 10.17 4.17 8.52 0.09 288.07 301.72 56078 +1975 182 15.78 9.78 14.13 0 401.91 389.53 56035 +1975 183 18.92 12.92 17.27 0.22 480.96 285.16 55987 +1975 184 22.67 16.67 21.02 0 592.35 366.78 55935 +1975 185 26.62 20.62 24.97 0.38 732.62 262.02 55879 +1975 186 27.62 21.62 25.97 0.54 772.27 258.08 55818 +1975 187 26.97 20.97 25.32 0.15 746.3 260.41 55753 +1975 188 24.91 18.91 23.26 1.34 668.79 267.48 55684 +1975 189 21.33 15.33 19.68 0.22 550.27 278.16 55611 +1975 190 22.5 16.5 20.85 1.84 586.86 274.59 55533 +1975 191 20.84 14.84 19.19 0.55 535.53 279.01 55451 +1975 192 24.34 18.34 22.69 0.12 648.58 268.53 55366 +1975 193 26.22 20.22 24.57 0.14 717.24 261.96 55276 +1975 194 21.85 15.85 20.2 0.72 566.28 275.66 55182 +1975 195 18.02 12.02 16.37 0.16 457.05 285.09 55085 +1975 196 17.09 11.09 15.44 0 433.42 382.43 54984 +1975 197 19.62 13.62 17.97 0 500.28 374.23 54879 +1975 198 20.99 14.99 19.34 0 540 369.13 54770 +1975 199 19.96 13.96 18.31 0 509.9 372.32 54658 +1975 200 21.11 15.11 19.46 2.82 543.61 275.96 54542 +1975 201 18.46 12.46 16.81 0.41 468.61 282.18 54423 +1975 202 20.67 14.67 19.02 0.02 530.49 276.35 54301 +1975 203 21.31 15.31 19.66 0.3 549.66 274.28 54176 +1975 204 18.79 12.79 17.14 0 477.44 373.63 54047 +1975 205 25.05 19.05 23.4 0.01 673.83 262.32 53915 +1975 206 23.36 17.36 21.71 0.94 615.06 267.25 53780 +1975 207 27.18 21.18 25.53 0 754.61 338.64 53643 +1975 208 30.13 24.13 28.48 2.21 879.89 241.69 53502 +1975 209 25.56 19.56 23.91 0 692.47 345.06 53359 +1975 210 24.65 18.65 23 0.12 659.51 261.35 53213 +1975 211 24.34 18.34 22.69 0.23 648.58 261.77 53064 +1975 212 24.74 18.74 23.09 0 662.71 346.56 52913 +1975 213 19.63 13.63 17.98 2.46 500.56 273.7 52760 +1975 214 23.03 17.03 21.38 0.64 604.11 264.08 52604 +1975 215 22.46 16.46 20.81 0.01 585.58 265.22 52445 +1975 216 25.18 19.18 23.53 0 678.54 341.57 52285 +1975 217 23.93 17.93 22.28 0 634.38 346 52122 +1975 218 26.09 20.09 24.44 0 712.3 335.87 51958 +1975 219 26.46 20.46 24.81 0 726.43 333.16 51791 +1975 220 22.05 16.05 20.4 0.16 572.55 262.89 51622 +1975 221 25.4 19.4 23.75 0 686.58 336.11 51451 +1975 222 26.6 20.6 24.95 0.2 731.84 247.27 51279 +1975 223 25.33 19.33 23.68 0.07 684.01 250.74 51105 +1975 224 19.64 13.64 17.99 0.19 500.84 265.86 50929 +1975 225 20.36 14.36 18.71 0 521.41 351.03 50751 +1975 226 23.46 17.46 21.81 0.74 618.41 254.1 50572 +1975 227 21.35 15.35 19.7 0.32 550.88 258.97 50392 +1975 228 21.47 15.47 19.82 0 554.54 343.67 50210 +1975 229 22.27 16.27 20.62 0 579.51 339.62 50026 +1975 230 25.1 19.1 23.45 0.02 675.64 245.49 49842 +1975 231 19.64 13.64 17.99 0.81 500.84 259.29 49656 +1975 232 20.21 14.21 18.56 0.33 517.07 256.93 49469 +1975 233 20.04 14.04 18.39 0.28 512.18 256.28 49280 +1975 234 17.8 11.8 16.15 0.28 451.37 260.17 49091 +1975 235 20.68 14.68 19.03 0.21 530.79 252.58 48900 +1975 236 19.82 13.82 18.17 0.09 505.92 253.55 48709 +1975 237 22.16 16.16 20.51 0.42 576.02 246.56 48516 +1975 238 15.42 9.42 13.77 0.31 393.6 259.99 48323 +1975 239 17.07 11.07 15.42 0.3 432.93 255.76 48128 +1975 240 23.79 17.79 22.14 0.14 629.58 238.51 47933 +1975 241 19.65 13.65 18 0.02 501.12 247.74 47737 +1975 242 23.68 17.68 22.03 0 625.84 315.09 47541 +1975 243 22.07 16.07 20.42 0 573.18 319.04 47343 +1975 244 19.31 13.31 17.66 0 491.64 325.92 47145 +1975 245 18.41 12.41 16.76 0 467.28 326.63 46947 +1975 246 15.32 9.32 13.67 0 391.32 332.38 46747 +1975 247 15.66 9.66 14.01 0 399.12 329.72 46547 +1975 248 16.46 10.46 14.81 0.29 418.01 244.4 46347 +1975 249 18.74 12.74 17.09 0 476.09 317.92 46146 +1975 250 19.91 13.91 18.26 0 508.47 312.68 45945 +1975 251 20.58 14.58 18.93 0.2 527.84 231.46 45743 +1975 252 16.02 10.02 14.37 0 407.53 318.54 45541 +1975 253 21.27 15.27 19.62 0.01 548.44 226.74 45339 +1975 254 20.72 14.72 19.07 0 531.97 301.91 45136 +1975 255 19.21 13.21 17.56 0.06 488.88 228.01 44933 +1975 256 18.42 12.42 16.77 0 467.55 303.88 44730 +1975 257 19.67 13.67 18.02 0.19 501.68 223.79 44527 +1975 258 20.4 14.4 18.75 0.52 522.58 220.52 44323 +1975 259 22.29 16.29 20.64 0 580.15 285.94 44119 +1975 260 18.63 12.63 16.98 0 473.14 294.11 43915 +1975 261 20.35 14.35 18.7 0.02 521.12 215.31 43711 +1975 262 19.39 13.39 17.74 0 493.86 287.38 43507 +1975 263 20.02 14.02 18.37 0.02 511.61 212.46 43303 +1975 264 23.19 17.19 21.54 0 609.4 271.34 43099 +1975 265 26.17 20.17 24.52 0.15 715.34 193.99 42894 +1975 266 27.71 21.71 26.06 0 775.93 250.32 42690 +1975 267 23.28 17.28 21.63 0 612.39 263.91 42486 +1975 268 21.34 15.34 19.69 0 550.57 267.32 42282 +1975 269 23.52 17.52 21.87 0 620.43 258.35 42078 +1975 270 27.65 21.65 26 0 773.49 241.15 41875 +1975 271 26.96 20.96 25.31 0 745.9 241.46 41671 +1975 272 24.42 18.42 22.77 0.01 651.39 185.94 41468 +1975 273 22.76 16.76 21.11 0.7 595.27 188.06 41265 +1975 274 11.97 5.97 10.32 0 321.12 272 41062 +1975 275 13.77 7.77 12.12 0 357.36 266.23 40860 +1975 276 10.38 4.38 8.73 0.17 291.77 201.62 40658 +1975 277 10.59 4.59 8.94 1.43 295.51 199.37 40456 +1975 278 12.03 6.03 10.38 0.01 322.28 195.6 40255 +1975 279 13.74 7.74 12.09 0.07 356.73 191.42 40054 +1975 280 7.93 1.93 6.28 0.06 251.05 195.58 39854 +1975 281 10.1 4.1 8.45 0.06 286.85 191.47 39654 +1975 282 12.07 6.07 10.42 0 323.05 249.75 39455 +1975 283 9.76 3.76 8.11 0 280.97 250.09 39256 +1975 284 9.07 3.07 7.42 0.24 269.35 185.92 39058 +1975 285 11.01 5.01 9.36 0.18 303.11 182.04 38861 +1975 286 11.65 5.65 10 0.17 315.02 179.29 38664 +1975 287 8.9 2.9 7.25 0.04 266.55 179.72 38468 +1975 288 12.66 6.66 11.01 0 334.62 231.88 38273 +1975 289 9.17 3.17 7.52 0 271 233.82 38079 +1975 290 14.98 8.98 13.33 0 383.64 222.8 37885 +1975 291 17.02 11.02 15.37 0 431.69 216.58 37693 +1975 292 14 8 12.35 0 362.24 219.04 37501 +1975 293 16.55 10.55 14.9 0 420.19 212.15 37311 +1975 294 11.57 5.57 9.92 0.24 313.51 162.67 37121 +1975 295 12.52 6.52 10.87 0.31 331.84 159.6 36933 +1975 296 13.4 7.4 11.75 0.28 349.64 156.75 36745 +1975 297 15.1 9.1 13.45 0.71 386.34 152.82 36560 +1975 298 13.81 7.81 12.16 0.02 358.21 152.36 36375 +1975 299 13.7 7.7 12.05 0 355.89 200.55 36191 +1975 300 18.53 12.53 16.88 0 470.47 190.08 36009 +1975 301 14.68 8.68 13.03 0.88 376.98 145.53 35829 +1975 302 14.74 8.74 13.09 0.67 378.3 143.54 35650 +1975 303 14.53 8.53 12.88 0 373.68 189.16 35472 +1975 304 14.32 8.32 12.67 1.19 369.11 140.29 35296 +1975 305 7.44 1.44 5.79 0.27 243.52 144.13 35122 +1975 306 8.22 2.22 6.57 0 255.6 189.18 34950 +1975 307 7.86 1.86 6.21 0 249.96 187 34779 +1975 308 8.77 2.77 7.12 0.07 264.42 137.65 34610 +1975 309 7.79 1.79 6.14 0 248.88 182.12 34444 +1975 310 5.65 -0.35 4 0.03 217.64 136.09 34279 +1975 311 3.01 -2.99 1.36 0.11 183.8 135.83 34116 +1975 312 5.14 -0.86 3.49 0 210.72 176.97 33956 +1975 313 -1.43 -7.43 -3.08 0.02 137.07 173.15 33797 +1975 314 -0.57 -6.57 -2.22 0.35 145.22 172.51 33641 +1975 315 4.51 -1.49 2.86 0.18 202.42 167.99 33488 +1975 316 1.77 -4.23 0.12 0 169.54 210.15 33337 +1975 317 3.74 -2.26 2.09 0 192.67 166.83 33188 +1975 318 6.94 0.94 5.29 0 236.04 162.2 33042 +1975 319 6.13 0.13 4.48 0 224.34 161.11 32899 +1975 320 6.48 0.48 4.83 0 229.33 158.98 32758 +1975 321 8.95 2.95 7.3 0.06 267.37 116.16 32620 +1975 322 9.28 3.28 7.63 0.08 272.84 114.59 32486 +1975 323 7.86 1.86 6.21 0 249.96 152.37 32354 +1975 324 5.5 -0.5 3.85 0 215.58 152.06 32225 +1975 325 3.52 -2.48 1.87 1.87 189.96 113.69 32100 +1975 326 5.62 -0.38 3.97 0 217.23 148.79 31977 +1975 327 5.45 -0.55 3.8 0 214.9 147.06 31858 +1975 328 7.56 1.56 5.91 0 245.35 143.6 31743 +1975 329 10.47 4.47 8.82 0 293.37 139.72 31631 +1975 330 9.2 3.2 7.55 0.2 271.5 104.54 31522 +1975 331 8.84 2.84 7.19 0 265.57 138.38 31417 +1975 332 8.78 2.78 7.13 0 264.59 136.8 31316 +1975 333 5.51 -0.49 3.86 0 215.72 138.05 31218 +1975 334 5.82 -0.18 4.17 0 219.99 136.76 31125 +1975 335 2.51 -3.49 0.86 0.14 177.93 103.13 31035 +1975 336 1.76 -4.24 0.11 0 169.43 136.8 30949 +1975 337 2.08 -3.92 0.43 0 173.01 134.97 30867 +1975 338 1.55 -4.45 -0.1 0 167.11 134.28 30790 +1975 339 -0.85 -6.85 -2.5 0 142.52 134.55 30716 +1975 340 -0.8 -6.8 -2.45 0 143 133.78 30647 +1975 341 1.02 -4.98 -0.63 0 161.39 132.07 30582 +1975 342 0.31 -5.69 -1.34 0.02 153.98 98.71 30521 +1975 343 1.47 -4.53 -0.18 0 166.24 130.26 30465 +1975 344 -0.32 -6.32 -1.97 0 147.66 129.91 30413 +1975 345 5.38 -0.62 3.73 0 213.95 126.62 30366 +1975 346 4.56 -1.44 2.91 0 203.07 126.55 30323 +1975 347 1.2 -4.8 -0.45 0 163.31 127.66 30284 +1975 348 0.56 -5.44 -1.09 0 156.56 127.59 30251 +1975 349 -0.1 -6.1 -1.75 0 149.84 127.49 30221 +1975 350 3.78 -2.22 2.13 0 193.17 125.32 30197 +1975 351 0.26 -5.74 -1.39 0 153.47 126.78 30177 +1975 352 3.52 -2.48 1.87 0 189.96 125.14 30162 +1975 353 4.84 -1.16 3.19 0.12 206.73 93.27 30151 +1975 354 8.16 2.16 6.51 0.24 254.65 91.65 30145 +1975 355 8.27 2.27 6.62 0 256.39 122.13 30144 +1975 356 8.21 2.21 6.56 0.35 255.44 91.65 30147 +1975 357 9.44 3.44 7.79 1.06 275.52 91.01 30156 +1975 358 8.69 2.69 7.04 0.01 263.12 91.49 30169 +1975 359 4.43 -1.57 2.78 0 201.39 124.84 30186 +1975 360 6.07 0.07 4.42 0 223.49 124.24 30208 +1975 361 3.47 -2.53 1.82 1.41 189.35 94.54 30235 +1975 362 0.28 -5.72 -1.37 0 153.68 128.01 30267 +1975 363 5.14 -0.86 3.49 0 210.72 126.15 30303 +1975 364 2.6 -3.4 0.95 0 178.98 127.93 30343 +1975 365 -0.55 -6.55 -2.2 0 145.41 129.92 30388 +1976 1 -0.98 -6.98 -2.63 0.46 141.28 143.06 30438 +1976 2 -0.19 -6.19 -1.84 0.18 148.95 143.86 30492 +1976 3 -0.26 -6.26 -1.91 0.03 148.25 144.61 30551 +1976 4 0.43 -5.57 -1.22 0.14 155.21 144.92 30614 +1976 5 6.07 0.07 4.42 0.35 223.49 142.25 30681 +1976 6 5.57 -0.43 3.92 0.1 216.54 142.31 30752 +1976 7 5.4 -0.6 3.75 0 214.22 132.74 30828 +1976 8 1.35 -4.65 -0.3 0.21 164.93 102.33 30907 +1976 9 0.89 -5.11 -0.76 0.06 160.01 103.44 30991 +1976 10 0.36 -5.64 -1.29 0.99 154.5 104.6 31079 +1976 11 0.45 -5.55 -1.2 0.04 155.42 105.32 31171 +1976 12 4.64 -1.36 2.99 0 204.11 139.22 31266 +1976 13 3.84 -2.16 2.19 0 193.91 141.32 31366 +1976 14 0.5 -5.5 -1.15 0 155.94 144.55 31469 +1976 15 0.48 -5.52 -1.17 0 155.73 146.01 31575 +1976 16 5.86 -0.14 4.21 0 220.55 144.25 31686 +1976 17 7.43 1.43 5.78 0 243.37 144.8 31800 +1976 18 3.84 -2.16 2.19 0 193.91 149.1 31917 +1976 19 4.4 -1.6 2.75 0.01 201 113.02 32038 +1976 20 1.18 -4.82 -0.47 0 163.1 154.11 32161 +1976 21 6.72 0.72 5.07 0 232.81 152.68 32289 +1976 22 5.5 -0.5 3.85 0 215.58 155.29 32419 +1976 23 8.04 2.04 6.39 0.14 252.77 116.35 32552 +1976 24 9.06 3.06 7.41 0.09 269.18 117.23 32688 +1976 25 8.81 2.81 7.16 0 265.08 158.38 32827 +1976 26 10.34 4.34 8.69 0 291.06 158.86 32969 +1976 27 7.67 1.67 6.02 0.2 247.03 122.43 33114 +1976 28 6.3 0.3 4.65 0.03 226.75 124.89 33261 +1976 29 4.95 -1.05 3.3 0 208.18 169.89 33411 +1976 30 0.78 -5.22 -0.87 0.03 158.85 131.05 33564 +1976 31 1.29 -4.71 -0.36 0.52 164.28 132.63 33718 +1976 32 3.38 -2.62 1.73 0 188.25 177.68 33875 +1976 33 3.71 -2.29 2.06 0 192.3 180.1 34035 +1976 34 0.35 -5.65 -1.3 0 154.39 184.36 34196 +1976 35 0.93 -5.07 -0.72 0 160.43 186.2 34360 +1976 36 -1.65 -7.65 -3.3 0.14 135.05 181.2 34526 +1976 37 0.4 -5.6 -1.25 0.02 154.91 182 34694 +1976 38 -0.18 -6.18 -1.83 0.12 149.05 184.46 34863 +1976 39 0.17 -5.83 -1.48 0.31 152.56 186.09 35035 +1976 40 -1.99 -7.99 -3.64 0 131.98 238.94 35208 +1976 41 1.61 -4.39 -0.04 0 167.77 239.2 35383 +1976 42 4.1 -1.9 2.45 0 197.18 202.29 35560 +1976 43 8.22 2.22 6.57 0 255.6 201.41 35738 +1976 44 6.8 0.8 5.15 0 233.98 205.3 35918 +1976 45 5.35 -0.65 3.7 0 213.54 209.19 36099 +1976 46 3.48 -2.52 1.83 0 189.47 213.36 36282 +1976 47 3.55 -2.45 1.9 0.1 190.33 162.11 36466 +1976 48 4.85 -1.15 3.2 0 206.86 217.92 36652 +1976 49 3.7 -2.3 2.05 0 192.17 221.63 36838 +1976 50 3.93 -2.07 2.28 0 195.04 224.13 37026 +1976 51 1.94 -4.06 0.29 0 171.44 228.61 37215 +1976 52 1.8 -4.2 0.15 0 169.87 231.57 37405 +1976 53 2.84 -3.16 1.19 0 181.79 233.78 37596 +1976 54 3.69 -2.31 2.04 0 192.05 235.88 37788 +1976 55 4.88 -1.12 3.23 0 207.26 237.87 37981 +1976 56 3.7 -2.3 2.05 0 192.17 241.59 38175 +1976 57 4.69 -1.31 3.04 0.1 204.76 182.73 38370 +1976 58 3.49 -2.51 1.84 0 189.59 247.62 38565 +1976 59 4.6 -1.4 2.95 0 203.59 249.38 38761 +1976 60 10.8 4.8 9.15 0 299.29 245.32 38958 +1976 61 8.1 2.1 6.45 0 253.71 251.6 39156 +1976 62 7.88 1.88 6.23 0.04 250.27 190.98 39355 +1976 63 7.97 1.97 6.32 0 251.67 257.53 39553 +1976 64 4.19 -1.81 2.54 0.32 198.32 198.27 39753 +1976 65 6.26 0.26 4.61 0.01 226.18 198.91 39953 +1976 66 5.04 -0.96 3.39 0.07 209.38 201.91 40154 +1976 67 7.6 1.6 5.95 0.01 245.96 202.02 40355 +1976 68 4.55 -1.45 2.9 0.06 202.94 206.63 40556 +1976 69 4.49 -1.51 2.84 0.47 202.16 208.66 40758 +1976 70 3.39 -2.61 1.74 0 188.37 282.12 40960 +1976 71 2.42 -3.58 0.77 0.18 176.89 214.45 41163 +1976 72 4.6 -1.4 2.95 0.07 203.59 215.07 41366 +1976 73 3.22 -2.78 1.57 0.42 186.32 218.09 41569 +1976 74 6.06 0.06 4.41 0 223.35 290.66 41772 +1976 75 3.44 -2.56 1.79 0 188.98 296.12 41976 +1976 76 4.31 -1.69 2.66 0.84 199.85 223.45 42179 +1976 77 3.05 -2.95 1.4 0.09 184.28 226.35 42383 +1976 78 1.14 -4.86 -0.51 0 162.67 306.21 42587 +1976 79 5.52 -0.48 3.87 0 215.86 304.72 42791 +1976 80 12.25 6.25 10.6 0 326.54 297.82 42996 +1976 81 8.86 2.86 7.21 0 265.89 305.66 43200 +1976 82 4.06 -1.94 2.41 0 196.67 314.15 43404 +1976 83 7.82 1.82 6.17 0 249.34 312.23 43608 +1976 84 3.36 -2.64 1.71 0 188.01 319.97 43812 +1976 85 5.41 -0.59 3.76 0 214.36 320.3 44016 +1976 86 5.92 -0.08 4.27 0 221.39 322.13 44220 +1976 87 6.09 0.09 4.44 0 223.77 324.48 44424 +1976 88 1.23 -4.77 -0.42 0.22 163.64 248.98 44627 +1976 89 5.34 -0.66 3.69 0.14 213.41 247.55 44831 +1976 90 4.75 -1.25 3.1 0 205.55 333.15 45034 +1976 91 12.56 6.56 10.91 1.01 332.64 242.91 45237 +1976 92 11.75 5.75 10.1 0.24 316.91 245.69 45439 +1976 93 13.65 7.65 12 0.36 354.84 244.62 45642 +1976 94 13.42 7.42 11.77 2.14 350.05 246.56 45843 +1976 95 10.2 4.2 8.55 0.63 288.6 252.56 46045 +1976 96 10.16 4.16 8.51 0.05 287.9 254.2 46246 +1976 97 9.75 3.75 8.1 0.78 280.79 256.24 46446 +1976 98 6.84 0.84 5.19 0.08 234.57 260.97 46647 +1976 99 2.44 -3.56 0.79 0 177.12 355.21 46846 +1976 100 5.05 -0.95 3.4 0 209.51 354.29 47045 +1976 101 1.21 -4.79 -0.44 0 163.42 360.42 47243 +1976 102 3.89 -2.11 2.24 0.06 194.54 269.69 47441 +1976 103 6.37 0.37 4.72 0.38 227.75 268.8 47638 +1976 104 8.18 2.18 6.53 0.05 254.97 268.25 47834 +1976 105 11.18 5.18 9.53 0 306.24 354.47 48030 +1976 106 11.45 5.45 9.8 0 311.26 355.63 48225 +1976 107 16.82 10.82 15.17 0.01 426.76 259.06 48419 +1976 108 17.24 11.24 15.59 0 437.16 346.02 48612 +1976 109 17.57 11.57 15.92 0 445.49 346.7 48804 +1976 110 18.78 12.78 17.13 0 477.17 344.65 48995 +1976 111 17.59 11.59 15.94 0.03 446 262.15 49185 +1976 112 16.47 10.47 14.82 0.12 418.26 265.5 49374 +1976 113 19.19 13.19 17.54 0 488.33 347.7 49561 +1976 114 22.09 16.09 20.44 0 573.81 339.58 49748 +1976 115 20.66 14.66 19.01 0.01 530.2 259.4 49933 +1976 116 22.39 16.39 20.74 0.31 583.34 255.75 50117 +1976 117 19.54 13.54 17.89 0 498.04 351.9 50300 +1976 118 17.85 11.85 16.2 0.02 452.65 268.66 50481 +1976 119 16.86 10.86 15.21 0.01 427.74 271.59 50661 +1976 120 13.22 7.22 11.57 1.07 345.94 279.08 50840 +1976 121 14.49 8.49 12.84 0 372.81 370.37 51016 +1976 122 19.15 13.15 17.5 0.06 487.23 269.21 51191 +1976 123 21.66 15.66 20.01 0.08 560.39 263.69 51365 +1976 124 18.42 12.42 16.77 0 467.55 363.22 51536 +1976 125 15.53 9.53 13.88 2.83 396.12 279.09 51706 +1976 126 14.86 8.86 13.21 1.75 380.96 281.08 51874 +1976 127 14.81 8.81 13.16 1.13 379.85 281.84 52039 +1976 128 16.87 10.87 15.22 0 427.99 371.46 52203 +1976 129 18.28 12.28 16.63 0 463.85 368.27 52365 +1976 130 18.72 12.72 17.07 0.21 475.56 275.79 52524 +1976 131 14.95 8.95 13.3 0.03 382.97 284.16 52681 +1976 132 13.89 7.89 12.24 0 359.9 382.24 52836 +1976 133 18.35 12.35 16.7 0 465.7 371.13 52989 +1976 134 19.23 13.23 17.58 0 489.43 369.1 53138 +1976 135 16.82 10.82 15.17 0 426.76 376.94 53286 +1976 136 15.21 9.21 13.56 0 388.82 381.83 53430 +1976 137 16.18 10.18 14.53 0 411.32 380.02 53572 +1976 138 16.92 10.92 15.27 0 429.22 378.6 53711 +1976 139 22.1 16.1 20.45 0.17 574.13 271.82 53848 +1976 140 23.49 17.49 21.84 0 619.42 357.45 53981 +1976 141 18.57 12.57 16.92 0.1 471.54 281.52 54111 +1976 142 16.31 10.31 14.66 0 414.42 382.39 54238 +1976 143 19.84 13.84 18.19 0 506.48 372.32 54362 +1976 144 20.79 14.79 19.14 0 534.04 369.54 54483 +1976 145 20.16 14.16 18.51 0.04 515.63 279.13 54600 +1976 146 20.56 14.56 18.91 0.19 527.26 278.38 54714 +1976 147 16.88 10.88 15.23 0.28 428.23 287.37 54824 +1976 148 17.21 11.21 15.56 0.06 436.41 286.96 54931 +1976 149 17.8 11.8 16.15 0.01 451.37 285.9 55034 +1976 150 17.81 11.81 16.16 0.05 451.62 286.13 55134 +1976 151 16.58 10.58 14.93 0 420.91 385.43 55229 +1976 152 19.81 13.81 18.16 0 505.63 375.71 55321 +1976 153 23.39 17.39 21.74 0 616.06 362.7 55409 +1976 154 21.03 15.03 19.38 0 541.2 372.04 55492 +1976 155 19.9 13.9 18.25 0.03 508.19 282.11 55572 +1976 156 26.87 20.87 25.22 0.07 742.37 260.87 55648 +1976 157 26.3 20.3 24.65 0.11 720.29 263.07 55719 +1976 158 25.99 19.99 24.34 0.09 708.52 264.3 55786 +1976 159 21.41 15.41 19.76 0 552.71 371.75 55849 +1976 160 23.05 17.05 21.4 0 604.77 365.63 55908 +1976 161 20.26 14.26 18.61 0 518.51 376.07 55962 +1976 162 19.54 13.54 17.89 0 498.04 378.56 56011 +1976 163 20.52 14.52 18.87 0 526.08 375.45 56056 +1976 164 16.34 10.34 14.69 0.49 415.13 291.34 56097 +1976 165 16.71 10.71 15.06 0.32 424.07 290.65 56133 +1976 166 18.93 12.93 17.28 0.03 481.23 285.73 56165 +1976 167 18.39 12.39 16.74 0.72 466.76 286.96 56192 +1976 168 16.84 10.84 15.19 0 427.25 387.27 56214 +1976 169 18.93 12.93 17.28 0 481.23 381 56231 +1976 170 24.45 18.45 22.8 0.19 652.44 270.27 56244 +1976 171 21.09 15.09 19.44 0 543 373.74 56252 +1976 172 18.05 12.05 16.4 0 457.83 383.79 56256 +1976 173 22.23 16.23 20.58 0 578.24 369.47 56255 +1976 174 18.92 12.92 17.27 0.45 480.96 285.74 56249 +1976 175 19.32 13.32 17.67 1.48 491.92 284.75 56238 +1976 176 23.6 17.6 21.95 0.29 623.13 272.89 56223 +1976 177 25.53 19.53 23.88 0.88 691.36 266.48 56203 +1976 178 26.49 20.49 24.84 0.18 727.59 263.1 56179 +1976 179 19.63 13.63 17.98 0.01 500.56 283.82 56150 +1976 180 21.3 15.3 19.65 0.03 549.35 279.38 56116 +1976 181 19.16 13.16 17.51 0.18 487.51 284.83 56078 +1976 182 19.02 13.02 17.37 0.16 483.68 285.06 56035 +1976 183 15.21 9.21 13.56 1 388.82 293.12 55987 +1976 184 16.69 10.69 15.04 2.89 423.59 290.03 55935 +1976 185 14.24 8.24 12.59 0.07 367.38 294.74 55879 +1976 186 13.69 7.69 12.04 0 355.68 394.03 55818 +1976 187 12.07 6.07 10.42 0 323.05 397.44 55753 +1976 188 17.01 11.01 15.36 0 431.44 385 55684 +1976 189 20.86 14.86 19.21 0.75 536.12 279.43 55611 +1976 190 21.34 15.34 19.69 0 550.57 370.48 55533 +1976 191 23.93 17.93 22.28 0.29 634.38 270.06 55451 +1976 192 24.3 18.3 22.65 0 647.19 358.22 55366 +1976 193 22.3 16.3 20.65 0.03 580.46 274.55 55276 +1976 194 27.52 21.52 25.87 0 768.23 342.67 55182 +1976 195 23.48 17.48 21.83 0 619.08 360.9 55085 +1976 196 23.6 17.6 21.95 0 623.13 360.01 54984 +1976 197 24.71 18.71 23.06 0 661.64 354.86 54879 +1976 198 22.55 16.55 20.9 0.05 588.47 272.5 54770 +1976 199 25.58 19.58 23.93 0.07 693.21 262.67 54658 +1976 200 25.22 19.22 23.57 0 679.99 351.47 54542 +1976 201 27.32 21.32 25.67 0.05 760.19 255.8 54423 +1976 202 27.64 21.64 25.99 0.07 773.09 254.19 54301 +1976 203 20.33 14.33 18.68 0 520.54 369.13 54176 +1976 204 20.67 14.67 19.02 0.01 530.49 275.59 54047 +1976 205 22.61 16.61 20.96 0 590.41 359.84 53915 +1976 206 27.47 21.47 25.82 0 766.21 337.81 53780 +1976 207 30.49 24.49 28.84 0.8 896.31 240.56 53643 +1976 208 29.85 23.85 28.2 1.1 867.29 242.89 53502 +1976 209 33.48 27.48 31.83 0 1042.97 300.56 53359 +1976 210 32.57 26.57 30.92 0 996.35 306.12 53213 +1976 211 31.65 25.65 30 0 951 311.29 53064 +1976 212 28.76 22.76 27.11 0 819.68 327.25 52913 +1976 213 19.68 13.68 18.03 0.01 501.96 273.58 52760 +1976 214 19.86 13.86 18.21 0 507.05 363.43 52604 +1976 215 20.63 14.63 18.98 0 529.31 360.19 52445 +1976 216 15.86 9.86 14.21 0 403.78 373.35 52285 +1976 217 18.41 12.41 16.76 0.11 467.28 274.02 52122 +1976 218 17.59 11.59 15.94 0 446 366.92 51958 +1976 219 20.1 14.1 18.45 0 513.9 358.2 51791 +1976 220 22.51 16.51 20.86 0.47 587.18 261.61 51622 +1976 221 21.08 15.08 19.43 0.52 542.7 264.73 51451 +1976 222 23.61 17.61 21.96 0 623.47 342.57 51279 +1976 223 21.29 15.29 19.64 0.18 549.05 262.55 51105 +1976 224 23.72 17.72 22.07 0.03 627.2 255 50929 +1976 225 17.84 11.84 16.19 0 452.4 358.73 50751 +1976 226 17.81 11.81 16.16 0.92 451.62 268.24 50572 +1976 227 16.95 10.95 15.3 0.54 429.96 269.04 50392 +1976 228 15.34 9.34 13.69 0 391.77 361.6 50210 +1976 229 17.57 11.57 15.92 0.05 445.49 265.91 50026 +1976 230 16.88 10.88 15.23 0.18 428.23 266.34 49842 +1976 231 19.82 13.82 18.17 0.01 505.92 258.87 49656 +1976 232 21.78 15.78 20.13 0 564.11 337.34 49469 +1976 233 21.65 15.65 20 0 560.08 336.39 49280 +1976 234 21.22 15.22 19.57 0 546.93 336.46 49091 +1976 235 20.35 14.35 18.7 0.4 521.12 253.37 48900 +1976 236 19.95 13.95 18.3 0.27 509.61 253.25 48709 +1976 237 19.55 13.55 17.9 0 498.32 337.25 48516 +1976 238 17.09 11.09 15.44 0 433.42 342.5 48323 +1976 239 18.61 12.61 16.96 0 472.61 336.83 48128 +1976 240 18.67 12.67 17.02 0 474.21 334.9 47933 +1976 241 18.88 12.88 17.23 0 479.87 332.57 47737 +1976 242 24.73 18.73 23.08 0.04 662.35 233.29 47541 +1976 243 25.32 19.32 23.67 0.08 683.64 230.18 47343 +1976 244 20.85 14.85 19.2 1.43 535.82 240.94 47145 +1976 245 18.87 12.87 17.22 0.8 479.6 244.01 46947 +1976 246 16.49 10.49 14.84 0.16 418.74 247.22 46747 +1976 247 16.02 10.02 14.37 0 407.53 328.88 46547 +1976 248 21.54 15.54 19.89 0 556.69 311.6 46347 +1976 249 19.03 13.03 17.38 0.04 483.95 237.84 46146 +1976 250 21.82 15.82 20.17 0.37 565.35 230.09 45945 +1976 251 22.11 16.11 20.46 0 574.44 303.79 45743 +1976 252 20.49 14.49 18.84 0.05 525.2 230.07 45541 +1976 253 18.71 12.71 17.06 0.25 475.29 232.29 45339 +1976 254 12.01 6.01 10.36 0 321.89 322.4 45136 +1976 255 9.83 3.83 8.18 0 282.17 323.72 44933 +1976 256 10.34 4.34 8.69 0.11 291.06 240.43 44730 +1976 257 7.56 1.56 5.91 0.07 245.35 241.8 44527 +1976 258 9.42 3.42 7.77 0.23 275.19 238 44323 +1976 259 11.83 5.83 10.18 0 318.44 310.96 44119 +1976 260 10.88 4.88 9.23 0 300.74 310.1 43915 +1976 261 14.91 8.91 13.26 0 382.08 300.24 43711 +1976 262 17.71 11.71 16.06 0.31 449.06 218.72 43507 +1976 263 17.56 11.56 15.91 0.01 445.23 217.16 43303 +1976 264 22.73 16.73 21.08 0 594.29 272.82 43099 +1976 265 17.09 11.09 15.44 0.44 433.42 214.3 42894 +1976 266 19.59 13.59 17.94 0.24 499.44 207.89 42690 +1976 267 20.11 14.11 18.46 0 514.19 273.2 42486 +1976 268 18.82 12.82 17.17 0 478.25 274.01 42282 +1976 269 17.77 11.77 16.12 0 450.6 274.05 42078 +1976 270 19.11 13.11 17.46 0 486.14 268.26 41875 +1976 271 20.33 14.33 18.68 2.6 520.54 196.95 41671 +1976 272 19.27 13.27 17.62 1.72 490.54 196.98 41468 +1976 273 16.76 10.76 15.11 0.14 425.29 199.42 41265 +1976 274 13.53 7.53 11.88 0 352.34 269.42 41062 +1976 275 13.4 7.4 11.75 0 349.64 266.87 40860 +1976 276 16.48 10.48 14.83 0 418.5 258.43 40658 +1976 277 14.67 8.67 13.02 0 376.76 259.27 40456 +1976 278 19.2 13.2 17.55 0 488.61 247.08 40255 +1976 279 18.38 12.38 16.73 0 466.49 246.22 40054 +1976 280 15.68 9.68 14.03 1.45 399.59 186.85 39854 +1976 281 13.45 7.45 11.8 0.08 350.68 187.76 39654 +1976 282 9.61 3.61 7.96 0.04 278.4 189.86 39455 +1976 283 9.31 3.31 7.66 0 273.34 250.66 39256 +1976 284 4.68 -1.32 3.03 0 204.63 252.55 39058 +1976 285 4.94 -1.06 3.29 0 208.05 249.59 38861 +1976 286 7.79 1.79 6.14 0 248.88 243.88 38664 +1976 287 13.73 7.73 12.08 0 356.52 233.02 38468 +1976 288 14.59 8.59 12.94 0 375 228.87 38273 +1976 289 15.76 9.76 14.11 0.07 401.44 168.22 38079 +1976 290 18.23 12.23 16.58 0 462.54 216.86 37885 +1976 291 18.69 12.69 17.04 0.37 474.75 160 37693 +1976 292 16.84 10.84 15.19 0 427.25 214.29 37501 +1976 293 18.35 12.35 16.7 0.11 465.7 156.59 37311 +1976 294 12.16 6.16 10.51 0.09 324.79 162.08 37121 +1976 295 10.31 4.31 8.66 0.58 290.53 161.72 36933 +1976 296 7.29 1.29 5.64 0.05 241.26 162.21 36745 +1976 297 6.05 0.05 4.4 0 223.21 214.67 36560 +1976 298 9.03 3.03 7.38 0 268.69 209.11 36375 +1976 299 11.01 5.01 9.36 0 303.11 204.06 36191 +1976 300 18.3 12.3 16.65 0 464.38 190.5 36009 +1976 301 18.88 12.88 17.23 0.24 479.87 140.26 35829 +1976 302 18.02 12.02 16.37 0.34 457.05 139.56 35650 +1976 303 17.5 11.5 15.85 1.27 443.71 138.38 35472 +1976 304 13.32 7.32 11.67 0.78 347.99 141.31 35296 +1976 305 9.77 3.77 8.12 0.85 281.14 142.42 35122 +1976 306 11.36 5.36 9.71 0 309.57 185.9 34950 +1976 307 12.84 6.84 11.19 0.06 338.22 136.23 34779 +1976 308 9.08 3.08 7.43 0 269.51 183.23 34610 +1976 309 11.6 5.6 9.95 0 314.07 178.26 34444 +1976 310 11.84 5.84 10.19 0 318.63 175.57 34279 +1976 311 10.64 4.64 8.99 0.01 296.41 131.05 34116 +1976 312 7.78 1.78 6.13 0 248.73 174.85 33956 +1976 313 8.22 2.22 6.57 0.14 255.6 129.25 33797 +1976 314 7.52 1.52 5.87 0 244.74 170.99 33641 +1976 315 6.12 0.12 4.47 0 224.2 169.57 33488 +1976 316 4.31 -1.69 2.66 0 199.85 168.67 33337 +1976 317 4.49 -1.51 2.84 0 202.16 166.33 33188 +1976 318 3.34 -2.66 1.69 0.63 187.77 123.54 33042 +1976 319 3.6 -2.4 1.95 0 190.94 162.84 32899 +1976 320 7.42 1.42 5.77 0 243.22 158.25 32758 +1976 321 9.74 3.74 8.09 0.05 280.62 115.63 32620 +1976 322 10.13 4.13 8.48 0.59 287.37 114.01 32486 +1976 323 9.05 3.05 7.4 0 269.02 151.38 32354 +1976 324 7.51 1.51 5.86 0 244.59 150.6 32225 +1976 325 8.55 2.55 6.9 0.3 260.86 111.04 32100 +1976 326 7.94 1.94 6.29 1.89 251.21 110.33 31977 +1976 327 8.43 2.43 6.78 0.14 258.94 108.66 31858 +1976 328 10.94 4.94 9.29 0 301.83 140.75 31743 +1976 329 11.27 5.27 9.62 0 307.9 138.98 31631 +1976 330 15.1 9.1 13.45 0 386.34 133.52 31522 +1976 331 9.48 3.48 7.83 0 276.2 137.85 31417 +1976 332 11.61 5.61 9.96 0 314.26 134.34 31316 +1976 333 12.75 6.75 11.1 0 336.42 132.18 31218 +1976 334 13.27 7.27 11.62 0 346.96 130.59 31125 +1976 335 4.09 -1.91 2.44 0.39 197.05 102.48 31035 +1976 336 5.04 -0.96 3.39 0.28 209.38 101.25 30949 +1976 337 7.57 1.57 5.92 0.83 245.5 98.75 30867 +1976 338 6.65 0.65 5 0 231.79 131.37 30790 +1976 339 7.04 1.04 5.39 0.1 237.52 97.75 30716 +1976 340 7.66 1.66 6.01 0.05 246.88 96.88 30647 +1976 341 1.47 -4.53 -0.18 1.34 166.24 98.89 30582 +1976 342 2.13 -3.87 0.48 0.08 173.58 98.08 30521 +1976 343 3.53 -2.47 1.88 0.4 190.08 96.92 30465 +1976 344 -0.2 -6.2 -1.85 0.03 148.85 140.89 30413 +1976 345 2.95 -3.05 1.3 0.04 183.09 95.98 30366 +1976 346 3.84 -2.16 2.19 0 193.91 126.95 30323 +1976 347 2.81 -3.19 1.16 0.01 181.43 95.17 30284 +1976 348 3.15 -2.85 1.5 0 185.47 126.37 30251 +1976 349 7.3 1.3 5.65 0 241.41 123.53 30221 +1976 350 2.37 -3.63 0.72 0 176.32 126.04 30197 +1976 351 3.69 -2.31 2.04 0.02 192.05 93.86 30177 +1976 352 4.67 -1.33 3.02 0 204.5 124.52 30162 +1976 353 2.62 -3.38 0.97 1.43 179.21 94.15 30151 +1976 354 1.21 -4.79 -0.44 0.6 163.42 94.63 30145 +1976 355 0.64 -5.36 -1.01 0.08 157.39 94.81 30144 +1976 356 -2.03 -8.03 -3.68 0.42 131.62 140.75 30147 +1976 357 0.19 -5.81 -1.46 0.22 152.76 140.11 30156 +1976 358 4.43 -1.57 2.78 0.08 201.39 138.02 30169 +1976 359 -1.1 -7.1 -2.75 0.04 140.15 140.14 30186 +1976 360 -2.4 -8.4 -4.05 0.38 128.35 141.95 30208 +1976 361 -1.04 -7.04 -2.69 0 140.71 173.82 30235 +1976 362 1.54 -4.46 -0.11 0 167 172.91 30267 +1976 363 5.61 -0.39 3.96 0.08 217.09 139.06 30303 +1976 364 2.36 -3.64 0.71 0 176.2 172.33 30343 +1976 365 1.35 -4.65 -0.3 1 164.93 140.86 30388 +1977 1 1.83 -4.17 0.18 0.01 170.21 141.05 30438 +1977 2 1.12 -4.88 -0.53 0.05 162.45 141.63 30492 +1977 3 5.18 -0.82 3.53 0 211.25 129.65 30551 +1977 4 5.25 -0.75 3.6 0 212.19 130.51 30614 +1977 5 3.36 -2.64 1.71 0 188.01 132.24 30681 +1977 6 3.04 -2.96 1.39 0.44 184.16 99.97 30752 +1977 7 -0.59 -6.59 -2.24 0.01 145.02 144.71 30828 +1977 8 1.24 -4.76 -0.41 1.19 163.74 102.37 30907 +1977 9 -2.17 -8.17 -3.82 0.79 130.38 149.44 30991 +1977 10 1.89 -4.11 0.24 1.79 170.88 148.73 31079 +1977 11 2.88 -3.12 1.23 0 182.26 183.38 31171 +1977 12 5.96 -0.04 4.31 0 221.95 181.65 31266 +1977 13 10.48 4.48 8.83 0.03 293.55 102.38 31366 +1977 14 6.79 0.79 5.14 0.13 233.83 105.67 31469 +1977 15 8.26 2.26 6.61 0.14 256.23 105.92 31575 +1977 16 4.45 -1.55 2.8 0.02 201.65 108.87 31686 +1977 17 4.57 -1.43 2.92 0.14 203.2 110.07 31800 +1977 18 2.29 -3.71 0.64 0 175.4 149.99 31917 +1977 19 4.87 -1.13 3.22 0 207.13 150.39 32038 +1977 20 3.4 -2.6 1.75 0 188.49 152.89 32161 +1977 21 0.98 -5.02 -0.67 0.01 160.96 117.17 32289 +1977 22 1.07 -4.93 -0.58 0.77 161.92 118.46 32419 +1977 23 4.31 -1.69 2.66 0.28 199.85 118.39 32552 +1977 24 2.95 -3.05 1.3 0.17 183.09 120.57 32688 +1977 25 3.1 -2.9 1.45 0 184.88 162.56 32827 +1977 26 3.66 -2.34 2.01 0.01 191.68 123.11 32969 +1977 27 4.1 -1.9 2.45 0 197.18 165.88 33114 +1977 28 0.76 -5.24 -0.89 0.04 158.64 127.56 33261 +1977 29 1.97 -4.03 0.32 0 171.77 171.8 33411 +1977 30 5.08 -0.92 3.43 0 209.91 172.03 33564 +1977 31 4.6 -1.4 2.95 0 203.59 174.74 33718 +1977 32 6.9 0.9 5.25 0 235.45 175.09 33875 +1977 33 9.99 3.99 8.34 0 284.93 174.86 34035 +1977 34 13.51 7.51 11.86 0 351.92 173.02 34196 +1977 35 11.19 5.19 9.54 0.26 306.42 133.39 34360 +1977 36 10.3 4.3 8.65 0.01 290.36 135.95 34526 +1977 37 12.26 6.26 10.61 0.12 326.74 136.07 34694 +1977 38 11.82 5.82 10.17 0.46 318.25 138.47 34863 +1977 39 8.42 2.42 6.77 0 258.78 190.83 35035 +1977 40 4.89 -1.11 3.24 0.1 207.39 147.38 35208 +1977 41 4.68 -1.32 3.03 0.31 204.63 149.46 35383 +1977 42 3.85 -2.15 2.2 0.02 194.04 151.85 35560 +1977 43 3.32 -2.68 1.67 1.96 187.52 154.18 35738 +1977 44 4 -2 2.35 0.19 195.92 155.73 35918 +1977 45 6.49 0.49 4.84 0 229.48 208.19 36099 +1977 46 6.14 0.14 4.49 0 224.48 211.18 36282 +1977 47 8.76 2.76 7.11 0.05 264.26 158.57 36466 +1977 48 11.58 5.58 9.93 0.76 313.7 158.17 36652 +1977 49 11.77 5.77 10.12 0.05 317.3 160.02 36838 +1977 50 8.75 2.75 7.1 0.69 264.1 164.7 37026 +1977 51 5.65 -0.35 4 0.35 217.64 169.22 37215 +1977 52 3.96 -2.04 2.31 0.15 195.41 172.44 37405 +1977 53 1.93 -4.07 0.28 0.03 171.33 175.85 37596 +1977 54 0.71 -5.29 -0.94 0.01 158.12 178.57 37788 +1977 55 4.95 -1.05 3.3 0 208.18 237.81 37981 +1977 56 8.19 2.19 6.54 0 255.13 237.25 38175 +1977 57 5.55 -0.45 3.9 0 216.27 242.84 38370 +1977 58 4.02 -1.98 2.37 0.04 196.17 185.38 38565 +1977 59 3.63 -2.37 1.98 0.23 191.31 187.67 38761 +1977 60 10.98 4.98 9.33 0 302.56 245.08 38958 +1977 61 13.99 7.99 12.34 0 362.02 243.4 39156 +1977 62 11.75 5.75 10.1 0.17 316.91 187.21 39355 +1977 63 8.09 2.09 6.44 0 253.55 257.39 39553 +1977 64 9.62 3.62 7.97 0 278.57 258.38 39753 +1977 65 6.82 0.82 5.17 0 234.27 264.61 39953 +1977 66 8.38 2.38 6.73 0 258.14 265.53 40154 +1977 67 9.27 3.27 7.62 0 272.67 267.29 40355 +1977 68 13.53 7.53 11.88 0 352.34 263.74 40556 +1977 69 15.58 9.58 13.93 0 397.27 262.55 40758 +1977 70 17.78 11.78 16.13 0 450.85 260.7 40960 +1977 71 16.16 10.16 14.51 0 410.84 266.95 41163 +1977 72 12.63 6.63 10.98 0.9 334.03 207.17 41366 +1977 73 15.28 9.28 13.63 0 390.41 274.02 41569 +1977 74 14.83 8.83 13.18 0.17 380.3 208.17 41772 +1977 75 12.81 6.81 11.16 0.95 337.62 212.93 41976 +1977 76 7.29 1.29 5.64 0 241.26 294.6 42179 +1977 77 9.09 3.09 7.44 0.49 269.68 221.14 42383 +1977 78 11.51 5.51 9.86 0.43 312.38 220.4 42587 +1977 79 11.36 5.36 9.71 0 309.57 296.8 42791 +1977 80 10.92 4.92 9.27 0.2 301.47 225.01 42996 +1977 81 13.09 7.09 11.44 0 343.28 298.87 43200 +1977 82 12.89 6.89 11.24 0.01 339.23 226.38 43404 +1977 83 10.97 4.97 9.32 0.3 302.38 230.7 43608 +1977 84 11.55 5.55 9.9 0 313.13 309.15 43812 +1977 85 12.15 6.15 10.5 0 324.6 310.59 44016 +1977 86 10.91 4.91 9.26 0 301.29 315.09 44220 +1977 87 10.82 4.82 9.17 0.27 299.65 238.31 44424 +1977 88 7.21 1.21 5.56 0 240.06 325.43 44627 +1977 89 11.71 5.71 10.06 0 316.16 320.84 44831 +1977 90 13.07 7.07 11.42 0.03 342.87 240.51 45034 +1977 91 11.52 5.52 9.87 0 312.57 325.76 45237 +1977 92 14.17 8.17 12.52 0.01 365.87 242.19 45439 +1977 93 9.76 3.76 8.11 0 280.97 333.15 45642 +1977 94 13.61 7.61 11.96 0 354.01 328.37 45843 +1977 95 14.17 8.17 12.52 0 365.87 329.33 46045 +1977 96 16.56 10.56 14.91 0.2 420.43 244.49 46246 +1977 97 15.08 9.08 13.43 0.05 385.89 248.59 46446 +1977 98 14.19 8.19 12.54 0.69 366.3 251.49 46647 +1977 99 12.21 6.21 10.56 0.45 325.76 255.98 46846 +1977 100 12.99 6.99 11.34 0 341.25 341.73 47045 +1977 101 11.55 5.55 9.9 0 313.13 346.42 47243 +1977 102 11 5 9.35 0 302.93 349.32 47441 +1977 103 11.48 5.48 9.83 0 311.82 350.3 47638 +1977 104 9.54 3.54 7.89 0 277.21 355.52 47834 +1977 105 13.51 7.51 11.86 0.09 351.92 262.42 48030 +1977 106 12.34 6.34 10.69 0.04 328.3 265.44 48225 +1977 107 10.93 4.93 9.28 0 301.65 358.27 48419 +1977 108 11.78 5.78 10.13 0.02 317.49 268.82 48612 +1977 109 14.16 8.16 12.51 0.02 365.66 266.33 48804 +1977 110 9.59 3.59 7.94 0.11 278.06 274.07 48995 +1977 111 5.6 -0.4 3.95 2.11 216.95 279.72 49185 +1977 112 4.5 -1.5 2.85 0.29 202.29 281.94 49374 +1977 113 6.03 0.03 4.38 0.11 222.93 281.5 49561 +1977 114 10.01 4.01 8.36 0.23 285.28 278.01 49748 +1977 115 11.01 5.01 9.36 0 303.11 370.31 49933 +1977 116 14.42 8.42 12.77 0.16 371.28 273.32 50117 +1977 117 13.13 7.13 11.48 0.11 344.1 276.45 50300 +1977 118 12.28 6.28 10.63 0.27 327.13 278.78 50481 +1977 119 8.63 2.63 6.98 0.02 262.15 284.69 50661 +1977 120 9.84 3.84 8.19 0 282.34 378.73 50840 +1977 121 12.5 6.5 10.85 0 331.45 374.77 51016 +1977 122 16.59 10.59 14.94 0 421.16 366.3 51191 +1977 123 14.19 8.19 12.54 0 366.3 373.29 51365 +1977 124 14.79 8.79 13.14 0 379.41 372.96 51536 +1977 125 10.79 4.79 9.14 0.29 299.11 286.88 51706 +1977 126 12.53 6.53 10.88 0 332.04 380.04 51874 +1977 127 11.45 5.45 9.8 0 311.26 383.15 52039 +1977 128 14 8 12.35 0 362.24 378.7 52203 +1977 129 14.51 8.51 12.86 0 373.25 378.35 52365 +1977 130 20.73 14.73 19.08 0.08 532.26 270.89 52524 +1977 131 17.26 11.26 15.61 0 437.66 372.79 52681 +1977 132 15.65 9.65 14 0 398.89 377.95 52836 +1977 133 17.32 11.32 15.67 0 439.17 374.14 52989 +1977 134 18.73 12.73 17.08 0 475.82 370.67 53138 +1977 135 15.17 9.17 13.52 0 387.92 381.29 53286 +1977 136 12.98 6.98 11.33 0 341.05 387.08 53430 +1977 137 16.96 10.96 15.31 0 430.2 377.89 53572 +1977 138 20.52 14.52 18.87 0 526.08 367.43 53711 +1977 139 21.83 15.83 20.18 0 565.66 363.43 53848 +1977 140 23.65 17.65 22 0.02 624.82 267.6 53981 +1977 141 24.12 18.12 22.47 0.01 640.93 266.44 54111 +1977 142 28.9 22.9 27.25 0.01 825.67 249.54 54238 +1977 143 28.4 22.4 26.75 0.14 804.45 251.93 54362 +1977 144 26.9 20.9 25.25 0 743.54 344.02 54483 +1977 145 24.93 18.93 23.28 0.18 669.5 265.24 54600 +1977 146 19.62 13.62 17.97 1.98 500.28 280.76 54714 +1977 147 14.8 8.8 13.15 0.02 379.63 291.49 54824 +1977 148 15.78 9.78 14.13 0 401.91 386.54 54931 +1977 149 13.18 7.18 11.53 0 345.12 393.21 55034 +1977 150 15.76 9.76 14.11 0.07 401.44 290.43 55134 +1977 151 12.99 6.99 11.34 0.01 341.25 295.78 55229 +1977 152 17.07 11.07 15.42 1.59 432.93 288.12 55321 +1977 153 15.63 9.63 13.98 1.26 398.43 291.26 55409 +1977 154 16.61 10.61 14.96 0 421.64 386.02 55492 +1977 155 16.87 10.87 15.22 0 427.99 385.49 55572 +1977 156 19.14 13.14 17.49 0 486.96 378.97 55648 +1977 157 20.82 14.82 19.17 0.15 534.93 280.1 55719 +1977 158 20 14 18.35 0.11 511.04 282.35 55786 +1977 159 18.43 12.43 16.78 0.03 467.81 286.34 55849 +1977 160 17.51 11.51 15.86 0 443.96 384.74 55908 +1977 161 20.02 14.02 18.37 0 511.61 376.89 55962 +1977 162 18.9 12.9 17.25 0 480.41 380.63 56011 +1977 163 18.14 12.14 16.49 0 460.18 383.21 56056 +1977 164 21.78 15.78 20.13 0.06 564.11 278.2 56097 +1977 165 19.44 13.44 17.79 0 495.25 379.24 56133 +1977 166 23.73 17.73 22.08 0 627.54 363.39 56165 +1977 167 26.76 20.76 25.11 0 738.06 349.57 56192 +1977 168 30.47 24.47 28.82 0 895.39 329.43 56214 +1977 169 26.88 20.88 25.23 0 742.76 349.06 56231 +1977 170 26.37 20.37 24.72 0.83 722.97 263.67 56244 +1977 171 21.87 15.87 20.22 0.25 566.91 278.15 56252 +1977 172 20.08 14.08 18.43 0 513.33 377.27 56256 +1977 173 20.18 14.18 18.53 0.44 516.2 282.68 56255 +1977 174 29.26 23.26 27.61 0 841.24 336.43 56249 +1977 175 29.08 23.08 27.43 0 833.43 337.41 56238 +1977 176 28.4 22.4 26.75 0 804.45 341.1 56223 +1977 177 21.38 15.38 19.73 0.04 551.79 279.3 56203 +1977 178 22.3 16.3 20.65 0 580.46 368.98 56179 +1977 179 21.23 15.23 19.58 0 547.23 372.88 56150 +1977 180 19.59 13.59 17.94 0 499.44 378.44 56116 +1977 181 23.89 17.89 22.24 0.17 633 271.71 56078 +1977 182 26.85 20.85 25.2 0.07 741.58 261.47 56035 +1977 183 27.16 21.16 25.51 0 753.81 346.91 55987 +1977 184 24.63 18.63 22.98 0.11 658.8 268.98 55935 +1977 185 22.25 16.25 20.6 0.54 578.87 276.24 55879 +1977 186 20.82 14.82 19.17 0 534.93 373.34 55818 +1977 187 22.86 16.86 21.21 0.54 598.53 274.13 55753 +1977 188 23.8 17.8 22.15 0 629.93 361.42 55684 +1977 189 22.71 16.71 21.06 0 593.64 365.66 55611 +1977 190 28.26 22.26 26.61 0 798.6 339.81 55533 +1977 191 31.92 25.92 30.27 0 964.12 318.12 55451 +1977 192 29.01 23.01 27.36 0 830.4 335.22 55366 +1977 193 27.52 21.52 25.87 0.11 768.23 257.16 55276 +1977 194 24.88 18.88 23.23 0.06 667.71 266.41 55182 +1977 195 19.18 13.18 17.53 0 488.06 376.52 55085 +1977 196 17.74 11.74 16.09 0 449.83 380.54 54984 +1977 197 19.88 13.88 18.23 0.06 507.62 280.03 54879 +1977 198 25.5 19.5 23.85 0 690.25 350.93 54770 +1977 199 25.06 19.06 23.41 0.47 674.19 264.43 54658 +1977 200 23.93 17.93 22.28 0.68 634.38 267.79 54542 +1977 201 20.67 14.67 19.02 0.8 530.49 276.77 54423 +1977 202 17.94 11.94 16.29 3.69 454.98 282.93 54301 +1977 203 14.76 8.76 13.11 0.85 378.75 289 54176 +1977 204 13.17 7.17 11.52 0 344.91 388.54 54047 +1977 205 17.23 11.23 15.58 0 436.91 377.74 53915 +1977 206 18.15 12.15 16.5 0 460.44 374.49 53780 +1977 207 21.48 15.48 19.83 0 554.85 362.86 53643 +1977 208 20.84 14.84 19.19 0 535.53 364.48 53502 +1977 209 23.32 17.32 21.67 0 613.72 354.58 53359 +1977 210 18.11 12.11 16.46 1.15 459.4 278.99 53213 +1977 211 15.34 9.34 13.69 0 391.77 378.78 53064 +1977 212 17.98 11.98 16.33 0 456.02 370.78 52913 +1977 213 19.64 13.64 17.99 0 500.84 364.9 52760 +1977 214 20.16 14.16 18.51 0 515.63 362.45 52604 +1977 215 21.65 15.65 20 0 560.08 356.62 52445 +1977 216 23.13 17.13 21.48 0.32 607.41 262.54 52285 +1977 217 19.18 13.18 17.53 1.05 488.06 272.26 52122 +1977 218 18.75 12.75 17.1 1.15 476.36 272.63 51958 +1977 219 19.79 13.79 18.14 0.01 505.07 269.4 51791 +1977 220 21.41 15.41 19.76 0 552.71 352.81 51622 +1977 221 22.36 16.36 20.71 0 582.38 348.39 51451 +1977 222 23.9 17.9 22.25 0 633.35 341.41 51279 +1977 223 23.4 17.4 21.75 0.02 616.4 256.71 51105 +1977 224 22.79 16.79 21.14 0.34 596.25 257.7 50929 +1977 225 25.9 19.9 24.25 0 705.14 329.71 50751 +1977 226 26.26 20.26 24.61 0 718.77 327.01 50572 +1977 227 25.79 19.79 24.14 0.48 701.02 245.92 50392 +1977 228 24.02 18.02 22.37 0.21 637.47 250.63 50210 +1977 229 19.01 13.01 17.36 0.3 483.41 262.79 50026 +1977 230 19.97 13.97 18.32 1.05 510.18 259.61 49842 +1977 231 21.14 15.14 19.49 0 544.51 340.87 49656 +1977 232 23.74 17.74 22.09 0 627.88 330.12 49469 +1977 233 21.33 15.33 19.68 0.06 550.27 253.11 49280 +1977 234 21.61 15.61 19.96 0.17 558.84 251.35 49091 +1977 235 21.76 15.76 20.11 0 563.48 333.15 48900 +1977 236 23.67 17.67 22.02 0.04 625.5 243.62 48709 +1977 237 22.31 16.31 20.66 0 580.78 328.22 48516 +1977 238 18.61 12.61 16.96 0.25 472.61 253.76 48323 +1977 239 22.35 16.35 20.7 0.28 582.06 243.73 48128 +1977 240 21.52 15.52 19.87 0 556.07 326.1 47933 +1977 241 20.82 14.82 19.17 0.17 534.93 245.02 47737 +1977 242 16.94 10.94 15.29 0 429.71 336.07 47541 +1977 243 14.5 8.5 12.85 0.03 373.03 254.97 47343 +1977 244 11.87 5.87 10.22 0.1 319.2 257.57 47145 +1977 245 10.95 4.95 9.3 0.47 302.02 257.38 46947 +1977 246 10.93 4.93 9.28 1.04 301.65 255.88 46747 +1977 247 8.81 2.81 7.16 0.11 265.08 257.03 46547 +1977 248 9.81 3.81 8.16 0.12 281.82 254.33 46347 +1977 249 10.82 4.82 9.17 1.04 299.65 251.47 46146 +1977 250 13.55 7.55 11.9 0.09 352.75 246.16 45945 +1977 251 15.98 9.98 14.33 0 406.59 320.81 45743 +1977 252 19.3 13.3 17.65 0 491.36 310.2 45541 +1977 253 17.75 11.75 16.1 0 450.08 312.22 45339 +1977 254 16.63 10.63 14.98 0.05 422.13 234.63 45136 +1977 255 17.08 11.08 15.43 0 433.18 309.5 44933 +1977 256 15.57 9.57 13.92 0.04 397.04 233.03 44730 +1977 257 13.16 7.16 11.51 0 344.71 313.43 44527 +1977 258 13.05 7.05 11.4 0 342.47 311.25 44323 +1977 259 16.73 10.73 15.08 0 424.56 301.12 44119 +1977 260 22.57 16.57 20.92 0 589.12 282.76 43915 +1977 261 21.96 15.96 20.31 0 569.72 282.33 43711 +1977 262 22.33 16.33 20.68 0.07 581.42 209.17 43507 +1977 263 20.59 14.59 18.94 0.33 528.14 211.27 43303 +1977 264 19.59 13.59 17.94 0.52 499.44 211.44 43099 +1977 265 21.17 15.17 19.52 0 545.42 275.25 42894 +1977 266 16.34 10.34 14.69 0 415.13 284.93 42690 +1977 267 14.19 8.19 12.54 0 366.3 286.61 42486 +1977 268 17.4 11.4 15.75 0 441.18 277.38 42282 +1977 269 18.87 12.87 17.22 0.01 479.6 203.57 42078 +1977 270 21.05 15.05 19.4 0 541.8 263.18 41875 +1977 271 20.89 14.89 19.24 0 537.02 261.1 41671 +1977 272 17.53 11.53 15.88 0 444.47 266.72 41468 +1977 273 22.51 16.51 20.86 0 587.18 251.49 41265 +1977 274 21.26 15.26 19.61 0 548.14 252.47 41062 +1977 275 17.53 11.53 15.88 0 444.47 258.88 40860 +1977 276 12.4 6.4 10.75 0.97 329.48 199.35 40658 +1977 277 13.54 7.54 11.89 0 352.55 261.25 40456 +1977 278 10.63 4.63 8.98 0 296.23 262.86 40255 +1977 279 11.17 5.17 9.52 0 306.05 259.25 40054 +1977 280 12.2 6.2 10.55 0 325.57 255.04 39854 +1977 281 11.93 5.93 10.28 0.08 320.35 189.53 39654 +1977 282 8.94 2.94 7.29 0 267.2 253.99 39455 +1977 283 9.53 3.53 7.88 0.03 277.05 187.79 39256 +1977 284 11.86 5.86 10.21 0 319.01 244.19 39058 +1977 285 14.02 8.02 12.37 0.45 362.66 178.67 38861 +1977 286 11.87 5.87 10.22 0 319.2 238.75 38664 +1977 287 12.67 6.67 11.02 0 334.82 234.64 38468 +1977 288 13.61 7.61 11.96 0.02 354.01 172.83 38273 +1977 289 15.61 9.61 13.96 0 397.97 224.55 38079 +1977 290 15.5 9.5 13.85 0 395.43 221.93 37885 +1977 291 11.18 5.18 9.53 0 306.24 225.72 37693 +1977 292 8.83 2.83 7.18 0 265.4 225.85 37501 +1977 293 9.09 3.09 7.44 0 269.68 222.8 37311 +1977 294 11.88 5.88 10.23 0 319.39 216.49 37121 +1977 295 11.95 5.95 10.3 0 320.74 213.56 36933 +1977 296 14.89 8.89 13.24 0 381.63 206.77 36745 +1977 297 15.17 9.17 13.52 0 387.92 203.66 36560 +1977 298 16.16 10.16 14.51 0 410.84 199.51 36375 +1977 299 16.39 10.39 14.74 0 416.33 196.42 36191 +1977 300 18.26 12.26 16.61 0.38 463.33 142.93 36009 +1977 301 19.3 13.3 17.65 0 491.36 186.21 35829 +1977 302 20.47 14.47 18.82 0 524.62 181.4 35650 +1977 303 23.08 17.08 21.43 0 605.76 173.27 35472 +1977 304 21.29 15.29 19.64 0.29 549.05 131.23 35296 +1977 305 11.43 5.43 9.78 0.78 310.88 141.04 35122 +1977 306 7.79 1.79 6.14 0.22 248.88 142.19 34950 +1977 307 10.01 4.01 8.36 0.6 285.28 138.66 34779 +1977 308 8.38 2.38 6.73 0.01 258.14 137.93 34610 +1977 309 11.55 5.55 9.9 0.14 313.13 133.74 34444 +1977 310 8.1 2.1 6.45 0.08 253.71 134.54 34279 +1977 311 6.02 0.02 4.37 0.65 222.79 134.22 34116 +1977 312 4.28 -1.72 2.63 0 199.47 177.58 33956 +1977 313 2.81 -3.19 1.16 0.36 181.43 132.3 33797 +1977 314 3.26 -2.74 1.61 0.43 186.8 130.6 33641 +1977 315 1 -5 -0.65 0 161.18 172.9 33488 +1977 316 3.73 -2.27 2.08 0 192.55 169.05 33337 +1977 317 9.3 3.3 7.65 0 273.17 162.53 33188 +1977 318 7.58 1.58 5.93 0.3 245.65 121.27 33042 +1977 319 5.61 -0.39 3.96 0 217.09 161.49 32899 +1977 320 4.15 -1.85 2.5 0 197.81 160.6 32758 +1977 321 6.62 0.62 4.97 0.39 231.36 117.57 32620 +1977 322 8.54 2.54 6.89 0.15 260.7 115.07 32486 +1977 323 7.49 1.49 5.84 0.1 244.28 114.5 32354 +1977 324 8.3 2.3 6.65 0 256.87 149.97 32225 +1977 325 12.25 6.25 10.6 0.17 326.54 108.48 32100 +1977 326 12.74 6.74 11.09 0 336.22 142.71 31977 +1977 327 12.79 6.79 11.14 0 337.22 140.86 31858 +1977 328 15.42 9.42 13.77 0 393.6 135.96 31743 +1977 329 12.78 6.78 11.13 0.44 337.02 103.11 31631 +1977 330 10.82 4.82 9.17 0.33 299.65 103.48 31522 +1977 331 10.18 4.18 8.53 0.77 288.25 102.94 31417 +1977 332 9.48 3.48 7.83 0.3 276.2 102.17 31316 +1977 333 13.77 7.77 12.12 0 357.36 131.12 31218 +1977 334 16.13 10.13 14.48 0.09 410.13 95.52 31125 +1977 335 5.49 -0.51 3.84 0.14 215.45 101.85 31035 +1977 336 2.09 -3.91 0.44 0.01 173.13 102.48 30949 +1977 337 0.8 -5.2 -0.85 0 159.06 135.59 30867 +1977 338 2.22 -3.78 0.57 0.1 174.6 100.47 30790 +1977 339 0.4 -5.6 -1.25 0 154.91 134.02 30716 +1977 340 0.74 -5.26 -0.91 0 158.43 133.12 30647 +1977 341 3.63 -2.37 1.98 0 191.31 130.76 30582 +1977 342 -0.56 -6.56 -2.21 0 145.31 131.98 30521 +1977 343 4.2 -1.8 2.55 0 198.45 128.86 30465 +1977 344 5.07 -0.93 3.42 0 209.78 127.23 30413 +1977 345 4.21 -1.79 2.56 0 198.57 127.29 30366 +1977 346 9.88 3.88 8.23 0 283.03 122.95 30323 +1977 347 6.8 0.8 5.15 0.02 233.98 93.44 30284 +1977 348 5.54 -0.46 3.89 0 216.13 125.03 30251 +1977 349 6.85 0.85 5.2 0.26 234.71 92.87 30221 +1977 350 4.73 -1.27 3.08 0 205.29 124.79 30197 +1977 351 5.03 -0.97 3.38 0 209.25 124.4 30177 +1977 352 6.36 0.36 4.71 0 227.61 123.5 30162 +1977 353 3.21 -2.79 1.56 0.16 186.2 93.93 30151 +1977 354 5.53 -0.47 3.88 0.02 215.99 92.94 30145 +1977 355 3.41 -2.59 1.76 0.61 188.62 93.82 30144 +1977 356 0.54 -5.46 -1.11 0 156.35 126.49 30147 +1977 357 0.56 -5.44 -1.09 1.01 156.56 94.9 30156 +1977 358 -1.41 -7.41 -3.06 1 137.25 142.5 30169 +1977 359 -2.38 -8.38 -4.03 0.56 128.53 144.61 30186 +1977 360 -2.37 -8.37 -4.02 0 128.62 176.92 30208 +1977 361 -1.82 -7.82 -3.47 0.05 133.5 145.07 30235 +1977 362 -2.32 -8.32 -3.97 0 129.05 177.75 30267 +1977 363 -1.74 -7.74 -3.39 0 134.23 178.07 30303 +1977 364 -2.64 -8.64 -4.29 0.05 126.27 146.36 30343 +1977 365 -5.1 -11.1 -6.75 0 106.58 180.19 30388 +1978 1 0.65 -5.35 -1 0 157.49 178.83 30438 +1978 2 -3.63 -9.63 -5.28 0 118 181.12 30492 +1978 3 -4.39 -10.39 -6.04 0.56 111.97 150.52 30551 +1978 4 -2.43 -8.43 -4.08 0.23 128.09 151.34 30614 +1978 5 2.07 -3.93 0.42 0 172.9 183.24 30681 +1978 6 0.77 -5.23 -0.88 0 158.75 184.53 30752 +1978 7 0.03 -5.97 -1.62 0.08 151.15 151.65 30828 +1978 8 -0.16 -6.16 -1.81 0 149.25 186.98 30907 +1978 9 1.34 -4.66 -0.31 0.25 164.82 152.83 30991 +1978 10 2.12 -3.88 0.47 0 173.47 187.76 31079 +1978 11 2.14 -3.86 0.49 0 173.69 188.32 31171 +1978 12 8.26 2.26 6.61 0 256.23 184.24 31266 +1978 13 9.23 3.23 7.58 0 272 183.74 31366 +1978 14 7.06 1.06 5.41 0 237.82 185.81 31469 +1978 15 6.74 0.74 5.09 0 233.1 186.45 31575 +1978 16 3.03 -2.97 1.38 0 184.04 189.55 31686 +1978 17 5.9 -0.1 4.25 0 221.11 188.54 31800 +1978 18 2.56 -3.44 0.91 0 178.51 192.01 31917 +1978 19 -1.8 -7.8 -3.45 0 133.69 195.89 32038 +1978 20 -3.47 -9.47 -5.12 0 119.3 198 32161 +1978 21 -0.62 -6.62 -2.27 0 144.73 198.69 32289 +1978 22 2.09 -3.91 0.44 0.01 173.13 159.31 32419 +1978 23 -1.24 -7.24 -2.89 0 138.83 201.93 32552 +1978 24 6.3 0.3 4.65 0 226.75 158.54 32688 +1978 25 7.65 1.65 6 0.02 246.72 119.52 32827 +1978 26 5.06 -0.94 3.41 0 209.65 163.22 32969 +1978 27 6.38 0.38 4.73 0.27 227.89 123.2 33114 +1978 28 6.15 0.15 4.5 0 224.62 166.64 33261 +1978 29 7.47 1.47 5.82 0 243.98 167.95 33411 +1978 30 12.47 6.47 10.82 0 330.86 165.25 33564 +1978 31 11.46 5.46 9.81 0.19 311.44 126.51 33718 +1978 32 7.98 1.98 6.33 0.05 251.83 130.63 33875 +1978 33 4.1 -1.9 2.45 0.44 197.18 134.87 34035 +1978 34 2.59 -3.41 0.94 0 178.86 183.04 34196 +1978 35 1.05 -4.95 -0.6 0 161.71 186.14 34360 +1978 36 1.74 -4.26 0.09 0.61 169.21 141.19 34526 +1978 37 1.11 -4.89 -0.54 0 162.35 191.08 34694 +1978 38 4.48 -1.52 2.83 0 202.04 191.59 34863 +1978 39 -1.11 -7.11 -2.76 0 140.05 197.71 35035 +1978 40 -1.69 -7.69 -3.34 0 134.68 200.66 35208 +1978 41 -1.33 -7.33 -2.98 0 137.99 203.13 35383 +1978 42 1.96 -4.04 0.31 0 171.66 203.79 35560 +1978 43 2.56 -3.44 0.91 0 178.51 206.11 35738 +1978 44 0.33 -5.67 -1.32 0.01 154.19 157.6 35918 +1978 45 0.9 -5.1 -0.75 0 160.12 212.43 36099 +1978 46 0.13 -5.87 -1.52 0 152.15 215.62 36282 +1978 47 2.52 -3.48 0.87 0 178.05 216.9 36466 +1978 48 -1.28 -7.28 -2.93 0 138.46 222.13 36652 +1978 49 -0.57 -6.57 -2.22 0 145.22 224.54 36838 +1978 50 -2.07 -8.07 -3.72 0 131.26 228.09 37026 +1978 51 0.38 -5.62 -1.27 0 154.7 229.66 37215 +1978 52 3.12 -2.88 1.47 0 185.11 230.59 37405 +1978 53 4.13 -1.87 2.48 0 197.56 232.75 37596 +1978 54 6.8 0.8 5.15 0.02 233.98 174.8 37788 +1978 55 7.43 1.43 5.78 0 243.37 235.4 37981 +1978 56 6.82 0.82 5.17 0 234.27 238.71 38175 +1978 57 9.69 3.69 8.04 0 279.77 238.35 38370 +1978 58 8.31 2.31 6.66 0 257.03 242.89 38565 +1978 59 7.68 1.68 6.03 1.14 247.19 184.72 38761 +1978 60 13.08 7.08 11.43 0 343.08 242.01 38958 +1978 61 13.88 7.88 12.23 0 359.69 243.58 39156 +1978 62 16.13 10.13 14.48 0 410.13 242.29 39355 +1978 63 14.14 8.14 12.49 0 365.23 248.78 39553 +1978 64 13.7 7.7 12.05 0 355.89 252.35 39753 +1978 65 14.5 8.5 12.85 0 373.03 253.78 39953 +1978 66 16.24 10.24 14.59 0 412.74 253.17 40154 +1978 67 15.66 9.66 14.01 0 399.12 257.09 40355 +1978 68 13.58 7.58 11.93 0 353.38 263.66 40556 +1978 69 13.02 7.02 11.37 0 341.86 267.16 40758 +1978 70 11.46 5.46 9.81 0 311.44 272.45 40960 +1978 71 10.82 4.82 9.17 0 299.65 276.29 41163 +1978 72 7.86 1.86 6.21 0 249.96 283.11 41366 +1978 73 8.04 2.04 6.39 0 252.77 285.55 41569 +1978 74 6.64 0.64 4.99 0.02 231.65 217.5 41772 +1978 75 5.13 -0.87 3.48 0.07 210.58 220.82 41976 +1978 76 5.95 -0.05 4.3 0.66 221.81 222.14 42179 +1978 77 6.48 0.48 4.83 0.43 229.33 223.64 42383 +1978 78 10.17 4.17 8.52 0.09 288.07 221.96 42587 +1978 79 10.71 4.71 9.06 0 297.67 297.83 42791 +1978 80 10.49 4.49 8.84 0 293.72 300.69 42996 +1978 81 5.14 -0.86 3.49 0 210.72 310.31 43200 +1978 82 7.39 1.39 5.74 0 242.76 310.29 43404 +1978 83 9.78 3.78 8.13 0 281.31 309.46 43608 +1978 84 9.27 3.27 7.62 0.01 272.67 234.56 43812 +1978 85 10.61 4.61 8.96 1.08 295.87 234.88 44016 +1978 86 9.76 3.76 8.11 0.21 280.97 237.68 44220 +1978 87 7.71 1.71 6.06 0.03 247.65 241.8 44424 +1978 88 7.05 1.05 5.4 0.83 237.67 244.23 44627 +1978 89 6.5 0.5 4.85 0.59 229.62 246.49 44831 +1978 90 4.35 -1.65 2.7 0 200.36 333.6 45034 +1978 91 9.88 3.88 8.23 0.03 283.03 246.37 45237 +1978 92 9.61 3.61 7.96 0.18 278.4 248.38 45439 +1978 93 8.23 2.23 6.58 0 255.76 335.47 45642 +1978 94 3.19 -2.81 1.54 0.19 185.95 257.92 45843 +1978 95 4.07 -1.93 2.42 0.22 196.8 258.85 46045 +1978 96 4.02 -1.98 2.37 0 196.17 347.35 46246 +1978 97 7.42 1.42 5.77 0 243.22 345.17 46446 +1978 98 10.51 4.51 8.86 0.13 294.08 256.78 46647 +1978 99 13.79 7.79 12.14 0.05 357.78 253.62 46846 +1978 100 14.84 8.84 13.19 0 380.52 337.81 47045 +1978 101 9.47 3.47 7.82 0 276.03 350.02 47243 +1978 102 12.25 6.25 10.6 0 326.54 347 47441 +1978 103 10.32 4.32 8.67 0 290.71 352.37 47638 +1978 104 12.01 6.01 10.36 0 321.89 351.12 47834 +1978 105 16.5 10.5 14.85 1.03 418.98 257.24 48030 +1978 106 17.64 11.64 15.99 0 447.27 341.62 48225 +1978 107 14.22 8.22 12.57 0 366.95 351.65 48419 +1978 108 14.59 8.59 12.94 0.12 375 264.41 48612 +1978 109 12.77 6.77 11.12 0.26 336.82 268.56 48804 +1978 110 8.75 2.75 7.1 0 264.1 366.8 48995 +1978 111 13.17 7.17 11.52 0 344.91 360.21 49185 +1978 112 12.04 6.04 10.39 0 322.47 364.04 49374 +1978 113 13.23 7.23 11.58 0 346.14 362.94 49561 +1978 114 13.62 7.62 11.97 0.39 354.21 272.69 49748 +1978 115 12.76 6.76 11.11 0.21 336.62 275.14 49933 +1978 116 14.22 8.22 12.57 0.89 366.95 273.67 50117 +1978 117 16.42 10.42 14.77 0.12 417.05 270.61 50300 +1978 118 16.18 10.18 14.53 0.42 411.32 272.05 50481 +1978 119 18.18 12.18 16.53 0.51 461.23 268.83 50661 +1978 120 17.49 11.49 15.84 0.18 443.46 271.16 50840 +1978 121 17.12 11.12 15.47 1.01 434.17 272.76 51016 +1978 122 16.99 10.99 15.34 0.16 430.95 273.91 51191 +1978 123 14.33 8.33 12.68 0.51 369.33 279.72 51365 +1978 124 13.36 7.36 11.71 0.28 348.81 282.19 51536 +1978 125 13.16 7.16 11.51 0.39 344.71 283.26 51706 +1978 126 17.14 11.14 15.49 0.25 434.67 276.63 51874 +1978 127 17.77 11.77 16.12 0 450.6 367.94 52039 +1978 128 22.18 16.18 20.53 0.05 576.65 265.82 52203 +1978 129 21.32 15.32 19.67 0.06 549.96 268.77 52365 +1978 130 19.33 13.33 17.68 0.47 492.19 274.36 52524 +1978 131 15.11 9.11 13.46 0.03 386.56 283.87 52681 +1978 132 17.57 11.57 15.92 0.03 445.49 279.55 52836 +1978 133 13.18 7.18 11.53 0.39 345.12 288.42 52989 +1978 134 11.65 5.65 10 1.74 315.02 291.4 53138 +1978 135 13.82 7.82 12.17 0.43 358.42 288.4 53286 +1978 136 13.57 7.57 11.92 0.64 353.17 289.32 53430 +1978 137 17.35 11.35 15.7 0.17 439.92 282.59 53572 +1978 138 18.14 12.14 16.49 0 460.18 375.07 53711 +1978 139 19.7 13.7 18.05 1.23 502.53 278.15 53848 +1978 140 15.05 9.05 13.4 1.31 385.21 288.54 53981 +1978 141 13.66 7.66 12.01 0.51 355.05 291.38 54111 +1978 142 14.1 8.1 12.45 0 364.37 387.99 54238 +1978 143 17.77 11.77 16.12 0.28 450.6 284.1 54362 +1978 144 15.02 9.02 13.37 0 384.54 386.77 54483 +1978 145 13.88 7.88 12.23 0 359.69 390.01 54600 +1978 146 14.2 8.2 12.55 0.11 366.52 292.23 54714 +1978 147 14.9 8.9 13.25 0 381.86 388.41 54824 +1978 148 11.42 5.42 9.77 0.23 310.69 297.49 54931 +1978 149 15.24 9.24 13.59 0.02 389.5 291.19 55034 +1978 150 16.64 10.64 14.99 0.04 422.37 288.65 55134 +1978 151 17.87 11.87 16.22 0.93 453.17 286.29 55229 +1978 152 20.58 14.58 18.93 0 527.84 373.08 55321 +1978 153 21.35 15.35 19.7 0.06 550.88 277.93 55409 +1978 154 20.44 14.44 18.79 0.04 523.74 280.59 55492 +1978 155 22.52 16.52 20.87 0.16 587.51 275 55572 +1978 156 21.22 15.22 19.57 0.82 546.93 278.9 55648 +1978 157 23.62 17.62 21.97 0.48 623.81 272.04 55719 +1978 158 23.83 17.83 22.18 0 630.95 362.02 55786 +1978 159 20.77 14.77 19.12 0.11 533.45 280.54 55849 +1978 160 21.05 15.05 19.4 0.03 541.8 279.92 55908 +1978 161 20.04 14.04 18.39 0.36 512.18 282.62 55962 +1978 162 24.6 18.6 22.95 0.3 657.73 269.44 56011 +1978 163 22.36 16.36 20.71 0.79 582.38 276.51 56056 +1978 164 23.68 17.68 22.03 0.49 625.84 272.57 56097 +1978 165 22.44 16.44 20.79 0 584.94 368.51 56133 +1978 166 22.08 16.08 20.43 0.48 573.49 277.48 56165 +1978 167 17.61 11.61 15.96 0.03 446.5 288.72 56192 +1978 168 22.12 16.12 20.47 0.22 574.76 277.38 56214 +1978 169 20.47 14.47 18.82 0.02 524.62 281.91 56231 +1978 170 21.09 15.09 19.44 0.8 543 280.26 56244 +1978 171 23.94 17.94 22.29 0 634.72 362.6 56252 +1978 172 20.27 14.27 18.62 0 518.8 376.62 56256 +1978 173 20.48 14.48 18.83 0.06 524.91 281.9 56255 +1978 174 20.37 14.37 18.72 0.74 521.7 282.13 56249 +1978 175 20.12 14.12 18.47 0 514.48 377 56238 +1978 176 16.38 10.38 14.73 0 416.09 388.44 56223 +1978 177 16.43 10.43 14.78 0.39 417.29 291.15 56203 +1978 178 15.6 9.6 13.95 0 397.74 390.45 56179 +1978 179 12.89 6.89 11.24 0.43 339.23 297.68 56150 +1978 180 18.15 12.15 16.5 0.08 460.44 287.26 56116 +1978 181 16.04 10.04 14.39 0 408 388.98 56078 +1978 182 14.83 8.83 13.18 0 380.3 391.97 56035 +1978 183 13.6 7.6 11.95 0 353.8 394.76 55987 +1978 184 12.42 6.42 10.77 0 329.87 397.24 55935 +1978 185 14.78 8.78 13.13 0.47 379.19 293.75 55879 +1978 186 16.08 10.08 14.43 0.52 408.95 291.02 55818 +1978 187 16.62 10.62 14.97 0.02 421.88 289.78 55753 +1978 188 20.75 14.75 19.1 0 532.86 373.14 55684 +1978 189 22.47 16.47 20.82 0 585.9 366.6 55611 +1978 190 20.7 14.7 19.05 0 531.38 372.77 55533 +1978 191 19.44 13.44 17.79 0 495.25 376.76 55451 +1978 192 20.41 14.41 18.76 0.31 522.87 279.91 55366 +1978 193 20.05 14.05 18.4 0 512.47 374.16 55276 +1978 194 17.7 11.7 16.05 0.59 448.8 286.02 55182 +1978 195 17.55 11.55 15.9 0.46 444.98 286.14 55085 +1978 196 19.98 13.98 18.33 0.37 510.47 280.12 54984 +1978 197 16.41 10.41 14.76 0.11 416.81 287.89 54879 +1978 198 18.51 12.51 16.86 0.1 469.94 283 54770 +1978 199 22 16 20.35 0 570.98 365.09 54658 +1978 200 22.33 16.33 20.68 0.85 581.42 272.58 54542 +1978 201 19.75 13.75 18.1 0.28 503.94 279.11 54423 +1978 202 19.89 13.89 18.24 0.06 507.9 278.34 54301 +1978 203 19.76 13.76 18.11 0.01 504.22 278.28 54176 +1978 204 22.16 16.16 20.51 0 576.02 362.07 54047 +1978 205 21.32 15.32 19.67 0.38 549.96 273.48 53915 +1978 206 24.64 18.64 22.99 0.31 659.15 263.26 53780 +1978 207 28.08 22.08 26.43 0.96 791.12 250.56 53643 +1978 208 30.13 24.13 28.48 0 879.89 322.25 53502 +1978 209 30.85 24.85 29.2 0 912.99 317.43 53359 +1978 210 30.81 24.81 29.16 0 911.12 317.11 53213 +1978 211 31.06 25.06 29.41 0 922.84 314.9 53064 +1978 212 32.37 26.37 30.72 0.25 986.34 229.52 52913 +1978 213 26.41 20.41 24.76 1 724.51 253.74 52760 +1978 214 22.18 16.18 20.53 0 576.65 355.34 52604 +1978 215 22.91 16.91 21.26 0 600.17 351.91 52445 +1978 216 22.42 16.42 20.77 0.22 584.3 264.58 52285 +1978 217 24.46 18.46 22.81 0.03 652.79 257.85 52122 +1978 218 25.72 19.72 24.07 1.29 698.41 253.16 51958 +1978 219 25.32 19.32 23.67 1.41 683.64 253.74 51791 +1978 220 25.15 19.15 23.5 0.07 677.45 253.62 51622 +1978 221 24.08 18.08 22.43 0 639.54 341.7 51451 +1978 222 22.54 16.54 20.89 0 588.15 346.69 51279 +1978 223 22.08 16.08 20.43 0 573.49 347.26 51105 +1978 224 21.65 15.65 20 0 560.08 347.76 50929 +1978 225 21.74 15.74 20.09 0 562.86 346.32 50751 +1978 226 24.15 18.15 22.5 0.05 641.97 252.04 50572 +1978 227 23.02 17.02 21.37 0 603.78 339.24 50392 +1978 228 20.83 14.83 19.18 0 535.23 345.85 50210 +1978 229 20.73 14.73 19.08 0 532.26 344.95 50026 +1978 230 19.14 13.14 17.49 0 486.96 348.72 49842 +1978 231 22.27 16.27 20.62 0 579.51 336.93 49656 +1978 232 19.43 13.43 17.78 0 494.97 345.01 49469 +1978 233 16.46 10.46 14.81 0 418.01 351.89 49280 +1978 234 14.37 8.37 12.72 0 370.19 355.47 49091 +1978 235 18.42 12.42 16.77 0 467.55 343.65 48900 +1978 236 18.76 12.76 17.11 0 476.63 341.24 48709 +1978 237 23.55 17.55 21.9 0.01 621.44 242.77 48516 +1978 238 18.97 12.97 17.32 0 482.32 337.31 48323 +1978 239 19.43 13.43 17.78 0.05 494.97 250.83 48128 +1978 240 20.83 14.83 19.18 0 535.23 328.36 47933 +1978 241 21.06 15.06 19.41 0.15 542.1 244.44 47737 +1978 242 17.4 11.4 15.75 0 441.18 334.88 47541 +1978 243 16.78 10.78 15.13 0.33 425.78 250.95 47343 +1978 244 13.39 7.39 11.74 0 349.43 340.45 47145 +1978 245 15.02 9.02 13.37 0 384.54 335.06 46947 +1978 246 16.8 10.8 15.15 0.53 426.27 246.65 46747 +1978 247 16.22 10.22 14.57 0.21 412.27 246.3 46547 +1978 248 22.71 16.71 21.06 0 593.64 307.69 46347 +1978 249 21.94 15.94 20.29 0 569.1 308.29 46146 +1978 250 22.06 16.06 20.41 0.29 572.86 229.5 45945 +1978 251 19.43 13.43 17.78 0.3 494.97 233.98 45743 +1978 252 20.62 14.62 18.97 0 529.02 306.37 45541 +1978 253 25.17 19.17 23.52 0.08 678.18 216.58 45339 +1978 254 21 15 19.35 0 540.3 301.07 45136 +1978 255 19.95 13.95 18.3 0.06 509.61 226.46 44933 +1978 256 21.7 15.7 20.05 0 561.62 294.5 44730 +1978 257 20.01 14.01 18.36 0.63 511.32 223.08 44527 +1978 258 17.4 11.4 15.75 1.64 441.18 226.47 44323 +1978 259 15.86 9.86 14.21 0 403.78 303.08 44119 +1978 260 18.56 12.56 16.91 0.2 471.27 220.72 43915 +1978 261 17.94 11.94 16.29 0 454.98 293.42 43711 +1978 262 16.79 10.79 15.14 0 426.03 293.79 43507 +1978 263 15.95 9.95 14.3 0 405.89 293.19 43303 +1978 264 15.55 9.55 13.9 0 396.58 291.46 43099 +1978 265 15.91 9.91 14.26 0.03 404.95 216.25 42894 +1978 266 15.05 9.05 13.4 0.08 385.21 215.72 42690 +1978 267 13.01 7.01 11.36 0 341.66 288.77 42486 +1978 268 12.52 6.52 10.87 0 331.84 287.02 42282 +1978 269 13.19 7.19 11.54 0 345.32 283.31 42078 +1978 270 17.02 11.02 15.37 0.11 431.69 204.85 41875 +1978 271 16.78 10.78 15.13 0 425.78 271.06 41671 +1978 272 20.15 14.15 18.5 0 515.34 260.42 41468 +1978 273 21.71 15.71 20.06 0 561.93 253.79 41265 +1978 274 18.82 12.82 17.17 0 478.25 258.66 41062 +1978 275 16.76 10.76 15.11 0.78 425.29 195.39 40860 +1978 276 14.09 8.09 12.44 0.36 364.16 197.22 40658 +1978 277 12.58 6.58 10.93 0 333.03 262.83 40456 +1978 278 11.33 5.33 9.68 0 309.02 261.86 40255 +1978 279 12.43 6.43 10.78 0 330.07 257.36 40054 +1978 280 12.86 6.86 11.21 0 338.63 254.02 39854 +1978 281 8.71 2.71 7.06 0.01 263.45 192.79 39654 +1978 282 12.92 6.92 11.27 0.34 339.83 186.34 39455 +1978 283 14.77 8.77 13.12 0 378.97 242.58 39256 +1978 284 13.55 7.55 11.9 0.02 352.75 181.21 39058 +1978 285 10.59 4.59 8.94 1.08 295.51 182.46 38861 +1978 286 10.69 4.69 9.04 0.01 297.3 180.27 38664 +1978 287 12.71 6.71 11.06 0.06 335.62 175.94 38468 +1978 288 10.52 4.52 8.87 0.18 294.26 176.12 38273 +1978 289 9.41 3.41 7.76 0 275.02 233.53 38079 +1978 290 12.43 6.43 10.78 0.36 330.07 170.04 37885 +1978 291 15.87 9.87 14.22 0.03 404.01 163.98 37693 +1978 292 13.94 7.94 12.29 0.15 360.96 164.35 37501 +1978 293 14.6 8.6 12.95 0.22 375.22 161.56 37311 +1978 294 14.53 8.53 12.88 0.83 373.68 159.5 37121 +1978 295 13.94 7.94 12.29 0 360.96 210.77 36933 +1978 296 18.19 12.19 16.54 0 461.49 201.08 36745 +1978 297 19.68 13.68 18.03 0 501.96 195.53 36560 +1978 298 18.01 12.01 16.36 0 456.79 196.28 36375 +1978 299 15.41 9.41 13.76 0 393.37 198 36191 +1978 300 14.98 8.98 13.33 0 383.64 196.06 36009 +1978 301 15.3 9.3 13.65 0 390.86 193.1 35829 +1978 302 13.68 7.68 12.03 0 355.47 192.89 35650 +1978 303 10.77 4.77 9.12 0 298.75 193.99 35472 +1978 304 9.95 3.95 8.3 0 284.24 192.44 35296 +1978 305 -1.75 -7.75 -3.4 0 134.14 198.47 35122 +1978 306 -2.04 -8.04 -3.69 0.12 131.53 185.31 34950 +1978 307 -1.87 -7.87 -3.52 0.54 133.05 184.98 34779 +1978 308 -2.35 -8.35 -4 0 128.79 231.13 34610 +1978 309 1.68 -4.32 0.03 0.39 168.54 179.95 34444 +1978 310 4.11 -1.89 2.46 0 197.3 222.26 34279 +1978 311 4.34 -1.66 2.69 0 200.23 219.56 34116 +1978 312 2.97 -3.03 1.32 0 183.33 217.64 33956 +1978 313 -0.33 -6.33 -1.98 0 147.56 217.55 33797 +1978 314 1.49 -4.51 -0.16 0.07 166.46 170.77 33641 +1978 315 2.97 -3.03 1.32 0 183.33 171.75 33488 +1978 316 0.35 -5.65 -1.3 0.01 154.39 128.26 33337 +1978 317 -1.03 -7.03 -2.68 0.09 140.81 167.13 33188 +1978 318 4.24 -1.76 2.59 0.24 198.96 123.11 33042 +1978 319 7 1 5.35 0.81 236.93 120.34 32899 +1978 320 6.61 0.61 4.96 0 231.21 158.88 32758 +1978 321 6.07 0.07 4.42 0 223.49 157.17 32620 +1978 322 3.37 -2.63 1.72 0 188.13 157.12 32486 +1978 323 6.28 0.28 4.63 0 226.47 153.57 32354 +1978 324 2.93 -3.07 1.28 0 182.85 153.68 32225 +1978 325 5.24 -0.76 3.59 0 212.06 150.51 32100 +1978 326 10.25 4.25 8.6 0 289.48 145.15 31977 +1978 327 11.54 5.54 9.89 0.05 312.94 106.59 31858 +1978 328 9.63 3.63 7.98 0.12 278.74 106.45 31743 +1978 329 7.5 1.5 5.85 0 244.43 142.15 31631 +1978 330 7.4 1.4 5.75 0 242.92 140.79 31522 +1978 331 10.13 4.13 8.48 0 287.37 137.3 31417 +1978 332 9.61 3.61 7.96 0 278.4 136.12 31316 +1978 333 11.79 5.79 10.14 0 317.68 133.12 31218 +1978 334 14.25 8.25 12.6 0 367.6 129.54 31125 +1978 335 11.68 5.68 10.03 0 315.59 131.01 31035 +1978 336 6.77 0.77 5.12 0.03 233.54 100.41 30949 +1978 337 5.62 -0.38 3.97 0 217.23 132.98 30867 +1978 338 7.11 1.11 5.46 0.06 238.56 98.3 30790 +1978 339 4.81 -1.19 3.16 0.53 206.34 98.81 30716 +1978 340 3.05 -2.95 1.4 0 184.28 132 30647 +1978 341 1.24 -4.76 -0.41 0 163.74 131.97 30582 +1978 342 0.05 -5.95 -1.6 0 151.35 131.73 30521 +1978 343 0.52 -5.48 -1.13 0 156.14 130.69 30465 +1978 344 -1.52 -7.52 -3.17 0.59 136.24 143.05 30413 +1978 345 0.6 -5.4 -1.05 0 156.97 174.34 30366 +1978 346 4.89 -1.11 3.24 0.01 207.39 139.44 30323 +1978 347 6.23 0.23 4.58 0 225.75 168.85 30284 +1978 348 2.74 -3.26 1.09 0 180.61 126.57 30251 +1978 349 1.14 -4.86 -0.51 0.15 162.67 95.21 30221 +1978 350 3.52 -2.48 1.87 0.36 189.96 94.09 30197 +1978 351 3.88 -2.12 2.23 0.51 194.41 93.78 30177 +1978 352 2.88 -3.12 1.23 0.26 182.26 94.1 30162 +1978 353 2.52 -3.48 0.87 0 178.05 125.59 30151 +1978 354 7.69 1.69 6.04 0 247.34 122.53 30145 +1978 355 6.25 0.25 4.6 0 226.04 123.48 30144 +1978 356 3.77 -2.23 2.12 0 193.04 124.94 30147 +1978 357 -0.24 -6.24 -1.89 0 148.45 126.87 30156 +1978 358 2.54 -3.46 0.89 0.32 178.28 94.29 30169 +1978 359 9.22 3.22 7.57 0.16 271.84 91.28 30186 +1978 360 5.79 -0.21 4.14 0.08 219.58 93.31 30208 +1978 361 6.28 0.28 4.63 0.93 226.47 93.33 30235 +1978 362 5.47 -0.53 3.82 0.01 215.17 94.03 30267 +1978 363 2.26 -3.74 0.61 0.2 175.06 95.77 30303 +1978 364 -0.21 -6.21 -1.86 0 148.75 129.21 30343 +1978 365 -2.24 -8.24 -3.89 0 129.76 130.57 30388 +1979 1 -6.22 -12.22 -7.87 0 98.53 132.73 30438 +1979 2 -5.72 -11.72 -7.37 0.21 102.06 143.95 30492 +1979 3 -5.74 -11.74 -7.39 0 101.91 178.17 30551 +1979 4 -1.15 -7.15 -2.8 0 139.68 177.45 30614 +1979 5 -0.55 -6.55 -2.2 0.69 145.41 146.41 30681 +1979 6 3.61 -2.39 1.96 0 191.06 178.25 30752 +1979 7 5.29 -0.71 3.64 0.03 212.73 144.06 30828 +1979 8 6.93 0.93 5.28 0 235.89 176.66 30907 +1979 9 6.3 0.3 4.65 0 226.75 134.89 30991 +1979 10 2.92 -3.08 1.27 0.16 182.73 103.66 31079 +1979 11 -0.62 -6.62 -2.27 0 144.73 140.9 31171 +1979 12 -1.24 -7.24 -2.89 0 138.83 142.18 31266 +1979 13 -0.7 -6.7 -2.35 0 143.96 143.59 31366 +1979 14 1.35 -4.65 -0.3 0.01 164.93 108.1 31469 +1979 15 0.02 -5.98 -1.63 0.01 151.05 109.67 31575 +1979 16 0.02 -5.98 -1.63 0.71 151.05 110.64 31686 +1979 17 -4.96 -10.96 -6.61 0.46 107.62 156.28 31800 +1979 18 -4.55 -10.55 -6.2 0.61 110.73 159.29 31917 +1979 19 -4.82 -10.82 -6.47 0.17 108.68 161.18 32038 +1979 20 -3.15 -9.15 -4.8 0 121.95 200.77 32161 +1979 21 -1.98 -7.98 -3.63 0.04 132.07 162.88 32289 +1979 22 -1.71 -7.71 -3.36 1.08 134.5 167.15 32419 +1979 23 -0.49 -6.49 -2.14 0.26 145.99 168.65 32552 +1979 24 1.62 -4.38 -0.03 0 167.88 209.39 32688 +1979 25 1.54 -4.46 -0.11 0 167 210.94 32827 +1979 26 1.07 -4.93 -0.58 0 161.92 212.8 32969 +1979 27 1.87 -4.13 0.22 0 170.65 213.96 33114 +1979 28 2.59 -3.41 0.94 0.14 178.86 172.98 33261 +1979 29 3.34 -2.66 1.69 0 187.77 216.55 33411 +1979 30 5.57 -0.43 3.92 0.06 216.54 173.46 33564 +1979 31 2.01 -3.99 0.36 1.2 172.22 176.58 33718 +1979 32 5.81 -0.19 4.16 1.54 219.85 175.33 33875 +1979 33 6.41 0.41 4.76 0 228.32 220.5 34035 +1979 34 4.79 -1.21 3.14 0 206.07 223.18 34196 +1979 35 7.75 1.75 6.1 0 248.26 221.81 34360 +1979 36 5.71 -0.29 4.06 0 218.47 225.16 34526 +1979 37 3.51 -2.49 1.86 0 189.84 228.61 34694 +1979 38 5.35 -0.65 3.7 0.31 213.54 181.45 34863 +1979 39 8.77 2.77 7.12 0.78 264.42 142.87 35035 +1979 40 4.72 -1.28 3.07 0.42 205.16 147.48 35208 +1979 41 4.15 -1.85 2.5 0.44 197.81 149.77 35383 +1979 42 6.45 0.45 4.8 0.25 228.9 150.28 35560 +1979 43 6.53 0.53 4.88 0.11 230.05 152.25 35738 +1979 44 6.75 0.75 5.1 0 233.25 205.35 35918 +1979 45 7.25 1.25 5.6 0 240.65 207.49 36099 +1979 46 0.84 -5.16 -0.81 0.04 159.48 161.39 36282 +1979 47 3.82 -2.18 2.17 0 193.66 215.94 36466 +1979 48 2.61 -3.39 0.96 0.07 179.09 164.74 36652 +1979 49 2.15 -3.85 0.5 0.01 173.81 167.09 36838 +1979 50 0.49 -5.51 -1.16 0.2 155.83 169.95 37026 +1979 51 -1.76 -7.76 -3.41 0 134.05 230.94 37215 +1979 52 -2.77 -8.77 -4.42 0 125.16 234.35 37405 +1979 53 0.2 -5.8 -1.45 0 152.86 235.64 37596 +1979 54 4.7 -1.3 3.05 0 204.89 235.03 37788 +1979 55 0.63 -5.37 -1.02 0.05 157.28 180.88 37981 +1979 56 6.08 0.08 4.43 0.16 223.63 179.59 38175 +1979 57 9.37 3.37 7.72 0 274.35 238.74 38370 +1979 58 6.51 0.51 4.86 0.02 229.76 183.62 38565 +1979 59 7.89 1.89 6.24 0 250.43 246.06 38761 +1979 60 16.39 10.39 14.74 1.11 416.33 177.23 38958 +1979 61 10.24 4.24 8.59 0.57 289.3 186.72 39156 +1979 62 11.3 5.3 9.65 0 308.46 250.26 39355 +1979 63 10.94 4.94 9.29 0.04 301.83 190.3 39553 +1979 64 13.09 7.09 11.44 0 343.28 253.35 39753 +1979 65 9.71 3.71 8.06 0 280.11 261.13 39953 +1979 66 10.77 4.77 9.12 0 298.75 262.38 40154 +1979 67 7.15 1.15 5.5 0.23 239.16 202.41 40355 +1979 68 10.5 4.5 8.85 0.09 293.9 201.35 40556 +1979 69 11.48 5.48 9.83 0.18 311.82 202.21 40758 +1979 70 9.74 3.74 8.09 0.17 280.62 206.21 40960 +1979 71 13 7 11.35 0.67 341.45 204.63 41163 +1979 72 13.05 7.05 11.4 0.01 342.47 206.64 41366 +1979 73 12.44 6.44 10.79 0 330.27 279.16 41569 +1979 74 13.83 7.83 12.18 0 358.63 279.43 41772 +1979 75 9.15 3.15 7.5 0 270.67 289.55 41976 +1979 76 9.58 3.58 7.93 0 277.89 291.57 42179 +1979 77 7.81 1.81 6.16 0 249.19 296.56 42383 +1979 78 13.01 7.01 11.36 0.01 341.66 218.49 42587 +1979 79 13.86 7.86 12.21 0 359.26 292.43 42791 +1979 80 11.54 5.54 9.89 0 312.94 299.01 42996 +1979 81 8.32 2.32 6.67 0.08 257.19 229.8 43200 +1979 82 11.36 5.36 9.71 0.05 309.57 228.37 43404 +1979 83 8.72 2.72 7.07 0 263.61 311 43608 +1979 84 6.97 0.97 5.32 0.66 236.48 236.91 43812 +1979 85 7.49 1.49 5.84 0 244.28 317.73 44016 +1979 86 9.21 3.21 7.56 0 271.67 317.74 44220 +1979 87 7.96 1.96 6.31 0.15 251.52 241.54 44424 +1979 88 6.73 0.73 5.08 0.6 232.96 244.54 44627 +1979 89 7.78 1.78 6.13 2.25 248.73 245.22 44831 +1979 90 3.33 -2.67 1.68 0.35 187.64 251.02 45034 +1979 91 5.96 -0.04 4.31 0.24 221.95 250.51 45237 +1979 92 6.53 0.53 4.88 0.28 230.05 251.67 45439 +1979 93 8.46 2.46 6.81 0.12 259.42 251.35 45642 +1979 94 10.12 4.12 8.47 1.39 287.2 251.05 45843 +1979 95 12.08 6.08 10.43 0.17 323.24 250.09 46045 +1979 96 7.95 1.95 6.3 0.06 251.36 256.76 46246 +1979 97 5.49 -0.51 3.84 0.07 215.45 260.78 46446 +1979 98 8.62 2.62 6.97 0.33 261.99 259.06 46647 +1979 99 11.83 5.83 10.18 0 318.44 342.03 46846 +1979 100 16.39 10.39 14.74 0 416.33 334.17 47045 +1979 101 15.44 9.44 13.79 0.04 394.06 253.75 47243 +1979 102 13.42 7.42 11.77 0 350.05 344.66 47441 +1979 103 11.36 5.36 9.71 0 309.57 350.52 47638 +1979 104 14.73 8.73 13.08 0 378.08 345.45 47834 +1979 105 13.08 7.08 11.43 0.12 343.08 263.09 48030 +1979 106 12.97 6.97 11.32 0 340.85 352.65 48225 +1979 107 11.18 5.18 9.53 0.26 306.24 268.36 48419 +1979 108 11.53 5.53 9.88 0.22 312.76 269.18 48612 +1979 109 11.21 5.21 9.56 0.39 306.79 270.84 48804 +1979 110 10.89 4.89 9.24 0.23 300.92 272.35 48995 +1979 111 13.65 7.65 12 0.14 354.84 269.38 49185 +1979 112 15.61 9.61 13.96 0.06 397.97 267.12 49374 +1979 113 15.25 9.25 13.6 0 389.73 358.36 49561 +1979 114 13.92 7.92 12.27 0 360.53 362.92 49748 +1979 115 15.21 9.21 13.56 0 388.82 361.35 49933 +1979 116 14.51 8.51 12.86 0.3 373.25 273.17 50117 +1979 117 15.8 9.8 14.15 0 402.38 362.4 50300 +1979 118 13.47 7.47 11.82 0.54 351.09 276.89 50481 +1979 119 13.14 7.14 11.49 0.04 344.3 278.32 50661 +1979 120 16.45 10.45 14.8 0.25 417.77 273.28 50840 +1979 121 21.07 15.07 19.42 0.27 542.4 263.64 51016 +1979 122 22.39 16.39 20.74 0 583.34 347.94 51191 +1979 123 19.04 13.04 17.39 0.09 484.22 270.21 51365 +1979 124 14.24 8.24 12.59 0 367.38 374.26 51536 +1979 125 14.54 8.54 12.89 0 373.9 374.54 51706 +1979 126 13.66 7.66 12.01 0 355.05 377.58 51874 +1979 127 15.21 9.21 13.56 0 388.82 374.8 52039 +1979 128 13.62 7.62 11.97 0 354.21 379.57 52203 +1979 129 12.8 6.8 11.15 0 337.42 382.24 52365 +1979 130 12.2 6.2 10.55 0 325.57 384.31 52524 +1979 131 13.12 7.12 11.47 0 343.89 383.15 52681 +1979 132 16.22 10.22 14.57 0 412.27 376.46 52836 +1979 133 12.82 6.82 11.17 0.02 337.82 289.02 52989 +1979 134 16.95 10.95 15.3 0.4 429.96 281.91 53138 +1979 135 15.61 9.61 13.96 0 397.97 380.17 53286 +1979 136 16.13 10.13 14.48 0 410.13 379.45 53430 +1979 137 18.97 12.97 17.32 0 482.32 371.93 53572 +1979 138 25.02 19.02 23.37 0 672.74 349.86 53711 +1979 139 25.06 19.06 23.41 0 674.19 350.34 53848 +1979 140 21.2 15.2 19.55 0 546.32 366.19 53981 +1979 141 24.26 18.26 22.61 0 645.79 354.67 54111 +1979 142 21.7 15.7 20.05 0.4 561.62 273.96 54238 +1979 143 23.55 17.55 21.9 0.02 621.44 268.96 54362 +1979 144 21.57 15.57 19.92 0 557.61 366.75 54483 +1979 145 21.51 15.51 19.86 0 555.77 367.43 54600 +1979 146 23.45 17.45 21.8 0 618.08 360.29 54714 +1979 147 23.97 17.97 22.32 0 635.75 358.6 54824 +1979 148 21.14 15.14 19.49 0 544.51 369.97 54931 +1979 149 20.47 14.47 18.82 0 524.62 372.64 55034 +1979 150 19 13 17.35 0 483.13 377.85 55134 +1979 151 24.69 18.69 23.04 0 660.93 356.87 55229 +1979 152 25.71 19.71 24.06 0.02 698.04 264.28 55321 +1979 153 27.01 21.01 25.36 0.03 747.87 259.77 55409 +1979 154 23.32 17.32 21.67 0.72 613.72 272.47 55492 +1979 155 20.83 14.83 19.18 0.14 535.23 279.71 55572 +1979 156 21.68 15.68 20.03 0.13 561.01 277.63 55648 +1979 157 26.1 20.1 24.45 0.04 712.68 263.79 55719 +1979 158 26.82 20.82 25.17 0.34 740.41 261.3 55786 +1979 159 28.28 22.28 26.63 0.13 799.43 255.85 55849 +1979 160 22.11 16.11 20.46 0.33 574.44 276.98 55908 +1979 161 22.46 16.46 20.81 2.88 585.58 276.02 55962 +1979 162 24.68 18.68 23.03 2.84 660.57 269.17 56011 +1979 163 22.61 16.61 20.96 0 590.41 367.71 56056 +1979 164 25.69 19.69 24.04 0 697.29 354.58 56097 +1979 165 24.73 18.73 23.08 0.6 662.35 269.27 56133 +1979 166 21.53 15.53 19.88 0.62 556.38 279.03 56165 +1979 167 23.84 17.84 22.19 0 631.29 362.88 56192 +1979 168 24.09 18.09 22.44 0.32 639.89 271.42 56214 +1979 169 24.82 18.82 23.17 0 665.56 358.73 56231 +1979 170 25.65 19.65 24 0 695.8 354.97 56244 +1979 171 21.87 15.87 20.22 0.44 566.91 278.15 56252 +1979 172 21.15 15.15 19.5 0.27 544.81 280.13 56256 +1979 173 21.29 15.29 19.64 0.03 549.05 279.74 56255 +1979 174 16.6 10.6 14.95 0 421.4 387.9 56249 +1979 175 17.28 11.28 15.63 0 438.16 385.94 56238 +1979 176 20.77 14.77 19.12 0.1 533.45 281.03 56223 +1979 177 21.26 15.26 19.61 0 548.14 372.84 56203 +1979 178 19.25 13.25 17.6 1.73 489.98 284.84 56179 +1979 179 20.36 14.36 18.71 0.76 521.41 281.97 56150 +1979 180 26.48 20.48 24.83 0 727.2 350.63 56116 +1979 181 27.72 21.72 26.07 0 776.34 344.35 56078 +1979 182 22.38 16.38 20.73 1.89 583.02 276.18 56035 +1979 183 23.79 17.79 22.14 0.58 629.58 271.79 55987 +1979 184 24.7 18.7 23.05 1.37 661.28 268.75 55935 +1979 185 18.74 12.74 17.09 0.27 476.09 285.41 55879 +1979 186 18.68 12.68 17.03 0.12 474.48 285.35 55818 +1979 187 18.03 12.03 16.38 0 457.31 382.28 55753 +1979 188 17.59 11.59 15.94 0.51 446 287.49 55684 +1979 189 19.91 13.91 18.26 0.21 508.47 281.89 55611 +1979 190 15.92 9.92 14.27 0 405.18 387.43 55533 +1979 191 17.43 11.43 15.78 0 441.94 382.96 55451 +1979 192 18.05 12.05 16.4 0 457.83 380.82 55366 +1979 193 22.42 16.42 20.77 0 584.3 365.6 55276 +1979 194 21.47 15.47 19.82 0 554.54 368.95 55182 +1979 195 21.13 15.13 19.48 0.39 544.21 277.43 55085 +1979 196 17.68 11.68 16.03 0.24 448.29 285.54 54984 +1979 197 19.74 13.74 18.09 0 503.65 373.83 54879 +1979 198 18.65 12.65 17 1.3 473.68 282.67 54770 +1979 199 19.56 13.56 17.91 1 498.6 280.23 54658 +1979 200 19.33 13.33 17.68 0 492.19 373.98 54542 +1979 201 18.04 12.04 16.39 0.17 457.57 283.14 54423 +1979 202 19.93 13.93 18.28 0.32 509.04 278.24 54301 +1979 203 20.01 14.01 18.36 1.27 511.32 277.66 54176 +1979 204 19.02 13.02 17.37 0.84 483.68 279.68 54047 +1979 205 23.4 17.4 21.75 0.86 616.4 267.54 53915 +1979 206 26.3 20.3 24.65 1.22 720.29 257.64 53780 +1979 207 23.04 17.04 21.39 0.03 604.44 267.73 53643 +1979 208 24.77 18.77 23.12 0.34 663.78 261.88 53502 +1979 209 23.73 17.73 22.08 1.18 627.54 264.69 53359 +1979 210 24.76 18.76 23.11 0.15 663.42 260.99 53213 +1979 211 24.94 18.94 23.29 0.01 669.86 259.85 53064 +1979 212 23.13 17.13 21.48 0.01 607.41 264.89 52913 +1979 213 21.51 15.51 19.86 0 555.77 358.53 52760 +1979 214 24.82 18.82 23.17 0.01 665.56 258.57 52604 +1979 215 22.43 16.43 20.78 0 584.62 353.74 52445 +1979 216 24.61 18.61 22.96 0.09 658.09 258.02 52285 +1979 217 22.09 16.09 20.44 1.11 573.81 264.85 52122 +1979 218 24.45 18.45 22.8 0.8 652.44 257.29 51958 +1979 219 18.15 12.15 16.5 0.24 460.44 273.18 51791 +1979 220 20.92 14.92 19.27 0 537.91 354.51 51622 +1979 221 18.4 12.4 16.75 0.02 467.02 271.16 51451 +1979 222 16.7 10.7 15.05 0 423.83 365.27 51279 +1979 223 18.81 12.81 17.16 0 477.98 358.11 51105 +1979 224 17.43 11.43 15.78 0.03 441.94 270.78 50929 +1979 225 18.92 12.92 17.27 0.03 480.96 266.67 50751 +1979 226 17.71 11.71 16.06 0.05 449.06 268.45 50572 +1979 227 19.35 13.35 17.7 0.11 492.75 263.86 50392 +1979 228 22.15 16.15 20.5 0 575.7 341.27 50210 +1979 229 21.99 15.99 20.34 0.55 570.66 255.47 50026 +1979 230 23.6 17.6 21.95 0 623.13 333.39 49842 +1979 231 25.03 19.03 23.38 0 673.11 326.21 49656 +1979 232 21.56 15.56 19.91 0.18 557.3 253.58 49469 +1979 233 20.2 14.2 18.55 0.6 516.78 255.9 49280 +1979 234 18.75 12.75 17.1 2.66 476.36 258.15 49091 +1979 235 20.61 14.61 18.96 0.04 528.72 252.75 48900 +1979 236 21.36 15.36 19.71 0 551.18 333.11 48709 +1979 237 25.06 19.06 23.41 0 674.19 317.73 48516 +1979 238 29.13 23.13 27.48 0.02 835.59 223.11 48323 +1979 239 27.95 21.95 26.3 0.52 785.75 226.44 48128 +1979 240 23.92 17.92 22.27 0.25 634.03 238.14 47933 +1979 241 23.73 17.73 22.08 0 627.54 316.58 47737 +1979 242 20.55 14.55 18.9 0 526.96 325.83 47541 +1979 243 23.22 17.22 21.57 0 610.39 314.99 47343 +1979 244 19.22 13.22 17.57 0.01 489.16 244.64 47145 +1979 245 18.44 12.44 16.79 0 468.08 326.54 46947 +1979 246 12.69 6.69 11.04 0 335.22 337.93 46747 +1979 247 12.83 6.83 11.18 0 338.02 335.75 46547 +1979 248 11.6 5.6 9.95 0 314.07 336.05 46347 +1979 249 15.21 9.21 13.56 0.37 388.82 245.01 46146 +1979 250 13.36 7.36 11.71 0 348.81 328.59 45945 +1979 251 13.56 7.56 11.91 0 352.96 326.03 45743 +1979 252 17.95 11.95 16.3 0.68 455.24 235.37 45541 +1979 253 18.65 12.65 17 0 473.68 309.88 45339 +1979 254 21.07 15.07 19.42 0 542.4 300.85 45136 +1979 255 22.38 16.38 20.73 0 583.02 294.52 44933 +1979 256 23.25 17.25 21.6 0 611.39 289.43 44730 +1979 257 22.8 16.8 21.15 0 596.57 288.88 44527 +1979 258 22.51 16.51 20.86 0 587.18 287.58 44323 +1979 259 26.97 20.97 25.32 0 746.3 268.95 44119 +1979 260 23.73 17.73 22.08 0 627.54 278.91 43915 +1979 261 24.08 18.08 22.43 0.25 639.54 206.54 43711 +1979 262 21.91 15.91 20.26 0.48 568.16 210.15 43507 +1979 263 23.36 17.36 21.71 0.66 615.06 204.93 43303 +1979 264 25.01 19.01 23.36 0.07 672.38 198.85 43099 +1979 265 22.11 16.11 20.46 0 574.44 272.47 42894 +1979 266 19.98 13.98 18.33 0.11 510.47 207.12 42690 +1979 267 18.93 12.93 17.28 0 481.23 276.25 42486 +1979 268 15.64 9.64 13.99 0.76 398.66 210.89 42282 +1979 269 14.35 8.35 12.7 0 369.76 281.2 42078 +1979 270 18.18 12.18 16.53 0 461.23 270.5 41875 +1979 271 19.68 13.68 18.03 0 501.96 264.28 41671 +1979 272 17.38 11.38 15.73 0 440.68 267.05 41468 +1979 273 11.91 5.91 10.26 0 319.97 274.8 41265 +1979 274 5.05 -0.95 3.4 0 209.51 280.86 41062 +1979 275 7.47 1.47 5.82 0.02 243.98 206.51 40860 +1979 276 9.46 3.46 7.81 0 275.86 270.09 40658 +1979 277 12.59 6.59 10.94 0 333.23 262.82 40456 +1979 278 16.62 10.62 14.97 0 421.88 252.7 40255 +1979 279 18.62 12.62 16.97 0.01 472.87 184.26 40054 +1979 280 15.76 9.76 14.11 0.04 401.44 186.74 39854 +1979 281 13.36 7.36 11.71 0 348.81 250.49 39654 +1979 282 15.01 9.01 13.36 0.23 384.31 183.72 39455 +1979 283 12.3 6.3 10.65 0 327.52 246.57 39256 +1979 284 8.11 2.11 6.46 0 253.87 249.02 39058 +1979 285 14.15 8.15 12.5 0 365.44 238.01 38861 +1979 286 20.41 14.41 18.76 0.02 522.87 167.18 38664 +1979 287 18.48 12.48 16.83 0.23 469.14 168.27 38468 +1979 288 16.54 10.54 14.89 0.04 419.95 169.1 38273 +1979 289 10.89 4.89 9.24 0 300.92 231.69 38079 +1979 290 15.76 9.76 14.11 0 401.44 221.48 37885 +1979 291 15.79 9.79 14.14 1.33 402.14 164.08 37693 +1979 292 15.65 9.65 14 0.04 398.89 162.28 37501 +1979 293 10.89 4.89 9.24 0.05 300.92 165.49 37311 +1979 294 11.18 5.18 9.53 0 306.24 217.39 37121 +1979 295 11.24 5.24 9.59 0.23 307.35 160.86 36933 +1979 296 10.32 4.32 8.67 0 290.71 213.01 36745 +1979 297 10.18 4.18 8.53 0.18 288.25 157.83 36560 +1979 298 10.81 4.81 9.16 0.02 299.47 155.31 36375 +1979 299 9.58 3.58 7.93 0 277.89 205.71 36191 +1979 300 5.82 -0.18 4.17 0 219.99 206.68 36009 +1979 301 11.19 5.19 9.54 0.25 306.42 149.01 35829 +1979 302 10.28 4.28 8.63 0 290 197.12 35650 +1979 303 7.93 1.93 6.28 0 251.05 196.96 35472 +1979 304 5.35 -0.65 3.7 0 213.54 196.73 35296 +1979 305 1.05 -4.95 -0.6 0.04 161.71 147.7 35122 +1979 306 -0.97 -6.97 -2.62 0 141.38 195.74 34950 +1979 307 6.08 0.08 4.43 0.74 223.63 141.41 34779 +1979 308 6.62 0.62 4.97 0.74 231.36 139.1 34610 +1979 309 7.66 1.66 6.01 0.95 246.88 136.68 34444 +1979 310 6.42 0.42 4.77 0.23 228.47 135.63 34279 +1979 311 7.45 1.45 5.8 0 243.67 177.78 34116 +1979 312 8.23 2.23 6.58 0.14 255.76 130.84 33956 +1979 313 7.75 1.75 6.1 0.84 248.26 129.56 33797 +1979 314 11.16 5.16 9.51 2.16 305.87 125.66 33641 +1979 315 11.7 5.7 10.05 1.57 315.97 123.34 33488 +1979 316 12.49 6.49 10.84 0 331.25 161.44 33337 +1979 317 10.77 4.77 9.12 0 298.75 161.11 33188 +1979 318 10.12 4.12 8.47 0 287.2 159.44 33042 +1979 319 8.94 2.94 7.29 0.03 267.2 119.13 32899 +1979 320 10.91 4.91 9.26 0.66 301.29 116.36 32758 +1979 321 8.41 2.41 6.76 0.18 258.62 116.51 32620 +1979 322 5.04 -0.96 3.39 0.13 209.38 117.04 32486 +1979 323 4.79 -1.21 3.14 0.01 206.07 115.95 32354 +1979 324 7.63 1.63 5.98 0.25 246.42 112.88 32225 +1979 325 7.04 1.04 5.39 0.07 237.52 111.93 32100 +1979 326 9.01 3.01 7.36 0.51 268.36 109.68 31977 +1979 327 8.54 2.54 6.89 0 260.7 144.79 31858 +1979 328 11.54 5.54 9.89 0 312.94 140.18 31743 +1979 329 10.54 4.54 8.89 0 294.62 139.65 31631 +1979 330 9.14 3.14 7.49 0.12 270.51 104.58 31522 +1979 331 10.81 4.81 9.16 0.4 299.47 102.52 31417 +1979 332 12.14 6.14 10.49 0.55 324.4 100.38 31316 +1979 333 12.7 6.7 11.05 0.1 335.42 99.17 31218 +1979 334 11.37 5.37 9.72 0.83 309.76 99.33 31125 +1979 335 3.41 -2.59 1.76 0.27 188.62 102.77 31035 +1979 336 -0.01 -6.01 -1.66 1.14 150.74 149.41 30949 +1979 337 2.51 -3.49 0.86 0 177.93 180.74 30867 +1979 338 2.88 -3.12 1.23 0 182.26 179.34 30790 +1979 339 0.45 -5.55 -1.2 0.37 155.42 146.27 30716 +1979 340 3.86 -2.14 2.21 0.17 194.16 144.04 30647 +1979 341 7.1 1.1 5.45 0 238.41 173.18 30582 +1979 342 4.28 -1.72 2.63 0 199.47 173.69 30521 +1979 343 8.09 2.09 6.44 0 253.55 126.39 30465 +1979 344 10.48 4.48 8.83 0 293.55 123.41 30413 +1979 345 9.24 3.24 7.59 0 272.17 123.99 30366 +1979 346 8.1 2.1 6.45 0.32 253.71 93.22 30323 +1979 347 5.56 -0.44 3.91 0.01 216.41 94.03 30284 +1979 348 9.72 3.72 8.07 0 280.28 122.15 30251 +1979 349 7.17 1.17 5.52 0.21 239.46 92.72 30221 +1979 350 6.46 0.46 4.81 0.01 229.04 92.81 30197 +1979 351 7.66 1.66 6.01 0 246.88 122.74 30177 +1979 352 8.33 2.33 6.68 0.24 257.34 91.63 30162 +1979 353 9.6 3.6 7.95 0 278.23 121.17 30151 +1979 354 7.59 1.59 5.94 0 245.81 122.6 30145 +1979 355 7.61 1.61 5.96 0.75 246.11 91.94 30144 +1979 356 8.44 2.44 6.79 0.7 259.1 91.52 30147 +1979 357 6.85 0.85 5.2 0.04 234.71 92.38 30156 +1979 358 7.07 1.07 5.42 0 237.97 123.12 30169 +1979 359 6.47 0.47 4.82 0.98 229.19 92.72 30186 +1979 360 5.4 -0.6 3.75 0.84 214.22 93.48 30208 +1979 361 8.21 2.21 6.56 0 255.44 123.14 30235 +1979 362 9.94 3.94 8.29 0 284.07 122.27 30267 +1979 363 12.6 6.6 10.95 0 333.43 120.53 30303 +1979 364 10.87 4.87 9.22 0 300.56 122.46 30343 +1979 365 11.12 5.12 9.47 0 305.13 122.8 30388 +1980 1 8.6 2.6 6.95 0 261.67 125.7 30438 +1980 2 8.5 2.5 6.85 0 260.06 126.49 30492 +1980 3 8.55 2.55 6.9 0 260.86 127.39 30551 +1980 4 5.31 -0.69 3.66 0 213 130.48 30614 +1980 5 2.11 -3.89 0.46 0 173.35 132.88 30681 +1980 6 1.61 -4.39 -0.04 0 167.77 134.02 30752 +1980 7 2.24 -3.76 0.59 0.36 174.83 100.88 30828 +1980 8 2.95 -3.05 1.3 0 183.09 135.63 30907 +1980 9 0.78 -5.22 -0.87 0.57 158.85 103.48 30991 +1980 10 -1.52 -7.52 -3.17 0.74 136.24 149.96 31079 +1980 11 -1.96 -7.96 -3.61 0.14 132.25 151.14 31171 +1980 12 -2.54 -8.54 -4.19 0 127.14 187.61 31266 +1980 13 1.13 -4.87 -0.52 0 162.56 187.39 31366 +1980 14 -0.43 -6.43 -2.08 0 146.58 189.45 31469 +1980 15 2.33 -3.67 0.68 0 175.86 189.12 31575 +1980 16 4.63 -1.37 2.98 0 203.98 188.34 31686 +1980 17 5.13 -0.87 3.48 0.25 210.58 152.29 31800 +1980 18 0.13 -5.87 -1.52 0 152.15 193.4 31917 +1980 19 0.17 -5.83 -1.48 0 152.56 195.15 32038 +1980 20 0.68 -5.32 -0.97 0 157.8 196.25 32161 +1980 21 -0.83 -6.83 -2.48 0 142.71 198.82 32289 +1980 22 -4.63 -10.63 -6.28 0 110.12 201.94 32419 +1980 23 -5.35 -11.35 -7 0 104.73 203.82 32552 +1980 24 -3.6 -9.6 -5.25 0.06 118.24 164.32 32688 +1980 25 -3.78 -9.78 -5.43 0 116.79 207.11 32827 +1980 26 -8.88 -14.88 -10.53 0 81.51 210.52 32969 +1980 27 -10.63 -16.63 -12.28 0.07 71.76 170.06 33114 +1980 28 -8.68 -14.68 -10.33 0 82.69 214.64 33261 +1980 29 -2.94 -8.94 -4.59 0 123.71 214.92 33411 +1980 30 -2.46 -8.46 -4.11 0.04 127.83 172.85 33564 +1980 31 0.11 -5.89 -1.54 0 151.95 217.9 33718 +1980 32 4.24 -1.76 2.59 0 198.96 216.84 33875 +1980 33 2.03 -3.97 0.38 0 172.45 220.48 34035 +1980 34 4.31 -1.69 2.66 0 199.85 220.5 34196 +1980 35 8.1 2.1 6.45 0 253.71 180.96 34360 +1980 36 7.48 1.48 5.83 0.03 244.13 138.01 34526 +1980 37 8.16 2.16 6.51 0.38 254.65 139.34 34694 +1980 38 6.96 0.96 5.31 0.33 236.34 142.19 34863 +1980 39 5.17 -0.83 3.52 0 211.12 193.67 35035 +1980 40 6.27 0.27 4.62 0.25 226.32 146.53 35208 +1980 41 5.29 -0.71 3.64 0 212.73 198.8 35383 +1980 42 4.87 -1.13 3.22 0 207.13 201.69 35560 +1980 43 5.95 -0.05 4.3 0 221.81 203.5 35738 +1980 44 5.27 -0.73 3.62 0 212.46 206.63 35918 +1980 45 4.2 -1.8 2.55 0 198.45 210.12 36099 +1980 46 4.67 -1.33 3.02 0.05 204.5 159.33 36282 +1980 47 6.62 0.62 4.97 0.46 231.36 160.17 36466 +1980 48 5.33 -0.67 3.68 0.03 213.27 163.13 36652 +1980 49 5.23 -0.77 3.58 0 211.92 220.37 36838 +1980 50 5.9 -0.1 4.25 0 221.11 222.44 37026 +1980 51 6.91 0.91 5.26 0 235.6 224.45 37215 +1980 52 6.1 0.1 4.45 0 223.91 228.04 37405 +1980 53 5.12 -0.88 3.47 0 210.45 231.9 37596 +1980 54 5.91 -0.09 4.26 0 221.25 233.93 37788 +1980 55 7.99 1.99 6.34 0.12 251.99 176.1 37981 +1980 56 6.5 0.5 4.85 0 229.62 239.04 38175 +1980 57 5.09 -0.91 3.44 0.4 210.05 182.46 38370 +1980 58 2.52 -3.48 0.87 0.49 178.05 186.31 38565 +1980 59 2.02 -3.98 0.37 0 172.34 251.53 38761 +1980 60 2.91 -3.09 1.26 0 182.61 253.74 38958 +1980 61 5.28 -0.72 3.63 0 212.6 254.58 39156 +1980 62 6.26 0.26 4.61 0 226.18 256.4 39355 +1980 63 11.65 5.65 10 0 315.02 252.71 39553 +1980 64 11.57 5.57 9.92 0.15 313.51 191.76 39753 +1980 65 8.98 2.98 7.33 0 267.86 262.07 39953 +1980 66 13.75 7.75 12.1 0 356.94 257.74 40154 +1980 67 8.07 2.07 6.42 0 253.24 268.8 40355 +1980 68 7.07 1.07 5.42 0.03 237.97 204.63 40556 +1980 69 3.49 -2.51 1.84 0 189.59 279.15 40758 +1980 70 5.59 -0.41 3.94 0 216.82 279.96 40960 +1980 71 9.02 3.02 7.37 0 268.52 278.81 41163 +1980 72 5.79 -0.21 4.14 0 219.58 285.51 41366 +1980 73 7.29 1.29 5.64 0 241.26 286.47 41569 +1980 74 8.41 2.41 6.76 0 258.62 287.82 41772 +1980 75 13.02 7.02 11.37 0.86 341.86 212.66 41976 +1980 76 13.87 7.87 12.22 0.38 359.47 213.45 42179 +1980 77 16.78 10.78 15.13 0.33 425.78 210.92 42383 +1980 78 15.01 9.01 13.36 0 384.31 287.54 42587 +1980 79 13.14 7.14 11.49 0.15 344.3 220.32 42791 +1980 80 7.48 1.48 5.83 0 244.13 304.92 42996 +1980 81 7.81 1.81 6.16 0.46 249.19 230.31 43200 +1980 82 11.77 5.77 10.12 0 317.3 303.8 43404 +1980 83 8.05 2.05 6.4 0.05 252.93 233.94 43608 +1980 84 2.72 -3.28 1.07 0.04 180.38 240.45 43812 +1980 85 0.75 -5.25 -0.9 0 158.54 324.93 44016 +1980 86 0.87 -5.13 -0.78 0 159.8 327.29 44220 +1980 87 2.92 -3.08 1.27 0 182.73 327.98 44424 +1980 88 6.12 0.12 4.47 0 224.2 326.82 44627 +1980 89 6.57 0.57 4.92 0 230.63 328.56 44831 +1980 90 6.09 0.09 4.44 0 223.77 331.56 45034 +1980 91 10.36 4.36 8.71 0 291.42 327.73 45237 +1980 92 14.21 8.21 12.56 0 366.73 322.84 45439 +1980 93 15.42 9.42 13.77 0 393.6 322.4 45642 +1980 94 11.55 5.55 9.9 0.32 313.13 249.21 45843 +1980 95 14.38 8.38 12.73 0 370.41 328.88 46045 +1980 96 17.85 11.85 16.2 0.12 452.65 242.04 46246 +1980 97 13.45 7.45 11.8 0.56 350.68 251.2 46446 +1980 98 11.32 5.32 9.67 0.19 308.83 255.71 46647 +1980 99 9.27 3.27 7.62 0.01 272.67 259.82 46846 +1980 100 10.8 4.8 9.15 0.05 299.29 259.38 47045 +1980 101 12.44 6.44 10.79 0 330.27 344.73 47243 +1980 102 12.77 6.77 11.12 0 336.82 345.98 47441 +1980 103 13.48 7.48 11.83 0 351.3 346.36 47638 +1980 104 14.51 8.51 12.86 0.61 373.25 259.46 47834 +1980 105 8.7 2.7 7.05 0.02 263.29 269.01 48030 +1980 106 12.33 6.33 10.68 0 328.11 353.94 48225 +1980 107 9.48 3.48 7.83 0.48 276.2 270.59 48419 +1980 108 11.19 5.19 9.54 0.47 306.42 269.66 48612 +1980 109 6.03 0.03 4.38 0.08 222.93 277.02 48804 +1980 110 4.13 -1.87 2.48 0.09 197.56 279.91 48995 +1980 111 7.11 1.11 5.46 1.02 238.56 278.16 49185 +1980 112 7.87 1.87 6.22 1.68 250.12 278.48 49374 +1980 113 8.49 2.49 6.84 0.05 259.9 278.78 49561 +1980 114 10.88 4.88 9.23 0 300.74 369.11 49748 +1980 115 10.1 4.1 8.45 0 286.85 371.97 49933 +1980 116 8.95 2.95 7.3 0.17 267.37 281.38 50117 +1980 117 7.41 1.41 5.76 0.34 243.07 284.2 50300 +1980 118 6.55 0.55 4.9 0.65 230.34 286.16 50481 +1980 119 10.23 4.23 8.58 0 289.12 376.85 50661 +1980 120 9.32 3.32 7.67 0 273.51 379.64 50840 +1980 121 13.17 7.17 11.52 0.7 344.91 280.01 51016 +1980 122 16.21 10.21 14.56 0.59 412.03 275.47 51191 +1980 123 19.66 13.66 18.01 0.38 501.4 268.75 51365 +1980 124 19.94 13.94 18.29 0 509.33 358.49 51536 +1980 125 22.66 16.66 21.01 0 592.02 349.87 51706 +1980 126 21.43 15.43 19.78 0.21 553.32 266.5 51874 +1980 127 23.81 17.81 22.16 0 630.27 347.14 52039 +1980 128 23.33 17.33 21.68 0.16 614.06 262.51 52203 +1980 129 15.97 9.97 14.32 0.45 406.36 281.03 52365 +1980 130 15.7 9.7 14.05 0 400.05 376.2 52524 +1980 131 17.42 11.42 15.77 0 441.69 372.34 52681 +1980 132 17.03 11.03 15.38 0.01 431.94 280.69 52836 +1980 133 19.57 13.57 17.92 0.19 498.88 275.49 52989 +1980 134 16.44 10.44 14.79 0 417.53 377.28 53138 +1980 135 16.49 10.49 14.84 0.08 418.74 283.38 53286 +1980 136 14.29 8.29 12.64 0.08 368.46 288.06 53430 +1980 137 8.51 2.51 6.86 0.01 260.22 297.31 53572 +1980 138 7.77 1.77 6.12 0.67 248.57 298.69 53711 +1980 139 14.86 8.86 13.21 0.5 380.96 288.53 53848 +1980 140 15.34 9.34 13.69 1.16 391.77 288 53981 +1980 141 9.05 3.05 7.4 0 269.02 397.79 54111 +1980 142 6.35 0.35 4.7 0.27 227.47 301.97 54238 +1980 143 11.48 5.48 9.83 0.43 311.82 295.71 54362 +1980 144 10.98 4.98 9.33 0 302.56 395.77 54483 +1980 145 12.97 6.97 11.32 0 340.85 392.09 54600 +1980 146 16.51 10.51 14.86 0 419.22 383.71 54714 +1980 147 15.76 9.76 14.11 0 401.44 386.21 54824 +1980 148 13.16 7.16 11.51 0 344.71 392.93 54931 +1980 149 12.34 6.34 10.69 0.49 328.3 296.29 55034 +1980 150 11.37 5.37 9.72 0 309.76 397.42 55134 +1980 151 13.84 7.84 12.19 0 358.84 392.42 55229 +1980 152 20.73 14.73 19.08 0 532.26 372.55 55321 +1980 153 25.74 19.74 24.09 0 699.15 352.46 55409 +1980 154 26.65 20.65 25 0.2 733.78 261.32 55492 +1980 155 24.18 18.18 22.53 0 643.01 359.89 55572 +1980 156 23.98 17.98 22.33 0.04 636.09 270.79 55648 +1980 157 18.34 12.34 16.69 0.33 465.43 286.24 55719 +1980 158 19.63 13.63 17.98 0 500.56 377.71 55786 +1980 159 19.42 13.42 17.77 0 494.69 378.64 55849 +1980 160 23.28 17.28 21.63 0.5 612.39 273.53 55908 +1980 161 17.9 11.9 16.25 0.17 453.94 287.74 55962 +1980 162 16.84 10.84 15.19 0.34 427.25 290.1 56011 +1980 163 19.38 13.38 17.73 2.39 493.58 284.47 56056 +1980 164 18.81 12.81 17.16 0.01 477.98 285.88 56097 +1980 165 20.37 14.37 18.72 0.07 521.7 282.08 56133 +1980 166 18.51 12.51 16.86 0.49 469.94 286.72 56165 +1980 167 21.29 15.29 19.64 0 549.05 372.87 56192 +1980 168 22.41 16.41 20.76 0 583.98 368.73 56214 +1980 169 18.48 12.48 16.83 0 469.14 382.42 56231 +1980 170 19.41 13.41 17.76 0.04 494.41 284.59 56244 +1980 171 19.01 13.01 17.36 0.22 483.41 285.61 56252 +1980 172 27.91 21.91 26.26 0.06 784.11 257.89 56256 +1980 173 25.66 19.66 24.01 0.37 696.18 266.21 56255 +1980 174 25.85 19.85 24.2 0.04 703.26 265.49 56249 +1980 175 23.32 17.32 21.67 0 613.72 365.04 56238 +1980 176 19.84 13.84 18.19 0.13 506.48 283.43 56223 +1980 177 16.42 10.42 14.77 0 417.05 388.22 56203 +1980 178 14.01 8.01 12.36 0 362.45 394.43 56179 +1980 179 12.01 6.01 10.36 0.23 321.89 299.11 56150 +1980 180 18.64 12.64 16.99 0.41 473.41 286.12 56116 +1980 181 21.08 15.08 19.43 0.1 542.7 279.92 56078 +1980 182 23.39 17.39 21.74 0.47 616.06 273.16 56035 +1980 183 25.04 19.04 23.39 0.36 673.47 267.73 55987 +1980 184 19.66 13.66 18.01 0 501.4 377.66 55935 +1980 185 18.11 12.11 16.46 0.72 459.4 286.87 55879 +1980 186 17.96 11.96 16.31 3.34 455.5 287.01 55818 +1980 187 17.41 11.41 15.76 0.26 441.43 288.09 55753 +1980 188 16.66 10.66 15.01 0.86 422.85 289.49 55684 +1980 189 18.68 12.68 17.03 0.42 474.48 284.88 55611 +1980 190 15.3 9.3 13.65 0 390.86 389.05 55533 +1980 191 18.07 12.07 16.42 0 458.35 381.06 55451 +1980 192 19.25 13.25 17.6 0 489.98 377.08 55366 +1980 193 17.93 11.93 16.28 0 454.72 380.9 55276 +1980 194 26.57 20.57 24.92 0.04 730.68 260.55 55182 +1980 195 23.69 17.69 22.04 0 626.18 360.04 55085 +1980 196 19.14 13.14 17.49 0.09 486.96 282.18 54984 +1980 197 20.24 14.24 18.59 0.07 517.94 279.12 54879 +1980 198 16.22 10.22 14.57 0 412.27 383.94 54770 +1980 199 19.79 13.79 18.14 0 505.07 372.89 54658 +1980 200 22.59 16.59 20.94 0 589.76 362.44 54542 +1980 201 21.35 15.35 19.7 0 550.88 366.62 54423 +1980 202 19.49 13.49 17.84 0 496.64 372.43 54301 +1980 203 24.01 18.01 22.36 0 637.13 355.22 54176 +1980 204 26.42 20.42 24.77 0 724.89 343.97 54047 +1980 205 26.58 20.58 24.93 0 731.07 342.72 53915 +1980 206 28.31 22.31 26.66 0 800.68 333.5 53780 +1980 207 27.57 21.57 25.92 0.2 770.25 252.52 53643 +1980 208 23.04 17.04 21.39 0.01 604.44 267.24 53502 +1980 209 21.83 15.83 20.18 0 565.66 360.29 53359 +1980 210 22.98 16.98 21.33 0 602.46 355.31 53213 +1980 211 23.21 17.21 21.56 0 610.06 353.65 53064 +1980 212 24.63 18.63 22.98 0.01 658.8 260.27 52913 +1980 213 26.63 20.63 24.98 0.23 733 252.96 52760 +1980 214 25.08 19.08 23.43 0.03 674.91 257.73 52604 +1980 215 22.83 16.83 21.18 0.04 597.55 264.16 52445 +1980 216 20.41 14.41 18.76 0 522.87 359.92 52285 +1980 217 18.25 12.25 16.6 0 463.06 365.84 52122 +1980 218 21.94 15.94 20.29 0 569.1 352.87 51958 +1980 219 20.3 14.3 18.65 0 519.67 357.54 51791 +1980 220 19.98 13.98 18.33 0 510.47 357.65 51622 +1980 221 18.31 12.31 16.66 0 464.64 361.81 51451 +1980 222 17.99 11.99 16.34 0 456.27 361.69 51279 +1980 223 22.85 16.85 21.2 0 598.2 344.4 51105 +1980 224 23.35 17.35 21.7 0 614.73 341.45 50929 +1980 225 26.57 20.57 24.92 0 730.68 326.67 50751 +1980 226 24.92 18.92 23.27 0 669.14 332.88 50572 +1980 227 26.37 20.37 24.72 0 722.97 325.3 50392 +1980 228 27.32 21.32 25.67 0 760.19 319.72 50210 +1980 229 27.62 21.62 25.97 0 772.27 317.12 50026 +1980 230 26.98 20.98 25.33 0 746.69 318.98 49842 +1980 231 21.11 15.11 19.46 0.04 543.61 255.73 49656 +1980 232 22.14 16.14 20.49 0 575.39 336.07 49469 +1980 233 25.79 19.79 24.14 0.6 701.02 240.25 49280 +1980 234 21.75 15.75 20.1 0.18 563.17 250.99 49091 +1980 235 20.16 14.16 18.51 0.25 515.63 253.82 48900 +1980 236 22.64 16.64 20.99 0 591.38 328.65 48709 +1980 237 24.76 18.76 23.11 0 663.42 318.95 48516 +1980 238 22.4 16.4 20.75 0 583.66 326.27 48323 +1980 239 23.91 17.91 22.26 0 633.69 319.25 48128 +1980 240 20.27 14.27 18.62 0 518.8 330.13 47933 +1980 241 17.29 11.29 15.64 0 438.42 336.93 47737 +1980 242 19.36 13.36 17.71 0 493.03 329.45 47541 +1980 243 18.74 12.74 17.09 3.18 476.09 247.03 47343 +1980 244 14.92 8.92 13.27 0.55 382.3 252.87 47145 +1980 245 16.12 10.12 14.47 0 409.89 332.51 46947 +1980 246 16.65 10.65 15 0 422.61 329.23 46747 +1980 247 15.78 9.78 14.13 0.08 401.91 247.08 46547 +1980 248 15.12 9.12 13.47 0.37 386.79 246.73 46347 +1980 249 14.62 8.62 12.97 0.12 375.66 245.98 46146 +1980 250 14.83 8.83 13.18 0.05 380.3 244.15 45945 +1980 251 12.45 6.45 10.8 0 330.46 328.18 45743 +1980 252 19.46 13.46 17.81 0 495.8 309.75 45541 +1980 253 16.88 10.88 15.23 0.06 428.23 235.78 45339 +1980 254 19.45 13.45 17.8 0.25 495.53 229.19 45136 +1980 255 21.96 15.96 20.31 0.02 569.72 221.91 44933 +1980 256 19.3 13.3 17.65 0 491.36 301.53 44730 +1980 257 22.74 16.74 21.09 0.62 594.62 216.81 44527 +1980 258 16.07 10.07 14.42 0.76 408.71 228.79 44323 +1980 259 13.84 7.84 12.19 0.17 358.84 230.45 44119 +1980 260 13.66 7.66 12.01 0.03 355.05 228.9 43915 +1980 261 16.91 10.91 15.26 0.17 428.97 221.91 43711 +1980 262 15.06 9.06 13.41 0.19 385.44 223.15 43507 +1980 263 17.52 11.52 15.87 0 444.22 289.64 43303 +1980 264 19.06 13.06 17.41 0 484.77 283.3 43099 +1980 265 21.35 15.35 19.7 0.14 550.88 206.05 42894 +1980 266 21.68 15.68 20.03 0 561.01 271.38 42690 +1980 267 22.6 16.6 20.95 0 590.08 266.05 42486 +1980 268 22.72 16.72 21.07 1.26 593.97 197.43 42282 +1980 269 23.59 17.59 21.94 0.74 622.79 193.59 42078 +1980 270 19.71 13.71 18.06 0.18 502.81 200.06 41875 +1980 271 20.21 14.21 18.56 0.26 517.07 197.18 41671 +1980 272 23.24 17.24 21.59 0 611.06 251.68 41468 +1980 273 25.45 19.45 23.8 0 688.41 242.11 41265 +1980 274 17.4 11.4 15.75 0 441.18 261.89 41062 +1980 275 19.44 13.44 17.79 0 495.25 254.48 40860 +1980 276 22.05 16.05 20.4 0 572.55 245.08 40658 +1980 277 22 16 20.35 0.18 570.98 182.02 40456 +1980 278 19.52 13.52 17.87 0.34 497.48 184.74 40255 +1980 279 18.19 12.19 16.54 0.44 461.49 184.98 40054 +1980 280 16.94 10.94 15.29 0 429.71 246.68 39854 +1980 281 10.81 4.81 9.16 0 299.47 254.32 39654 +1980 282 9.26 3.26 7.61 0 272.5 253.59 39455 +1980 283 9.8 3.8 8.15 0 281.65 250.04 39256 +1980 284 8.67 2.67 7.02 0.35 262.8 186.28 39058 +1980 285 8.22 2.22 6.57 0.56 255.6 184.65 38861 +1980 286 11.94 5.94 10.29 0.02 320.54 178.98 38664 +1980 287 13.61 7.61 11.96 0.76 354.01 174.91 38468 +1980 288 11.41 5.41 9.76 0 310.51 233.64 38273 +1980 289 11.95 5.95 10.3 0 320.74 230.26 38079 +1980 290 11.02 5.02 9.37 0.66 303.3 171.48 37885 +1980 291 15.03 9.03 13.38 2.01 384.76 165.04 37693 +1980 292 14.37 8.37 12.72 0 370.19 218.47 37501 +1980 293 13.38 7.38 11.73 0.79 349.23 162.95 37311 +1980 294 15.06 9.06 13.41 0.44 385.44 158.87 37121 +1980 295 11.43 5.43 9.78 0.03 310.88 160.68 36933 +1980 296 12.73 6.73 11.08 0.05 336.02 157.45 36745 +1980 297 11.51 5.51 9.86 0.35 312.38 156.62 36560 +1980 298 11.92 5.92 10.27 0.91 320.16 154.28 36375 +1980 299 9.8 3.8 8.15 0.35 281.65 154.1 36191 +1980 300 11.84 5.84 10.19 0.54 318.63 150.29 36009 +1980 301 11.62 5.62 9.97 1.1 314.45 148.62 35829 +1980 302 10.41 4.41 8.76 0 292.3 196.97 35650 +1980 303 11.23 5.23 9.58 0.18 307.16 145.09 35472 +1980 304 8.63 2.63 6.98 0 262.15 193.8 35296 +1980 305 0.62 -5.38 -1.03 0 157.18 197.19 35122 +1980 306 1.42 -4.58 -0.23 0.13 165.69 145.8 34950 +1980 307 -0.81 -6.81 -2.46 0 142.9 193.08 34779 +1980 308 1.11 -4.89 -0.54 0 162.35 189.36 34610 +1980 309 7.07 1.07 5.42 0.31 237.97 137.06 34444 +1980 310 8.22 2.22 6.57 0.34 255.6 134.46 34279 +1980 311 9.92 3.92 8.27 0.34 283.72 131.61 34116 +1980 312 12.65 6.65 11 1.39 334.42 127.41 33956 +1980 313 14.65 8.65 13 0.3 376.32 123.99 33797 +1980 314 10.95 4.95 9.3 0.03 302.02 125.82 33641 +1980 315 15.09 9.09 13.44 0 386.11 160.38 33488 +1980 316 13.94 7.94 12.29 0.37 360.96 119.8 33337 +1980 317 8.89 2.89 7.24 1.03 266.38 122.17 33188 +1980 318 7.03 1.03 5.38 0.8 237.37 121.6 33042 +1980 319 2.8 -3.2 1.15 1.35 181.32 122.49 32899 +1980 320 6.1 0.1 4.45 0 223.91 159.26 32758 +1980 321 1.2 -4.8 -0.45 1.38 163.31 120.14 32620 +1980 322 3.75 -2.25 2.1 0.19 192.79 117.67 32486 +1980 323 4.95 -1.05 3.3 0.16 208.18 115.87 32354 +1980 324 6.28 0.28 4.63 0 226.47 151.52 32225 +1980 325 6.44 0.44 4.79 0.12 228.76 112.26 32100 +1980 326 5.14 -0.86 3.49 0.04 210.72 111.84 31977 +1980 327 3.8 -2.2 2.15 0.75 193.42 111.07 31858 +1980 328 4.77 -1.23 3.12 0.01 205.81 109.14 31743 +1980 329 5.66 -0.34 4.01 0.09 217.78 107.59 31631 +1980 330 6.61 0.61 4.96 0.68 231.21 106.02 31522 +1980 331 7.89 1.89 6.24 0.16 250.43 104.34 31417 +1980 332 9.48 3.48 7.83 1.03 276.2 102.17 31316 +1980 333 6.57 0.57 4.92 0 230.63 137.35 31218 +1980 334 9.32 3.32 7.67 0 273.51 134.21 31125 +1980 335 5.06 -0.94 3.41 0.01 209.65 102.05 31035 +1980 336 2.98 -3.02 1.33 0 183.44 136.18 30949 +1980 337 4.86 -1.14 3.21 0 206.99 133.45 30867 +1980 338 3.31 -2.69 1.66 0 187.4 133.39 30790 +1980 339 6.72 0.72 5.07 0 232.81 130.55 30716 +1980 340 7.77 1.77 6.12 0 248.57 129.09 30647 +1980 341 8.14 2.14 6.49 0 254.34 127.92 30582 +1980 342 7.4 1.4 5.75 0 242.92 127.69 30521 +1980 343 6.38 0.38 4.73 0 227.89 127.55 30465 +1980 344 6.47 0.47 4.82 0 229.19 126.37 30413 +1980 345 2.82 -3.18 1.17 0.08 181.55 96.03 30366 +1980 346 3.95 -2.05 2.3 0 195.29 126.89 30323 +1980 347 2.76 -3.24 1.11 0 180.85 126.91 30284 +1980 348 2.45 -3.55 0.8 0 177.24 126.72 30251 +1980 349 4.72 -1.28 3.07 0 205.16 125.13 30221 +1980 350 3.49 -2.51 1.84 0.38 189.59 94.1 30197 +1980 351 1.88 -4.12 0.23 0 170.77 126.05 30177 +1980 352 2.15 -3.85 0.5 0.56 173.81 94.37 30162 +1980 353 2.83 -3.17 1.18 0.59 181.67 94.07 30151 +1980 354 2.98 -3.02 1.33 1 183.44 93.99 30145 +1980 355 -4.33 -10.33 -5.98 0.53 112.43 141.66 30144 +1980 356 -1.57 -7.57 -3.22 0 135.78 172.8 30147 +1980 357 -1.99 -7.99 -3.64 0 131.98 173.01 30156 +1980 358 1.61 -4.39 -0.04 0 167.77 171.38 30169 +1980 359 3.17 -2.83 1.52 0.34 185.71 138.91 30186 +1980 360 1.07 -4.93 -0.58 0.02 161.92 139.77 30208 +1980 361 2.01 -3.99 0.36 0.59 172.22 139.39 30235 +1980 362 1.51 -4.49 -0.14 0 166.68 171.51 30267 +1980 363 0.25 -5.75 -1.4 0 153.37 172.58 30303 +1980 364 1.56 -4.44 -0.09 0 167.22 172.12 30343 +1980 365 1.52 -4.48 -0.13 0 166.78 129.02 30388 +1981 1 0.77 -5.23 -0.88 0 158.75 130.26 30438 +1981 2 -1.64 -7.64 -3.29 0.35 135.14 143.38 30492 +1981 3 -3.31 -9.31 -4.96 0 120.62 177.85 30551 +1981 4 -4.93 -10.93 -6.58 0 107.85 179.21 30614 +1981 5 -1.72 -7.72 -3.37 0 134.41 178.67 30681 +1981 6 0.71 -5.29 -0.94 0.07 158.12 144.75 30752 +1981 7 1.95 -4.05 0.3 1.48 171.55 144.55 30828 +1981 8 -1.41 -7.41 -3.06 0.24 137.25 147.43 30907 +1981 9 -1.68 -7.68 -3.33 0 134.77 183.09 30991 +1981 10 -0.33 -6.33 -1.98 0 147.56 183.73 31079 +1981 11 -1.77 -7.77 -3.42 0 133.96 185.19 31171 +1981 12 -0.95 -6.95 -2.6 0 141.57 185.75 31266 +1981 13 -2.1 -8.1 -3.75 0 131 187.71 31366 +1981 14 1.16 -4.84 -0.49 0 162.88 187.49 31469 +1981 15 4.66 -1.34 3.01 0 204.37 186.26 31575 +1981 16 1.23 -4.77 -0.42 0.06 163.64 152.42 31686 +1981 17 0.11 -5.89 -1.54 0 151.95 191.22 31800 +1981 18 3.64 -2.36 1.99 0 191.43 190.66 31917 +1981 19 3.28 -2.72 1.63 0.03 187.04 113.53 32038 +1981 20 4.71 -1.29 3.06 0 205.02 152.08 32161 +1981 21 3.78 -2.22 2.13 0 193.17 154.66 32289 +1981 22 3.49 -2.51 1.84 0 189.59 156.59 32419 +1981 23 -0.05 -6.05 -1.7 0 150.34 160.29 32552 +1981 24 4.71 -1.29 3.06 0 205.02 159.65 32688 +1981 25 3.52 -2.48 1.87 0 189.96 162.31 32827 +1981 26 2.89 -3.11 1.24 0.02 182.38 123.47 32969 +1981 27 3.06 -2.94 1.41 0.07 184.4 124.91 33114 +1981 28 1.66 -4.34 0.01 0 168.32 169.59 33261 +1981 29 3.05 -2.95 1.4 0 184.28 171.15 33411 +1981 30 3.01 -2.99 1.36 0 183.8 173.42 33564 +1981 31 1.37 -4.63 -0.28 0.02 165.15 132.59 33718 +1981 32 5.69 -0.31 4.04 0 218.19 176.05 33875 +1981 33 3.97 -2.03 2.32 0 195.54 179.92 34035 +1981 34 3.95 -2.05 2.3 0 195.29 182.14 34196 +1981 35 4.87 -1.13 3.22 0 207.13 183.63 34360 +1981 36 7.05 1.05 5.4 0 237.67 184.38 34526 +1981 37 5.98 -0.02 4.33 0 222.23 187.69 34694 +1981 38 8.07 2.07 6.42 0 253.24 188.59 34863 +1981 39 5.08 -0.92 3.43 0.56 209.91 145.31 35035 +1981 40 3.82 -2.18 2.17 0.01 193.66 147.98 35208 +1981 41 6.11 0.11 4.46 0.09 224.06 148.59 35383 +1981 42 3.69 -2.31 2.04 0.25 192.05 151.94 35560 +1981 43 5.65 -0.35 4 0 217.64 203.75 35738 +1981 44 7.23 1.23 5.58 0.05 240.35 153.68 35918 +1981 45 5.37 -0.63 3.72 0 213.82 209.17 36099 +1981 46 5.4 -0.6 3.75 0.38 214.22 158.87 36282 +1981 47 2.53 -3.47 0.88 0 178.16 216.89 36466 +1981 48 1.02 -4.98 -0.63 0.02 161.39 165.56 36652 +1981 49 4.84 -1.16 3.19 0 206.73 220.71 36838 +1981 50 4.41 -1.59 2.76 0.39 201.13 167.8 37026 +1981 51 -1.66 -7.66 -3.31 0.01 134.96 208.66 37215 +1981 52 1.76 -4.24 0.11 0.15 169.43 173.7 37405 +1981 53 0.42 -5.58 -1.23 0.17 155.11 176.62 37596 +1981 54 -0.16 -6.16 -1.81 0 149.25 238.66 37788 +1981 55 -0.1 -6.1 -1.75 0 149.84 241.66 37981 +1981 56 3.13 -2.87 1.48 0 185.23 242.06 38175 +1981 57 4.44 -1.56 2.79 0.37 201.52 182.89 38370 +1981 58 7.4 1.4 5.75 0 242.92 243.9 38565 +1981 59 5.35 -0.65 3.7 0 213.54 248.68 38761 +1981 60 16.12 10.12 14.47 0.03 409.89 177.61 38958 +1981 61 11.97 5.97 10.32 0 321.12 246.55 39156 +1981 62 13.11 7.11 11.46 0 343.69 247.54 39355 +1981 63 14.5 8.5 12.85 0 373.03 248.16 39553 +1981 64 17.85 11.85 16.2 0 452.65 244.49 39753 +1981 65 16.26 10.26 14.61 0 413.22 250.5 39953 +1981 66 12.77 6.77 11.12 0.08 336.82 194.52 40154 +1981 67 13.39 7.39 11.74 0.02 349.43 195.88 40355 +1981 68 11.78 5.78 10.13 0.38 317.49 199.93 40556 +1981 69 8.92 2.92 7.27 0.21 266.88 204.91 40758 +1981 70 12.29 6.29 10.64 0.39 327.32 203.36 40960 +1981 71 6.27 0.27 4.62 0 226.32 282.15 41163 +1981 72 9.96 3.96 8.31 0 284.41 280.33 41366 +1981 73 13.27 7.27 11.62 0 346.96 277.75 41569 +1981 74 14.82 8.82 13.17 0.11 380.08 208.18 41772 +1981 75 16.88 10.88 15.23 0 428.23 275.98 41976 +1981 76 14.49 8.49 12.84 0.08 372.81 212.57 42179 +1981 77 12.91 6.91 11.26 2.61 339.63 216.65 42383 +1981 78 13.11 7.11 11.46 0.19 343.69 218.35 42587 +1981 79 10.44 4.44 8.79 0 292.83 298.25 42791 +1981 80 10.71 4.71 9.06 0.03 297.67 225.26 42996 +1981 81 4.96 -1.04 3.31 0 208.32 310.51 43200 +1981 82 3.88 -2.12 2.23 0 194.41 314.34 43404 +1981 83 8.7 2.7 7.05 0 263.29 311.03 43608 +1981 84 9.7 3.7 8.05 0 279.94 312.11 43812 +1981 85 9.46 3.46 7.81 0 275.86 314.96 44016 +1981 86 11.21 5.21 9.56 0 306.79 314.59 44220 +1981 87 11.23 5.23 9.58 0 307.16 317.07 44424 +1981 88 14.13 8.13 12.48 0 365.02 314.02 44627 +1981 89 9.41 3.41 7.76 0 275.02 324.6 44831 +1981 90 11.99 5.99 10.34 0 321.51 322.69 45034 +1981 91 15.85 9.85 14.2 0 403.54 317.08 45237 +1981 92 17.8 11.8 16.15 0 451.37 314.53 45439 +1981 93 16.37 10.37 14.72 0 415.85 320.2 45642 +1981 94 15.49 9.49 13.84 0 395.2 324.34 45843 +1981 95 14.07 8.07 12.42 0 363.73 329.54 46045 +1981 96 14.12 8.12 12.47 0 364.8 331.51 46246 +1981 97 16.66 10.66 15.01 0 422.85 327.74 46446 +1981 98 14.7 8.7 13.05 0 377.42 334.22 46647 +1981 99 17.1 11.1 15.45 0 433.67 330.5 46846 +1981 100 12.35 6.35 10.7 0 328.5 342.98 47045 +1981 101 13.9 7.9 12.25 0 360.11 341.76 47243 +1981 102 11.9 5.9 10.25 0 319.78 347.67 47441 +1981 103 12.66 6.66 11.01 0 334.62 348.03 47638 +1981 104 14.16 8.16 12.51 0 365.66 346.72 47834 +1981 105 14.05 8.05 12.4 0 363.3 348.73 48030 +1981 106 12.7 6.7 11.05 0 335.42 353.2 48225 +1981 107 9.66 3.66 8.01 0 279.26 360.48 48419 +1981 108 9.38 3.38 7.73 0 274.51 362.71 48612 +1981 109 8.38 2.38 6.73 0 258.14 365.95 48804 +1981 110 9.66 3.66 8.01 0 279.26 365.3 48995 +1981 111 6.57 0.57 4.92 0.15 230.63 278.74 49185 +1981 112 10.55 4.55 8.9 0 294.79 366.85 49374 +1981 113 13.81 7.81 12.16 0.04 358.21 271.26 49561 +1981 114 13.66 7.66 12.01 0 355.05 363.5 49748 +1981 115 13.43 7.43 11.78 1.52 350.26 274.07 49933 +1981 116 13.02 7.02 11.37 0 341.86 367.53 50117 +1981 117 16.77 10.77 15.12 0 425.54 359.89 50300 +1981 118 15.49 9.49 13.84 0 395.2 364.48 50481 +1981 119 16.49 10.49 14.84 0 418.74 363.11 50661 +1981 120 14.22 8.22 12.57 0 366.95 369.87 50840 +1981 121 16.41 10.41 14.76 0 416.81 365.59 51016 +1981 122 18.2 12.2 16.55 0 461.75 361.8 51191 +1981 123 20.97 14.97 19.32 0 539.4 354 51365 +1981 124 20.43 14.43 18.78 0 523.45 356.87 51536 +1981 125 19.19 13.19 17.54 0 488.33 361.83 51706 +1981 126 17.36 11.36 15.71 0 440.17 368.23 51874 +1981 127 14.68 8.68 13.03 0 376.98 376.09 52039 +1981 128 16.86 10.86 15.21 0 427.74 371.49 52203 +1981 129 18.63 12.63 16.98 0 473.14 367.21 52365 +1981 130 20.01 14.01 18.36 0.43 511.32 272.71 52524 +1981 131 26.47 20.47 24.82 0 726.82 338.68 52681 +1981 132 20.45 14.45 18.8 0.03 524.04 272.79 52836 +1981 133 18.38 12.38 16.73 0 466.49 371.04 52989 +1981 134 21.61 15.61 19.96 0 558.84 361.01 53138 +1981 135 23.66 17.66 22.01 0 625.16 353.79 53286 +1981 136 23.42 17.42 21.77 0.71 617.07 266.52 53430 +1981 137 18.57 12.57 16.92 0.27 471.54 279.88 53572 +1981 138 19.32 13.32 17.67 1.44 491.92 278.56 53711 +1981 139 16.18 10.18 14.53 0.77 411.32 285.99 53848 +1981 140 20.07 14.07 18.42 0 513.04 370.11 53981 +1981 141 15.41 9.41 13.76 0.11 393.37 288.19 54111 +1981 142 11.58 5.58 9.93 0 313.7 393.53 54238 +1981 143 13.12 7.12 11.47 0 343.89 390.79 54362 +1981 144 11.98 5.98 10.33 0.8 321.31 295.31 54483 +1981 145 11.97 5.97 10.32 0.89 321.12 295.69 54600 +1981 146 14.82 8.82 13.17 0.24 380.08 291.09 54714 +1981 147 15.66 9.66 14.01 0.98 399.12 289.85 54824 +1981 148 12.2 6.2 10.55 0.08 325.57 296.27 54931 +1981 149 15.1 9.1 13.45 0 386.34 388.61 55034 +1981 150 20.19 14.19 18.54 0.42 516.49 280.45 55134 +1981 151 17.83 11.83 16.18 0.48 452.14 286.38 55229 +1981 152 22.23 16.23 20.58 0.12 578.24 275.29 55321 +1981 153 20.35 14.35 18.7 0.88 521.12 280.59 55409 +1981 154 19.27 13.27 17.62 0.73 490.54 283.53 55492 +1981 155 20.16 14.16 18.51 0.05 515.63 281.45 55572 +1981 156 19.45 13.45 17.8 1.45 495.53 283.47 55648 +1981 157 19.23 13.23 17.58 0.59 489.43 284.13 55719 +1981 158 17.63 11.63 15.98 0.18 447.01 287.97 55786 +1981 159 19.89 13.89 18.24 0 507.9 377.08 55849 +1981 160 25.64 19.64 23.99 0.42 695.43 265.84 55908 +1981 161 24.66 18.66 23.01 0.43 659.86 269.2 55962 +1981 162 24.73 18.73 23.08 0.07 662.35 269.01 56011 +1981 163 23.58 17.58 21.93 0.3 622.45 272.85 56056 +1981 164 23.92 17.92 22.27 0.26 634.03 271.82 56097 +1981 165 20.74 14.74 19.09 0 532.56 374.81 56133 +1981 166 20.26 14.26 18.61 0 518.51 376.57 56165 +1981 167 20.2 14.2 18.55 0.04 516.78 282.54 56192 +1981 168 23.21 17.21 21.56 0 610.06 365.55 56214 +1981 169 25.61 19.61 23.96 0.46 694.32 266.36 56231 +1981 170 25.32 19.32 23.67 0.02 683.64 267.36 56244 +1981 171 25.66 19.66 24.01 0.9 696.18 266.23 56252 +1981 172 16.83 10.83 15.18 0 427.01 387.36 56256 +1981 173 14.78 8.78 13.13 0.17 379.19 294.59 56255 +1981 174 16.11 10.11 14.46 0.13 409.66 291.93 56249 +1981 175 17.19 11.19 15.54 0.63 435.91 289.65 56238 +1981 176 21.88 15.88 20.23 0.35 567.22 277.99 56223 +1981 177 25.57 19.57 23.92 0 692.84 355.12 56203 +1981 178 24.85 18.85 23.2 0 666.63 358.41 56179 +1981 179 26.81 20.81 25.16 0 740.02 349.13 56150 +1981 180 25.37 19.37 23.72 0.43 685.47 266.89 56116 +1981 181 25.14 19.14 23.49 0.16 677.09 267.63 56078 +1981 182 23.66 17.66 22.01 0.05 625.16 272.33 56035 +1981 183 23.96 17.96 22.31 1.46 635.41 271.25 55987 +1981 184 22.94 16.94 21.29 1.07 601.15 274.28 55935 +1981 185 20.2 14.2 18.55 0 516.78 375.76 55879 +1981 186 22.34 16.34 20.69 0.06 581.74 275.79 55818 +1981 187 22.64 16.64 20.99 0.4 591.38 274.78 55753 +1981 188 20.56 14.56 18.91 0.38 527.26 280.35 55684 +1981 189 24.44 18.44 22.79 0.06 652.09 268.89 55611 +1981 190 23 17 21.35 2.27 603.12 273.11 55533 +1981 191 20.89 14.89 19.24 1.49 537.02 278.87 55451 +1981 192 18.62 12.62 16.97 0 472.87 379.07 55366 +1981 193 18.32 12.32 16.67 0 464.91 379.72 55276 +1981 194 24.91 18.91 23.26 0 668.79 355.08 55182 +1981 195 30.93 24.93 29.28 0 916.73 323.38 55085 +1981 196 28.05 22.05 26.4 0.32 789.88 254.47 54984 +1981 197 27.73 21.73 26.08 0.3 776.75 255.4 54879 +1981 198 25.96 19.96 24.31 0 707.39 348.81 54770 +1981 199 27.74 21.74 26.09 0.01 777.15 254.81 54658 +1981 200 25.92 19.92 24.27 0.01 705.89 261.21 54542 +1981 201 26.23 20.23 24.58 0 717.62 346.37 54423 +1981 202 20.93 14.93 19.28 0.02 538.21 275.67 54301 +1981 203 18.77 12.77 17.12 0 476.9 374.21 54176 +1981 204 21.04 15.04 19.39 0 541.5 366.16 54047 +1981 205 26.39 20.39 24.74 0.29 723.74 257.72 53915 +1981 206 21.12 15.12 19.47 0 543.91 364.8 53780 +1981 207 19.33 13.33 17.68 0 492.19 370.18 53643 +1981 208 16.76 10.76 15.11 0 425.29 377.15 53502 +1981 209 14.57 8.57 12.92 0.16 374.56 286.6 53359 +1981 210 17.59 11.59 15.94 0.03 446 280.13 53213 +1981 211 21.8 15.8 20.15 0 564.73 359.02 53064 +1981 212 23.75 17.75 22.1 0 628.22 350.7 52913 +1981 213 21.54 15.54 19.89 0 556.69 358.42 52760 +1981 214 20.4 14.4 18.75 0 522.58 361.64 52604 +1981 215 20.36 14.36 18.71 0 521.41 361.1 52445 +1981 216 17.9 11.9 16.25 0 453.94 367.77 52285 +1981 217 18.77 12.77 17.12 0 476.9 364.27 52122 +1981 218 16.15 10.15 14.5 0 410.61 370.85 51958 +1981 219 15.73 9.73 14.08 0 400.75 370.86 51791 +1981 220 16.54 10.54 14.89 0.01 419.95 275.84 51622 +1981 221 17.28 11.28 15.63 0.11 438.16 273.57 51451 +1981 222 14.42 8.42 12.77 0.02 371.28 278.23 51279 +1981 223 20.89 14.89 19.24 0 537.02 351.45 51105 +1981 224 19.8 13.8 18.15 0 505.35 353.98 50929 +1981 225 22.31 16.31 20.66 0 580.78 344.26 50751 +1981 226 23.32 17.32 21.67 0 613.72 339.34 50572 +1981 227 24.99 18.99 23.34 0 671.66 331.35 50392 +1981 228 25.48 19.48 23.83 0 689.52 328.09 50210 +1981 229 26.19 20.19 24.54 0 716.1 323.79 50026 +1981 230 27.04 21.04 25.39 0.01 749.06 239.02 49842 +1981 231 30.01 24.01 28.36 0 874.47 302.29 49656 +1981 232 29.6 23.6 27.95 0 856.17 303.28 49469 +1981 233 30.63 24.63 28.98 0 902.77 296.36 49280 +1981 234 27.19 21.19 25.54 0 755 312.7 49091 +1981 235 27.95 21.95 26.3 0.14 785.75 230.78 48900 +1981 236 29.36 23.36 27.71 0.61 845.61 224.5 48709 +1981 237 30.01 24.01 28.36 0 874.47 294.4 48516 +1981 238 29.87 23.87 28.22 0.24 868.18 220.22 48323 +1981 239 24.67 18.67 23.02 0.75 660.22 237.21 48128 +1981 240 21.44 15.44 19.79 0.65 553.62 244.78 47933 +1981 241 18.9 12.9 17.25 1.27 480.41 249.39 47737 +1981 242 21.92 15.92 20.27 0.81 568.47 241.02 47541 +1981 243 21.57 15.57 19.92 0.36 557.61 240.54 47343 +1981 244 18.61 12.61 16.96 0.05 472.61 245.94 47145 +1981 245 22.51 16.51 20.86 0.09 587.18 235.47 46947 +1981 246 18.93 12.93 17.28 0.11 481.23 242.42 46747 +1981 247 15.65 9.65 14 0.48 398.89 247.31 46547 +1981 248 13.87 7.87 12.22 0.9 359.47 248.75 46347 +1981 249 13.46 7.46 11.81 0.76 350.88 247.79 46146 +1981 250 10.69 4.69 9.04 1.34 297.3 250.12 45945 +1981 251 13.45 7.45 11.8 2.03 350.68 244.69 45743 +1981 252 13.96 7.96 12.31 0 361.38 323.01 45541 +1981 253 15.52 9.52 13.87 0 395.89 317.54 45339 +1981 254 18.67 12.67 17.02 0 474.21 307.71 45136 +1981 255 18.38 12.38 16.73 0 466.49 306.23 44933 +1981 256 18.79 12.79 17.14 0 477.44 302.91 44730 +1981 257 24.45 18.45 22.8 0 652.44 283.16 44527 +1981 258 26.06 20.06 24.41 0 711.17 274.87 44323 +1981 259 23.71 17.71 22.06 0.33 626.86 210.93 44119 +1981 260 20.58 14.58 18.93 0.58 527.84 216.61 43915 +1981 261 21.66 15.66 20.01 0.53 560.39 212.43 43711 +1981 262 22.79 16.79 21.14 0.08 596.25 208.08 43507 +1981 263 26.57 20.57 24.92 0 730.68 261.66 43303 +1981 264 26.6 20.6 24.95 0 731.84 259.17 43099 +1981 265 23.68 17.68 22.03 0 625.84 267.49 42894 +1981 266 23.71 17.71 22.06 0.31 626.86 198.79 42690 +1981 267 22.53 16.53 20.88 0.84 587.83 199.7 42486 +1981 268 20.06 14.06 18.41 0.53 512.76 203.13 42282 +1981 269 17.35 11.35 15.7 0.59 439.92 206.25 42078 +1981 270 16.58 10.58 14.93 0.29 420.91 205.56 41875 +1981 271 17.24 11.24 15.59 0.29 437.16 202.54 41671 +1981 272 18.64 12.64 16.99 0 473.41 264.17 41468 +1981 273 19.08 13.08 17.43 0.78 485.32 195.48 41265 +1981 274 12.7 6.7 11.05 0 335.42 270.83 41062 +1981 275 11.25 5.25 9.6 0.02 307.53 202.73 40860 +1981 276 14.69 8.69 13.04 0.04 377.2 196.42 40658 +1981 277 14.35 8.35 12.7 1.16 369.76 194.89 40456 +1981 278 14.78 8.78 13.13 0.46 379.19 192.16 40255 +1981 279 12.34 6.34 10.69 0 328.3 257.5 40054 +1981 280 17.97 11.97 16.32 0 455.76 244.53 39854 +1981 281 18.88 12.88 17.23 0 479.87 239.89 39654 +1981 282 17.85 11.85 16.2 0.33 452.65 179.6 39455 +1981 283 19.46 13.46 17.81 0 495.8 233.2 39256 +1981 284 19.2 13.2 17.55 0.04 488.61 173.15 39058 +1981 285 18.64 12.64 16.99 0 473.41 229.54 38861 +1981 286 17.47 11.47 15.82 0.3 442.95 171.96 38664 +1981 287 16.04 10.04 14.39 0.06 408 171.83 38468 +1981 288 15.65 9.65 14 0.09 398.89 170.3 38273 +1981 289 12.85 6.85 11.2 0 338.42 228.97 38079 +1981 290 17.12 11.12 15.47 0 434.17 219.02 37885 +1981 291 19.01 13.01 17.36 0 483.41 212.67 37693 +1981 292 16.69 10.69 15.04 0.26 423.59 160.92 37501 +1981 293 11.73 5.73 10.08 0.34 316.53 164.68 37311 +1981 294 13.67 7.67 12.02 0 355.26 213.98 37121 +1981 295 14 8 12.35 0.37 362.24 158.01 36933 +1981 296 9.49 3.49 7.84 0 276.37 213.97 36745 +1981 297 12.53 6.53 10.88 0 332.04 207.5 36560 +1981 298 14.79 8.79 13.14 0.67 379.41 151.27 36375 +1981 299 12.55 6.55 10.9 0.14 332.44 151.59 36191 +1981 300 14.27 8.27 12.62 0 368.03 197.11 36009 +1981 301 15.36 9.36 13.71 0 392.23 193.01 35829 +1981 302 18.18 12.18 16.53 0 461.23 185.79 35650 +1981 303 13.76 7.76 12.11 0 357.15 190.24 35472 +1981 304 13.91 7.91 12.26 0.86 360.32 140.71 35296 +1981 305 7.17 1.17 5.52 0 239.46 192.42 35122 +1981 306 9.86 3.86 8.21 0 282.68 187.55 34950 +1981 307 12.85 6.85 11.2 1.24 338.42 136.22 34779 +1981 308 10.63 4.63 8.98 0.01 296.23 136.22 34610 +1981 309 8.59 2.59 6.94 0 261.51 181.38 34444 +1981 310 7.03 1.03 5.38 0 237.37 180.33 34279 +1981 311 7.33 1.33 5.68 0 241.86 177.88 34116 +1981 312 4.47 -1.53 2.82 0 201.91 177.45 33956 +1981 313 8.34 2.34 6.69 0.25 257.5 129.17 33797 +1981 314 7.84 1.84 6.19 0.29 249.65 128.04 33641 +1981 315 6.64 0.64 4.99 0.01 231.65 126.88 33488 +1981 316 4.58 -1.42 2.93 0 203.33 168.49 33337 +1981 317 4 -2 2.35 0 195.92 166.66 33188 +1981 318 0.92 -5.08 -0.73 0 160.33 166.11 33042 +1981 319 2.96 -3.04 1.31 0.24 183.21 122.42 32899 +1981 320 8.49 2.49 6.84 0.09 259.9 118.03 32758 +1981 321 8.34 2.34 6.69 0 257.5 155.4 32620 +1981 322 12.48 6.48 10.83 0 331.05 149.67 32486 +1981 323 14.31 8.31 12.66 0 368.89 146.04 32354 +1981 324 10.57 4.57 8.92 0 295.15 147.99 32225 +1981 325 11.53 5.53 9.88 0.05 312.76 109.03 32100 +1981 326 11.62 5.62 9.97 0 314.45 143.86 31977 +1981 327 8.06 2.06 6.41 0 253.08 145.17 31858 +1981 328 11.42 5.42 9.77 0.19 310.69 105.23 31743 +1981 329 9.9 3.9 8.25 0.6 283.37 105.16 31631 +1981 330 8.93 2.93 7.28 0.29 267.04 104.7 31522 +1981 331 10.21 4.21 8.56 0 288.77 137.23 31417 +1981 332 8.08 2.08 6.43 0.2 253.4 103.01 31316 +1981 333 3.76 -2.24 2.11 1.23 192.92 104.33 31218 +1981 334 4.88 -1.12 3.23 0.9 207.26 103.01 31125 +1981 335 -2.95 -8.95 -4.6 0.2 123.63 148.06 31035 +1981 336 1.25 -4.75 -0.4 0 163.85 180.16 30949 +1981 337 3.91 -2.09 2.26 0 194.79 134 30867 +1981 338 6.49 0.49 4.84 0.3 229.48 98.61 30790 +1981 339 7.52 1.52 5.87 0.01 244.74 97.5 30716 +1981 340 10.4 4.4 8.75 0 292.12 127.05 30647 +1981 341 10.16 4.16 8.51 1.03 287.9 94.76 30582 +1981 342 11.87 5.87 10.22 0.42 319.2 93.09 30521 +1981 343 7.64 1.64 5.99 0.16 246.57 95.03 30465 +1981 344 5.13 -0.87 3.48 0.01 210.58 95.4 30413 +1981 345 3.89 -2.11 2.24 0 194.54 127.47 30366 +1981 346 3.46 -2.54 1.81 0 189.23 127.15 30323 +1981 347 -0.89 -6.89 -2.54 0 142.14 128.54 30284 +1981 348 0.79 -5.21 -0.86 0.08 158.96 95.62 30251 +1981 349 0.64 -5.36 -1.01 0.87 157.39 95.38 30221 +1981 350 3.9 -2.1 2.25 0.4 194.66 93.94 30197 +1981 351 4.79 -1.21 3.14 0.48 206.07 93.41 30177 +1981 352 4.6 -1.4 2.95 0.63 203.59 93.42 30162 +1981 353 4.39 -1.61 2.74 0.6 200.88 93.46 30151 +1981 354 0.47 -5.53 -1.18 0 155.63 126.49 30145 +1981 355 3.14 -2.86 1.49 0.17 185.35 93.93 30144 +1981 356 1.9 -4.1 0.25 0.07 170.99 94.41 30147 +1981 357 -0.37 -6.37 -2.02 0.01 147.17 139 30156 +1981 358 4.79 -1.21 3.14 0.8 206.07 93.39 30169 +1981 359 3.21 -2.79 1.56 1.94 186.2 94.12 30186 +1981 360 0.41 -5.59 -1.24 0.36 155.01 95.38 30208 +1981 361 -3.22 -9.22 -4.87 0.07 121.37 140.55 30235 +1981 362 -3.66 -9.66 -5.31 0.08 117.76 141.2 30267 +1981 363 -4.07 -10.07 -5.72 0 114.47 174.24 30303 +1981 364 -1.37 -7.37 -3.02 0 137.62 173.65 30343 +1981 365 2.55 -3.45 0.9 0 178.39 172.1 30388 +1982 1 -3.35 -9.35 -5 0 120.29 175.36 30438 +1982 2 -1.3 -7.3 -2.95 0 138.27 175.28 30492 +1982 3 -2.16 -8.16 -3.81 0 130.46 176.48 30551 +1982 4 2.03 -3.97 0.38 0 172.45 132.27 30614 +1982 5 -0.11 -6.11 -1.76 0 149.74 133.9 30681 +1982 6 2.01 -3.99 0.36 0 172.22 133.83 30752 +1982 7 2.69 -3.31 1.04 0 180.03 134.28 30828 +1982 8 5.03 -0.97 3.38 0.01 209.25 100.84 30907 +1982 9 3.67 -2.33 2.02 0 191.8 136.5 30991 +1982 10 1.69 -4.31 0.04 0 168.65 138.84 31079 +1982 11 -2.19 -8.19 -3.84 0 130.2 141.53 31171 +1982 12 -1.2 -7.2 -2.85 0.59 139.21 150.65 31266 +1982 13 -1.36 -7.36 -3.01 0 137.72 187.76 31366 +1982 14 -4.1 -10.1 -5.75 0 114.24 190.14 31469 +1982 15 0.95 -5.05 -0.7 0.54 160.64 152.82 31575 +1982 16 -1.14 -7.14 -2.79 0.01 139.77 154.38 31686 +1982 17 4.14 -1.86 2.49 0 197.68 189.7 31800 +1982 18 7.12 1.12 5.47 0 238.71 188.53 31917 +1982 19 8.97 2.97 7.32 0 267.7 147.35 32038 +1982 20 4.15 -1.85 2.5 0 197.81 152.43 32161 +1982 21 4.53 -1.47 2.88 0.03 202.68 115.65 32289 +1982 22 1.32 -4.68 -0.33 0.15 164.61 118.36 32419 +1982 23 4.94 -1.06 3.29 0.09 208.05 118.08 32552 +1982 24 1.75 -4.25 0.1 0.09 169.32 121.09 32688 +1982 25 -3.61 -9.61 -5.26 0 118.16 165.83 32827 +1982 26 -3.44 -9.44 -5.09 0.08 119.55 166.06 32969 +1982 27 -2.52 -8.52 -4.17 0.05 127.31 167.29 33114 +1982 28 -8.6 -14.6 -10.25 0.81 83.17 172.7 33261 +1982 29 -10.49 -16.49 -12.14 0 72.5 218.86 33411 +1982 30 -9.06 -15.06 -10.71 0 80.45 220.6 33564 +1982 31 -6.7 -12.7 -8.35 0 95.25 222.13 33718 +1982 32 -2.11 -8.11 -3.76 0 130.91 222.33 33875 +1982 33 -0.8 -6.8 -2.45 0 143 224.17 34035 +1982 34 -4.55 -10.55 -6.2 0 110.73 227.87 34196 +1982 35 -2.09 -8.09 -3.74 0 131.09 228.81 34360 +1982 36 -1.56 -7.56 -3.21 0 135.87 230.91 34526 +1982 37 -1.89 -7.89 -3.54 0 132.87 233.33 34694 +1982 38 1.45 -4.55 -0.2 0 166.02 233.92 34863 +1982 39 -0.15 -6.15 -1.8 0 149.35 237.28 35035 +1982 40 -1.68 -7.68 -3.33 0 134.77 240.54 35208 +1982 41 -0.52 -6.52 -2.17 0 145.7 242.39 35383 +1982 42 2.78 -3.22 1.13 0 181.08 242.42 35560 +1982 43 2.88 -3.12 1.23 0 182.26 244.54 35738 +1982 44 1.16 -4.84 -0.49 0 162.88 247.95 35918 +1982 45 5.69 -0.31 4.04 0 218.19 246.4 36099 +1982 46 2.36 -3.64 0.71 0 176.2 251.23 36282 +1982 47 6.38 0.38 4.73 0 227.89 213.78 36466 +1982 48 7.96 1.96 6.31 0 251.52 215.04 36652 +1982 49 10.35 4.35 8.7 0 291.24 215.14 36838 +1982 50 3.98 -2.02 2.33 0 195.67 224.09 37026 +1982 51 -1.06 -7.06 -2.71 0 140.52 230.54 37215 +1982 52 1.01 -4.99 -0.64 0 161.28 232.11 37405 +1982 53 1.85 -4.15 0.2 0 170.43 234.52 37596 +1982 54 2.19 -3.81 0.54 0 174.26 237.05 37788 +1982 55 3.8 -2.2 2.15 0 193.42 238.8 37981 +1982 56 3.5 -2.5 1.85 0 189.71 241.76 38175 +1982 57 5.08 -0.92 3.43 0 209.91 243.28 38370 +1982 58 5.71 -0.29 4.06 0 218.47 245.62 38565 +1982 59 6.4 0.4 4.75 0 228.18 247.65 38761 +1982 60 9.34 3.34 7.69 0 273.84 247.21 38958 +1982 61 7.69 1.69 6.04 0 247.34 252.07 39156 +1982 62 9.89 3.89 8.24 0 283.2 252.18 39355 +1982 63 12.61 6.61 10.96 0.03 333.63 188.45 39553 +1982 64 5.75 -0.25 4.1 0.14 219.02 197.14 39753 +1982 65 10.34 4.34 8.69 0 291.06 260.28 39953 +1982 66 7.66 1.66 6.01 0 246.88 266.39 40154 +1982 67 10.46 4.46 8.81 0 293.19 265.68 40355 +1982 68 10.38 4.38 8.73 0 291.77 268.64 40556 +1982 69 13.83 7.83 12.18 0 358.63 265.78 40758 +1982 70 10.29 4.29 8.64 0.24 290.18 205.63 40960 +1982 71 10.52 4.52 8.87 0 294.26 276.73 41163 +1982 72 13.84 7.84 12.19 0 358.84 274.13 41366 +1982 73 10.14 4.14 8.49 0 287.55 282.72 41569 +1982 74 14.21 8.21 12.56 0 366.73 278.73 41772 +1982 75 15.6 9.6 13.95 0 397.74 278.68 41976 +1982 76 10.67 4.67 9.02 0.12 296.95 217.48 42179 +1982 77 9.13 3.13 7.48 0.54 270.34 221.1 42383 +1982 78 7.73 1.73 6.08 1.72 247.95 224.5 42587 +1982 79 6.79 0.79 5.14 0 233.83 303.24 42791 +1982 80 7.96 1.96 6.31 0.39 251.52 228.23 42996 +1982 81 7.43 1.43 5.78 0.04 243.37 230.68 43200 +1982 82 8.06 2.06 6.41 0 253.08 309.41 43404 +1982 83 6.3 0.3 4.65 0 226.75 314.16 43608 +1982 84 7.2 1.2 5.55 0 239.91 315.59 43812 +1982 85 5.77 -0.23 4.12 0.37 219.3 239.91 44016 +1982 86 2.59 -3.41 0.94 0 178.86 325.73 44220 +1982 87 4.11 -1.89 2.46 0 197.3 326.75 44424 +1982 88 8.11 2.11 6.46 0 253.87 324.21 44627 +1982 89 10.56 4.56 8.91 0.01 294.97 242.09 44831 +1982 90 5.68 -0.32 4.03 0.01 218.05 249.05 45034 +1982 91 5.11 -0.89 3.46 0 210.31 335.03 45237 +1982 92 10.88 4.88 9.23 0 300.74 329.1 45439 +1982 93 10.36 4.36 8.71 0.01 291.42 249.13 45642 +1982 94 11.77 5.77 10.12 0.65 317.3 248.92 45843 +1982 95 11.45 5.45 9.8 0 311.26 334.6 46045 +1982 96 13.13 7.13 11.48 0 344.1 333.54 46246 +1982 97 9.08 3.08 7.43 0 269.51 342.72 46446 +1982 98 8.18 2.18 6.53 0.1 254.97 259.55 46647 +1982 99 6.19 0.19 4.54 0.17 225.19 263.15 46846 +1982 100 8.64 2.64 6.99 0.02 262.32 262.03 47045 +1982 101 11.09 5.09 9.44 0 304.58 347.26 47243 +1982 102 13.25 7.25 11.6 0 346.55 345.01 47441 +1982 103 13.63 7.63 11.98 0 354.42 346.05 47638 +1982 104 13.76 7.76 12.11 0 357.15 347.58 47834 +1982 105 12.93 6.93 11.28 0 340.04 351.09 48030 +1982 106 13.93 7.93 12.28 0.42 360.75 262.97 48225 +1982 107 11.91 5.91 10.26 0.64 319.97 267.32 48419 +1982 108 10.09 4.09 8.44 0 286.67 361.51 48612 +1982 109 7.07 1.07 5.42 0 237.97 367.91 48804 +1982 110 12.02 6.02 10.37 0 322.08 360.99 48995 +1982 111 12.62 6.62 10.97 0 333.83 361.35 49185 +1982 112 12.09 6.09 10.44 0 323.43 363.94 49374 +1982 113 8.48 2.48 6.83 0 259.74 371.72 49561 +1982 114 10.04 4.04 8.39 0.03 285.8 277.97 49748 +1982 115 11.57 5.57 9.92 0 313.51 369.24 49933 +1982 116 10.93 4.93 9.28 0.44 301.65 278.77 50117 +1982 117 14.07 8.07 12.42 0 363.73 366.53 50300 +1982 118 12.84 6.84 11.19 0.03 338.22 277.91 50481 +1982 119 13.44 7.44 11.79 0.09 350.47 277.84 50661 +1982 120 10.79 4.79 9.14 0 299.11 377.01 50840 +1982 121 19.85 13.85 18.2 0.01 506.77 266.68 51016 +1982 122 21.71 15.71 20.06 0.07 561.93 262.81 51191 +1982 123 18.31 12.31 16.66 0 464.64 362.48 51365 +1982 124 20.99 14.99 19.34 0.01 540 266.23 51536 +1982 125 16.3 10.3 14.65 0.02 414.18 277.6 51706 +1982 126 18.22 12.22 16.57 0.46 462.28 274.31 51874 +1982 127 18.34 12.34 16.69 1.4 465.43 274.7 52039 +1982 128 21.79 15.79 20.14 0 564.42 355.86 52203 +1982 129 21.25 15.25 19.6 0.14 547.84 268.96 52365 +1982 130 20.57 14.57 18.92 0 527.55 361.74 52524 +1982 131 20.41 14.41 18.76 0.23 522.87 272.29 52681 +1982 132 21.25 15.25 19.6 0.1 547.84 270.71 52836 +1982 133 17.1 11.1 15.45 0.02 433.67 281.07 52989 +1982 134 17.16 11.16 15.51 0.28 435.17 281.47 53138 +1982 135 13.11 7.11 11.46 0.11 343.69 289.61 53286 +1982 136 14.13 8.13 12.48 0 365.02 384.46 53430 +1982 137 16.47 10.47 14.82 0 418.26 379.24 53572 +1982 138 14.24 8.24 12.59 0.33 367.38 289.14 53711 +1982 139 15.34 9.34 13.69 0 391.77 383.51 53848 +1982 140 14.73 8.73 13.08 0.46 378.08 289.14 53981 +1982 141 15.67 9.67 14.02 0 399.35 383.58 54111 +1982 142 15.77 9.77 14.12 0.86 401.68 287.87 54238 +1982 143 17.79 11.79 16.14 0.21 451.11 284.06 54362 +1982 144 20.29 14.29 18.64 0.14 519.38 278.46 54483 +1982 145 22.36 16.36 20.71 0 582.38 364.24 54600 +1982 146 20.13 14.13 18.48 0 514.76 372.65 54714 +1982 147 23.51 17.51 21.86 0 620.09 360.51 54824 +1982 148 20.89 14.89 19.24 0 537.02 370.86 54931 +1982 149 21.38 15.38 19.73 0 551.79 369.41 55034 +1982 150 19.27 13.27 17.62 0 490.54 376.98 55134 +1982 151 19.17 13.17 17.52 0 487.78 377.69 55229 +1982 152 21.37 15.37 19.72 0 551.49 370.26 55321 +1982 153 18.89 12.89 17.24 0 480.14 378.94 55409 +1982 154 17.84 11.84 16.19 0 452.4 382.48 55492 +1982 155 19.85 13.85 18.2 0.04 506.77 282.24 55572 +1982 156 20.21 14.21 18.56 0.69 517.07 281.56 55648 +1982 157 19.32 13.32 17.67 0.04 491.92 283.91 55719 +1982 158 18.84 12.84 17.19 0.52 478.79 285.2 55786 +1982 159 20.43 14.43 18.78 0.09 523.45 281.43 55849 +1982 160 21.5 15.5 19.85 0.06 555.46 278.7 55908 +1982 161 23.61 17.61 21.96 0.19 623.47 272.56 55962 +1982 162 25.37 19.37 23.72 0.17 685.47 266.85 56011 +1982 163 26.12 20.12 24.47 0.17 713.44 264.39 56056 +1982 164 26.54 20.54 24.89 0.11 729.52 262.9 56097 +1982 165 25.61 19.61 23.96 0.08 694.32 266.28 56133 +1982 166 27.28 21.28 25.63 0.53 758.59 260.27 56165 +1982 167 24.75 18.75 23.1 0 663.06 358.95 56192 +1982 168 25.47 19.47 23.82 0.17 689.15 266.84 56214 +1982 169 26.72 20.72 25.07 0 736.5 349.85 56231 +1982 170 26.36 20.36 24.71 0 722.59 351.61 56244 +1982 171 25.89 19.89 24.24 0.1 704.76 265.43 56252 +1982 172 24.28 18.28 22.63 0 646.49 361.14 56256 +1982 173 29.15 23.15 27.5 0.89 836.46 252.85 56255 +1982 174 26.23 20.23 24.58 0.83 717.62 264.14 56249 +1982 175 19.78 13.78 18.13 0 504.78 378.15 56238 +1982 176 17.84 11.84 16.19 0.36 452.4 288.19 56223 +1982 177 15.51 9.51 13.86 0.39 395.66 293 56203 +1982 178 16.48 10.48 14.83 1.45 418.5 291.06 56179 +1982 179 19.23 13.23 17.58 1.58 489.43 284.81 56150 +1982 180 21.32 15.32 19.67 0.36 549.96 279.32 56116 +1982 181 20.2 14.2 18.55 0.06 516.78 282.24 56078 +1982 182 21.47 15.47 19.82 0 554.54 371.67 56035 +1982 183 23.81 17.81 22.16 0.01 630.27 271.73 55987 +1982 184 22.28 16.28 20.63 0.04 579.83 276.22 55935 +1982 185 25.05 19.05 23.4 0.17 673.83 267.53 55879 +1982 186 24.2 18.2 22.55 0 643.7 360.17 55818 +1982 187 24.8 18.8 23.15 0.25 664.85 268.04 55753 +1982 188 22.45 16.45 20.8 0 585.26 366.86 55684 +1982 189 26.74 20.74 25.09 0.12 737.28 260.95 55611 +1982 190 25.06 19.06 23.41 0.22 674.19 266.58 55533 +1982 191 23.1 17.1 21.45 0 606.42 363.49 55451 +1982 192 21.39 15.39 19.74 0.42 552.1 277.3 55366 +1982 193 19.94 13.94 18.29 0.24 509.33 280.9 55276 +1982 194 22.22 16.22 20.57 0 577.92 366.15 55182 +1982 195 23.52 17.52 21.87 0.01 620.43 270.55 55085 +1982 196 23.84 17.84 22.19 0 631.29 359.02 54984 +1982 197 26.05 20.05 24.4 0.81 710.79 261.59 54879 +1982 198 22.45 16.45 20.8 2.14 585.26 272.79 54770 +1982 199 23.92 17.92 22.27 0.34 634.03 268.11 54658 +1982 200 23.95 17.95 22.3 0.19 635.06 267.73 54542 +1982 201 24.23 18.23 22.58 0 644.75 355.33 54423 +1982 202 22.58 16.58 20.93 0.25 589.44 271.1 54301 +1982 203 24.54 18.54 22.89 0.27 655.61 264.73 54176 +1982 204 24.09 18.09 22.44 0 639.89 354.39 54047 +1982 205 22.76 16.76 21.11 0 595.27 359.26 53915 +1982 206 29.37 23.37 27.72 0 846.05 327.76 53780 +1982 207 29.88 23.88 28.23 1.08 868.63 243.21 53643 +1982 208 26.94 20.94 25.29 0.95 745.11 254.4 53502 +1982 209 22.1 16.1 20.45 1.42 574.13 269.47 53359 +1982 210 17.36 11.36 15.71 0.19 440.17 280.62 53213 +1982 211 21.94 15.94 20.29 0.57 569.1 268.88 53064 +1982 212 22.85 16.85 21.2 0.01 598.2 265.71 52913 +1982 213 22.95 16.95 21.3 1.13 601.48 264.86 52760 +1982 214 22.12 16.12 20.47 0.08 574.76 266.67 52604 +1982 215 25.52 19.52 23.87 0.31 690.99 255.79 52445 +1982 216 23.51 17.51 21.86 0.23 620.09 261.42 52285 +1982 217 25.16 19.16 23.51 0.91 677.81 255.6 52122 +1982 218 23.93 17.93 22.28 0.46 634.38 258.9 51958 +1982 219 22.54 16.54 20.89 0.08 588.15 262.22 51791 +1982 220 22.85 16.85 21.2 0.4 598.2 260.65 51622 +1982 221 21.45 15.45 19.8 0 553.93 351.68 51451 +1982 222 19.13 13.13 17.48 0.41 486.69 268.71 51279 +1982 223 20.12 14.12 18.47 0 514.48 354.01 51105 +1982 224 20.52 14.52 18.87 0 526.08 351.64 50929 +1982 225 21.99 15.99 20.34 0 570.66 345.42 50751 +1982 226 18.56 12.56 16.91 0.05 471.27 266.61 50572 +1982 227 16.87 10.87 15.22 0 427.99 358.94 50392 +1982 228 22.71 16.71 21.06 0 593.64 339.22 50210 +1982 229 23.94 17.94 22.29 0 634.72 333.29 50026 +1982 230 21.22 15.22 19.57 0.37 546.93 256.54 49842 +1982 231 20.89 14.89 19.24 0.41 537.02 256.28 49656 +1982 232 19.06 13.06 17.41 0.24 484.77 259.6 49469 +1982 233 20.49 14.49 18.84 0 525.2 340.27 49280 +1982 234 22.51 16.51 20.86 0.07 587.18 248.97 49091 +1982 235 25.41 19.41 23.76 0.54 686.94 239.4 48900 +1982 236 25.33 19.33 23.68 0.01 684.01 238.63 48709 +1982 237 21.16 15.16 19.51 0.12 545.11 249.12 48516 +1982 238 23.37 17.37 21.72 0.06 615.39 242.06 48323 +1982 239 24.39 18.39 22.74 0.16 650.34 238.04 48128 +1982 240 27.64 21.64 25.99 0.49 773.09 226.32 47933 +1982 241 25.04 19.04 23.39 0.13 673.47 233.6 47737 +1982 242 26.89 20.89 25.24 0 743.15 301.97 47541 +1982 243 25.62 19.62 23.97 0.13 694.69 229.26 47343 +1982 244 22.66 16.66 21.01 0.52 592.02 236.42 47145 +1982 245 22.8 16.8 21.15 0.2 596.57 234.71 46947 +1982 246 20.1 14.1 18.45 0 513.9 319.82 46747 +1982 247 20.16 14.16 18.51 0 515.63 317.81 46547 +1982 248 21.56 15.56 19.91 0 557.3 311.54 46347 +1982 249 24.67 18.67 23.02 0 660.22 298.58 46146 +1982 250 24.79 18.79 23.14 0.29 664.49 222.21 45945 +1982 251 23.23 17.23 21.58 0.12 610.73 224.99 45743 +1982 252 25.7 19.7 24.05 0.07 697.66 216.52 45541 +1982 253 23.91 17.91 22.26 0 633.69 293.47 45339 +1982 254 24.15 18.15 22.5 0.07 641.97 217.93 45136 +1982 255 23.01 17.01 21.36 0.05 603.45 219.32 44933 +1982 256 22.31 16.31 20.66 0 580.78 292.56 44730 +1982 257 21.82 15.82 20.17 0 565.35 292.04 44527 +1982 258 19.18 13.18 17.53 0 488.06 297.42 44323 +1982 259 19.68 13.68 18.03 0.19 501.96 220.25 44119 +1982 260 22.58 16.58 20.93 0 589.44 282.73 43915 +1982 261 21.46 15.46 19.81 0.03 554.23 212.89 43711 +1982 262 18.95 12.95 17.3 0 481.77 288.54 43507 +1982 263 19.47 13.47 17.82 0 496.08 284.76 43303 +1982 264 20.3 14.3 18.65 0 519.67 280 43099 +1982 265 20.55 14.55 18.9 0 526.96 277.01 42894 +1982 266 21.36 15.36 19.71 0 551.18 272.32 42690 +1982 267 18.94 12.94 17.29 0.75 481.5 207.17 42486 +1982 268 21.17 15.17 19.52 0.31 545.42 200.85 42282 +1982 269 20.49 14.49 18.84 1.28 525.2 200.44 42078 +1982 270 20.2 14.2 18.55 0 516.78 265.47 41875 +1982 271 21.42 15.42 19.77 0 553.01 259.63 41671 +1982 272 20.19 14.19 18.54 0 516.49 260.32 41468 +1982 273 22.78 16.78 21.13 0 595.92 250.69 41265 +1982 274 13.81 7.81 12.16 0 358.21 268.93 41062 +1982 275 10.64 4.64 8.99 0 296.41 271.2 40860 +1982 276 13.78 7.78 12.13 0.01 357.57 197.63 40658 +1982 277 15.27 9.27 13.62 0 390.18 258.17 40456 +1982 278 19.6 13.6 17.95 0 499.72 246.13 40255 +1982 279 15.8 9.8 14.15 0.12 402.38 188.65 40054 +1982 280 19.41 13.41 17.76 0.08 494.41 180.98 39854 +1982 281 18.4 12.4 16.75 0.6 467.02 180.71 39654 +1982 282 18.06 12.06 16.41 0.02 458.09 179.26 39455 +1982 283 16.24 10.24 14.59 0.22 412.74 179.93 39256 +1982 284 18.18 12.18 16.53 0 461.23 233.08 39058 +1982 285 17.17 11.17 15.52 0 435.41 232.56 38861 +1982 286 11.96 5.96 10.31 0 320.93 238.62 38664 +1982 287 8.72 2.72 7.07 0 263.61 239.84 38468 +1982 288 13.15 7.15 11.5 0 344.5 231.15 38273 +1982 289 16.55 10.55 14.9 0.02 420.19 167.16 38079 +1982 290 13.77 7.77 12.12 0 357.36 224.74 37885 +1982 291 12.87 6.87 11.22 0.24 338.83 167.55 37693 +1982 292 13.41 7.41 11.76 0.14 349.85 164.95 37501 +1982 293 12.28 6.28 10.63 1.46 327.13 164.12 37311 +1982 294 10.75 4.75 9.1 0.52 298.39 163.45 37121 +1982 295 11.57 5.57 9.92 2.8 313.51 160.54 36933 +1982 296 13.25 7.25 11.6 0 346.55 209.21 36745 +1982 297 13.4 7.4 11.75 0 349.64 206.3 36560 +1982 298 13.66 7.66 12.01 0.14 355.05 152.52 36375 +1982 299 13.21 7.21 11.56 0 345.73 201.23 36191 +1982 300 13.5 7.5 11.85 0 351.71 198.2 36009 +1982 301 12.81 6.81 11.16 0.11 337.62 147.48 35829 +1982 302 13.74 7.74 12.09 0.94 356.73 144.61 35650 +1982 303 15.24 9.24 13.59 0 389.5 188.12 35472 +1982 304 14.99 8.99 13.34 0.26 383.87 139.57 35296 +1982 305 11.5 5.5 9.85 0 312.19 187.97 35122 +1982 306 4.93 -1.07 3.28 0.76 207.92 144 34950 +1982 307 2.33 -3.67 0.68 0 175.86 191.27 34779 +1982 308 3.86 -2.14 2.21 0.67 194.16 140.69 34610 +1982 309 3.29 -2.71 1.64 0 187.16 185.63 34444 +1982 310 1.92 -4.08 0.27 0 171.21 184.01 34279 +1982 311 1.93 -4.07 0.28 0 171.33 181.78 34116 +1982 312 1.24 -4.76 -0.41 0 163.74 179.5 33956 +1982 313 1.65 -4.35 0 0 168.21 177.1 33797 +1982 314 8.45 2.45 6.8 0.2 259.26 127.64 33641 +1982 315 9.81 3.81 8.16 0.07 281.82 124.8 33488 +1982 316 14.99 8.99 13.34 0 383.87 158.4 33337 +1982 317 11.14 5.14 9.49 0 305.5 160.74 33188 +1982 318 12.49 6.49 10.84 0 331.25 156.99 33042 +1982 319 14.2 8.2 12.55 0.05 366.52 115.01 32899 +1982 320 10.91 4.91 9.26 0 301.29 155.15 32758 +1982 321 11.65 5.65 10 0 315.02 152.33 32620 +1982 322 11.9 5.9 10.25 0 319.78 150.28 32486 +1982 323 10.9 4.9 9.25 0.01 301.11 112.27 32354 +1982 324 8.32 2.32 6.67 0.18 257.19 112.47 32225 +1982 325 10.52 4.52 8.87 0.26 294.26 109.75 32100 +1982 326 8.82 2.82 7.17 0.01 265.24 109.8 31977 +1982 327 4.84 -1.16 3.19 0 206.73 147.46 31858 +1982 328 8.21 2.21 6.56 0 255.44 143.09 31743 +1982 329 9.27 3.27 7.62 0 272.67 140.76 31631 +1982 330 8.66 2.66 7.01 0 262.64 139.82 31522 +1982 331 12.07 6.07 10.42 0 323.05 135.51 31417 +1982 332 14.31 8.31 12.66 0 368.89 131.57 31316 +1982 333 13.61 7.61 11.96 0.26 354.01 98.47 31218 +1982 334 14.23 8.23 12.58 0 367.17 129.56 31125 +1982 335 11.71 5.71 10.06 0 316.16 130.98 31035 +1982 336 13.95 7.95 12.3 0 361.17 127.7 30949 +1982 337 14.39 8.39 12.74 0 370.63 125.61 30867 +1982 338 11.95 5.95 10.3 1.29 320.74 95.37 30790 +1982 339 8.66 2.66 7.01 0.14 262.64 96.87 30716 +1982 340 10.31 4.31 8.66 0.49 290.53 95.35 30647 +1982 341 10.27 4.27 8.62 0.47 289.83 94.7 30582 +1982 342 7.33 1.33 5.68 0.2 241.86 95.8 30521 +1982 343 7.44 1.44 5.79 0.06 243.52 95.13 30465 +1982 344 7.42 1.42 5.77 0 243.22 125.73 30413 +1982 345 5.28 -0.72 3.63 0.31 212.6 95.01 30366 +1982 346 4.43 -1.57 2.78 0 201.39 126.62 30323 +1982 347 6.46 0.46 4.81 0.25 229.04 93.61 30284 +1982 348 8.9 2.9 7.25 0 266.55 122.77 30251 +1982 349 4.49 -1.51 2.84 0 202.16 125.26 30221 +1982 350 0.63 -5.37 -1.02 0.1 157.28 95.13 30197 +1982 351 -2.36 -8.36 -4.01 0.35 128.7 140.7 30177 +1982 352 1.7 -4.3 0.05 0.02 168.77 139.18 30162 +1982 353 0.06 -5.94 -1.59 0.86 151.45 139.68 30151 +1982 354 2.61 -3.39 0.96 0 179.09 169.83 30145 +1982 355 -0.08 -6.08 -1.73 0.2 150.04 140 30144 +1982 356 2.35 -3.65 0.7 0.27 176.09 138.88 30147 +1982 357 2.51 -3.49 0.86 0.31 177.93 138.52 30156 +1982 358 6.82 0.82 5.17 0 234.27 123.28 30169 +1982 359 2.17 -3.83 0.52 0.23 174.03 94.51 30186 +1982 360 7.11 1.11 5.46 0 238.56 123.57 30208 +1982 361 5.45 -0.55 3.8 0 214.9 124.95 30235 +1982 362 6.41 0.41 4.76 0 228.32 124.79 30267 +1982 363 5.11 -0.89 3.46 0.27 210.31 94.63 30303 +1982 364 6.81 0.81 5.16 0.21 234.13 94.13 30343 +1982 365 6.16 0.16 4.51 0.25 224.76 94.87 30388 +1983 1 6.82 0.82 5.17 0.38 234.27 95.21 30438 +1983 2 8.78 2.78 7.13 0.02 264.59 94.71 30492 +1983 3 13.08 7.08 11.43 0.04 343.08 92.62 30551 +1983 4 11.6 5.6 9.95 0.21 314.07 94.33 30614 +1983 5 10.69 4.69 9.04 0 297.3 127.2 30681 +1983 6 10.1 4.1 8.45 0.08 286.85 96.42 30752 +1983 7 6.91 0.91 5.26 0 235.6 131.75 30828 +1983 8 8.85 2.85 7.2 0 265.73 131.81 30907 +1983 9 5.06 -0.94 3.41 0.42 209.65 101.76 30991 +1983 10 3.68 -2.32 2.03 0 191.93 137.79 31079 +1983 11 4.37 -1.63 2.72 0.12 200.62 103.78 31171 +1983 12 1.18 -4.82 -0.47 0 163.1 141.1 31266 +1983 13 3.91 -2.09 2.26 0 194.79 141.28 31366 +1983 14 1.48 -4.52 -0.17 0 166.35 144.07 31469 +1983 15 2.61 -3.39 0.96 0 179.09 144.93 31575 +1983 16 8.18 2.18 6.53 0 254.97 142.56 31686 +1983 17 3.53 -2.47 1.88 0.57 190.08 110.54 31800 +1983 18 1.95 -4.05 0.3 0.02 171.55 112.63 31917 +1983 19 2.2 -3.8 0.55 0 174.37 151.98 32038 +1983 20 1.44 -4.56 -0.21 0.02 165.91 115.48 32161 +1983 21 4.32 -1.68 2.67 0 199.98 154.33 32289 +1983 22 6.67 0.67 5.02 0 232.08 154.45 32419 +1983 23 9.47 3.47 7.82 0 276.03 153.91 32552 +1983 24 10.97 4.97 9.32 0 302.38 154.52 32688 +1983 25 9.81 3.81 8.16 0 281.82 157.48 32827 +1983 26 8.08 2.08 6.43 1.5 253.4 120.68 32969 +1983 27 6.74 0.74 5.09 0.16 233.1 122.99 33114 +1983 28 8.28 2.28 6.63 0.19 256.55 123.68 33261 +1983 29 6.7 0.7 5.05 0 232.52 168.58 33411 +1983 30 8.54 2.54 6.89 0 260.7 169.24 33564 +1983 31 7.11 1.11 5.46 0 238.56 172.82 33718 +1983 32 6.65 0.65 5 0 231.79 175.3 33875 +1983 33 2.88 -3.12 1.23 0.39 182.26 135.48 34035 +1983 34 -1.72 -7.72 -3.37 0.57 134.41 179.26 34196 +1983 35 -4.16 -10.16 -5.81 0.2 113.76 182.07 34360 +1983 36 -5.85 -11.85 -7.5 1.19 101.13 187.58 34526 +1983 37 -5.11 -11.11 -6.76 0.51 106.5 190.43 34694 +1983 38 -2.11 -8.11 -3.76 0.04 130.91 191.44 34863 +1983 39 -2.36 -8.36 -4.01 0 128.7 242.88 35035 +1983 40 -2.29 -8.29 -3.94 0.32 129.32 195.92 35208 +1983 41 2.86 -3.14 1.21 0 182.02 245.27 35383 +1983 42 1.83 -4.17 0.18 0.11 170.21 197.13 35560 +1983 43 2.33 -3.67 0.68 0 175.86 250.01 35738 +1983 44 2.56 -3.44 0.91 1.5 178.51 199.76 35918 +1983 45 6.87 0.87 5.22 0 235.01 250.1 36099 +1983 46 4.64 -1.36 2.99 0 204.11 253.98 36282 +1983 47 5.41 -0.59 3.76 0 214.36 255.36 36466 +1983 48 2.7 -3.3 1.05 0 180.14 259.81 36652 +1983 49 5.42 -0.58 3.77 0 214.49 259.63 36838 +1983 50 3.31 -2.69 1.66 0 187.4 263.47 37026 +1983 51 2.41 -3.59 0.76 0 176.78 266.67 37215 +1983 52 2.57 -3.43 0.92 0 178.63 268.94 37405 +1983 53 3.99 -2.01 2.34 0.29 195.79 211.96 37596 +1983 54 4.65 -1.35 3 0.03 204.24 212.93 37788 +1983 55 2.26 -3.74 0.61 0.17 175.06 216.21 37981 +1983 56 5 -1 3.35 0 208.85 275.95 38175 +1983 57 7.91 1.91 6.26 0 250.74 274.9 38370 +1983 58 2.83 -3.17 1.18 0.09 181.67 186.12 38565 +1983 59 2.61 -3.39 0.96 0.01 179.09 188.3 38761 +1983 60 8.66 2.66 7.01 0.03 262.64 186.03 38958 +1983 61 9.61 3.61 7.96 0.41 278.4 187.33 39156 +1983 62 7.1 1.1 5.45 0.02 238.41 191.63 39355 +1983 63 5.4 -0.6 3.75 0.03 214.22 195.21 39553 +1983 64 7.24 1.24 5.59 0 240.5 261.26 39753 +1983 65 7.62 1.62 5.97 0 246.26 263.71 39953 +1983 66 6.47 0.47 4.82 0 229.19 267.73 40154 +1983 67 4.59 -1.41 2.94 0.03 203.46 204.43 40355 +1983 68 3.72 -2.28 2.07 0 192.42 276.29 40556 +1983 69 5.47 -0.53 3.82 0 215.17 277.22 40758 +1983 70 9.89 3.89 8.24 0 283.2 274.73 40960 +1983 71 15.43 9.43 13.78 0 393.83 268.41 41163 +1983 72 14.12 8.12 12.47 0 364.8 273.63 41366 +1983 73 15.56 9.56 13.91 0.01 396.81 205.1 41569 +1983 74 13.36 7.36 11.71 0 348.81 280.27 41772 +1983 75 12.91 6.91 11.26 0 339.63 283.73 41976 +1983 76 14.04 8.04 12.39 0 363.09 284.28 42179 +1983 77 15.58 9.58 13.93 0 397.27 283.79 42383 +1983 78 15.39 9.39 13.74 0.29 392.91 215.07 42587 +1983 79 12.15 6.15 10.5 0.01 324.6 221.62 42791 +1983 80 9.23 3.23 7.58 0 272 302.56 42996 +1983 81 9.35 3.35 7.7 0 274.01 304.96 43200 +1983 82 9.89 3.89 8.24 0.15 283.2 230.11 43404 +1983 83 6.29 0.29 4.64 0.56 226.61 235.63 43608 +1983 84 8.77 2.77 7.12 0.16 264.42 235.1 43812 +1983 85 9.61 3.61 7.96 0.18 278.4 236.05 44016 +1983 86 8.05 2.05 6.4 0.25 252.93 239.54 44220 +1983 87 9.14 3.14 7.49 0.19 270.51 240.28 44424 +1983 88 9.11 3.11 7.46 0.48 270.01 242.08 44627 +1983 89 10 4 8.35 0.03 285.11 242.76 44831 +1983 90 13.84 7.84 12.19 0.08 358.84 239.38 45034 +1983 91 21.7 15.7 20.05 0.23 561.62 225.91 45237 +1983 92 21.1 15.1 19.45 0 543.31 305.21 45439 +1983 93 16.92 10.92 15.27 0 429.22 318.88 45642 +1983 94 17.05 11.05 15.4 0 432.43 320.65 45843 +1983 95 17.21 11.21 15.56 0.96 436.41 241.74 46045 +1983 96 16.74 10.74 15.09 0.97 424.8 244.16 46246 +1983 97 16.04 10.04 14.39 0.79 408 246.93 46446 +1983 98 14.24 8.24 12.59 0.58 367.38 251.41 46647 +1983 99 17.19 11.19 15.54 0 435.91 330.27 46846 +1983 100 14.26 8.26 12.61 0.07 367.81 254.31 47045 +1983 101 8.6 2.6 6.95 0 261.67 351.39 47243 +1983 102 8.75 2.75 7.1 0 264.1 353.08 47441 +1983 103 3.13 -2.87 1.48 0 185.23 362.32 47638 +1983 104 5.26 -0.74 3.61 0 212.33 361.7 47834 +1983 105 9.37 3.37 7.72 0.06 274.35 268.21 48030 +1983 106 13.8 7.8 12.15 0.01 357.99 263.18 48225 +1983 107 12.9 6.9 11.25 0 339.43 354.46 48419 +1983 108 11.67 5.67 10.02 0 315.4 358.64 48612 +1983 109 13.79 7.79 12.14 0 357.78 355.93 48804 +1983 110 14.26 8.26 12.61 0 367.81 356.29 48995 +1983 111 15.38 9.38 13.73 0.03 392.69 266.41 49185 +1983 112 15.29 9.29 13.64 0 390.64 356.94 49374 +1983 113 19.64 13.64 17.99 0 500.84 346.32 49561 +1983 114 22.02 16.02 20.37 0 571.61 339.83 49748 +1983 115 22.95 16.95 21.3 0.04 601.48 253.33 49933 +1983 116 22.64 16.64 20.99 0 591.38 340.08 50117 +1983 117 18.42 12.42 16.77 0.01 467.55 266.47 50300 +1983 118 16.03 10.03 14.38 0 407.77 363.12 50481 +1983 119 18.14 12.14 16.49 0 460.18 358.55 50661 +1983 120 17.2 11.2 15.55 0 436.16 362.35 50840 +1983 121 23.32 17.32 21.67 0 613.72 343.27 51016 +1983 122 23.3 17.3 21.65 0 613.06 344.47 51191 +1983 123 22.98 16.98 21.33 0 602.46 346.69 51365 +1983 124 26.19 20.19 24.54 0.18 716.1 250.63 51536 +1983 125 25.64 19.64 23.99 0.68 695.43 253.18 51706 +1983 126 23.51 17.51 21.86 0.49 620.09 260.63 51874 +1983 127 21.1 15.1 19.45 0.43 543.31 268.02 52039 +1983 128 18.93 12.93 17.28 0.94 481.23 274.09 52203 +1983 129 17.59 11.59 15.94 0.18 446 277.71 52365 +1983 130 19.64 13.64 17.99 0 500.84 364.82 52524 +1983 131 15.77 9.77 14.12 0 401.68 376.82 52681 +1983 132 16.29 10.29 14.64 0.01 413.94 282.2 52836 +1983 133 20.61 14.61 18.96 0.26 528.72 272.89 52989 +1983 134 21.25 15.25 19.6 0.04 547.84 271.73 53138 +1983 135 17.03 11.03 15.38 0.72 431.94 282.27 53286 +1983 136 18.14 12.14 16.49 1.77 460.18 280.33 53430 +1983 137 14.17 8.17 12.52 0 365.87 385.07 53572 +1983 138 12.36 6.36 10.71 0.22 328.69 292.32 53711 +1983 139 14.34 8.34 12.69 0.07 369.54 289.48 53848 +1983 140 15.02 9.02 13.37 0.01 384.54 288.6 53981 +1983 141 13.22 7.22 11.57 0.53 345.94 292.14 54111 +1983 142 14.74 8.74 13.09 0 378.3 386.44 54238 +1983 143 16.81 10.81 15.16 0 426.52 381.55 54362 +1983 144 14.8 8.8 13.15 0 379.63 387.32 54483 +1983 145 17.47 11.47 15.82 0.14 442.95 285.47 54600 +1983 146 18.87 12.87 17.22 0 479.6 376.76 54714 +1983 147 19.81 13.81 18.16 1.3 505.63 280.65 54824 +1983 148 20.29 14.29 18.64 0 519.38 372.95 54931 +1983 149 23.15 17.15 21.5 0.1 608.07 271.98 55034 +1983 150 25.31 19.31 23.66 0 683.28 353.73 55134 +1983 151 25.71 19.71 24.06 0 698.04 352.28 55229 +1983 152 26.18 20.18 24.53 0.19 715.72 262.62 55321 +1983 153 25.94 19.94 24.29 0.84 706.64 263.64 55409 +1983 154 19.82 13.82 18.17 0.15 505.92 282.17 55492 +1983 155 22.65 16.65 21 1.46 591.7 274.62 55572 +1983 156 18.15 12.15 16.5 0.38 460.44 286.55 55648 +1983 157 19.11 13.11 17.46 0.01 486.14 284.42 55719 +1983 158 17.63 11.63 15.98 0 447.01 383.97 55786 +1983 159 17.03 11.03 15.38 0 431.94 385.95 55849 +1983 160 22.41 16.41 20.76 0.11 583.98 276.12 55908 +1983 161 21.35 15.35 19.7 0.51 550.88 279.16 55962 +1983 162 14.84 8.84 13.19 0.35 380.52 294.09 56011 +1983 163 15.94 9.94 14.29 0 405.65 389.49 56056 +1983 164 19.2 13.2 17.55 0 488.61 379.93 56097 +1983 165 20.35 14.35 18.7 0 521.12 376.18 56133 +1983 166 21.66 15.66 20.01 0.54 560.39 278.67 56165 +1983 167 20.48 14.48 18.83 0.33 524.91 281.81 56192 +1983 168 22.47 16.47 20.82 0 585.9 368.5 56214 +1983 169 24.23 18.23 22.58 0.17 644.75 270.98 56231 +1983 170 20.12 14.12 18.47 1.02 514.48 282.81 56244 +1983 171 21.75 15.75 20.1 0.22 563.17 278.49 56252 +1983 172 22.47 16.47 20.82 0 585.9 368.56 56256 +1983 173 23.7 17.7 22.05 0 626.52 363.58 56255 +1983 174 23.38 17.38 21.73 0 615.73 364.82 56249 +1983 175 27.3 21.3 25.65 0.39 759.39 260.16 56238 +1983 176 23.62 17.62 21.97 0 623.81 363.77 56223 +1983 177 22.89 16.89 21.24 0 599.51 366.64 56203 +1983 178 22.07 16.07 20.42 0.14 573.18 277.39 56179 +1983 179 18.85 12.85 17.2 0.49 479.06 285.72 56150 +1983 180 19.23 13.23 17.58 0.94 489.43 284.71 56116 +1983 181 14.28 8.28 12.63 0.18 368.25 295.11 56078 +1983 182 18.55 12.55 16.9 0.33 471 286.17 56035 +1983 183 20.14 14.14 18.49 0 515.05 376.2 55987 +1983 184 20.02 14.02 18.37 0 511.61 376.45 55935 +1983 185 22.33 16.33 20.68 0.17 581.42 276.01 55879 +1983 186 26.22 20.22 24.57 0 717.24 351.04 55818 +1983 187 25.68 19.68 24.03 0 696.92 353.41 55753 +1983 188 23.96 17.96 22.31 0.01 635.41 270.56 55684 +1983 189 24.69 18.69 23.04 0.38 660.93 268.08 55611 +1983 190 27.04 21.04 25.39 0.34 749.06 259.57 55533 +1983 191 27.88 21.88 26.23 0 782.88 341.56 55451 +1983 192 26.74 20.74 25.09 0 737.28 347.03 55366 +1983 193 27.2 21.2 25.55 0 755.4 344.5 55276 +1983 194 26.71 20.71 25.06 0.8 736.11 260.04 55182 +1983 195 25.23 19.23 23.58 0.15 680.36 265.05 55085 +1983 196 23.51 17.51 21.86 0.02 620.09 270.29 54984 +1983 197 25.52 19.52 23.87 0 690.99 351.25 54879 +1983 198 28.14 22.14 26.49 0 793.6 338 54770 +1983 199 27.46 21.46 25.81 0.07 765.81 255.88 54658 +1983 200 27.81 21.81 26.16 0.14 780.01 254.26 54542 +1983 201 28.19 22.19 26.54 0.29 795.68 252.45 54423 +1983 202 24.13 18.13 22.48 0.02 641.27 266.41 54301 +1983 203 28.03 22.03 26.38 0 789.05 336.44 54176 +1983 204 26.41 20.41 24.76 0.04 724.51 258.01 54047 +1983 205 28.18 22.18 26.53 0 795.27 334.7 53915 +1983 206 27.18 21.18 25.53 0 754.61 339.26 53780 +1983 207 27.25 21.25 25.6 0 757.39 338.29 53643 +1983 208 24.5 18.5 22.85 0.53 654.2 262.75 53502 +1983 209 25.64 19.64 23.99 0.06 695.43 258.52 53359 +1983 210 24.18 18.18 22.53 0 643.01 350.46 53213 +1983 211 24.73 18.73 23.08 0 662.35 347.37 53064 +1983 212 23.21 17.21 21.56 0.2 610.06 264.65 52913 +1983 213 20.64 14.64 18.99 0 529.61 361.58 52760 +1983 214 23.72 17.72 22.07 0 627.2 349.36 52604 +1983 215 22.28 16.28 20.63 0 579.83 354.3 52445 +1983 216 20.94 14.94 19.29 0 538.51 358.11 52285 +1983 217 21.75 15.75 20.1 0 563.17 354.37 52122 +1983 218 21.98 15.98 20.33 0 570.35 352.73 51958 +1983 219 21.39 15.39 19.74 0.03 552.1 265.36 51791 +1983 220 20.84 14.84 19.19 0.11 535.53 266.09 51622 +1983 221 21.76 15.76 20.11 0.14 563.48 262.93 51451 +1983 222 20.47 14.47 18.82 0.39 524.62 265.5 51279 +1983 223 21.7 15.7 20.05 0 561.62 348.63 51105 +1983 224 25.3 19.3 23.65 0.5 682.91 250.08 50929 +1983 225 23.48 17.48 21.83 0 619.08 339.83 50751 +1983 226 23.01 17.01 21.36 0.27 603.45 255.4 50572 +1983 227 21.51 15.51 19.86 1.25 555.77 258.55 50392 +1983 228 22.97 16.97 21.32 2.04 602.13 253.68 50210 +1983 229 23.74 17.74 22.09 0.14 627.88 250.56 50026 +1983 230 27.3 21.3 25.65 0 759.39 317.47 49842 +1983 231 24.34 18.34 22.69 0 648.58 329.04 49656 +1983 232 25.99 19.99 24.34 0 708.52 320.8 49469 +1983 233 27.14 21.14 25.49 0 753.02 314.25 49280 +1983 234 26.37 20.37 24.72 0.03 722.97 237.33 49091 +1983 235 28.11 22.11 26.46 0 792.36 306.92 48900 +1983 236 29.06 23.06 27.41 0.07 832.56 225.66 48709 +1983 237 26.79 20.79 25.14 0 739.23 310.27 48516 +1983 238 26.11 20.11 24.46 0 713.06 311.71 48323 +1983 239 19.19 13.19 17.54 0 488.33 335.15 48128 +1983 240 20.35 14.35 18.7 0 521.12 329.88 47933 +1983 241 21.78 15.78 20.13 0.27 564.11 242.65 47737 +1983 242 20.22 14.22 18.57 0.32 517.36 245.15 47541 +1983 243 21.17 15.17 19.52 0.32 545.42 241.52 47343 +1983 244 19.68 13.68 18.03 0.14 501.96 243.63 47145 +1983 245 21.03 15.03 19.38 0 541.2 318.87 46947 +1983 246 25.25 19.25 23.6 0 681.09 301.86 46747 +1983 247 24.23 18.23 22.58 0.31 644.75 228.05 46547 +1983 248 22.69 16.69 21.04 0.11 593 230.82 46347 +1983 249 23 17 21.35 0.17 603.12 228.52 46146 +1983 250 19.93 13.93 18.28 0 509.04 312.62 45945 +1983 251 24.55 18.55 22.9 0.18 655.97 221.39 45743 +1983 252 22.61 16.61 20.96 1.3 590.41 225.02 45541 +1983 253 18.68 12.68 17.03 0.97 474.48 232.35 45339 +1983 254 16.63 10.63 14.98 0.12 422.13 234.63 45136 +1983 255 18.34 12.34 16.69 0.13 465.43 229.75 44933 +1983 256 22.4 16.4 20.75 0 583.66 292.27 44730 +1983 257 20.31 14.31 18.66 0 519.96 296.58 44527 +1983 258 18.6 12.6 16.95 0.21 472.34 224.21 44323 +1983 259 17.64 11.64 15.99 0 447.27 298.96 44119 +1983 260 19.61 13.61 17.96 0 500 291.52 43915 +1983 261 18.29 12.29 16.64 0 464.12 292.56 43711 +1983 262 17.82 11.82 16.17 0.02 451.88 218.52 43507 +1983 263 21.85 15.85 20.2 0 566.28 278.01 43303 +1983 264 18.79 12.79 17.14 0 477.44 283.99 43099 +1983 265 14.7 8.7 13.05 0.17 377.42 218.11 42894 +1983 266 16.27 10.27 14.62 0 413.46 285.09 42690 +1983 267 16.41 10.41 14.76 0 416.81 282.12 42486 +1983 268 17.98 11.98 16.33 0 456.02 276.04 42282 +1983 269 19.6 13.6 17.95 0.13 499.72 202.2 42078 +1983 270 15.09 9.09 13.44 1.78 386.11 207.85 41875 +1983 271 13.76 7.76 12.11 0.01 357.15 207.75 41671 +1983 272 15.21 9.21 13.56 0.01 388.82 203.66 41468 +1983 273 13.92 7.92 12.27 0 360.53 271.42 41265 +1983 274 12.59 6.59 10.94 0.34 333.23 203.25 41062 +1983 275 10.63 4.63 8.98 0 296.23 271.21 40860 +1983 276 10.93 4.93 9.28 0 301.65 268.04 40658 +1983 277 14.25 8.25 12.6 0 367.6 260.02 40456 +1983 278 14.41 8.41 12.76 0 371.06 256.88 40255 +1983 279 12.59 6.59 10.94 0.93 333.23 192.83 40054 +1983 280 13.01 7.01 11.36 0.07 341.66 190.33 39854 +1983 281 16.41 10.41 14.76 0 416.81 245.06 39654 +1983 282 14.14 8.14 12.49 0.43 365.23 184.85 39455 +1983 283 11.96 5.96 10.31 0.01 320.93 185.31 39256 +1983 284 14.84 8.84 13.19 0 380.52 239.46 39058 +1983 285 19.21 13.21 17.56 0 488.88 228.3 38861 +1983 286 16.04 10.04 14.39 0 408 232 38664 +1983 287 16.84 10.84 15.19 0 427.25 227.63 38468 +1983 288 20.34 14.34 18.69 0.61 520.83 163.2 38273 +1983 289 14.44 8.44 12.79 0 371.72 226.51 38079 +1983 290 16.74 10.74 15.09 0 424.8 219.73 37885 +1983 291 14.17 8.17 12.52 0.38 365.87 166.08 37693 +1983 292 14.76 8.76 13.11 0 378.75 217.85 37501 +1983 293 16.01 10.01 14.36 0 407.3 213.09 37311 +1983 294 14.71 8.71 13.06 0 377.64 212.39 37121 +1983 295 17.13 11.13 15.48 0 434.42 205.54 36933 +1983 296 17.65 11.65 16 0 447.52 202.09 36745 +1983 297 17.35 11.35 15.7 0 439.92 199.99 36560 +1983 298 17.07 11.07 15.42 0 432.93 197.97 36375 +1983 299 12.62 6.62 10.97 1.87 333.83 151.52 36191 +1983 300 10.92 4.92 9.27 0.28 301.47 151.13 36009 +1983 301 10.11 4.11 8.46 0 287.02 199.92 35829 +1983 302 10.6 4.6 8.95 0 295.69 196.76 35650 +1983 303 9.59 3.59 7.94 0.35 278.06 146.47 35472 +1983 304 8.96 2.96 7.31 0.08 267.53 145.1 35296 +1983 305 3.17 -2.83 1.52 0 185.71 195.57 35122 +1983 306 -1.42 -7.42 -3.07 0 137.16 195.97 34950 +1983 307 1.28 -4.72 -0.37 0.08 164.17 143.94 34779 +1983 308 5.1 -0.9 3.45 0 210.18 186.68 34610 +1983 309 8.39 2.39 6.74 0 258.3 181.57 34444 +1983 310 8.89 2.89 7.24 0 266.38 178.66 34279 +1983 311 8.67 2.67 7.02 0 262.8 176.69 34116 +1983 312 7.2 1.2 5.55 0 239.91 175.34 33956 +1983 313 4.39 -1.61 2.74 0 200.88 175.36 33797 +1983 314 6.4 0.4 4.75 0 228.18 171.9 33641 +1983 315 3.69 -2.31 2.04 0.05 192.05 128.47 33488 +1983 316 5.71 -0.29 4.06 0 218.47 167.68 33337 +1983 317 11.63 5.63 9.98 0 314.64 160.22 33188 +1983 318 8.28 2.28 6.63 0 256.55 161.1 33042 +1983 319 9.78 3.78 8.13 0 281.31 158.08 32899 +1983 320 12.39 6.39 10.74 0 329.28 153.61 32758 +1983 321 12.75 6.75 11.1 0 336.42 151.16 32620 +1983 322 12.58 6.58 10.93 0.29 333.03 112.17 32486 +1983 323 11.47 5.47 9.82 0 311.63 149.14 32354 +1983 324 12.32 6.32 10.67 0 327.91 146.25 32225 +1983 325 9.15 3.15 7.5 0.57 270.67 110.67 32100 +1983 326 10.12 4.12 8.47 0 287.2 145.27 31977 +1983 327 7.64 1.64 5.99 0 246.57 145.5 31858 +1983 328 5.12 -0.88 3.47 0 210.45 145.3 31743 +1983 329 -0.09 -6.09 -1.74 0 149.94 146.63 31631 +1983 330 1.42 -4.58 -0.23 0 165.69 144.44 31522 +1983 331 -2.86 -8.86 -4.51 0 124.39 144.95 31417 +1983 332 -2.02 -8.02 -3.67 0 131.71 142.96 31316 +1983 333 -3.97 -9.97 -5.62 0.87 115.27 151.88 31218 +1983 334 -2.07 -8.07 -3.72 0.56 131.26 152.38 31125 +1983 335 -0.92 -6.92 -2.57 0 141.85 186.05 31035 +1983 336 0.91 -5.09 -0.74 0.16 160.22 149.88 30949 +1983 337 -1.61 -7.61 -3.26 0 135.41 183.7 30867 +1983 338 -0.84 -6.84 -2.49 0.25 142.61 149.5 30790 +1983 339 1.85 -4.15 0.2 0.66 170.43 147.87 30716 +1983 340 0.66 -5.34 -0.99 0 157.6 181.04 30647 +1983 341 -0.16 -6.16 -1.81 0 149.25 180.57 30582 +1983 342 6.18 0.18 4.53 0 225.05 175.76 30521 +1983 343 5.57 -0.43 3.92 0 216.54 174.67 30465 +1983 344 8.71 2.71 7.06 0 263.45 170.35 30413 +1983 345 5.33 -0.67 3.68 0 213.27 171.55 30366 +1983 346 4.61 -1.39 2.96 0 203.72 170.87 30323 +1983 347 4.07 -1.93 2.42 0 196.8 170.09 30284 +1983 348 12.04 6.04 10.39 0 322.47 120.19 30251 +1983 349 9.35 3.35 7.7 0 274.01 122.06 30221 +1983 350 8.22 2.22 6.57 0 255.6 122.56 30197 +1983 351 13.53 7.53 11.88 0.05 352.34 88.41 30177 +1983 352 13.18 7.18 11.53 0 345.12 118.13 30162 +1983 353 10.29 4.29 8.64 0 290.18 120.63 30151 +1983 354 9.73 3.73 8.08 0 280.45 121.04 30145 +1983 355 10.31 4.31 8.66 0 290.53 120.58 30144 +1983 356 4.73 -1.27 3.08 0 205.29 124.41 30147 +1983 357 2.87 -3.13 1.22 0.02 182.14 94.1 30156 +1983 358 -4.81 -10.81 -6.46 0 108.75 128.56 30169 +1983 359 -1.79 -7.79 -3.44 0 133.78 127.69 30186 +1983 360 -5.09 -11.09 -6.74 0 106.65 129.14 30208 +1983 361 -3.3 -9.3 -4.95 0 120.7 128.92 30235 +1983 362 -3.17 -9.17 -4.82 0 121.78 129.32 30267 +1983 363 0.62 -5.38 -1.03 0.31 157.18 96.34 30303 +1983 364 -1.61 -7.61 -3.26 0.07 135.41 141.05 30343 +1983 365 1.97 -4.03 0.32 0.28 171.77 96.61 30388 +1984 1 -1.48 -7.48 -3.13 0.01 136.61 141.79 30438 +1984 2 3.99 -2.01 2.34 0.39 195.79 97.04 30492 +1984 3 6.26 0.26 4.61 0.04 226.18 96.73 30551 +1984 4 7.99 1.99 6.34 0 251.99 128.7 30614 +1984 5 4.95 -1.05 3.3 0 208.18 131.34 30681 +1984 6 5.46 -0.54 3.81 0.82 215.04 98.93 30752 +1984 7 6.63 0.63 4.98 0 231.5 131.94 30828 +1984 8 9.7 3.7 8.05 0.08 279.94 98.35 30907 +1984 9 9.22 3.22 7.57 0.07 271.84 99.57 30991 +1984 10 6.25 0.25 4.6 0.07 226.04 102.16 31079 +1984 11 5.58 -0.42 3.93 0.02 216.68 103.22 31171 +1984 12 4.95 -1.05 3.3 0.01 208.18 104.27 31266 +1984 13 3.43 -2.57 1.78 0.24 188.86 106.17 31366 +1984 14 2.99 -3.01 1.34 0.44 183.56 107.46 31469 +1984 15 0.28 -5.72 -1.37 1.05 153.68 109.58 31575 +1984 16 -2.45 -8.45 -4.1 0 127.92 148.57 31686 +1984 17 -1.69 -7.69 -3.34 0 134.68 149.97 31800 +1984 18 -3.02 -9.02 -4.67 0 123.04 152.41 31917 +1984 19 -3.13 -9.13 -4.78 0.35 122.12 158.06 32038 +1984 20 -3.52 -9.52 -5.17 0 118.89 198.26 32161 +1984 21 -3.73 -9.73 -5.38 0 117.19 200.2 32289 +1984 22 -0.09 -6.09 -1.74 1.1 149.94 163.9 32419 +1984 23 1.07 -4.93 -0.58 0.45 161.92 164.49 32552 +1984 24 4.51 -1.49 2.86 0.25 202.42 163.79 32688 +1984 25 7.79 1.79 6.14 0.28 248.88 162.24 32827 +1984 26 4.53 -1.47 2.88 0.25 202.68 164.75 32969 +1984 27 1.49 -4.51 -0.16 0 166.46 209.17 33114 +1984 28 6.55 0.55 4.9 0 230.34 207.06 33261 +1984 29 4.56 -1.44 2.91 0 203.07 210.15 33411 +1984 30 5.57 -0.43 3.92 0 216.54 171.67 33564 +1984 31 6.57 0.57 4.92 0 230.63 173.26 33718 +1984 32 7.01 1.01 5.36 0 237.08 175 33875 +1984 33 0.95 -5.05 -0.7 0.02 160.64 136.35 34035 +1984 34 0.14 -5.86 -1.51 0.2 152.26 138.36 34196 +1984 35 3.07 -2.93 1.42 0.39 184.52 138.67 34360 +1984 36 6.72 0.72 5.07 0.8 232.81 138.5 34526 +1984 37 8.19 2.19 6.54 0.03 255.13 139.32 34694 +1984 38 6.97 0.97 5.32 0.03 236.48 142.19 34863 +1984 39 6.7 0.7 5.05 0 232.52 192.41 35035 +1984 40 8.25 2.25 6.6 0.27 256.08 145.19 35208 +1984 41 8.17 2.17 6.52 0 254.81 196.25 35383 +1984 42 6.2 0.2 4.55 0 225.33 200.59 35560 +1984 43 0.28 -5.72 -1.37 0.17 153.68 155.67 35738 +1984 44 -1.08 -7.08 -2.73 0.2 140.33 195.48 35918 +1984 45 -3.56 -9.56 -5.21 0.05 118.57 198.36 36099 +1984 46 -0.87 -6.87 -2.52 0 142.33 253.24 36282 +1984 47 -0.67 -6.67 -2.32 0 144.25 255.8 36466 +1984 48 -2.41 -8.41 -4.06 0 128.27 259.4 36652 +1984 49 -1.02 -7.02 -2.67 0 140.9 261.29 36838 +1984 50 0.11 -5.89 -1.54 0 151.95 263.12 37026 +1984 51 1.09 -4.91 -0.56 0.54 162.13 207.88 37215 +1984 52 2.8 -3.2 1.15 0.85 181.32 208.63 37405 +1984 53 0.62 -5.38 -1.03 0 157.18 270.62 37596 +1984 54 2.9 -3.1 1.25 0.04 182.5 177.39 37788 +1984 55 4.54 -1.46 2.89 0 202.81 238.17 37981 +1984 56 4.45 -1.55 2.8 0 201.65 240.95 38175 +1984 57 1.59 -4.41 -0.06 0.47 167.55 184.61 38370 +1984 58 6.48 0.48 4.83 0 229.33 244.86 38565 +1984 59 5.51 -0.49 3.86 0 215.72 248.53 38761 +1984 60 12.25 6.25 10.6 0.73 326.54 182.45 38958 +1984 61 9.09 3.09 7.44 0.03 269.68 187.82 39156 +1984 62 11.89 5.89 10.24 0 319.59 249.41 39355 +1984 63 8.89 2.89 7.24 0 266.38 256.43 39553 +1984 64 8.46 2.46 6.81 0 259.42 259.84 39753 +1984 65 5.28 -0.72 3.63 0 212.6 266.22 39953 +1984 66 5.91 -0.09 4.26 0 221.25 268.33 40154 +1984 67 10.22 4.22 8.57 0 288.95 266.02 40355 +1984 68 10.47 4.47 8.82 0 293.37 268.51 40556 +1984 69 7.38 1.38 5.73 0 242.61 275.11 40758 +1984 70 6.12 0.12 4.47 0 224.2 279.39 40960 +1984 71 5.98 -0.02 4.33 0 222.23 282.47 41163 +1984 72 7.39 1.39 5.74 0 242.76 283.68 41366 +1984 73 9.56 3.56 7.91 0 277.55 283.54 41569 +1984 74 10.92 4.92 9.27 0 301.47 284.28 41772 +1984 75 8.29 2.29 6.64 0 256.71 290.7 41976 +1984 76 7.4 1.4 5.75 0 242.92 294.47 42179 +1984 77 6.92 0.92 5.27 0.24 235.74 223.25 42383 +1984 78 5.8 -0.2 4.15 0 219.72 301.66 42587 +1984 79 3.52 -2.48 1.87 0 189.96 306.82 42791 +1984 80 3.91 -2.09 2.26 0 194.79 309 42996 +1984 81 4.59 -1.41 2.94 0 203.46 310.91 43200 +1984 82 5.13 -0.87 3.48 0.24 210.58 234.75 43404 +1984 83 5.13 -0.87 3.48 0.79 210.58 236.64 43608 +1984 84 1.96 -4.04 0.31 0.03 171.66 240.99 43812 +1984 85 0.56 -5.44 -1.09 0 156.56 325.09 44016 +1984 86 8.27 2.27 6.62 0.23 256.39 239.32 44220 +1984 87 9.02 3.02 7.37 0.89 268.52 240.41 44424 +1984 88 12.42 6.42 10.77 0 329.87 317.31 44627 +1984 89 14.04 8.04 12.39 0.41 363.09 237.33 44831 +1984 90 10.43 4.43 8.78 0.25 292.66 244.02 45034 +1984 91 12.23 6.23 10.58 0 326.15 324.49 45237 +1984 92 13.12 7.12 11.47 0 343.89 325.03 45439 +1984 93 11.8 5.8 10.15 0.27 317.87 247.27 45642 +1984 94 12.75 6.75 11.1 0.47 336.42 247.55 45843 +1984 95 10.97 4.97 9.32 0 302.38 335.44 46045 +1984 96 12.99 6.99 11.34 0 341.25 333.81 46246 +1984 97 12.36 6.36 10.71 0.03 328.69 252.8 46446 +1984 98 13.66 7.66 12.01 0.04 355.05 252.33 46647 +1984 99 12.5 6.5 10.85 0 331.45 340.76 46846 +1984 100 12.14 6.14 10.49 0 324.4 343.39 47045 +1984 101 9.78 3.78 8.13 0 281.31 349.51 47243 +1984 102 8.96 2.96 7.31 0 267.53 352.75 47441 +1984 103 9.86 3.86 8.21 0.47 282.68 264.86 47638 +1984 104 14.7 8.7 13.05 0 377.42 345.52 47834 +1984 105 15.71 9.71 14.06 0 400.28 344.93 48030 +1984 106 15.19 9.19 13.54 0 388.37 347.79 48225 +1984 107 13.22 7.22 11.57 0 345.94 353.8 48419 +1984 108 17.13 11.13 15.48 0 434.42 346.31 48612 +1984 109 16.24 10.24 14.59 0 412.74 350.19 48804 +1984 110 12.41 6.41 10.76 0 329.68 360.22 48995 +1984 111 13.59 7.59 11.94 0 353.59 359.31 49185 +1984 112 17.65 11.65 16 0 447.52 350.85 49374 +1984 113 17.41 11.41 15.76 0 441.43 352.82 49561 +1984 114 16.29 10.29 14.64 0.07 413.94 267.94 49748 +1984 115 11.82 5.82 10.17 0.53 318.25 276.57 49933 +1984 116 10.14 4.14 8.49 0.17 287.55 279.85 50117 +1984 117 10.24 4.24 8.59 0.3 289.3 280.71 50300 +1984 118 9.13 3.13 7.48 0 270.34 377.55 50481 +1984 119 5.02 -0.98 3.37 0.15 209.11 288.64 50661 +1984 120 6.26 0.26 4.61 2.54 226.18 288.29 50840 +1984 121 9.65 3.65 8 1.49 279.08 285.16 51016 +1984 122 12.65 6.65 11 0.08 334.42 281.75 51191 +1984 123 16.59 10.59 14.94 0 421.16 367.32 51365 +1984 124 11.69 5.69 10.04 0.47 315.78 284.82 51536 +1984 125 16.9 10.9 15.25 0 428.73 368.52 51706 +1984 126 17.13 11.13 15.48 0.04 434.42 276.66 51874 +1984 127 18.34 12.34 16.69 0 465.43 366.27 52039 +1984 128 18.27 12.27 16.62 0 463.59 367.46 52203 +1984 129 22.42 16.42 20.77 0.1 584.3 265.75 52365 +1984 130 19.27 13.27 17.62 0.51 490.54 274.5 52524 +1984 131 17.47 11.47 15.82 0.05 442.95 279.15 52681 +1984 132 16.53 10.53 14.88 0.05 419.7 281.72 52836 +1984 133 17.8 11.8 16.15 0.21 451.37 279.57 52989 +1984 134 16.24 10.24 14.59 1.07 412.74 283.36 53138 +1984 135 15.1 9.1 13.45 0.05 386.34 286.1 53286 +1984 136 12.92 6.92 11.27 0.09 339.83 290.41 53430 +1984 137 13.02 7.02 11.37 0.52 341.86 290.78 53572 +1984 138 14.71 8.71 13.06 0.2 377.64 288.29 53711 +1984 139 11.65 5.65 10 0.21 315.02 293.95 53848 +1984 140 16.5 10.5 14.85 0.11 418.98 285.7 53981 +1984 141 16.34 10.34 14.69 0.11 415.13 286.35 54111 +1984 142 19.23 13.23 17.58 0 489.43 373.78 54238 +1984 143 19.04 13.04 17.39 0.59 484.22 281.19 54362 +1984 144 20.59 14.59 18.94 0.01 528.14 277.68 54483 +1984 145 16.92 10.92 15.27 0 429.22 382.19 54600 +1984 146 18.83 12.83 17.18 0 478.52 376.89 54714 +1984 147 18.32 12.32 16.67 1.05 464.91 284.21 54824 +1984 148 19.12 13.12 17.47 0.73 486.41 282.62 54931 +1984 149 15.92 9.92 14.27 0.02 405.18 289.86 55034 +1984 150 15.12 9.12 13.47 0.39 386.79 291.68 55134 +1984 151 14.92 8.92 13.27 0.95 382.3 292.35 55229 +1984 152 20.13 14.13 18.48 0.02 514.76 280.97 55321 +1984 153 15.76 9.76 14.11 0.35 401.44 291 55409 +1984 154 17.22 11.22 15.57 0.02 436.66 288.22 55492 +1984 155 16.58 10.58 14.93 0 420.91 386.3 55572 +1984 156 18.69 12.69 17.04 0 474.75 380.4 55648 +1984 157 21.38 15.38 19.73 0 551.79 371.45 55719 +1984 158 18.77 12.77 17.12 0 476.9 380.49 55786 +1984 159 20.59 14.59 18.94 0 528.14 374.68 55849 +1984 160 24 18 22.35 0.99 636.78 271.28 55908 +1984 161 22.12 16.12 20.47 0.08 574.76 277 55962 +1984 162 25.65 19.65 24 0 695.8 354.52 56011 +1984 163 26.76 20.76 25.11 0 738.06 349.42 56056 +1984 164 25.08 19.08 23.43 0.4 674.91 268.03 56097 +1984 165 24.99 18.99 23.34 0.04 671.66 268.4 56133 +1984 166 23.36 17.36 21.71 0.11 615.06 273.69 56165 +1984 167 20.97 14.97 19.32 0.17 539.4 280.52 56192 +1984 168 19.72 13.72 18.07 0.12 503.09 283.81 56214 +1984 169 21.79 15.79 20.14 0.08 564.42 278.33 56231 +1984 170 21.65 15.65 20 0 560.08 371.63 56244 +1984 171 22.22 16.22 20.57 0.42 577.92 277.15 56252 +1984 172 20.68 14.68 19.03 0.04 530.79 281.39 56256 +1984 173 21.63 15.63 19.98 0 559.46 371.74 56255 +1984 174 19.33 13.33 17.68 0 492.19 379.66 56249 +1984 175 17.95 11.95 16.3 0.1 455.24 287.97 56238 +1984 176 19.68 13.68 18.03 1.84 501.96 283.83 56223 +1984 177 15.01 9.01 13.36 0 384.31 391.95 56203 +1984 178 13.96 7.96 12.31 0 361.38 394.55 56179 +1984 179 16.57 10.57 14.92 0.16 420.67 290.8 56150 +1984 180 16.93 10.93 15.28 0.91 429.47 289.95 56116 +1984 181 13.17 7.17 11.52 0 344.91 396.08 56078 +1984 182 16.37 10.37 14.72 0.05 415.85 290.95 56035 +1984 183 18.7 12.7 17.05 0.26 475.02 285.68 55987 +1984 184 20.23 14.23 18.58 0.21 517.65 281.8 55935 +1984 185 14.03 8.03 12.38 0.18 362.88 295.12 55879 +1984 186 18.48 12.48 16.83 0.64 469.14 285.82 55818 +1984 187 16.94 10.94 15.29 0 429.71 385.47 55753 +1984 188 18.37 12.37 16.72 0 466.23 380.98 55684 +1984 189 16.17 10.17 14.52 0 411.08 387.14 55611 +1984 190 18.28 12.28 16.63 0 463.85 380.7 55533 +1984 191 19.87 13.87 18.22 0 507.33 375.34 55451 +1984 192 25.35 19.35 23.7 0.25 684.74 265.19 55366 +1984 193 25.3 19.3 23.65 0.35 682.91 265.16 55276 +1984 194 23.83 17.83 22.18 0 630.95 359.72 55182 +1984 195 23.96 17.96 22.31 0.42 635.41 269.19 55085 +1984 196 21.39 15.39 19.74 0.05 552.1 276.42 54984 +1984 197 23.52 17.52 21.87 0.01 620.43 269.92 54879 +1984 198 20.57 14.57 18.92 1.72 527.55 277.95 54770 +1984 199 19.17 13.17 17.52 1.68 487.78 281.18 54658 +1984 200 20.78 14.78 19.13 0.41 533.75 276.83 54542 +1984 201 23.06 17.06 21.41 0.4 605.1 270.1 54423 +1984 202 25.77 19.77 24.12 0.11 700.27 260.99 54301 +1984 203 23.54 17.54 21.89 0.68 621.1 267.87 54176 +1984 204 20.36 14.36 18.71 0 521.41 368.52 54047 +1984 205 18.45 12.45 16.8 0.14 468.34 280.62 53915 +1984 206 23.43 17.43 21.78 0.7 617.4 267.04 53780 +1984 207 21.78 15.78 20.13 0.12 564.11 271.33 53643 +1984 208 23.3 17.3 21.65 0 613.06 355.29 53502 +1984 209 25.61 19.61 23.96 0 694.32 344.83 53359 +1984 210 26.02 20.02 24.37 0.39 709.66 256.77 53213 +1984 211 21.28 15.28 19.63 0.74 548.75 270.67 53064 +1984 212 20.67 14.67 19.02 0.37 530.49 271.67 52913 +1984 213 18.88 12.88 17.23 0 479.87 367.3 52760 +1984 214 20.73 14.73 19.08 0 532.26 360.52 52604 +1984 215 19.61 13.61 17.96 0 500 363.56 52445 +1984 216 18.03 12.03 16.38 0.38 457.31 275.54 52285 +1984 217 21.84 15.84 20.19 0.08 565.97 265.53 52122 +1984 218 24.47 18.47 22.82 0 653.15 342.97 51958 +1984 219 25.58 19.58 23.93 0 693.21 337.17 51791 +1984 220 31.93 25.93 30.28 0.57 964.61 227.05 51622 +1984 221 31.91 25.91 30.26 0.3 963.63 226.48 51451 +1984 222 27.75 21.75 26.1 0.04 777.56 243.11 51279 +1984 223 26.18 20.18 24.53 0 715.72 330.54 51105 +1984 224 23.88 17.88 22.23 0 632.66 339.36 50929 +1984 225 23.54 17.54 21.89 0.83 621.1 254.7 50751 +1984 226 22.25 16.25 20.6 0 578.87 343.36 50572 +1984 227 21.49 15.49 19.84 0 555.15 344.8 50392 +1984 228 18.87 12.87 17.22 0 479.6 352.05 50210 +1984 229 20.2 14.2 18.55 0 516.78 346.68 50026 +1984 230 15.44 9.44 13.79 0.18 394.06 269.08 49842 +1984 231 17.71 11.71 16.06 0.22 449.06 263.53 49656 +1984 232 17.62 11.62 15.97 0 446.76 350.26 49469 +1984 233 16.43 10.43 14.78 0 417.29 351.97 49280 +1984 234 16.76 10.76 15.11 0.03 425.29 262.26 49091 +1984 235 18.83 12.83 17.18 0 478.52 342.47 48900 +1984 236 21.42 15.42 19.77 0.39 553.01 249.68 48709 +1984 237 22.26 16.26 20.61 0.49 579.19 246.3 48516 +1984 238 23.4 17.4 21.75 0.02 616.4 241.98 48323 +1984 239 22.51 16.51 20.86 0.02 587.18 243.31 48128 +1984 240 25.09 19.09 23.44 0.16 675.27 234.68 47933 +1984 241 21.91 15.91 20.26 0.84 568.16 242.32 47737 +1984 242 16.79 10.79 15.14 0.08 426.03 252.34 47541 +1984 243 18.13 12.13 16.48 0.48 459.92 248.3 47343 +1984 244 13.8 7.8 12.15 0.11 357.99 254.7 47145 +1984 245 13.5 7.5 11.85 0 351.71 338.33 46947 +1984 246 18 12 16.35 0.08 456.53 244.33 46747 +1984 247 19.19 13.19 17.54 0 488.33 320.65 46547 +1984 248 18.32 12.32 16.67 0 464.91 321.12 46347 +1984 249 22.99 16.99 21.34 0 602.79 304.73 46146 +1984 250 26.36 20.36 24.71 0 722.59 289.99 45945 +1984 251 23.61 17.61 21.96 0.59 623.47 223.98 45743 +1984 252 24.82 18.82 23.17 0.31 665.56 219.09 45541 +1984 253 23.21 17.21 21.56 0.05 610.06 221.96 45339 +1984 254 22.95 16.95 21.3 0 601.48 294.79 45136 +1984 255 19.98 13.98 18.33 0 510.47 301.86 44933 +1984 256 17.31 11.31 15.66 0.64 438.92 230 44730 +1984 257 13.12 7.12 11.47 1.05 343.89 235.13 44527 +1984 258 14.5 8.5 12.85 0.61 373.03 231.31 44323 +1984 259 10.39 4.39 8.74 0 291.95 313.34 44119 +1984 260 9.79 3.79 8.14 0.01 281.48 233.86 43915 +1984 261 15.77 9.77 14.12 0.01 401.68 223.82 43711 +1984 262 15.49 9.49 13.84 0.08 395.2 222.48 43507 +1984 263 14.44 8.44 12.79 0 371.72 296.31 43303 +1984 264 16.1 10.1 14.45 0 409.42 290.29 43099 +1984 265 15.95 9.95 14.3 0.1 405.89 216.18 42894 +1984 266 21.19 15.19 19.54 0.81 546.02 204.6 42690 +1984 267 22.63 16.63 20.98 0.71 591.05 199.47 42486 +1984 268 22.24 16.24 20.59 0.46 578.56 198.52 42282 +1984 269 20.05 14.05 18.4 0.13 512.47 201.32 42078 +1984 270 19.09 13.09 17.44 2.33 485.59 201.23 41875 +1984 271 21.54 15.54 19.89 0.32 556.69 194.47 41671 +1984 272 20.35 14.35 18.7 0 521.12 259.9 41468 +1984 273 20.36 14.36 18.71 0.09 521.41 193.08 41265 +1984 274 14.7 8.7 13.05 0 377.42 267.32 41062 +1984 275 14.71 8.71 13.06 1.35 377.64 198.41 40860 +1984 276 12.02 6.02 10.37 0.68 322.08 199.8 40658 +1984 277 16.88 10.88 15.23 0.42 428.23 191.24 40456 +1984 278 18.03 12.03 16.38 0 457.31 249.73 40255 +1984 279 17.93 11.93 16.28 0 454.72 247.2 40054 +1984 280 18 12 16.35 0 456.53 244.47 39854 +1984 281 16.08 10.08 14.43 0 408.95 245.69 39654 +1984 282 13.23 7.23 11.58 0.1 346.14 185.97 39455 +1984 283 13.32 7.32 11.67 0.55 347.99 183.75 39256 +1984 284 8.97 2.97 7.32 0 267.7 248.01 39058 +1984 285 11.48 5.48 9.83 0.03 311.82 181.55 38861 +1984 286 15.21 9.21 13.56 0 388.82 233.48 38664 +1984 287 13.4 7.4 11.75 0.01 349.64 175.15 38468 +1984 288 16.46 10.46 14.81 0 418.01 225.62 38273 +1984 289 16.37 10.37 14.72 0 415.85 223.2 38079 +1984 290 16.22 10.22 14.57 0.01 412.27 165.5 37885 +1984 291 11.69 5.69 10.04 0.42 315.78 168.78 37693 +1984 292 10.46 4.46 8.81 0.88 293.19 167.95 37501 +1984 293 11.07 5.07 9.42 0 304.21 220.43 37311 +1984 294 17.73 11.73 16.08 0 449.57 207.19 37121 +1984 295 16.08 10.08 14.43 0 408.95 207.37 36933 +1984 296 13.77 7.77 12.12 0 357.36 208.46 36745 +1984 297 13.2 7.2 11.55 0 345.53 206.58 36560 +1984 298 12.88 6.88 11.23 0 339.03 204.44 36375 +1984 299 15.09 9.09 13.44 0 386.11 198.5 36191 +1984 300 17.47 11.47 15.82 0 442.95 191.99 36009 +1984 301 16.11 10.11 14.46 0.41 409.66 143.88 35829 +1984 302 18.63 12.63 16.98 0.03 473.14 138.73 35650 +1984 303 15.12 9.12 13.47 1.16 386.79 141.23 35472 +1984 304 10.95 4.95 9.3 0.37 302.02 143.5 35296 +1984 305 4.58 -1.42 2.93 0.2 203.33 145.92 35122 +1984 306 4.38 -1.62 2.73 0 200.75 192.41 34950 +1984 307 2.95 -3.05 1.3 0.08 183.09 143.15 34779 +1984 308 6.59 0.59 4.94 0.06 230.92 139.12 34610 +1984 309 2.19 -3.81 0.54 1.35 174.26 139.75 34444 +1984 310 4.3 -1.7 2.65 0.18 199.72 136.84 34279 +1984 311 5.99 -0.01 4.34 0 222.37 178.98 34116 +1984 312 8.89 2.89 7.24 0.33 266.38 130.38 33956 +1984 313 8.82 2.82 7.17 0.81 265.24 128.85 33797 +1984 314 6.5 0.5 4.85 0 229.62 171.82 33641 +1984 315 10.29 4.29 8.64 0 290.18 165.92 33488 +1984 316 8.13 2.13 6.48 0 254.18 165.75 33337 +1984 317 6.45 0.45 4.8 0 228.9 164.92 33188 +1984 318 6.73 0.73 5.08 0 232.96 162.36 33042 +1984 319 5.16 -0.84 3.51 0 210.98 161.81 32899 +1984 320 6.31 0.31 4.66 0 226.89 159.11 32758 +1984 321 7.39 1.39 5.74 0 242.76 156.17 32620 +1984 322 9.72 3.72 8.07 0 280.28 152.39 32486 +1984 323 5.07 -0.93 3.42 0 209.78 154.41 32354 +1984 324 10.65 4.65 9 0 296.59 147.91 32225 +1984 325 13.24 7.24 11.59 0.09 346.35 107.69 32100 +1984 326 12.17 6.17 10.52 0 324.99 143.31 31977 +1984 327 11.45 5.45 9.8 0.57 311.26 106.66 31858 +1984 328 12.36 6.36 10.71 0.26 328.69 104.53 31743 +1984 329 12.56 6.56 10.91 0 332.64 137.71 31631 +1984 330 12.6 6.6 10.95 0.09 333.43 102.2 31522 +1984 331 10.02 4.02 8.37 0 285.45 137.4 31417 +1984 332 12.85 6.85 11.2 0 338.42 133.13 31316 +1984 333 14.65 8.65 13 0.49 376.32 97.61 31218 +1984 334 11.64 5.64 9.99 0.3 314.83 99.14 31125 +1984 335 3.41 -2.59 1.76 0 188.62 137.02 31035 +1984 336 3.41 -2.59 1.76 0 188.62 135.95 30949 +1984 337 2.54 -3.46 0.89 0.16 178.28 101.06 30867 +1984 338 -0.29 -6.29 -1.94 0 147.96 135.11 30790 +1984 339 -3.58 -9.58 -5.23 0 118.4 135.56 30716 +1984 340 -4.22 -10.22 -5.87 0 113.29 135.01 30647 +1984 341 -2.24 -8.24 -3.89 0.07 129.76 143.43 30582 +1984 342 -4.08 -10.08 -5.73 0 114.39 176.73 30521 +1984 343 -3.81 -9.81 -5.46 0 116.55 175.88 30465 +1984 344 -0.81 -6.81 -2.46 0 142.9 173.73 30413 +1984 345 -3.47 -9.47 -5.12 0.79 119.3 144.17 30366 +1984 346 -2.43 -8.43 -4.08 0.05 128.09 143.7 30323 +1984 347 2.67 -3.33 1.02 0 179.79 173.08 30284 +1984 348 2.94 -3.06 1.29 0 182.97 172.25 30251 +1984 349 5.94 -0.06 4.29 0 221.67 169.44 30221 +1984 350 2.7 -3.3 1.05 0 180.14 170.58 30197 +1984 351 3.08 -2.92 1.43 0 184.64 169.79 30177 +1984 352 3.33 -2.67 1.68 0 187.64 169.14 30162 +1984 353 5.51 -0.49 3.86 0 215.72 123.96 30151 +1984 354 5.71 -0.29 4.06 0 218.47 123.81 30145 +1984 355 3.12 -2.88 1.47 0 185.11 125.25 30144 +1984 356 3.25 -2.75 1.6 0.25 186.68 93.91 30147 +1984 357 2.38 -3.62 0.73 0.03 176.43 94.28 30156 +1984 358 5.82 -0.18 4.17 0.14 219.99 92.93 30169 +1984 359 7.06 1.06 5.41 0 237.82 123.24 30186 +1984 360 11.41 5.41 9.76 0 310.51 120.29 30208 +1984 361 9.12 3.12 7.47 0 270.17 122.47 30235 +1984 362 8.78 2.78 7.13 0 264.59 123.16 30267 +1984 363 8.16 2.16 6.51 0.37 254.65 93.14 30303 +1984 364 8.9 2.9 7.25 0.3 266.55 93.03 30343 +1984 365 8.24 2.24 6.59 0.02 255.92 93.81 30388 +1985 1 4.91 -1.09 3.26 0.46 207.65 96.1 30438 +1985 2 0.61 -5.39 -1.04 0.1 157.08 98.3 30492 +1985 3 -0.17 -6.17 -1.82 0.19 149.15 143.07 30551 +1985 4 -1.8 -7.8 -3.45 0 133.69 177.64 30614 +1985 5 -4.34 -10.34 -5.99 0 112.36 179.09 30681 +1985 6 -5.66 -11.66 -7.31 0 102.49 180.29 30752 +1985 7 -5.98 -11.98 -7.63 0.1 100.21 146.98 30828 +1985 8 -8.43 -14.43 -10.08 0 84.19 183.45 30907 +1985 9 -9.07 -15.07 -10.72 0 80.4 184.76 30991 +1985 10 -6.66 -12.66 -8.31 0.28 95.52 150.72 31079 +1985 11 -8.5 -14.5 -10.15 0 83.77 187.58 31171 +1985 12 -5.95 -11.95 -7.6 0 100.42 187.8 31266 +1985 13 -5.74 -11.74 -7.39 0 101.91 189.24 31366 +1985 14 -2.47 -8.47 -4.12 0 127.74 189.49 31469 +1985 15 -1.72 -7.72 -3.37 0.08 134.41 154.01 31575 +1985 16 -2.29 -8.29 -3.94 0 129.32 192.13 31686 +1985 17 -0.12 -6.12 -1.77 0 149.64 192.76 31800 +1985 18 0.29 -5.71 -1.36 0 153.78 194.28 31917 +1985 19 0.36 -5.64 -1.29 0.2 154.5 157.76 32038 +1985 20 3.43 -2.57 1.78 0.12 188.86 157.12 32161 +1985 21 1.48 -4.52 -0.17 1.22 166.35 159.1 32289 +1985 22 1.89 -4.11 0.24 0.33 170.88 159.85 32419 +1985 23 -1.08 -7.08 -2.73 0 140.33 202.32 32552 +1985 24 -0.53 -6.53 -2.18 0 145.6 203.98 32688 +1985 25 0.02 -5.98 -1.63 0.26 151.05 164.38 32827 +1985 26 -1.86 -7.86 -3.51 0 133.14 208.09 32969 +1985 27 -1 -7 -2.65 0.07 141.09 167.59 33114 +1985 28 -2.5 -8.5 -4.15 0.01 127.48 169.61 33261 +1985 29 -6.83 -12.83 -8.48 0 94.38 216.35 33411 +1985 30 -4.74 -10.74 -6.39 0 109.28 217.73 33564 +1985 31 -1.98 -7.98 -3.63 0.09 132.07 174.46 33718 +1985 32 -0.01 -6.01 -1.66 0.2 150.74 175.72 33875 +1985 33 -0.08 -6.08 -1.73 0.19 150.04 178.08 34035 +1985 34 -1.35 -7.35 -3 0 137.81 226.35 34196 +1985 35 3.06 -2.94 1.41 0 184.4 225.46 34360 +1985 36 2.85 -3.15 1.2 0 181.9 227.59 34526 +1985 37 0.38 -5.62 -1.27 0 154.7 231.3 34694 +1985 38 0.23 -5.77 -1.42 0.29 153.17 185.34 34863 +1985 39 -1.69 -7.69 -3.34 0 134.68 237.38 35035 +1985 40 3.08 -2.92 1.43 0 184.64 236.67 35208 +1985 41 1.41 -4.59 -0.24 0.36 165.58 189.66 35383 +1985 42 -0.74 -6.74 -2.39 0.42 143.57 193.48 35560 +1985 43 3.25 -2.75 1.6 0.13 186.68 193.08 35738 +1985 44 4.24 -1.76 2.59 0 198.96 245.65 35918 +1985 45 4.54 -1.46 2.89 0 202.81 247.34 36099 +1985 46 4.7 -1.3 3.05 0 204.89 249.19 36282 +1985 47 -0.24 -6.24 -1.89 0.21 148.45 201.17 36466 +1985 48 -0.55 -6.55 -2.2 0 145.41 258.68 36652 +1985 49 -0.63 -6.63 -2.28 0 144.63 261.35 36838 +1985 50 -3.51 -9.51 -5.16 0 118.98 265.41 37026 +1985 51 -2.02 -8.02 -3.67 0.01 131.71 209.74 37215 +1985 52 -0.71 -6.71 -2.36 0.14 143.86 211.51 37405 +1985 53 1.39 -4.61 -0.26 0.64 165.37 212.4 37596 +1985 54 0.87 -5.13 -0.78 0.09 159.8 214.48 37788 +1985 55 -5.09 -11.09 -6.74 0 106.65 280.17 37981 +1985 56 -2.51 -8.51 -4.16 0 127.4 281.45 38175 +1985 57 -0.8 -6.8 -2.45 0 143 283.21 38370 +1985 58 -3.27 -9.27 -4.92 0 120.95 287.43 38565 +1985 59 -3.24 -9.24 -4.89 0 121.2 290 38761 +1985 60 6.22 0.22 4.57 0.07 225.61 222.3 38958 +1985 61 7.67 1.67 6.02 0.23 247.03 189.07 39156 +1985 62 6.7 0.7 5.05 0.06 232.52 191.96 39355 +1985 63 8.62 2.62 6.97 0 261.99 256.76 39553 +1985 64 4.04 -1.96 2.39 0.87 196.42 198.37 39753 +1985 65 5.54 -0.46 3.89 1.44 216.13 199.47 39953 +1985 66 2.27 -3.73 0.62 0.71 175.17 203.79 40154 +1985 67 2.28 -3.72 0.63 0.05 175.29 205.99 40355 +1985 68 0.21 -5.79 -1.44 0.03 152.96 209.38 40556 +1985 69 3.81 -2.19 2.16 0 193.54 278.86 40758 +1985 70 5.66 -0.34 4.01 0 217.78 279.88 40960 +1985 71 3.42 -2.58 1.77 0.15 188.74 213.78 41163 +1985 72 7.59 1.59 5.94 0 245.81 283.44 41366 +1985 73 9.03 3.03 7.38 0 268.69 284.26 41569 +1985 74 9.3 3.3 7.65 0 273.17 286.63 41772 +1985 75 11.49 5.49 9.84 1.91 312.01 214.57 41976 +1985 76 11.41 5.41 9.76 0 310.51 288.82 42179 +1985 77 6.38 0.38 4.73 0 227.89 298.3 42383 +1985 78 7.46 1.46 5.81 0 243.83 299.67 42587 +1985 79 5.41 -0.59 3.76 0 214.36 304.84 42791 +1985 80 8.82 2.82 7.17 0 265.24 303.14 42996 +1985 81 9.45 3.45 7.8 0 275.69 304.81 43200 +1985 82 10.38 4.38 8.73 0 291.77 306.06 43404 +1985 83 8.02 2.02 6.37 0 252.46 311.97 43608 +1985 84 5.11 -0.89 3.46 0.21 210.31 238.58 43812 +1985 85 2.56 -3.44 0.91 0 178.51 323.3 44016 +1985 86 3.98 -2.02 2.33 0 195.67 324.32 44220 +1985 87 9.5 3.5 7.85 0 276.54 319.84 44424 +1985 88 12.29 6.29 10.64 0 327.32 317.55 44627 +1985 89 12.82 6.82 11.17 0 337.82 318.82 44831 +1985 90 13.46 7.46 11.81 0 350.88 319.93 45034 +1985 91 19.06 13.06 17.41 0.12 484.77 231.78 45237 +1985 92 17.89 11.89 16.24 0 453.69 314.3 45439 +1985 93 18.81 12.81 17.16 0.5 477.98 235.49 45642 +1985 94 17.67 11.67 16.02 0.01 448.04 239.31 45843 +1985 95 15.34 9.34 13.69 0 391.77 326.78 46045 +1985 96 17.33 11.33 15.68 0.58 439.42 243.05 46246 +1985 97 17.37 11.37 15.72 0 440.43 325.95 46446 +1985 98 18.4 12.4 16.75 0 467.02 325.12 46647 +1985 99 17.38 11.38 15.73 0 440.68 329.78 46846 +1985 100 13.9 7.9 12.25 0 360.11 339.85 47045 +1985 101 13.62 7.62 11.97 0 354.21 342.35 47243 +1985 102 11.96 5.96 10.31 0 320.93 347.56 47441 +1985 103 12.47 6.47 10.82 0 330.86 348.41 47638 +1985 104 13.71 7.71 12.06 0 356.1 347.69 47834 +1985 105 11.65 5.65 10 0 315.02 353.6 48030 +1985 106 7.33 1.33 5.68 0 241.86 362.42 48225 +1985 107 7.34 1.34 5.69 0.07 242.01 273.08 48419 +1985 108 11.1 5.1 9.45 0 304.76 359.71 48612 +1985 109 12.06 6.06 10.41 0 322.85 359.5 48804 +1985 110 17.02 11.02 15.37 1.58 431.69 262.17 48995 +1985 111 12.36 6.36 10.71 0.38 328.69 271.4 49185 +1985 112 12.55 6.55 10.9 0.17 332.44 272.26 49374 +1985 113 10.44 4.44 8.79 0.06 292.83 276.3 49561 +1985 114 10.8 4.8 9.15 0 299.29 369.26 49748 +1985 115 12.85 6.85 11.2 0 338.42 366.66 49933 +1985 116 10.51 4.51 8.86 0 294.08 372.47 50117 +1985 117 12.4 6.4 10.75 0 329.48 370.14 50300 +1985 118 14.99 8.99 13.34 0 383.87 365.7 50481 +1985 119 11.72 5.72 10.07 0.14 316.34 280.52 50661 +1985 120 7.85 1.85 6.2 0.03 249.81 286.53 50840 +1985 121 12.55 6.55 10.9 0.04 332.44 281 51016 +1985 122 14.82 8.82 13.17 1.04 380.08 278.08 51191 +1985 123 18.29 12.29 16.64 0.58 464.12 271.91 51365 +1985 124 17.47 11.47 15.82 0 442.95 365.97 51536 +1985 125 14.85 8.85 13.2 0.4 380.74 280.35 51706 +1985 126 13.79 7.79 12.14 1.38 357.78 282.96 51874 +1985 127 19.47 13.47 17.82 0.04 496.08 272.09 52039 +1985 128 20.91 14.91 19.26 0.23 537.61 269.24 52203 +1985 129 14.6 8.6 12.95 0.51 375.22 283.6 52365 +1985 130 17.56 11.56 15.91 0.1 445.23 278.36 52524 +1985 131 18.6 12.6 16.95 0 472.34 368.86 52681 +1985 132 16.8 10.8 15.15 0.1 426.27 281.17 52836 +1985 133 18.06 12.06 16.41 0 458.09 371.99 52989 +1985 134 17.6 11.6 15.95 0.54 446.25 280.53 53138 +1985 135 20.17 14.17 18.52 0 515.92 366.72 53286 +1985 136 18.66 12.66 17.01 0 473.94 372.2 53430 +1985 137 19.98 13.98 18.33 0 510.47 368.67 53572 +1985 138 23.33 17.33 21.68 0 614.06 356.98 53711 +1985 139 23.95 17.95 22.3 0.68 635.06 266.33 53848 +1985 140 23.86 17.86 22.21 0.01 631.98 266.95 53981 +1985 141 21.71 15.71 20.06 0.6 561.93 273.57 54111 +1985 142 21.37 15.37 19.72 1.31 551.49 274.87 54238 +1985 143 16.83 10.83 15.18 0.24 427.01 286.12 54362 +1985 144 13.58 7.58 11.93 0.01 353.38 292.67 54483 +1985 145 18.68 12.68 17.03 0 474.48 376.99 54600 +1985 146 16.62 10.62 14.97 0 421.88 383.41 54714 +1985 147 19.21 13.21 17.56 0 488.88 376.16 54824 +1985 148 24.49 18.49 22.84 0.42 653.85 267.56 54931 +1985 149 24.38 18.38 22.73 0.28 649.98 268.14 55034 +1985 150 26.7 20.7 25.05 0 735.72 347.19 55134 +1985 151 27.07 21.07 25.42 0 750.24 345.74 55229 +1985 152 24.52 18.52 22.87 0.3 654.91 268.28 55321 +1985 153 24.89 18.89 23.24 0.88 668.07 267.24 55409 +1985 154 27.14 21.14 25.49 0.07 753.02 259.5 55492 +1985 155 27.57 21.57 25.92 0 770.25 344 55572 +1985 156 24.31 18.31 22.66 0 647.54 359.65 55648 +1985 157 23.97 17.97 22.32 0 635.75 361.26 55719 +1985 158 21.4 15.4 19.75 0.04 552.4 278.66 55786 +1985 159 18.63 12.63 16.98 0 473.14 381.17 55849 +1985 160 19.38 13.38 17.73 0.08 493.58 284.22 55908 +1985 161 18.49 12.49 16.84 0 469.41 381.86 55962 +1985 162 18.97 12.97 17.32 0.13 482.32 285.31 56011 +1985 163 22.61 16.61 20.96 0.3 590.41 275.78 56056 +1985 164 19.83 13.83 18.18 0.43 506.2 283.39 56097 +1985 165 21.33 15.33 19.68 0.37 550.27 279.52 56133 +1985 166 21.33 15.33 19.68 0 550.27 372.77 56165 +1985 167 19.59 13.59 17.94 0.33 499.44 284.08 56192 +1985 168 17.57 11.57 15.92 0.3 445.49 288.87 56214 +1985 169 17.38 11.38 15.73 0.72 440.68 289.3 56231 +1985 170 17.65 11.65 16 0.68 447.52 288.7 56244 +1985 171 11.69 5.69 10.04 0.47 315.78 299.9 56252 +1985 172 14.86 8.86 13.21 1.41 380.96 294.45 56256 +1985 173 15.26 9.26 13.61 0.33 389.95 293.68 56255 +1985 174 19.16 13.16 17.51 0.07 487.51 285.16 56249 +1985 175 20.37 14.37 18.72 0.1 521.7 282.11 56238 +1985 176 15.89 9.89 14.24 0 404.48 389.77 56223 +1985 177 16.01 10.01 14.36 0.05 407.3 292.01 56203 +1985 178 12.61 6.61 10.96 0 333.63 397.64 56179 +1985 179 14.26 8.26 12.61 0 367.81 393.72 56150 +1985 180 16.99 10.99 15.34 0.68 430.95 289.82 56116 +1985 181 14.39 8.39 12.74 1.73 370.63 294.91 56078 +1985 182 18.67 12.67 17.02 0 474.21 381.19 56035 +1985 183 20.77 14.77 19.12 0.26 533.45 280.51 55987 +1985 184 20.35 14.35 18.7 0.12 521.12 281.49 55935 +1985 185 20.12 14.12 18.47 0.21 514.48 282.02 55879 +1985 186 21.58 15.58 19.93 0.16 557.92 277.95 55818 +1985 187 17.61 11.61 15.96 0 446.5 383.54 55753 +1985 188 25.75 19.75 24.1 0.5 699.53 264.62 55684 +1985 189 21.92 15.92 20.27 0 568.47 368.7 55611 +1985 190 21.26 15.26 19.61 0.05 548.14 278.08 55533 +1985 191 22.52 16.52 20.87 0 587.51 365.78 55451 +1985 192 22.73 16.73 21.08 0.37 594.29 273.5 55366 +1985 193 21.32 15.32 19.67 1 549.96 277.29 55276 +1985 194 20.61 14.61 18.96 0.08 528.72 279.01 55182 +1985 195 22.98 16.98 21.33 0.36 602.46 272.19 55085 +1985 196 21.63 15.63 19.98 0.92 559.46 275.76 54984 +1985 197 26.48 20.48 24.83 0 727.2 346.75 54879 +1985 198 25.06 19.06 23.41 0.01 674.19 264.68 54770 +1985 199 22.96 16.96 21.31 0 601.8 361.39 54658 +1985 200 20.3 14.3 18.65 0 519.67 370.77 54542 +1985 201 23.31 17.31 21.66 0 613.39 359.14 54423 +1985 202 23.92 17.92 22.27 0 634.03 356.09 54301 +1985 203 27.56 21.56 25.91 0 769.85 338.85 54176 +1985 204 27.66 21.66 26.01 0 773.9 337.87 54047 +1985 205 29.21 23.21 27.56 0 839.06 329.17 53915 +1985 206 25.57 19.57 23.92 0 692.84 346.89 53780 +1985 207 26.76 20.76 25.11 0 738.06 340.69 53643 +1985 208 26.49 20.49 24.84 0 727.59 341.36 53502 +1985 209 26.49 20.49 24.84 0.55 727.59 255.56 53359 +1985 210 29.97 23.97 28.32 0 872.67 322.01 53213 +1985 211 26.09 20.09 24.44 0.38 712.3 255.97 53064 +1985 212 25.77 19.77 24.12 0 700.27 342 52913 +1985 213 27.65 21.65 26 0.32 773.49 249.22 52760 +1985 214 24.18 18.18 22.53 0.89 643.01 260.6 52604 +1985 215 22.48 16.48 20.83 2.33 586.22 265.16 52445 +1985 216 23.49 17.49 21.84 0 619.42 348.64 52285 +1985 217 21.89 15.89 20.24 0.15 567.53 265.4 52122 +1985 218 18.68 12.68 17.03 0.93 474.48 272.79 51958 +1985 219 20.87 14.87 19.22 0.03 536.42 266.71 51791 +1985 220 22.43 16.43 20.78 0 584.62 349.11 51622 +1985 221 24.54 18.54 22.89 0 655.61 339.8 51451 +1985 222 20.82 14.82 19.17 0.36 534.93 264.61 51279 +1985 223 20.27 14.27 18.62 0 518.8 353.52 51105 +1985 224 20.48 14.48 18.83 0.05 524.91 263.83 50929 +1985 225 17.6 11.6 15.95 0 446.25 359.4 50751 +1985 226 22.05 16.05 20.4 0.19 572.55 258.06 50572 +1985 227 22.1 16.1 20.45 0 574.13 342.64 50392 +1985 228 26.59 20.59 24.94 0.06 731.45 242.36 50210 +1985 229 25.35 19.35 23.7 0.88 684.74 245.61 50026 +1985 230 25.46 19.46 23.81 0.99 688.78 244.34 49842 +1985 231 23.85 17.85 22.2 0 631.63 330.99 49656 +1985 232 25.65 19.65 24 0 695.8 322.28 49469 +1985 233 25.62 19.62 23.97 0.26 694.69 240.8 49280 +1985 234 22.16 16.16 20.51 0 576.02 333.22 49091 +1985 235 21.36 15.36 19.71 1.38 551.18 250.89 48900 +1985 236 24.04 18.04 22.39 0 638.16 323.4 48709 +1985 237 20.39 14.39 18.74 0.66 522.29 250.99 48516 +1985 238 23.15 17.15 21.5 0.32 608.07 242.67 48323 +1985 239 24.95 18.95 23.3 0.3 670.22 236.36 48128 +1985 240 25.54 19.54 23.89 0.11 691.73 233.28 47933 +1985 241 24.52 18.52 22.87 1.1 654.91 235.15 47737 +1985 242 27.99 21.99 26.34 1.41 787.4 222.69 47541 +1985 243 26.85 20.85 25.2 0.23 741.58 225.3 47343 +1985 244 23.62 17.62 21.97 0 623.81 311.77 47145 +1985 245 22.6 16.6 20.95 0 590.08 313.65 46947 +1985 246 21.48 15.48 19.83 0 554.85 315.5 46747 +1985 247 19.6 13.6 17.95 0 499.72 319.47 46547 +1985 248 21.16 15.16 19.51 0.02 545.11 234.61 46347 +1985 249 20.56 14.56 18.91 0 527.26 312.66 46146 +1985 250 20.59 14.59 18.94 0 528.14 310.65 45945 +1985 251 20.35 14.35 18.7 0 521.12 309.3 45743 +1985 252 19.8 13.8 18.15 0 505.35 308.78 45541 +1985 253 22.1 16.1 20.45 0 574.13 299.67 45339 +1985 254 19.43 13.43 17.78 0.04 494.97 229.23 45136 +1985 255 19.49 13.49 17.84 0.43 496.64 227.43 44933 +1985 256 17.78 11.78 16.13 0.89 450.85 229.13 44730 +1985 257 16.09 10.09 14.44 0.06 409.18 230.52 44527 +1985 258 19.95 13.95 18.3 0 509.61 295.3 44323 +1985 259 18.91 12.91 17.26 0 480.69 295.74 44119 +1985 260 18.34 12.34 16.69 0.03 465.43 221.14 43915 +1985 261 17.65 11.65 16 0.01 447.52 220.6 43711 +1985 262 17.99 11.99 16.34 0.04 456.27 218.21 43507 +1985 263 18.65 12.65 17 0.1 473.68 215.16 43303 +1985 264 17.58 11.58 15.93 0.04 445.74 215.21 43099 +1985 265 18.37 12.37 16.72 0.04 466.23 212.03 42894 +1985 266 18.45 12.45 16.8 0 468.34 280.07 42690 +1985 267 16.43 10.43 14.78 0 417.29 282.07 42486 +1985 268 17.44 11.44 15.79 0 442.19 277.29 42282 +1985 269 19.84 13.84 18.19 0 506.48 268.98 42078 +1985 270 18.47 12.47 16.82 0.04 468.88 202.36 41875 +1985 271 21.12 15.12 19.47 1.62 543.91 195.35 41671 +1985 272 22.49 16.49 20.84 0.14 586.54 190.46 41468 +1985 273 20.34 14.34 18.69 0 520.83 257.49 41265 +1985 274 12.9 6.9 11.25 0 339.43 270.49 41062 +1985 275 11.81 5.81 10.16 0.11 318.06 202.09 40860 +1985 276 8.97 2.97 7.32 0 267.7 270.73 40658 +1985 277 10.15 4.15 8.5 0 287.72 266.44 40456 +1985 278 10.36 4.36 8.71 0 291.42 263.24 40255 +1985 279 16.02 10.02 14.37 0 407.53 251.11 40054 +1985 280 18.42 12.42 16.77 0 467.55 243.55 39854 +1985 281 19.29 13.29 17.64 0 491.09 238.96 39654 +1985 282 16.52 10.52 14.87 0 419.46 242.15 39455 +1985 283 14.46 8.46 12.81 0 372.15 243.11 39256 +1985 284 14.88 8.88 13.23 0 381.41 239.4 39058 +1985 285 17.64 11.64 15.99 0 447.27 231.62 38861 +1985 286 16.25 10.25 14.6 0 412.98 231.62 38664 +1985 287 14.89 8.89 13.24 0 381.63 231.13 38468 +1985 288 14.08 8.08 12.43 0.08 363.94 172.28 38273 +1985 289 15.8 9.8 14.15 0 402.38 224.22 38079 +1985 290 11.76 5.76 10.11 0 317.1 227.65 37885 +1985 291 13.29 7.29 11.64 0.2 347.37 167.09 37693 +1985 292 9.3 3.3 7.65 0 273.17 225.32 37501 +1985 293 7.96 1.96 6.31 0 251.52 224.03 37311 +1985 294 11.3 5.3 9.65 0 308.46 217.24 37121 +1985 295 12.87 6.87 11.22 0 338.83 212.31 36933 +1985 296 11.3 5.3 9.65 0 308.46 211.82 36745 +1985 297 12.99 6.99 11.34 0 341.25 206.87 36560 +1985 298 15.04 9.04 13.39 0.41 384.99 150.98 36375 +1985 299 14.74 8.74 13.09 0 378.3 199.03 36191 +1985 300 11.76 5.76 10.11 0 317.1 200.49 36009 +1985 301 9.18 3.18 7.53 0.11 271.17 150.7 35829 +1985 302 10.58 4.58 8.93 0 295.33 196.78 35650 +1985 303 10.83 4.83 9.18 0 299.83 193.92 35472 +1985 304 13.88 7.88 12.23 0 359.69 187.66 35296 +1985 305 1.08 -4.92 -0.57 0 162.03 196.92 35122 +1985 306 5.45 -0.55 3.8 0.2 214.9 143.69 34950 +1985 307 2.71 -3.29 1.06 0.37 180.26 143.27 34779 +1985 308 1.83 -4.17 0.18 0.25 170.21 141.69 34610 +1985 309 1.61 -4.39 -0.04 0.13 167.77 140.02 34444 +1985 310 3.16 -2.84 1.51 1.24 185.59 137.42 34279 +1985 311 0.93 -5.07 -0.72 2.3 160.43 136.77 34116 +1985 312 6.76 0.76 5.11 0.23 233.39 131.78 33956 +1985 313 5.4 -0.6 3.75 0.05 214.22 130.97 33797 +1985 314 8.56 2.56 6.91 0.62 261.02 127.56 33641 +1985 315 9.19 3.19 7.54 0.09 271.34 125.24 33488 +1985 316 9 3 7.35 0 268.19 164.98 33337 +1985 317 9.89 3.89 8.24 0.46 283.2 121.48 33188 +1985 318 8.2 2.2 6.55 0 255.28 161.17 33042 +1985 319 3.8 -2.2 2.15 0 193.42 162.71 32899 +1985 320 8.67 2.67 7.02 0 262.8 157.22 32758 +1985 321 9.84 3.84 8.19 0.94 282.34 115.56 32620 +1985 322 8.11 2.11 6.46 0 253.87 153.78 32486 +1985 323 4.93 -1.07 3.28 0.19 207.92 115.88 32354 +1985 324 3.52 -2.48 1.87 0.07 189.96 115 32225 +1985 325 5.31 -0.69 3.66 1.56 213 112.85 32100 +1985 326 1.83 -4.17 0.18 0.61 170.21 113.3 31977 +1985 327 4.43 -1.57 2.78 2.37 201.39 110.78 31858 +1985 328 3.59 -2.41 1.94 0.06 190.82 109.68 31743 +1985 329 7.45 1.45 5.8 0.46 243.67 106.64 31631 +1985 330 2.83 -3.17 1.18 0.23 181.67 107.78 31522 +1985 331 8.87 2.87 7.22 0 266.06 138.35 31417 +1985 332 7.93 1.93 6.28 0 251.05 137.45 31316 +1985 333 11.87 5.87 10.22 0.8 319.2 99.78 31218 +1985 334 11.9 5.9 10.25 0 319.78 131.94 31125 +1985 335 12.13 6.13 10.48 0 324.21 130.58 31035 +1985 336 9.15 3.15 7.5 0 270.67 132.13 30949 +1985 337 10.9 4.9 9.25 0 301.11 129.03 30867 +1985 338 14.93 8.93 13.28 0 382.52 124.11 30790 +1985 339 16.18 10.18 14.53 0 411.32 121.92 30716 +1985 340 17.31 11.31 15.66 0.46 438.92 89.88 30647 +1985 341 16.01 10.01 14.36 0.09 407.3 90.42 30582 +1985 342 15.19 9.19 13.54 0.08 388.37 90.58 30521 +1985 343 12.02 6.02 10.37 0 322.08 123.18 30465 +1985 344 10.72 4.72 9.07 0 297.85 123.21 30413 +1985 345 9.87 3.87 8.22 0.06 282.86 92.62 30366 +1985 346 11.8 5.8 10.15 0 317.87 121.32 30323 +1985 347 7.36 1.36 5.71 0.01 242.31 93.16 30284 +1985 348 7.67 1.67 6.02 0.19 247.03 92.74 30251 +1985 349 7.14 1.14 5.49 0 239.01 123.64 30221 +1985 350 7.72 1.72 6.07 0.2 247.8 92.19 30197 +1985 351 2.2 -3.8 0.55 0 174.37 125.9 30177 +1985 352 0.03 -5.97 -1.62 0 151.15 126.78 30162 +1985 353 -1.51 -7.51 -3.16 0 136.33 127.32 30151 +1985 354 -4.42 -10.42 -6.07 1.71 111.74 145.44 30145 +1985 355 -2.98 -8.98 -4.63 0.5 123.38 146.68 30144 +1985 356 -2.2 -8.2 -3.85 0 130.11 178.38 30147 +1985 357 1.31 -4.69 -0.34 0 164.5 176.84 30156 +1985 358 1.85 -4.15 0.2 0 170.43 176.41 30169 +1985 359 1.84 -4.16 0.19 0 170.32 176.26 30186 +1985 360 3.93 -2.07 2.28 0.43 195.04 143.64 30208 +1985 361 4.51 -1.49 2.86 0.89 202.42 143 30235 +1985 362 5.69 -0.31 4.04 0 218.19 173.31 30267 +1985 363 7.16 1.16 5.51 0 239.31 171.94 30303 +1985 364 9.51 3.51 7.86 0 276.71 169.3 30343 +1985 365 9.58 3.58 7.93 0 277.89 168.47 30388 +1986 1 6.43 0.43 4.78 0 228.61 170.67 30438 +1986 2 5.06 -0.94 3.41 0 209.65 128.78 30492 +1986 3 6.07 0.07 4.42 0.06 223.49 96.82 30551 +1986 4 5.07 -0.93 3.42 0.05 209.78 97.97 30614 +1986 5 2.44 -3.56 0.79 0.26 177.12 99.54 30681 +1986 6 0.77 -5.23 -0.88 0 158.75 134.41 30752 +1986 7 -0.29 -6.29 -1.94 0 147.96 135.68 30828 +1986 8 1.47 -4.53 -0.18 0.71 166.24 102.29 30907 +1986 9 -0.65 -6.65 -2.3 0 144.44 138.6 30991 +1986 10 0.19 -5.81 -1.46 0 152.76 139.55 31079 +1986 11 1.24 -4.76 -0.41 0 163.74 140.06 31171 +1986 12 0.75 -5.25 -0.9 0.07 158.54 105.98 31266 +1986 13 0.79 -5.21 -0.86 0 158.96 142.92 31366 +1986 14 0.62 -5.38 -1.03 0 157.18 144.49 31469 +1986 15 4.67 -1.33 3.02 0 204.5 143.74 31575 +1986 16 4.3 -1.7 2.65 0.07 199.72 108.94 31686 +1986 17 0.1 -5.9 -1.55 0 151.85 149.18 31800 +1986 18 1.3 -4.7 -0.35 0.18 164.39 112.88 31917 +1986 19 2.1 -3.9 0.45 0 173.24 152.03 32038 +1986 20 1.85 -4.15 0.2 0 170.43 153.76 32161 +1986 21 0.68 -5.32 -0.97 0.46 157.8 117.29 32289 +1986 22 0.93 -5.07 -0.72 0 160.43 158.02 32419 +1986 23 2.79 -3.21 1.14 0.08 181.2 119.09 32552 +1986 24 4.49 -1.51 2.84 0 202.16 159.8 32688 +1986 25 2.77 -3.23 1.12 0.25 180.96 122.07 32827 +1986 26 3.64 -2.36 1.99 0 191.43 164.16 32969 +1986 27 9.7 3.7 8.05 0 279.94 161.45 33114 +1986 28 9.81 3.81 8.16 0 281.82 163.52 33261 +1986 29 9.63 3.63 7.98 0.32 278.74 124.52 33411 +1986 30 9.16 3.16 7.51 0.15 270.84 126.51 33564 +1986 31 8.71 2.71 7.06 1.17 263.45 128.57 33718 +1986 32 -1.77 -7.77 -3.42 0.89 133.96 176.89 33875 +1986 33 2.35 -3.65 0.7 0.34 176.09 176.75 34035 +1986 34 -2.47 -8.47 -4.12 1.12 127.74 183.29 34196 +1986 35 -3.19 -9.19 -4.84 0.25 121.62 185.65 34360 +1986 36 -2.69 -8.69 -4.34 1.04 125.84 190.08 34526 +1986 37 -4.82 -10.82 -6.47 0 108.68 240.86 34694 +1986 38 -2.75 -8.75 -4.4 0.06 125.33 193.74 34863 +1986 39 -4.69 -10.69 -6.34 0 109.66 245.96 35035 +1986 40 -4.3 -10.3 -5.95 0 112.67 248.23 35208 +1986 41 0.32 -5.68 -1.33 0 154.09 248.34 35383 +1986 42 0.15 -5.85 -1.5 0 152.36 250.77 35560 +1986 43 3.51 -2.49 1.86 0 189.84 250.68 35738 +1986 44 2.41 -3.59 0.76 0.01 176.78 201.35 35918 +1986 45 1.47 -4.53 -0.18 0 166.24 256.43 36099 +1986 46 1.74 -4.26 0.09 0.41 169.21 204.89 36282 +1986 47 -0.14 -6.14 -1.79 0.01 149.44 207.72 36466 +1986 48 -0.74 -6.74 -2.39 0.05 143.57 210.03 36652 +1986 49 -1.92 -7.92 -3.57 0 132.6 268.74 36838 +1986 50 -0.7 -6.7 -2.35 0 143.96 270.54 37026 +1986 51 -0.57 -6.57 -2.22 0.16 145.22 216.1 37215 +1986 52 -1.1 -7.1 -2.75 0 140.15 276.62 37405 +1986 53 -0.86 -6.86 -2.51 0.11 142.42 220.47 37596 +1986 54 -1.72 -7.72 -3.37 0 134.41 282.63 37788 +1986 55 -0.99 -6.99 -2.64 0.18 141.19 224.93 37981 +1986 56 -0.88 -6.88 -2.53 0 142.23 287.93 38175 +1986 57 -4.88 -10.88 -6.53 0 108.22 292.8 38370 +1986 58 -1.02 -7.02 -2.67 0 140.9 293.49 38565 +1986 59 -2.38 -8.38 -4.03 0 128.53 296.84 38761 +1986 60 7.49 1.49 5.84 0 244.28 290.78 38958 +1986 61 8.95 2.95 7.3 0.03 267.37 228.22 39156 +1986 62 9.21 3.21 7.56 0 271.67 292.17 39355 +1986 63 7.49 1.49 5.84 0 244.28 296.25 39553 +1986 64 7.95 1.95 6.3 0 251.36 297.62 39753 +1986 65 7.69 1.69 6.04 0 247.34 299.84 39953 +1986 66 7.49 1.49 5.84 0.05 244.28 235.22 40154 +1986 67 3.21 -2.79 1.56 0.44 186.2 240.17 40355 +1986 68 2.58 -3.42 0.93 1.01 178.74 242.33 40556 +1986 69 4.03 -1.97 2.38 0.83 196.29 242.77 40758 +1986 70 2.98 -3.02 1.33 0 183.44 315.81 40960 +1986 71 3.78 -2.22 2.13 0 193.17 317.49 41163 +1986 72 3.12 -2.88 1.47 0 185.11 320.49 41366 +1986 73 3.59 -2.41 1.94 0 190.82 322.25 41569 +1986 74 3.27 -2.73 1.62 0 186.92 293.52 41772 +1986 75 7.79 1.79 6.14 0.02 248.88 218.5 41976 +1986 76 9.3 3.3 7.65 0.02 273.17 218.97 42179 +1986 77 4.5 -1.5 2.85 0.14 202.29 225.28 42383 +1986 78 2.5 -3.5 0.85 0.12 177.82 228.76 42587 +1986 79 0.45 -5.55 -1.2 0 155.42 309.55 42791 +1986 80 5.61 -0.39 3.96 0 217.09 307.18 42996 +1986 81 6.65 0.65 5 0 231.79 308.55 43200 +1986 82 10.29 4.29 8.64 0 290.18 306.2 43404 +1986 83 7.69 1.69 6.04 0 247.34 312.41 43608 +1986 84 12.8 6.8 11.15 0 337.42 306.96 43812 +1986 85 10.5 4.5 8.85 0 293.9 313.35 44016 +1986 86 9.06 3.06 7.41 0 269.18 317.96 44220 +1986 87 7.63 1.63 5.98 0 246.42 322.51 44424 +1986 88 4.14 -1.86 2.49 0 197.68 329.11 44627 +1986 89 4.86 -1.14 3.21 0.03 206.99 247.97 44831 +1986 90 7.96 1.96 6.31 0 251.52 329.1 45034 +1986 91 14.46 8.46 12.81 0.25 372.15 240.09 45237 +1986 92 13.39 7.39 11.74 0.37 349.43 243.37 45439 +1986 93 13.93 7.93 12.28 0.18 360.75 244.19 45642 +1986 94 14.56 8.56 12.91 0 374.34 326.39 45843 +1986 95 15.48 9.48 13.83 0 394.97 326.46 46045 +1986 96 15.93 9.93 14.28 0 405.42 327.49 46246 +1986 97 16.84 10.84 15.19 0 427.25 327.29 46446 +1986 98 17.17 11.17 15.52 0 435.41 328.37 46647 +1986 99 13.9 7.9 12.25 0.27 360.11 253.45 46846 +1986 100 13.5 7.5 11.85 0 351.71 340.69 47045 +1986 101 16.01 10.01 14.36 0 407.3 336.99 47243 +1986 102 16.62 10.62 14.97 0 421.88 337.35 47441 +1986 103 17.32 11.32 15.67 0 439.17 337.35 47638 +1986 104 15.37 9.37 13.72 0 392.46 343.98 47834 +1986 105 13.87 7.87 12.22 0.02 359.47 261.84 48030 +1986 106 9.97 3.97 8.32 0.1 284.59 268.7 48225 +1986 107 9.95 3.95 8.3 0.32 284.24 270 48419 +1986 108 9.07 3.07 7.42 0 269.35 363.22 48612 +1986 109 7.94 1.94 6.29 0 251.21 366.63 48804 +1986 110 9.43 3.43 7.78 0 275.36 365.69 48995 +1986 111 14.97 8.97 13.32 0 383.42 356.19 49185 +1986 112 15.49 9.49 13.84 0 395.2 356.45 49374 +1986 113 17.91 11.91 16.26 0.04 454.2 263.58 49561 +1986 114 18.69 12.69 17.04 0.06 474.75 262.98 49748 +1986 115 15.6 9.6 13.95 0.73 397.74 270.3 49933 +1986 116 13.28 7.28 11.63 0.19 347.17 275.23 50117 +1986 117 14.9 8.9 13.25 0 381.86 364.61 50300 +1986 118 17.12 11.12 15.47 0.03 434.17 270.19 50481 +1986 119 17.7 11.7 16.05 0 448.8 359.81 50661 +1986 120 18.47 12.47 16.82 0 468.88 358.73 50840 +1986 121 25.7 19.7 24.05 0.33 697.66 250.01 51016 +1986 122 18.73 12.73 17.08 0.08 475.82 270.17 51191 +1986 123 16.93 10.93 15.28 0.3 429.47 274.8 51365 +1986 124 15.83 9.83 14.18 0 403.08 370.37 51536 +1986 125 20.03 14.03 18.38 0 511.9 359.15 51706 +1986 126 19.18 13.18 17.53 0 488.06 362.84 51874 +1986 127 15.39 9.39 13.74 0.16 392.91 280.76 52039 +1986 128 18.61 12.61 16.96 0 472.61 366.44 52203 +1986 129 18.34 12.34 16.69 0.02 465.43 276.06 52365 +1986 130 18.47 12.47 16.82 0.1 468.88 276.36 52524 +1986 131 22.39 16.39 20.74 0.06 583.34 266.98 52681 +1986 132 23.9 17.9 22.25 0 633.35 350.8 52836 +1986 133 27.04 21.04 25.39 0 749.06 337.35 52989 +1986 134 28.1 22.1 26.45 0.08 791.95 249.49 53138 +1986 135 26.47 20.47 24.82 0.06 726.82 256.05 53286 +1986 136 25.64 19.64 23.99 0.04 695.43 259.39 53430 +1986 137 22.97 16.97 21.32 0.59 602.13 268.37 53572 +1986 138 20.77 14.77 19.12 0 533.45 366.57 53711 +1986 139 20.13 14.13 18.48 0 514.76 369.43 53848 +1986 140 22.45 16.45 20.8 0.78 585.26 271.17 53981 +1986 141 21.77 15.77 20.12 0 563.79 364.54 54111 +1986 142 21.37 15.37 19.72 0.01 551.49 274.87 54238 +1986 143 24.03 18.03 22.38 0.58 637.82 267.47 54362 +1986 144 19.16 13.16 17.51 1.01 487.51 281.25 54483 +1986 145 17.44 11.44 15.79 0.72 442.19 285.53 54600 +1986 146 17.75 11.75 16.1 0.29 450.08 285.13 54714 +1986 147 18.72 12.72 17.07 0.88 475.56 283.28 54824 +1986 148 18.71 12.71 17.06 0.09 475.29 283.59 54931 +1986 149 17.65 11.65 16 0.4 447.52 286.24 55034 +1986 150 17.15 11.15 15.5 0.28 434.92 287.57 55134 +1986 151 12.41 6.41 10.76 0.01 329.68 296.73 55229 +1986 152 16.26 10.26 14.61 0 413.22 386.42 55321 +1986 153 20.76 14.76 19.11 0 533.15 372.69 55409 +1986 154 21.32 15.32 19.67 0.02 549.96 278.25 55492 +1986 155 21.1 15.1 19.45 0 543.31 371.98 55572 +1986 156 22.33 16.33 20.68 0 581.42 367.72 55648 +1986 157 22.58 16.58 20.93 0 589.44 366.91 55719 +1986 158 21.37 15.37 19.72 0.04 551.49 278.74 55786 +1986 159 23.1 17.1 21.45 0.01 606.42 273.94 55849 +1986 160 23.49 17.49 21.84 0.97 619.42 272.88 55908 +1986 161 23.46 17.46 21.81 1.33 618.41 273.02 55962 +1986 162 27.17 21.17 25.52 0.21 754.21 260.38 56011 +1986 163 25.51 19.51 23.86 0.48 690.62 266.53 56056 +1986 164 25.45 19.45 23.8 0.03 688.41 266.77 56097 +1986 165 24.92 18.92 23.27 0.64 669.14 268.63 56133 +1986 166 20.94 14.94 19.29 2.03 538.51 280.64 56165 +1986 167 21.02 15.02 19.37 0.47 540.9 280.38 56192 +1986 168 21.01 15.01 19.36 0.26 540.6 280.47 56214 +1986 169 18.32 12.32 16.67 1.25 464.91 287.19 56231 +1986 170 18.66 12.66 17.01 0 473.94 381.86 56244 +1986 171 18.33 12.33 16.68 0 465.17 382.94 56252 +1986 172 19.46 13.46 17.81 0 495.8 379.34 56256 +1986 173 19.94 13.94 18.29 0 509.33 377.72 56255 +1986 174 22.55 16.55 20.9 0 588.47 368.14 56249 +1986 175 19.46 13.46 17.81 0.1 495.8 284.41 56238 +1986 176 17.34 11.34 15.69 1.81 439.67 289.3 56223 +1986 177 14.93 8.93 13.28 0.49 382.52 294.11 56203 +1986 178 13.73 7.73 12.08 0 356.52 395.09 56179 +1986 179 18 12 16.35 0 456.53 383.59 56150 +1986 180 17.47 11.47 15.82 0.29 442.95 288.78 56116 +1986 181 17.68 11.68 16.03 0 448.29 384.35 56078 +1986 182 18.87 12.87 17.22 0.27 479.6 285.42 56035 +1986 183 19 13 17.35 0 483.13 379.96 55987 +1986 184 18.86 12.86 17.21 0.03 479.33 285.19 55935 +1986 185 19.58 13.58 17.93 0 499.16 377.84 55879 +1986 186 25.4 19.4 23.75 0 686.58 354.87 55818 +1986 187 20.67 14.67 19.02 0 530.49 373.69 55753 +1986 188 23.45 17.45 21.8 0 618.08 362.87 55684 +1986 189 18.05 12.05 16.4 0 457.83 381.77 55611 +1986 190 20.86 14.86 19.21 0.7 536.12 279.15 55533 +1986 191 24.77 18.77 23.12 1.81 663.78 267.35 55451 +1986 192 22.01 16.01 20.36 0 571.29 367.43 55366 +1986 193 25.68 19.68 24.03 0 696.92 351.81 55276 +1986 194 25.92 19.92 24.27 0 705.89 350.49 55182 +1986 195 24.59 18.59 22.94 0.22 657.38 267.17 55085 +1986 196 24.66 18.66 23.01 0.99 659.86 266.64 54984 +1986 197 25.72 19.72 24.07 0.23 698.41 262.75 54879 +1986 198 21.64 15.64 19.99 0.33 559.77 275.08 54770 +1986 199 19.41 13.41 17.76 0 494.41 374.13 54658 +1986 200 23.85 17.85 22.2 0.04 631.63 268.04 54542 +1986 201 24.98 18.98 23.33 0.05 671.3 264.07 54423 +1986 202 24.73 18.73 23.08 0 662.35 352.64 54301 +1986 203 26.28 20.28 24.63 0.76 719.53 258.84 54176 +1986 204 24.32 18.32 22.67 0.07 647.88 265.07 54047 +1986 205 23.59 17.59 21.94 0 622.79 355.96 53915 +1986 206 27.49 21.49 25.84 0.01 767.02 253.29 53780 +1986 207 20.59 14.59 18.94 0.42 528.14 274.5 53643 +1986 208 22.5 16.5 20.85 0.29 586.86 268.82 53502 +1986 209 18.38 12.38 16.73 0.76 466.49 278.86 53359 +1986 210 14.77 8.77 13.12 0.41 378.97 285.75 53213 +1986 211 17.53 11.53 15.88 0 444.47 372.89 53064 +1986 212 21.27 15.27 19.62 0.11 548.44 270.1 52913 +1986 213 27.41 21.41 25.76 0.09 763.8 250.12 52760 +1986 214 26.73 20.73 25.08 0.64 736.89 252.07 52604 +1986 215 27.38 21.38 25.73 0 762.6 332.31 52445 +1986 216 27.23 21.23 25.58 1.04 756.6 249.06 52285 +1986 217 28.23 22.23 26.58 0 797.35 326.24 52122 +1986 218 31.16 25.16 29.51 0 927.56 309.2 51958 +1986 219 26.45 20.45 24.8 0.01 726.05 249.91 51791 +1986 220 29.01 23.01 27.36 0 830.4 319.56 51622 +1986 221 26.47 20.47 24.82 0.22 726.82 248.46 51451 +1986 222 29.08 23.08 27.43 0.92 833.43 237.98 51279 +1986 223 23.9 17.9 22.25 0.51 633.35 255.23 51105 +1986 224 24.93 18.93 23.28 0 669.5 335.03 50929 +1986 225 25.45 19.45 23.8 1.21 688.41 248.77 50751 +1986 226 27.49 21.49 25.84 0.5 767.02 240.93 50572 +1986 227 21.06 15.06 19.41 0.1 542.1 259.71 50392 +1986 228 21.31 15.31 19.66 0.78 549.66 258.17 50210 +1986 229 21.25 15.25 19.6 0.87 547.84 257.4 50026 +1986 230 19.79 13.79 18.14 1.01 505.07 260.04 49842 +1986 231 16.72 10.72 15.07 0.67 424.32 265.53 49656 +1986 232 18.27 12.27 16.62 1.84 463.59 261.33 49469 +1986 233 21.78 15.78 20.13 1.8 564.11 251.96 49280 +1986 234 24.05 18.05 22.4 0.12 638.51 244.62 49091 +1986 235 22.19 16.19 20.54 0.4 576.97 248.74 48900 +1986 236 22.37 16.37 20.72 0.55 582.7 247.22 48709 +1986 237 25.9 19.9 24.25 0.42 705.14 235.65 48516 +1986 238 22.57 16.57 20.92 0 589.12 325.67 48323 +1986 239 22.17 16.17 20.52 0 576.34 325.61 48128 +1986 240 20.26 14.26 18.61 0 518.51 330.17 47933 +1986 241 19.76 13.76 18.11 0.02 504.22 247.49 47737 +1986 242 15.21 9.21 13.56 0.7 388.82 255.2 47541 +1986 243 15.38 9.38 13.73 0.05 392.69 253.48 47343 +1986 244 9.15 3.15 7.5 0.02 270.67 261.07 47145 +1986 245 10.93 4.93 9.28 0 301.65 343.21 46947 +1986 246 14.19 8.19 12.54 0.19 366.3 251.16 46747 +1986 247 11.74 5.74 10.09 0 316.72 337.81 46547 +1986 248 11.26 5.26 9.61 0 307.72 336.66 46347 +1986 249 17.77 11.77 16.12 0 450.6 320.51 46146 +1986 250 13.36 7.36 11.71 0 348.81 328.59 45945 +1986 251 13 7 11.35 0 341.45 327.13 45743 +1986 252 16.75 10.75 15.1 0 425.05 316.82 45541 +1986 253 18.53 12.53 16.88 0 470.47 310.2 45339 +1986 254 19.38 13.38 17.73 0.89 493.58 229.33 45136 +1986 255 14.58 8.58 12.93 0 374.78 315.12 44933 +1986 256 19.39 13.39 17.74 0 493.86 301.29 44730 +1986 257 21.68 15.68 20.03 0.42 561.01 219.36 44527 +1986 258 17.38 11.38 15.73 0 440.68 302.01 44323 +1986 259 19.18 13.18 17.53 0 488.06 295.02 44119 +1986 260 19.87 13.87 18.22 0 507.33 290.81 43915 +1986 261 21.73 15.73 20.08 0 562.55 283.03 43711 +1986 262 21.35 15.35 19.7 0 550.88 281.88 43507 +1986 263 24.54 18.54 22.89 0 655.61 269.22 43303 +1986 264 23.45 17.45 21.8 0 618.08 270.49 43099 +1986 265 22.36 16.36 20.71 0.05 582.38 203.78 42894 +1986 266 22.67 16.67 21.02 0.23 592.35 201.29 42690 +1986 267 23.27 17.27 21.62 0.46 612.06 197.96 42486 +1986 268 23.22 17.22 21.57 0.47 610.39 196.26 42282 +1986 269 24.33 18.33 22.68 0.86 648.23 191.77 42078 +1986 270 20.82 14.82 19.17 0 534.93 263.81 41875 +1986 271 22.32 16.32 20.67 0 581.1 257.04 41671 +1986 272 22.36 16.36 20.71 0 582.38 254.33 41468 +1986 273 21.91 15.91 20.26 0 568.16 253.22 41265 +1986 274 14.67 8.67 13.02 0.01 376.76 200.53 41062 +1986 275 14.13 8.13 12.48 0 365.02 265.6 40860 +1986 276 11.71 5.71 10.06 0 316.16 266.88 40658 +1986 277 12.39 6.39 10.74 0 329.28 263.13 40456 +1986 278 14.05 8.05 12.4 0.14 363.3 193.13 40255 +1986 279 13.2 7.2 11.55 0.16 345.53 192.09 40054 +1986 280 9.72 3.72 8.07 0.26 280.28 193.91 39854 +1986 281 10.01 4.01 8.36 0 285.28 255.41 39654 +1986 282 9.31 3.31 7.66 0 273.34 253.53 39455 +1986 283 11.75 5.75 10.1 0 316.91 247.38 39256 +1986 284 16.4 10.4 14.75 0 416.57 236.64 39058 +1986 285 14.71 8.71 13.06 0.69 377.64 177.8 38861 +1986 286 13.48 7.48 11.83 0 351.3 236.34 38664 +1986 287 16.11 10.11 14.46 0 409.66 228.99 38468 +1986 288 16.98 10.98 15.33 2.42 430.7 168.48 38273 +1986 289 18.78 12.78 17.13 1.56 477.17 163.88 38079 +1986 290 15.12 9.12 13.47 0 386.79 222.57 37885 +1986 291 12.75 6.75 11.1 0.21 336.42 167.68 37693 +1986 292 11.96 5.96 10.31 0 320.93 221.99 37501 +1986 293 12.5 6.5 10.85 0.09 331.45 163.89 37311 +1986 294 10.13 4.13 8.48 0.07 287.37 164.02 37121 +1986 295 12.27 6.27 10.62 0 326.93 213.14 36933 +1986 296 12.59 6.59 10.94 0 333.23 210.13 36745 +1986 297 12.41 6.41 10.76 0.32 329.68 155.75 36560 +1986 298 12.09 6.09 10.44 0.1 323.43 154.12 36375 +1986 299 19.87 13.87 18.22 0 507.33 190.01 36191 +1986 300 19.39 13.39 17.74 0.28 493.86 141.32 36009 +1986 301 19 13 17.35 0.2 483.13 140.09 35829 +1986 302 17.03 11.03 15.38 0.09 431.94 140.84 35650 +1986 303 11.32 5.32 9.67 0 308.83 193.35 35472 +1986 304 14 8 12.35 0 362.24 187.5 35296 +1986 305 11.66 5.66 10.01 0.31 315.21 140.83 35122 +1986 306 10.3 4.3 8.65 0 290.36 187.08 34950 +1986 307 9.11 3.11 7.46 0 270.01 185.8 34779 +1986 308 6.94 0.94 5.29 0 236.04 185.19 34610 +1986 309 5.95 -0.05 4.3 0 221.81 183.68 34444 +1986 310 6.02 0.02 4.37 0 222.79 181.16 34279 +1986 311 8.63 2.63 6.98 0 262.15 176.72 34116 +1986 312 11.31 5.31 9.66 0 308.64 171.4 33956 +1986 313 7.25 1.25 5.6 0.1 240.65 129.88 33797 +1986 314 11.08 5.08 9.43 0 304.4 167.63 33641 +1986 315 9.09 3.09 7.44 0 269.68 167.07 33488 +1986 316 7.85 1.85 6.2 0 249.81 165.99 33337 +1986 317 5.05 -0.95 3.4 0.03 209.51 124.46 33188 +1986 318 4.18 -1.82 2.53 0.18 198.19 123.14 33042 +1986 319 4.59 -1.41 2.94 0 203.46 162.2 32899 +1986 320 8.29 2.29 6.64 0 256.71 157.54 32758 +1986 321 5.31 -0.69 3.66 1.1 213 118.28 32620 +1986 322 2.76 -3.24 1.11 0.16 180.85 118.11 32486 +1986 323 3.14 -2.86 1.49 0 185.35 155.62 32354 +1986 324 3.1 -2.9 1.45 0.13 184.88 115.18 32225 +1986 325 6.61 0.61 4.96 0.11 231.21 112.17 32100 +1986 326 8.03 2.03 6.38 0.41 252.61 110.27 31977 +1986 327 8.01 2.01 6.36 0 252.3 145.21 31858 +1986 328 9.35 3.35 7.7 0 274.01 142.17 31743 +1986 329 9.71 3.71 8.06 0 280.11 140.38 31631 +1986 330 12.33 6.33 10.68 0 328.11 136.53 31522 +1986 331 14.17 8.17 12.52 0 365.87 133.32 31417 +1986 332 13.49 7.49 11.84 0 351.51 132.46 31316 +1986 333 15.2 9.2 13.55 0 388.59 129.52 31218 +1986 334 12.86 6.86 11.21 0 338.63 131 31125 +1986 335 6.5 0.5 4.85 0 229.62 135.14 31035 +1986 336 6.18 0.18 4.53 0 225.05 134.28 30949 +1986 337 4.25 -1.75 2.6 0 199.08 133.81 30867 +1986 338 5.26 -0.74 3.61 0 212.33 132.27 30790 +1986 339 8.06 2.06 6.41 0 253.08 129.61 30716 +1986 340 9.13 3.13 7.48 0.03 270.34 96.06 30647 +1986 341 6.39 0.39 4.74 0 228.04 129.12 30582 +1986 342 10.93 4.93 9.28 0 301.65 124.96 30521 +1986 343 9.64 3.64 7.99 0 278.91 125.21 30465 +1986 344 9.61 3.61 7.96 0.93 278.4 93.09 30413 +1986 345 5.29 -0.71 3.64 0.85 212.73 95 30366 +1986 346 1.75 -4.25 0.1 0.34 169.32 96 30323 +1986 347 -0.93 -6.93 -2.58 0 141.76 128.56 30284 +1986 348 0.7 -5.3 -0.95 0.61 158.01 95.65 30251 +1986 349 -4.89 -10.89 -6.54 0 108.15 129.17 30221 +1986 350 -3.65 -9.65 -5.3 0.21 117.84 140.72 30197 +1986 351 -7.27 -13.27 -8.92 0.12 91.48 141.73 30177 +1986 352 -7.57 -13.57 -9.22 0.21 89.54 142.41 30162 +1986 353 -0.93 -6.93 -2.58 0 141.76 172.6 30151 +1986 354 0.78 -5.22 -0.87 0 158.85 171.76 30145 +1986 355 1.36 -4.64 -0.29 0 165.04 171.32 30144 +1986 356 -4.46 -10.46 -6.11 0 111.43 173.53 30147 +1986 357 -5.09 -11.09 -6.74 0 106.65 173.76 30156 +1986 358 -2.04 -8.04 -3.69 0 131.53 172.84 30169 +1986 359 1.45 -4.55 -0.2 0 166.02 171.32 30186 +1986 360 3.06 -2.94 1.41 0.36 184.4 138.98 30208 +1986 361 5.1 -0.9 3.45 0 210.18 168.96 30235 +1986 362 0.44 -5.56 -1.21 0 155.32 171.65 30267 +1986 363 4.9 -1.1 3.25 0 207.52 126.29 30303 +1986 364 5.14 -0.86 3.49 0.06 210.72 94.91 30343 +1986 365 1.44 -4.56 -0.21 0 165.91 129.06 30388 +1987 1 2.17 -3.83 0.52 0 174.03 129.6 30438 +1987 2 1.34 -4.66 -0.31 0 164.82 130.74 30492 +1987 3 -1.97 -7.97 -3.62 0 132.16 133.07 30551 +1987 4 -0.6 -6.6 -2.25 0 144.92 133.45 30614 +1987 5 0.61 -5.39 -1.04 0.03 157.08 100.19 30681 +1987 6 1.67 -4.33 0.02 0.18 168.43 100.49 30752 +1987 7 -0.23 -6.23 -1.88 0 148.55 135.66 30828 +1987 8 -1.37 -7.37 -3.02 0 137.62 137.63 30907 +1987 9 0.27 -5.73 -1.38 0.11 153.58 103.65 30991 +1987 10 -2.23 -8.23 -3.88 0.51 129.85 149.46 31079 +1987 11 0.39 -5.61 -1.26 0 154.8 184.32 31171 +1987 12 4.45 -1.55 2.8 0 201.65 182.5 31266 +1987 13 -0.38 -6.38 -2.03 0.42 147.07 151.9 31366 +1987 14 -5.41 -11.41 -7.06 0.09 104.3 154.55 31469 +1987 15 -3.56 -9.56 -5.21 1.67 118.57 160.12 31575 +1987 16 -2.38 -8.38 -4.03 0 128.53 197.73 31686 +1987 17 -2.75 -8.75 -4.4 0 125.33 199.4 31800 +1987 18 -1.23 -7.23 -2.88 0 138.93 200.53 31917 +1987 19 -3.82 -9.82 -5.47 0.06 116.47 164.83 32038 +1987 20 -4.03 -10.03 -5.68 0.6 114.79 167.7 32161 +1987 21 -3.69 -9.69 -5.34 0.13 117.51 169.32 32289 +1987 22 -2.76 -8.76 -4.41 0.59 125.24 171.93 32419 +1987 23 0.66 -5.34 -0.99 0.21 157.6 171.83 32552 +1987 24 -0.38 -6.38 -2.03 0.97 147.07 176.41 32688 +1987 25 -1.94 -7.94 -3.59 0.32 132.42 179.07 32827 +1987 26 -2.06 -8.06 -3.71 0.41 131.35 181.53 32969 +1987 27 -2.5 -8.5 -4.15 0.11 127.48 183.28 33114 +1987 28 0.74 -5.26 -0.91 0.4 158.43 183.47 33261 +1987 29 -0.84 -6.84 -2.49 0.48 142.61 187 33411 +1987 30 -0.6 -6.6 -2.25 0 144.92 232.21 33564 +1987 31 1.12 -4.88 -0.53 0 162.45 233.31 33718 +1987 32 6.01 0.01 4.36 0 222.65 231.2 33875 +1987 33 7.44 1.44 5.79 0.22 243.52 187.19 34035 +1987 34 6.53 0.53 4.88 0 230.05 233.43 34196 +1987 35 4.49 -1.51 2.84 0.12 202.16 190.38 34360 +1987 36 7.29 1.29 5.64 0.42 241.26 189.48 34526 +1987 37 5.67 -0.33 4.02 0 217.92 238.38 34694 +1987 38 6.28 0.28 4.63 0.19 226.47 192.1 34863 +1987 39 5.76 -0.24 4.11 0 219.16 241.76 35035 +1987 40 7.76 1.76 6.11 0 248.42 241.48 35208 +1987 41 5.74 -0.26 4.09 0.15 218.88 195.37 35383 +1987 42 1.44 -4.56 -0.21 1.35 165.91 199.24 35560 +1987 43 6.59 0.59 4.94 0.05 230.92 197.38 35738 +1987 44 4.03 -1.97 2.38 0 196.29 252.12 35918 +1987 45 3.55 -2.45 1.9 0.04 190.33 201.84 36099 +1987 46 1.71 -4.29 0.06 0.62 168.88 204.43 36282 +1987 47 2.33 -3.67 0.68 0 175.86 260.03 36466 +1987 48 1.63 -4.37 -0.02 0 167.99 262.94 36652 +1987 49 1.37 -4.63 -0.28 0.19 165.15 209.72 36838 +1987 50 0.1 -5.9 -1.55 0.85 151.85 212.13 37026 +1987 51 0.97 -5.03 -0.68 0.26 160.86 213.65 37215 +1987 52 1.59 -4.41 -0.06 0 167.55 273.02 37405 +1987 53 3.09 -2.91 1.44 0 184.76 274.35 37596 +1987 54 2.94 -3.06 1.29 0.49 182.97 217.6 37788 +1987 55 -0.24 -6.24 -1.89 0.05 148.45 221.47 37981 +1987 56 -0.03 -6.03 -1.68 0.11 150.54 223.5 38175 +1987 57 -0.25 -6.25 -1.9 0 148.35 287.45 38370 +1987 58 3.09 -2.91 1.44 0 184.76 287.46 38565 +1987 59 6.01 0.01 4.36 0 222.65 286.72 38761 +1987 60 7.66 1.66 6.01 0.23 246.88 224.58 38958 +1987 61 8.9 2.9 7.25 0.32 266.55 224.58 39156 +1987 62 6.92 0.92 5.27 0.68 235.74 227.47 39355 +1987 63 4.91 -1.09 3.26 0.02 207.65 230.58 39553 +1987 64 7.92 1.92 6.27 0.31 250.9 229.39 39753 +1987 65 6.31 0.31 4.66 0.15 226.89 232.1 39953 +1987 66 5.36 -0.64 3.71 0.31 213.68 201.67 40154 +1987 67 8.31 2.31 6.66 0 257.03 268.51 40355 +1987 68 0.96 -5.04 -0.69 0.08 160.75 208.96 40556 +1987 69 2.14 -3.86 0.49 0.23 173.69 210.25 40758 +1987 70 2.72 -3.28 1.07 0.04 180.38 212.04 40960 +1987 71 0.83 -5.17 -0.82 0.34 159.38 215.43 41163 +1987 72 -1.2 -7.2 -2.85 0.01 139.21 250.63 41366 +1987 73 0.17 -5.83 -1.48 0 152.56 325.1 41569 +1987 74 -1.55 -7.55 -3.2 0 135.96 328.98 41772 +1987 75 2.29 -3.71 0.64 0 175.4 297.17 41976 +1987 76 0.46 -5.54 -1.19 0.13 155.52 226.04 42179 +1987 77 2.56 -3.44 0.91 0.09 178.51 226.69 42383 +1987 78 4.91 -1.09 3.26 0 207.65 302.63 42587 +1987 79 5.96 -0.04 4.31 0 221.95 304.22 42791 +1987 80 5.28 -0.72 3.63 0.11 212.6 230.66 42996 +1987 81 7.46 1.46 5.81 0.79 243.83 230.65 43200 +1987 82 4.16 -1.84 2.51 0.07 197.94 235.54 43404 +1987 83 4.95 -1.05 3.3 0 208.18 315.72 43608 +1987 84 7.36 1.36 5.71 0.01 242.31 236.54 43812 +1987 85 7.37 1.37 5.72 0 242.46 317.89 44016 +1987 86 0.19 -5.81 -1.46 0.69 152.76 245.9 44220 +1987 87 0.71 -5.29 -0.94 0.02 158.12 247.52 44424 +1987 88 1.11 -4.89 -0.54 0 162.35 332.08 44627 +1987 89 3.02 -2.98 1.37 0 183.92 332.6 44831 +1987 90 0.5 -5.5 -1.15 0 155.94 337.37 45034 +1987 91 7.81 1.81 6.16 0.04 249.19 248.68 45237 +1987 92 10.59 4.59 8.94 0 295.51 329.59 45439 +1987 93 13.14 7.14 11.49 0 344.3 327.18 45642 +1987 94 16.31 10.31 14.66 0.78 414.42 241.83 45843 +1987 95 15.38 9.38 13.73 0.13 392.69 245.02 46045 +1987 96 13.36 7.36 11.71 0.06 348.81 249.81 46246 +1987 97 11.04 5.04 9.39 0 303.66 339.48 46446 +1987 98 14.32 8.32 12.67 0 369.11 335.05 46647 +1987 99 17.89 11.89 16.24 0 453.69 328.44 46846 +1987 100 15.02 9.02 13.37 0.06 384.54 253.05 47045 +1987 101 17.61 11.61 15.96 0.07 446.5 249.71 47243 +1987 102 13.87 7.87 12.22 0 359.47 343.71 47441 +1987 103 11.96 5.96 10.31 0 320.93 349.39 47638 +1987 104 15.79 9.79 14.14 0 402.14 342.98 47834 +1987 105 16.57 10.57 14.92 0 420.67 342.81 48030 +1987 106 20.94 14.94 19.29 0 538.51 331.79 48225 +1987 107 19.13 13.13 17.48 0 486.69 339.02 48419 +1987 108 19.12 13.12 17.47 0 486.41 340.74 48612 +1987 109 14.17 8.17 12.52 0 365.87 355.09 48804 +1987 110 15.53 9.53 13.88 0.49 396.12 264.99 48995 +1987 111 13.76 7.76 12.11 0 357.15 358.94 49185 +1987 112 12.78 6.78 11.13 0 337.02 362.54 49374 +1987 113 10.66 4.66 9.01 0 296.77 368.01 49561 +1987 114 11.41 5.41 9.76 0 310.51 368.11 49748 +1987 115 14.3 8.3 12.65 0 368.68 363.49 49933 +1987 116 12.68 6.68 11.03 0 335.02 368.24 50117 +1987 117 11.74 5.74 10.09 0.01 316.72 278.6 50300 +1987 118 13.86 7.86 12.21 0.55 359.26 276.24 50481 +1987 119 8.55 2.55 6.9 0.02 260.86 284.79 50661 +1987 120 7.49 1.49 5.84 0 244.28 382.59 50840 +1987 121 11.38 5.38 9.73 0.01 309.95 282.77 51016 +1987 122 12.44 6.44 10.79 0.14 330.27 282.07 51191 +1987 123 15.17 9.17 13.52 0.14 387.92 278.22 51365 +1987 124 17.58 11.58 15.93 0.61 445.74 274.24 51536 +1987 125 18.19 12.19 16.54 1.61 461.49 273.65 51706 +1987 126 20.11 14.11 18.46 1.34 514.19 269.89 51874 +1987 127 15.65 9.65 14 0.05 398.89 280.27 52039 +1987 128 17.62 11.62 15.97 0.02 446.76 277.02 52203 +1987 129 21.2 15.2 19.55 0.19 546.32 269.09 52365 +1987 130 22.08 16.08 20.43 0.55 573.49 267.28 52524 +1987 131 21.5 15.5 19.85 0.01 555.46 269.44 52681 +1987 132 18.26 12.26 16.61 0 463.33 370.7 52836 +1987 133 15.6 9.6 13.95 0.64 397.74 284.09 52989 +1987 134 15.68 9.68 14.03 0.58 399.59 284.47 53138 +1987 135 17.39 11.39 15.74 0.78 440.93 281.5 53286 +1987 136 17.36 11.36 15.71 0.46 440.17 282.04 53430 +1987 137 14.85 8.85 13.2 0.98 380.74 287.57 53572 +1987 138 18.54 12.54 16.89 0 470.74 373.86 53711 +1987 139 17.54 11.54 15.89 0 444.72 377.53 53848 +1987 140 14.11 8.11 12.46 0.8 364.59 290.26 53981 +1987 141 13.51 7.51 11.86 0.68 351.92 291.64 54111 +1987 142 14.86 8.86 13.21 1.02 380.96 289.61 54238 +1987 143 11.61 5.61 9.96 0.07 314.26 295.52 54362 +1987 144 10.42 4.42 8.77 0 292.48 396.85 54483 +1987 145 13.96 7.96 12.31 0.06 361.38 292.37 54600 +1987 146 14.73 8.73 13.08 0 378.08 388.35 54714 +1987 147 16.31 10.31 14.66 0 414.42 384.74 54824 +1987 148 18.1 12.1 16.45 0 459.14 379.99 54931 +1987 149 17.56 11.56 15.91 0 445.23 381.91 55034 +1987 150 19.32 13.32 17.67 0 491.92 376.82 55134 +1987 151 17.69 11.69 16.04 0 448.55 382.25 55229 +1987 152 21.55 15.55 19.9 0 557 369.6 55321 +1987 153 21.88 15.88 20.23 0.09 567.22 276.46 55409 +1987 154 21.35 15.35 19.7 0 550.88 370.89 55492 +1987 155 22.14 16.14 20.49 0.09 575.39 276.09 55572 +1987 156 23.58 17.58 21.93 0.07 622.45 272.04 55648 +1987 157 20.57 14.57 18.92 0 527.55 374.34 55719 +1987 158 17.22 11.22 15.57 0.35 436.66 288.87 55786 +1987 159 18.57 12.57 16.92 0.89 471.54 286.02 55849 +1987 160 20.28 14.28 18.63 0 519.09 375.94 55908 +1987 161 17.22 11.22 15.57 0.02 436.66 289.24 55962 +1987 162 19.37 13.37 17.72 0 493.3 379.12 56011 +1987 163 23.89 17.89 22.24 1.27 633 271.88 56056 +1987 164 26.18 20.18 24.53 1.47 715.72 264.2 56097 +1987 165 24.27 18.27 22.62 0.3 646.14 270.77 56133 +1987 166 25.2 19.2 23.55 1.08 679.27 267.75 56165 +1987 167 23.3 17.3 21.65 0 613.06 365.11 56192 +1987 168 27.71 21.71 26.06 0 775.93 344.84 56214 +1987 169 23.28 17.28 21.63 0 612.39 365.28 56231 +1987 170 24.23 18.23 22.58 0.1 644.75 270.98 56244 +1987 171 25.12 19.12 23.47 0.72 676.36 268.09 56252 +1987 172 23.09 17.09 21.44 0.13 606.09 274.57 56256 +1987 173 18.51 12.51 16.86 1.27 469.94 286.77 56255 +1987 174 20.43 14.43 18.78 0 523.45 375.96 56249 +1987 175 19.61 13.61 17.96 0.16 500 284.04 56238 +1987 176 18.48 12.48 16.83 0.88 469.14 286.73 56223 +1987 177 17.36 11.36 15.71 0.45 440.17 289.17 56203 +1987 178 16.27 10.27 14.62 0.4 413.46 291.5 56179 +1987 179 15.52 9.52 13.87 0.44 395.89 292.92 56150 +1987 180 17.14 11.14 15.49 0 434.67 386 56116 +1987 181 20.31 14.31 18.66 0 519.96 375.94 56078 +1987 182 21.5 15.5 19.85 0.23 555.46 278.67 56035 +1987 183 16.64 10.64 14.99 1.9 422.37 290.26 55987 +1987 184 15.47 9.47 13.82 0.59 394.74 292.5 55935 +1987 185 15.57 9.57 13.92 0.01 397.04 292.23 55879 +1987 186 18.03 12.03 16.38 0.01 457.31 286.85 55818 +1987 187 23.89 17.89 22.24 0 633 361.31 55753 +1987 188 28.28 22.28 26.63 0 799.43 340.22 55684 +1987 189 23.7 17.7 22.05 0 626.52 361.66 55611 +1987 190 21.85 15.85 20.2 0.04 566.28 276.45 55533 +1987 191 22.47 16.47 20.82 0.63 585.9 274.48 55451 +1987 192 23.98 17.98 22.33 0.41 636.09 269.68 55366 +1987 193 28.14 22.14 26.49 0 793.6 339.67 55276 +1987 194 27.94 21.94 26.29 0.06 785.34 255.38 55182 +1987 195 26.93 20.93 25.28 0.95 744.72 259.03 55085 +1987 196 24.58 18.58 22.93 0 657.03 355.87 54984 +1987 197 24.31 18.31 22.66 0.31 647.54 267.44 54879 +1987 198 25.83 19.83 24.18 0.06 702.51 262.06 54770 +1987 199 22.13 16.13 20.48 0 575.07 364.6 54658 +1987 200 19.35 13.35 17.7 0 492.75 373.92 54542 +1987 201 24.13 18.13 22.48 0.01 641.27 266.82 54423 +1987 202 24.03 18.03 22.38 0.36 637.82 266.72 54301 +1987 203 26.18 20.18 24.53 0 715.72 345.59 54176 +1987 204 19.14 13.14 17.49 0.12 486.96 279.4 54047 +1987 205 20.17 14.17 18.52 0.27 515.92 276.48 53915 +1987 206 20.91 14.91 19.26 1.01 537.61 274.16 53780 +1987 207 21.69 15.69 20.04 0.1 561.31 271.57 53643 +1987 208 25.31 19.31 23.66 0.01 683.28 260.1 53502 +1987 209 24.58 18.58 22.93 0.47 657.03 262.03 53359 +1987 210 23.36 17.36 21.71 0.32 615.06 265.36 53213 +1987 211 23.7 17.7 22.05 0 626.52 351.68 53064 +1987 212 23.66 17.66 22.01 2.6 625.16 263.3 52913 +1987 213 19.15 13.15 17.5 0.85 487.23 274.84 52760 +1987 214 21.84 15.84 20.19 0.04 565.97 267.45 52604 +1987 215 25.66 19.66 24.01 0 696.18 340.42 52445 +1987 216 25.07 19.07 23.42 0.04 674.55 256.54 52285 +1987 217 27.69 21.69 26.04 0.06 775.12 246.73 52122 +1987 218 28.86 22.86 27.21 0.01 823.96 241.64 51958 +1987 219 27.06 21.06 25.41 0 749.85 330.32 51791 +1987 220 22.44 16.44 20.79 0 584.94 349.08 51622 +1987 221 22.55 16.55 20.9 0 588.47 347.68 51451 +1987 222 20.02 14.02 18.37 0 511.61 355.47 51279 +1987 223 22.92 16.92 21.27 0 600.49 344.14 51105 +1987 224 22.42 16.42 20.77 0 584.3 344.98 50929 +1987 225 24.65 18.65 23 0.18 659.51 251.33 50751 +1987 226 24.66 18.66 23.01 0.08 659.86 250.47 50572 +1987 227 22.2 16.2 20.55 0 577.29 342.28 50392 +1987 228 24.51 18.51 22.86 0.72 654.55 249.14 50210 +1987 229 18.92 12.92 17.27 0.88 480.96 262.99 50026 +1987 230 20.54 14.54 18.89 0.48 526.67 258.24 49842 +1987 231 15.08 9.08 13.43 0.83 385.89 268.6 49656 +1987 232 13.98 7.98 12.33 0.01 361.81 269.45 49469 +1987 233 17.37 11.37 15.72 0.34 440.43 262.12 49280 +1987 234 20.9 14.9 19.25 0.2 537.31 253.14 49091 +1987 235 21.83 15.83 20.18 0.74 565.66 249.68 48900 +1987 236 22.04 16.04 20.39 0.18 572.24 248.09 48709 +1987 237 22.24 16.24 20.59 0 578.56 328.47 48516 +1987 238 20.34 14.34 18.69 0 520.83 333.16 48323 +1987 239 18.77 12.77 17.12 0 476.9 336.37 48128 +1987 240 17.01 11.01 15.36 1.21 431.44 254.54 47933 +1987 241 17.87 11.87 16.22 0.23 453.17 251.54 47737 +1987 242 17.8 11.8 16.15 0.44 451.37 250.37 47541 +1987 243 21.63 15.63 19.98 0.07 559.46 240.39 47343 +1987 244 23.16 17.16 21.51 0 608.4 313.44 47145 +1987 245 26.33 20.33 24.68 0 721.44 299.24 46947 +1987 246 27.86 21.86 26.21 0 782.06 290.62 46747 +1987 247 26.1 20.1 24.45 0 712.68 296.64 46547 +1987 248 26.7 20.7 25.05 1.47 735.72 219.21 46347 +1987 249 24.61 18.61 22.96 0.63 658.09 224.11 46146 +1987 250 18.07 12.07 16.42 0.92 458.35 238.33 45945 +1987 251 15.07 9.07 13.42 0.14 385.66 242.15 45743 +1987 252 17.28 11.28 15.63 0 438.16 315.52 45541 +1987 253 19.68 13.68 18.03 0.01 501.96 230.28 45339 +1987 254 23.21 17.21 21.56 0 610.06 293.9 45136 +1987 255 23.85 17.85 22.2 0 631.63 289.51 44933 +1987 256 20.85 14.85 19.2 0.41 535.82 222.83 44730 +1987 257 17.62 11.62 15.97 0 446.76 303.76 44527 +1987 258 20.56 14.56 18.91 0 527.26 293.56 44323 +1987 259 21.41 15.41 19.76 0 552.71 288.68 44119 +1987 260 19.37 13.37 17.72 0 493.3 292.17 43915 +1987 261 20.55 14.55 18.9 0 526.96 286.51 43711 +1987 262 20.76 14.76 19.11 0.01 533.15 212.7 43507 +1987 263 23.66 17.66 22.01 0 625.16 272.24 43303 +1987 264 23.61 17.61 21.96 0 623.47 269.96 43099 +1987 265 19.24 13.24 17.59 0.7 489.71 210.39 42894 +1987 266 23.01 17.01 21.36 0 603.45 267.32 42690 +1987 267 24.73 18.73 23.08 0 662.35 259.09 42486 +1987 268 22.99 16.99 21.34 0.01 602.79 196.8 42282 +1987 269 23.85 17.85 22.2 0 631.63 257.28 42078 +1987 270 20.55 14.55 18.9 0.73 526.96 198.41 41875 +1987 271 18.89 12.89 17.24 0.22 480.14 199.68 41671 +1987 272 18 12 16.35 0 456.53 265.66 41468 +1987 273 18.58 12.58 16.93 0 471.8 261.84 41265 +1987 274 14.44 8.44 12.79 0 371.72 267.8 41062 +1987 275 14.57 8.57 12.92 0 374.56 264.8 40860 +1987 276 14.98 8.98 13.33 0 383.64 261.35 40658 +1987 277 15.91 9.91 14.26 0 404.95 256.94 40456 +1987 278 19.32 13.32 17.67 0 491.92 246.8 40255 +1987 279 15.64 9.64 13.99 0 398.66 251.83 40054 +1987 280 14.79 8.79 13.14 0 379.41 250.77 39854 +1987 281 14.23 8.23 12.58 0 367.17 249.04 39654 +1987 282 13.74 7.74 12.09 0.45 356.73 185.35 39455 +1987 283 11.9 5.9 10.25 0.62 319.78 185.37 39256 +1987 284 13.22 7.22 11.57 0 345.94 242.14 39058 +1987 285 11.84 5.84 10.19 0.39 318.63 181.17 38861 +1987 286 13.49 7.49 11.84 0.13 351.51 177.24 38664 +1987 287 13.25 7.25 11.6 0.62 346.55 175.33 38468 +1987 288 19.83 13.83 18.18 0 506.2 218.76 38273 +1987 289 14.56 8.56 12.91 0.07 374.34 169.74 38079 +1987 290 14.14 8.14 12.49 0 365.23 224.16 37885 +1987 291 13.7 7.7 12.05 0 355.89 222.16 37693 +1987 292 15.71 9.71 14.06 0 400.28 216.28 37501 +1987 293 7.98 1.98 6.33 0 251.83 224.01 37311 +1987 294 7.2 1.2 5.55 0 239.91 221.88 37121 +1987 295 9.71 3.71 8.06 0.1 280.11 162.25 36933 +1987 296 11.76 5.76 10.11 0.2 317.1 158.42 36745 +1987 297 11.48 5.48 9.83 0.31 311.82 156.65 36560 +1987 298 14.31 8.31 12.66 0.6 368.89 151.81 36375 +1987 299 13.4 7.4 11.75 0 349.64 200.97 36191 +1987 300 16.19 10.19 14.54 0.05 411.56 145.62 36009 +1987 301 13.48 7.48 11.83 0.47 351.3 146.81 35829 +1987 302 17.54 11.54 15.89 0 444.72 186.92 35650 +1987 303 22.1 16.1 20.45 0.02 574.13 131.63 35472 +1987 304 19.78 13.78 18.13 0.56 504.78 133.51 35296 +1987 305 19.06 13.06 17.41 0.48 484.77 132.57 35122 +1987 306 17.39 11.39 15.74 0.14 440.93 133.14 34950 +1987 307 16.7 10.7 15.05 0 423.83 176.22 34779 +1987 308 14.55 8.55 12.9 0.37 374.12 132.63 34610 +1987 309 9.03 3.03 7.38 0.14 268.69 135.72 34444 +1987 310 7.28 1.28 5.63 0 241.11 180.12 34279 +1987 311 6.23 0.23 4.58 0 225.75 178.79 34116 +1987 312 6.76 0.76 5.11 0 233.39 175.71 33956 +1987 313 4.45 -1.55 2.8 0.67 201.65 131.49 33797 +1987 314 2.39 -3.61 0.74 0 176.55 174.67 33641 +1987 315 5.26 -0.74 3.61 0 212.33 170.21 33488 +1987 316 2.64 -3.36 0.99 0 179.44 169.74 33337 +1987 317 1.73 -4.27 0.08 0 169.1 168.04 33188 +1987 318 4.49 -1.51 2.84 0 202.16 163.98 33042 +1987 319 2.83 -3.17 1.18 0.75 181.67 122.48 32899 +1987 320 4.13 -1.87 2.48 0 197.56 160.61 32758 +1987 321 6.33 0.33 4.68 0 227.18 156.98 32620 +1987 322 6.39 0.39 4.74 0 228.04 155.11 32486 +1987 323 7.28 1.28 5.63 0.12 241.11 114.62 32354 +1987 324 5.78 -0.22 4.13 0 219.44 151.87 32225 +1987 325 2.8 -3.2 1.15 0.16 181.32 114.01 32100 +1987 326 5.16 -0.84 3.51 0.16 210.98 111.83 31977 +1987 327 9.26 3.26 7.61 0.1 272.5 108.15 31858 +1987 328 12.68 6.68 11.03 1.3 335.02 104.28 31743 +1987 329 12.75 6.75 11.1 2.21 336.42 103.14 31631 +1987 330 12.31 6.31 10.66 0 327.71 136.55 31522 +1987 331 9.87 3.87 8.22 0 282.86 137.52 31417 +1987 332 14.08 8.08 12.43 0.19 363.94 98.87 31316 +1987 333 10.13 4.13 8.48 1.43 287.37 100.96 31218 +1987 334 7.52 1.52 5.87 0.02 244.74 101.69 31125 +1987 335 8.7 2.7 7.05 0 263.29 133.54 31035 +1987 336 12.63 6.63 10.98 0 334.03 129.05 30949 +1987 337 12.17 6.17 10.52 0.3 324.99 95.9 30867 +1987 338 8.74 2.74 7.09 0 263.94 129.88 30790 +1987 339 14.05 8.05 12.4 0 363.3 124.32 30716 +1987 340 10.79 4.79 9.14 0 299.11 126.72 30647 +1987 341 9.42 3.42 7.77 0 275.19 126.95 30582 +1987 342 4.77 -1.23 3.12 0 205.81 129.36 30521 +1987 343 3.8 -2.2 2.15 0 193.42 129.08 30465 +1987 344 3.49 -2.51 1.84 0 189.59 128.12 30413 +1987 345 1.56 -4.44 -0.09 0.01 167.22 96.49 30366 +1987 346 3.98 -2.02 2.33 0 195.67 126.87 30323 +1987 347 1.17 -4.83 -0.48 0 162.99 127.67 30284 +1987 348 -1.75 -7.75 -3.4 0 134.14 128.52 30251 +1987 349 2.35 -3.65 0.7 0 176.09 126.38 30221 +1987 350 -1.84 -7.84 -3.49 0 133.32 127.83 30197 +1987 351 -3.37 -9.37 -5.02 0.19 120.12 140.45 30177 +1987 352 -2.39 -8.39 -4.04 0 128.44 172.07 30162 +1987 353 -2.39 -8.39 -4.04 0 128.44 172.02 30151 +1987 354 0.8 -5.2 -0.85 0.14 159.06 139.05 30145 +1987 355 -2.29 -8.29 -3.94 0 129.32 171.85 30144 +1987 356 3.1 -2.9 1.45 0 184.88 169.15 30147 +1987 357 2.97 -3.03 1.32 0.24 183.33 94.06 30156 +1987 358 5.77 -0.23 4.12 0.03 219.3 92.96 30169 +1987 359 5.13 -0.87 3.48 0 210.58 124.44 30186 +1987 360 8.57 2.57 6.92 0 261.19 122.55 30208 +1987 361 10.59 4.59 8.94 0 295.51 121.31 30235 +1987 362 10.14 4.14 8.49 0.31 287.55 91.58 30267 +1987 363 8.57 2.57 6.92 1.03 261.19 92.92 30303 +1987 364 7.2 1.2 5.55 0.76 239.91 93.93 30343 +1987 365 6.29 0.29 4.64 0.13 226.61 94.8 30388 +1988 1 12.57 6.57 10.92 0 332.83 122.36 30438 +1988 2 5.75 -0.25 4.1 0 219.02 128.36 30492 +1988 3 2.63 -3.37 0.98 0 179.33 131.06 30551 +1988 4 5.94 -0.06 4.29 0 221.67 130.09 30614 +1988 5 6.34 0.34 4.69 0 227.32 130.47 30681 +1988 6 6.02 0.02 4.37 0 222.79 131.56 30752 +1988 7 7.12 1.12 5.47 0 238.71 131.61 30828 +1988 8 10.4 4.4 8.75 0.12 292.12 97.91 30907 +1988 9 8.65 2.65 7 0.45 262.48 99.9 30991 +1988 10 7.17 1.17 5.52 0.02 239.46 101.69 31079 +1988 11 6.26 0.26 4.61 0.39 226.18 102.89 31171 +1988 12 3.68 -2.32 2.03 0 191.93 139.79 31266 +1988 13 4.14 -1.86 2.49 0.84 197.68 105.86 31366 +1988 14 2.78 -3.22 1.13 0 181.08 143.39 31469 +1988 15 0.37 -5.63 -1.28 0.19 154.6 109.55 31575 +1988 16 2.91 -3.09 1.26 0.14 182.61 109.54 31686 +1988 17 2.69 -3.31 1.04 0 180.03 147.87 31800 +1988 18 3.24 -2.76 1.59 0 186.56 149.46 31917 +1988 19 2.52 -3.48 0.87 0 178.05 151.8 32038 +1988 20 -0.6 -6.6 -2.25 0.3 144.92 158.17 32161 +1988 21 -0.04 -6.04 -1.69 0.01 150.44 159.35 32289 +1988 22 0.27 -5.73 -1.38 0 153.58 199.95 32419 +1988 23 1.55 -4.45 -0.1 0 167.11 200.72 32552 +1988 24 2.62 -3.38 0.97 0 179.21 201.7 32688 +1988 25 6.11 0.11 4.46 0 224.06 160.55 32827 +1988 26 6.94 0.94 5.29 0.02 236.04 121.37 32969 +1988 27 13.4 7.4 11.75 0 349.64 157.54 33114 +1988 28 15.9 9.9 14.25 0 404.71 156.47 33261 +1988 29 15.89 9.89 14.24 0 404.48 158.76 33411 +1988 30 16.03 10.03 14.38 0.09 407.77 120.53 33564 +1988 31 12.18 6.18 10.53 0 325.18 167.89 33718 +1988 32 10.61 4.61 8.96 0 295.87 171.65 33875 +1988 33 8.94 2.94 7.29 0 267.2 175.89 34035 +1988 34 7.96 1.96 6.31 0 251.52 178.97 34196 +1988 35 10.67 4.67 9.02 0 296.95 178.41 34360 +1988 36 10.97 4.97 9.32 0 302.38 180.55 34526 +1988 37 11.1 5.1 9.45 0.11 304.76 137.08 34694 +1988 38 8.22 2.22 6.57 0.85 255.6 141.33 34863 +1988 39 6.59 0.59 4.94 0.22 230.92 144.38 35035 +1988 40 3.7 -2.3 2.05 0 192.17 197.39 35208 +1988 41 1.6 -4.4 -0.05 0 167.66 201.45 35383 +1988 42 2.27 -3.73 0.62 0.97 175.17 152.69 35560 +1988 43 1.04 -4.96 -0.61 0 161.6 207.1 35738 +1988 44 5.44 -0.56 3.79 0.02 214.77 154.87 35918 +1988 45 7.22 1.22 5.57 0 240.2 207.52 36099 +1988 46 7.78 1.78 6.13 0.62 248.73 157.23 36282 +1988 47 6.99 0.99 5.34 0 236.78 213.21 36466 +1988 48 4.53 -1.47 2.88 0 202.68 218.18 36652 +1988 49 5.71 -0.29 4.06 0.44 218.47 164.96 36838 +1988 50 7.27 1.27 5.62 0.11 240.96 165.85 37026 +1988 51 6.1 0.1 4.45 0 223.91 225.22 37215 +1988 52 8.37 2.37 6.72 0 257.98 225.75 37405 +1988 53 4.91 -1.09 3.26 0 207.65 232.09 37596 +1988 54 3.02 -2.98 1.37 0 183.92 236.42 37788 +1988 55 1.28 -4.72 -0.37 0 164.17 240.73 37981 +1988 56 4.67 -1.33 3.02 0 204.5 240.76 38175 +1988 57 6.31 0.31 4.66 0 226.89 242.11 38370 +1988 58 7.48 1.48 5.83 0.75 244.13 182.86 38565 +1988 59 4.7 -1.3 3.05 0.59 204.89 186.97 38761 +1988 60 5.98 -0.02 4.33 0.42 222.23 188.22 38958 +1988 61 5.23 -0.77 3.58 0 211.92 254.63 39156 +1988 62 8.77 2.77 7.12 0.03 264.42 190.19 39355 +1988 63 7.1 1.1 5.45 0.03 238.41 193.88 39553 +1988 64 8.81 2.81 7.16 0 265.08 259.41 39753 +1988 65 6.09 0.09 4.44 0 223.77 265.4 39953 +1988 66 10.91 4.91 9.26 0 301.29 262.18 40154 +1988 67 8.63 2.63 6.98 0 262.15 268.11 40355 +1988 68 10.74 4.74 9.09 0.01 298.21 201.09 40556 +1988 69 9.48 3.48 7.83 0 276.2 272.47 40758 +1988 70 9.03 3.03 7.38 1.34 268.69 206.92 40960 +1988 71 7.29 1.29 5.64 0.17 241.26 210.73 41163 +1988 72 5.77 -0.23 4.12 0 219.3 285.53 41366 +1988 73 5.52 -0.48 3.87 0 215.86 288.49 41569 +1988 74 6.56 0.56 4.91 0.17 230.49 217.57 41772 +1988 75 1.73 -4.27 0.08 0.64 169.1 223.24 41976 +1988 76 3.25 -2.75 1.6 0.25 186.68 224.23 42179 +1988 77 3.71 -2.29 2.06 0.13 192.3 225.88 42383 +1988 78 2.53 -3.47 0.88 1.19 178.16 228.74 42587 +1988 79 4.74 -1.26 3.09 0.52 205.42 229.18 42791 +1988 80 5.4 -0.6 3.75 0 214.22 307.41 42996 +1988 81 5.74 -0.26 4.09 0 218.88 309.63 43200 +1988 82 6.83 0.83 5.18 0 234.42 311 43404 +1988 83 7.5 1.5 5.85 0 244.43 312.65 43608 +1988 84 8.53 2.53 6.88 0.01 260.54 235.35 43812 +1988 85 9.84 3.84 8.19 0 282.34 314.39 44016 +1988 86 10.85 4.85 9.2 0 300.2 315.18 44220 +1988 87 13.02 7.02 11.37 0.01 341.86 235.41 44424 +1988 88 13.99 7.99 12.34 0.36 362.02 235.73 44627 +1988 89 15.49 9.49 13.84 0.31 395.2 235.03 44831 +1988 90 11.47 5.47 9.82 0 311.63 323.61 45034 +1988 91 17.55 11.55 15.9 0 444.98 313.01 45237 +1988 92 16.32 10.32 14.67 0 414.65 318.17 45439 +1988 93 15.72 9.72 14.07 0.04 400.51 241.29 45642 +1988 94 17.48 11.48 15.83 0.03 443.2 239.67 45843 +1988 95 14.54 8.54 12.89 0 373.9 328.54 46045 +1988 96 13.69 7.69 12.04 0 355.68 332.41 46246 +1988 97 13.64 7.64 11.99 0 354.63 334.54 46446 +1988 98 13.48 7.48 11.83 0 351.3 336.81 46647 +1988 99 11.66 5.66 10.01 0 315.21 342.34 46846 +1988 100 14.1 8.1 12.45 0.02 364.37 254.57 47045 +1988 101 13.51 7.51 11.86 0 351.92 342.58 47243 +1988 102 15.73 9.73 14.08 0 400.75 339.52 47441 +1988 103 14.45 8.45 12.8 0.5 371.94 258.21 47638 +1988 104 13.8 7.8 12.15 1.12 357.99 260.62 47834 +1988 105 15.53 9.53 13.88 0.01 396.12 259.02 48030 +1988 106 14.53 8.53 12.88 0 373.68 349.3 48225 +1988 107 11.93 5.93 10.28 0.17 320.35 267.3 48419 +1988 108 11.83 5.83 10.18 0 318.44 358.33 48612 +1988 109 11.76 5.76 10.11 1.11 317.1 270.06 48804 +1988 110 13.76 7.76 12.11 0.02 357.15 268.05 48995 +1988 111 9.37 3.37 7.72 0.64 274.35 275.52 49185 +1988 112 11.81 5.81 10.16 0.38 318.06 273.37 49374 +1988 113 12.57 6.57 10.92 0 332.83 364.32 49561 +1988 114 12.05 6.05 10.4 0.01 322.66 275.15 49748 +1988 115 11.82 5.82 10.17 0 318.25 368.76 49933 +1988 116 12.21 6.21 10.56 0 325.76 369.21 50117 +1988 117 8.08 2.08 6.43 0.11 253.4 283.43 50300 +1988 118 7.91 1.91 6.26 0 250.74 379.52 50481 +1988 119 5.76 -0.24 4.11 0 219.16 383.87 50661 +1988 120 7.35 1.35 5.7 0 242.16 382.8 50840 +1988 121 10.58 4.58 8.93 0 295.33 378.54 51016 +1988 122 17.06 11.06 15.41 0.46 432.68 273.77 51191 +1988 123 13.25 7.25 11.6 0.11 346.55 281.56 51365 +1988 124 15.88 9.88 14.23 0 404.24 370.25 51536 +1988 125 17.46 11.46 15.81 0 442.7 366.97 51706 +1988 126 20.05 14.05 18.4 0 512.47 360.05 51874 +1988 127 20.14 14.14 18.49 0.05 515.05 270.46 52039 +1988 128 23.37 17.37 21.72 0.02 615.39 262.39 52203 +1988 129 22.68 16.68 21.03 0 592.67 353.35 52365 +1988 130 18.74 12.74 17.09 0 476.09 367.65 52524 +1988 131 20.2 14.2 18.55 0.52 516.78 272.82 52681 +1988 132 13.24 7.24 11.59 0.18 346.35 287.79 52836 +1988 133 11.4 5.4 9.75 0 310.32 388.31 52989 +1988 134 16.01 10.01 14.36 0.73 407.3 283.82 53138 +1988 135 18.79 12.79 17.14 0.07 477.44 278.38 53286 +1988 136 19.33 13.33 17.68 0 492.19 370.1 53430 +1988 137 19.74 13.74 18.09 0.38 503.65 277.09 53572 +1988 138 21.27 15.27 19.62 1.62 548.44 273.6 53711 +1988 139 22.47 16.47 20.82 0.31 585.9 270.77 53848 +1988 140 19.92 13.92 18.27 0.06 508.76 277.96 53981 +1988 141 18.2 12.2 16.55 0 461.75 376.49 54111 +1988 142 18.13 12.13 16.48 0 459.92 377.2 54238 +1988 143 16.43 10.43 14.78 0 417.29 382.6 54362 +1988 144 16.45 10.45 14.8 0 417.77 383.02 54483 +1988 145 21.12 15.12 19.47 0 543.91 368.84 54600 +1988 146 21.22 15.22 19.57 0 546.93 368.84 54714 +1988 147 23.95 17.95 22.3 0.06 635.06 269.01 54824 +1988 148 21.88 15.88 20.23 0.05 567.22 275.45 54931 +1988 149 23.34 17.34 21.69 0 614.39 361.87 55034 +1988 150 24.3 18.3 22.65 0 647.19 358.18 55134 +1988 151 24.35 18.35 22.7 0 648.93 358.35 55229 +1988 152 26.65 20.65 25 0 733.78 347.9 55321 +1988 153 25.7 19.7 24.05 0.4 697.66 264.48 55409 +1988 154 22.44 16.44 20.79 0.15 584.94 275.09 55492 +1988 155 20.44 14.44 18.79 1.26 523.74 280.73 55572 +1988 156 20.66 14.66 19.01 0.07 530.2 280.39 55648 +1988 157 21.75 15.75 20.1 0 563.17 370.08 55719 +1988 158 20.46 14.46 18.81 0 524.33 374.9 55786 +1988 159 20.91 14.91 19.26 0 537.61 373.55 55849 +1988 160 21.45 15.45 19.8 0 553.93 371.78 55908 +1988 161 21.82 15.82 20.17 0.71 565.35 277.85 55962 +1988 162 22.97 16.97 21.32 0.07 602.13 274.56 56011 +1988 163 21.82 15.82 20.17 0.16 565.35 278.06 56056 +1988 164 21.02 15.02 19.37 0 540.9 373.72 56097 +1988 165 20.09 14.09 18.44 0.03 513.62 282.8 56133 +1988 166 19.24 13.24 17.59 0 489.71 379.97 56165 +1988 167 19.85 13.85 18.2 0.04 506.77 283.43 56192 +1988 168 18.55 12.55 16.9 0.28 471 286.64 56214 +1988 169 20.75 14.75 19.1 0 532.86 374.89 56231 +1988 170 18.89 12.89 17.24 0 480.14 381.13 56244 +1988 171 21.05 15.05 19.4 0.29 541.8 280.41 56252 +1988 172 19.59 13.59 17.94 0 499.44 378.91 56256 +1988 173 19.82 13.82 18.17 0.13 505.92 283.6 56255 +1988 174 19.86 13.86 18.21 0.34 507.05 283.43 56249 +1988 175 17.73 11.73 16.08 0.45 449.57 288.46 56238 +1988 176 16.02 10.02 14.37 0.18 407.53 292.06 56223 +1988 177 19.66 13.66 18.01 0 501.4 378.41 56203 +1988 178 20.35 14.35 18.7 0 521.12 376.1 56179 +1988 179 19.29 13.29 17.64 0 491.09 379.55 56150 +1988 180 19.85 13.85 18.2 0.52 506.77 283.18 56116 +1988 181 19.57 13.57 17.92 0.07 498.88 283.83 56078 +1988 182 23.25 17.25 21.6 0.15 611.39 273.59 56035 +1988 183 22.59 16.59 20.94 0.27 589.76 275.43 55987 +1988 184 22.5 16.5 20.85 0.67 586.86 275.58 55935 +1988 185 23.54 17.54 21.89 0 621.1 363.19 55879 +1988 186 25.05 19.05 23.4 0 673.83 356.45 55818 +1988 187 25.9 19.9 24.25 0 705.14 352.38 55753 +1988 188 30.53 24.53 28.88 0 898.15 327.5 55684 +1988 189 31.49 25.49 29.84 0 943.29 321.44 55611 +1988 190 27.93 21.93 26.28 0.28 784.93 256.16 55533 +1988 191 27.31 21.31 25.66 0.22 759.79 258.36 55451 +1988 192 27.07 21.07 25.42 0.77 750.24 259.05 55366 +1988 193 24.63 18.63 22.98 0.37 658.8 267.4 55276 +1988 194 21.97 15.97 20.32 0.18 570.04 275.32 55182 +1988 195 20.14 14.14 18.49 0 515.05 373.36 55085 +1988 196 20.82 14.82 19.17 0.25 534.93 277.95 54984 +1988 197 19.47 13.47 17.82 0.33 496.08 281.04 54879 +1988 198 22.7 16.7 21.05 0 593.32 362.76 54770 +1988 199 22.06 16.06 20.41 0.5 572.86 273.65 54658 +1988 200 18.76 12.76 17.11 1.2 476.63 281.84 54542 +1988 201 17.31 11.31 15.66 0 438.92 379.65 54423 +1988 202 19.3 13.3 17.65 0 491.36 373.04 54301 +1988 203 23.5 17.5 21.85 0 619.76 357.32 54176 +1988 204 23.16 17.16 21.51 0.08 608.4 268.65 54047 +1988 205 25.68 19.68 24.03 0.01 696.92 260.2 53915 +1988 206 28.04 22.04 26.39 0 789.46 334.91 53780 +1988 207 29.15 23.15 27.5 0 836.46 328.37 53643 +1988 208 28.75 22.75 27.1 0 819.26 329.93 53502 +1988 209 29.19 23.19 27.54 0 838.19 326.95 53359 +1988 210 28.52 22.52 26.87 0 809.5 329.98 53213 +1988 211 28.31 22.31 26.66 0.02 800.68 247.77 53064 +1988 212 26.41 20.41 24.76 0.46 724.51 254.28 52913 +1988 213 29.51 23.51 27.86 0 852.2 322.46 52760 +1988 214 26.13 20.13 24.48 0.07 713.82 254.19 52604 +1988 215 24.58 18.58 22.93 0.25 657.03 258.86 52445 +1988 216 21.96 15.96 20.31 0.15 569.72 265.86 52285 +1988 217 24.71 18.71 23.06 0 661.64 342.75 52122 +1988 218 24.65 18.65 23 0 659.51 342.21 51958 +1988 219 25.72 19.72 24.07 0 698.41 336.55 51791 +1988 220 22.85 16.85 21.2 0.14 598.2 260.65 51622 +1988 221 25.05 19.05 23.4 1.73 673.83 253.22 51451 +1988 222 25.81 19.81 24.16 0 701.77 333.3 51279 +1988 223 24.2 18.2 22.55 0 643.7 339.09 51105 +1988 224 26.83 20.83 25.18 0 740.8 326.53 50929 +1988 225 25.18 19.18 23.53 0.07 678.54 249.65 50751 +1988 226 21.62 15.62 19.97 0.76 559.15 259.21 50572 +1988 227 21.46 15.46 19.81 1.57 554.23 258.68 50392 +1988 228 19.62 13.62 17.97 0.73 500.28 262.32 50210 +1988 229 22.98 16.98 21.33 0.65 602.46 252.75 50026 +1988 230 26.64 20.64 24.99 0 733.39 320.55 49842 +1988 231 22.95 16.95 21.3 0 601.48 334.44 49656 +1988 232 20.74 14.74 19.09 0.03 532.56 255.65 49469 +1988 233 21.9 15.9 20.25 0 567.85 335.52 49280 +1988 234 20.81 14.81 19.16 0.01 534.64 253.36 49091 +1988 235 21.43 15.43 19.78 0.04 553.32 250.71 48900 +1988 236 20.22 14.22 18.57 0.22 517.36 252.62 48709 +1988 237 20.91 14.91 19.26 0.19 537.61 249.73 48516 +1988 238 21.65 15.65 20 0.12 560.08 246.65 48323 +1988 239 24.47 18.47 22.82 0.2 653.15 237.8 48128 +1988 240 23.73 17.73 22.08 0 627.54 318.24 47933 +1988 241 21.26 15.26 19.61 0 548.14 325.27 47737 +1988 242 25.11 19.11 23.46 0 676 309.53 47541 +1988 243 29.33 23.33 27.68 0.13 844.3 216.5 47343 +1988 244 20.88 14.88 19.23 1.11 536.72 240.87 47145 +1988 245 18.14 12.14 16.49 1.1 460.18 245.52 46947 +1988 246 18.11 12.11 16.46 1.22 459.4 244.11 46747 +1988 247 20.46 14.46 18.81 0 524.33 316.9 46547 +1988 248 19.18 13.18 17.53 0 488.06 318.75 46347 +1988 249 19.32 13.32 17.67 0 491.92 316.3 46146 +1988 250 23.72 17.72 22.07 1.09 627.2 225.2 45945 +1988 251 22.81 16.81 21.16 0 596.9 301.44 45743 +1988 252 23.11 17.11 21.46 0.01 606.75 223.74 45541 +1988 253 23.81 17.81 22.16 0.01 630.27 220.38 45339 +1988 254 19.43 13.43 17.78 0.03 494.97 229.23 45136 +1988 255 15.68 9.68 14.03 1.04 399.59 234.56 44933 +1988 256 12.54 6.54 10.89 0.12 332.24 237.6 44730 +1988 257 20.23 14.23 18.58 0 517.65 296.81 44527 +1988 258 19.65 13.65 18 0.71 501.12 222.1 44323 +1988 259 21.5 15.5 19.85 0 555.46 288.4 44119 +1988 260 20.8 14.8 19.15 0 534.34 288.17 43915 +1988 261 18.15 12.15 16.5 0.19 460.44 219.68 43711 +1988 262 15.14 9.14 13.49 0 387.24 297.37 43507 +1988 263 15.69 9.69 14.04 0 399.82 293.75 43303 +1988 264 16.26 10.26 14.61 0 413.22 289.95 43099 +1988 265 18.62 12.62 16.97 0.42 472.87 211.57 42894 +1988 266 17.18 11.18 15.53 0 435.66 283.07 42690 +1988 267 19.9 13.9 18.25 0.46 508.19 205.32 42486 +1988 268 21.78 15.78 20.13 0 564.11 266.05 42282 +1988 269 16.73 10.73 15.08 0.44 424.56 207.28 42078 +1988 270 15.38 9.38 13.73 0 392.69 276.56 41875 +1988 271 19.25 13.25 17.6 0 489.98 265.35 41671 +1988 272 22.69 16.69 21.04 0 593 253.35 41468 +1988 273 19.4 13.4 17.75 1.24 494.14 194.9 41265 +1988 274 14.69 8.69 13.04 0 377.2 267.34 41062 +1988 275 12.62 6.62 10.97 0.57 333.83 201.13 40860 +1988 276 13.18 7.18 11.53 0 345.12 264.53 40658 +1988 277 10.65 4.65 9 0 296.59 265.74 40456 +1988 278 12.69 6.69 11.04 0.02 335.22 194.83 40255 +1988 279 16.05 10.05 14.4 0 408.24 251.05 40054 +1988 280 13.83 7.83 12.18 0.28 358.63 189.32 39854 +1988 281 13.94 7.94 12.29 0 360.96 249.53 39654 +1988 282 9.46 3.46 7.81 0.14 275.86 190 39455 +1988 283 11.38 5.38 9.73 0 309.95 247.91 39256 +1988 284 11.49 5.49 9.84 0.1 312.01 183.54 39058 +1988 285 14.27 8.27 12.62 0 368.03 237.81 38861 +1988 286 18.06 12.06 16.41 0.51 458.09 171.06 38664 +1988 287 17.02 11.02 15.37 0.37 431.69 170.46 38468 +1988 288 17.99 11.99 16.34 0.08 456.27 167 38273 +1988 289 17.6 11.6 15.95 0.15 446.25 165.67 38079 +1988 290 16.06 10.06 14.41 0 408.48 220.95 37885 +1988 291 18.15 12.15 16.5 0 460.44 214.41 37693 +1988 292 16.29 10.29 14.64 0 413.94 215.27 37501 +1988 293 15.67 9.67 14.02 0.03 399.35 160.25 37311 +1988 294 15.5 9.5 13.85 0 395.43 211.12 37121 +1988 295 16.87 10.87 15.22 0 427.99 206 36933 +1988 296 13.48 7.48 11.83 0 351.3 208.88 36745 +1988 297 9.92 3.92 8.27 0.16 283.72 158.06 36560 +1988 298 12.35 6.35 10.7 0.91 328.5 153.86 36375 +1988 299 11.76 5.76 10.11 0.91 317.1 152.36 36191 +1988 300 9.35 3.35 7.7 1.07 274.01 152.46 36009 +1988 301 8.57 2.57 6.92 0 261.19 201.56 35829 +1988 302 9.26 3.26 7.61 0 272.5 198.22 35650 +1988 303 9.82 3.82 8.17 0 282 195.04 35472 +1988 304 12.84 6.84 11.19 0 338.22 189.04 35296 +1988 305 -0.24 -6.24 -1.89 0 148.45 197.68 35122 +1988 306 -1.86 -7.86 -3.51 0 133.14 196.19 34950 +1988 307 0.66 -5.34 -0.99 0 157.6 192.28 34779 +1988 308 2.12 -3.88 0.47 0 173.47 188.74 34610 +1988 309 1.61 -4.39 -0.04 0 167.77 186.69 34444 +1988 310 -0.09 -6.09 -1.74 0 149.94 185.15 34279 +1988 311 1.77 -4.23 0.12 0.53 169.54 136.41 34116 +1988 312 0.99 -5.01 -0.66 0.51 161.07 134.73 33956 +1988 313 2.31 -3.69 0.66 0.75 175.63 132.53 33797 +1988 314 0.27 -5.73 -1.38 0.11 153.58 131.9 33641 +1988 315 1.98 -4.02 0.33 0 171.89 172.34 33488 +1988 316 0.27 -5.73 -1.38 0 153.58 171.06 33337 +1988 317 -0.93 -6.93 -2.58 0 141.76 169.41 33188 +1988 318 1.53 -4.47 -0.12 0 166.89 165.78 33042 +1988 319 4.04 -1.96 2.39 0 196.42 162.56 32899 +1988 320 7.22 1.22 5.57 0.01 240.2 118.81 32758 +1988 321 3.35 -2.65 1.7 0.19 187.89 119.23 32620 +1988 322 5.19 -0.81 3.54 1.45 211.39 116.97 32486 +1988 323 8.62 2.62 6.97 0.2 261.99 113.81 32354 +1988 324 10.09 4.09 8.44 0.04 286.67 111.32 32225 +1988 325 12.93 6.93 11.28 0.18 340.04 107.94 32100 +1988 326 11.96 5.96 10.31 0 320.93 143.52 31977 +1988 327 7.26 1.26 5.61 0 240.81 145.78 31858 +1988 328 7.87 1.87 6.22 0 250.12 143.36 31743 +1988 329 9.61 3.61 7.96 0 278.4 140.47 31631 +1988 330 7.25 1.25 5.6 0.49 240.65 105.67 31522 +1988 331 9.08 3.08 7.43 0 269.51 138.18 31417 +1988 332 7.79 1.79 6.14 0 248.88 137.56 31316 +1988 333 5.2 -0.8 3.55 0 211.52 138.25 31218 +1988 334 -0.37 -6.37 -2.02 0 147.17 140.06 31125 +1988 335 -3.15 -9.15 -4.8 0 121.95 139.95 31035 +1988 336 0.41 -5.59 -1.24 0.39 155.01 103.08 30949 +1988 337 5.99 -0.01 4.34 0 222.37 132.75 30867 +1988 338 6.48 0.48 4.83 0 229.33 131.49 30790 +1988 339 7.45 1.45 5.8 0 243.67 130.04 30716 +1988 340 6.22 0.22 4.57 0 225.61 130.15 30647 +1988 341 4.4 -1.6 2.75 0.34 201 97.75 30582 +1988 342 4.66 -1.34 3.01 0.02 204.37 97.07 30521 +1988 343 9.35 3.35 7.7 0.22 274.01 94.08 30465 +1988 344 8.36 2.36 6.71 0 257.82 125.07 30413 +1988 345 5.72 -0.28 4.07 0.07 218.61 94.81 30366 +1988 346 5.99 -0.01 4.34 0 222.37 125.7 30323 +1988 347 5.01 -0.99 3.36 0 208.98 125.69 30284 +1988 348 4.59 -1.41 2.94 1.28 203.46 94.19 30251 +1988 349 1.97 -4.03 0.32 0.02 171.77 94.93 30221 +1988 350 1.42 -4.58 -0.23 0 165.69 126.49 30197 +1988 351 0.02 -5.98 -1.63 0 151.05 126.88 30177 +1988 352 2.43 -3.57 0.78 0 177.01 125.69 30162 +1988 353 6.07 0.07 4.42 0.07 223.49 92.72 30151 +1988 354 3.34 -2.66 1.69 0 187.77 125.14 30145 +1988 355 4.52 -1.48 2.87 0 202.55 124.5 30144 +1988 356 5.26 -0.74 3.61 0 212.33 124.1 30147 +1988 357 8.41 2.41 6.76 0 258.62 122.11 30156 +1988 358 10.14 4.14 8.49 0 287.55 120.88 30169 +1988 359 8.16 2.16 6.51 0 254.65 122.49 30186 +1988 360 6.69 0.69 5.04 0 232.37 123.85 30208 +1988 361 6.25 0.25 4.6 0.77 226.04 93.34 30235 +1988 362 2.65 -3.35 1 0.16 179.56 95.19 30267 +1988 363 1.99 -4.01 0.34 0 172 127.83 30303 +1988 364 3.83 -2.17 2.18 0 193.79 127.29 30343 +1988 365 3.82 -2.18 2.17 0.01 193.66 95.9 30388 +1989 1 -0.38 -6.38 -2.03 0 147.07 130.75 30438 +1989 2 2.18 -3.82 0.53 0 174.15 130.34 30492 +1989 3 1.21 -4.79 -0.44 0 163.42 131.74 30551 +1989 4 2.83 -3.17 1.18 0 181.67 131.87 30614 +1989 5 4.8 -1.2 3.15 0 206.2 131.43 30681 +1989 6 3.05 -2.95 1.4 0 184.28 133.29 30752 +1989 7 -0.11 -6.11 -1.76 0 149.74 135.6 30828 +1989 8 1.62 -4.38 -0.03 0 167.88 136.31 30907 +1989 9 -1.23 -7.23 -2.88 0 138.93 138.84 30991 +1989 10 -2.36 -8.36 -4.01 0 128.7 140.59 31079 +1989 11 0.6 -5.4 -1.05 0 156.97 140.36 31171 +1989 12 0.98 -5.02 -0.67 0.09 160.96 105.9 31266 +1989 13 -1.26 -7.26 -2.91 0.01 138.65 149.99 31366 +1989 14 2.66 -3.34 1.01 0 179.67 143.46 31469 +1989 15 1.41 -4.59 -0.24 0 165.58 145.56 31575 +1989 16 3.38 -2.62 1.73 0 188.25 145.79 31686 +1989 17 -3.63 -9.63 -5.28 0 118 150.71 31800 +1989 18 -0.92 -6.92 -2.57 0 141.85 151.56 31917 +1989 19 -0.7 -6.7 -2.35 0 143.96 153.41 32038 +1989 20 1.66 -4.34 0.01 0 168.32 153.86 32161 +1989 21 4.82 -1.18 3.17 0 206.47 154.01 32289 +1989 22 5.87 -0.13 4.22 0 220.69 155.03 32419 +1989 23 8.41 2.41 6.76 0 258.62 154.83 32552 +1989 24 5.92 -0.08 4.27 0 221.39 158.81 32688 +1989 25 8.48 2.48 6.83 0 259.74 158.66 32827 +1989 26 9.22 3.22 7.57 0.06 271.84 119.93 32969 +1989 27 5.87 -0.13 4.22 0.02 220.69 123.49 33114 +1989 28 6.02 0.02 4.37 0 222.79 166.74 33261 +1989 29 3.78 -2.22 2.13 0 193.17 170.68 33411 +1989 30 4.05 -1.95 2.4 0 196.55 172.75 33564 +1989 31 3.53 -2.47 1.88 0 190.08 175.47 33718 +1989 32 7.63 1.63 5.98 0 246.42 174.48 33875 +1989 33 9.35 3.35 7.7 0 274.01 175.5 34035 +1989 34 8.43 2.43 6.78 0 258.94 178.54 34196 +1989 35 5.88 -0.12 4.23 0.23 220.83 137.14 34360 +1989 36 5.35 -0.65 3.7 0.13 213.54 139.33 34526 +1989 37 5.59 -0.41 3.94 0 216.82 188 34694 +1989 38 2.67 -3.33 1.02 0 179.79 192.86 34863 +1989 39 3.17 -2.83 1.52 0 185.71 195.14 35035 +1989 40 5.07 -0.93 3.42 0 209.78 196.36 35208 +1989 41 3.68 -2.32 2.03 0 191.93 200.03 35383 +1989 42 4.36 -1.64 2.71 0 200.49 202.09 35560 +1989 43 9.09 3.09 7.44 0.01 269.68 150.39 35738 +1989 44 6.64 0.64 4.99 0 231.65 205.45 35918 +1989 45 3.9 -2.1 2.25 0 194.66 210.35 36099 +1989 46 4.49 -1.51 2.84 0.43 202.16 159.43 36282 +1989 47 3.93 -2.07 2.28 0 195.04 215.85 36466 +1989 48 5.63 -0.37 3.98 0 217.37 217.25 36652 +1989 49 7.9 1.9 6.25 0 250.58 217.86 36838 +1989 50 10.46 4.46 8.81 0 293.19 217.62 37026 +1989 51 8.78 2.78 7.13 0 264.59 222.5 37215 +1989 52 9.57 3.57 7.92 0 277.72 224.39 37405 +1989 53 11.33 5.33 9.68 0 309.02 225.12 37596 +1989 54 13.48 7.48 11.83 0 351.3 224.77 37788 +1989 55 15.05 9.05 13.4 0 385.21 225.16 37981 +1989 56 12.89 6.89 11.24 0.01 339.23 173.39 38175 +1989 57 9.04 3.04 7.39 0 268.85 239.14 38370 +1989 58 7.23 1.23 5.58 0.84 240.35 183.06 38565 +1989 59 3.76 -2.24 2.11 0.57 192.92 187.59 38761 +1989 60 8.08 2.08 6.43 0.02 253.4 186.53 38958 +1989 61 8.1 2.1 6.45 0 253.71 251.6 39156 +1989 62 4.65 -1.35 3 0.1 204.24 193.49 39355 +1989 63 7 1 5.35 1.09 236.93 193.97 39553 +1989 64 8.2 2.2 6.55 0.23 255.28 195.11 39753 +1989 65 7.51 1.51 5.86 0 244.59 263.84 39953 +1989 66 5.02 -0.98 3.37 0.59 209.11 201.93 40154 +1989 67 2.93 -3.07 1.28 0 182.85 274.09 40355 +1989 68 3.99 -2.01 2.34 0 195.79 276.04 40556 +1989 69 8.38 2.38 6.73 0 258.14 273.9 40758 +1989 70 13.26 7.26 11.61 0 346.76 269.54 40960 +1989 71 16.06 10.06 14.41 0 408.48 267.16 41163 +1989 72 18.32 12.32 16.67 0 464.91 264.94 41366 +1989 73 17.29 11.29 15.64 0 438.42 269.82 41569 +1989 74 17.21 11.21 15.56 0 436.41 272.63 41772 +1989 75 14.74 8.74 13.09 0.01 378.3 210.29 41976 +1989 76 15.56 9.56 13.91 0.22 396.81 210.99 42179 +1989 77 9.37 3.37 7.72 0.02 274.35 220.84 42383 +1989 78 7.95 1.95 6.3 0.15 251.36 224.28 42587 +1989 79 11.57 5.57 9.92 0.58 313.51 222.34 42791 +1989 80 14.79 8.79 13.14 0 379.41 293.1 42996 +1989 81 13.82 7.82 12.17 0.62 358.42 223.13 43200 +1989 82 10.78 4.78 9.13 0.03 298.93 229.07 43404 +1989 83 14.44 8.44 12.79 0 371.72 301.34 43608 +1989 84 15.78 9.78 14.13 0 401.91 301.01 43812 +1989 85 13.61 7.61 11.96 0 354.01 307.9 44016 +1989 86 15.37 9.37 13.72 0 392.46 306.66 44220 +1989 87 17.79 11.79 16.14 0.01 451.11 227.63 44424 +1989 88 18.94 12.94 17.29 0.13 481.5 227.08 44627 +1989 89 17.82 11.82 16.17 0 451.88 307.87 44831 +1989 90 18.93 12.93 17.28 0 481.23 307.24 45034 +1989 91 21.07 15.07 19.42 0 542.4 303.19 45237 +1989 92 18.82 12.82 17.17 0.56 478.25 233.88 45439 +1989 93 14.31 8.31 12.66 0.59 368.89 243.6 45642 +1989 94 12.81 6.81 11.16 0.52 337.62 247.46 45843 +1989 95 14.2 8.2 12.55 0 366.52 329.26 46045 +1989 96 14.99 8.99 13.34 0 383.87 329.63 46246 +1989 97 17.48 11.48 15.83 0 443.2 325.67 46446 +1989 98 16.57 10.57 14.92 0 420.67 329.87 46647 +1989 99 16.53 10.53 14.88 0.84 419.7 248.95 46846 +1989 100 16.98 10.98 15.33 0.03 430.7 249.53 47045 +1989 101 17.77 11.77 16.12 0 450.6 332.52 47243 +1989 102 16.34 10.34 14.69 0 415.13 338.05 47441 +1989 103 14.49 8.49 12.84 0 372.81 344.19 47638 +1989 104 15.94 9.94 14.29 0 405.65 342.61 47834 +1989 105 16.87 10.87 15.22 0.03 427.99 256.53 48030 +1989 106 14.52 8.52 12.87 0.26 373.46 261.99 48225 +1989 107 13.26 7.26 11.61 0.11 346.76 265.29 48419 +1989 108 12.97 6.97 11.32 0.11 340.85 267.05 48612 +1989 109 16.07 10.07 14.42 0.27 408.71 262.96 48804 +1989 110 13.99 7.99 12.34 0.89 362.02 267.67 48995 +1989 111 13.74 7.74 12.09 0.77 356.73 269.24 49185 +1989 112 12.78 6.78 11.13 0.11 337.02 271.9 49374 +1989 113 11.39 5.39 9.74 0.64 310.13 274.99 49561 +1989 114 14.97 8.97 13.32 0.17 383.42 270.38 49748 +1989 115 9.69 3.69 8.04 0 279.77 372.68 49933 +1989 116 8.68 2.68 7.03 0.72 262.96 281.71 50117 +1989 117 12.5 6.5 10.85 0.09 331.45 277.45 50300 +1989 118 10.58 4.58 8.93 0.1 295.33 281.25 50481 +1989 119 10.84 4.84 9.19 0.11 300.02 281.79 50661 +1989 120 11.44 5.44 9.79 0.3 311.07 281.82 50840 +1989 121 15.81 9.81 14.16 0 402.61 367.14 51016 +1989 122 15.84 9.84 14.19 0 403.31 368.25 51191 +1989 123 15.21 9.21 13.56 0 388.82 370.86 51365 +1989 124 16.84 10.84 15.19 0.24 427.25 275.78 51536 +1989 125 17.67 11.67 16.02 0.64 448.04 274.78 51706 +1989 126 15.95 9.95 14.3 1.69 405.89 279.03 51874 +1989 127 15.9 9.9 14.25 0 404.71 373.05 52039 +1989 128 11.94 5.94 10.29 0 320.54 383.18 52203 +1989 129 18.46 12.46 16.81 0 468.61 367.73 52365 +1989 130 23.03 17.03 21.38 0.46 604.11 264.56 52524 +1989 131 17.27 11.27 15.62 0.88 437.91 279.57 52681 +1989 132 16.6 10.6 14.95 0.72 421.4 281.58 52836 +1989 133 17.37 11.37 15.72 2.59 440.43 280.5 52989 +1989 134 17.98 11.98 16.33 0.07 456.02 279.7 53138 +1989 135 21.81 15.81 20.16 0.2 565.04 270.72 53286 +1989 136 18.92 12.92 17.27 0.24 480.96 278.54 53430 +1989 137 19.71 13.71 18.06 0 502.81 369.56 53572 +1989 138 17.97 11.97 16.32 0.45 455.76 281.69 53711 +1989 139 18.35 12.35 16.7 0.37 465.7 281.34 53848 +1989 140 18.84 12.84 17.19 0 478.79 374.09 53981 +1989 141 18.62 12.62 16.97 0.1 472.87 281.41 54111 +1989 142 16.87 10.87 15.22 0 427.99 380.85 54238 +1989 143 17.92 11.92 16.27 0.12 454.46 283.77 54362 +1989 144 17.42 11.42 15.77 0 441.69 380.3 54483 +1989 145 20.32 14.32 18.67 0 520.25 371.64 54600 +1989 146 18.32 12.32 16.67 0 464.91 378.47 54714 +1989 147 19.4 13.4 17.75 0.46 494.14 281.66 54824 +1989 148 18.5 12.5 16.85 0 469.67 378.77 54931 +1989 149 15.04 9.04 13.39 0 384.99 388.77 55034 +1989 150 13.04 7.04 11.39 0.93 342.26 295.4 55134 +1989 151 15.64 9.64 13.99 0 398.66 387.96 55229 +1989 152 17.39 11.39 15.74 0.01 440.93 287.43 55321 +1989 153 15.68 9.68 14.03 0.34 399.59 291.16 55409 +1989 154 14.88 8.88 13.23 0 381.41 390.59 55492 +1989 155 19.49 13.49 17.84 0.37 496.64 283.13 55572 +1989 156 23.18 17.18 21.53 0 609.06 364.36 55648 +1989 157 19.9 13.9 18.25 0.05 508.19 282.48 55719 +1989 158 17.19 11.19 15.54 0.23 435.91 288.94 55786 +1989 159 19.18 13.18 17.53 2.01 488.06 284.57 55849 +1989 160 20.03 14.03 18.38 0 511.9 376.79 55908 +1989 161 22.5 16.5 20.85 0 586.86 367.87 55962 +1989 162 22.14 16.14 20.49 0.11 575.39 276.99 56011 +1989 163 21.8 15.8 20.15 0.15 564.73 278.11 56056 +1989 164 24.32 18.32 22.67 0.63 647.88 270.54 56097 +1989 165 23.66 17.66 22.01 2.99 625.16 272.7 56133 +1989 166 20.08 14.08 18.43 0.75 513.33 282.89 56165 +1989 167 22.22 16.22 20.57 0 577.92 369.39 56192 +1989 168 19.33 13.33 17.68 0.2 492.19 284.78 56214 +1989 169 15.86 9.86 14.21 0.16 403.78 292.48 56231 +1989 170 16.63 10.63 14.98 0.51 422.13 290.9 56244 +1989 171 18.71 12.71 17.06 0 475.29 381.76 56252 +1989 172 24.2 18.2 22.55 0.08 643.7 271.11 56256 +1989 173 22.81 16.81 21.16 0.49 596.9 275.4 56255 +1989 174 19.3 13.3 17.65 0 491.36 379.76 56249 +1989 175 15.66 9.66 14.01 0.03 399.12 292.81 56238 +1989 176 14.68 8.68 13.03 0 376.98 392.88 56223 +1989 177 18.11 12.11 16.46 0.15 459.4 287.5 56203 +1989 178 19.42 13.42 17.77 0 494.69 379.23 56179 +1989 179 17.16 11.16 15.51 0.97 435.17 289.55 56150 +1989 180 19.79 13.79 18.14 0 505.07 377.78 56116 +1989 181 23.4 17.4 21.75 0.27 616.4 273.24 56078 +1989 182 25.98 19.98 24.33 0 708.15 352.82 56035 +1989 183 25.83 19.83 24.18 0.39 702.51 265.02 55987 +1989 184 25.39 19.39 23.74 0 686.21 355.24 55935 +1989 185 27.33 21.33 25.68 0.02 760.59 259.37 55879 +1989 186 24.7 18.7 23.05 0.58 661.28 268.5 55818 +1989 187 23.75 17.75 22.1 0.42 628.22 271.42 55753 +1989 188 22.89 16.89 21.24 0.45 599.51 273.85 55684 +1989 189 23.82 17.82 22.17 1.11 630.61 270.87 55611 +1989 190 20.73 14.73 19.08 1.31 532.26 279.49 55533 +1989 191 20.59 14.59 18.94 0 528.14 372.88 55451 +1989 192 19.85 13.85 18.2 0.03 506.77 281.33 55366 +1989 193 21.72 15.72 20.07 0.45 562.24 276.19 55276 +1989 194 21.2 15.2 19.55 0 546.32 369.93 55182 +1989 195 25.52 19.52 23.87 0.27 690.99 264.06 55085 +1989 196 24.1 18.1 22.45 0.25 640.23 268.45 54984 +1989 197 24.17 18.17 22.52 0.5 642.66 267.89 54879 +1989 198 19.97 13.97 18.32 0.05 510.18 279.48 54770 +1989 199 20.17 14.17 18.52 0.76 515.92 278.71 54658 +1989 200 19.55 13.55 17.9 0 498.32 373.27 54542 +1989 201 17.9 11.9 16.25 0 453.94 377.93 54423 +1989 202 22.77 16.77 21.12 0.3 595.59 270.54 54301 +1989 203 22.61 16.61 20.96 0.01 590.41 270.64 54176 +1989 204 25.57 19.57 23.92 0.62 692.84 260.95 54047 +1989 205 25.03 19.03 23.38 0.75 673.11 262.39 53915 +1989 206 22.51 16.51 20.86 0.44 587.18 269.76 53780 +1989 207 23.71 17.71 22.06 0.53 626.86 265.71 53643 +1989 208 24.62 18.62 22.97 0 658.44 349.82 53502 +1989 209 26.91 20.91 25.26 0.21 743.94 254.05 53359 +1989 210 27.24 21.24 25.59 0.11 757 252.4 53213 +1989 211 29.03 23.03 27.38 0.24 831.27 244.9 53064 +1989 212 29.43 23.43 27.78 0 848.68 323.6 52913 +1989 213 26.85 20.85 25.2 0 741.58 336.23 52760 +1989 214 29.92 23.92 28.27 0.17 870.42 239.62 52604 +1989 215 29.24 23.24 27.59 1.12 840.37 241.99 52445 +1989 216 27.52 21.52 25.87 0.07 768.23 247.99 52285 +1989 217 28.63 22.63 26.98 1.02 814.16 243.12 52122 +1989 218 26.57 20.57 24.92 1.81 730.68 250.23 51958 +1989 219 23.77 17.77 22.12 0.31 628.9 258.63 51791 +1989 220 22.44 16.44 20.79 1.36 584.94 261.81 51622 +1989 221 26.31 20.31 24.66 0.62 720.68 249.02 51451 +1989 222 27.16 21.16 25.51 1.5 753.81 245.27 51279 +1989 223 26.94 20.94 25.29 0.75 745.11 245.26 51105 +1989 224 25.24 19.24 23.59 0.12 680.72 250.28 50929 +1989 225 26.95 20.95 25.3 0.05 745.51 243.67 50751 +1989 226 26.05 20.05 24.4 1.87 710.79 245.97 50572 +1989 227 19.9 13.9 18.25 0.74 508.19 262.57 50392 +1989 228 19.13 13.13 17.48 1.08 486.69 263.45 50210 +1989 229 17.69 11.69 16.04 2.53 448.55 265.66 50026 +1989 230 14.35 8.35 12.7 1.29 369.76 271.01 49842 +1989 231 18.23 12.23 16.58 0 462.54 349.91 49656 +1989 232 17.71 11.71 16.06 1.14 449.06 262.51 49469 +1989 233 15.55 9.55 13.9 0.37 396.58 265.62 49280 +1989 234 16.25 10.25 14.6 1.52 412.98 263.24 49091 +1989 235 14.99 8.99 13.34 0.25 383.87 264.39 48900 +1989 236 17.09 11.09 15.44 0 433.42 345.85 48709 +1989 237 17.31 11.31 15.66 0.07 438.92 257.7 48516 +1989 238 22.54 16.54 20.89 0.1 588.15 244.33 48323 +1989 239 21.97 15.97 20.32 0.1 570.04 244.72 48128 +1989 240 23.83 17.83 22.18 0.21 630.95 238.39 47933 +1989 241 23.47 17.47 21.82 0.43 618.75 238.16 47737 +1989 242 23.47 17.47 21.82 0 618.75 315.87 47541 +1989 243 25.89 19.89 24.24 0.12 704.76 228.41 47343 +1989 244 21.26 15.26 19.61 0 548.14 319.94 47145 +1989 245 24.01 18.01 22.36 1.3 637.13 231.41 46947 +1989 246 17.87 11.87 16.22 0 453.17 326.12 46747 +1989 247 15.25 9.25 13.6 0 389.73 330.66 46547 +1989 248 17.49 11.49 15.84 0 443.46 323.3 46347 +1989 249 15.63 9.63 13.98 0.08 398.43 244.3 46146 +1989 250 15.38 9.38 13.73 1.31 392.69 243.24 45945 +1989 251 15.61 9.61 13.96 0 397.97 321.66 45743 +1989 252 17.95 11.95 16.3 0 455.24 313.82 45541 +1989 253 19.12 13.12 17.47 0.14 486.41 231.45 45339 +1989 254 15.81 9.81 14.16 0.06 402.61 236.05 45136 +1989 255 18.38 12.38 16.73 0.2 466.49 229.67 44933 +1989 256 16.34 10.34 14.69 0.09 415.13 231.73 44730 +1989 257 14.47 8.47 12.82 1.24 372.37 233.14 44527 +1989 258 17.72 11.72 16.07 0.42 449.31 225.88 44323 +1989 259 18.72 12.72 17.07 0 475.56 296.23 44119 +1989 260 16.14 10.14 14.49 0 410.37 300.07 43915 +1989 261 15.91 9.91 14.26 0.05 404.95 223.59 43711 +1989 262 15.04 9.04 13.39 0 384.99 297.58 43507 +1989 263 21 15 19.35 0 540.3 280.52 43303 +1989 264 21.63 15.63 19.98 0.22 559.46 207.14 43099 +1989 265 22.43 16.43 20.78 0.19 584.62 203.62 42894 +1989 266 23 17 21.35 0 603.12 267.35 42690 +1989 267 20.65 14.65 19 0 529.9 271.73 42486 +1989 268 20.82 14.82 19.17 0.88 534.93 201.59 42282 +1989 269 21.91 15.91 20.26 0.18 568.16 197.45 42078 +1989 270 26.2 20.2 24.55 0.28 716.48 185.02 41875 +1989 271 25.32 19.32 23.67 0 683.64 247.42 41671 +1989 272 24.89 18.89 23.24 0 668.07 246.36 41468 +1989 273 22.38 16.38 20.73 0 583.02 251.87 41265 +1989 274 15.55 9.55 13.9 0 396.58 265.7 41062 +1989 275 18.1 12.1 16.45 0.02 459.14 193.22 40860 +1989 276 18.03 12.03 16.38 0.21 457.31 191.35 40658 +1989 277 21.64 15.64 19.99 0.08 559.77 182.76 40456 +1989 278 18.75 12.75 17.1 0.02 476.36 186.09 40255 +1989 279 16.53 10.53 14.88 0 419.7 250.11 40054 +1989 280 20.77 14.77 19.12 0 533.45 238 39854 +1989 281 24.25 18.25 22.6 0.29 645.44 169.34 39654 +1989 282 17.71 11.71 16.06 0 449.06 239.76 39455 +1989 283 15.36 9.36 13.71 0 392.23 241.54 39256 +1989 284 9.42 3.42 7.77 0 275.19 247.46 39058 +1989 285 9.21 3.21 7.56 0 271.67 245.04 38861 +1989 286 12.78 6.78 11.13 0 337.02 237.42 38664 +1989 287 13.17 7.17 11.52 0 344.91 233.89 38468 +1989 288 15.58 9.58 13.93 0 397.27 227.19 38273 +1989 289 14.65 8.65 13 0 376.32 226.17 38079 +1989 290 17.11 11.11 15.46 0 433.92 219.04 37885 +1989 291 12.17 6.17 10.52 0 324.99 224.39 37693 +1989 292 9.98 3.98 8.33 0 284.76 224.52 37501 +1989 293 8.75 2.75 7.1 0 264.1 223.18 37311 +1989 294 4.73 -1.27 3.08 0 205.29 224.14 37121 +1989 295 9.95 3.95 8.3 0 284.24 216.05 36933 +1989 296 5.19 -0.81 3.54 0 211.39 218.2 36745 +1989 297 13.98 7.98 12.33 0 361.81 205.46 36560 +1989 298 19.72 13.72 18.07 2.09 503.09 144.73 36375 +1989 299 19.99 13.99 18.34 0.11 510.75 142.32 36191 +1989 300 13.88 7.88 12.23 0.07 359.69 148.25 36009 +1989 301 11.68 5.68 10.03 0 315.59 198.08 35829 +1989 302 10.96 4.96 9.31 0 302.2 196.34 35650 +1989 303 13.01 7.01 11.36 0 341.66 191.25 35472 +1989 304 12.55 6.55 10.9 0 332.44 189.41 35296 +1989 305 8.27 2.27 6.62 0.04 256.39 143.55 35122 +1989 306 4.99 -1.01 3.34 0 208.72 191.95 34950 +1989 307 7.11 1.11 5.46 0.02 238.56 140.75 34779 +1989 308 7.15 1.15 5.5 0 239.16 185.01 34610 +1989 309 6.93 0.93 5.28 0 235.89 182.87 34444 +1989 310 9.77 3.77 8.12 0 281.14 177.8 34279 +1989 311 8.37 2.37 6.72 0.06 257.98 132.72 34116 +1989 312 9.89 3.89 8.24 0.51 283.2 129.66 33956 +1989 313 8.29 2.29 6.64 0.38 256.71 129.21 33797 +1989 314 13.58 7.58 11.93 0 353.38 164.78 33641 +1989 315 12.75 6.75 11.1 0.71 336.42 122.46 33488 +1989 316 11.21 5.21 9.56 0 306.79 162.83 33337 +1989 317 5.6 -0.4 3.95 0.16 216.95 124.17 33188 +1989 318 3.44 -2.56 1.79 0 188.98 164.66 33042 +1989 319 7.29 1.29 5.64 0 241.26 160.22 32899 +1989 320 5.01 -0.99 3.36 0.13 208.98 120.02 32758 +1989 321 6.26 0.26 4.61 0.65 226.18 117.77 32620 +1989 322 4.97 -1.03 3.32 0 208.45 156.11 32486 +1989 323 2.05 -3.95 0.4 0 172.67 156.24 32354 +1989 324 2.08 -3.92 0.43 0 173.01 154.15 32225 +1989 325 3.91 -2.09 2.26 0 194.79 151.36 32100 +1989 326 3.38 -2.62 1.73 0 188.25 150.2 31977 +1989 327 0.22 -5.78 -1.43 0.12 153.07 112.5 31858 +1989 328 3.55 -2.45 1.9 0 190.33 146.26 31743 +1989 329 5.07 -0.93 3.42 0.06 209.78 107.87 31631 +1989 330 5.85 -0.15 4.2 0 220.41 141.88 31522 +1989 331 8.55 2.55 6.9 0.54 260.86 103.96 31417 +1989 332 9.06 3.06 7.41 0.07 269.18 102.43 31316 +1989 333 8.5 2.5 6.85 0 260.06 135.95 31218 +1989 334 10.49 4.49 8.84 0 293.72 133.23 31125 +1989 335 9.41 3.41 7.76 0 275.02 132.98 31035 +1989 336 5.96 -0.04 4.31 0 221.95 134.42 30949 +1989 337 4.32 -1.68 2.67 0 199.98 133.77 30867 +1989 338 7.52 1.52 5.87 0 244.74 130.77 30790 +1989 339 9.09 3.09 7.44 0 269.68 128.83 30716 +1989 340 7.47 1.47 5.82 0 243.98 129.31 30647 +1989 341 4.83 -1.17 3.18 0 206.6 130.09 30582 +1989 342 1.47 -4.53 -0.18 0 166.24 131.09 30521 +1989 343 3.43 -2.57 1.78 0 188.86 129.28 30465 +1989 344 5.36 -0.64 3.71 0 213.68 127.06 30413 +1989 345 2.08 -3.92 0.43 0 173.01 128.4 30366 +1989 346 -0.68 -6.68 -2.33 0 144.15 129.06 30323 +1989 347 -0.14 -6.14 -1.79 0.02 149.44 139.83 30284 +1989 348 4.12 -1.88 2.47 0.26 197.43 94.39 30251 +1989 349 5.6 -0.4 3.95 0 216.95 124.62 30221 +1989 350 4.11 -1.89 2.46 0.04 197.3 93.85 30197 +1989 351 8.41 2.41 6.76 0 258.62 122.21 30177 +1989 352 9.79 3.79 8.14 0 281.48 121.09 30162 +1989 353 6.45 0.45 4.8 0 228.9 123.38 30151 +1989 354 6.03 0.03 4.38 0 222.93 123.61 30145 +1989 355 6.12 0.12 4.47 0 224.2 123.56 30144 +1989 356 3.69 -2.31 2.04 0 192.05 124.98 30147 +1989 357 3.06 -2.94 1.41 0 184.4 125.37 30156 +1989 358 2.61 -3.39 0.96 0.09 179.09 94.26 30169 +1989 359 5.94 -0.06 4.29 0.21 221.67 92.97 30186 +1989 360 2.65 -3.35 1 0 179.56 126.15 30208 +1989 361 5.17 -0.83 3.52 0 211.12 125.11 30235 +1989 362 6.17 0.17 4.52 0 224.9 124.94 30267 +1989 363 6.01 0.01 4.36 0 222.65 125.62 30303 +1989 364 7.65 1.65 6 0 246.72 124.94 30343 +1989 365 7.03 1.03 5.38 0.01 237.37 94.44 30388 +1990 1 2.69 -3.31 1.04 0 180.03 129.35 30438 +1990 2 -1.52 -7.52 -3.17 0 136.24 131.94 30492 +1990 3 0.46 -5.54 -1.19 0 155.52 132.08 30551 +1990 4 -1.36 -7.36 -3.01 0 137.72 133.76 30614 +1990 5 0.28 -5.72 -1.37 0 153.68 133.74 30681 +1990 6 -0.88 -6.88 -2.53 0 142.23 135.12 30752 +1990 7 1.43 -4.57 -0.22 0 165.8 134.91 30828 +1990 8 0.64 -5.36 -1.01 0 157.39 136.77 30907 +1990 9 4.69 -1.31 3.04 0.11 204.76 101.93 30991 +1990 10 7.42 1.42 5.77 0 243.22 135.4 31079 +1990 11 6.22 0.22 4.57 0 225.61 137.21 31171 +1990 12 6.81 0.81 5.16 0.01 234.13 103.36 31266 +1990 13 6.83 0.83 5.18 0 234.42 139.4 31366 +1990 14 2.68 -3.32 1.03 0 179.91 143.45 31469 +1990 15 1.07 -4.93 -0.58 0 161.92 145.73 31575 +1990 16 0.94 -5.06 -0.71 0.02 160.54 110.32 31686 +1990 17 0.82 -5.18 -0.83 0.13 159.27 111.63 31800 +1990 18 0.7 -5.3 -0.95 0.12 158.01 113.11 31917 +1990 19 2.75 -3.25 1.1 0 180.73 151.67 32038 +1990 20 10.56 4.56 8.91 0 294.97 147.49 32161 +1990 21 10.17 4.17 8.52 0.01 288.07 112.37 32289 +1990 22 8.5 2.5 6.85 0.02 260.06 114.75 32419 +1990 23 6.17 0.17 4.52 0 224.9 156.58 32552 +1990 24 8.07 2.07 6.42 0 253.24 157.15 32688 +1990 25 3.95 -2.05 2.3 0 195.29 162.03 32827 +1990 26 1.12 -4.88 -0.53 0 162.45 165.63 32969 +1990 27 0.11 -5.89 -1.54 0 151.95 168.19 33114 +1990 28 -0.39 -6.39 -2.04 0 146.97 170.67 33261 +1990 29 -1.77 -7.77 -3.42 0 133.96 173.72 33411 +1990 30 -2.42 -8.42 -4.07 0 128.18 176.28 33564 +1990 31 -1.66 -7.66 -3.31 0.1 134.96 173.19 33718 +1990 32 9.04 3.04 7.39 0 268.85 173.2 33875 +1990 33 7.02 1.02 5.37 0.97 237.22 133.2 34035 +1990 34 5.33 -0.67 3.68 1.91 213.27 135.86 34196 +1990 35 4.54 -1.46 2.89 0 202.81 183.87 34360 +1990 36 2.19 -3.81 0.54 0.01 174.26 140.99 34526 +1990 37 2.13 -3.87 0.48 0.03 173.58 142.84 34694 +1990 38 5.54 -0.46 3.89 0 216.13 190.77 34863 +1990 39 5.62 -0.38 3.97 0 217.23 193.31 35035 +1990 40 11.71 5.71 10.06 0 316.16 189.85 35208 +1990 41 13.83 7.83 12.18 0.09 358.63 142.26 35383 +1990 42 12.82 6.82 11.17 0 337.82 193.5 35560 +1990 43 12.15 6.15 10.5 0 324.6 196.99 35738 +1990 44 16.88 10.88 15.23 0 428.23 192.51 35918 +1990 45 17.86 11.86 16.21 0 452.91 193.28 36099 +1990 46 18.66 12.66 17.01 0 473.94 194.32 36282 +1990 47 15.92 9.92 14.27 0 405.18 201.86 36466 +1990 48 14.07 8.07 12.42 0.61 363.73 155.59 36652 +1990 49 9.55 3.55 7.9 0 277.38 216.07 36838 +1990 50 11.26 5.26 9.61 0 307.72 216.63 37026 +1990 51 6.9 0.9 5.25 0 235.45 224.46 37215 +1990 52 8.02 2.02 6.37 0.01 252.46 169.59 37405 +1990 53 5.6 -0.4 3.95 0 216.95 231.47 37596 +1990 54 5.25 -0.75 3.6 0 212.19 234.54 37788 +1990 55 5.14 -0.86 3.49 0 210.72 237.64 37981 +1990 56 6.92 0.92 5.27 0 235.74 238.61 38175 +1990 57 8.92 2.92 7.27 0 266.88 239.28 38370 +1990 58 14.27 8.27 12.62 0 368.03 234.67 38565 +1990 59 14.66 8.66 13.01 0 376.54 236.64 38761 +1990 60 16.09 10.09 14.44 0.04 409.18 177.65 38958 +1990 61 15.32 9.32 13.67 0.01 391.32 180.83 39156 +1990 62 13.2 7.2 11.55 1.03 345.53 185.55 39355 +1990 63 16.08 10.08 14.43 0 408.95 245.28 39553 +1990 64 15.22 9.22 13.57 0 389.05 249.69 39753 +1990 65 15.03 9.03 13.38 0 384.76 252.83 39953 +1990 66 13.01 7.01 11.36 0 341.66 258.97 40154 +1990 67 11 5 9.35 0.01 302.93 198.68 40355 +1990 68 13.68 7.68 12.03 0 355.47 263.49 40556 +1990 69 15.04 9.04 13.39 0.53 384.99 197.69 40758 +1990 70 13.88 7.88 12.23 0.63 359.69 201.35 40960 +1990 71 8.37 2.37 6.72 0.77 257.98 209.74 41163 +1990 72 8.62 2.62 6.97 0 261.99 282.14 41366 +1990 73 8.44 2.44 6.79 0.07 259.1 213.78 41569 +1990 74 15.77 9.77 14.12 0.03 401.68 206.77 41772 +1990 75 16.65 10.65 15 0 422.61 276.48 41976 +1990 76 15.54 9.54 13.89 0.82 396.35 211.02 42179 +1990 77 8.05 2.05 6.4 0.04 252.93 222.18 42383 +1990 78 8.85 2.85 7.2 0.1 265.73 223.38 42587 +1990 79 13 7 11.35 0 341.45 294.01 42791 +1990 80 12.29 6.29 10.64 0 327.32 297.75 42996 +1990 81 12.98 6.98 11.33 0.11 341.05 224.3 43200 +1990 82 9.23 3.23 7.58 0 272 307.78 43404 +1990 83 9.3 3.3 7.65 0 273.17 310.17 43608 +1990 84 10.13 4.13 8.48 0 287.37 311.45 43812 +1990 85 11.86 5.86 10.21 0 319.01 311.09 44016 +1990 86 10.62 4.62 8.97 0.2 296.05 236.67 44220 +1990 87 13.48 7.48 11.83 0 351.3 313 44424 +1990 88 13.9 7.9 12.25 0 360.11 314.49 44627 +1990 89 12.57 6.57 10.92 0 332.83 319.29 44831 +1990 90 13.47 7.47 11.82 0 351.09 319.91 45034 +1990 91 16.49 10.49 14.84 0 418.74 315.59 45237 +1990 92 21.9 15.9 20.25 0.07 567.85 227.01 45439 +1990 93 18.8 12.8 17.15 0 477.71 314.01 45642 +1990 94 18.02 12.02 16.37 0.55 457.05 238.63 45843 +1990 95 13.99 7.99 12.34 1.24 362.02 247.28 46045 +1990 96 14.67 8.67 13.02 0.1 376.76 247.75 46246 +1990 97 12.59 6.59 10.94 0.31 333.23 252.47 46446 +1990 98 7.98 1.98 6.33 1.7 251.83 259.77 46647 +1990 99 10.27 4.27 8.62 0.18 289.83 258.59 46846 +1990 100 11.38 5.38 9.73 0.03 309.95 258.6 47045 +1990 101 10.32 4.32 8.67 0 290.71 348.6 47243 +1990 102 12.51 6.51 10.86 0 331.65 346.49 47441 +1990 103 10.78 4.78 9.13 0 298.93 351.56 47638 +1990 104 8.99 2.99 7.34 0.03 268.03 267.31 47834 +1990 105 13.31 7.31 11.66 1.22 347.78 262.73 48030 +1990 106 11.75 5.75 10.1 0.47 316.91 266.3 48225 +1990 107 6.07 0.07 4.42 0 223.49 365.88 48419 +1990 108 7.67 1.67 6.02 0 247.03 365.4 48612 +1990 109 8.21 2.21 6.56 0.01 255.44 274.66 48804 +1990 110 7.54 1.54 5.89 0 245.04 368.67 48995 +1990 111 10.83 4.83 9.18 0 299.83 364.81 49185 +1990 112 9.44 3.44 7.79 0.1 275.52 276.59 49374 +1990 113 11.95 5.95 10.3 0 320.74 365.56 49561 +1990 114 16.36 10.36 14.71 0 415.61 357.07 49748 +1990 115 17.71 11.71 16.06 0 449.06 354.85 49933 +1990 116 15.8 9.8 14.15 0.23 402.38 270.83 50117 +1990 117 15.43 9.43 13.78 0.29 393.83 272.49 50300 +1990 118 15.03 9.03 13.38 0 384.76 365.6 50481 +1990 119 13.79 7.79 12.14 0 357.78 369.67 50661 +1990 120 11.23 5.23 9.58 0.06 307.16 282.13 50840 +1990 121 19.5 13.5 17.85 0 496.92 356.69 51016 +1990 122 19.95 13.95 18.3 0 509.61 356.41 51191 +1990 123 16.64 10.64 14.99 0.61 422.37 275.39 51365 +1990 124 14.05 8.05 12.4 0.3 363.3 281.02 51536 +1990 125 19.62 13.62 17.97 0 500.28 360.48 51706 +1990 126 16.59 10.59 14.94 0 421.16 370.35 51874 +1990 127 19.03 13.03 17.38 0.52 483.95 273.13 52039 +1990 128 16.85 10.85 15.2 0 427.5 371.51 52203 +1990 129 17.11 11.11 15.46 0 433.92 371.64 52365 +1990 130 19.04 13.04 17.39 0 484.22 366.73 52524 +1990 131 19.16 13.16 17.51 0 487.51 367.13 52681 +1990 132 17.94 11.94 16.29 0 454.98 371.65 52836 +1990 133 21.19 15.19 19.54 0 546.02 361.84 52989 +1990 134 17.4 11.4 15.75 0.57 441.18 280.96 53138 +1990 135 16.03 10.03 14.38 0 407.77 379.07 53286 +1990 136 16.39 10.39 14.74 0 416.33 378.75 53430 +1990 137 24.8 18.8 23.15 0 664.85 350.25 53572 +1990 138 25.83 19.83 24.18 0 702.51 346.2 53711 +1990 139 23.39 17.39 21.74 0 616.06 357.4 53848 +1990 140 24.45 18.45 22.8 0 652.44 353.45 53981 +1990 141 22.7 16.7 21.05 0 593.32 361.01 54111 +1990 142 19.88 13.88 18.23 0 507.62 371.66 54238 +1990 143 20.81 14.81 19.16 0 534.64 369.01 54362 +1990 144 23.42 17.42 21.77 0.28 617.07 269.7 54483 +1990 145 21.42 15.42 19.77 0.57 553.01 275.82 54600 +1990 146 19.44 13.44 17.79 0.01 495.25 281.2 54714 +1990 147 18.69 12.69 17.04 0 474.75 377.8 54824 +1990 148 19.29 13.29 17.64 0 491.09 376.28 54931 +1990 149 19.43 13.43 17.78 0.18 494.97 282.1 55034 +1990 150 17.77 11.77 16.12 0 450.6 381.63 55134 +1990 151 20.51 14.51 18.86 0 525.79 373.22 55229 +1990 152 19.5 13.5 17.85 0 496.92 376.73 55321 +1990 153 20.38 14.38 18.73 0.01 522 280.51 55409 +1990 154 20.19 14.19 18.54 0 516.49 374.98 55492 +1990 155 23.41 17.41 21.76 0 616.73 363.11 55572 +1990 156 26.51 20.51 24.86 0 728.36 349.59 55648 +1990 157 27.44 21.44 25.79 0 765.01 345.13 55719 +1990 158 23.79 17.79 22.14 0 629.58 362.18 55786 +1990 159 22.72 16.72 21.07 0 593.97 366.77 55849 +1990 160 23.52 17.52 21.87 0.05 620.43 272.79 55908 +1990 161 19.88 13.88 18.23 0 507.62 377.37 55962 +1990 162 21.59 15.59 19.94 0.29 558.23 278.54 56011 +1990 163 19.35 13.35 17.7 0.76 492.75 284.55 56056 +1990 164 15.73 9.73 14.08 0.77 400.75 292.57 56097 +1990 165 15.54 9.54 13.89 0.75 396.35 293.02 56133 +1990 166 19.19 13.19 17.54 0 488.33 380.13 56165 +1990 167 19.78 13.78 18.13 0 504.78 378.14 56192 +1990 168 17.99 11.99 16.34 0.04 456.27 287.93 56214 +1990 169 18.47 12.47 16.82 0.12 468.88 286.84 56231 +1990 170 19.36 13.36 17.71 0 493.03 379.62 56244 +1990 171 18.58 12.58 16.93 0 471.8 382.17 56252 +1990 172 20.04 14.04 18.39 0 512.18 377.4 56256 +1990 173 17.17 11.17 15.52 0 435.41 386.37 56255 +1990 174 18.44 12.44 16.79 0 468.08 382.49 56249 +1990 175 22.9 16.9 21.25 0 599.84 366.73 56238 +1990 176 25.13 19.13 23.48 0.1 676.72 267.93 56223 +1990 177 26.99 20.99 25.34 0.27 747.08 261.23 56203 +1990 178 27.17 21.17 25.52 0.74 754.21 260.58 56179 +1990 179 24.88 18.88 23.23 2.24 667.71 268.64 56150 +1990 180 19.8 13.8 18.15 1.46 505.35 283.31 56116 +1990 181 21.79 15.79 20.14 0 564.42 370.62 56078 +1990 182 26.36 20.36 24.71 0 722.59 351.01 56035 +1990 183 29.2 23.2 27.55 0 838.63 336.07 55987 +1990 184 23.72 17.72 22.07 0.21 627.2 271.9 55935 +1990 185 21.12 15.12 19.47 0.59 543.91 279.39 55879 +1990 186 22.67 16.67 21.02 0.16 592.35 274.83 55818 +1990 187 21.02 15.02 19.37 0 540.9 372.45 55753 +1990 188 24.77 18.77 23.12 0 663.78 357.26 55684 +1990 189 22.98 16.98 21.33 0 602.46 364.59 55611 +1990 190 22.25 16.25 20.6 0 578.87 367.08 55533 +1990 191 20.37 14.37 18.72 0 521.7 373.65 55451 +1990 192 17.64 11.64 15.99 0.27 447.27 286.53 55366 +1990 193 19.46 13.46 17.81 0.66 495.8 282.09 55276 +1990 194 21.39 15.39 19.74 0 552.1 369.24 55182 +1990 195 20.9 14.9 19.25 1.77 537.31 278.04 55085 +1990 196 24.72 18.72 23.07 0.26 661.99 266.45 54984 +1990 197 21.7 15.7 20.05 0 561.62 366.97 54879 +1990 198 22.33 16.33 20.68 0.01 581.42 273.14 54770 +1990 199 23.6 17.6 21.95 0.75 623.13 269.11 54658 +1990 200 23.41 17.41 21.76 0 616.73 359.19 54542 +1990 201 21.17 15.17 19.52 0 545.42 367.27 54423 +1990 202 21.75 15.75 20.1 0 563.17 364.6 54301 +1990 203 22.35 16.35 20.7 0 582.06 361.85 54176 +1990 204 25.52 19.52 23.87 0 690.99 348.16 54047 +1990 205 24.74 18.74 23.09 0.04 662.71 263.34 53915 +1990 206 26.98 20.98 25.33 0 746.69 340.25 53780 +1990 207 23.81 17.81 22.16 0 630.27 353.87 53643 +1990 208 26.06 20.06 24.41 0 711.17 343.39 53502 +1990 209 23.37 17.37 21.72 0 615.39 354.38 53359 +1990 210 21.82 15.82 20.17 1.69 565.35 269.78 53213 +1990 211 19.73 13.73 18.08 0 503.37 366.17 53064 +1990 212 22.67 16.67 21.02 0 592.35 354.97 52913 +1990 213 22.04 16.04 20.39 0 572.24 356.6 52760 +1990 214 23.35 17.35 21.7 0 614.73 350.84 52604 +1990 215 23.29 17.29 21.64 0.05 612.72 262.82 52445 +1990 216 20.61 14.61 18.96 0 528.72 359.25 52285 +1990 217 19.68 13.68 18.03 0 501.96 361.43 52122 +1990 218 14.4 8.4 12.75 0 370.85 375.19 51958 +1990 219 17.35 11.35 15.7 0 439.92 366.54 51791 +1990 220 21.08 15.08 19.43 0 542.7 353.96 51622 +1990 221 21.43 15.43 19.78 0 553.32 351.75 51451 +1990 222 20.6 14.6 18.95 0 528.43 353.56 51279 +1990 223 23.01 17.01 21.36 0 603.45 343.8 51105 +1990 224 21.57 15.57 19.92 0.01 557.61 261.03 50929 +1990 225 21.94 15.94 20.29 0.07 569.1 259.2 50751 +1990 226 26.22 20.22 24.57 0.15 717.24 245.39 50572 +1990 227 27.03 21.03 25.38 0.29 748.66 241.68 50392 +1990 228 27.67 21.67 26.02 0.18 774.3 238.52 50210 +1990 229 24.01 18.01 22.36 0 637.13 333.01 50026 +1990 230 22.1 16.1 20.45 0 574.13 338.98 49842 +1990 231 21.08 15.08 19.43 0 542.7 341.07 49656 +1990 232 24.25 18.25 22.6 0 645.44 328.1 49469 +1990 233 25.84 19.84 24.19 0 702.89 320.11 49280 +1990 234 24.83 18.83 23.18 0.01 665.92 242.27 49091 +1990 235 26.71 20.71 25.06 0 736.11 313.51 48900 +1990 236 27.04 21.04 25.39 0 749.06 310.67 48709 +1990 237 26.74 20.74 25.09 0 737.28 310.49 48516 +1990 238 29.52 23.52 27.87 0 852.64 295.47 48323 +1990 239 32.9 26.9 31.25 0.05 1013.05 206.21 48128 +1990 240 27.9 21.9 26.25 0.2 783.7 225.4 47933 +1990 241 25.76 19.76 24.11 0.54 699.9 231.37 47737 +1990 242 26.13 20.13 24.48 0 713.82 305.28 47541 +1990 243 26.04 20.04 24.39 0.15 710.41 227.94 47343 +1990 244 19.74 13.74 18.09 0.18 503.65 243.5 47145 +1990 245 21.44 15.44 19.79 1.59 553.62 238.16 46947 +1990 246 19.72 13.72 18.07 0.8 503.09 240.71 46747 +1990 247 21 15 19.35 0.29 540.3 236.42 46547 +1990 248 21.13 15.13 19.48 0 544.21 312.91 46347 +1990 249 21.24 15.24 19.59 0 547.53 310.55 46146 +1990 250 18.26 12.26 16.61 1.03 463.33 237.96 45945 +1990 251 19.87 13.87 18.22 0.35 507.33 233.03 45743 +1990 252 21.62 15.62 19.97 0 559.15 303.27 45541 +1990 253 19.97 13.97 18.32 0.36 510.18 229.66 45339 +1990 254 22.7 16.7 21.05 0 593.32 295.64 45136 +1990 255 19.87 13.87 18.22 0.51 507.33 226.63 44933 +1990 256 16.48 10.48 14.83 0.37 418.5 231.48 44730 +1990 257 17.08 11.08 15.43 0.49 433.18 228.8 44527 +1990 258 19.01 13.01 17.36 0.32 483.41 223.4 44323 +1990 259 18.14 12.14 16.49 0 460.18 297.72 44119 +1990 260 14.62 8.62 12.97 0 375.66 303.3 43915 +1990 261 14.15 8.15 12.5 0 365.44 301.77 43711 +1990 262 13.5 7.5 11.85 0.02 351.71 225.46 43507 +1990 263 16.01 10.01 14.36 0.18 407.3 219.79 43303 +1990 264 15.15 9.15 13.5 0.11 387.46 219.22 43099 +1990 265 17.11 11.11 15.46 0.19 433.92 214.27 42894 +1990 266 12.32 6.32 10.67 0.1 327.91 219.51 42690 +1990 267 11.22 5.22 9.57 0.58 306.98 218.82 42486 +1990 268 12.97 6.97 11.32 0.03 340.85 214.68 42282 +1990 269 14.48 8.48 12.83 0.25 372.59 210.71 42078 +1990 270 17.17 11.17 15.52 0 435.41 272.8 41875 +1990 271 16.56 10.56 14.91 0.38 420.43 203.65 41671 +1990 272 17.28 11.28 15.63 0 438.16 267.27 41468 +1990 273 16.08 10.08 14.43 0 408.95 267.3 41265 +1990 274 12.2 6.2 10.55 0.21 325.57 203.73 41062 +1990 275 16.05 10.05 14.4 0.66 408.24 196.48 40860 +1990 276 16.02 10.02 14.37 0.04 407.53 194.52 40658 +1990 277 13.68 7.68 12.03 0.38 355.47 195.76 40456 +1990 278 11.86 5.86 10.21 0 319.01 261.06 40255 +1990 279 14.76 8.76 13.11 0 378.75 253.46 40054 +1990 280 16.52 10.52 14.87 0 419.46 247.52 39854 +1990 281 16.91 10.91 15.26 0 428.97 244.07 39654 +1990 282 13.82 7.82 12.17 0 358.42 247 39455 +1990 283 15.52 9.52 13.87 0.87 395.89 180.94 39256 +1990 284 13.89 7.89 12.24 0.02 359.9 180.8 39058 +1990 285 16.49 10.49 14.84 1.2 418.74 175.41 38861 +1990 286 18.29 12.29 16.64 0.77 464.12 170.71 38664 +1990 287 17.11 11.11 15.46 1.07 433.92 170.33 38468 +1990 288 16.11 10.11 14.46 0 409.66 226.25 38273 +1990 289 13.04 7.04 11.39 0 342.26 228.69 38079 +1990 290 9.71 3.71 8.06 0 280.11 230.28 37885 +1990 291 12.92 6.92 11.27 0 339.83 223.32 37693 +1990 292 16.88 10.88 15.23 0 428.23 214.22 37501 +1990 293 16.33 10.33 14.68 0 414.89 212.53 37311 +1990 294 12.5 6.5 10.85 0 331.45 215.65 37121 +1990 295 16.32 10.32 14.67 0 414.65 206.96 36933 +1990 296 16.9 10.9 15.25 0 428.73 203.44 36745 +1990 297 15.99 9.99 14.34 0.12 406.83 151.75 36560 +1990 298 15.95 9.95 14.3 0.01 405.89 149.89 36375 +1990 299 9.78 3.78 8.13 0.2 281.31 154.12 36191 +1990 300 8.45 2.45 6.8 0 259.26 204.22 36009 +1990 301 8.47 2.47 6.82 0.01 259.58 151.25 35829 +1990 302 9.65 3.65 8 0 279.08 197.81 35650 +1990 303 12.08 6.08 10.43 0 323.24 192.43 35472 +1990 304 15.69 9.69 14.04 0 399.82 185.05 35296 +1990 305 7.8 1.8 6.15 0 249.03 191.84 35122 +1990 306 7.3 1.3 5.65 0 241.41 190.03 34950 +1990 307 6.4 0.4 4.75 0 228.18 188.28 34779 +1990 308 7.56 1.56 5.91 0 245.35 184.65 34610 +1990 309 6.51 0.51 4.86 0 229.76 183.22 34444 +1990 310 5.06 -0.94 3.41 0.82 209.65 136.42 34279 +1990 311 4.54 -1.46 2.89 0.24 202.81 135.05 34116 +1990 312 6.01 0.01 4.36 0.13 222.65 132.23 33956 +1990 313 5.39 -0.61 3.74 0 214.09 174.64 33797 +1990 314 6.84 0.84 5.19 0 234.57 171.55 33641 +1990 315 6.99 0.99 5.34 0 236.78 168.89 33488 +1990 316 4.79 -1.21 3.14 0 206.07 168.34 33337 +1990 317 8.49 2.49 6.84 0 259.9 163.25 33188 +1990 318 8.51 2.51 6.86 0.05 260.22 120.68 33042 +1990 319 7.87 1.87 6.22 0.45 250.12 119.81 32899 +1990 320 4.7 -1.3 3.05 1.17 204.89 120.18 32758 +1990 321 2.45 -3.55 0.8 1.59 177.24 119.63 32620 +1990 322 1.8 -4.2 0.15 0.1 169.87 118.51 32486 +1990 323 5.8 -0.2 4.15 0 219.72 153.91 32354 +1990 324 10.55 4.55 8.9 0 294.79 148.01 32225 +1990 325 10.15 4.15 8.5 0 287.72 146.68 32100 +1990 326 11.09 5.09 9.44 0 304.58 144.37 31977 +1990 327 10.3 4.3 8.65 0 290.36 143.29 31858 +1990 328 13.67 7.67 12.02 0 355.26 137.99 31743 +1990 329 13.71 7.71 12.06 0.33 356.1 102.37 31631 +1990 330 11.73 5.73 10.08 1.36 316.53 102.84 31522 +1990 331 16.26 10.26 14.61 0.11 413.22 98.13 31417 +1990 332 17.89 11.89 16.24 0.1 453.69 95.35 31316 +1990 333 19.64 13.64 17.99 0.38 500.84 92.7 31218 +1990 334 16.89 10.89 15.24 0.31 428.48 94.81 31125 +1990 335 7.65 1.65 6 0 246.72 134.33 31035 +1990 336 7.05 1.05 5.4 0 237.67 133.69 30949 +1990 337 5.04 -0.96 3.39 0 209.38 133.34 30867 +1990 338 2.62 -3.38 0.97 0 179.21 133.75 30790 +1990 339 3.55 -2.45 1.9 0 190.33 132.47 30716 +1990 340 5.83 -0.17 4.18 0 220.13 130.39 30647 +1990 341 8.34 2.34 6.69 0.06 257.5 95.83 30582 +1990 342 8.55 2.55 6.9 0 260.86 126.86 30521 +1990 343 11.33 5.33 9.68 0 309.02 123.8 30465 +1990 344 8.28 2.28 6.63 0 256.55 125.13 30413 +1990 345 7.79 1.79 6.14 0 248.88 125.05 30366 +1990 346 9.44 3.44 7.79 0 275.52 123.29 30323 +1990 347 3.67 -2.33 2.02 0.02 191.8 94.83 30284 +1990 348 6.92 0.92 5.27 0.37 235.74 93.12 30251 +1990 349 4.86 -1.14 3.21 0.18 206.99 93.79 30221 +1990 350 3.98 -2.02 2.33 0 195.67 125.21 30197 +1990 351 1.37 -4.63 -0.28 0.02 165.15 94.72 30177 +1990 352 1.44 -4.56 -0.21 0.17 165.91 94.62 30162 +1990 353 4.09 -1.91 2.44 0.64 197.05 93.58 30151 +1990 354 -0.29 -6.29 -1.94 0 147.96 126.81 30145 +1990 355 -1.32 -7.32 -2.97 0 138.09 127.21 30144 +1990 356 1.71 -4.29 0.06 0.13 168.88 94.47 30147 +1990 357 -2.8 -8.8 -4.45 0 124.9 127.83 30156 +1990 358 -4.57 -10.57 -6.22 0 110.58 128.49 30169 +1990 359 -6.29 -12.29 -7.94 0 98.05 129.1 30186 +1990 360 -3.46 -9.46 -5.11 0 119.39 128.63 30208 +1990 361 -3.84 -9.84 -5.49 0.07 116.3 140.7 30235 +1990 362 2.96 -3.04 1.31 0 183.21 126.76 30267 +1990 363 5.26 -0.74 3.61 0 212.33 126.08 30303 +1990 364 2.93 -3.07 1.28 0.29 182.85 95.82 30343 +1990 365 4.8 -1.2 3.15 1.31 206.2 95.48 30388 +1991 1 6.54 0.54 4.89 0.01 230.2 95.35 30438 +1991 2 6.98 0.98 5.33 0 236.63 127.56 30492 +1991 3 5.01 -0.99 3.36 0 208.98 129.75 30551 +1991 4 2.51 -3.49 0.86 0 177.93 132.03 30614 +1991 5 0.7 -5.3 -0.95 0 158.01 133.55 30681 +1991 6 3.84 -2.16 2.19 0 193.91 132.86 30752 +1991 7 1.38 -4.62 -0.27 0 165.26 134.93 30828 +1991 8 -2.29 -8.29 -3.94 0 129.32 137.98 30907 +1991 9 -0.18 -6.18 -1.83 0 149.05 138.4 30991 +1991 10 2.28 -3.72 0.63 0.01 175.29 103.91 31079 +1991 11 5.59 -0.41 3.94 0 216.82 137.62 31171 +1991 12 2.19 -3.81 0.54 0 174.26 140.6 31266 +1991 13 4.56 -1.44 2.91 0 203.07 140.89 31366 +1991 14 1.88 -4.12 0.23 0 170.77 143.87 31469 +1991 15 3.44 -2.56 1.79 0 188.98 144.47 31575 +1991 16 2.43 -3.57 0.78 0 177.01 146.32 31686 +1991 17 4.9 -1.1 3.25 0.55 207.52 109.91 31800 +1991 18 5.34 -0.66 3.69 0 213.41 148.16 31917 +1991 19 4.52 -1.48 2.87 0 202.55 150.61 32038 +1991 20 7.79 1.79 6.14 0 248.88 149.87 32161 +1991 21 7.02 1.02 5.37 0 237.22 152.46 32289 +1991 22 6.81 0.81 5.16 0 234.13 154.35 32419 +1991 23 7.18 1.18 5.53 0.17 239.61 116.86 32552 +1991 24 7.08 1.08 5.43 0.61 238.11 118.46 32688 +1991 25 6.01 0.01 4.36 0 222.65 160.62 32827 +1991 26 3.8 -2.2 2.15 0 193.42 164.06 32969 +1991 27 -2.55 -8.55 -4.2 0.03 127.05 167.01 33114 +1991 28 -1.65 -7.65 -3.3 0.08 135.05 168.45 33261 +1991 29 -1.2 -7.2 -2.85 0.01 139.21 169.95 33411 +1991 30 1.74 -4.26 0.09 0.01 169.21 170.11 33564 +1991 31 1.67 -4.33 0.02 0 168.43 176.62 33718 +1991 32 2.92 -3.08 1.27 0.55 182.73 133.49 33875 +1991 33 -1.16 -7.16 -2.81 0.15 139.58 176.39 34035 +1991 34 3.89 -2.11 2.24 0 194.54 182.18 34196 +1991 35 5.46 -0.54 3.81 0 215.04 183.18 34360 +1991 36 0.73 -5.27 -0.92 0.11 158.33 141.64 34526 +1991 37 4.48 -1.52 2.83 0.02 202.04 141.64 34694 +1991 38 2.09 -3.91 0.44 0 173.13 193.24 34863 +1991 39 4.66 -1.34 3.01 0.04 204.37 145.55 35035 +1991 40 1.74 -4.26 0.09 0 169.21 198.72 35208 +1991 41 1.28 -4.72 -0.37 0 164.17 201.65 35383 +1991 42 -0.17 -6.17 -1.82 0 149.15 205.09 35560 +1991 43 5 -1 3.35 0 208.85 204.29 35738 +1991 44 1.41 -4.59 -0.24 0 165.58 209.46 35918 +1991 45 1.19 -4.81 -0.46 0.1 163.21 159.18 36099 +1991 46 2.76 -3.24 1.11 0 180.85 213.89 36282 +1991 47 -0.61 -6.61 -2.26 0 144.83 218.91 36466 +1991 48 1.29 -4.71 -0.36 0 164.28 220.57 36652 +1991 49 0.5 -5.5 -1.15 0 155.94 223.89 36838 +1991 50 3.42 -2.58 1.77 0.33 188.74 168.4 37026 +1991 51 4.73 -1.27 3.08 0.38 205.29 169.83 37215 +1991 52 0.1 -5.9 -1.55 0 151.85 232.71 37405 +1991 53 0.2 -5.8 -1.45 0 152.86 235.64 37596 +1991 54 -0.77 -6.77 -2.42 0 143.28 239.04 37788 +1991 55 -0.45 -6.45 -2.1 0 146.39 241.88 37981 +1991 56 -0.32 -6.32 -1.97 0 147.66 244.53 38175 +1991 57 -4.87 -10.87 -6.52 0.14 108.3 222.23 38370 +1991 58 -4.55 -10.55 -6.2 0 110.73 287.39 38565 +1991 59 -3.22 -9.22 -4.87 0 121.37 289.3 38761 +1991 60 6.68 0.68 5.03 0 232.23 250.24 38958 +1991 61 10.76 4.76 9.11 0 298.57 248.26 39156 +1991 62 12.91 6.91 11.26 0.11 339.63 185.89 39355 +1991 63 15.48 9.48 13.83 0 394.97 246.41 39553 +1991 64 13.62 7.62 11.97 0.11 354.21 189.36 39753 +1991 65 15.74 9.74 14.09 0 400.98 251.51 39953 +1991 66 15.26 9.26 13.61 0 389.95 255.05 40154 +1991 67 13.36 7.36 11.71 0.02 348.81 195.92 40355 +1991 68 13.51 7.51 11.86 0 351.92 263.78 40556 +1991 69 15.3 9.3 13.65 0 390.86 263.09 40758 +1991 70 14.97 8.97 13.32 0.02 383.42 199.85 40960 +1991 71 18.82 12.82 17.17 0 478.25 261.08 41163 +1991 72 18.31 12.31 16.66 0 464.64 264.96 41366 +1991 73 12.3 6.3 10.65 0 327.52 279.39 41569 +1991 74 9.08 3.08 7.43 0 269.51 286.93 41772 +1991 75 8.81 2.81 7.16 0.01 265.08 217.51 41976 +1991 76 9.21 3.21 7.56 0 271.67 292.09 42179 +1991 77 11.38 5.38 9.73 0 309.95 291.44 42383 +1991 78 13.33 7.33 11.68 0.14 348.2 218.05 42587 +1991 79 9.61 3.61 7.96 0 278.4 299.48 42791 +1991 80 8.79 2.79 7.14 0.24 264.75 227.38 42996 +1991 81 3.88 -2.12 2.23 0 194.41 311.65 43200 +1991 82 3.04 -2.96 1.39 0.12 184.16 236.38 43404 +1991 83 5.97 -0.03 4.32 0.14 222.09 235.92 43608 +1991 84 4.76 -1.24 3.11 0 205.68 318.5 43812 +1991 85 5.51 -0.49 3.86 0 215.72 320.18 44016 +1991 86 7.41 1.41 5.76 0.44 243.07 240.19 44220 +1991 87 12.58 6.58 10.93 0.07 333.03 236.02 44424 +1991 88 9.95 3.95 8.3 0.31 284.24 241.12 44627 +1991 89 7.18 1.18 5.53 0 239.61 327.77 44831 +1991 90 8.51 2.51 6.86 0.04 260.22 246.23 45034 +1991 91 7.47 1.47 5.82 0 243.98 332.05 45237 +1991 92 9.54 3.54 7.89 0 277.21 331.28 45439 +1991 93 8.67 2.67 7.02 0 262.8 334.83 45642 +1991 94 9.78 3.78 8.13 0 281.31 335.28 45843 +1991 95 14.02 8.02 12.37 0 362.66 329.64 46045 +1991 96 11.8 5.8 10.15 0 317.87 336.07 46246 +1991 97 8.81 2.81 7.16 0 265.08 343.14 46446 +1991 98 6.76 0.76 5.11 0 233.39 348.07 46647 +1991 99 8.94 2.94 7.29 0 267.2 346.95 46846 +1991 100 10.01 4.01 8.36 0 285.28 347.19 47045 +1991 101 14.22 8.22 12.57 1 366.95 255.81 47243 +1991 102 18.13 12.13 16.48 0.14 459.92 250.04 47441 +1991 103 17.94 11.94 16.29 0 454.98 335.69 47638 +1991 104 17.17 11.17 15.52 0.42 435.41 254.64 47834 +1991 105 20.42 14.42 18.77 0 523.16 331.9 48030 +1991 106 15.94 9.94 14.29 0.03 405.65 259.49 48225 +1991 107 18.95 12.95 17.3 0 481.77 339.55 48419 +1991 108 22.06 16.06 20.41 0.1 572.86 248.43 48612 +1991 109 16.37 10.37 14.72 0 415.85 349.86 48804 +1991 110 12.44 6.44 10.79 0.01 330.27 270.12 48995 +1991 111 11.7 5.7 10.05 0 315.97 363.17 49185 +1991 112 13.23 7.23 11.58 0.25 346.14 271.2 49374 +1991 113 12.74 6.74 11.09 0 336.22 363.97 49561 +1991 114 13.92 7.92 12.27 0 360.53 362.92 49748 +1991 115 6.29 0.29 4.64 0.13 226.61 283.47 49933 +1991 116 8.22 2.22 6.57 0.17 255.6 282.26 50117 +1991 117 6.27 0.27 4.62 0 226.32 380.59 50300 +1991 118 5.3 -0.7 3.65 0.01 212.87 287.44 50481 +1991 119 7.89 1.89 6.24 0 250.43 380.77 50661 +1991 120 9.77 3.77 8.12 0 281.14 378.86 50840 +1991 121 12.15 6.15 10.5 0 324.6 375.49 51016 +1991 122 12.93 6.93 11.28 0 340.04 375.07 51191 +1991 123 13.23 7.23 11.58 0.14 346.14 281.59 51365 +1991 124 15.88 9.88 14.23 0.51 404.24 277.68 51536 +1991 125 16.06 10.06 14.41 1.2 408.48 278.07 51706 +1991 126 15.77 9.77 14.12 1.13 401.68 279.37 51874 +1991 127 17.86 11.86 16.21 0.16 452.91 275.76 52039 +1991 128 18.3 12.3 16.65 0 464.38 367.37 52203 +1991 129 18.08 12.08 16.43 0.44 458.62 276.64 52365 +1991 130 18 12 16.35 0.6 456.53 277.41 52524 +1991 131 17.86 11.86 16.21 0.52 452.91 278.3 52681 +1991 132 16.87 10.87 15.22 0.05 427.99 281.02 52836 +1991 133 9.81 3.81 8.16 0.91 281.82 293.49 52989 +1991 134 10.55 4.55 8.9 0.13 294.79 293.01 53138 +1991 135 12.17 6.17 10.52 0.2 324.99 291.13 53286 +1991 136 17.23 11.23 15.58 1.52 436.91 282.32 53430 +1991 137 14.21 8.21 12.56 0.46 366.73 288.73 53572 +1991 138 17.35 11.35 15.7 0.82 439.92 283.04 53711 +1991 139 13.86 7.86 12.21 0.32 359.26 290.33 53848 +1991 140 17.75 11.75 16.1 0 450.08 377.4 53981 +1991 141 20.65 14.65 19 0 529.9 368.55 54111 +1991 142 21.75 15.75 20.1 0.1 563.17 273.82 54238 +1991 143 17.66 11.66 16.01 0.73 447.78 284.34 54362 +1991 144 15.36 9.36 13.71 1.88 392.23 289.43 54483 +1991 145 13.37 7.37 11.72 1.65 349.02 293.39 54600 +1991 146 14.99 8.99 13.34 0.71 383.87 290.78 54714 +1991 147 13.93 7.93 12.28 0.07 360.75 293.07 54824 +1991 148 13.49 7.49 11.84 0.26 351.51 294.13 54931 +1991 149 9.77 3.77 8.12 0.35 281.14 300.11 55034 +1991 150 7.66 1.66 6.01 0.31 246.88 303.09 55134 +1991 151 12.92 6.92 11.27 0.03 339.83 295.89 55229 +1991 152 25.56 19.56 23.91 0 692.47 353.06 55321 +1991 153 26.28 20.28 24.63 0.02 719.53 262.44 55409 +1991 154 23.65 17.65 22 0.46 624.82 271.46 55492 +1991 155 22.19 16.19 20.54 1.17 576.97 275.95 55572 +1991 156 19.91 13.91 18.26 0.15 508.47 282.33 55648 +1991 157 17.59 11.59 15.94 0.21 446 287.93 55719 +1991 158 17.15 11.15 15.5 0 434.92 385.36 55786 +1991 159 15.59 9.59 13.94 0.15 397.51 292.41 55849 +1991 160 15.55 9.55 13.9 0.03 396.58 292.63 55908 +1991 161 16.21 10.21 14.56 0.3 412.03 291.36 55962 +1991 162 18.13 12.13 16.48 0 459.92 383.02 56011 +1991 163 17.47 11.47 15.82 0.64 442.95 288.91 56056 +1991 164 16.8 10.8 15.15 0 426.27 387.18 56097 +1991 165 18.42 12.42 16.77 0.01 467.55 286.87 56133 +1991 166 19.83 13.83 18.18 0 506.2 378.03 56165 +1991 167 21.13 15.13 19.48 0 544.21 373.45 56192 +1991 168 19.73 13.73 18.08 0 503.37 378.39 56214 +1991 169 19.18 13.18 17.53 0.06 488.06 285.15 56231 +1991 170 22.9 16.9 21.25 0 599.84 366.81 56244 +1991 171 24.64 18.64 22.99 0.15 659.15 269.69 56252 +1991 172 24.2 18.2 22.55 0.12 643.7 271.11 56256 +1991 173 27.39 21.39 25.74 0.01 763 259.9 56255 +1991 174 25.8 19.8 24.15 0 701.39 354.22 56249 +1991 175 24.17 18.17 22.52 0 642.66 361.49 56238 +1991 176 26.12 20.12 24.47 0 713.44 352.65 56223 +1991 177 27.79 21.79 26.14 0 779.19 344.23 56203 +1991 178 23.29 17.29 21.64 0 612.72 365.05 56179 +1991 179 23.47 17.47 21.82 0.05 618.75 273.16 56150 +1991 180 18.73 12.73 17.08 0.09 475.82 285.91 56116 +1991 181 17.41 11.41 15.76 0.41 441.43 288.86 56078 +1991 182 23.26 17.26 21.61 1.79 611.72 273.56 56035 +1991 183 23.69 17.69 22.04 0.24 626.18 272.1 55987 +1991 184 24.42 18.42 22.77 0.45 651.39 269.67 55935 +1991 185 26.94 20.94 25.29 2.93 745.11 260.84 55879 +1991 186 26.33 20.33 24.68 1.82 721.44 262.89 55818 +1991 187 29.01 23.01 27.36 1.66 830.4 252.38 55753 +1991 188 30.42 24.42 28.77 0.39 893.1 246.12 55684 +1991 189 31.31 25.31 29.66 0 934.69 322.57 55611 +1991 190 26.94 20.94 25.29 0 745.11 346.58 55533 +1991 191 25.39 19.39 23.74 0.11 686.21 265.27 55451 +1991 192 22.06 16.06 20.41 1.15 572.86 275.43 55366 +1991 193 21.31 15.31 19.66 0.26 549.66 277.31 55276 +1991 194 21.94 15.94 20.29 0 569.1 367.21 55182 +1991 195 24.85 18.85 23.2 0.14 666.63 266.31 55085 +1991 196 29.15 23.15 27.5 0 836.46 333.37 54984 +1991 197 25.11 19.11 23.46 0.12 676 264.82 54879 +1991 198 25.61 19.61 23.96 0 694.32 350.43 54770 +1991 199 23.67 17.67 22.02 0.02 625.5 268.89 54658 +1991 200 24.91 18.91 23.26 1.83 668.79 264.64 54542 +1991 201 21.93 15.93 20.28 0.06 568.78 273.37 54423 +1991 202 23.57 17.57 21.92 0 622.12 357.53 54301 +1991 203 24.47 18.47 22.82 0 653.15 353.27 54176 +1991 204 28.93 22.93 27.28 0.04 826.96 248.38 54047 +1991 205 26.09 20.09 24.44 0.93 712.3 258.78 53915 +1991 206 21.8 15.8 20.15 0.04 564.73 271.76 53780 +1991 207 20.41 14.41 18.76 0.07 522.87 274.96 53643 +1991 208 24.79 18.79 23.14 1.05 664.49 261.82 53502 +1991 209 25.63 19.63 23.98 0.11 695.06 258.55 53359 +1991 210 23.46 17.46 21.81 0.37 618.41 265.06 53213 +1991 211 22.84 16.84 21.19 0.06 597.88 266.32 53064 +1991 212 23.85 17.85 22.2 0.16 631.63 262.72 52913 +1991 213 23.78 17.78 22.13 0 629.24 349.84 52760 +1991 214 25.82 19.82 24.17 1.02 702.14 255.25 52604 +1991 215 24.55 18.55 22.9 0 655.97 345.27 52445 +1991 216 25.71 19.71 24.06 0 698.04 339.22 52285 +1991 217 25.25 19.25 23.6 0 681.09 340.41 52122 +1991 218 26.19 20.19 24.54 0.13 716.1 251.56 51958 +1991 219 24.86 18.86 23.21 0.37 666.99 255.23 51791 +1991 220 20.14 14.14 18.49 0.61 515.05 267.85 51622 +1991 221 21.28 15.28 19.63 0 548.75 352.27 51451 +1991 222 20.42 14.42 18.77 1 523.16 265.62 51279 +1991 223 26.46 20.46 24.81 0.24 726.43 246.94 51105 +1991 224 25.13 19.13 23.48 0.04 676.72 250.63 50929 +1991 225 25.33 19.33 23.68 0.16 684.01 249.16 50751 +1991 226 24.35 18.35 22.7 0 648.93 335.24 50572 +1991 227 25.73 19.73 24.08 0 698.78 328.16 50392 +1991 228 22.63 16.63 20.98 0.26 591.05 254.64 50210 +1991 229 24.34 18.34 22.69 0.01 648.58 248.76 50026 +1991 230 21.3 15.3 19.65 0 549.35 341.78 49842 +1991 231 21.27 15.27 19.62 0 548.44 340.43 49656 +1991 232 21.23 15.23 19.58 0 547.23 339.23 49469 +1991 233 23.64 17.64 21.99 0.59 624.48 246.85 49280 +1991 234 23.63 17.63 21.98 0.02 624.15 245.85 49091 +1991 235 24.44 18.44 22.79 0 652.09 323.18 48900 +1991 236 26.35 20.35 24.7 0.12 722.21 235.34 48709 +1991 237 27.55 21.55 25.9 0.33 769.44 230.07 48516 +1991 238 22.89 16.89 21.24 0.6 599.51 243.39 48323 +1991 239 21.17 15.17 19.52 0.01 545.42 246.74 48128 +1991 240 22.63 16.63 20.98 0.29 591.05 241.7 47933 +1991 241 17.77 11.77 16.12 0 450.6 335.65 47737 +1991 242 19.95 13.95 18.3 1.16 509.61 245.76 47541 +1991 243 17.75 11.75 16.1 0.64 450.08 249.06 47343 +1991 244 13.7 7.7 12.05 0 355.89 339.81 47145 +1991 245 17.48 11.48 15.83 0.01 443.2 246.83 46947 +1991 246 19.79 13.79 18.14 0.53 505.07 240.56 46747 +1991 247 20.22 14.22 18.57 0 517.36 317.63 46547 +1991 248 22.41 16.41 20.76 0 583.98 308.72 46347 +1991 249 22.05 16.05 20.4 1.08 572.55 230.94 46146 +1991 250 19.32 13.32 17.67 0.85 491.92 235.78 45945 +1991 251 20.9 14.9 19.25 0 537.31 307.63 45743 +1991 252 25.42 19.42 23.77 0 687.31 289.8 45541 +1991 253 24 18 22.35 0.25 636.78 219.86 45339 +1991 254 20.53 14.53 18.88 0 526.38 302.48 45136 +1991 255 20.24 14.24 18.59 0.07 517.94 225.84 44933 +1991 256 19.57 13.57 17.92 0.17 498.88 225.59 44730 +1991 257 21.21 15.21 19.56 0 546.63 293.92 44527 +1991 258 22.65 16.65 21 0 591.7 287.12 44323 +1991 259 26.86 20.86 25.21 0.96 741.97 202.05 44119 +1991 260 25.11 19.11 23.46 0.22 676 205.5 43915 +1991 261 25.96 19.96 24.31 0.29 707.39 201.38 43711 +1991 262 21.84 15.84 20.19 1.07 565.97 210.31 43507 +1991 263 18.74 12.74 17.09 0.51 476.09 214.99 43303 +1991 264 17.22 11.22 15.57 0.44 436.66 215.84 43099 +1991 265 14.6 8.6 12.95 0.16 375.22 218.26 42894 +1991 266 16.12 10.12 14.47 0.2 409.89 214.06 42690 +1991 267 18.43 12.43 16.78 0 467.81 277.49 42486 +1991 268 22.2 16.2 20.55 0 577.29 264.81 42282 +1991 269 19.21 13.21 17.56 0 488.88 270.58 42078 +1991 270 19.39 13.39 17.74 0 493.86 267.56 41875 +1991 271 15.23 9.23 13.58 0 389.27 274.24 41671 +1991 272 16.28 10.28 14.63 0 413.7 269.41 41468 +1991 273 19.55 13.55 17.9 0 498.32 259.49 41265 +1991 274 16.83 10.83 15.18 0.02 427.01 197.33 41062 +1991 275 13.89 7.89 12.24 0.81 359.9 199.51 40860 +1991 276 14.08 8.08 12.43 0.03 363.94 197.24 40658 +1991 277 11.81 5.81 10.16 0.02 318.06 198.03 40456 +1991 278 11.15 5.15 9.5 0 305.68 262.12 40255 +1991 279 13.28 7.28 11.63 0.01 347.17 192 40054 +1991 280 15.26 9.26 13.61 1.54 389.95 187.44 39854 +1991 281 8.44 2.44 6.79 0.5 259.1 193.04 39654 +1991 282 9.87 3.87 8.22 0.05 282.86 189.61 39455 +1991 283 12.73 6.73 11.08 0 336.02 245.92 39256 +1991 284 11.18 5.18 9.53 0.04 306.24 183.86 39058 +1991 285 12.53 6.53 10.88 0.02 332.04 180.41 38861 +1991 286 16.96 10.96 15.31 0 430.2 230.27 38664 +1991 287 17.67 11.67 16.02 0 448.04 226.01 38468 +1991 288 14.09 8.09 12.44 0 364.16 229.69 38273 +1991 289 14.19 8.19 12.54 0 366.3 226.92 38079 +1991 290 14.33 8.33 12.68 0 369.33 223.86 37885 +1991 291 14.99 8.99 13.34 0 383.87 220.12 37693 +1991 292 15.39 9.39 13.74 0 392.91 216.82 37501 +1991 293 11.15 5.15 9.5 0.53 305.68 165.24 37311 +1991 294 13.13 7.13 11.48 0.12 344.1 161.07 37121 +1991 295 12.92 6.92 11.27 1.66 339.83 159.18 36933 +1991 296 11.11 5.11 9.46 0 304.95 212.05 36745 +1991 297 11.15 5.15 9.5 0.43 305.68 156.96 36560 +1991 298 6.45 0.45 4.8 0.03 228.9 158.75 36375 +1991 299 4.79 -1.21 3.14 0 206.07 210.26 36191 +1991 300 9.09 3.09 7.44 0.31 269.68 152.67 36009 +1991 301 7.68 1.68 6.03 0.05 247.19 151.83 35829 +1991 302 10.73 4.73 9.08 0 298.03 196.61 35650 +1991 303 13.29 7.29 11.64 0 347.37 190.88 35472 +1991 304 12.22 6.22 10.57 0 325.96 189.82 35296 +1991 305 9.73 3.73 8.08 0.26 280.45 142.45 35122 +1991 306 9.68 3.68 8.03 0.51 279.6 140.8 34950 +1991 307 14.71 8.71 13.06 0.43 377.64 134.38 34779 +1991 308 15.75 9.75 14.1 0.04 401.21 131.35 34610 +1991 309 17.41 11.41 15.76 0.11 441.43 127.76 34444 +1991 310 15.18 9.18 13.53 0 388.14 171.34 34279 +1991 311 11.06 5.06 9.41 0.08 304.03 130.72 34116 +1991 312 12.45 6.45 10.8 0 330.46 170.12 33956 +1991 313 10.63 4.63 8.98 0 296.23 170.03 33797 +1991 314 7.18 1.18 5.53 0 239.61 171.27 33641 +1991 315 8.43 2.43 6.78 0 258.94 167.67 33488 +1991 316 8.09 2.09 6.44 0.17 253.55 124.34 33337 +1991 317 9.42 3.42 7.77 0.61 275.19 121.81 33188 +1991 318 8.23 2.23 6.58 0.1 255.76 120.86 33042 +1991 319 9.37 3.37 7.72 0.14 274.35 118.84 32899 +1991 320 8.53 2.53 6.88 0.8 260.54 118 32758 +1991 321 12.06 6.06 10.41 0.03 322.85 113.92 32620 +1991 322 9.95 3.95 8.3 0.01 284.24 114.14 32486 +1991 323 8.24 2.24 6.59 0 255.92 152.06 32354 +1991 324 7.16 1.16 5.51 0.45 239.31 113.15 32225 +1991 325 4.19 -1.81 2.54 0.34 198.32 113.39 32100 +1991 326 3.94 -2.06 2.29 0 195.16 149.87 31977 +1991 327 4.92 -1.08 3.27 0 207.79 147.4 31858 +1991 328 6.42 0.42 4.77 0 228.47 144.42 31743 +1991 329 3.75 -2.25 2.1 0.13 192.79 108.48 31631 +1991 330 4.22 -1.78 2.57 0 198.7 142.91 31522 +1991 331 3.02 -2.98 1.37 0.13 183.92 106.7 31417 +1991 332 -0.23 -6.23 -1.88 0 148.55 142.22 31316 +1991 333 2.77 -3.23 1.12 0 180.96 139.66 31218 +1991 334 7.22 1.22 5.57 0 240.2 135.81 31125 +1991 335 0.26 -5.74 -1.39 0 153.47 138.59 31035 +1991 336 4.83 -1.17 3.18 0 206.6 135.13 30949 +1991 337 9.42 3.42 7.77 0 275.19 130.27 30867 +1991 338 6.77 0.77 5.12 0.1 233.54 98.47 30790 +1991 339 7.85 1.85 6.2 0 249.81 129.76 30716 +1991 340 11.53 5.53 9.88 0 312.76 126.07 30647 +1991 341 8.7 2.7 7.05 0 263.29 127.5 30582 +1991 342 7.71 1.71 6.06 0 247.65 127.47 30521 +1991 343 2.45 -3.55 0.8 0.03 177.24 97.34 30465 +1991 344 -0.33 -6.33 -1.98 0 147.56 129.91 30413 +1991 345 -1.52 -7.52 -3.17 0 136.24 129.95 30366 +1991 346 -3.05 -9.05 -4.7 0 122.79 129.94 30323 +1991 347 2.47 -3.53 0.82 0 177.47 127.06 30284 +1991 348 -1.12 -7.12 -2.77 0 139.96 128.28 30251 +1991 349 -1.85 -7.85 -3.5 0 133.23 128.17 30221 +1991 350 1.68 -4.32 0.03 0.01 168.54 94.78 30197 +1991 351 1.17 -4.83 -0.48 0.01 162.99 94.79 30177 +1991 352 2.41 -3.59 0.76 0.19 176.78 94.28 30162 +1991 353 4.27 -1.73 2.62 0.56 199.34 93.51 30151 +1991 354 5.45 -0.55 3.8 0 214.9 123.97 30145 +1991 355 2.65 -3.35 1 0.06 179.56 94.11 30144 +1991 356 1.81 -4.19 0.16 0.01 169.99 94.44 30147 +1991 357 -0.87 -6.87 -2.52 0.21 142.33 139.78 30156 +1991 358 0.92 -5.08 -0.73 0.1 160.33 139.15 30169 +1991 359 -0.39 -6.39 -2.04 0.6 146.97 141.54 30186 +1991 360 0.97 -5.03 -0.68 0.13 160.86 141.22 30208 +1991 361 0.25 -5.75 -1.4 0.02 153.37 141.63 30235 +1991 362 3.27 -2.73 1.62 0.03 186.92 140.41 30267 +1991 363 4.11 -1.89 2.46 0 197.3 171.6 30303 +1991 364 3.58 -2.42 1.93 0 190.7 171.75 30343 +1991 365 3.41 -2.59 1.76 0 188.62 171.89 30388 +1992 1 6.75 0.75 5.1 0 233.25 126.99 30438 +1992 2 9.48 3.48 7.83 0 276.2 125.74 30492 +1992 3 6.55 0.55 4.9 0 230.34 128.78 30551 +1992 4 7.07 1.07 5.42 0 237.97 129.34 30614 +1992 5 6.71 0.71 5.06 0 232.66 130.22 30681 +1992 6 10.05 4.05 8.4 0 285.98 128.61 30752 +1992 7 5.87 -0.13 4.22 0 220.69 132.44 30828 +1992 8 7.97 1.97 6.32 0.17 251.67 99.36 30907 +1992 9 1.06 -4.94 -0.59 0 161.81 137.84 30991 +1992 10 0.05 -5.95 -1.6 0 151.35 139.61 31079 +1992 11 -0.34 -6.34 -1.99 0 147.46 140.78 31171 +1992 12 -0.75 -6.75 -2.4 0 143.48 141.98 31266 +1992 13 3.57 -2.43 1.92 0 190.57 141.47 31366 +1992 14 8.75 2.75 7.1 0 264.1 139.42 31469 +1992 15 11.47 5.47 9.82 0 311.63 138.45 31575 +1992 16 11.23 5.23 9.58 0.04 307.16 104.94 31686 +1992 17 9.81 3.81 8.16 0.41 281.82 107.15 31800 +1992 18 4.38 -1.62 2.73 0 200.75 148.77 31917 +1992 19 5.18 -0.82 3.53 0 211.25 150.19 32038 +1992 20 4.01 -1.99 2.36 0.05 196.04 114.39 32161 +1992 21 1.97 -4.03 0.32 0 171.77 155.71 32289 +1992 22 0.17 -5.83 -1.48 0 152.56 158.4 32419 +1992 23 3.24 -2.76 1.59 0.25 186.56 118.89 32552 +1992 24 3.67 -2.33 2.02 0.05 191.8 120.24 32688 +1992 25 4.07 -1.93 2.42 0 196.8 161.96 32827 +1992 26 4.45 -1.55 2.8 0 201.65 163.63 32969 +1992 27 -1.15 -7.15 -2.8 0.03 139.68 166.55 33114 +1992 28 -0.88 -6.88 -2.53 0 142.23 210.68 33261 +1992 29 2.7 -3.3 1.05 0 180.14 171.37 33411 +1992 30 -0.14 -6.14 -1.79 0 149.44 175.21 33564 +1992 31 1.75 -4.25 0.1 0 169.32 176.57 33718 +1992 32 5.25 -0.75 3.6 0 212.19 176.38 33875 +1992 33 6.43 0.43 4.78 0 228.61 178.09 34035 +1992 34 12.01 6.01 10.36 0 321.89 174.84 34196 +1992 35 11.33 5.33 9.68 0 309.02 177.69 34360 +1992 36 8.12 2.12 6.47 0.58 254.02 137.57 34526 +1992 37 7.37 1.37 5.72 0 242.46 186.51 34694 +1992 38 9.85 3.85 8.2 0 282.51 186.82 34863 +1992 39 9.12 3.12 7.47 0 270.17 190.14 35035 +1992 40 7.11 1.11 5.46 0.05 238.56 145.98 35208 +1992 41 4.99 -1.01 3.34 0.34 208.72 149.28 35383 +1992 42 4.22 -1.78 2.57 0 198.7 202.19 35560 +1992 43 2.07 -3.93 0.42 0 172.9 206.44 35738 +1992 44 3.98 -2.02 2.33 0 195.67 207.66 35918 +1992 45 5.42 -0.58 3.77 0 214.49 209.13 36099 +1992 46 5.86 -0.14 4.21 0.06 220.55 158.57 36282 +1992 47 7.25 1.25 5.6 0 240.65 212.96 36466 +1992 48 5.23 -0.77 3.58 0 211.92 217.6 36652 +1992 49 8.12 2.12 6.47 0 254.02 217.63 36838 +1992 50 10.69 4.69 9.04 0 297.3 217.34 37026 +1992 51 7.02 1.02 5.37 0 237.22 224.34 37215 +1992 52 7.31 1.31 5.66 0 241.56 226.86 37405 +1992 53 7.14 1.14 5.49 0 239.01 229.98 37596 +1992 54 6.25 0.25 4.6 0 226.04 233.61 37788 +1992 55 7.25 1.25 5.6 0.02 240.65 176.69 37981 +1992 56 4.89 -1.11 3.24 0.06 207.39 180.42 38175 +1992 57 7.04 1.04 5.39 0.07 237.52 181.02 38370 +1992 58 6.5 0.5 4.85 0 229.62 244.84 38565 +1992 59 6.15 0.15 4.5 0 224.62 247.9 38761 +1992 60 9.43 3.43 7.78 0 275.36 247.1 38958 +1992 61 14.22 8.22 12.57 0 366.95 243.01 39156 +1992 62 12.05 6.05 10.4 0 322.66 249.17 39355 +1992 63 13.38 7.38 11.73 0.19 349.23 187.53 39553 +1992 64 10.82 4.82 9.17 1.75 299.65 192.57 39753 +1992 65 5.03 -0.97 3.38 0 209.25 266.47 39953 +1992 66 5.56 -0.44 3.91 0 216.41 268.69 40154 +1992 67 6.48 0.48 4.83 0.23 229.33 202.97 40355 +1992 68 10.73 4.73 9.08 0.23 298.03 201.1 40556 +1992 69 14.51 8.51 12.86 0 373.25 264.56 40758 +1992 70 12.9 6.9 11.25 0.14 339.43 202.61 40960 +1992 71 12.65 6.65 11 0.09 334.42 205.07 41163 +1992 72 7.23 1.23 5.58 0 240.35 283.87 41366 +1992 73 8.17 2.17 6.52 0.13 254.81 214.04 41569 +1992 74 7.92 1.92 6.27 0.05 250.9 216.33 41772 +1992 75 5.64 -0.36 3.99 0.2 217.5 220.4 41976 +1992 76 4.87 -1.13 3.22 0.21 207.13 223.02 42179 +1992 77 6.05 0.05 4.4 0 223.21 298.69 42383 +1992 78 7.82 1.82 6.17 0 249.34 299.21 42587 +1992 79 9.22 3.22 7.57 0 271.84 300.04 42791 +1992 80 10.84 4.84 9.19 0 300.02 300.14 42996 +1992 81 7.75 1.75 6.1 0 248.26 307.16 43200 +1992 82 12.73 6.73 11.08 0 336.02 302.13 43404 +1992 83 11.04 5.04 9.39 0 303.66 307.48 43608 +1992 84 8.11 2.11 6.46 0 253.87 314.39 43812 +1992 85 9.54 3.54 7.89 0.01 277.21 236.13 44016 +1992 86 6.18 0.18 4.53 0 225.05 321.82 44220 +1992 87 5.35 -0.65 3.7 0 213.54 325.37 44424 +1992 88 6.61 0.61 4.96 0.52 231.21 244.66 44627 +1992 89 7.92 1.92 6.27 0 250.9 326.77 44831 +1992 90 9.61 3.61 7.96 0.72 278.4 245 45034 +1992 91 11.96 5.96 10.31 0.49 320.93 243.73 45237 +1992 92 13.37 7.37 11.72 0 349.02 324.54 45439 +1992 93 13.97 7.97 12.32 0 361.6 325.51 45642 +1992 94 14.95 8.95 13.3 0 382.97 325.55 45843 +1992 95 17.77 11.77 16.12 0 450.6 320.89 46045 +1992 96 14.25 8.25 12.6 0 367.6 331.24 46246 +1992 97 15.93 9.93 14.28 0 405.42 329.49 46446 +1992 98 11.8 5.8 10.15 0 317.87 340.08 46647 +1992 99 10.77 4.77 9.12 0 298.75 343.93 46846 +1992 100 13.06 7.06 11.41 0.33 342.67 256.19 47045 +1992 101 17 11 15.35 0 431.19 334.53 47243 +1992 102 15.26 9.26 13.61 0 389.95 340.63 47441 +1992 103 20.18 14.18 18.53 0.62 516.2 246.89 47638 +1992 104 18.16 12.16 16.51 0.22 460.7 252.64 47834 +1992 105 21.87 15.87 20.22 0.01 566.91 245.34 48030 +1992 106 17.46 11.46 15.81 0 442.7 342.1 48225 +1992 107 15.25 9.25 13.6 0 389.73 349.3 48419 +1992 108 15.65 9.65 14 0 398.89 350.06 48612 +1992 109 14.48 8.48 12.83 0.18 372.59 265.79 48804 +1992 110 11.27 5.27 9.62 0 307.9 362.43 48995 +1992 111 18.47 12.47 16.82 0 468.88 347.06 49185 +1992 112 16.07 10.07 14.42 0 408.71 355.02 49374 +1992 113 14.23 8.23 12.58 0.29 367.17 270.56 49561 +1992 114 15.96 9.96 14.31 0 406.12 358.09 49748 +1992 115 14.23 8.23 12.58 0 367.17 363.65 49933 +1992 116 12.04 6.04 10.39 0 322.47 369.55 50117 +1992 117 12.93 6.93 11.28 1.05 340.04 276.77 50300 +1992 118 9.06 3.06 7.41 0.14 269.18 283.25 50481 +1992 119 9.32 3.32 7.67 1.6 273.51 283.83 50661 +1992 120 12.58 6.58 10.93 0.03 333.03 280.1 50840 +1992 121 16.24 10.24 14.59 0 412.74 366.04 51016 +1992 122 16.21 10.21 14.56 0 412.03 367.3 51191 +1992 123 12.49 6.49 10.84 0 331.25 377.04 51365 +1992 124 14.08 8.08 12.43 0 363.94 374.63 51536 +1992 125 13.75 7.75 12.1 0 356.94 376.37 51706 +1992 126 15.67 9.67 14.02 0.39 399.35 279.57 51874 +1992 127 19.91 13.91 18.26 0 508.47 361.37 52039 +1992 128 20.12 14.12 18.47 1.58 514.48 271.24 52203 +1992 129 19.9 13.9 18.25 0.82 508.19 272.4 52365 +1992 130 18.62 12.62 16.97 0 472.87 368.02 52524 +1992 131 18.09 12.09 16.44 0.12 458.88 277.8 52681 +1992 132 18.2 12.2 16.55 0 461.75 370.88 52836 +1992 133 20.75 14.75 19.1 0 532.86 363.37 52989 +1992 134 18.84 12.84 17.19 0 478.79 370.33 53138 +1992 135 18.28 12.28 16.63 0.05 463.85 279.55 53286 +1992 136 18.93 12.93 17.28 0 481.23 371.36 53430 +1992 137 18.87 12.87 17.22 0 479.6 372.24 53572 +1992 138 16.2 10.2 14.55 0 411.79 380.57 53711 +1992 139 15.59 9.59 13.94 0 397.51 382.87 53848 +1992 140 16.2 10.2 14.55 0 411.79 381.75 53981 +1992 141 18.66 12.66 17.01 0 473.94 375.08 54111 +1992 142 19.64 13.64 17.99 0 500.84 372.45 54238 +1992 143 21.34 15.34 19.69 0 550.57 367.12 54362 +1992 144 21.07 15.07 19.42 0 542.4 368.55 54483 +1992 145 20 14 18.35 0 511.04 372.72 54600 +1992 146 17.84 11.84 16.19 0.24 452.4 284.93 54714 +1992 147 21.55 15.55 19.9 0 557 368.11 54824 +1992 148 20.34 14.34 18.69 0 520.83 372.78 54931 +1992 149 25.8 19.8 24.15 0 701.39 351.17 55034 +1992 150 23.43 17.43 21.78 0 617.4 361.82 55134 +1992 151 23.59 17.59 21.94 0 622.79 361.55 55229 +1992 152 24.09 18.09 22.44 0.23 639.89 269.67 55321 +1992 153 21.98 15.98 20.33 0 570.35 368.24 55409 +1992 154 19.4 13.4 17.75 0.56 494.14 283.21 55492 +1992 155 21.28 15.28 19.63 0 548.75 371.33 55572 +1992 156 24.3 18.3 22.65 0 647.19 359.69 55648 +1992 157 21.26 15.26 19.61 0 548.14 371.88 55719 +1992 158 24.79 18.79 23.14 0 664.49 357.89 55786 +1992 159 22.99 16.99 21.34 0 602.79 365.69 55849 +1992 160 20.66 14.66 19.01 0 530.2 374.62 55908 +1992 161 15.35 9.35 13.7 0 392 390.76 55962 +1992 162 16.07 10.07 14.42 1.63 408.71 291.69 56011 +1992 163 17.27 11.27 15.62 0 437.91 385.79 56056 +1992 164 18.8 12.8 17.15 0.53 477.71 285.9 56097 +1992 165 17.51 11.51 15.86 1.2 443.96 288.92 56133 +1992 166 18.75 12.75 17.1 0 476.36 381.54 56165 +1992 167 20.42 14.42 18.77 0.55 523.16 281.97 56192 +1992 168 19.62 13.62 17.97 0.75 500.28 284.06 56214 +1992 169 21.01 15.01 19.36 0 540.6 373.97 56231 +1992 170 22.6 16.6 20.95 0 590.08 368 56244 +1992 171 22.93 16.93 21.28 0 600.82 366.75 56252 +1992 172 21.52 15.52 19.87 0 556.07 372.16 56256 +1992 173 22.51 16.51 20.86 0.02 587.18 276.29 56255 +1992 174 25.93 19.93 24.28 0.08 706.27 265.21 56249 +1992 175 24.48 18.48 22.83 0.04 653.5 270.11 56238 +1992 176 27.42 21.42 25.77 0.07 764.2 259.68 56223 +1992 177 27.71 21.71 26.06 1.15 775.93 258.49 56203 +1992 178 27.29 21.29 25.64 0.01 758.99 260.12 56179 +1992 179 25.37 19.37 23.72 0.39 685.47 266.98 56150 +1992 180 24.92 18.92 23.27 0.38 669.14 268.41 56116 +1992 181 24.04 18.04 22.39 2.45 638.16 271.24 56078 +1992 182 23.19 17.19 21.54 0.5 609.4 273.77 56035 +1992 183 24.79 18.79 23.14 0 664.49 358.09 55987 +1992 184 25.91 19.91 24.26 0 705.51 352.83 55935 +1992 185 27.56 21.56 25.91 0.03 769.85 258.49 55879 +1992 186 25.75 19.75 24.1 0.06 699.53 264.94 55818 +1992 187 22.19 16.19 20.54 0.3 576.97 276.09 55753 +1992 188 24.19 18.19 22.54 0 643.35 359.78 55684 +1992 189 21.65 15.65 20 1.62 560.08 277.28 55611 +1992 190 22.47 16.47 20.82 0 585.9 366.23 55533 +1992 191 21.62 15.62 19.97 0.95 559.15 276.89 55451 +1992 192 19.68 13.68 18.03 0 501.96 375.67 55366 +1992 193 22.03 16.03 20.38 0.04 571.92 275.32 55276 +1992 194 19.84 13.84 18.19 0 506.48 374.64 55182 +1992 195 19.99 13.99 18.34 0 510.75 373.86 55085 +1992 196 19.08 13.08 17.43 0.01 485.32 282.33 54984 +1992 197 23.47 17.47 21.82 0.06 618.75 270.07 54879 +1992 198 22.27 16.27 20.62 0.11 579.51 273.31 54770 +1992 199 18.62 12.62 16.97 0.01 472.87 282.47 54658 +1992 200 19.72 13.72 18.07 0.35 503.09 279.54 54542 +1992 201 22.48 16.48 20.83 0.01 586.22 271.8 54423 +1992 202 21.35 15.35 19.7 0 550.88 366.06 54301 +1992 203 24.01 18.01 22.36 0 637.13 355.22 54176 +1992 204 25.96 19.96 24.31 0 707.39 346.14 54047 +1992 205 24.35 18.35 22.7 1 648.93 264.59 53915 +1992 206 25.51 19.51 23.86 0 690.62 347.17 53780 +1992 207 29.17 23.17 27.52 0.1 837.32 246.19 53643 +1992 208 29.14 23.14 27.49 0 836.02 327.82 53502 +1992 209 29.66 23.66 28.01 0.57 858.83 243.25 53359 +1992 210 30.64 24.64 28.99 0.01 903.23 238.59 53213 +1992 211 27.94 21.94 26.29 0.04 785.34 249.21 53064 +1992 212 30.38 24.38 28.73 0.04 891.26 238.66 52913 +1992 213 27.2 21.2 25.55 0 755.4 334.53 52760 +1992 214 27.2 21.2 25.55 0 755.4 333.82 52604 +1992 215 27.2 21.2 25.55 0 755.4 333.19 52445 +1992 216 27.2 21.2 25.55 0.12 755.4 249.17 52285 +1992 217 27.2 21.2 25.55 0 755.4 331.39 52122 +1992 218 27.2 21.2 25.55 0.03 755.4 247.97 51958 +1992 219 27.2 21.2 25.55 0 755.4 329.64 51791 +1992 220 27.2 21.2 25.55 0.04 755.4 246.57 51622 +1992 221 27.2 21.2 25.55 0 755.4 327.82 51451 +1992 222 27.2 21.2 25.55 0 755.4 326.84 51279 +1992 223 27.2 21.2 25.55 0 755.4 325.77 51105 +1992 224 27.2 21.2 25.55 0 755.4 324.78 50929 +1992 225 27.2 21.2 25.55 0 755.4 323.7 50751 +1992 226 27.2 21.2 25.55 0.35 755.4 241.97 50572 +1992 227 27.2 21.2 25.55 0 755.4 321.43 50392 +1992 228 27.2 21.2 25.55 0 755.4 320.29 50210 +1992 229 27.2 21.2 25.55 0 755.4 319.13 50026 +1992 230 27.2 21.2 25.55 0.31 755.4 238.46 49842 +1992 231 27.2 21.2 25.55 0 755.4 316.56 49656 +1992 232 27.2 21.2 25.55 0 755.4 315.3 49469 +1992 233 27.2 21.2 25.55 0 755.4 313.97 49280 +1992 234 27.2 21.2 25.55 0 755.4 312.65 49091 +1992 235 27.2 21.2 25.55 0 755.4 311.26 48900 +1992 236 27.2 21.2 25.55 0 755.4 309.94 48709 +1992 237 27.2 21.2 25.55 0 755.4 308.4 48516 +1992 238 27.2 21.2 25.55 0.09 755.4 230.13 48323 +1992 239 27.2 21.2 25.55 0 755.4 305.43 48128 +1992 240 27.2 21.2 25.55 0 755.4 303.79 47933 +1992 241 27.2 21.2 25.55 0 755.4 302.19 47737 +1992 242 27.2 21.2 25.55 0 755.4 300.57 47541 +1992 243 27.2 21.2 25.55 0 755.4 298.84 47343 +1992 244 20.5 14.5 18.85 0.31 525.5 241.76 47145 +1992 245 18.89 12.89 17.24 0 480.14 325.29 46947 +1992 246 19.47 13.47 17.82 0 496.08 321.68 46747 +1992 247 20.09 14.09 18.44 0.02 513.62 238.51 46547 +1992 248 20.89 14.89 19.24 0 537.02 313.67 46347 +1992 249 23.2 17.2 21.55 0 609.73 303.99 46146 +1992 250 19.18 13.18 17.53 0 488.06 314.77 45945 +1992 251 19.76 13.76 18.11 0 504.22 311.03 45743 +1992 252 19.52 13.52 17.87 0.56 497.48 232.18 45541 +1992 253 16.48 10.48 14.83 0.14 418.5 236.5 45339 +1992 254 17.09 11.09 15.44 0.51 433.42 233.8 45136 +1992 255 12.05 6.05 10.4 0.01 322.66 240.01 44933 +1992 256 12.75 6.75 11.1 0 336.42 316.41 44730 +1992 257 15.78 9.78 14.13 0 401.91 308.06 44527 +1992 258 21.3 15.3 19.65 0.21 549.35 218.53 44323 +1992 259 23.12 17.12 21.47 0.2 607.08 212.43 44119 +1992 260 16.16 10.16 14.51 0 410.84 300.03 43915 +1992 261 20.43 14.43 18.78 0 523.45 286.85 43711 +1992 262 18.57 12.57 16.92 0 471.54 289.51 43507 +1992 263 22.98 16.98 21.33 1.01 602.46 205.86 43303 +1992 264 21.04 15.04 19.39 0.18 541.5 208.44 43099 +1992 265 19.4 13.4 17.75 0 494.14 280.1 42894 +1992 266 17.52 11.52 15.87 0 444.22 282.29 42690 +1992 267 19.78 13.78 18.13 0.76 504.78 205.56 42486 +1992 268 21.92 15.92 20.27 0 568.47 265.64 42282 +1992 269 21.34 15.34 19.69 0 550.57 264.91 42078 +1992 270 24.78 18.78 23.13 0 664.13 251.72 41875 +1992 271 27.44 21.44 25.79 0.15 765.01 179.71 41671 +1992 272 21.69 15.69 20.04 0 561.31 256.26 41468 +1992 273 20.3 14.3 18.65 0.03 519.67 193.19 41265 +1992 274 17.66 11.66 16.01 0 447.78 261.32 41062 +1992 275 14.94 8.94 13.29 0.73 382.75 198.09 40860 +1992 276 14.95 8.95 13.3 0.35 382.97 196.06 40658 +1992 277 11.91 5.91 10.26 0.37 319.97 197.91 40456 +1992 278 11.45 5.45 9.8 0.7 311.26 196.26 40255 +1992 279 10.38 4.38 8.73 1.12 291.77 195.27 40054 +1992 280 9.12 3.12 7.47 0.07 270.17 194.49 39854 +1992 281 8.9 2.9 7.25 1.94 266.55 192.62 39654 +1992 282 11.38 5.38 9.73 1.62 309.95 188.07 39455 +1992 283 9.5 3.5 7.85 0.63 276.54 187.82 39256 +1992 284 5.2 -0.8 3.55 0.1 211.52 189.05 39058 +1992 285 6.73 0.73 5.08 0.36 232.96 185.87 38861 +1992 286 8.03 2.03 6.38 0.01 252.61 182.71 38664 +1992 287 9.55 3.55 7.9 0 277.38 238.85 38468 +1992 288 9.77 3.77 8.12 0 281.14 235.76 38273 +1992 289 11.82 5.82 10.17 0.36 318.25 172.83 38079 +1992 290 13.67 7.67 12.02 0.03 355.26 168.67 37885 +1992 291 12.87 6.87 11.22 0 338.83 223.4 37693 +1992 292 15.07 9.07 13.42 0.29 385.66 163.01 37501 +1992 293 14.43 8.43 12.78 0.55 371.5 161.76 37311 +1992 294 12.71 6.71 11.06 0 335.62 215.36 37121 +1992 295 16.39 10.39 14.74 0 416.33 206.84 36933 +1992 296 16.49 10.49 14.84 0 418.74 204.15 36745 +1992 297 17.88 11.88 16.23 1.05 453.43 149.27 36560 +1992 298 16.31 10.31 14.66 0 414.42 199.26 36375 +1992 299 16.3 10.3 14.65 0.99 414.18 147.42 36191 +1992 300 15.63 9.63 13.98 0.53 398.43 146.29 36009 +1992 301 10.73 4.73 9.08 0 298.03 199.22 35829 +1992 302 10.16 4.16 8.51 0.22 287.9 147.94 35650 +1992 303 14.09 8.09 12.44 0 364.16 189.79 35472 +1992 304 9.95 3.95 8.3 0 284.24 192.44 35296 +1992 305 2.64 -3.36 0.99 0 179.44 195.93 35122 +1992 306 3.52 -2.48 1.87 0 189.96 193.03 34950 +1992 307 4.24 -1.76 2.59 0 198.96 189.96 34779 +1992 308 4.11 -1.89 2.46 0 197.3 187.41 34610 +1992 309 5.99 -0.01 4.34 0 222.37 183.65 34444 +1992 310 4.17 -1.83 2.52 0 198.07 182.54 34279 +1992 311 3.56 -2.44 1.91 0 190.45 180.75 34116 +1992 312 6.18 0.18 4.53 0 225.05 176.17 33956 +1992 313 7.29 1.29 5.64 0.16 241.26 129.86 33797 +1992 314 11.02 5.02 9.37 0 303.3 167.69 33641 +1992 315 11.21 5.21 9.56 0.02 306.79 123.74 33488 +1992 316 13.94 7.94 12.29 0 360.96 159.73 33337 +1992 317 11.73 5.73 10.08 0.15 316.53 120.09 33188 +1992 318 12.38 6.38 10.73 2.47 329.09 117.83 33042 +1992 319 8.3 2.3 6.65 1 256.87 119.54 32899 +1992 320 5.24 -0.76 3.59 0.51 212.06 119.9 32758 +1992 321 10.18 4.18 8.53 0.11 288.25 115.33 32620 +1992 322 7.92 1.92 6.27 0 250.9 153.93 32486 +1992 323 9.34 3.34 7.69 0.19 273.84 113.35 32354 +1992 324 6.36 0.36 4.71 0 227.61 151.46 32225 +1992 325 13.56 7.56 11.91 0.15 352.96 107.43 32100 +1992 326 15.42 9.42 13.77 0 393.6 139.64 31977 +1992 327 10.69 4.69 9.04 0 297.3 142.93 31858 +1992 328 12.11 6.11 10.46 0.04 323.82 104.72 31743 +1992 329 8.78 2.78 7.13 0.71 264.59 105.87 31631 +1992 330 9.96 3.96 8.31 0.35 284.41 104.06 31522 +1992 331 11.89 5.89 10.24 0.83 319.59 101.76 31417 +1992 332 9.97 3.97 8.32 0 284.59 135.82 31316 +1992 333 7.71 1.71 6.06 0.95 247.65 102.41 31218 +1992 334 7.09 1.09 5.44 1.99 238.26 101.92 31125 +1992 335 3.29 -2.71 1.64 0.27 187.16 102.82 31035 +1992 336 4.51 -1.49 2.86 0.29 202.42 101.49 30949 +1992 337 2.99 -3.01 1.34 0 183.56 134.51 30867 +1992 338 4.86 -1.14 3.21 0.03 206.99 99.38 30790 +1992 339 3.68 -2.32 2.03 0 191.93 132.39 30716 +1992 340 5.98 -0.02 4.33 0.21 222.23 97.72 30647 +1992 341 4.69 -1.31 3.04 0.01 204.76 97.63 30582 +1992 342 2.72 -3.28 1.07 0 180.38 130.48 30521 +1992 343 4.36 -1.64 2.71 0 200.49 128.77 30465 +1992 344 4.68 -1.32 3.03 0.02 204.63 95.59 30413 +1992 345 5.27 -0.73 3.62 0 212.46 126.68 30366 +1992 346 3.56 -2.44 1.91 0 190.45 127.1 30323 +1992 347 2.72 -3.28 1.07 0 180.38 126.93 30284 +1992 348 3.12 -2.88 1.47 0 185.11 126.38 30251 +1992 349 3.99 -2.01 2.34 0.12 195.79 94.16 30221 +1992 350 6.97 0.97 5.32 0.01 236.48 92.57 30197 +1992 351 5.36 -0.64 3.71 0 213.68 124.21 30177 +1992 352 5.61 -0.39 3.96 0 217.09 123.97 30162 +1992 353 3.75 -2.25 2.1 0.72 192.79 93.72 30151 +1992 354 4.28 -1.72 2.63 0.11 199.47 93.48 30145 +1992 355 3.69 -2.31 2.04 0.28 192.05 93.71 30144 +1992 356 0.41 -5.59 -1.24 0.7 155.01 94.91 30147 +1992 357 2.16 -3.84 0.51 0.08 173.92 94.36 30156 +1992 358 1.55 -4.45 -0.1 0 167.11 126.19 30169 +1992 359 3.34 -2.66 1.69 0 187.77 125.43 30186 +1992 360 0.16 -5.84 -1.49 0 152.46 127.29 30208 +1992 361 -2.01 -8.01 -3.66 0 131.8 128.47 30235 +1992 362 1.69 -4.31 0.04 0.04 168.65 95.54 30267 +1992 363 -0.3 -6.3 -1.95 0.21 147.86 140.86 30303 +1992 364 -2.7 -8.7 -4.35 0.57 125.76 143.59 30343 +1992 365 -3.07 -9.07 -4.72 0 122.62 176.76 30388 +1993 1 4.67 -1.33 3.02 0 204.5 173.48 30438 +1993 2 5.43 -0.57 3.78 0 214.63 172.96 30492 +1993 3 3.74 -2.26 2.09 0 192.67 174.3 30551 +1993 4 2.4 -3.6 0.75 0 176.66 175.51 30614 +1993 5 4.7 -1.3 3.05 0.35 204.89 98.61 30681 +1993 6 2.32 -3.68 0.67 0 175.74 133.67 30752 +1993 7 0.79 -5.21 -0.86 0 158.96 135.21 30828 +1993 8 5.41 -0.59 3.76 0 214.36 134.21 30907 +1993 9 1.09 -4.91 -0.56 0.33 162.13 103.37 30991 +1993 10 0.61 -5.39 -1.04 0.1 157.08 104.52 31079 +1993 11 2.83 -3.17 1.18 0.61 181.67 104.44 31171 +1993 12 5.69 -0.31 4.04 0 218.19 138.56 31266 +1993 13 7.79 1.79 6.14 0 248.88 138.71 31366 +1993 14 7.71 1.71 6.06 0.44 247.65 105.17 31469 +1993 15 7.51 1.51 5.86 0 244.59 141.8 31575 +1993 16 4.92 -1.08 3.27 0 207.79 144.86 31686 +1993 17 4.46 -1.54 2.81 0.07 201.78 110.12 31800 +1993 18 7.91 1.91 6.26 0 250.74 146.3 31917 +1993 19 9.13 3.13 7.48 0 270.34 147.22 32038 +1993 20 4.2 -1.8 2.55 0 198.45 152.4 32161 +1993 21 3.31 -2.69 1.66 0.06 187.4 116.21 32289 +1993 22 4.3 -1.7 2.65 0 199.72 156.09 32419 +1993 23 4.74 -1.26 3.09 0 205.42 157.57 32552 +1993 24 4.32 -1.68 2.67 0 199.98 159.91 32688 +1993 25 3.31 -2.69 1.66 0 187.4 162.44 32827 +1993 26 1.28 -4.72 -0.37 0 164.17 165.54 32969 +1993 27 1.54 -4.46 -0.11 0 167 167.43 33114 +1993 28 -0.23 -6.23 -1.88 0.01 148.55 167.66 33261 +1993 29 3.98 -2.02 2.33 0.31 195.67 127.91 33411 +1993 30 6.05 0.05 4.4 0 223.21 171.31 33564 +1993 31 0.73 -5.27 -0.92 0 158.33 177.15 33718 +1993 32 1.16 -4.84 -0.49 0 162.88 179.04 33875 +1993 33 3.01 -2.99 1.36 0 183.8 180.56 34035 +1993 34 1.92 -4.08 0.27 0.17 171.21 137.59 34196 +1993 35 -0.36 -6.36 -2.01 0 147.27 186.91 34360 +1993 36 2.76 -3.24 1.11 0 180.85 187.62 34526 +1993 37 3.6 -2.4 1.95 0 190.94 189.48 34694 +1993 38 0.31 -5.69 -1.34 0 153.98 194.3 34863 +1993 39 2.83 -3.17 1.18 0 181.67 195.38 35035 +1993 40 3.61 -2.39 1.96 0 191.06 197.46 35208 +1993 41 1.12 -4.88 -0.53 0 162.45 201.74 35383 +1993 42 4.38 -1.62 2.73 0 200.75 202.07 35560 +1993 43 4.22 -1.78 2.57 0 198.7 204.9 35738 +1993 44 4.33 -1.67 2.68 0 200.11 207.39 35918 +1993 45 7.76 1.76 6.11 0 248.42 207 36099 +1993 46 7.64 1.64 5.99 0 246.57 209.78 36282 +1993 47 5.61 -0.39 3.96 0.39 217.09 160.85 36466 +1993 48 4.91 -1.09 3.26 0 207.65 217.87 36652 +1993 49 3.32 -2.68 1.67 0 187.52 221.93 36838 +1993 50 2.11 -3.89 0.46 0 173.35 225.5 37026 +1993 51 3.31 -2.69 1.66 0 187.4 227.6 37215 +1993 52 2.47 -3.53 0.82 0.79 177.47 173.31 37405 +1993 53 -3.04 -9.04 -4.69 0 122.87 237.51 37596 +1993 54 -1.84 -7.84 -3.49 0 133.32 239.67 37788 +1993 55 0.74 -5.26 -0.91 0 158.43 241.11 37981 +1993 56 2.31 -3.69 0.66 0 175.63 242.7 38175 +1993 57 6.24 0.24 4.59 0 225.9 242.18 38370 +1993 58 2.7 -3.3 1.05 0 180.14 248.26 38565 +1993 59 3.43 -2.57 1.78 0.13 188.86 187.8 38761 +1993 60 9.31 3.31 7.66 0 273.34 247.25 38958 +1993 61 5.96 -0.04 4.31 0 221.95 253.91 39156 +1993 62 4.17 -1.83 2.52 0.25 198.07 193.82 39355 +1993 63 3.48 -2.52 1.83 0 189.47 262.07 39553 +1993 64 3.36 -2.64 1.71 0.08 188.01 198.83 39753 +1993 65 2.1 -3.9 0.45 0 173.24 269.08 39953 +1993 66 3.2 -2.8 1.55 0.17 186.07 203.2 40154 +1993 67 8.32 2.32 6.67 0.79 257.19 201.37 40355 +1993 68 8.58 2.58 6.93 0 261.35 271.03 40556 +1993 69 10.79 4.79 9.14 0 299.11 270.64 40758 +1993 70 5.95 -0.05 4.3 0.65 221.81 209.68 40960 +1993 71 6.12 0.12 4.47 0.25 224.2 211.74 41163 +1993 72 9.32 3.32 7.67 0.78 273.51 210.91 41366 +1993 73 8.02 2.02 6.37 0 252.46 285.57 41569 +1993 74 11.15 5.15 9.5 0 305.68 283.93 41772 +1993 75 13.1 7.1 11.45 0 343.48 283.4 41976 +1993 76 8.61 2.61 6.96 0.09 261.83 219.68 42179 +1993 77 11.73 5.73 10.08 0.32 316.53 218.15 42383 +1993 78 7.61 1.61 5.96 0 246.11 299.48 42587 +1993 79 7.3 1.3 5.65 0 241.41 302.61 42791 +1993 80 8.1 2.1 6.45 0 253.71 304.12 42996 +1993 81 8.31 2.31 6.66 0 257.03 306.42 43200 +1993 82 5.12 -0.88 3.47 0 210.45 313.01 43404 +1993 83 7.3 1.3 5.65 0 241.41 312.91 43608 +1993 84 8.84 2.84 7.19 0 265.57 313.37 43812 +1993 85 10.45 4.45 8.8 0 293.01 313.43 44016 +1993 86 10.28 4.28 8.63 0 290 316.1 44220 +1993 87 9.15 3.15 7.5 0.02 270.67 240.27 44424 +1993 88 10.56 4.56 8.91 0 294.97 320.52 44627 +1993 89 6.82 0.82 5.17 0 234.27 328.24 44831 +1993 90 4.8 -1.2 3.15 0 206.2 333.1 45034 +1993 91 12.47 6.47 10.82 0 330.86 324.05 45237 +1993 92 12.93 6.93 11.28 0 340.04 325.39 45439 +1993 93 14.51 8.51 12.86 0 373.25 324.38 45642 +1993 94 14.73 8.73 13.08 0 378.08 326.03 45843 +1993 95 17.47 11.47 15.82 0 442.95 321.66 46045 +1993 96 16.62 10.62 14.97 0 421.88 325.84 46246 +1993 97 17.96 11.96 16.31 0 455.5 324.41 46446 +1993 98 12.91 6.91 11.26 0 339.63 337.96 46647 +1993 99 14.63 8.63 12.98 0.01 375.88 252.27 46846 +1993 100 17.55 11.55 15.9 0.16 444.98 248.42 47045 +1993 101 17.42 11.42 15.77 0 441.69 333.44 47243 +1993 102 14.94 8.94 13.29 0.61 382.75 256.02 47441 +1993 103 10.63 4.63 8.98 0 296.23 351.83 47638 +1993 104 7.38 1.38 5.73 0 242.61 358.85 47834 +1993 105 8.64 2.64 6.99 0 262.32 358.78 48030 +1993 106 13.6 7.6 11.95 0 353.8 351.34 48225 +1993 107 11.19 5.19 9.54 0 306.42 357.79 48419 +1993 108 10.77 4.77 9.12 0.58 298.75 270.23 48612 +1993 109 9.78 3.78 8.13 0 281.31 363.67 48804 +1993 110 10.25 4.25 8.6 1.36 289.48 273.21 48995 +1993 111 11.45 5.45 9.8 0 311.26 363.65 49185 +1993 112 15.04 9.04 13.39 0 384.99 357.53 49374 +1993 113 15.42 9.42 13.77 0 393.6 357.95 49561 +1993 114 20.56 14.56 18.91 0 527.26 344.82 49748 +1993 115 18.52 12.52 16.87 0 470.21 352.53 49933 +1993 116 19.44 13.44 17.79 0 495.25 350.94 50117 +1993 117 17.04 11.04 15.39 0 432.18 359.17 50300 +1993 118 15.16 9.16 13.51 0.15 387.69 273.97 50481 +1993 119 11.33 5.33 9.68 0.83 309.02 281.09 50661 +1993 120 12.78 6.78 11.13 0.43 337.02 279.79 50840 +1993 121 16.39 10.39 14.74 0.23 416.33 274.23 51016 +1993 122 14.08 8.08 12.43 0.54 363.94 279.39 51191 +1993 123 16.81 10.81 15.16 0 426.52 366.72 51365 +1993 124 19.63 13.63 17.98 0 500.56 359.49 51536 +1993 125 18.31 12.31 16.66 0.05 464.64 273.38 51706 +1993 126 21.05 15.05 19.4 0.12 541.8 267.5 51874 +1993 127 20.89 14.89 19.24 0 537.02 358.08 52039 +1993 128 26.52 20.52 24.87 0.03 728.75 252.15 52203 +1993 129 23.5 17.5 21.85 0 619.76 350.14 52365 +1993 130 21.86 15.86 20.21 0 566.6 357.18 52524 +1993 131 21.07 15.07 19.42 0 542.4 360.78 52681 +1993 132 23.67 17.67 22.02 0 625.5 351.74 52836 +1993 133 24.78 18.78 23.13 0 664.13 347.75 52989 +1993 134 24.42 18.42 22.77 0 651.39 349.96 53138 +1993 135 24.81 18.81 23.16 0 665.2 348.94 53286 +1993 136 27.26 21.26 25.61 0.04 757.79 253.61 53430 +1993 137 25.24 19.24 23.59 0 680.72 348.31 53572 +1993 138 26.39 20.39 24.74 0 723.74 343.58 53711 +1993 139 26.06 20.06 24.41 0 711.17 345.79 53848 +1993 140 24.18 18.18 22.53 0 643.01 354.6 53981 +1993 141 23.57 17.57 21.92 0 622.12 357.54 54111 +1993 142 21.23 15.23 19.58 0 547.23 366.99 54238 +1993 143 14.94 8.94 13.29 0 382.75 386.49 54362 +1993 144 17.45 11.45 15.8 0 442.44 380.21 54483 +1993 145 18.47 12.47 16.82 0.24 468.88 283.23 54600 +1993 146 18.86 12.86 17.21 0 479.33 376.8 54714 +1993 147 19.4 13.4 17.75 0.37 494.14 281.66 54824 +1993 148 20.5 14.5 18.85 0 525.5 372.23 54931 +1993 149 17.28 11.28 15.63 0 438.16 382.72 55034 +1993 150 14.74 8.74 13.09 0 378.3 389.85 55134 +1993 151 15.3 9.3 13.65 0 390.86 388.84 55229 +1993 152 14.75 8.75 13.1 0.01 378.52 292.75 55321 +1993 153 18.03 12.03 16.38 0.01 457.31 286.2 55409 +1993 154 19.15 13.15 17.5 0 487.23 378.43 55492 +1993 155 18.81 12.81 17.16 0.12 477.98 284.77 55572 +1993 156 17.09 11.09 15.44 0 433.42 385.19 55648 +1993 157 16.71 10.71 15.06 0.5 424.07 289.82 55719 +1993 158 16.62 10.62 14.97 0 421.88 386.86 55786 +1993 159 16.34 10.34 14.69 0.01 415.13 290.91 55849 +1993 160 14.36 8.36 12.71 0 369.98 393.17 55908 +1993 161 18.79 12.79 17.14 0 477.44 380.92 55962 +1993 162 17.81 11.81 16.16 0 451.62 383.99 56011 +1993 163 21.32 15.32 19.67 0 549.96 372.59 56056 +1993 164 20.36 14.36 18.71 1.09 521.41 282.04 56097 +1993 165 23.6 17.6 21.95 0.25 623.13 272.89 56133 +1993 166 24.06 18.06 22.41 0.48 638.85 271.5 56165 +1993 167 26.19 20.19 24.54 0.75 716.1 264.25 56192 +1993 168 28.14 22.14 26.49 1.03 793.6 256.94 56214 +1993 169 28.34 22.34 26.69 0.23 801.94 256.15 56231 +1993 170 26.81 20.81 25.16 0.21 740.02 262.06 56244 +1993 171 27.53 21.53 25.88 0 768.63 345.84 56252 +1993 172 31.41 25.41 29.76 0 939.46 323.71 56256 +1993 173 30.06 24.06 28.41 0 876.72 331.91 56255 +1993 174 27.38 21.38 25.73 0 762.6 346.5 56249 +1993 175 25.16 19.16 23.51 0 677.81 357.13 56238 +1993 176 20.02 14.02 18.37 0 511.61 377.3 56223 +1993 177 24.81 18.81 23.16 0.01 665.2 268.92 56203 +1993 178 22.59 16.59 20.94 0 589.76 367.85 56179 +1993 179 20.51 14.51 18.86 0.01 525.79 281.58 56150 +1993 180 20.76 14.76 19.11 0.78 533.15 280.83 56116 +1993 181 20.11 14.11 18.46 0.73 514.19 282.47 56078 +1993 182 20.11 14.11 18.46 1.14 514.19 282.36 56035 +1993 183 21.66 15.66 20.01 0.05 560.39 278.09 55987 +1993 184 25.02 19.02 23.37 0 672.74 356.91 55935 +1993 185 19.13 13.13 17.48 0.14 486.69 284.48 55879 +1993 186 17.92 11.92 16.27 2.29 454.46 287.1 55818 +1993 187 16.67 10.67 15.02 0.02 423.1 289.67 55753 +1993 188 15.28 9.28 13.63 0.58 390.41 292.25 55684 +1993 189 20.98 14.98 19.33 0.41 539.7 279.11 55611 +1993 190 19.89 13.89 18.24 0.68 507.9 281.66 55533 +1993 191 18.86 12.86 17.21 0.78 479.33 283.97 55451 +1993 192 20.15 14.15 18.5 0.17 515.34 280.57 55366 +1993 193 22.35 16.35 20.7 0 582.06 365.87 55276 +1993 194 25.53 19.53 23.88 0 691.36 352.29 55182 +1993 195 27.19 21.19 25.54 0 755 344.09 55085 +1993 196 29.5 23.5 27.85 0 851.75 331.41 54984 +1993 197 30.59 24.59 28.94 0.88 900.92 243.48 54879 +1993 198 28.79 22.79 27.14 0.07 820.96 250.89 54770 +1993 199 28.92 22.92 27.27 0 826.53 333.49 54658 +1993 200 27.15 21.15 25.5 0 753.41 342.36 54542 +1993 201 26.11 20.11 24.46 0.11 713.06 260.21 54423 +1993 202 24.29 18.29 22.64 0.33 646.84 265.9 54301 +1993 203 26.09 20.09 24.44 0.22 712.3 259.51 54176 +1993 204 24.62 18.62 22.97 0.68 658.44 264.1 54047 +1993 205 20.68 14.68 19.03 0 530.79 366.9 53915 +1993 206 19.55 13.55 17.9 0 498.32 370.13 53780 +1993 207 19.95 13.95 18.3 0.25 509.61 276.12 53643 +1993 208 18.77 12.77 17.12 0 476.9 371.28 53502 +1993 209 18.05 12.05 16.4 0 457.83 372.8 53359 +1993 210 22.57 16.57 20.92 0 589.12 356.9 53213 +1993 211 22.87 16.87 21.22 0 598.86 354.98 53064 +1993 212 24.8 18.8 23.15 0 664.85 346.3 52913 +1993 213 24.7 18.7 23.05 0.86 661.28 259.5 52760 +1993 214 22.4 16.4 20.75 0.82 583.66 265.89 52604 +1993 215 18.9 12.9 17.25 0.71 480.41 274.35 52445 +1993 216 22.73 16.73 21.08 0 594.29 351.6 52285 +1993 217 26.95 20.95 25.3 0 745.51 332.6 52122 +1993 218 24.02 18.02 22.37 0.03 637.47 258.63 51958 +1993 219 22.85 16.85 21.2 1.1 598.2 261.34 51791 +1993 220 19.54 13.54 17.89 1.53 498.04 269.3 51622 +1993 221 23.75 17.75 22.1 1.77 628.22 257.27 51451 +1993 222 24.89 18.89 23.24 0.04 668.07 252.98 51279 +1993 223 22.42 16.42 20.77 0 584.3 346.02 51105 +1993 224 20.88 14.88 19.23 1.36 536.72 262.82 50929 +1993 225 19.78 13.78 18.13 0 504.78 352.9 50751 +1993 226 24.1 18.1 22.45 0 640.23 336.26 50572 +1993 227 22.67 16.67 21.02 0 592.35 340.56 50392 +1993 228 24.15 18.15 22.5 0.38 641.97 250.24 50210 +1993 229 24.85 18.85 23.2 0.93 666.63 247.19 50026 +1993 230 23.05 17.05 21.4 0.44 604.77 251.62 49842 +1993 231 22.3 16.3 20.65 0.92 580.46 252.62 49656 +1993 232 19.32 13.32 17.67 0.12 491.92 259.01 49469 +1993 233 22.27 16.27 20.62 0.35 579.51 250.66 49280 +1993 234 22.19 16.19 20.54 0 576.97 333.11 49091 +1993 235 24.52 18.52 22.87 0 654.91 322.86 48900 +1993 236 25.41 19.41 23.76 0.12 686.94 238.38 48709 +1993 237 26.93 20.93 25.28 0.08 744.72 232.23 48516 +1993 238 27.93 21.93 26.28 0 784.93 303.41 48323 +1993 239 29.03 23.03 27.38 0.1 831.27 222.47 48128 +1993 240 26.92 20.92 25.27 0 744.33 305.06 47933 +1993 241 25.38 19.38 23.73 0.24 685.84 232.56 47737 +1993 242 22.91 16.91 21.26 0 600.17 317.91 47541 +1993 243 22.49 16.49 20.84 0.49 586.54 238.19 47343 +1993 244 23.15 17.15 21.5 0 608.07 313.48 47145 +1993 245 23.15 17.15 21.5 0.3 608.07 233.78 46947 +1993 246 21.08 15.08 19.43 0 542.7 316.79 46747 +1993 247 18.93 12.93 17.28 0.06 481.23 241.03 46547 +1993 248 18.85 12.85 17.2 0 479.06 319.67 46347 +1993 249 21.49 15.49 19.84 0.25 555.15 232.31 46146 +1993 250 22.58 16.58 20.93 0 589.44 304.26 45945 +1993 251 21.4 15.4 19.75 0 552.4 306.08 45743 +1993 252 21.11 15.11 19.46 0.29 543.61 228.66 45541 +1993 253 21.13 15.13 19.48 0.04 544.21 227.06 45339 +1993 254 21.82 15.82 20.17 0.53 565.35 223.88 45136 +1993 255 20.29 14.29 18.64 0.4 519.38 225.73 44933 +1993 256 20.28 14.28 18.63 0.29 519.09 224.08 44730 +1993 257 19.94 13.94 18.29 0 509.33 297.63 44527 +1993 258 18.02 12.02 16.37 0 457.05 300.43 44323 +1993 259 15.55 9.55 13.9 0.02 396.58 227.82 44119 +1993 260 13.59 7.59 11.94 0.08 353.59 229 43915 +1993 261 11.49 5.49 9.84 0.2 312.01 229.94 43711 +1993 262 17.18 11.18 15.53 0.17 435.66 219.67 43507 +1993 263 13.28 7.28 11.63 0.01 347.17 223.89 43303 +1993 264 14.07 8.07 12.42 0 363.73 294.43 43099 +1993 265 17.94 11.94 16.29 0 454.98 283.75 42894 +1993 266 21.25 15.25 19.6 0.16 547.84 204.48 42690 +1993 267 19.75 13.75 18.1 0.24 503.94 205.61 42486 +1993 268 16.57 10.57 14.92 1.24 420.67 209.42 42282 +1993 269 16.09 10.09 14.44 0 409.18 277.74 42078 +1993 270 12.13 6.13 10.48 0.01 324.21 211.83 41875 +1993 271 12.38 6.38 10.73 1.25 329.09 209.53 41671 +1993 272 13.68 7.68 12.03 2.69 355.47 205.79 41468 +1993 273 11.94 5.94 10.29 0.36 320.54 206.07 41265 +1993 274 12.72 6.72 11.07 0 335.82 270.79 41062 +1993 275 11.36 5.36 9.71 0.03 309.57 202.6 40860 +1993 276 15.75 9.75 14.1 0.01 401.21 194.92 40658 +1993 277 13.45 7.45 11.8 0.48 350.68 196.05 40456 +1993 278 12.4 6.4 10.75 0.44 329.48 195.17 40255 +1993 279 14.55 8.55 12.9 0.13 374.12 190.37 40054 +1993 280 14.9 8.9 13.25 0.3 381.86 187.93 39854 +1993 281 10.31 4.31 8.66 0 290.53 255.01 39654 +1993 282 12.72 6.72 11.07 0 335.82 248.76 39455 +1993 283 11.11 5.11 9.46 0 304.95 248.29 39256 +1993 284 13.99 7.99 12.34 0.05 362.02 180.67 39058 +1993 285 15.19 9.19 13.54 0.99 388.37 177.18 38861 +1993 286 14.42 8.42 12.77 0.46 371.28 176.12 38664 +1993 287 14.99 8.99 13.34 0.24 383.87 173.22 38468 +1993 288 13.53 7.53 11.88 0.9 352.34 172.93 38273 +1993 289 11.99 5.99 10.34 0 321.51 230.2 38079 +1993 290 11.4 5.4 9.75 0.03 310.32 171.11 37885 +1993 291 14.13 8.13 12.48 0 365.02 221.5 37693 +1993 292 14.08 8.08 12.43 0 363.94 218.92 37501 +1993 293 11.23 5.23 9.58 2.42 307.16 165.17 37311 +1993 294 14.58 8.58 12.93 0.37 374.78 159.44 37121 +1993 295 13.82 7.82 12.17 0.23 358.42 158.21 36933 +1993 296 12.84 6.84 11.19 0 338.22 209.79 36745 +1993 297 14.68 8.68 13.03 0 376.98 204.42 36560 +1993 298 13.51 7.51 11.86 0.02 351.92 152.68 36375 +1993 299 15.22 9.22 13.57 0.07 389.05 148.72 36191 +1993 300 17.15 11.15 15.5 0.05 434.92 144.41 36009 +1993 301 18.06 12.06 16.41 0 458.09 188.52 35829 +1993 302 16.6 10.6 14.95 0.16 421.4 141.38 35650 +1993 303 16.83 10.83 15.18 0.63 427.01 139.22 35472 +1993 304 15.54 9.54 13.89 0.05 396.35 138.96 35296 +1993 305 2.38 -3.62 0.73 0.2 176.43 147.08 35122 +1993 306 1.99 -4.01 0.34 0.55 172 145.53 34950 +1993 307 3.29 -2.71 1.64 0.09 187.16 142.97 34779 +1993 308 0.68 -5.32 -0.97 0 157.8 189.6 34610 +1993 309 2.18 -3.82 0.53 0 174.15 186.34 34444 +1993 310 0.23 -5.77 -1.42 0 153.17 184.98 34279 +1993 311 4.19 -1.81 2.54 0 198.32 180.32 34116 +1993 312 4.23 -1.77 2.58 0 198.83 177.62 33956 +1993 313 5.17 -0.83 3.52 0 211.12 174.8 33797 +1993 314 2.63 -3.37 0.98 0 179.33 174.53 33641 +1993 315 6.26 0.26 4.61 0 226.18 169.46 33488 +1993 316 7.48 1.48 5.83 0 244.13 166.3 33337 +1993 317 8.26 2.26 6.61 0 256.23 163.45 33188 +1993 318 11.09 5.09 9.44 0.17 304.58 118.86 33042 +1993 319 8.38 2.38 6.73 0.41 258.14 119.49 32899 +1993 320 6.66 0.66 5.01 0.36 231.94 119.13 32758 +1993 321 3.95 -2.05 2.3 0.07 195.29 118.95 32620 +1993 322 1.59 -4.41 -0.06 0.63 167.55 118.6 32486 +1993 323 -2.12 -8.12 -3.77 0 130.82 158.23 32354 +1993 324 0.83 -5.17 -0.82 0 159.38 154.8 32225 +1993 325 5.5 -0.5 3.85 0 215.58 150.34 32100 +1993 326 2.2 -3.8 0.55 0.01 174.37 113.15 31977 +1993 327 5.44 -0.56 3.79 0.41 214.77 110.3 31858 +1993 328 3.42 -2.58 1.77 0.64 188.74 109.75 31743 +1993 329 5.44 -0.56 3.79 0 214.77 143.59 31631 +1993 330 5.23 -0.77 3.58 0.79 211.92 106.71 31522 +1993 331 4.87 -1.13 3.22 2.01 207.13 105.89 31417 +1993 332 8.8 2.8 7.15 0.42 264.91 102.59 31316 +1993 333 3.9 -2.1 2.25 0.95 194.66 104.27 31218 +1993 334 3.44 -2.56 1.79 1.76 188.98 103.64 31125 +1993 335 5.48 -0.52 3.83 0.4 215.31 101.85 31035 +1993 336 7 1 5.35 0.03 236.93 100.3 30949 +1993 337 9.55 3.55 7.9 0.03 277.38 97.62 30867 +1993 338 7.27 1.27 5.62 0.02 240.96 98.21 30790 +1993 339 3.4 -2.6 1.75 0.61 188.49 99.41 30716 +1993 340 3.3 -2.7 1.65 0.02 187.28 98.9 30647 +1993 341 1.11 -4.89 -0.54 0 162.35 132.03 30582 +1993 342 1.73 -4.27 0.08 0 169.1 130.97 30521 +1993 343 0.48 -5.52 -1.17 0 155.73 130.71 30465 +1993 344 7.06 1.06 5.41 0 237.82 125.98 30413 +1993 345 6.29 0.29 4.64 0 226.61 126.05 30366 +1993 346 6.55 0.55 4.9 0.01 230.34 94.01 30323 +1993 347 2.09 -3.91 0.44 0 173.13 127.24 30284 +1993 348 5.62 -0.38 3.97 0 217.23 124.98 30251 +1993 349 7.47 1.47 5.82 0.29 243.98 92.56 30221 +1993 350 8.3 2.3 6.65 0.47 256.87 91.88 30197 +1993 351 8.99 2.99 7.34 0 268.03 121.79 30177 +1993 352 7.62 1.62 5.97 0 246.26 122.68 30162 +1993 353 6.25 0.25 4.6 0.07 226.04 92.63 30151 +1993 354 8.53 2.53 6.88 0 260.54 121.94 30145 +1993 355 6.13 0.13 4.48 0.14 224.34 92.66 30144 +1993 356 2.7 -3.3 1.05 0.53 180.14 94.12 30147 +1993 357 -0.74 -6.74 -2.39 0.19 143.57 139.68 30156 +1993 358 1.27 -4.73 -0.38 0.51 164.07 138.92 30169 +1993 359 1.84 -4.16 0.19 0.21 170.32 138.55 30186 +1993 360 4.39 -1.61 2.74 0.22 200.88 93.92 30208 +1993 361 6.56 0.56 4.91 0.25 230.49 93.19 30235 +1993 362 4.36 -1.64 2.71 0.19 200.49 94.51 30267 +1993 363 3.86 -2.14 2.21 0.17 194.16 95.16 30303 +1993 364 3.59 -2.41 1.94 0.77 190.82 95.56 30343 +1993 365 0.62 -5.38 -1.03 0.6 157.18 97.07 30388 +1994 1 -0.78 -6.78 -2.43 0 143.19 130.91 30438 +1994 2 0.45 -5.55 -1.2 0 155.42 131.14 30492 +1994 3 -1.89 -7.89 -3.54 0 132.87 133.04 30551 +1994 4 4.55 -1.45 2.9 0 202.94 130.93 30614 +1994 5 4.31 -1.69 2.66 0.35 199.85 98.78 30681 +1994 6 4.31 -1.69 2.66 0 199.85 132.6 30752 +1994 7 9.42 3.42 7.77 0 275.19 129.89 30828 +1994 8 6.71 0.71 5.06 0 232.66 133.37 30907 +1994 9 3.75 -2.25 2.1 0.37 192.79 102.34 30991 +1994 10 1.94 -4.06 0.29 0 171.44 138.72 31079 +1994 11 3.88 -2.12 2.23 0.24 194.41 104 31171 +1994 12 8.37 2.37 6.72 0 257.98 136.66 31266 +1994 13 8.26 2.26 6.61 0 256.23 138.35 31366 +1994 14 7.48 1.48 5.83 0 244.13 140.4 31469 +1994 15 7.47 1.47 5.82 0 243.98 141.83 31575 +1994 16 10.79 4.79 9.14 0 299.11 140.34 31686 +1994 17 12.25 6.25 10.6 0 326.54 140.56 31800 +1994 18 12.34 6.34 10.69 0 328.3 142.32 31917 +1994 19 11.67 5.67 10.02 0.58 315.4 108.66 32038 +1994 20 5.91 -0.09 4.26 0.09 221.25 113.45 32161 +1994 21 3.14 -2.86 1.49 0.37 185.35 116.29 32289 +1994 22 8.69 2.69 7.04 0.05 263.12 114.63 32419 +1994 23 13.82 7.82 12.17 0.11 358.42 112.08 32552 +1994 24 7.41 1.41 5.76 0 243.07 157.68 32688 +1994 25 7.92 1.92 6.27 0 250.9 159.14 32827 +1994 26 10.72 4.72 9.07 0 297.85 158.49 32969 +1994 27 6.94 0.94 5.29 0 236.04 163.83 33114 +1994 28 7.71 1.71 6.06 0 247.65 165.39 33261 +1994 29 7.81 1.81 6.16 0.04 249.19 125.75 33411 +1994 30 5.98 -0.02 4.33 0.03 222.23 128.52 33564 +1994 31 2.9 -3.1 1.25 0.14 182.5 131.91 33718 +1994 32 0.44 -5.56 -1.21 0 155.32 179.43 33875 +1994 33 3.37 -2.63 1.72 0 188.13 180.32 34035 +1994 34 5.68 -0.32 4.03 0 218.05 180.87 34196 +1994 35 3.35 -2.65 1.7 0.06 187.89 138.53 34360 +1994 36 3.98 -2.02 2.33 0.16 195.67 140.09 34526 +1994 37 5.76 -0.24 4.11 0.11 219.16 140.9 34694 +1994 38 3.18 -2.82 1.53 0.57 185.83 144.39 34863 +1994 39 1.38 -4.62 -0.27 0.17 165.26 147.23 35035 +1994 40 6.17 0.17 4.52 0.03 224.9 146.6 35208 +1994 41 6.21 0.21 4.56 0 225.47 198.04 35383 +1994 42 7.53 1.53 5.88 0 244.89 199.39 35560 +1994 43 7.88 1.88 6.23 0 250.27 201.74 35738 +1994 44 3.62 -2.38 1.97 0 191.19 207.93 35918 +1994 45 3.32 -2.68 1.67 0 187.52 210.78 36099 +1994 46 4.13 -1.87 2.48 0 197.56 212.86 36282 +1994 47 5.94 -0.06 4.29 0 221.67 214.18 36466 +1994 48 5.34 -0.66 3.69 0 213.41 217.5 36652 +1994 49 9.4 3.4 7.75 0 274.85 216.24 36838 +1994 50 11.62 5.62 9.97 0 314.45 216.16 37026 +1994 51 10.36 4.36 8.71 0 291.42 220.67 37215 +1994 52 12.25 6.25 10.6 0.22 326.54 165.74 37405 +1994 53 10.8 4.8 9.15 0 299.29 225.81 37596 +1994 54 10.18 4.18 8.53 0 288.25 229.3 37788 +1994 55 6.89 0.89 5.24 0 235.3 235.96 37981 +1994 56 4.95 -1.05 3.3 0 208.18 240.51 38175 +1994 57 1.32 -4.68 -0.33 0 164.61 246.35 38370 +1994 58 2.4 -3.6 0.75 0.05 176.66 186.38 38565 +1994 59 4.54 -1.46 2.89 0.26 202.81 187.07 38761 +1994 60 15.04 9.04 13.39 0.01 384.99 179.08 38958 +1994 61 12.84 6.84 11.19 0 338.22 245.24 39156 +1994 62 11.69 5.69 10.04 0 315.78 249.7 39355 +1994 63 14.39 8.39 12.74 0 370.63 248.35 39553 +1994 64 13.87 7.87 12.22 0 359.47 252.06 39753 +1994 65 14.38 8.38 12.73 0 370.41 253.99 39953 +1994 66 14.23 8.23 12.58 0 367.17 256.91 40154 +1994 67 16.93 10.93 15.28 0 429.47 254.56 40355 +1994 68 14.95 8.95 13.3 0 382.97 261.21 40556 +1994 69 17.28 11.28 15.63 0.22 438.16 194.31 40758 +1994 70 14.94 8.94 13.29 0.03 382.75 199.9 40960 +1994 71 16.04 10.04 14.39 0.08 408 200.4 41163 +1994 72 14.93 8.93 13.28 0.5 382.52 204.09 41366 +1994 73 12.47 6.47 10.82 0.72 330.86 209.33 41569 +1994 74 10.21 4.21 8.56 1.27 288.77 214 41772 +1994 75 7.37 1.37 5.72 0 242.46 291.86 41976 +1994 76 6.28 0.28 4.63 0 226.47 295.8 42179 +1994 77 11.11 5.11 9.46 0 304.95 291.86 42383 +1994 78 11.03 5.03 9.38 0 303.48 294.63 42587 +1994 79 8.61 2.61 6.96 0 261.83 300.89 42791 +1994 80 6.22 0.22 4.57 0 225.61 306.47 42996 +1994 81 10.67 4.67 9.02 0 296.95 302.97 43200 +1994 82 10.01 4.01 8.36 0.26 285.28 229.97 43404 +1994 83 7.96 1.96 6.31 0 251.52 312.05 43608 +1994 84 11.5 5.5 9.85 0 312.19 309.24 43812 +1994 85 11.45 5.45 9.8 0 311.26 311.8 44016 +1994 86 11.73 5.73 10.08 0.05 316.53 235.28 44220 +1994 87 13.99 7.99 12.34 0 362.02 312 44424 +1994 88 12.08 6.08 10.43 0 323.24 317.92 44627 +1994 89 12.04 6.04 10.39 1.39 322.47 240.19 44831 +1994 90 14.82 8.82 13.17 0 380.08 317.14 45034 +1994 91 17.79 11.79 16.14 0 451.11 312.4 45237 +1994 92 18.22 12.22 16.57 0 462.28 313.44 45439 +1994 93 16.4 10.4 14.75 0 416.57 320.13 45642 +1994 94 20.9 14.9 19.25 0 537.31 309.95 45843 +1994 95 21.69 15.69 20.04 0.31 561.31 232.1 46045 +1994 96 19.62 13.62 17.97 0.61 500.28 238.38 46246 +1994 97 18.15 12.15 16.5 0.4 460.44 242.93 46446 +1994 98 14.26 8.26 12.61 0 367.81 335.18 46647 +1994 99 13.84 7.84 12.19 0 358.84 338.05 46846 +1994 100 16.96 10.96 15.31 0 430.2 332.75 47045 +1994 101 12.19 6.19 10.54 0 325.37 345.22 47243 +1994 102 11.87 5.87 10.22 0.03 319.2 260.79 47441 +1994 103 13.23 7.23 11.58 0.05 346.14 260.16 47638 +1994 104 14.12 8.12 12.47 0.01 364.8 260.1 47834 +1994 105 14.97 8.97 13.32 0.03 383.42 260.01 48030 +1994 106 9.35 3.35 7.7 1.17 274.01 269.48 48225 +1994 107 9.05 3.05 7.4 0 269.02 361.49 48419 +1994 108 6.92 0.92 5.27 0.23 235.74 274.86 48612 +1994 109 9.29 3.29 7.64 0 273.01 364.49 48804 +1994 110 8.84 2.84 7.19 0.02 265.57 274.99 48995 +1994 111 9.68 3.68 8.03 0 279.6 366.84 49185 +1994 112 9.31 3.31 7.66 0 273.34 369 49374 +1994 113 12.55 6.55 10.9 0.8 332.44 273.27 49561 +1994 114 12.48 6.48 10.83 0.31 331.05 274.5 49748 +1994 115 9.92 3.92 8.27 0 283.72 372.28 49933 +1994 116 10.21 4.21 8.56 0 288.77 373.01 50117 +1994 117 15.46 9.46 13.81 0.07 394.52 272.44 50300 +1994 118 16.09 10.09 14.44 2.13 409.18 272.23 50481 +1994 119 10.53 4.53 8.88 1.39 294.44 282.22 50661 +1994 120 8.74 2.74 7.09 1.36 263.94 285.46 50840 +1994 121 16.26 10.26 14.61 0.43 413.22 274.49 51016 +1994 122 18.77 12.77 17.12 1.62 476.9 270.08 51191 +1994 123 23.61 17.61 21.96 0.35 623.47 258.17 51365 +1994 124 24.9 18.9 23.25 0.68 668.43 254.93 51536 +1994 125 23.19 17.19 21.54 0.22 609.4 260.87 51706 +1994 126 24.08 18.08 22.43 0.28 639.54 258.9 51874 +1994 127 23.76 17.76 22.11 0 628.56 347.34 52039 +1994 128 21.59 15.59 19.94 0 558.23 356.58 52203 +1994 129 17.64 11.64 15.99 0 447.27 370.14 52365 +1994 130 19.14 13.14 17.49 0 486.96 366.41 52524 +1994 131 18.55 12.55 16.9 0.15 471 276.76 52681 +1994 132 14.67 8.67 13.02 0.07 376.76 285.3 52836 +1994 133 15.52 9.52 13.87 0 395.89 378.99 52989 +1994 134 16.02 10.02 14.37 0 407.53 378.4 53138 +1994 135 17.81 11.81 16.16 0.55 451.62 280.59 53286 +1994 136 19 13 17.35 0.72 483.13 278.36 53430 +1994 137 18.46 12.46 16.81 0.02 468.61 280.13 53572 +1994 138 16.61 10.61 14.96 0 421.64 379.46 53711 +1994 139 15.03 9.03 13.38 0 384.76 384.29 53848 +1994 140 15.78 9.78 14.13 0 401.91 382.86 53981 +1994 141 12.63 6.63 10.98 0.08 334.03 293.11 54111 +1994 142 12.62 6.62 10.97 0.38 333.83 293.51 54238 +1994 143 14.67 8.67 13.02 0.62 376.76 290.37 54362 +1994 144 13.78 7.78 12.13 0.01 357.57 292.33 54483 +1994 145 16.11 10.11 14.46 0 409.66 384.42 54600 +1994 146 17.87 11.87 16.22 0 453.17 379.82 54714 +1994 147 24.51 18.51 22.86 0 654.55 356.3 54824 +1994 148 21.87 15.87 20.22 0 566.91 367.3 54931 +1994 149 19.51 13.51 17.86 0 497.2 375.87 55034 +1994 150 19.47 13.47 17.82 0.3 496.08 282.25 55134 +1994 151 20.76 14.76 19.11 0.29 533.15 279.26 55229 +1994 152 24.01 18.01 22.36 0.89 637.13 269.92 55321 +1994 153 23.12 17.12 21.47 0.08 607.08 272.85 55409 +1994 154 20.07 14.07 18.42 0.22 513.04 281.54 55492 +1994 155 19.93 13.93 18.28 0.16 509.04 282.04 55572 +1994 156 18.9 12.9 17.25 0.02 480.41 284.8 55648 +1994 157 15.73 9.73 14.08 0.05 400.75 291.82 55719 +1994 158 16.96 10.96 15.31 0 430.2 385.9 55786 +1994 159 17.33 11.33 15.68 0.23 439.42 288.81 55849 +1994 160 19.9 13.9 18.25 0 508.19 377.23 55908 +1994 161 20.75 14.75 19.1 0.74 532.86 280.78 55962 +1994 162 25.24 19.24 23.59 0.22 680.72 267.3 56011 +1994 163 23.47 17.47 21.82 0 618.75 364.26 56056 +1994 164 24.55 18.55 22.9 0.09 655.97 269.79 56097 +1994 165 21.94 15.94 20.29 0.14 569.1 277.82 56133 +1994 166 21.92 15.92 20.27 0.35 568.47 277.94 56165 +1994 167 19.12 13.12 17.47 1.04 486.41 285.23 56192 +1994 168 19.09 13.09 17.44 0.56 485.59 285.36 56214 +1994 169 17.93 11.93 16.28 0.27 454.72 288.08 56231 +1994 170 19.76 13.76 18.11 0.07 504.22 283.72 56244 +1994 171 20.9 14.9 19.25 1.24 537.31 280.81 56252 +1994 172 25.11 19.11 23.46 0 676 357.48 56256 +1994 173 30.01 24.01 28.36 0.02 874.47 249.15 56255 +1994 174 25.01 19.01 23.36 0.22 672.38 268.38 56249 +1994 175 21.89 15.89 20.24 0 567.53 370.65 56238 +1994 176 24.74 18.74 23.09 0 662.71 358.97 56223 +1994 177 25.2 19.2 23.55 0 679.27 356.82 56203 +1994 178 21.02 15.02 19.37 0 540.9 373.74 56179 +1994 179 21.11 15.11 19.46 0 543.61 373.31 56150 +1994 180 22.53 16.53 20.88 0 587.83 367.86 56116 +1994 181 26.27 20.27 24.62 0.17 719.15 263.69 56078 +1994 182 28.43 22.43 26.78 0.16 805.71 255.35 56035 +1994 183 27.04 21.04 25.39 0.1 749.06 260.63 55987 +1994 184 27.76 21.76 26.11 0 777.97 343.7 55935 +1994 185 29.87 23.87 28.22 0 868.18 332.04 55879 +1994 186 28.47 22.47 26.82 0.01 807.4 254.72 55818 +1994 187 27.49 21.49 25.84 0.29 767.02 258.45 55753 +1994 188 26.58 20.58 24.93 0.74 731.07 261.66 55684 +1994 189 24.07 18.07 22.42 2.16 639.2 270.08 55611 +1994 190 23.26 17.26 21.61 1.22 611.72 272.33 55533 +1994 191 20.94 14.94 19.29 0.86 538.51 278.74 55451 +1994 192 20.42 14.42 18.77 0.23 523.16 279.88 55366 +1994 193 20.02 14.02 18.37 0.19 511.61 280.7 55276 +1994 194 19.22 13.22 17.57 0.01 489.16 282.5 55182 +1994 195 19.14 13.14 17.49 0 486.96 376.65 55085 +1994 196 19.54 13.54 17.89 0.09 498.04 281.21 54984 +1994 197 21.79 15.79 20.14 0.69 564.42 274.98 54879 +1994 198 23.84 17.84 22.19 0 631.29 358.16 54770 +1994 199 20.89 14.89 19.24 1.27 537.02 276.84 54658 +1994 200 23.8 17.8 22.15 0.18 629.93 268.19 54542 +1994 201 20.94 14.94 19.29 0.02 538.51 276.06 54423 +1994 202 24.8 18.8 23.15 0 664.85 352.33 54301 +1994 203 28.66 22.66 27.01 0 815.43 333.11 54176 +1994 204 30.11 24.11 28.46 0 878.98 324.55 54047 +1994 205 30.29 24.29 28.64 0 887.15 323.03 53915 +1994 206 30.68 24.68 29.03 0.31 905.08 240.17 53780 +1994 207 31.3 25.3 29.65 0 934.21 315.87 53643 +1994 208 30.91 24.91 29.26 0.12 915.8 238.24 53502 +1994 209 30.88 24.88 29.23 0 914.39 317.25 53359 +1994 210 30.21 24.21 28.56 0.31 883.51 240.48 53213 +1994 211 33.92 27.92 32.27 0.44 1066.17 222.23 53064 +1994 212 27.81 21.81 26.16 0 780.01 332.19 52913 +1994 213 29.12 23.12 27.47 0.04 835.16 243.45 52760 +1994 214 27.79 21.79 26.14 0 779.19 330.89 52604 +1994 215 27.22 21.22 25.57 2.48 756.2 249.82 52445 +1994 216 27.43 21.43 25.78 0.56 764.6 248.33 52285 +1994 217 26.61 20.61 24.96 1.42 732.23 250.67 52122 +1994 218 27.38 21.38 25.73 0.15 762.6 247.31 51958 +1994 219 27.03 21.03 25.38 0.43 748.66 247.85 51791 +1994 220 22.83 16.83 21.18 0.28 597.55 260.7 51622 +1994 221 20.16 14.16 18.51 0.82 515.63 267.05 51451 +1994 222 20.65 14.65 19 1.12 529.9 265.05 51279 +1994 223 23.85 17.85 22.2 0.6 631.63 255.38 51105 +1994 224 24.67 18.67 23.02 0 660.22 336.12 50929 +1994 225 29.12 23.12 27.47 0.96 835.16 235.52 50751 +1994 226 26.55 20.55 24.9 0.05 729.9 244.26 50572 +1994 227 22.42 16.42 20.77 0.01 584.3 256.11 50392 +1994 228 25.32 19.32 23.67 1.44 683.64 246.59 50210 +1994 229 19.31 13.31 17.66 0.02 491.64 262.11 50026 +1994 230 21.98 15.98 20.33 0 570.35 339.41 49842 +1994 231 24.52 18.52 22.87 0 654.91 328.31 49656 +1994 232 25.69 19.69 24.04 0 697.29 322.11 49469 +1994 233 22.92 16.92 21.27 0 600.49 331.85 49280 +1994 234 27.76 21.76 26.11 0 777.97 310 49091 +1994 235 23.51 17.51 21.86 0 620.09 326.81 48900 +1994 236 22.42 16.42 20.77 1.61 584.3 247.08 48709 +1994 237 19.34 13.34 17.69 0.43 492.47 253.41 48516 +1994 238 18.21 12.21 16.56 0.21 462.01 254.6 48323 +1994 239 24.32 18.32 22.67 0.89 647.88 238.24 48128 +1994 240 26.18 20.18 24.53 0.44 715.72 231.24 47933 +1994 241 23.87 17.87 22.22 0.14 632.32 237.04 47737 +1994 242 24.14 18.14 22.49 0.03 641.62 235.01 47541 +1994 243 25.11 19.11 23.46 0 676 307.76 47343 +1994 244 19.6 13.6 17.95 0.18 499.72 243.81 47145 +1994 245 22.65 16.65 21 0.03 591.7 235.1 46947 +1994 246 23.32 17.32 21.67 0.51 613.72 231.9 46747 +1994 247 19.6 13.6 17.95 0.04 499.72 239.6 46547 +1994 248 20.32 14.32 18.67 0.75 520.25 236.56 46347 +1994 249 18.29 12.29 16.64 0 464.12 319.14 46146 +1994 250 18.42 12.42 16.77 0.07 467.55 237.64 45945 +1994 251 16.72 10.72 15.07 0.01 424.32 239.3 45743 +1994 252 18.3 12.3 16.65 0 464.38 312.91 45541 +1994 253 23.05 17.05 21.4 0 604.77 296.5 45339 +1994 254 20.11 14.11 18.46 0.64 514.19 227.78 45136 +1994 255 22.43 16.43 20.78 0.28 584.62 220.77 44933 +1994 256 26.79 20.79 25.14 0.66 739.23 207.07 44730 +1994 257 21.88 15.88 20.23 0.17 567.22 218.89 44527 +1994 258 18.79 12.79 17.14 0 477.44 298.45 44323 +1994 259 16.96 10.96 15.31 0.08 430.2 225.44 44119 +1994 260 18.05 12.05 16.4 0 457.83 295.58 43915 +1994 261 21.74 15.74 20.09 0 562.86 283 43711 +1994 262 16.66 10.66 15.01 0 422.85 294.08 43507 +1994 263 20.42 14.42 18.77 0 523.16 282.17 43303 +1994 264 19.35 13.35 17.7 0 492.75 282.55 43099 +1994 265 19.33 13.33 17.68 0 492.19 280.28 42894 +1994 266 19.35 13.35 17.7 0 492.75 277.81 42690 +1994 267 22.7 16.7 21.05 0 593.32 265.74 42486 +1994 268 22.42 16.42 20.77 0 584.3 264.15 42282 +1994 269 23.67 17.67 22.02 0 625.5 257.87 42078 +1994 270 26.78 20.78 25.13 0.19 738.84 183.4 41875 +1994 271 27.45 21.45 25.8 0 765.41 239.57 41671 +1994 272 25.52 19.52 23.87 0 690.99 244.2 41468 +1994 273 21.44 15.44 19.79 0 553.62 254.54 41265 +1994 274 13.63 7.63 11.98 0.03 354.42 201.94 41062 +1994 275 14.18 8.18 12.53 0 366.09 265.51 40860 +1994 276 11.76 5.76 10.11 0 317.1 266.8 40658 +1994 277 12.32 6.32 10.67 0.2 327.91 197.43 40456 +1994 278 11.09 5.09 9.44 0.31 304.58 196.65 40255 +1994 279 7.56 1.56 5.91 0.14 245.35 197.94 40054 +1994 280 9.95 3.95 8.3 0.01 284.24 193.69 39854 +1994 281 11.98 5.98 10.33 0 321.31 252.64 39654 +1994 282 12.02 6.02 10.37 0 322.08 249.82 39455 +1994 283 14 8 12.35 0.16 362.24 182.92 39256 +1994 284 13.1 7.1 11.45 0 343.48 242.32 39058 +1994 285 15.98 9.98 14.33 2.18 406.59 176.12 38861 +1994 286 16.24 10.24 14.59 0.8 412.74 173.73 38664 +1994 287 12.78 6.78 11.13 0.49 337.02 175.86 38468 +1994 288 15.34 9.34 13.69 0.02 391.77 170.71 38273 +1994 289 12.76 6.76 11.11 0 336.62 229.1 38079 +1994 290 10.94 4.94 9.29 0 301.83 228.75 37885 +1994 291 11.14 5.14 9.49 0 305.5 225.77 37693 +1994 292 10.67 4.67 9.02 0 296.95 223.67 37501 +1994 293 14.63 8.63 12.98 0.39 375.88 161.52 37311 +1994 294 13.09 7.09 11.44 0.71 343.28 161.11 37121 +1994 295 14.73 8.73 13.08 0.34 378.08 157.17 36933 +1994 296 8.43 2.43 6.78 0.11 258.94 161.34 36745 +1994 297 5.21 -0.79 3.56 0 211.65 215.4 36560 +1994 298 8.98 2.98 7.33 0 267.86 209.16 36375 +1994 299 7.82 1.82 6.17 0.24 249.34 155.66 36191 +1994 300 8.06 2.06 6.41 0 253.08 204.61 36009 +1994 301 10.42 4.42 8.77 0 292.48 199.57 35829 +1994 302 11.88 5.88 10.23 0.06 319.39 146.43 35650 +1994 303 14.61 8.61 12.96 0 375.44 189.05 35472 +1994 304 13.46 7.46 11.81 0 350.88 188.23 35296 +1994 305 10.97 4.97 9.32 0 302.38 188.58 35122 +1994 306 15.41 9.41 13.76 0.06 393.37 135.46 34950 +1994 307 14.59 8.59 12.94 0.2 375 134.5 34779 +1994 308 11.07 5.07 9.42 0.01 304.21 135.86 34610 +1994 309 12.81 6.81 11.16 0.15 337.62 132.62 34444 +1994 310 11.1 5.1 9.45 0.22 304.76 132.3 34279 +1994 311 9.6 3.6 7.95 0 278.23 175.8 34116 +1994 312 6.3 0.3 4.65 0 226.75 176.08 33956 +1994 313 7.69 1.69 6.04 0 247.34 172.8 33797 +1994 314 9.88 3.88 8.23 0 283.03 168.84 33641 +1994 315 15.32 9.32 13.67 0 391.32 160.07 33488 +1994 316 13.11 7.11 11.46 0.02 343.69 120.54 33337 +1994 317 14.51 8.51 12.86 0.3 373.25 117.66 33188 +1994 318 10.94 4.94 9.29 0.47 301.83 118.97 33042 +1994 319 8.48 2.48 6.83 0.14 259.74 119.43 32899 +1994 320 12.03 6.03 10.38 0 322.28 154 32758 +1994 321 13.32 7.32 11.67 0 347.99 150.52 32620 +1994 322 12.88 6.88 11.23 0.02 339.03 111.93 32486 +1994 323 8.9 2.9 7.25 0.7 266.55 113.63 32354 +1994 324 6.67 0.67 5.02 0 232.08 151.24 32225 +1994 325 6.77 0.77 5.12 0 233.54 149.44 32100 +1994 326 6.02 0.02 4.37 0.01 222.79 111.39 31977 +1994 327 1.42 -4.58 -0.23 0.02 165.69 112.06 31858 +1994 328 3.67 -2.33 2.02 0 191.8 146.19 31743 +1994 329 3.77 -2.23 2.12 0 193.04 144.63 31631 +1994 330 8.35 2.35 6.7 0.27 257.66 105.05 31522 +1994 331 9.33 3.33 7.68 0.14 273.67 103.48 31417 +1994 332 12.01 6.01 10.36 0.5 321.89 100.47 31316 +1994 333 9.97 3.97 8.32 0.43 284.59 101.06 31218 +1994 334 8.88 2.88 7.23 1.02 266.22 100.92 31125 +1994 335 5.74 -0.26 4.09 0.03 218.88 101.73 31035 +1994 336 6.38 0.38 4.73 0.1 227.89 100.61 30949 +1994 337 5.34 -0.66 3.69 0 213.41 133.16 30867 +1994 338 6.14 0.14 4.49 0 224.48 131.71 30790 +1994 339 3.51 -2.49 1.86 0.45 189.84 99.37 30716 +1994 340 -0.04 -6.04 -1.69 0 150.44 133.46 30647 +1994 341 2.75 -3.25 1.1 0.01 180.73 98.42 30582 +1994 342 0.13 -5.87 -1.52 0 152.15 131.69 30521 +1994 343 1.37 -4.63 -0.28 0 165.15 130.31 30465 +1994 344 7.81 1.81 6.16 0 249.19 125.46 30413 +1994 345 6.43 0.43 4.78 0 228.61 125.97 30366 +1994 346 5.21 -0.79 3.56 0 211.65 126.17 30323 +1994 347 3.74 -2.26 2.09 0 192.67 126.41 30284 +1994 348 2.72 -3.28 1.07 0 180.38 126.58 30251 +1994 349 3.63 -2.37 1.98 0 191.31 125.73 30221 +1994 350 0.77 -5.23 -0.88 0 158.75 126.78 30197 +1994 351 1.38 -4.62 -0.27 0.42 165.26 94.71 30177 +1994 352 0.32 -5.68 -1.33 0 154.09 126.66 30162 +1994 353 5.1 -0.9 3.45 0 210.18 124.21 30151 +1994 354 4.69 -1.31 3.04 0.04 204.76 93.31 30145 +1994 355 8.15 2.15 6.5 0 254.5 122.21 30144 +1994 356 6.47 0.47 4.82 0 229.19 123.36 30147 +1994 357 3.47 -2.53 1.82 0 189.35 125.15 30156 +1994 358 6.46 0.46 4.81 0 229.04 123.51 30169 +1994 359 3.5 -2.5 1.85 0 189.71 125.35 30186 +1994 360 5.95 -0.05 4.3 0 221.81 124.31 30208 +1994 361 7.23 1.23 5.58 0.07 240.35 92.86 30235 +1994 362 8.93 2.93 7.28 0.24 267.04 92.28 30267 +1994 363 7.35 1.35 5.7 2.94 242.16 93.56 30303 +1994 364 2.88 -3.12 1.23 0 182.26 127.79 30343 +1994 365 1.27 -4.73 -0.38 0.1 164.07 96.85 30388 +1995 1 0.48 -5.52 -1.17 0 155.73 130.39 30438 +1995 2 3.5 -2.5 1.85 0 189.71 129.66 30492 +1995 3 1.98 -4.02 0.33 0 171.89 131.38 30551 +1995 4 6.08 0.08 4.43 0.05 223.63 97.5 30614 +1995 5 5.26 -0.74 3.61 0.44 212.33 98.36 30681 +1995 6 1.84 -4.16 0.19 0.52 170.32 100.43 30752 +1995 7 0.83 -5.17 -0.82 0 159.38 135.19 30828 +1995 8 1.04 -4.96 -0.61 0 161.6 136.59 30907 +1995 9 3.22 -2.78 1.57 0 186.32 136.74 30991 +1995 10 3.61 -2.39 1.96 0 191.06 137.83 31079 +1995 11 5.24 -0.76 3.59 0 212.06 137.85 31171 +1995 12 4.05 -1.95 2.4 0 196.55 139.58 31266 +1995 13 5.72 -0.28 4.07 1.43 218.61 105.12 31366 +1995 14 3.05 -2.95 1.4 0.21 184.28 107.43 31469 +1995 15 -2.09 -8.09 -3.74 0.39 131.09 153.33 31575 +1995 16 -0.77 -6.77 -2.42 0 143.28 190.72 31686 +1995 17 -1.41 -7.41 -3.06 0.05 137.25 155.23 31800 +1995 18 0.56 -5.44 -1.09 0 156.56 193.49 31917 +1995 19 -0.37 -6.37 -2.02 0.03 147.17 157.48 32038 +1995 20 -1.52 -7.52 -3.17 0 136.24 197.75 32161 +1995 21 -3.14 -9.14 -4.79 0 122.03 200.27 32289 +1995 22 0.84 -5.16 -0.81 0 159.48 200 32419 +1995 23 1.46 -4.54 -0.19 0 166.13 201.11 32552 +1995 24 4.06 -1.94 2.41 0 196.67 200.99 32688 +1995 25 5.72 -0.28 4.07 0.07 218.61 120.62 32827 +1995 26 5.52 -0.48 3.87 0.03 215.86 122.17 32969 +1995 27 7.65 1.65 6 0 246.72 163.26 33114 +1995 28 8.79 2.79 7.14 0.15 264.75 123.34 33261 +1995 29 5.58 -0.42 3.93 0.39 216.68 127.07 33411 +1995 30 3.89 -2.11 2.24 0.06 194.54 129.64 33564 +1995 31 3.3 -2.7 1.65 0 187.28 175.62 33718 +1995 32 8.2 2.2 6.55 0.41 255.28 130.48 33875 +1995 33 9.54 3.54 7.89 0 277.21 175.31 34035 +1995 34 12.23 6.23 10.58 0 326.15 174.58 34196 +1995 35 10.25 4.25 8.6 0 289.48 178.86 34360 +1995 36 10.68 4.68 9.03 0 297.12 180.87 34526 +1995 37 10.16 4.16 8.51 0.01 287.9 137.85 34694 +1995 38 12.81 6.81 11.16 0 337.62 183.42 34863 +1995 39 8.83 2.83 7.18 1.6 265.4 142.82 35035 +1995 40 3.98 -2.02 2.33 1.01 195.67 147.89 35208 +1995 41 -0.4 -6.4 -2.05 0.28 146.88 190.04 35383 +1995 42 2.81 -3.19 1.16 0 181.43 240.77 35560 +1995 43 6.77 0.77 5.12 0 233.54 202.78 35738 +1995 44 8.95 2.95 7.3 0 267.37 203.2 35918 +1995 45 10.21 4.21 8.56 0 288.77 204.4 36099 +1995 46 9.94 3.94 8.29 0 284.07 207.35 36282 +1995 47 4.59 -1.41 2.94 1.15 203.46 161.49 36466 +1995 48 8.91 2.91 7.26 0 266.71 214.04 36652 +1995 49 10.72 4.72 9.07 0 297.85 214.69 36838 +1995 50 10.25 4.25 8.6 0 289.48 217.88 37026 +1995 51 9.7 3.7 8.05 0 279.94 221.45 37215 +1995 52 8.32 2.32 6.67 0 257.19 225.8 37405 +1995 53 6.3 0.3 4.65 0 226.75 230.81 37596 +1995 54 5.53 -0.47 3.88 0.18 215.99 175.71 37788 +1995 55 3.83 -2.17 2.18 0.01 193.79 179.08 37981 +1995 56 6.5 0.5 4.85 0.24 229.62 179.28 38175 +1995 57 10.83 4.83 9.18 0.03 299.83 177.67 38370 +1995 58 14.36 8.36 12.71 0 369.98 234.53 38565 +1995 59 15.01 9.01 13.36 0.06 384.31 177.03 38761 +1995 60 16.86 10.86 15.21 0 427.74 235.41 38958 +1995 61 10.9 4.9 9.25 0 301.11 248.07 39156 +1995 62 7.8 1.8 6.15 0 249.03 254.73 39355 +1995 63 5.08 -0.92 3.43 0 209.91 260.6 39553 +1995 64 7.56 1.56 5.91 0 245.35 260.9 39753 +1995 65 9.2 3.2 7.55 0.01 271.5 196.34 39953 +1995 66 8.94 2.94 7.29 1.28 267.2 198.63 40154 +1995 67 7.57 1.57 5.92 0 245.5 269.4 40355 +1995 68 9.56 3.56 7.91 0 277.55 269.76 40556 +1995 69 8.99 2.99 7.34 0.04 268.03 204.84 40758 +1995 70 8.84 2.84 7.19 0.38 265.57 207.11 40960 +1995 71 8.5 2.5 6.85 0 260.06 279.48 41163 +1995 72 7.95 1.95 6.3 0.29 251.36 212.25 41366 +1995 73 4.51 -1.49 2.86 0.04 202.42 217.15 41569 +1995 74 7.1 1.1 5.45 0 238.41 289.45 41772 +1995 75 4.03 -1.97 2.38 0 196.29 295.55 41976 +1995 76 7.59 1.59 5.94 0 245.81 294.23 42179 +1995 77 8.64 2.64 6.99 0 262.32 295.47 42383 +1995 78 6.06 0.06 4.41 0 223.35 301.36 42587 +1995 79 5.04 -0.96 3.39 2.19 209.38 228.94 42791 +1995 80 4.71 -1.29 3.06 0 205.02 308.17 42996 +1995 81 6.13 0.13 4.48 0.01 224.34 231.88 43200 +1995 82 5.2 -0.8 3.55 0 211.52 312.92 43404 +1995 83 4.14 -1.86 2.49 0 197.68 316.6 43608 +1995 84 6.61 0.61 4.96 0.67 231.21 237.25 43812 +1995 85 6.84 0.84 5.19 0.13 234.57 238.93 44016 +1995 86 8.87 2.87 7.22 0.13 266.06 238.68 44220 +1995 87 8.04 2.04 6.39 0 252.77 321.95 44424 +1995 88 8.95 2.95 7.3 0 267.37 323.01 44627 +1995 89 10.65 4.65 9 0 296.59 322.64 44831 +1995 90 11.02 5.02 9.37 0 303.3 324.38 45034 +1995 91 16.69 10.69 15.04 0.17 423.59 236.34 45237 +1995 92 15.8 9.8 14.15 0 402.38 319.37 45439 +1995 93 11.59 5.59 9.94 1.2 313.89 247.55 45642 +1995 94 14.3 8.3 12.65 0.68 368.68 245.21 45843 +1995 95 13.2 7.2 11.55 0.19 345.53 248.48 46045 +1995 96 13.86 7.86 12.21 0.04 359.26 249.04 46246 +1995 97 16.13 10.13 14.48 0 410.13 329.02 46446 +1995 98 12.23 6.23 10.58 0 326.15 339.27 46647 +1995 99 15.49 9.49 13.84 0 395.2 334.41 46846 +1995 100 14.81 8.81 13.16 0 379.85 337.87 47045 +1995 101 17.65 11.65 16 0 447.52 332.84 47243 +1995 102 15.29 9.29 13.64 0 390.64 340.56 47441 +1995 103 17.69 11.69 16.04 0 448.55 336.37 47638 +1995 104 16.32 10.32 14.67 0.75 414.65 256.26 47834 +1995 105 11.47 5.47 9.82 1.3 311.63 265.45 48030 +1995 106 13.87 7.87 12.22 0 359.47 350.76 48225 +1995 107 10.56 4.56 8.91 0.16 294.97 269.2 48419 +1995 108 9.24 3.24 7.59 0.47 272.17 272.21 48612 +1995 109 11.91 5.91 10.26 0 319.97 359.79 48804 +1995 110 9.98 3.98 8.33 0.03 284.76 273.57 48995 +1995 111 13.49 7.49 11.84 0 351.51 359.52 49185 +1995 112 14.49 8.49 12.84 0 372.81 358.82 49374 +1995 113 14.04 8.04 12.39 0.15 363.09 270.88 49561 +1995 114 18 12 16.35 0 456.53 352.64 49748 +1995 115 14.49 8.49 12.84 0 372.81 363.05 49933 +1995 116 13.46 7.46 11.81 0 350.88 366.58 50117 +1995 117 16.59 10.59 14.94 0.05 421.16 270.28 50300 +1995 118 14.52 8.52 12.87 0.45 373.46 275.11 50481 +1995 119 15.06 9.06 13.41 0 385.44 366.71 50661 +1995 120 14.37 8.37 12.72 0 370.19 369.52 50840 +1995 121 19.79 13.79 18.14 0.17 505.07 266.82 51016 +1995 122 15.9 9.9 14.25 0.15 404.71 276.07 51191 +1995 123 13.04 7.04 11.39 0 342.26 375.87 51365 +1995 124 17.11 11.11 15.46 0 433.92 366.97 51536 +1995 125 17.51 11.51 15.86 0 443.96 366.83 51706 +1995 126 15.71 9.71 14.06 0.04 400.28 279.49 51874 +1995 127 17.65 11.65 16 0 447.52 368.29 52039 +1995 128 18.27 12.27 16.62 0 463.59 367.46 52203 +1995 129 11.84 5.84 10.19 0.71 318.63 288.18 52365 +1995 130 13.68 7.68 12.03 0.29 355.47 285.82 52524 +1995 131 15.36 9.36 13.71 0.13 392.23 283.4 52681 +1995 132 16.98 10.98 15.33 1.64 430.7 280.8 52836 +1995 133 17.49 11.49 15.84 0.38 443.46 280.24 52989 +1995 134 9.86 3.86 8.21 0.66 282.68 293.97 53138 +1995 135 11.65 5.65 10 0 315.02 389.24 53286 +1995 136 17.93 11.93 16.28 0 454.72 374.4 53430 +1995 137 21.42 15.42 19.77 1.47 553.01 272.76 53572 +1995 138 19.87 13.87 18.22 0.01 507.33 277.22 53711 +1995 139 20.99 14.99 19.34 0 540 366.47 53848 +1995 140 23.29 17.29 21.64 0.06 612.72 268.7 53981 +1995 141 21.13 15.13 19.48 0 544.21 366.87 54111 +1995 142 25.05 19.05 23.4 0 673.83 351.71 54238 +1995 143 25.87 19.87 24.22 0.93 704.01 261.37 54362 +1995 144 21.14 15.14 19.49 0.52 544.51 276.23 54483 +1995 145 20.96 14.96 19.31 0.26 539.11 277.06 54600 +1995 146 19.61 13.61 17.96 0.52 500 280.79 54714 +1995 147 18.44 12.44 16.79 0.02 468.08 283.93 54824 +1995 148 15.83 9.83 14.18 0.02 403.08 289.81 54931 +1995 149 13.84 7.84 12.19 0.07 358.84 293.76 55034 +1995 150 14.65 8.65 13 0 376.32 390.08 55134 +1995 151 18.38 12.38 16.73 0.09 466.49 285.13 55229 +1995 152 22.14 16.14 20.49 0 575.39 367.39 55321 +1995 153 19.24 13.24 17.59 0 489.71 377.82 55409 +1995 154 23.08 17.08 21.43 1.07 605.76 273.2 55492 +1995 155 17.06 11.06 15.41 0.64 432.68 288.71 55572 +1995 156 15.32 9.32 13.67 0.56 391.32 292.49 55648 +1995 157 18.53 12.53 16.88 0 470.47 381.06 55719 +1995 158 17.62 11.62 15.97 0 446.76 383.99 55786 +1995 159 19.08 13.08 17.43 0.58 485.32 284.81 55849 +1995 160 22.7 16.7 21.05 0.05 593.32 275.27 55908 +1995 161 22.02 16.02 20.37 0.99 571.61 277.29 55962 +1995 162 22.93 16.93 21.28 0 600.82 366.23 56011 +1995 163 24.9 18.9 23.25 1.16 668.43 268.6 56056 +1995 164 24.6 18.6 22.95 1.53 657.73 269.62 56097 +1995 165 23.81 17.81 22.16 1.32 630.27 272.23 56133 +1995 166 17.06 11.06 15.41 1.65 432.68 289.96 56165 +1995 167 18.24 12.24 16.59 0 462.8 383.07 56192 +1995 168 17.31 11.31 15.66 0.1 438.92 289.44 56214 +1995 169 22.27 16.27 20.62 0 579.51 369.28 56231 +1995 170 21.64 15.64 19.99 0 559.77 371.67 56244 +1995 171 19.66 13.66 18.01 0 501.4 378.69 56252 +1995 172 21.4 15.4 19.75 0 552.4 372.6 56256 +1995 173 23.25 17.25 21.6 0 611.39 365.43 56255 +1995 174 19.02 13.02 17.37 0 483.68 380.67 56249 +1995 175 21.81 15.81 20.16 0.1 565.04 278.21 56238 +1995 176 22.59 16.59 20.94 0 589.76 367.92 56223 +1995 177 19.72 13.72 18.07 0.06 503.09 283.66 56203 +1995 178 19.41 13.41 17.76 0 494.41 379.26 56179 +1995 179 16.16 10.16 14.51 0.15 410.84 291.64 56150 +1995 180 15.39 9.39 13.74 1.18 392.91 293.08 56116 +1995 181 18.11 12.11 16.46 0 459.4 383.06 56078 +1995 182 25.95 19.95 24.3 0 707.02 352.96 56035 +1995 183 28.73 22.73 27.08 0 818.41 338.68 55987 +1995 184 28.17 22.17 26.52 0 794.85 341.55 55935 +1995 185 29.69 23.69 28.04 0.3 860.16 249.81 55879 +1995 186 29.58 23.58 27.93 0.07 855.28 250.11 55818 +1995 187 28.53 22.53 26.88 0.29 809.93 254.35 55753 +1995 188 26.17 20.17 24.52 0.5 715.34 263.14 55684 +1995 189 24.88 18.88 23.23 0.01 667.71 267.45 55611 +1995 190 24.35 18.35 22.7 0 648.93 358.55 55533 +1995 191 26.94 20.94 25.29 0.61 745.11 259.75 55451 +1995 192 25.18 19.18 23.53 0 678.54 354.35 55366 +1995 193 22.02 16.02 20.37 0 571.61 367.13 55276 +1995 194 21.73 15.73 20.08 0.03 562.55 275.99 55182 +1995 195 24.65 18.65 23 0 659.51 355.96 55085 +1995 196 22.43 16.43 20.78 0 584.62 364.67 54984 +1995 197 19.79 13.79 18.14 0 505.07 373.67 54879 +1995 198 17.72 11.72 16.07 0 449.31 379.71 54770 +1995 199 21.08 15.08 19.43 0.24 542.7 276.34 54658 +1995 200 22.67 16.67 21.02 0.08 592.35 271.6 54542 +1995 201 26 20 24.35 0 708.9 347.46 54423 +1995 202 28.36 22.36 26.71 0.04 802.78 251.38 54301 +1995 203 28.41 22.41 26.76 0.1 804.87 250.83 54176 +1995 204 28.81 22.81 27.16 0 821.82 331.83 54047 +1995 205 27.66 21.66 26.01 0 773.9 337.38 53915 +1995 206 25.98 19.98 24.33 0.18 708.15 258.76 53780 +1995 207 24.33 18.33 22.68 1.8 648.23 263.77 53643 +1995 208 26.92 20.92 25.27 0 744.33 339.29 53502 +1995 209 27.52 21.52 25.87 0.36 768.23 251.79 53359 +1995 210 25.4 19.4 23.75 0.14 686.58 258.89 53213 +1995 211 25.12 19.12 23.47 0.24 676.36 259.25 53064 +1995 212 27.05 21.05 25.4 0 749.45 335.98 52913 +1995 213 24.07 18.07 22.42 0 639.2 348.65 52760 +1995 214 22.63 16.63 20.98 1.23 591.05 265.24 52604 +1995 215 18.28 12.28 16.63 0.49 463.85 275.76 52445 +1995 216 18.39 12.39 16.74 0 466.76 366.32 52285 +1995 217 19.23 13.23 17.58 0.02 489.43 272.14 52122 +1995 218 18.34 12.34 16.69 0 465.43 364.74 51958 +1995 219 23.82 17.82 22.17 0 630.61 344.63 51791 +1995 220 24.49 18.49 22.84 0 653.85 340.97 51622 +1995 221 22.39 16.39 20.74 0 583.34 348.28 51451 +1995 222 19.76 13.76 18.11 0 504.22 356.31 51279 +1995 223 19.15 13.15 17.5 0 487.23 357.08 51105 +1995 224 19.38 13.38 17.73 0 493.58 355.3 50929 +1995 225 22.38 16.38 20.73 0 583.02 344 50751 +1995 226 24.01 18.01 22.36 0 637.13 336.62 50572 +1995 227 18.64 12.64 16.99 0.8 473.41 265.47 50392 +1995 228 18.15 12.15 16.5 0.28 460.44 265.62 50210 +1995 229 18.14 12.14 16.49 0.02 460.18 264.7 50026 +1995 230 18.15 12.15 16.5 0 460.44 351.62 49842 +1995 231 16.16 10.16 14.51 0.1 410.84 266.61 49656 +1995 232 18.69 12.69 17.04 0.57 474.75 260.42 49469 +1995 233 23.69 17.69 22.04 0.26 626.18 246.7 49280 +1995 234 25.76 19.76 24.11 0.32 699.9 239.34 49091 +1995 235 25.45 19.45 23.8 1.46 688.41 239.27 48900 +1995 236 27.42 21.42 25.77 2.44 764.2 231.68 48709 +1995 237 26.25 20.25 24.6 0 718.38 312.67 48516 +1995 238 26.86 20.86 25.21 0.59 741.97 231.29 48323 +1995 239 28.04 22.04 26.39 0.16 789.46 226.12 48128 +1995 240 27.61 21.61 25.96 0 771.87 301.9 47933 +1995 241 25.47 19.47 23.82 0.64 689.15 232.28 47737 +1995 242 25.37 19.37 23.72 1.95 685.47 231.35 47541 +1995 243 25.65 19.65 24 0.11 695.8 229.16 47343 +1995 244 24.86 18.86 23.21 0.66 666.99 230.27 47145 +1995 245 24.7 18.7 23.05 0.03 661.28 229.42 46947 +1995 246 22.9 16.9 21.25 0.02 599.84 233.02 46747 +1995 247 19.82 13.82 18.17 0 505.92 318.82 46547 +1995 248 20.59 14.59 18.94 0.23 528.14 235.95 46347 +1995 249 18.35 12.35 16.7 0.14 465.7 239.23 46146 +1995 250 17.59 11.59 15.94 2.12 446 239.27 45945 +1995 251 19.28 13.28 17.63 0.98 490.81 234.29 45743 +1995 252 14.64 8.64 12.99 0.16 376.1 241.2 45541 +1995 253 15.07 9.07 13.42 0 385.66 318.52 45339 +1995 254 16.14 10.14 14.49 0.29 410.37 235.48 45136 +1995 255 13.49 7.49 11.84 0 351.51 317.32 44933 +1995 256 13.12 7.12 11.47 0.79 343.89 236.79 44730 +1995 257 17.34 11.34 15.69 0.24 439.67 228.33 44527 +1995 258 21.75 15.75 20.1 0.05 563.17 217.49 44323 +1995 259 18.68 12.68 17.03 0.21 474.48 222.25 44119 +1995 260 16.46 10.46 14.81 0 418.01 299.35 43915 +1995 261 18.73 12.73 17.08 0.01 475.82 218.58 43711 +1995 262 16.35 10.35 14.7 0.78 415.37 221.08 43507 +1995 263 14.37 8.37 12.72 3.97 370.19 222.33 43303 +1995 264 12.44 6.44 10.79 0 330.27 297.41 43099 +1995 265 13.58 7.58 11.93 0 353.38 292.96 42894 +1995 266 17.15 11.15 15.5 0 434.92 283.14 42690 +1995 267 13.36 7.36 11.71 0 348.81 288.14 42486 +1995 268 15.22 9.22 13.57 0 389.05 282.03 42282 +1995 269 18.01 12.01 16.36 1.41 456.79 205.12 42078 +1995 270 19.37 13.37 17.72 0.37 493.3 200.71 41875 +1995 271 17.49 11.49 15.84 0 443.46 269.5 41671 +1995 272 17.26 11.26 15.61 0 437.66 267.32 41468 +1995 273 13.81 7.81 12.16 0.85 358.21 203.71 41265 +1995 274 13.61 7.61 11.96 0 354.01 269.28 41062 +1995 275 14.35 8.35 12.7 0 369.76 265.2 40860 +1995 276 17.79 11.79 16.14 0 451.11 255.67 40658 +1995 277 14.14 8.14 12.49 0 365.23 260.22 40456 +1995 278 12.03 6.03 10.38 0 322.28 260.81 40255 +1995 279 11.55 5.55 9.9 0 313.13 258.69 40054 +1995 280 11.85 5.85 10.2 0 318.82 255.57 39854 +1995 281 12 6 10.35 0 321.7 252.61 39654 +1995 282 11.29 5.29 9.64 0.14 308.27 188.16 39455 +1995 283 10.48 4.48 8.83 0 293.55 249.15 39256 +1995 284 10.25 4.25 8.6 0.38 289.48 184.8 39058 +1995 285 10.29 4.29 8.64 0.16 290.18 182.76 38861 +1995 286 12.81 6.81 11.16 0 337.62 237.37 38664 +1995 287 11.4 5.4 9.75 0 310.32 236.45 38468 +1995 288 16.37 10.37 14.72 0 415.85 225.78 38273 +1995 289 17.67 11.67 16.02 0 448.04 220.75 38079 +1995 290 13.5 7.5 11.85 0 351.71 225.15 37885 +1995 291 14.65 8.65 13 0 376.32 220.68 37693 +1995 292 11.86 5.86 10.21 0 319.01 222.13 37501 +1995 293 11.98 5.98 10.33 0 321.31 219.23 37311 +1995 294 14.08 8.08 12.43 0.18 363.94 160.02 37121 +1995 295 14.76 8.76 13.11 0 378.75 209.52 36933 +1995 296 17.45 11.45 15.8 0 442.44 202.45 36745 +1995 297 20.09 14.09 18.44 0 513.62 194.68 36560 +1995 298 16.01 10.01 14.36 0 407.3 199.76 36375 +1995 299 18.48 12.48 16.83 0 469.14 192.72 36191 +1995 300 19.96 13.96 18.31 0 509.9 187.3 36009 +1995 301 19.67 13.67 18.02 0 501.68 185.49 35829 +1995 302 17.13 11.13 15.48 0 434.42 187.62 35650 +1995 303 21.28 15.28 19.63 0 548.75 177.29 35472 +1995 304 17.68 11.68 16.03 0.29 448.29 136.37 35296 +1995 305 10.07 4.07 8.42 0.4 286.32 142.18 35122 +1995 306 6.79 0.79 5.14 1.13 233.83 142.86 34950 +1995 307 4.28 -1.72 2.63 0.56 199.47 142.45 34779 +1995 308 3.88 -2.12 2.23 0.15 194.41 140.68 34610 +1995 309 4.1 -1.9 2.45 0.14 197.18 138.8 34444 +1995 310 6.55 0.55 4.9 0.64 230.34 135.55 34279 +1995 311 8.6 2.6 6.95 0 261.67 176.75 34116 +1995 312 9.67 3.67 8.02 0.04 279.43 129.82 33956 +1995 313 4.26 -1.74 2.61 0 199.21 175.45 33797 +1995 314 4.02 -1.98 2.37 0 196.17 173.63 33641 +1995 315 4.86 -1.14 3.21 0 206.99 170.5 33488 +1995 316 2.65 -3.35 1 0 179.56 169.73 33337 +1995 317 4.44 -1.56 2.79 0.01 201.52 124.78 33188 +1995 318 4.95 -1.05 3.3 0 208.18 163.67 33042 +1995 319 4.86 -1.14 3.21 0.72 206.99 121.51 32899 +1995 320 4.55 -1.45 2.9 0.01 202.94 120.25 32758 +1995 321 5.73 -0.27 4.08 0 218.75 157.41 32620 +1995 322 3.25 -2.75 1.6 0 186.68 157.19 32486 +1995 323 4.2 -1.8 2.55 0 198.45 154.98 32354 +1995 324 7.54 1.54 5.89 0 245.04 150.58 32225 +1995 325 6.11 0.11 4.46 0 224.06 149.91 32100 +1995 326 10.21 4.21 8.56 0 288.77 145.19 31977 +1995 327 10.33 4.33 8.68 0.51 290.89 107.44 31858 +1995 328 6.24 0.24 4.59 0.09 225.9 108.41 31743 +1995 329 3.81 -2.19 2.16 0.03 193.54 108.45 31631 +1995 330 1.34 -4.66 -0.31 0 164.82 144.48 31522 +1995 331 3.66 -2.34 2.01 0 191.68 141.91 31417 +1995 332 9.98 3.98 8.33 0 284.76 135.81 31316 +1995 333 7.79 1.79 6.14 0 248.88 136.48 31218 +1995 334 10.77 4.77 9.12 0 298.75 132.98 31125 +1995 335 7.33 1.33 5.68 0.22 241.86 100.92 31035 +1995 336 6.31 0.31 4.66 0.8 226.89 100.65 30949 +1995 337 7.23 1.23 5.58 0.08 240.35 98.93 30867 +1995 338 4.69 -1.31 3.04 0.52 204.76 99.46 30790 +1995 339 5.33 -0.67 3.68 1.45 213.27 98.58 30716 +1995 340 6.81 0.81 5.16 0.26 234.13 97.32 30647 +1995 341 8.66 2.66 7.01 0.07 262.64 95.65 30582 +1995 342 8.65 2.65 7 0 262.48 126.79 30521 +1995 343 7.78 1.78 6.13 0.06 248.73 94.95 30465 +1995 344 8.82 2.82 7.17 0 265.24 124.73 30413 +1995 345 7.87 1.87 6.22 0.87 250.12 93.75 30366 +1995 346 5.03 -0.97 3.38 0 209.25 126.28 30323 +1995 347 4.46 -1.54 2.81 0.45 201.78 94.51 30284 +1995 348 4.54 -1.46 2.89 1.15 202.81 94.21 30251 +1995 349 -5.2 -11.2 -6.85 0.37 105.84 141.8 30221 +1995 350 -7.17 -13.17 -8.82 0 92.13 174.34 30197 +1995 351 -1.72 -7.72 -3.37 0.1 134.41 140.91 30177 +1995 352 -2.28 -8.28 -3.93 0.06 129.41 141.2 30162 +1995 353 -1.5 -7.5 -3.15 0 136.42 172.78 30151 +1995 354 -0.33 -6.33 -1.98 0 147.56 172.3 30145 +1995 355 -0.78 -6.78 -2.43 0 143.19 172.48 30144 +1995 356 2.41 -3.59 0.76 0.59 176.78 139.37 30147 +1995 357 4.35 -1.65 2.7 0.56 200.36 138.07 30156 +1995 358 2.45 -3.55 0.8 2.26 177.24 138.53 30169 +1995 359 -2.6 -8.6 -4.25 1.33 126.62 144.4 30186 +1995 360 1.74 -4.26 0.09 0 169.21 174.73 30208 +1995 361 3.78 -2.22 2.13 0 193.17 173.49 30235 +1995 362 9.02 3.02 7.37 0 268.52 169.33 30267 +1995 363 7.45 1.45 5.8 0 243.67 169.99 30303 +1995 364 5.22 -0.78 3.57 0.11 211.79 139.42 30343 +1995 365 9.27 3.27 7.62 0.18 272.67 93.23 30388 +1996 1 4.69 -1.31 3.04 0.03 204.76 96.2 30438 +1996 2 0.83 -5.17 -0.82 1.49 159.38 98.23 30492 +1996 3 2.1 -3.9 0.45 0.06 173.24 98.49 30551 +1996 4 2.19 -3.81 0.54 0.14 174.26 99.14 30614 +1996 5 -0.37 -6.37 -2.02 0 147.17 134.01 30681 +1996 6 0.33 -5.67 -1.32 0.14 154.19 100.96 30752 +1996 7 0.62 -5.38 -1.03 0.02 157.18 101.46 30828 +1996 8 0.52 -5.48 -1.13 0 156.14 136.82 30907 +1996 9 1.14 -4.86 -0.51 0.02 162.67 103.35 30991 +1996 10 4.61 -1.39 2.96 0 203.72 137.25 31079 +1996 11 4.91 -1.09 3.26 0.15 207.65 103.54 31171 +1996 12 2.95 -3.05 1.3 0.85 183.09 105.15 31266 +1996 13 3 -3 1.35 0.27 183.68 106.34 31366 +1996 14 3.11 -2.89 1.46 0.11 184.99 107.41 31469 +1996 15 1.11 -4.89 -0.54 0 162.35 145.71 31575 +1996 16 2.96 -3.04 1.31 0 183.21 146.03 31686 +1996 17 -1.43 -7.43 -3.08 0.07 137.07 154.12 31800 +1996 18 1.5 -4.5 -0.15 0 166.57 191.79 31917 +1996 19 -5 -11 -6.65 0 107.32 196.29 32038 +1996 20 -1.14 -7.14 -2.79 0 139.77 196.27 32161 +1996 21 2.69 -3.31 1.04 0 180.03 155.31 32289 +1996 22 2.75 -3.25 1.1 0 180.73 157.03 32419 +1996 23 4.74 -1.26 3.09 0 205.42 157.57 32552 +1996 24 3.46 -2.54 1.81 0 189.23 160.45 32688 +1996 25 6.54 0.54 4.89 0.3 230.2 120.17 32827 +1996 26 2.37 -3.63 0.72 0 176.32 164.93 32969 +1996 27 4.68 -1.32 3.03 0 204.63 165.5 33114 +1996 28 7.11 1.11 5.46 0.01 238.56 124.42 33261 +1996 29 6.93 0.93 5.28 0 235.89 168.39 33411 +1996 30 5.01 -0.99 3.36 0.05 208.98 129.06 33564 +1996 31 7.26 1.26 5.61 0.13 240.81 129.52 33718 +1996 32 2.93 -3.07 1.28 0 182.85 177.98 33875 +1996 33 4.65 -1.35 3 0.19 204.24 134.58 34035 +1996 34 0.71 -5.29 -0.94 0 158.12 184.16 34196 +1996 35 -0.71 -6.71 -2.36 0 143.86 187.09 34360 +1996 36 -1.34 -7.34 -2.99 0 137.9 189.95 34526 +1996 37 -0.58 -6.58 -2.23 0 145.12 192.02 34694 +1996 38 1.53 -4.47 -0.12 0 166.89 193.59 34863 +1996 39 1.94 -4.06 0.29 0 171.44 195.96 35035 +1996 40 -1.15 -7.15 -2.8 0 139.68 200.38 35208 +1996 41 -2.06 -8.06 -3.71 0 131.35 203.5 35383 +1996 42 -2.59 -8.59 -4.24 0.34 126.7 192.8 35560 +1996 43 -1.74 -7.74 -3.39 0 134.23 246.52 35738 +1996 44 0.83 -5.17 -0.82 0.33 159.38 194.93 35918 +1996 45 1.82 -4.18 0.17 0 170.1 249.01 36099 +1996 46 4.69 -1.31 3.04 0.15 204.76 195.78 36282 +1996 47 2.53 -3.47 0.88 0 178.16 216.89 36466 +1996 48 1.76 -4.24 0.11 0 169.43 220.26 36652 +1996 49 1.37 -4.63 -0.28 0 165.15 223.32 36838 +1996 50 6.07 0.07 4.42 0.06 223.49 166.72 37026 +1996 51 2.22 -3.78 0.57 0.11 174.6 171.31 37215 +1996 52 -0.72 -6.72 -2.37 0.27 143.77 210.89 37405 +1996 53 0.02 -5.98 -1.63 0.41 151.05 212.61 37596 +1996 54 1.67 -4.33 0.02 0.63 168.43 213.51 37788 +1996 55 3.3 -2.7 1.65 1.07 187.28 214.32 37981 +1996 56 4.36 -1.64 2.71 0.29 200.49 180.77 38175 +1996 57 5 -1 3.35 0 208.85 243.36 38370 +1996 58 3.37 -2.63 1.72 0.31 188.13 185.79 38565 +1996 59 1.61 -4.39 -0.04 0 167.77 251.84 38761 +1996 60 9.67 3.67 8.02 0 279.43 246.8 38958 +1996 61 7.14 1.14 5.49 0 239.01 252.68 39156 +1996 62 7.9 1.9 6.25 0 250.58 254.61 39355 +1996 63 6.75 0.75 5.1 0 233.25 258.89 39553 +1996 64 7.01 1.01 5.36 0 237.08 261.51 39753 +1996 65 8.13 2.13 6.48 0 254.18 263.11 39953 +1996 66 12.65 6.65 11 0 334.42 259.55 40154 +1996 67 12.05 6.05 10.4 0.3 322.66 197.5 40355 +1996 68 8 2 6.35 0 252.14 271.75 40556 +1996 69 8.12 2.12 6.47 0 254.02 274.22 40758 +1996 70 1.23 -4.77 -0.42 0 163.64 283.96 40960 +1996 71 6.36 0.36 4.71 0 227.61 282.05 41163 +1996 72 6.09 0.09 4.44 0 223.77 285.18 41366 +1996 73 2.95 -3.05 1.3 0.7 183.09 218.27 41569 +1996 74 5.19 -0.81 3.54 0 211.39 291.61 41772 +1996 75 3.88 -2.12 2.23 0 194.41 295.7 41976 +1996 76 7.24 1.24 5.59 0 240.5 294.66 42179 +1996 77 0.95 -5.05 -0.7 0 160.64 303.65 42383 +1996 78 2.62 -3.38 0.97 0 179.21 304.91 42587 +1996 79 5.61 -0.39 3.96 0 217.09 304.62 42791 +1996 80 2.74 -3.26 1.09 0.09 180.61 232.61 42996 +1996 81 1.58 -4.42 -0.07 0 167.44 313.82 43200 +1996 82 6.44 0.44 4.79 0.21 228.76 233.61 43404 +1996 83 8.77 2.77 7.12 0 264.42 310.93 43608 +1996 84 4.31 -1.69 2.66 0.3 199.85 239.24 43812 +1996 85 3.2 -2.8 1.55 0.01 186.07 242.01 44016 +1996 86 3.59 -2.41 1.94 0 190.82 324.73 44220 +1996 87 6.32 0.32 4.67 0 227.04 324.2 44424 +1996 88 4.28 -1.72 2.63 0 199.47 328.96 44627 +1996 89 7.18 1.18 5.53 0.09 239.61 245.83 44831 +1996 90 5.75 -0.25 4.1 0.07 219.02 248.98 45034 +1996 91 12.87 6.87 11.22 0.03 338.83 242.47 45237 +1996 92 17.88 11.88 16.23 2 453.43 235.75 45439 +1996 93 21.71 15.71 20.06 1.12 561.93 229.02 45642 +1996 94 21.07 15.07 19.42 0.67 542.4 232.07 45843 +1996 95 16.85 10.85 15.2 0.15 427.5 242.41 46045 +1996 96 12.54 6.54 10.89 0 332.24 334.69 46246 +1996 97 17.23 11.23 15.58 0 436.91 326.31 46446 +1996 98 15.53 9.53 13.88 0 396.12 332.35 46647 +1996 99 15.98 9.98 14.33 0 406.59 333.26 46846 +1996 100 18.8 12.8 17.15 0.5 477.71 245.87 47045 +1996 101 17.5 11.5 15.85 0.01 443.71 249.93 47243 +1996 102 21.12 15.12 19.47 0 543.91 324.46 47441 +1996 103 19.74 13.74 18.09 0.18 503.65 247.9 47638 +1996 104 13.75 7.75 12.1 0 356.94 347.6 47834 +1996 105 14.18 8.18 12.53 0.14 366.09 261.34 48030 +1996 106 17.99 11.99 16.34 0 456.27 340.66 48225 +1996 107 12.42 6.42 10.77 0 329.87 355.43 48419 +1996 108 12.14 6.14 10.49 0.47 324.4 268.3 48612 +1996 109 12.1 6.1 10.45 0.11 323.63 269.57 48804 +1996 110 11.57 5.57 9.92 0 313.51 361.87 48995 +1996 111 9.64 3.64 7.99 0.01 278.91 275.18 49185 +1996 112 10.84 4.84 9.19 0 300.02 366.32 49374 +1996 113 7.96 1.96 6.31 0 251.52 372.53 49561 +1996 114 9.37 3.37 7.72 0 274.35 371.78 49748 +1996 115 9.6 3.6 7.95 0.43 278.23 279.63 49933 +1996 116 9.92 3.92 8.27 0.31 283.72 280.14 50117 +1996 117 14.77 8.77 13.12 1.96 378.97 273.69 50300 +1996 118 13.67 7.67 12.02 0.07 355.26 276.56 50481 +1996 119 10.05 4.05 8.4 0.52 285.98 282.88 50661 +1996 120 13.21 7.21 11.56 0 345.73 372.13 50840 +1996 121 19.83 13.83 18.18 0.95 506.2 266.73 51016 +1996 122 16.7 10.7 15.05 0.27 423.83 274.5 51191 +1996 123 15.96 9.96 14.31 0.04 406.12 276.73 51365 +1996 124 16.88 10.88 15.23 0 428.23 367.6 51536 +1996 125 17.75 11.75 16.1 0.14 450.08 274.61 51706 +1996 126 18.34 12.34 16.69 0.07 465.43 274.05 51874 +1996 127 16.42 10.42 14.77 0.06 417.05 278.76 52039 +1996 128 15.67 9.67 14.02 0.01 399.35 280.98 52203 +1996 129 15.2 9.2 13.55 0.66 388.59 282.5 52365 +1996 130 14.77 8.77 13.12 0 378.97 378.52 52524 +1996 131 18.5 12.5 16.85 0.12 469.67 276.88 52681 +1996 132 20.87 14.87 19.22 0.26 536.42 271.71 52836 +1996 133 18.56 12.56 16.91 0.97 471.27 277.87 52989 +1996 134 20.88 14.88 19.23 0 536.72 363.61 53138 +1996 135 20.13 14.13 18.48 0.04 514.76 275.14 53286 +1996 136 21.09 15.09 19.44 0.01 543 273.13 53430 +1996 137 22.36 16.36 20.71 1.83 582.38 270.14 53572 +1996 138 23.49 17.49 21.84 0.77 619.42 267.25 53711 +1996 139 26.48 20.48 24.83 1.28 727.2 257.85 53848 +1996 140 23.17 17.17 21.52 1.31 608.73 269.06 53981 +1996 141 21.69 15.69 20.04 0.05 561.31 273.63 54111 +1996 142 19.41 13.41 17.76 0 494.41 373.2 54238 +1996 143 21.77 15.77 20.12 0.03 563.79 274.16 54362 +1996 144 18.97 12.97 17.32 0.02 482.32 281.71 54483 +1996 145 21.19 15.19 19.54 0 546.02 368.59 54600 +1996 146 21.93 15.93 20.28 0 568.78 366.24 54714 +1996 147 21.62 15.62 19.97 0 559.15 367.85 54824 +1996 148 22.05 16.05 20.4 0 572.55 366.62 54931 +1996 149 20.99 14.99 19.34 0.16 540 278.11 55034 +1996 150 16.84 10.84 15.19 1.03 427.25 288.23 55134 +1996 151 18.7 12.7 17.05 0 475.02 379.18 55229 +1996 152 23.07 17.07 21.42 0 605.43 363.76 55321 +1996 153 23.47 17.47 21.82 0.36 618.75 271.78 55409 +1996 154 27.6 21.6 25.95 0.8 771.46 257.75 55492 +1996 155 26.4 20.4 24.75 0.15 724.13 262.36 55572 +1996 156 23.12 17.12 21.47 1.98 607.08 273.45 55648 +1996 157 18.35 12.35 16.7 0.01 465.7 286.22 55719 +1996 158 20.84 14.84 19.19 0.05 535.53 280.17 55786 +1996 159 24.06 18.06 22.41 0.23 638.85 270.96 55849 +1996 160 27.08 21.08 25.43 0 750.64 347.51 55908 +1996 161 27.27 21.27 25.62 0 758.19 346.61 55962 +1996 162 28.39 22.39 26.74 0 804.04 340.83 56011 +1996 163 27.42 21.42 25.77 0 764.2 346.11 56056 +1996 164 24.11 18.11 22.46 0 640.58 361.62 56097 +1996 165 21.56 15.56 19.91 0.08 557.3 278.89 56133 +1996 166 23.65 17.65 22 0.6 624.82 272.79 56165 +1996 167 20.32 14.32 18.67 0 520.25 376.31 56192 +1996 168 20.46 14.46 18.81 0 524.33 375.9 56214 +1996 169 23.44 17.44 21.79 0 617.74 364.62 56231 +1996 170 18.96 12.96 17.31 0.07 482.04 285.68 56244 +1996 171 16.27 10.27 14.62 0.85 413.46 291.69 56252 +1996 172 21.88 15.88 20.23 0 567.22 370.82 56256 +1996 173 21.12 15.12 19.47 0 543.91 373.6 56255 +1996 174 19.38 13.38 17.73 0 493.58 379.5 56249 +1996 175 21.04 15.04 19.39 0.98 541.5 280.33 56238 +1996 176 23.52 17.52 21.87 0 620.43 364.18 56223 +1996 177 24.77 18.77 23.12 0 663.78 358.74 56203 +1996 178 23.57 17.57 21.92 0 622.12 363.9 56179 +1996 179 21.36 15.36 19.71 0 551.18 372.4 56150 +1996 180 21.99 15.99 20.34 0 570.66 369.94 56116 +1996 181 23.42 17.42 21.77 0 617.07 364.23 56078 +1996 182 23.92 17.92 22.27 0 634.03 362.01 56035 +1996 183 23.47 17.47 21.82 0.26 618.75 272.78 55987 +1996 184 24.71 18.71 23.06 0.22 661.64 268.72 55935 +1996 185 23.12 17.12 21.47 0.21 607.08 273.68 55879 +1996 186 23.19 17.19 21.54 1.16 609.4 273.28 55818 +1996 187 21.88 15.88 20.23 0 567.22 369.29 55753 +1996 188 19.49 13.49 17.84 0.01 496.64 283.07 55684 +1996 189 17.2 11.2 15.55 0.11 436.16 288.2 55611 +1996 190 16.52 10.52 14.87 0 419.46 385.81 55533 +1996 191 17.31 11.31 15.66 0.23 438.92 287.48 55451 +1996 192 20.14 14.14 18.49 0 515.05 374.13 55366 +1996 193 26.16 20.16 24.51 0 714.96 349.57 55276 +1996 194 24.19 18.19 22.54 2.42 643.35 268.66 55182 +1996 195 22.39 16.39 20.74 1.3 583.34 273.92 55085 +1996 196 22.88 16.88 21.23 0.38 599.18 272.19 54984 +1996 197 23.68 17.68 22.03 0 625.84 359.24 54879 +1996 198 29.23 23.23 27.58 0.03 839.93 249.08 54770 +1996 199 27.2 21.2 25.55 0.01 755.4 256.86 54658 +1996 200 27.53 21.53 25.88 0 768.63 340.45 54542 +1996 201 24.58 18.58 22.93 0 657.03 353.84 54423 +1996 202 25.59 19.59 23.94 0.1 693.58 261.6 54301 +1996 203 22.31 16.31 20.66 0.11 580.78 271.5 54176 +1996 204 21.68 15.68 20.03 0.01 561.01 272.89 54047 +1996 205 17.48 11.48 15.83 0 443.2 377.03 53915 +1996 206 20.6 14.6 18.95 0 528.43 366.62 53780 +1996 207 19.58 13.58 17.93 0 499.16 369.37 53643 +1996 208 25.16 19.16 23.51 0 677.81 347.47 53502 +1996 209 23.9 17.9 22.25 0 633.35 352.23 53359 +1996 210 19.41 13.41 17.76 0 494.41 367.98 53213 +1996 211 19.64 13.64 17.99 0.52 500.84 274.84 53064 +1996 212 22.12 16.12 20.47 0 574.76 357.05 52913 +1996 213 20.83 14.83 19.18 0.29 535.23 270.69 52760 +1996 214 23.84 17.84 22.19 0.03 631.29 261.65 52604 +1996 215 23.29 17.29 21.64 0.03 612.72 262.82 52445 +1996 216 24.89 18.89 23.24 0 668.07 342.83 52285 +1996 217 23 17 21.35 0.1 603.12 262.27 52122 +1996 218 22.58 16.58 20.93 0.11 589.44 262.87 51958 +1996 219 18.91 12.91 17.26 0 480.69 361.97 51791 +1996 220 18.27 12.27 16.62 0 463.59 362.94 51622 +1996 221 19.95 13.95 18.3 0.27 509.61 267.56 51451 +1996 222 20.98 14.98 19.33 0.55 539.7 264.21 51279 +1996 223 19.19 13.19 17.54 0 488.33 356.95 51105 +1996 224 21.76 15.76 20.11 0 563.48 347.37 50929 +1996 225 23.96 17.96 22.31 0 635.41 337.93 50751 +1996 226 21.03 15.03 19.38 0.01 541.2 260.74 50572 +1996 227 19.28 13.28 17.63 0 490.81 352.03 50392 +1996 228 24.42 18.42 22.77 0 651.39 332.55 50210 +1996 229 23.69 17.69 22.04 0.58 626.18 250.71 50026 +1996 230 24.19 18.19 22.54 0.51 643.35 248.3 49842 +1996 231 25.21 19.21 23.56 0.11 679.63 244.09 49656 +1996 232 26.88 20.88 25.23 2.65 742.76 237.59 49469 +1996 233 25.82 19.82 24.17 1.18 702.14 240.15 49280 +1996 234 22.13 16.13 20.48 1.24 575.07 249.99 49091 +1996 235 22.63 16.63 20.98 1.36 591.05 247.56 48900 +1996 236 27.07 21.07 25.42 0.08 750.24 232.9 48709 +1996 237 26.97 20.97 25.32 0.11 746.3 232.09 48516 +1996 238 27 21 25.35 0.4 747.48 230.81 48323 +1996 239 24.44 18.44 22.79 0 652.09 317.19 48128 +1996 240 23.41 17.41 21.76 0 616.73 319.44 47933 +1996 241 23.48 17.48 21.83 0 619.08 317.51 47737 +1996 242 25.67 19.67 24.02 0.14 696.55 230.42 47541 +1996 243 27.62 21.62 25.97 0 772.27 296.92 47343 +1996 244 21.43 15.43 19.78 0.65 553.32 239.54 47145 +1996 245 18.87 12.87 17.22 1.88 479.6 244.01 46947 +1996 246 20.6 14.6 18.95 0.01 528.43 238.72 46747 +1996 247 20.84 14.84 19.19 0.07 535.53 236.79 46547 +1996 248 19.29 13.29 17.64 0.04 491.09 238.83 46347 +1996 249 16.48 10.48 14.83 0.07 418.5 242.8 46146 +1996 250 18.85 12.85 17.2 0 479.06 315.68 45945 +1996 251 22.06 16.06 20.41 0.86 572.86 227.96 45743 +1996 252 22.26 16.26 20.61 1.17 579.19 225.9 45541 +1996 253 24.24 18.24 22.59 0.61 645.09 219.21 45339 +1996 254 20.43 14.43 18.78 0.25 523.45 227.08 45136 +1996 255 19.29 13.29 17.64 0.32 491.09 227.85 44933 +1996 256 16.86 10.86 15.21 0.56 427.74 230.82 44730 +1996 257 15.48 9.48 13.83 1.14 394.97 231.54 44527 +1996 258 17.59 11.59 15.94 0.51 446 226.12 44323 +1996 259 17.93 11.93 16.28 0.01 454.72 223.68 44119 +1996 260 16.45 10.45 14.8 0.1 417.77 224.53 43915 +1996 261 14.95 8.95 13.3 0 382.97 300.16 43711 +1996 262 14.36 8.36 12.71 0 369.98 298.95 43507 +1996 263 14.95 8.95 13.3 0.46 382.97 221.46 43303 +1996 264 13.69 7.69 12.04 0.65 355.68 221.36 43099 +1996 265 12 6 10.35 0.09 321.7 221.81 42894 +1996 266 14.34 8.34 12.69 0.64 369.54 216.76 42690 +1996 267 13.12 7.12 11.47 0 343.89 288.57 42486 +1996 268 12.64 6.64 10.99 0.29 334.22 215.11 42282 +1996 269 12.65 6.65 11 0.75 334.42 213.18 42078 +1996 270 12.28 6.28 10.63 0.27 327.13 211.65 41875 +1996 271 11.42 5.42 9.77 0.04 310.69 210.68 41671 +1996 272 12.78 6.78 11.13 0 337.02 275.95 41468 +1996 273 11.13 5.13 9.48 1.35 305.31 207.01 41265 +1996 274 12.39 6.39 10.74 0.68 329.28 203.5 41062 +1996 275 14.54 8.54 12.89 0 373.9 264.86 40860 +1996 276 17.48 11.48 15.83 0 443.2 256.34 40658 +1996 277 20 14 18.35 0 511.04 247.93 40456 +1996 278 16.41 10.41 14.76 0.18 416.81 189.84 40255 +1996 279 16.68 10.68 15.03 0.56 423.34 187.36 40054 +1996 280 18.19 12.19 16.54 0.98 461.49 183.04 39854 +1996 281 17.83 11.83 16.18 0.51 452.14 181.63 39654 +1996 282 13.91 7.91 12.26 0.55 360.32 185.14 39455 +1996 283 12.34 6.34 10.69 0 328.3 246.51 39256 +1996 284 9.47 3.47 7.82 0.08 276.03 185.55 39058 +1996 285 9.76 3.76 8.11 0 280.97 244.36 38861 +1996 286 12.47 6.47 10.82 0 330.86 237.88 38664 +1996 287 14.97 8.97 13.32 0.03 383.42 173.24 38468 +1996 288 14.1 8.1 12.45 0.53 364.37 172.25 38273 +1996 289 15.24 9.24 13.59 0.65 389.5 168.89 38079 +1996 290 16.76 10.76 15.11 0 425.29 219.69 37885 +1996 291 14.16 8.16 12.51 0 365.66 221.45 37693 +1996 292 17.26 11.26 15.61 0 437.66 213.52 37501 +1996 293 14.91 8.91 13.26 0 382.08 214.92 37311 +1996 294 13.7 7.7 12.05 0 355.89 213.93 37121 +1996 295 17.18 11.18 15.53 0 435.66 205.45 36933 +1996 296 16 10 14.35 1.24 407.06 153.73 36745 +1996 297 19.41 13.41 17.76 0.49 494.41 147.06 36560 +1996 298 18.23 12.23 16.58 1.75 462.54 146.9 36375 +1996 299 16.94 10.94 15.29 0.3 429.71 146.62 36191 +1996 300 17.16 11.16 15.51 0.56 435.17 144.4 36009 +1996 301 14.1 8.1 12.45 0 364.37 194.88 35829 +1996 302 15.77 9.77 14.12 0 401.68 189.83 35650 +1996 303 16.67 10.67 15.02 0 423.1 185.89 35472 +1996 304 18.57 12.57 16.92 0 471.54 180.27 35296 +1996 305 12.64 6.64 10.99 0.25 334.22 139.94 35122 +1996 306 10.03 4.03 8.38 0 285.63 187.37 34950 +1996 307 11.09 5.09 9.44 0 304.58 183.71 34779 +1996 308 11.94 5.94 10.29 0.16 320.54 135.12 34610 +1996 309 12.59 6.59 10.94 0.17 333.23 132.82 34444 +1996 310 12.4 6.4 10.75 0.6 329.48 131.19 34279 +1996 311 13.13 7.13 11.48 0 344.1 171.9 34116 +1996 312 11.61 5.61 9.96 0 314.26 171.07 33956 +1996 313 10.53 4.53 8.88 0 294.44 170.13 33797 +1996 314 13.86 7.86 12.21 0 359.26 164.44 33641 +1996 315 15.42 9.42 13.77 0 393.6 159.94 33488 +1996 316 15.47 9.47 13.82 0 394.74 157.76 33337 +1996 317 15.2 9.2 13.55 0.2 388.59 117 33188 +1996 318 15.91 9.91 14.26 0 404.95 152.78 33042 +1996 319 12.62 6.62 10.97 0 333.83 155.19 32899 +1996 320 11.14 5.14 9.49 0.01 305.5 116.19 32758 +1996 321 12.07 6.07 10.42 0 323.05 151.89 32620 +1996 322 8 2 6.35 0 252.14 153.87 32486 +1996 323 10.1 4.1 8.45 0 286.85 150.45 32354 +1996 324 14.08 8.08 12.43 0.03 363.94 108.23 32225 +1996 325 9.46 3.46 7.81 0 275.86 147.29 32100 +1996 326 10.71 4.71 9.06 0.52 297.67 108.55 31977 +1996 327 12.7 6.7 11.05 0.16 335.42 105.71 31858 +1996 328 12.96 6.96 11.31 1.21 340.64 104.06 31743 +1996 329 5.7 -0.3 4.05 0 218.33 143.42 31631 +1996 330 8.04 2.04 6.39 0 252.77 140.31 31522 +1996 331 6.88 0.88 5.23 0 235.16 139.85 31417 +1996 332 8.66 2.66 7.01 0 262.64 136.89 31316 +1996 333 8.06 2.06 6.41 0 253.08 136.28 31218 +1996 334 10.52 4.52 8.87 0 294.26 133.2 31125 +1996 335 2.66 -3.34 1.01 0 179.67 137.43 31035 +1996 336 6.47 0.47 4.82 0 229.19 134.09 30949 +1996 337 7.21 1.21 5.56 0.03 240.06 98.94 30867 +1996 338 2.65 -3.35 1 1.06 179.56 100.3 30790 +1996 339 1.87 -4.13 0.22 0.03 170.65 100 30716 +1996 340 0.75 -5.25 -0.9 0 158.54 133.12 30647 +1996 341 4.76 -1.24 3.11 0 205.68 130.13 30582 +1996 342 3.92 -2.08 2.27 0 194.91 129.84 30521 +1996 343 6.04 0.04 4.39 0 223.07 127.77 30465 +1996 344 9.1 3.1 7.45 0 269.84 124.51 30413 +1996 345 10.75 4.75 9.1 0.11 298.39 92.08 30366 +1996 346 6.1 0.1 4.45 0.21 223.91 94.22 30323 +1996 347 1.37 -4.63 -0.28 0.17 165.15 95.69 30284 +1996 348 -0.86 -6.86 -2.51 0.19 142.42 140.37 30251 +1996 349 0.2 -5.8 -1.45 0.09 152.86 139.78 30221 +1996 350 4.82 -1.18 3.17 0.29 206.47 93.56 30197 +1996 351 4.16 -1.84 2.51 0 197.94 124.89 30177 +1996 352 2.19 -3.81 0.54 0.39 174.26 94.36 30162 +1996 353 -1.14 -7.14 -2.79 0 139.77 127.18 30151 +1996 354 -3.22 -9.22 -4.87 0 121.37 127.89 30145 +1996 355 -3.2 -9.2 -4.85 0 121.53 127.88 30144 +1996 356 -1.46 -7.46 -3.11 0 136.79 127.29 30147 +1996 357 -4.12 -10.12 -5.77 0.18 114.08 140.54 30156 +1996 358 4.02 -1.98 2.37 0 196.17 168.74 30169 +1996 359 2.59 -3.41 0.94 0.24 178.86 94.36 30186 +1996 360 1.36 -4.64 -0.29 0.58 165.04 95.07 30208 +1996 361 4.46 -1.54 2.81 0 201.78 125.52 30235 +1996 362 2.34 -3.66 0.69 0 175.97 127.07 30267 +1996 363 1.51 -4.49 -0.14 0 166.68 128.06 30303 +1996 364 0.93 -5.07 -0.72 0 160.43 128.72 30343 +1996 365 -1.31 -7.31 -2.96 0 138.18 130.22 30388 +1997 1 -2.65 -8.65 -4.3 0 126.19 131.62 30438 +1997 2 -0.74 -6.74 -2.39 0 143.57 131.64 30492 +1997 3 0.34 -5.66 -1.31 0 154.29 132.13 30551 +1997 4 3.3 -2.7 1.65 0 187.28 131.62 30614 +1997 5 6.27 0.27 4.62 0 226.32 130.51 30681 +1997 6 6.39 0.39 4.74 0 228.04 131.32 30752 +1997 7 4.35 -1.65 2.7 0.05 200.36 100.02 30828 +1997 8 3.44 -2.56 1.79 0 188.98 135.37 30907 +1997 9 3.94 -2.06 2.29 0 195.16 136.34 30991 +1997 10 0.76 -5.24 -0.89 0 158.64 139.29 31079 +1997 11 0.37 -5.63 -1.28 0.07 154.6 105.35 31171 +1997 12 0.84 -5.16 -0.81 0 159.48 141.27 31266 +1997 13 4.69 -1.31 3.04 0 204.76 140.81 31366 +1997 14 7.74 1.74 6.09 0 248.11 140.2 31469 +1997 15 5.04 -0.96 3.39 0 209.38 143.5 31575 +1997 16 1.46 -4.54 -0.19 0.36 166.13 110.12 31686 +1997 17 2.31 -3.69 0.66 0.22 175.63 111.06 31800 +1997 18 2.16 -3.84 0.51 0 173.92 150.06 31917 +1997 19 4.34 -1.66 2.69 0 200.23 150.73 32038 +1997 20 4.93 -1.07 3.28 0 207.92 151.93 32161 +1997 21 0.32 -5.68 -1.33 0 154.09 156.56 32289 +1997 22 0.32 -5.68 -1.33 0 154.09 158.32 32419 +1997 23 2.11 -3.89 0.46 0 173.35 159.17 32552 +1997 24 4.21 -1.79 2.56 0.16 198.57 119.99 32688 +1997 25 1.37 -4.63 -0.28 0 165.15 163.55 32827 +1997 26 6.1 0.1 4.45 0 223.91 162.47 32969 +1997 27 3.91 -2.09 2.26 0.01 194.79 124.51 33114 +1997 28 0.68 -5.32 -0.97 0 157.8 170.12 33261 +1997 29 0.34 -5.66 -1.31 0 154.29 172.7 33411 +1997 30 -0.15 -6.15 -1.8 0.08 149.35 170.97 33564 +1997 31 -1.05 -7.05 -2.7 0.75 140.62 175.05 33718 +1997 32 4.83 -1.17 3.18 0.05 206.6 173.26 33875 +1997 33 12 6 10.35 0 321.7 211.84 34035 +1997 34 12.59 6.59 10.94 0 333.23 174.15 34196 +1997 35 11.29 5.29 9.64 0 308.27 177.74 34360 +1997 36 11.4 5.4 9.75 0.03 310.32 135.05 34526 +1997 37 14.49 8.49 12.84 0 372.81 178.55 34694 +1997 38 12.58 6.58 10.93 0 333.03 183.71 34863 +1997 39 12.49 6.49 10.84 0 331.25 186.35 35035 +1997 40 12.26 6.26 10.61 0 326.74 189.18 35208 +1997 41 10.2 4.2 8.55 0 288.6 194.15 35383 +1997 42 11.96 5.96 10.31 0 320.93 194.59 35560 +1997 43 13.71 7.71 12.06 0 356.1 194.92 35738 +1997 44 13.75 7.75 12.1 0 356.94 197.35 35918 +1997 45 10.29 4.29 8.64 0 290.18 204.31 36099 +1997 46 7.05 1.05 5.4 0.11 237.67 157.76 36282 +1997 47 8.28 2.28 6.63 0.13 256.55 158.95 36466 +1997 48 6.79 0.79 5.14 0 233.83 216.19 36652 +1997 49 5.77 -0.23 4.12 0 219.3 219.9 36838 +1997 50 3.16 -2.84 1.51 0 185.59 224.73 37026 +1997 51 6.34 0.34 4.69 0.05 227.32 168.75 37215 +1997 52 5.04 -0.96 3.39 0 209.38 229.01 37405 +1997 53 4.48 -1.52 2.83 0.24 202.04 174.34 37596 +1997 54 1.16 -4.84 -0.49 0 162.88 237.79 37788 +1997 55 -1.67 -7.67 -3.32 0 134.87 242.61 37981 +1997 56 -1.2 -7.2 -2.85 0 139.21 245.08 38175 +1997 57 -1.67 -7.67 -3.32 0 134.87 248.29 38370 +1997 58 3.61 -2.39 1.96 0 191.06 247.52 38565 +1997 59 1.03 -4.97 -0.62 0 161.49 252.26 38761 +1997 60 8.05 2.05 6.4 0 252.93 248.74 38958 +1997 61 11.61 5.61 9.96 0 314.26 247.07 39156 +1997 62 7.03 1.03 5.38 0 237.37 255.59 39355 +1997 63 8.38 2.38 6.73 0.09 258.14 192.78 39553 +1997 64 5.62 -0.38 3.97 0.52 217.23 197.24 39753 +1997 65 4.3 -1.7 2.65 0.15 199.72 200.38 39953 +1997 66 9.43 3.43 7.78 0.32 275.36 198.15 40154 +1997 67 8.32 2.32 6.67 0.1 257.19 201.37 40355 +1997 68 9.66 3.66 8.01 0.09 279.26 202.22 40556 +1997 69 8.56 2.56 6.91 0.33 261.02 205.25 40758 +1997 70 11.25 5.25 9.6 0 307.53 272.77 40960 +1997 71 12.49 6.49 10.84 0 331.25 273.68 41163 +1997 72 11.63 5.63 9.98 0 314.64 277.84 41366 +1997 73 12.83 6.83 11.18 0.18 338.02 208.88 41569 +1997 74 13.34 7.34 11.69 0.29 348.4 210.23 41772 +1997 75 9.36 3.36 7.71 0.2 274.18 216.94 41976 +1997 76 9.75 3.75 8.1 0 280.79 291.33 42179 +1997 77 10.62 4.62 8.97 0 296.05 292.62 42383 +1997 78 9.87 3.87 8.22 0 282.86 296.39 42587 +1997 79 8.07 2.07 6.42 0 253.24 301.62 42791 +1997 80 11.21 5.21 9.56 0 306.79 299.55 42996 +1997 81 9.61 3.61 7.96 0 278.4 304.58 43200 +1997 82 11.96 5.96 10.31 0 320.93 303.48 43404 +1997 83 13.82 7.82 12.17 0 358.42 302.55 43608 +1997 84 12.03 6.03 10.38 0 322.28 308.33 43812 +1997 85 12.03 6.03 10.38 0 322.28 310.8 44016 +1997 86 6.31 0.31 4.66 0.08 226.89 241.24 44220 +1997 87 8.92 2.92 7.27 0.37 266.88 240.52 44424 +1997 88 7.44 1.44 5.79 0 243.52 325.13 44627 +1997 89 8.34 2.34 6.69 0 257.5 326.18 44831 +1997 90 6.51 0.51 4.86 0 229.76 331.03 45034 +1997 91 6.42 0.42 4.77 0 228.47 333.43 45237 +1997 92 7.47 1.47 5.82 1.02 243.98 250.73 45439 +1997 93 6.32 0.32 4.67 0.79 227.04 253.55 45642 +1997 94 4.82 -1.18 3.17 0.16 206.47 256.57 45843 +1997 95 5.16 -0.84 3.51 0.29 210.98 257.9 46045 +1997 96 9.22 3.22 7.57 0 271.84 340.44 46246 +1997 97 7.61 1.61 5.96 0 246.11 344.9 46446 +1997 98 6.83 0.83 5.18 0 234.42 347.98 46647 +1997 99 12.24 6.24 10.59 1.23 326.35 255.94 46846 +1997 100 11.78 5.78 10.13 0 317.49 344.06 47045 +1997 101 10.11 4.11 8.46 0 287.02 348.96 47243 +1997 102 10.36 4.36 8.71 0.02 291.42 262.84 47441 +1997 103 13.75 7.75 12.1 0 356.94 345.79 47638 +1997 104 9.59 3.59 7.94 0 278.06 355.44 47834 +1997 105 11.63 5.63 9.98 0 314.64 353.64 48030 +1997 106 12.47 6.47 10.82 0 330.86 353.66 48225 +1997 107 16.57 10.57 14.92 0 420.67 346.06 48419 +1997 108 14.17 8.17 12.52 0 365.87 353.49 48612 +1997 109 12.98 6.98 11.33 0 341.05 357.65 48804 +1997 110 10.32 4.32 8.67 0 290.71 364.16 48995 +1997 111 13.77 7.77 12.12 0 357.36 358.92 49185 +1997 112 11.24 5.24 9.59 0 307.35 365.58 49374 +1997 113 10.65 4.65 9 0 296.59 368.03 49561 +1997 114 14.86 8.86 13.21 0.13 380.96 270.58 49748 +1997 115 16.86 10.86 15.21 0 427.74 357.17 49933 +1997 116 17.59 11.59 15.94 0 446 356.38 50117 +1997 117 18.21 12.21 16.56 0 462.01 355.9 50300 +1997 118 17.9 11.9 16.25 0 453.94 358.08 50481 +1997 119 14.53 8.53 12.88 0 373.68 367.98 50661 +1997 120 15.26 9.26 13.61 0 389.95 367.39 50840 +1997 121 21.72 15.72 20.07 0.04 562.24 261.93 51016 +1997 122 16.74 10.74 15.09 2.16 424.8 274.42 51191 +1997 123 17.41 11.41 15.76 0 441.43 365.07 51365 +1997 124 19.41 13.41 17.76 0 494.41 360.18 51536 +1997 125 18.66 12.66 17.01 0.02 473.94 272.6 51706 +1997 126 20.48 14.48 18.83 0 524.91 358.62 51874 +1997 127 22.63 16.63 20.98 0 591.05 351.78 52039 +1997 128 20.26 14.26 18.61 0 518.51 361.19 52203 +1997 129 18.1 12.1 16.45 0 459.14 368.8 52365 +1997 130 17.71 11.71 16.06 0 449.06 370.72 52524 +1997 131 18.08 12.08 16.43 0.2 458.62 277.82 52681 +1997 132 17.44 11.44 15.79 0 442.19 373.1 52836 +1997 133 13.77 7.77 12.12 0 357.36 383.23 52989 +1997 134 15.85 9.85 14.2 0.02 403.54 284.13 53138 +1997 135 17.08 11.08 15.43 0.15 433.18 282.16 53286 +1997 136 16.8 10.8 15.15 0.48 426.27 283.22 53430 +1997 137 16.69 10.69 15.04 0 423.59 378.64 53572 +1997 138 21.52 15.52 19.87 0.77 556.07 272.92 53711 +1997 139 19.79 13.79 18.14 1.87 505.07 277.92 53848 +1997 140 24.7 18.7 23.05 0 661.28 352.37 53981 +1997 141 29.41 23.41 27.76 0.04 847.8 247.08 54111 +1997 142 29.18 23.18 27.53 0.05 837.76 248.38 54238 +1997 143 26.34 20.34 24.69 0 721.82 346.28 54362 +1997 144 22.04 16.04 20.39 0.01 572.24 273.75 54483 +1997 145 20.33 14.33 18.68 0 520.54 371.6 54600 +1997 146 25.21 19.21 23.56 0 679.63 352.76 54714 +1997 147 25.91 19.91 24.26 0 705.51 350 54824 +1997 148 19.57 13.57 17.92 0 498.88 375.37 54931 +1997 149 17.94 11.94 16.29 0 454.98 380.79 55034 +1997 150 18.48 12.48 16.83 0 469.14 379.48 55134 +1997 151 15.75 9.75 14.1 0 401.21 387.67 55229 +1997 152 13.86 7.86 12.21 0 359.26 392.49 55321 +1997 153 18.5 12.5 16.85 0.32 469.67 285.12 55409 +1997 154 20.76 14.76 19.11 1.05 533.15 279.75 55492 +1997 155 22.73 16.73 21.08 0.09 594.29 274.38 55572 +1997 156 24.46 18.46 22.81 0.18 652.79 269.25 55648 +1997 157 19.66 13.66 18.01 0.03 501.4 283.08 55719 +1997 158 19.51 13.51 17.86 1.32 497.2 283.58 55786 +1997 159 20.83 14.83 19.18 0.16 535.23 280.38 55849 +1997 160 17.98 11.98 16.33 0 456.02 383.35 55908 +1997 161 19.84 13.84 18.19 0 506.48 377.5 55962 +1997 162 19.33 13.33 17.68 0.26 492.19 284.43 56011 +1997 163 20.77 14.77 19.12 0 533.45 374.57 56056 +1997 164 23.42 17.42 21.77 0 617.07 364.5 56097 +1997 165 22.39 16.39 20.74 0.11 583.34 276.53 56133 +1997 166 23.4 17.4 21.75 0 616.4 364.76 56165 +1997 167 21.71 15.71 20.06 0.01 561.93 278.49 56192 +1997 168 19.91 13.91 18.26 0.13 508.47 283.34 56214 +1997 169 19.85 13.85 18.2 0.6 506.77 283.5 56231 +1997 170 16.59 10.59 14.94 0.55 421.16 290.99 56244 +1997 171 19.04 13.04 17.39 0.07 484.22 285.53 56252 +1997 172 20.53 14.53 18.88 0.75 526.38 281.79 56256 +1997 173 24 18 22.35 1.15 636.78 271.74 56255 +1997 174 25.02 19.02 23.37 0.36 672.74 268.34 56249 +1997 175 25.46 19.46 23.81 0 688.78 355.77 56238 +1997 176 29.08 23.08 27.43 0 833.43 337.38 56223 +1997 177 32.56 26.56 30.91 0 995.84 316 56203 +1997 178 27.81 21.81 26.16 0.06 780.01 258.12 56179 +1997 179 27.85 21.85 26.2 0 781.65 343.85 56150 +1997 180 24.47 18.47 22.82 1.2 653.15 269.9 56116 +1997 181 27.46 21.46 25.81 0.04 765.81 259.27 56078 +1997 182 23.21 17.21 21.56 0.57 610.06 273.71 56035 +1997 183 27.41 21.41 25.76 0 763.8 345.64 55987 +1997 184 27.12 21.12 25.47 0.19 752.22 260.22 55935 +1997 185 23.5 17.5 21.85 0.03 619.76 272.52 55879 +1997 186 22.05 16.05 20.4 0.25 572.55 276.63 55818 +1997 187 22.53 16.53 20.88 0.47 587.83 275.11 55753 +1997 188 22.4 16.4 20.75 0.78 583.66 275.29 55684 +1997 189 21.9 15.9 20.25 0.01 567.85 276.58 55611 +1997 190 23.67 17.67 22.02 0 625.5 361.42 55533 +1997 191 23.01 17.01 21.36 0 603.45 363.85 55451 +1997 192 19.49 13.49 17.84 0.22 496.64 282.22 55366 +1997 193 18.81 12.81 17.16 0 477.98 378.2 55276 +1997 194 18.36 12.36 16.71 0.77 465.96 284.53 55182 +1997 195 20.26 14.26 18.61 2.16 518.51 279.71 55085 +1997 196 21.46 15.46 19.81 1.12 554.23 276.23 54984 +1997 197 22.09 16.09 20.44 0.31 573.81 274.14 54879 +1997 198 27.68 21.68 26.03 0.3 774.71 255.29 54770 +1997 199 26.76 20.76 25.11 0 738.06 344.66 54658 +1997 200 27.11 21.11 25.46 0.16 751.83 256.92 54542 +1997 201 23.13 17.13 21.48 0.21 607.41 269.89 54423 +1997 202 25.19 19.19 23.54 0 678.9 350.61 54301 +1997 203 24.75 18.75 23.1 0.47 663.06 264.05 54176 +1997 204 23.91 17.91 22.26 2.41 633.69 266.36 54047 +1997 205 24.06 18.06 22.41 1.83 638.85 265.51 53915 +1997 206 22.56 16.56 20.91 0.21 588.79 269.61 53780 +1997 207 22.59 16.59 20.94 1.38 589.76 269.04 53643 +1997 208 22.8 16.8 21.15 0.01 596.57 267.95 53502 +1997 209 23.43 17.43 21.78 0.28 617.4 265.6 53359 +1997 210 19.43 13.43 17.78 0 494.97 367.91 53213 +1997 211 21.31 15.31 19.66 0.18 549.66 270.59 53064 +1997 212 23.1 17.1 21.45 0.62 606.42 264.98 52913 +1997 213 26.44 20.44 24.79 1.5 725.66 253.63 52760 +1997 214 23.39 17.39 21.74 0.83 616.06 263.01 52604 +1997 215 18.98 12.98 17.33 0.71 482.59 274.16 52445 +1997 216 18.66 12.66 17.01 0.08 473.94 274.13 52285 +1997 217 14.27 8.27 12.62 0.11 368.03 282.26 52122 +1997 218 14.15 8.15 12.5 0.03 365.44 281.83 51958 +1997 219 17.02 11.02 15.37 0.86 431.69 275.59 51791 +1997 220 17.95 11.95 16.3 0 455.24 363.88 51622 +1997 221 20.42 14.42 18.77 0 523.16 355.2 51451 +1997 222 22.74 16.74 21.09 0 594.62 345.94 51279 +1997 223 19.55 13.55 17.9 0.01 498.32 266.87 51105 +1997 224 26.99 20.99 25.34 0.03 747.08 244.33 50929 +1997 225 20.66 14.66 19.01 0.04 530.2 262.52 50751 +1997 226 18.97 12.97 17.32 0.01 482.32 265.69 50572 +1997 227 20.69 14.69 19.04 0 531.08 347.52 50392 +1997 228 23.74 17.74 22.09 0 627.88 335.28 50210 +1997 229 27.59 21.59 25.94 0 771.06 317.27 50026 +1997 230 23.95 17.95 22.3 0.02 635.06 249.02 49842 +1997 231 25.06 19.06 23.41 0 674.19 326.08 49656 +1997 232 26.99 20.99 25.34 0 747.08 316.28 49469 +1997 233 30.75 24.75 29.1 0.25 908.33 221.77 49280 +1997 234 28.3 22.3 26.65 0 800.27 307.37 49091 +1997 235 27.57 21.57 25.92 0 770.25 309.52 48900 +1997 236 28.41 22.41 26.76 0 804.87 304.14 48709 +1997 237 28.45 22.45 26.8 0 806.56 302.43 48516 +1997 238 28.74 22.74 27.09 0.86 818.83 224.59 48323 +1997 239 25.82 19.82 24.17 0.03 702.14 233.65 48128 +1997 240 25.19 19.19 23.54 0 678.9 312.49 47933 +1997 241 26.25 20.25 24.6 0 718.38 306.4 47737 +1997 242 24.2 18.2 22.55 0.26 643.7 234.84 47541 +1997 243 23.4 17.4 21.75 0 616.4 314.33 47343 +1997 244 19.58 13.58 17.93 0 499.16 325.13 47145 +1997 245 20.85 14.85 19.2 0.41 535.82 239.58 46947 +1997 246 20.69 14.69 19.04 0 531.08 318.01 46747 +1997 247 19.15 13.15 17.5 0.02 487.23 240.57 46547 +1997 248 21.98 15.98 20.33 0 570.35 310.16 46347 +1997 249 20.84 14.84 19.19 0.04 535.53 233.85 46146 +1997 250 18.93 12.93 17.28 0 481.23 315.46 45945 +1997 251 20.63 14.63 18.98 0 529.31 308.46 45743 +1997 252 16.02 10.02 14.37 1.29 407.53 238.9 45541 +1997 253 15.84 9.84 14.19 0 403.31 316.82 45339 +1997 254 14.74 8.74 13.09 0.87 378.3 237.8 45136 +1997 255 18.15 12.15 16.5 0.1 460.44 230.12 44933 +1997 256 17.62 11.62 15.97 0 446.76 305.91 44730 +1997 257 18.15 12.15 16.5 0 460.44 302.43 44527 +1997 258 19.89 13.89 18.24 0 507.9 295.47 44323 +1997 259 17.86 11.86 16.21 0.03 452.91 223.81 44119 +1997 260 19.72 13.72 18.07 0 503.09 291.22 43915 +1997 261 17.89 11.89 16.24 0.05 453.69 220.16 43711 +1997 262 18.94 12.94 17.29 0 481.5 288.56 43507 +1997 263 20.15 14.15 18.5 0 515.34 282.92 43303 +1997 264 20.11 14.11 18.46 0 514.19 280.52 43099 +1997 265 20.2 14.2 18.55 1.37 516.78 208.48 42894 +1997 266 20.02 14.02 18.37 0.01 511.61 207.04 42690 +1997 267 17.11 11.11 15.46 0.29 433.92 210.43 42486 +1997 268 17.92 11.92 16.27 0 454.46 276.18 42282 +1997 269 22.9 16.9 21.25 0 599.84 260.29 42078 +1997 270 20.95 14.95 19.3 0.01 538.81 197.59 41875 +1997 271 25.67 19.67 24.02 0 696.55 246.19 41671 +1997 272 25.3 19.3 23.65 0.66 682.91 183.72 41468 +1997 273 23.01 17.01 21.36 2.17 603.45 187.5 41265 +1997 274 12.92 6.92 11.27 0 339.83 270.46 41062 +1997 275 13.09 7.09 11.44 0.34 343.28 200.54 40860 +1997 276 9.51 3.51 7.86 0 276.71 270.02 40658 +1997 277 14.79 8.79 13.14 0 379.41 259.05 40456 +1997 278 13.4 7.4 11.75 0 349.64 258.61 40255 +1997 279 11.06 5.06 9.41 0.41 304.03 194.55 40054 +1997 280 13.56 7.56 11.91 0.2 352.96 189.66 39854 +1997 281 11.99 5.99 10.34 0 321.51 252.62 39654 +1997 282 14.55 8.55 12.9 0 374.12 245.76 39455 +1997 283 11.11 5.11 9.46 0.01 304.95 186.22 39256 +1997 284 13.73 7.73 12.08 0 356.52 241.32 39058 +1997 285 12.12 6.12 10.47 0.09 324.02 180.87 38861 +1997 286 12.4 6.4 10.75 0 329.48 237.98 38664 +1997 287 12.9 6.9 11.25 0.57 339.43 175.73 38468 +1997 288 10.53 4.53 8.88 1.04 294.44 176.11 38273 +1997 289 9.84 3.84 8.19 0.47 282.34 174.76 38079 +1997 290 13.03 7.03 11.38 0.01 342.06 169.39 37885 +1997 291 14.59 8.59 12.94 0.15 375 165.58 37693 +1997 292 13.95 7.95 12.3 0 361.17 219.12 37501 +1997 293 11.41 5.41 9.76 0 310.51 219.99 37311 +1997 294 14.23 8.23 12.58 0 367.17 213.13 37121 +1997 295 16.26 10.26 14.61 0 413.22 207.06 36933 +1997 296 14.58 8.58 12.93 0 374.78 207.25 36745 +1997 297 17.14 11.14 15.49 0 434.67 200.37 36560 +1997 298 15.6 9.6 13.95 0 397.74 200.42 36375 +1997 299 9.54 3.54 7.89 0.21 277.21 154.31 36191 +1997 300 9.26 3.26 7.61 0 272.5 203.38 36009 +1997 301 8.97 2.97 7.32 0.32 267.7 150.86 35829 +1997 302 8.17 2.17 6.52 0.59 254.81 149.5 35650 +1997 303 8.85 2.85 7.2 0.04 265.73 147.04 35472 +1997 304 10.58 4.58 8.93 0 295.33 191.75 35296 +1997 305 7.37 1.37 5.72 0 242.46 192.24 35122 +1997 306 12.31 6.31 10.66 0 327.71 184.77 34950 +1997 307 10.35 4.35 8.7 0.02 291.24 138.39 34779 +1997 308 6.49 0.49 4.84 0.07 229.48 139.18 34610 +1997 309 11.9 5.9 10.25 0.34 319.78 133.44 34444 +1997 310 7.14 1.14 5.49 0 239.01 180.24 34279 +1997 311 7.19 1.19 5.54 0 239.76 178 34116 +1997 312 2.36 -3.64 0.71 1.85 176.2 134.13 33956 +1997 313 3.03 -2.97 1.38 0.35 184.04 132.2 33797 +1997 314 3.66 -2.34 2.01 0.39 191.68 130.4 33641 +1997 315 8.15 2.15 6.5 0.03 254.5 125.94 33488 +1997 316 9.45 3.45 7.8 0.54 275.69 123.43 33337 +1997 317 10.26 4.26 8.61 0.66 289.65 121.21 33188 +1997 318 10.67 4.67 9.02 0.94 296.95 119.18 33042 +1997 319 12.83 6.83 11.18 0 338.02 154.95 32899 +1997 320 12.24 6.24 10.59 0.5 326.35 115.33 32758 +1997 321 11.3 5.3 9.65 0 308.46 152.68 32620 +1997 322 10.44 4.44 8.79 0 292.83 151.73 32486 +1997 323 10.57 4.57 8.92 0.23 295.15 112.51 32354 +1997 324 7.51 1.51 5.86 0 244.59 150.6 32225 +1997 325 7.88 1.88 6.23 0 250.27 148.6 32100 +1997 326 7.02 1.02 5.37 0 237.22 147.8 31977 +1997 327 11.78 5.78 10.13 0.57 317.49 106.42 31858 +1997 328 15.83 9.83 14.18 0.35 403.08 101.59 31743 +1997 329 13 7 11.35 0.02 341.45 102.94 31631 +1997 330 11.85 5.85 10.2 0.09 318.82 102.76 31522 +1997 331 12.13 6.13 10.48 0 324.21 135.45 31417 +1997 332 11.63 5.63 9.98 0 314.64 134.32 31316 +1997 333 9.59 3.59 7.94 0 278.06 135.07 31218 +1997 334 9.86 3.86 8.21 0.41 282.68 100.32 31125 +1997 335 4.34 -1.66 2.69 0.74 200.23 102.37 31035 +1997 336 5.53 -0.47 3.88 0.36 215.99 101.02 30949 +1997 337 6.61 0.61 4.96 0.53 231.21 99.25 30867 +1997 338 6.39 0.39 4.74 0 228.04 131.55 30790 +1997 339 10.1 4.1 8.45 0 286.85 128.02 30716 +1997 340 8.73 2.73 7.08 0 263.77 128.39 30647 +1997 341 4.51 -1.49 2.86 0 202.42 130.27 30582 +1997 342 4.79 -1.21 3.14 0 206.07 129.35 30521 +1997 343 4.79 -1.21 3.14 0.12 206.07 96.39 30465 +1997 344 2.67 -3.33 1.02 0.01 179.79 96.41 30413 +1997 345 8.86 2.86 7.21 0.84 265.89 93.21 30366 +1997 346 8.17 2.17 6.52 0.57 254.81 93.18 30323 +1997 347 5.92 -0.08 4.27 0.42 221.39 93.86 30284 +1997 348 8.28 2.28 6.63 0.37 256.55 92.42 30251 +1997 349 5.88 -0.12 4.23 0.02 220.83 93.34 30221 +1997 350 4.56 -1.44 2.91 0 203.07 124.89 30197 +1997 351 9.41 3.41 7.76 0 275.02 121.47 30177 +1997 352 9.16 3.16 7.51 0.04 270.84 91.18 30162 +1997 353 5.48 -0.52 3.83 0 215.31 123.98 30151 +1997 354 7.46 1.46 5.81 0.02 243.83 92.02 30145 +1997 355 8.88 2.88 7.23 0 266.22 121.68 30144 +1997 356 5.33 -0.67 3.68 0 213.27 124.06 30147 +1997 357 3.61 -2.39 1.96 0 191.06 125.08 30156 +1997 358 2.85 -3.15 1.2 0.15 181.9 94.17 30169 +1997 359 4.8 -1.2 3.15 0 206.2 124.63 30186 +1997 360 7.88 1.88 6.23 0.51 250.27 92.28 30208 +1997 361 11.17 5.17 9.52 0.09 306.05 90.61 30235 +1997 362 9.16 3.16 7.51 0.9 270.84 92.15 30267 +1997 363 7.52 1.52 5.87 0.02 244.74 93.48 30303 +1997 364 5.71 -0.29 4.06 0.07 218.47 94.65 30343 +1997 365 4.49 -1.51 2.84 1.42 202.16 95.62 30388 +1998 1 0.81 -5.19 -0.84 0.19 159.17 97.68 30438 +1998 2 1.19 -4.81 -0.46 0.4 163.21 98.1 30492 +1998 3 2.45 -3.55 0.8 0 177.24 131.15 30551 +1998 4 0.17 -5.83 -1.48 0.02 152.56 99.85 30614 +1998 5 4.09 -1.91 2.44 0 197.05 131.84 30681 +1998 6 7.18 1.18 5.53 0 239.61 130.78 30752 +1998 7 7.06 1.06 5.41 0.06 237.82 98.74 30828 +1998 8 5.57 -0.43 3.92 0 216.54 134.11 30907 +1998 9 3.88 -2.12 2.23 0 194.41 136.38 30991 +1998 10 2.22 -3.78 0.57 0.01 174.6 103.93 31079 +1998 11 0.8 -5.2 -0.85 0.08 159.06 105.2 31171 +1998 12 -0.17 -6.17 -1.82 0 149.15 141.73 31266 +1998 13 1.92 -4.08 0.27 0 171.21 142.37 31366 +1998 14 7.05 1.05 5.4 0.05 237.67 105.53 31469 +1998 15 6.25 0.25 4.6 0 226.04 142.7 31575 +1998 16 5.48 -0.52 3.83 0 215.31 144.5 31686 +1998 17 5.68 -0.32 4.03 0.35 218.05 109.53 31800 +1998 18 1.49 -4.51 -0.16 0.03 166.46 112.81 31917 +1998 19 3.13 -2.87 1.48 0.43 185.23 113.59 32038 +1998 20 4.33 -1.67 2.68 0 200.11 152.32 32161 +1998 21 6.98 0.98 5.33 0 236.63 152.49 32289 +1998 22 7.61 1.61 5.96 0 246.11 153.73 32419 +1998 23 11.44 5.44 9.79 0.42 311.07 114.02 32552 +1998 24 11.61 5.61 9.96 0 314.26 153.87 32688 +1998 25 10.6 4.6 8.95 0 295.69 156.72 32827 +1998 26 13.9 7.9 12.25 0 360.11 155 32969 +1998 27 16.98 10.98 15.33 0 430.7 152.84 33114 +1998 28 16.34 10.34 14.69 0 415.13 155.85 33261 +1998 29 10 4 8.35 0 285.11 165.67 33411 +1998 30 6.82 0.82 5.17 0 234.27 170.71 33564 +1998 31 2.12 -3.88 0.47 0 173.47 176.35 33718 +1998 32 7.73 1.73 6.08 0 247.95 174.39 33875 +1998 33 7.18 1.18 5.53 0 239.61 177.47 34035 +1998 34 9.57 3.57 7.92 0 277.72 177.45 34196 +1998 35 8.86 2.86 7.21 0 265.89 180.25 34360 +1998 36 8.82 2.82 7.17 0 265.24 182.77 34526 +1998 37 8.79 2.79 7.14 0 264.75 185.19 34694 +1998 38 8.4 2.4 6.75 0 258.46 188.27 34863 +1998 39 9.04 3.04 7.39 0 268.85 190.22 35035 +1998 40 10.84 4.84 9.19 0 300.02 190.87 35208 +1998 41 8.16 2.16 6.51 0 254.65 196.26 35383 +1998 42 6.99 0.99 5.34 0 236.78 199.89 35560 +1998 43 7.08 1.08 5.43 0.02 238.11 151.87 35738 +1998 44 7.44 1.44 5.79 0 243.52 204.71 35918 +1998 45 11.2 5.2 9.55 0 306.61 203.23 36099 +1998 46 11.1 5.1 9.45 0 304.76 205.98 36282 +1998 47 11.25 5.25 9.6 0 307.53 208.56 36466 +1998 48 8.16 2.16 6.51 0 254.65 214.83 36652 +1998 49 6.85 0.85 5.2 0 234.71 218.9 36838 +1998 50 8.94 2.94 7.29 0 267.2 219.39 37026 +1998 51 9.42 3.42 7.77 0 275.19 221.78 37215 +1998 52 11.73 5.73 10.08 0 316.53 221.69 37405 +1998 53 14.09 8.09 12.44 0 364.16 221.16 37596 +1998 54 14.9 8.9 13.25 0.11 381.86 166.89 37788 +1998 55 9.94 3.94 8.29 0.09 284.07 174.41 37981 +1998 56 6.6 0.6 4.95 0 231.07 238.94 38175 +1998 57 10.12 4.12 8.47 0 287.2 237.82 38370 +1998 58 9.39 3.39 7.74 0 274.68 241.62 38565 +1998 59 9.57 3.57 7.92 0.07 277.72 183.05 38761 +1998 60 11.21 5.21 9.56 0.01 306.79 183.57 38958 +1998 61 7.61 1.61 5.96 0.01 246.11 189.12 39156 +1998 62 10.32 4.32 8.67 0 290.71 251.61 39355 +1998 63 10.86 4.86 9.21 0 300.38 253.84 39553 +1998 64 3.9 -2.1 2.25 0 194.66 264.62 39753 +1998 65 2.41 -3.59 0.76 0 176.78 268.83 39953 +1998 66 6.73 0.73 5.08 0.12 232.96 200.59 40154 +1998 67 4.51 -1.49 2.86 0.83 202.42 204.49 40355 +1998 68 3.87 -2.13 2.22 0.07 194.29 207.11 40556 +1998 69 3.67 -2.33 2.02 0 191.8 278.99 40758 +1998 70 7.07 1.07 5.42 0 237.97 278.32 40960 +1998 71 6.42 0.42 4.77 0 228.47 281.98 41163 +1998 72 6.73 0.73 5.08 0.1 232.96 213.34 41366 +1998 73 7.84 1.84 6.19 0.27 249.65 214.35 41569 +1998 74 6.09 0.09 4.44 0.07 223.77 217.97 41772 +1998 75 8.91 2.91 7.26 0.32 266.71 217.41 41976 +1998 76 6.87 0.87 5.22 0.08 235.01 221.33 42179 +1998 77 11.63 5.63 9.98 0 314.64 291.03 42383 +1998 78 9.32 3.32 7.67 0 273.51 297.18 42587 +1998 79 10.78 4.78 9.13 0 298.93 297.72 42791 +1998 80 14.57 8.57 12.92 0 374.56 293.53 42996 +1998 81 14.88 8.88 13.23 0 381.41 295.43 43200 +1998 82 15.26 9.26 13.61 0 389.95 297.23 43404 +1998 83 13.07 7.07 11.42 0 342.87 303.97 43608 +1998 84 14.43 8.43 12.78 0 371.5 303.83 43812 +1998 85 15.08 9.08 13.43 0.21 385.89 228.7 44016 +1998 86 15.34 9.34 13.69 0 391.77 306.73 44220 +1998 87 11.67 5.67 10.02 0 315.4 316.32 44424 +1998 88 8.18 2.18 6.53 0 254.97 324.12 44627 +1998 89 7.71 1.71 6.06 0 247.65 327.06 44831 +1998 90 9.25 3.25 7.6 0 272.34 327.22 45034 +1998 91 15.89 9.89 14.24 0.06 404.48 237.74 45237 +1998 92 12.59 6.59 10.94 0.07 333.23 244.53 45439 +1998 93 10.24 4.24 8.59 0.37 289.3 249.28 45642 +1998 94 11.02 5.02 9.37 0 303.3 333.22 45843 +1998 95 13.97 7.97 12.32 0.01 361.6 247.31 46045 +1998 96 13.99 7.99 12.34 0 362.02 331.79 46246 +1998 97 13.19 7.19 11.54 0 345.32 335.45 46446 +1998 98 12.57 6.57 10.92 0.34 332.83 253.97 46647 +1998 99 10.76 4.76 9.11 0.1 298.57 257.96 46846 +1998 100 10.31 4.31 8.66 0.06 290.53 260.01 47045 +1998 101 14.29 8.29 12.64 0 368.46 340.93 47243 +1998 102 15.82 9.82 14.17 0.01 402.84 254.48 47441 +1998 103 16.93 10.93 15.28 0 429.47 338.36 47638 +1998 104 13.9 7.9 12.25 0 360.11 347.28 47834 +1998 105 17.47 11.47 15.82 0 442.95 340.47 48030 +1998 106 18.83 12.83 17.18 0 478.52 338.29 48225 +1998 107 12.42 6.42 10.77 0.13 329.87 266.58 48419 +1998 108 15.13 9.13 13.48 0 387.01 351.3 48612 +1998 109 16.84 10.84 15.19 0.26 427.25 261.49 48804 +1998 110 19.86 13.86 18.21 1.39 507.05 256.04 48995 +1998 111 22.27 16.27 20.62 1.03 579.51 251.11 49185 +1998 112 20.3 14.3 18.65 1.15 519.67 257.21 49374 +1998 113 14.84 8.84 13.19 0.11 380.52 269.5 49561 +1998 114 16.83 10.83 15.18 0.3 427.01 266.88 49748 +1998 115 17.96 11.96 16.31 0.31 455.5 265.61 49933 +1998 116 12.28 6.28 10.63 0 327.13 369.06 50117 +1998 117 12.8 6.8 11.15 0 337.42 369.31 50300 +1998 118 15.47 9.47 13.82 0.03 394.74 273.4 50481 +1998 119 15.82 9.82 14.17 0 402.84 364.84 50661 +1998 120 19.04 13.04 17.39 0 484.22 357.02 50840 +1998 121 18.95 12.95 17.3 0.06 481.77 268.79 51016 +1998 122 13.58 7.58 11.93 0.98 353.38 280.23 51191 +1998 123 16.78 10.78 15.13 1.17 425.78 275.1 51365 +1998 124 16.65 10.65 15 0.69 422.61 276.17 51536 +1998 125 18.63 12.63 16.98 0 473.14 363.55 51706 +1998 126 18.19 12.19 16.54 0.4 461.49 274.38 51874 +1998 127 18.32 12.32 16.67 0.81 464.91 274.75 52039 +1998 128 18.16 12.16 16.51 0 460.7 367.79 52203 +1998 129 22.22 16.22 20.57 0 577.92 355.09 52365 +1998 130 23.78 17.78 22.13 0.1 629.24 262.32 52524 +1998 131 24.06 18.06 22.41 0.06 638.85 262.02 52681 +1998 132 20.59 14.59 18.94 0 528.14 363.24 52836 +1998 133 21.66 15.66 20.01 0.12 560.39 270.11 52989 +1998 134 20.17 14.17 18.52 0.31 515.92 274.53 53138 +1998 135 16.81 10.81 15.16 0.14 426.52 282.73 53286 +1998 136 19.41 13.41 17.76 0.53 494.41 277.38 53430 +1998 137 19.83 13.83 18.18 0.36 506.2 276.87 53572 +1998 138 20.88 14.88 19.23 0 536.72 366.18 53711 +1998 139 16.74 10.74 15.09 0 424.8 379.79 53848 +1998 140 15.39 9.39 13.74 0.02 392.91 287.9 53981 +1998 141 10.67 4.67 9.02 0 296.95 394.82 54111 +1998 142 15.13 9.13 13.48 0 387.01 385.47 54238 +1998 143 16.87 10.87 15.22 0 427.99 381.39 54362 +1998 144 17.86 11.86 16.21 0.08 452.91 284.26 54483 +1998 145 20.78 14.78 19.13 0.05 533.75 277.53 54600 +1998 146 18.44 12.44 16.79 0 468.08 378.1 54714 +1998 147 19.04 13.04 17.39 0 484.22 376.7 54824 +1998 148 19.84 13.84 18.19 0 506.48 374.47 54931 +1998 149 25.14 19.14 23.49 0.28 677.09 265.64 55034 +1998 150 23.29 17.29 21.64 0 612.72 362.39 55134 +1998 151 20.01 14.01 18.36 0 511.32 374.93 55229 +1998 152 24.32 18.32 22.67 0 647.88 358.57 55321 +1998 153 24.49 18.49 22.84 0.51 653.85 268.55 55409 +1998 154 17.56 11.56 15.91 1.06 445.23 287.48 55492 +1998 155 23.26 17.26 21.61 0.01 611.72 272.79 55572 +1998 156 24.57 18.57 22.92 0.13 656.67 268.89 55648 +1998 157 23.13 17.13 21.48 1.55 607.41 273.54 55719 +1998 158 22.15 16.15 20.5 0.21 575.7 276.56 55786 +1998 159 23.35 17.35 21.7 0.95 614.73 273.18 55849 +1998 160 25.21 19.21 23.56 0 679.63 356.42 55908 +1998 161 26.36 20.36 24.71 0.03 722.59 263.33 55962 +1998 162 25.12 19.12 23.47 0 676.36 356.94 56011 +1998 163 27.46 21.46 25.81 0 765.81 345.91 56056 +1998 164 25.31 19.31 23.66 0.04 683.28 267.25 56097 +1998 165 24.08 18.08 22.43 0 639.54 361.84 56133 +1998 166 26.2 20.2 24.55 0.7 716.48 264.26 56165 +1998 167 22.08 16.08 20.43 0 573.49 369.92 56192 +1998 168 18.57 12.57 16.92 0.09 471.54 286.6 56214 +1998 169 21.95 15.95 20.3 0 569.41 370.5 56231 +1998 170 23.6 17.6 21.95 0.03 623.13 272.97 56244 +1998 171 23.3 17.3 21.65 0.09 613.06 273.94 56252 +1998 172 19.32 13.32 17.67 0 491.92 379.8 56256 +1998 173 19.82 13.82 18.17 0 505.92 378.13 56255 +1998 174 23.33 17.33 21.68 0.23 614.06 273.77 56249 +1998 175 23.76 17.76 22.11 0.78 628.56 272.42 56238 +1998 176 22.88 16.88 21.23 0.06 599.18 275.08 56223 +1998 177 26.28 20.28 24.63 0.32 719.53 263.84 56203 +1998 178 23.76 17.76 22.11 0 628.56 363.11 56179 +1998 179 21.9 15.9 20.25 0.67 567.85 277.8 56150 +1998 180 19.62 13.62 17.97 0.25 500.28 283.76 56116 +1998 181 17.2 11.2 15.55 0.1 436.16 289.31 56078 +1998 182 19.5 13.5 17.85 0.11 496.92 283.89 56035 +1998 183 19.96 13.96 18.31 0.49 509.9 282.61 55987 +1998 184 19.43 13.43 17.78 0.13 494.97 283.81 55935 +1998 185 17.35 11.35 15.7 0.12 439.92 288.56 55879 +1998 186 17.02 11.02 15.37 0.43 431.69 289.07 55818 +1998 187 16.39 10.39 14.74 0.36 416.33 290.25 55753 +1998 188 22.93 16.93 21.28 0 600.82 364.97 55684 +1998 189 25.6 19.6 23.95 0 693.95 353.35 55611 +1998 190 27.87 21.87 26.22 2.55 782.47 256.4 55533 +1998 191 27.4 21.4 25.75 1.8 763.4 258.02 55451 +1998 192 28.86 22.86 27.21 0.6 823.96 252.03 55366 +1998 193 21.12 15.12 19.47 0.52 543.91 277.83 55276 +1998 194 23.65 17.65 22 0 624.82 360.47 55182 +1998 195 29.97 23.97 28.32 0.23 872.67 246.82 55085 +1998 196 30.41 24.41 28.76 0 892.64 326.14 54984 +1998 197 28.43 22.43 26.78 0.48 805.71 252.64 54879 +1998 198 25.71 19.71 24.06 1.12 698.04 262.48 54770 +1998 199 26.53 20.53 24.88 0 729.13 345.77 54658 +1998 200 27.48 21.48 25.83 0 766.62 340.7 54542 +1998 201 30.71 24.71 29.06 0 906.47 322.44 54423 +1998 202 26.19 20.19 24.54 0.06 716.1 259.52 54301 +1998 203 23.69 17.69 22.04 1.1 626.18 267.41 54176 +1998 204 26.26 20.26 24.61 0 718.77 344.73 54047 +1998 205 27.56 21.56 25.91 0 769.85 337.89 53915 +1998 206 25.19 19.19 23.54 0.24 678.9 261.45 53780 +1998 207 25.41 19.41 23.76 0.44 686.94 260.24 53643 +1998 208 21.76 15.76 20.11 0 563.48 361.19 53502 +1998 209 21.33 15.33 19.68 0.37 550.27 271.58 53359 +1998 210 23.02 17.02 21.37 0.56 603.78 266.37 53213 +1998 211 22.39 16.39 20.74 0.16 583.34 267.62 53064 +1998 212 20.68 14.68 19.03 0.26 530.79 271.65 52913 +1998 213 20.47 14.47 18.82 0.17 524.62 271.62 52760 +1998 214 24.42 18.42 22.77 0.69 651.39 259.85 52604 +1998 215 19.01 13.01 17.36 0.45 483.41 274.09 52445 +1998 216 21.94 15.94 20.29 0 569.1 354.56 52285 +1998 217 25.05 19.05 23.4 0 673.83 341.28 52122 +1998 218 24.19 18.19 22.54 0.11 643.35 258.1 51958 +1998 219 19.59 13.59 17.94 1.73 499.44 269.88 51791 +1998 220 21.32 15.32 19.67 0.39 549.96 264.85 51622 +1998 221 24.6 18.6 22.95 0 657.73 339.55 51451 +1998 222 26.04 20.04 24.39 1.13 710.41 249.2 51279 +1998 223 28.2 22.2 26.55 0.38 796.1 240.62 51105 +1998 224 26.25 20.25 24.6 0.81 718.38 246.92 50929 +1998 225 22.99 16.99 21.34 0.05 602.79 256.29 50751 +1998 226 26.53 20.53 24.88 0.46 729.13 244.33 50572 +1998 227 22.29 16.29 20.64 0.08 580.15 256.47 50392 +1998 228 21.84 15.84 20.19 0.02 565.97 256.78 50210 +1998 229 24.63 18.63 22.98 0 658.8 330.5 50026 +1998 230 24.92 18.92 23.27 0 669.14 328.08 49842 +1998 231 27.5 21.5 25.85 0 767.42 315.14 49656 +1998 232 29.38 23.38 27.73 0 846.48 304.45 49469 +1998 233 26.63 20.63 24.98 0 733 316.6 49280 +1998 234 31.27 25.27 29.62 0 932.78 291.46 49091 +1998 235 31.08 25.08 29.43 0.05 923.78 218.42 48900 +1998 236 32.74 26.74 31.09 0 1004.92 280.11 48709 +1998 237 28.85 22.85 27.2 0.25 823.53 225.32 48516 +1998 238 28.86 22.86 27.21 0 823.96 298.85 48323 +1998 239 27.1 21.1 25.45 0.34 751.43 229.42 48128 +1998 240 23.61 17.61 21.96 0.79 623.47 239.02 47933 +1998 241 18.51 12.51 16.86 0.56 469.94 250.22 47737 +1998 242 15.99 9.99 14.34 0.12 406.83 253.82 47541 +1998 243 19.67 13.67 18.02 0 501.68 326.68 47343 +1998 244 12.11 6.11 10.46 0 323.82 342.97 47145 +1998 245 16.03 10.03 14.38 0 407.77 332.72 46947 +1998 246 18.41 12.41 16.76 0 467.28 324.66 46747 +1998 247 16.09 10.09 14.44 0.75 409.18 246.53 46547 +1998 248 19.34 13.34 17.69 0.15 492.47 238.72 46347 +1998 249 16.98 10.98 15.33 0.02 430.7 241.88 46146 +1998 250 19.36 13.36 17.71 0.26 493.03 235.69 45945 +1998 251 18.65 12.65 17 0.02 473.68 235.6 45743 +1998 252 24 18 22.35 1.27 636.78 221.37 45541 +1998 253 16.16 10.16 14.51 0.01 410.84 237.06 45339 +1998 254 18.97 12.97 17.32 0 482.32 306.9 45136 +1998 255 19.28 13.28 17.63 0 490.81 303.82 44933 +1998 256 20.83 14.83 19.18 0.02 535.23 222.87 44730 +1998 257 19.04 13.04 17.39 0.77 484.22 225.08 44527 +1998 258 18.32 12.32 16.67 0 464.91 299.67 44323 +1998 259 17.81 11.81 16.16 0 451.62 298.54 44119 +1998 260 20.3 14.3 18.65 0.31 519.67 217.21 43915 +1998 261 24.4 18.4 22.75 0.2 650.69 205.7 43711 +1998 262 25.31 19.31 23.66 0.2 683.28 201.56 43507 +1998 263 24.09 18.09 22.44 0 639.89 270.78 43303 +1998 264 22.47 16.47 20.82 0 585.9 273.63 43099 +1998 265 20.44 14.44 18.79 0 523.74 277.31 42894 +1998 266 20.53 14.53 18.88 0 526.38 274.66 42690 +1998 267 20.66 14.66 19.01 0 530.2 271.71 42486 +1998 268 23.53 17.53 21.88 0 620.77 260.68 42282 +1998 269 20.83 14.83 19.18 0 535.23 266.33 42078 +1998 270 19.34 13.34 17.69 0.25 492.47 200.76 41875 +1998 271 18.17 12.17 16.52 2.75 460.97 200.96 41671 +1998 272 14.46 8.46 12.81 4.12 372.15 204.73 41468 +1998 273 17.49 11.49 15.84 1.23 443.46 198.24 41265 +1998 274 12.47 6.47 10.82 2.52 330.86 203.4 41062 +1998 275 13.8 7.8 12.15 0 357.99 266.18 40860 +1998 276 15.73 9.73 14.08 0 400.75 259.93 40658 +1998 277 12.77 6.77 11.12 0.14 336.82 196.9 40456 +1998 278 13.9 7.9 12.25 0 360.11 257.77 40255 +1998 279 10.95 4.95 9.3 0.51 302.02 194.67 40054 +1998 280 12.92 6.92 11.27 0.23 339.83 190.44 39854 +1998 281 15.23 9.23 13.58 0.03 389.27 185.46 39654 +1998 282 10.7 4.7 9.05 0.58 297.48 188.78 39455 +1998 283 14.79 8.79 13.14 0.18 379.41 181.91 39256 +1998 284 15.11 9.11 13.46 1.35 386.56 179.25 39058 +1998 285 16.71 10.71 15.06 1.04 424.07 175.09 38861 +1998 286 17.91 11.91 16.26 0.06 454.2 171.29 38664 +1998 287 18.81 12.81 17.16 0 477.98 223.67 38468 +1998 288 15.95 9.95 14.3 1.03 405.89 169.91 38273 +1998 289 13.99 7.99 12.34 0 362.02 227.23 38079 +1998 290 16.46 10.46 14.81 0 418.01 220.24 37885 +1998 291 17.14 11.14 15.49 0 434.67 216.35 37693 +1998 292 15.95 9.95 14.3 0 405.89 215.87 37501 +1998 293 14.45 8.45 12.8 0.75 371.94 161.73 37311 +1998 294 16.66 10.66 15.01 1.42 422.85 156.85 37121 +1998 295 16.84 10.84 15.19 0.4 427.25 154.54 36933 +1998 296 16.96 10.96 15.31 0.21 430.2 152.5 36745 +1998 297 16.56 10.56 14.91 0.02 420.43 151.03 36560 +1998 298 14.37 8.37 12.72 0 370.19 202.32 36375 +1998 299 14.43 8.43 12.78 0.04 371.5 149.62 36191 +1998 300 19 13 17.35 0.17 483.13 141.89 36009 +1998 301 18.12 12.12 16.47 0 459.66 188.41 35829 +1998 302 18.01 12.01 16.36 0.27 456.79 139.57 35650 +1998 303 16.84 10.84 15.19 0.22 427.25 139.21 35472 +1998 304 17.99 11.99 16.34 0 456.27 181.3 35296 +1998 305 7.45 1.45 5.8 0 243.67 192.17 35122 +1998 306 7.72 1.72 6.07 0.02 247.8 142.24 34950 +1998 307 10.42 4.42 8.77 0 292.48 184.45 34779 +1998 308 13.21 7.21 11.56 0 345.73 178.61 34610 +1998 309 7.24 1.24 5.59 0 240.5 182.6 34444 +1998 310 6.28 0.28 4.63 0 226.47 180.95 34279 +1998 311 6.93 0.93 5.28 0.94 235.89 133.67 34116 +1998 312 7.84 1.84 6.19 0 249.65 174.79 33956 +1998 313 9.48 3.48 7.83 0.04 276.2 128.38 33797 +1998 314 10.62 4.62 8.97 0 296.05 168.1 33641 +1998 315 11.33 5.33 9.68 0 309.02 164.86 33488 +1998 316 7.37 1.37 5.72 0.08 242.46 124.79 33337 +1998 317 5.79 -0.21 4.14 1.24 219.58 124.06 33188 +1998 318 6.26 0.26 4.61 0.15 226.18 122.04 33042 +1998 319 4.68 -1.32 3.03 0.03 204.63 121.6 32899 +1998 320 7.31 1.31 5.66 0.01 241.56 118.76 32758 +1998 321 5.1 -0.9 3.45 0 210.18 157.85 32620 +1998 322 7.83 1.83 6.18 0 249.5 154.01 32486 +1998 323 5.64 -0.36 3.99 0 217.5 154.02 32354 +1998 324 6.22 0.22 4.57 0 225.61 151.56 32225 +1998 325 5.87 -0.13 4.22 0.03 220.69 112.56 32100 +1998 326 5.98 -0.02 4.33 0.9 222.23 111.41 31977 +1998 327 5.45 -0.55 3.8 0 214.9 147.06 31858 +1998 328 3.95 -2.05 2.3 0.03 195.29 109.52 31743 +1998 329 9.06 3.06 7.41 0.07 269.18 105.7 31631 +1998 330 8.01 2.01 6.36 0.17 252.3 105.25 31522 +1998 331 7.52 1.52 5.87 0.4 244.74 104.54 31417 +1998 332 6.77 0.77 5.12 1.9 233.54 103.72 31316 +1998 333 8.53 2.53 6.88 0 260.54 135.92 31218 +1998 334 10.25 4.25 8.6 0.1 289.48 100.08 31125 +1998 335 1.93 -4.07 0.28 0 171.33 137.8 31035 +1998 336 2.75 -3.25 1.1 0 180.73 136.3 30949 +1998 337 0.2 -5.8 -1.45 0.1 152.86 101.89 30867 +1998 338 3.25 -2.75 1.6 0 186.68 133.42 30790 +1998 339 1.29 -4.71 -0.36 0 164.28 133.61 30716 +1998 340 -2.86 -8.86 -4.51 0 124.39 134.56 30647 +1998 341 -1.73 -7.73 -3.38 0 134.32 133.21 30582 +1998 342 -1.97 -7.97 -3.62 0 132.16 132.53 30521 +1998 343 1.41 -4.59 -0.24 0 165.58 130.29 30465 +1998 344 2.77 -3.23 1.12 0 180.96 128.49 30413 +1998 345 4.64 -1.36 2.99 0 204.11 127.05 30366 +1998 346 4.97 -1.03 3.32 0 208.45 126.31 30323 +1998 347 8.06 2.06 6.41 0 253.08 123.73 30284 +1998 348 7.28 1.28 5.63 0.01 241.11 92.94 30251 +1998 349 8.11 2.11 6.46 1.11 253.87 92.23 30221 +1998 350 6.98 0.98 5.33 0.15 236.63 92.56 30197 +1998 351 6.26 0.26 4.61 0 226.18 123.66 30177 +1998 352 2.58 -3.42 0.93 0.45 178.74 94.22 30162 +1998 353 1.29 -4.71 -0.36 0 164.28 126.17 30151 +1998 354 0.64 -5.36 -1.01 0 157.39 126.42 30145 +1998 355 -0.07 -6.07 -1.72 0 150.14 126.72 30144 +1998 356 2.87 -3.13 1.22 0.02 182.14 94.05 30147 +1998 357 -1.41 -7.41 -3.06 0.11 137.25 139.62 30156 +1998 358 -1.15 -7.15 -2.8 0.16 139.68 140.11 30169 +1998 359 -4.02 -10.02 -5.67 0 114.87 173.03 30186 +1998 360 -7.97 -13.97 -9.62 0 87.02 174.45 30208 +1998 361 -7.13 -13.13 -8.78 0 92.39 174.55 30235 +1998 362 -2.53 -8.53 -4.18 0 127.22 173.57 30267 +1998 363 5.1 -0.9 3.45 0 210.18 169.91 30303 +1998 364 3.79 -2.21 2.14 0 193.29 127.31 30343 +1998 365 4.93 -1.07 3.28 0 207.92 127.24 30388 +1999 1 5.59 -0.41 3.94 0 216.82 127.73 30438 +1999 2 2.4 -3.6 0.75 0.36 176.66 97.67 30492 +1999 3 4.78 -1.22 3.13 0 205.94 129.88 30551 +1999 4 6.23 0.23 4.58 0 225.75 129.9 30614 +1999 5 10.13 4.13 8.48 0 287.37 127.67 30681 +1999 6 10.21 4.21 8.56 0 288.77 128.47 30752 +1999 7 7.23 1.23 5.58 0.14 240.35 98.65 30828 +1999 8 5.22 -0.78 3.57 0.12 211.79 100.75 30907 +1999 9 5.14 -0.86 3.49 0.25 210.72 101.72 30991 +1999 10 5.36 -0.64 3.71 0 213.68 136.79 31079 +1999 11 3.32 -2.68 1.67 0.01 187.52 104.24 31171 +1999 12 0.43 -5.57 -1.22 0.17 155.21 106.09 31266 +1999 13 -0.07 -6.07 -1.72 0 150.14 143.32 31366 +1999 14 -2.61 -8.61 -4.26 0 126.53 145.86 31469 +1999 15 -0.49 -6.49 -2.14 0 145.99 146.45 31575 +1999 16 -0.28 -6.28 -1.93 0 148.06 147.66 31686 +1999 17 0.29 -5.71 -1.36 0 153.78 149.09 31800 +1999 18 3.05 -2.95 1.4 0 184.28 149.57 31917 +1999 19 5.33 -0.67 3.68 0 213.27 150.09 32038 +1999 20 4.34 -1.66 2.69 0 200.23 152.31 32161 +1999 21 2.58 -3.42 0.93 0.13 178.74 116.53 32289 +1999 22 6.09 0.09 4.44 0 223.77 154.88 32419 +1999 23 4.6 -1.4 2.95 0.31 203.59 118.25 32552 +1999 24 3.78 -2.22 2.13 0.09 193.17 120.19 32688 +1999 25 5.54 -0.46 3.89 0.01 216.13 120.72 32827 +1999 26 4.85 -1.15 3.2 0.22 206.86 122.52 32969 +1999 27 2.39 -3.61 0.74 0.23 176.55 125.21 33114 +1999 28 -2.55 -8.55 -4.2 0.1 127.05 168.72 33261 +1999 29 -3.28 -9.28 -4.93 0 120.87 214.16 33411 +1999 30 -4.19 -10.19 -5.84 0.14 113.53 172.77 33564 +1999 31 -5.94 -11.94 -7.59 0.06 100.49 175.04 33718 +1999 32 -4.6 -10.6 -6.25 0.12 110.35 176.45 33875 +1999 33 -4.64 -10.64 -6.29 0.05 110.04 178.42 34035 +1999 34 -4.55 -10.55 -6.2 0 110.73 226.55 34196 +1999 35 -6.97 -12.97 -8.62 0.66 93.45 183.84 34360 +1999 36 -4.28 -10.28 -5.93 0 112.82 232.64 34526 +1999 37 1.56 -4.44 -0.09 0 167.22 231.8 34694 +1999 38 5.16 -0.84 3.51 0 210.98 231.27 34863 +1999 39 5.07 -0.93 3.42 0 209.78 233.17 35035 +1999 40 6.35 0.35 4.7 0 227.47 233.81 35208 +1999 41 6.79 0.79 5.14 0.1 233.83 185.68 35383 +1999 42 4.26 -1.74 2.61 0.1 199.21 151.62 35560 +1999 43 4.67 -1.33 3.02 0.04 204.5 153.41 35738 +1999 44 0.59 -5.41 -1.06 1.05 156.87 157.48 35918 +1999 45 -0.71 -6.71 -2.36 0 143.86 213.38 36099 +1999 46 4.62 -1.38 2.97 0 203.85 212.47 36282 +1999 47 2.46 -3.54 0.81 0 177.35 216.94 36466 +1999 48 0.61 -5.39 -1.04 0 157.08 221.01 36652 +1999 49 3.1 -2.9 1.45 0 184.88 222.09 36838 +1999 50 3.43 -2.57 1.78 0 188.86 224.52 37026 +1999 51 5.9 -0.1 4.25 0 221.11 225.41 37215 +1999 52 5.74 -0.26 4.09 0.98 218.88 171.28 37405 +1999 53 6.8 0.8 5.15 0 233.98 230.32 37596 +1999 54 5.75 -0.25 4.1 0 219.02 234.08 37788 +1999 55 10.37 4.37 8.72 0 291.59 232.01 37981 +1999 56 8.05 2.05 6.4 0.22 252.93 178.06 38175 +1999 57 13.9 7.9 12.25 0.39 360.11 174.32 38370 +1999 58 7.13 1.13 5.48 0 238.86 244.19 38565 +1999 59 11.01 5.01 9.36 0 303.11 242.2 38761 +1999 60 14.14 8.14 12.49 0 365.23 240.3 38958 +1999 61 11.15 5.15 9.5 0 305.68 247.73 39156 +1999 62 11.32 5.32 9.67 0 308.83 250.23 39355 +1999 63 13.53 7.53 11.88 0.07 352.34 187.35 39553 +1999 64 15.54 9.54 13.89 0 396.35 249.1 39753 +1999 65 13.02 7.02 11.37 0 341.86 256.28 39953 +1999 66 10.82 4.82 9.17 0 299.65 262.31 40154 +1999 67 13.96 7.96 12.31 0 361.38 260.2 40355 +1999 68 12.04 6.04 10.39 0.53 322.47 199.63 40556 +1999 69 13.41 7.41 11.76 0.83 349.85 199.88 40758 +1999 70 10.96 4.96 9.31 0 302.2 273.2 40960 +1999 71 10.95 4.95 9.3 0 302.02 276.09 41163 +1999 72 8.82 2.82 7.17 0 265.24 281.88 41366 +1999 73 8.05 2.05 6.4 0 252.93 285.54 41569 +1999 74 11.13 5.13 9.48 0 305.31 283.96 41772 +1999 75 7.3 1.3 5.65 0 241.41 291.94 41976 +1999 76 9.79 3.79 8.14 0 281.48 291.27 42179 +1999 77 12.78 6.78 11.13 0 337.02 289.1 42383 +1999 78 17.73 11.73 16.08 0 449.57 281.62 42587 +1999 79 18.16 12.16 16.51 0 460.7 283.21 42791 +1999 80 16.43 10.43 14.78 0 417.29 289.64 42996 +1999 81 12.32 6.32 10.67 0.09 327.91 225.18 43200 +1999 82 5.67 -0.33 4.02 0 217.92 312.39 43404 +1999 83 7.55 1.55 5.9 0 245.19 312.59 43608 +1999 84 4.64 -1.36 2.99 0 204.11 318.63 43812 +1999 85 7.47 1.47 5.82 0 243.98 317.75 44016 +1999 86 12.53 6.53 10.88 0.01 332.04 234.21 44220 +1999 87 7.34 1.34 5.69 1.1 242.01 242.17 44424 +1999 88 2.63 -3.37 0.98 0.03 179.33 248 44627 +1999 89 3.57 -2.43 1.92 0 190.57 332.04 44831 +1999 90 7.33 1.33 5.68 0 241.86 329.96 45034 +1999 91 13.61 7.61 11.96 0 354.01 321.85 45237 +1999 92 13.39 7.39 11.74 0 349.43 324.5 45439 +1999 93 14.77 8.77 13.12 0.18 378.97 242.87 45642 +1999 94 14.37 8.37 12.72 0 370.19 326.8 45843 +1999 95 10.37 4.37 8.72 0 291.59 336.46 46045 +1999 96 8.95 2.95 7.3 0 267.37 340.86 46246 +1999 97 15.61 9.61 13.96 0 397.97 330.24 46446 +1999 98 12.79 6.79 11.14 0 337.22 338.19 46647 +1999 99 14.68 8.68 13.03 0 376.98 336.25 46846 +1999 100 14.76 8.76 13.11 0 378.75 337.99 47045 +1999 101 13.98 7.98 12.33 1.14 361.81 256.2 47243 +1999 102 12.8 6.8 11.15 0.15 337.42 259.44 47441 +1999 103 11.16 5.16 9.51 0 305.87 350.88 47638 +1999 104 13.2 7.2 11.55 0 345.53 348.76 47834 +1999 105 15.96 9.96 14.31 0 406.12 344.33 48030 +1999 106 14.23 8.23 12.58 0.31 367.17 262.48 48225 +1999 107 14.62 8.62 12.97 0.97 375.66 263.07 48419 +1999 108 16.61 10.61 14.96 0.67 421.64 260.75 48612 +1999 109 17.84 11.84 16.19 0.17 452.4 259.47 48804 +1999 110 16.24 10.24 14.59 0.04 412.74 263.68 48995 +1999 111 14.16 8.16 12.51 0 365.66 358.05 49185 +1999 112 15.46 9.46 13.81 0.29 394.52 267.4 49374 +1999 113 13.09 7.09 11.44 0 343.28 363.23 49561 +1999 114 13.18 7.18 11.53 0 345.12 364.53 49748 +1999 115 17.34 11.34 15.69 0.03 439.67 266.91 49933 +1999 116 18.93 12.93 17.28 0.2 481.23 264.37 50117 +1999 117 19.18 13.18 17.53 0 488.06 353.01 50300 +1999 118 22.02 16.02 20.37 0.26 571.61 258.63 50481 +1999 119 18.2 12.2 16.55 0 461.75 358.38 50661 +1999 120 20.92 14.92 19.27 0 537.91 350.95 50840 +1999 121 21.75 15.75 20.1 0.13 563.17 261.85 51016 +1999 122 20.38 14.38 18.73 0.68 522 266.25 51191 +1999 123 18.21 12.21 16.56 0.02 462.01 272.08 51365 +1999 124 17.4 11.4 15.75 0.11 441.18 274.62 51536 +1999 125 18.44 12.44 16.79 0.52 468.08 273.09 51706 +1999 126 20.96 14.96 19.31 0.23 539.11 267.74 51874 +1999 127 21.75 15.75 20.1 0.01 563.17 266.28 52039 +1999 128 21.83 15.83 20.18 0.41 565.66 266.79 52203 +1999 129 20.62 14.62 18.97 0.97 529.02 270.6 52365 +1999 130 22.62 16.62 20.97 0 590.73 354.34 52524 +1999 131 23.63 17.63 21.98 0 624.15 351.12 52681 +1999 132 22.22 16.22 20.57 0 577.92 357.4 52836 +1999 133 21.87 15.87 20.22 0.68 566.91 269.53 52989 +1999 134 19.89 13.89 18.24 0.1 507.9 275.23 53138 +1999 135 20.8 14.8 19.15 0.33 534.34 273.43 53286 +1999 136 17.77 11.77 16.12 2.43 450.6 281.15 53430 +1999 137 15.18 9.18 13.53 0.49 388.14 286.96 53572 +1999 138 14.84 8.84 13.19 0 380.52 384.07 53711 +1999 139 17.53 11.53 15.88 0.15 444.47 283.17 53848 +1999 140 14.91 8.91 13.26 0.14 382.08 288.81 53981 +1999 141 16.84 10.84 15.19 0.56 427.25 285.32 54111 +1999 142 16.48 10.48 14.83 0 418.5 381.93 54238 +1999 143 19.24 13.24 17.59 0 489.71 374.28 54362 +1999 144 16.5 10.5 14.85 0.09 418.98 287.17 54483 +1999 145 17.29 11.29 15.64 0.02 438.42 285.86 54600 +1999 146 16.89 10.89 15.24 0.4 428.48 286.99 54714 +1999 147 15.18 9.18 13.53 0.02 388.14 290.78 54824 +1999 148 15.19 9.19 13.54 0.02 388.37 291.05 54931 +1999 149 14.25 8.25 12.6 0.05 367.6 293.03 55034 +1999 150 18.57 12.57 16.92 0.73 471.54 284.4 55134 +1999 151 20.02 14.02 18.37 1.49 511.61 281.17 55229 +1999 152 23.33 17.33 21.68 1.1 614.06 272.03 55321 +1999 153 20.33 14.33 18.68 3.23 520.54 280.64 55409 +1999 154 21.72 15.72 20.07 0.08 562.24 277.14 55492 +1999 155 19.22 13.22 17.57 0.03 489.16 283.79 55572 +1999 156 23.94 17.94 22.29 0 634.72 361.22 55648 +1999 157 23.25 17.25 21.6 0.55 611.39 273.18 55719 +1999 158 22.59 16.59 20.94 0 589.76 367.04 55786 +1999 159 25.08 19.08 23.43 0 674.91 356.83 55849 +1999 160 27.69 21.69 26.04 0 775.12 344.41 55908 +1999 161 24.07 18.07 22.42 0 639.2 361.48 55962 +1999 162 23.32 17.32 21.67 1.04 613.72 273.49 56011 +1999 163 21.74 15.74 20.09 0.01 562.86 278.28 56056 +1999 164 19.69 13.69 18.04 0 502.24 378.32 56097 +1999 165 17.59 11.59 15.94 0.65 446 288.75 56133 +1999 166 19.93 13.93 18.28 0 509.04 377.69 56165 +1999 167 18.46 12.46 16.81 0 468.61 382.39 56192 +1999 168 19.74 13.74 18.09 0.01 503.65 283.76 56214 +1999 169 18.53 12.53 16.88 0.04 470.47 286.7 56231 +1999 170 17.53 11.53 15.88 0 444.47 385.29 56244 +1999 171 17.37 11.37 15.72 0.02 440.43 289.36 56252 +1999 172 19 13 17.35 0 483.13 380.83 56256 +1999 173 16.45 10.45 14.8 0 417.77 388.4 56255 +1999 174 17.31 11.31 15.66 0 438.92 385.88 56249 +1999 175 24.22 18.22 22.57 0 644.4 361.27 56238 +1999 176 27.79 21.79 26.14 0.17 779.19 258.25 56223 +1999 177 22.9 16.9 21.25 0 599.84 366.6 56203 +1999 178 22.92 16.92 21.27 0.07 600.49 274.91 56179 +1999 179 24.13 18.13 22.48 0.19 641.27 271.09 56150 +1999 180 23.14 17.14 21.49 0.85 607.74 274.08 56116 +1999 181 25.37 19.37 23.72 0 685.47 355.79 56078 +1999 182 28.95 22.95 27.3 0 827.82 337.63 56035 +1999 183 30.6 24.6 28.95 0.05 901.38 245.95 55987 +1999 184 28.99 22.99 27.34 0.28 829.54 252.83 55935 +1999 185 25.13 19.13 23.48 0 676.72 356.34 55879 +1999 186 27.79 21.79 26.14 0 779.19 343.22 55818 +1999 187 28.33 22.33 26.68 1.29 801.52 255.16 55753 +1999 188 26.95 20.95 25.3 0.24 745.51 260.3 55684 +1999 189 25.13 19.13 23.48 0 676.72 355.48 55611 +1999 190 22.25 16.25 20.6 0.05 578.87 275.31 55533 +1999 191 22.07 16.07 20.42 0 573.18 367.5 55451 +1999 192 24.1 18.1 22.45 0.09 640.23 269.3 55366 +1999 193 23.3 17.3 21.65 0.42 613.06 271.59 55276 +1999 194 23.37 17.37 21.72 1.15 615.39 271.21 55182 +1999 195 23.75 17.75 22.1 0 628.22 359.79 55085 +1999 196 22.23 16.23 20.58 1.71 578.24 274.08 54984 +1999 197 20.63 14.63 18.98 0 529.31 370.81 54879 +1999 198 18.04 12.04 16.39 0 457.57 378.76 54770 +1999 199 26.32 20.32 24.67 0 721.06 346.78 54658 +1999 200 23.82 17.82 22.17 0.17 630.61 268.13 54542 +1999 201 27.27 21.27 25.62 0 758.19 341.32 54423 +1999 202 27.43 21.43 25.78 1.76 764.6 254.98 54301 +1999 203 26.92 20.92 25.27 0.27 744.33 256.53 54176 +1999 204 25.66 19.66 24.01 0 696.18 347.52 54047 +1999 205 22.97 16.97 21.32 0 602.13 358.44 53915 +1999 206 19.87 13.87 18.22 0.24 507.33 276.81 53780 +1999 207 22.33 16.33 20.68 0.06 581.42 269.79 53643 +1999 208 20.86 14.86 19.21 3.54 536.12 273.31 53502 +1999 209 20.88 14.88 19.23 0 536.72 363.69 53359 +1999 210 19.08 13.08 17.43 0.41 485.32 276.77 53213 +1999 211 16.88 10.88 15.23 1.13 428.23 281.04 53064 +1999 212 22.61 16.61 20.96 0 590.41 355.2 52913 +1999 213 22.07 16.07 20.42 0.43 573.18 267.37 52760 +1999 214 22.46 16.46 20.81 0 585.58 354.29 52604 +1999 215 25.34 19.34 23.69 0.12 684.38 256.39 52445 +1999 216 25.71 19.71 24.06 0.32 698.04 254.42 52285 +1999 217 23.66 17.66 22.01 0 625.16 347.09 52122 +1999 218 24.26 18.26 22.61 0 645.79 343.85 51958 +1999 219 22.11 16.11 20.46 1.75 574.44 263.42 51791 +1999 220 21.58 15.58 19.93 0.01 557.92 264.16 51622 +1999 221 22.22 16.22 20.57 0.06 577.92 261.68 51451 +1999 222 20.01 14.01 18.36 0.08 511.32 266.63 51279 +1999 223 22.27 16.27 20.62 0 579.51 346.57 51105 +1999 224 19.55 13.55 17.9 0 498.32 354.77 50929 +1999 225 19.21 13.21 17.56 0 488.88 354.68 50751 +1999 226 19.78 13.78 18.13 0 504.78 351.75 50572 +1999 227 21.35 15.35 19.7 0.16 550.88 258.97 50392 +1999 228 22.86 16.86 21.21 0 598.53 338.66 50210 +1999 229 22.75 16.75 21.1 0.08 594.94 253.39 50026 +1999 230 21.53 15.53 19.88 2.33 556.38 255.74 49842 +1999 231 24.85 18.85 23.2 0.63 666.63 245.22 49656 +1999 232 24.83 18.83 23.18 0.01 665.92 244.31 49469 +1999 233 21.89 15.89 20.24 0 567.53 335.56 49280 +1999 234 18.46 12.46 16.81 0.36 468.61 258.77 49091 +1999 235 21.91 15.91 20.26 0 568.16 332.63 48900 +1999 236 28.29 22.29 26.64 0 799.85 304.73 48709 +1999 237 23.84 17.84 22.19 0 631.29 322.58 48516 +1999 238 24.86 18.86 23.21 0 666.99 316.95 48323 +1999 239 26.2 20.2 24.55 0.61 716.48 232.42 48128 +1999 240 26.31 20.31 24.66 0.47 720.68 230.82 47933 +1999 241 26.53 20.53 24.88 1 729.13 228.89 47737 +1999 242 21 15 19.35 0 540.3 324.4 47541 +1999 243 21.85 15.85 20.2 0.26 566.28 239.84 47343 +1999 244 17.81 11.81 16.16 0 451.62 330.09 47145 +1999 245 19.58 13.58 17.93 0 499.16 323.31 46947 +1999 246 19.27 13.27 17.62 0 490.54 322.26 46747 +1999 247 19.39 13.39 17.74 0 493.86 320.07 46547 +1999 248 20.94 14.94 19.29 0 538.51 313.51 46347 +1999 249 19.52 13.52 17.87 0.15 497.48 236.8 46146 +1999 250 23.62 17.62 21.97 1.2 623.81 225.47 45945 +1999 251 27.05 21.05 25.4 1.71 749.45 213.82 45743 +1999 252 25.95 19.95 24.3 0.31 707.02 215.76 45541 +1999 253 21.43 15.43 19.78 0.09 553.32 226.36 45339 +1999 254 21.82 15.82 20.17 0.97 565.35 223.88 45136 +1999 255 19.89 13.89 18.24 1.07 507.9 226.59 44933 +1999 256 18.96 12.96 17.31 0.13 482.04 226.84 44730 +1999 257 17.51 11.51 15.86 0 443.96 304.03 44527 +1999 258 16.68 10.68 15.03 0.2 423.34 227.75 44323 +1999 259 12.54 6.54 10.89 0 332.24 309.71 44119 +1999 260 13.67 7.67 12.02 0 355.26 305.18 43915 +1999 261 17.87 11.87 16.22 0.07 453.17 220.2 43711 +1999 262 20.92 14.92 19.27 0.62 537.91 212.36 43507 +1999 263 22.7 16.7 21.05 0 593.32 275.37 43303 +1999 264 21.35 15.35 19.7 0.06 550.88 207.76 43099 +1999 265 25.84 19.84 24.19 0 702.89 259.9 42894 +1999 266 25.42 19.42 23.77 0 687.31 259.15 42690 +1999 267 26.57 20.57 24.92 0.06 730.68 189.29 42486 +1999 268 29.54 23.54 27.89 0 853.52 237.8 42282 +1999 269 25.18 19.18 23.53 0.01 678.54 189.59 42078 +1999 270 23.52 17.52 21.87 0.18 620.43 191.89 41875 +1999 271 25.89 19.89 24.24 0 704.76 245.41 41671 +1999 272 23.96 17.96 22.31 0 635.41 249.42 41468 +1999 273 20.92 14.92 19.27 0 537.91 255.95 41265 +1999 274 10.71 4.71 9.06 0.01 297.67 205.43 41062 +1999 275 14.19 8.19 12.54 0 366.3 265.49 40860 +1999 276 10.74 4.74 9.09 0 298.21 268.31 40658 +1999 277 9.31 3.31 7.66 0 273.34 267.57 40456 +1999 278 10.06 4.06 8.41 0.03 286.15 197.74 40255 +1999 279 11.79 5.79 10.14 0.01 317.68 193.75 40054 +1999 280 13.51 7.51 11.86 0 351.92 252.96 39854 +1999 281 10.42 4.42 8.77 0.05 292.48 191.14 39654 +1999 282 11.52 5.52 9.87 0 312.57 250.55 39455 +1999 283 14.49 8.49 12.84 0 372.81 243.06 39256 +1999 284 12.82 6.82 11.17 0.02 337.82 182.07 39058 +1999 285 13.04 7.04 11.39 0 342.26 239.78 38861 +1999 286 12.51 6.51 10.86 0 331.65 237.82 38664 +1999 287 14.49 8.49 12.84 0 372.81 231.8 38468 +1999 288 15.55 9.55 13.9 0.42 396.58 170.44 38273 +1999 289 18.16 12.16 16.51 0 460.7 219.78 38079 +1999 290 20.58 14.58 18.93 0 527.84 211.82 37885 +1999 291 21.17 15.17 19.52 0.62 545.42 155.92 37693 +1999 292 22.23 16.23 20.58 0 578.24 202.8 37501 +1999 293 20 14 18.35 0.26 511.04 154.04 37311 +1999 294 15.86 9.86 14.21 1.88 403.78 157.89 37121 +1999 295 15.51 9.51 13.86 0.32 395.66 156.24 36933 +1999 296 12.28 6.28 10.63 0 327.13 210.55 36745 +1999 297 15.99 9.99 14.34 0 406.83 202.33 36560 +1999 298 17.54 11.54 15.89 0 444.72 197.13 36375 +1999 299 15.63 9.63 13.98 0.31 398.43 148.24 36191 +1999 300 11.95 5.95 10.3 0.13 320.74 150.19 36009 +1999 301 12.27 6.27 10.62 0.07 326.93 148.01 35829 +1999 302 14.59 8.59 12.94 0.29 375 143.7 35650 +1999 303 14.24 8.24 12.59 0 367.38 189.58 35472 +1999 304 16.05 10.05 14.4 0.08 408.24 138.37 35296 +1999 305 5.33 -0.67 3.68 0.44 213.27 145.48 35122 +1999 306 4.7 -1.3 3.05 0.56 204.89 144.13 34950 +1999 307 3.5 -2.5 1.85 0 189.71 190.49 34779 +1999 308 4.18 -1.82 2.53 0 198.19 187.36 34610 +1999 309 4.71 -1.29 3.06 0 205.02 184.63 34444 +1999 310 2.87 -3.13 1.22 0 182.14 183.42 34279 +1999 311 3.26 -2.74 1.61 0 186.8 180.95 34116 +1999 312 8.09 2.09 6.44 1.44 253.55 130.93 33956 +1999 313 10.1 4.1 8.45 0.53 286.85 127.92 33797 +1999 314 9.9 3.9 8.25 0.05 283.37 126.62 33641 +1999 315 6.53 0.53 4.88 0 230.05 169.25 33488 +1999 316 5.97 -0.03 4.32 0 222.09 167.49 33337 +1999 317 9.71 3.71 8.06 0 280.11 162.14 33188 +1999 318 4.86 -1.14 3.21 0.18 206.99 122.8 33042 +1999 319 9.49 3.49 7.84 0.02 276.37 118.76 32899 +1999 320 10.59 4.59 8.94 0 295.51 155.46 32758 +1999 321 8.39 2.39 6.74 1.25 258.3 116.52 32620 +1999 322 9.53 3.53 7.88 0.16 277.05 114.42 32486 +1999 323 6.06 0.06 4.41 0 223.35 153.73 32354 +1999 324 5.3 -0.7 3.65 0 212.87 152.2 32225 +1999 325 5.77 -0.23 4.12 0.04 219.3 112.61 32100 +1999 326 4.81 -1.19 3.16 0.06 206.34 112 31977 +1999 327 10.3 4.3 8.65 1.08 290.36 107.46 31858 +1999 328 6.82 0.82 5.17 0.42 234.27 108.11 31743 +1999 329 5.14 -0.86 3.49 0.02 210.72 107.84 31631 +1999 330 4.35 -1.65 2.7 0 200.36 142.83 31522 +1999 331 9.35 3.35 7.7 0 274.01 137.96 31417 +1999 332 11.09 5.09 9.44 0.14 304.58 101.12 31316 +1999 333 7.84 1.84 6.19 0.26 249.65 102.33 31218 +1999 334 6.71 0.71 5.06 0.22 232.66 102.12 31125 +1999 335 3.18 -2.82 1.53 0.56 185.83 102.86 31035 +1999 336 5.55 -0.45 3.9 0.19 216.27 101.01 30949 +1999 337 7.45 1.45 5.8 0.16 243.67 98.82 30867 +1999 338 2.91 -3.09 1.26 0 182.61 133.6 30790 +1999 339 7.27 1.27 5.62 0 240.96 130.17 30716 +1999 340 5.75 -0.25 4.1 0 219.02 130.44 30647 +1999 341 4.89 -1.11 3.24 0.13 207.39 97.54 30582 +1999 342 -0.03 -6.03 -1.68 0.48 150.54 143.58 30521 +1999 343 -1.42 -7.42 -3.07 0.31 137.16 144.43 30465 +1999 344 1.91 -4.09 0.26 0 171.1 174.56 30413 +1999 345 6.33 0.33 4.68 0.09 227.18 139.4 30366 +1999 346 3.35 -2.65 1.7 0 187.89 171.7 30323 +1999 347 6.68 0.68 5.03 0 232.23 168.32 30284 +1999 348 -0.24 -6.24 -1.89 0.21 148.45 140.32 30251 +1999 349 -2.22 -8.22 -3.87 1.8 129.93 146.36 30221 +1999 350 -1.34 -7.34 -2.99 0.7 137.9 148.13 30197 +1999 351 -3.02 -9.02 -4.67 0.8 123.04 150.99 30177 +1999 352 -1.28 -7.28 -2.93 0 138.46 182.31 30162 +1999 353 -0.99 -6.99 -2.64 0 141.19 182.15 30151 +1999 354 3.09 -2.91 1.44 0 184.76 179.89 30145 +1999 355 6.44 0.44 4.79 0 228.76 177.12 30144 +1999 356 5.24 -0.76 3.59 0.11 212.06 146.14 30147 +1999 357 5.19 -0.81 3.54 0 211.39 176.55 30156 +1999 358 1.46 -4.54 -0.19 0 166.13 178.36 30169 +1999 359 4.43 -1.57 2.78 0.49 201.39 145.14 30186 +1999 360 3.81 -2.19 2.16 0 193.54 176.51 30208 +1999 361 5.15 -0.85 3.5 0 210.85 175.36 30235 +1999 362 2.97 -3.03 1.32 0 183.33 176.54 30267 +1999 363 7.82 1.82 6.17 0 249.34 173.11 30303 +1999 364 3.11 -2.89 1.46 0 184.99 175.88 30343 +1999 365 0.76 -5.24 -0.89 0.31 158.64 145.06 30388 +2000 1 -2.78 -8.78 -4.43 0 125.07 179.62 30438 +2000 2 0.78 -5.22 -0.87 0 158.85 178.76 30492 +2000 3 2.28 -3.72 0.63 0 175.29 178.61 30551 +2000 4 0.79 -5.21 -0.86 0.02 158.96 146.81 30614 +2000 5 0.39 -5.61 -1.26 0.3 154.8 147.28 30681 +2000 6 -0.11 -6.11 -1.76 1.5 149.74 152.69 30752 +2000 7 -0.54 -6.54 -2.19 0 145.51 187.25 30828 +2000 8 -2.39 -8.39 -4.04 0.16 128.44 155.34 30907 +2000 9 -1.89 -7.89 -3.54 0 132.87 190.79 30991 +2000 10 2.15 -3.85 0.5 0 173.81 189.88 31079 +2000 11 1.07 -4.93 -0.58 0 161.92 191.11 31171 +2000 12 1.56 -4.44 -0.09 0.26 167.22 156.31 31266 +2000 13 5.36 -0.64 3.71 0 213.68 190.16 31366 +2000 14 4.78 -1.22 3.13 0 205.94 191.22 31469 +2000 15 5.26 -0.74 3.61 0.01 212.33 155.68 31575 +2000 16 5.72 -0.28 4.07 0.06 218.61 155.52 31686 +2000 17 4.88 -1.12 3.23 0 207.26 193.04 31800 +2000 18 4.47 -1.53 2.82 0 201.91 194.46 31917 +2000 19 3.51 -2.49 1.86 0 189.84 196.36 32038 +2000 20 5.74 -0.26 4.09 0 218.88 195.62 32161 +2000 21 7.39 1.39 5.74 0.22 242.76 157.26 32289 +2000 22 4.13 -1.87 2.48 0 197.56 198.64 32419 +2000 23 4.69 -1.31 3.04 0.01 204.76 159.89 32552 +2000 24 2.97 -3.03 1.32 0 183.33 201.9 32688 +2000 25 1.78 -4.22 0.13 0 169.65 204.09 32827 +2000 26 -2.56 -8.56 -4.21 0 126.96 207.95 32969 +2000 27 -3.82 -9.82 -5.47 0 116.47 210.33 33114 +2000 28 -3.68 -9.68 -5.33 0 117.59 212.34 33261 +2000 29 -3.73 -9.73 -5.38 0 117.19 214.59 33411 +2000 30 -4.31 -10.31 -5.96 0 112.59 216.92 33564 +2000 31 -3.85 -9.85 -5.5 0 116.22 218.97 33718 +2000 32 0.59 -5.41 -1.06 1.12 156.87 173.94 33875 +2000 33 2.5 -3.5 0.85 0.08 177.82 174.61 34035 +2000 34 6.34 0.34 4.69 0.04 227.32 135.26 34196 +2000 35 6.18 0.18 4.53 0.14 225.05 136.96 34360 +2000 36 2.8 -3.2 1.15 0 181.32 187.59 34526 +2000 37 3.04 -2.96 1.39 0.01 184.16 142.4 34694 +2000 38 2.63 -3.37 0.98 0 179.33 192.89 34863 +2000 39 7.09 1.09 5.44 0 238.26 192.07 35035 +2000 40 9.6 3.6 7.95 0 278.23 192.22 35208 +2000 41 11.2 5.2 9.55 0 306.61 193.02 35383 +2000 42 10.82 4.82 9.17 0 299.65 195.96 35560 +2000 43 9.34 3.34 7.69 0 273.84 200.26 35738 +2000 44 8.8 2.8 7.15 0 264.91 203.35 35918 +2000 45 10.65 4.65 9 0 296.59 203.89 36099 +2000 46 9.72 3.72 8.07 0 280.28 207.6 36282 +2000 47 10.27 4.27 8.62 0 289.83 209.75 36466 +2000 48 8.05 2.05 6.4 0 252.93 214.95 36652 +2000 49 9.22 3.22 7.57 0.02 271.84 162.33 36838 +2000 50 10.59 4.59 8.94 0 295.51 217.47 37026 +2000 51 10.79 4.79 9.14 0 299.11 220.13 37215 +2000 52 6.28 0.28 4.63 0 226.47 227.87 37405 +2000 53 3.11 -2.89 1.46 0 184.99 233.58 37596 +2000 54 4.91 -1.09 3.26 0 207.65 234.85 37788 +2000 55 3.91 -2.09 2.26 0 194.79 238.71 37981 +2000 56 3.81 -2.19 2.16 0 193.54 241.5 38175 +2000 57 9.04 3.04 7.39 0.47 268.85 179.35 38370 +2000 58 9.43 3.43 7.78 0 275.36 241.57 38565 +2000 59 11.95 5.95 10.3 0 320.74 240.88 38761 +2000 60 9.29 3.29 7.64 0 273.01 247.27 38958 +2000 61 12.31 6.31 10.66 0 327.71 246.05 39156 +2000 62 11.29 5.29 9.64 0 308.27 250.27 39355 +2000 63 9.61 3.61 7.96 0 278.4 255.52 39553 +2000 64 9.53 3.53 7.88 0.09 277.05 193.87 39753 +2000 65 9.05 3.05 7.4 0 269.02 261.98 39953 +2000 66 7.71 1.71 6.06 0.69 247.65 199.75 40154 +2000 67 5.53 -0.47 3.88 0.04 215.99 203.73 40355 +2000 68 7 1 5.35 0.44 236.93 204.69 40556 +2000 69 5.34 -0.66 3.69 0.39 213.41 208.02 40758 +2000 70 4.05 -1.95 2.4 0.12 196.55 211.13 40960 +2000 71 5.77 -0.23 4.12 0.08 219.3 212.02 41163 +2000 72 8.19 2.19 6.54 0 255.13 282.7 41366 +2000 73 11.21 5.21 9.56 0 306.79 281.12 41569 +2000 74 12.52 6.52 10.87 0 331.84 281.72 41772 +2000 75 10.74 4.74 9.09 0 298.21 287.25 41976 +2000 76 12.77 6.77 11.12 0 336.82 286.56 42179 +2000 77 13.64 7.64 11.99 0.36 354.63 215.67 42383 +2000 78 14.64 8.64 12.99 0.47 376.1 216.2 42587 +2000 79 13.46 7.46 11.81 0 350.88 293.17 42791 +2000 80 14.49 8.49 12.84 0.04 372.81 220.27 42996 +2000 81 12.98 6.98 11.33 0.03 341.05 224.3 43200 +2000 82 12.41 6.41 10.76 0 329.68 302.7 43404 +2000 83 12.47 6.47 10.82 1.12 330.86 228.79 43608 +2000 84 10.62 4.62 8.97 1.93 296.05 233.01 43812 +2000 85 8.61 2.61 6.96 0 261.83 316.2 44016 +2000 86 5.15 -0.85 3.5 0 210.85 323.03 44220 +2000 87 6.28 0.28 4.63 0 226.47 324.25 44424 +2000 88 8.78 2.78 7.13 0.12 264.59 242.44 44627 +2000 89 8.44 2.44 6.79 0.49 259.1 244.53 44831 +2000 90 9.39 3.39 7.74 0.08 274.68 245.25 45034 +2000 91 10.56 4.56 8.91 0 294.97 327.4 45237 +2000 92 12.6 6.6 10.95 0.06 333.43 244.52 45439 +2000 93 11.93 5.93 10.28 0 320.35 329.46 45642 +2000 94 12.72 6.72 11.07 0 335.82 330.12 45843 +2000 95 13.74 7.74 12.09 0 356.73 330.22 46045 +2000 96 15.98 9.98 14.33 0 406.59 327.37 46246 +2000 97 16.51 10.51 14.86 0 419.22 328.1 46446 +2000 98 14.72 8.72 13.07 0.09 377.86 250.63 46647 +2000 99 17.41 11.41 15.76 0.19 441.43 247.28 46846 +2000 100 17 11 15.35 0.04 431.19 249.49 47045 +2000 101 18.75 12.75 17.1 0.77 476.36 247.37 47243 +2000 102 17.19 11.19 15.54 0.02 435.91 251.92 47441 +2000 103 17.29 11.29 15.64 0 438.42 337.43 47638 +2000 104 21.66 15.66 20.01 0.07 560.39 244.61 47834 +2000 105 20.91 14.91 19.26 0.02 537.61 247.75 48030 +2000 106 20.01 14.01 18.36 0 511.32 334.75 48225 +2000 107 17.01 11.01 15.36 0.01 431.44 258.69 48419 +2000 108 18.01 12.01 16.36 0.37 456.79 257.94 48612 +2000 109 13.84 7.84 12.19 0 358.84 355.82 48804 +2000 110 11.95 5.95 10.3 0 320.74 361.13 48995 +2000 111 13.33 7.33 11.68 0 348.2 359.87 49185 +2000 112 16.13 10.13 14.48 0.05 410.13 266.15 49374 +2000 113 17.97 11.97 16.32 0.07 455.76 263.45 49561 +2000 114 21.21 15.21 19.56 0.03 546.63 256.99 49748 +2000 115 18.26 12.26 16.61 0.44 463.33 264.97 49933 +2000 116 15.85 9.85 14.2 0.75 403.54 270.74 50117 +2000 117 14.35 8.35 12.7 0.16 369.76 274.42 50300 +2000 118 20.35 14.35 18.7 0.09 521.12 262.93 50481 +2000 119 15.15 9.15 13.5 0.02 387.46 274.87 50661 +2000 120 16.4 10.4 14.75 0 416.57 364.5 50840 +2000 121 17.93 11.93 16.28 0 454.72 361.41 51016 +2000 122 21.03 15.03 19.38 0 541.2 352.8 51191 +2000 123 23.77 17.77 22.12 0 628.9 343.58 51365 +2000 124 23.63 17.63 21.98 0 624.15 345.16 51536 +2000 125 17.96 11.96 16.31 0 455.5 365.54 51706 +2000 126 14.88 8.88 13.23 0 381.41 374.72 51874 +2000 127 15.06 9.06 13.41 0 385.44 375.17 52039 +2000 128 16.2 10.2 14.55 0 411.79 373.26 52203 +2000 129 13.85 7.85 12.2 0.02 359.05 284.92 52365 +2000 130 17.39 11.39 15.74 0 440.93 371.64 52524 +2000 131 20.16 14.16 18.51 0 515.63 363.89 52681 +2000 132 26.54 20.54 24.89 0 729.52 339.11 52836 +2000 133 23.82 17.82 22.17 0 630.61 351.8 52989 +2000 134 22.53 16.53 20.88 0 587.83 357.58 53138 +2000 135 19.44 13.44 17.79 0.03 495.25 276.84 53286 +2000 136 21.93 15.93 20.28 0.18 568.78 270.85 53430 +2000 137 17.29 11.29 15.64 0.49 438.42 282.72 53572 +2000 138 18.01 12.01 16.36 1.5 456.79 281.6 53711 +2000 139 16.05 10.05 14.4 0.05 408.24 286.25 53848 +2000 140 20.08 14.08 18.43 1.06 513.33 277.56 53981 +2000 141 14.65 8.65 13 0.36 376.32 289.62 54111 +2000 142 15.14 9.14 13.49 0 387.24 385.45 54238 +2000 143 14.37 8.37 12.72 0 370.19 387.89 54362 +2000 144 16.23 10.23 14.58 0.12 412.51 287.72 54483 +2000 145 20.16 14.16 18.51 0.5 515.63 279.13 54600 +2000 146 21.06 15.06 19.41 0.17 542.1 277.06 54714 +2000 147 22.39 16.39 20.74 0.21 583.34 273.72 54824 +2000 148 21.63 15.63 19.98 0.21 559.46 276.14 54931 +2000 149 21.66 15.66 20.01 0 560.39 368.38 55034 +2000 150 20.47 14.47 18.82 0 524.62 372.97 55134 +2000 151 17.95 11.95 16.3 0 455.24 381.48 55229 +2000 152 17.76 11.76 16.11 0 450.34 382.16 55321 +2000 153 17.92 11.92 16.27 0 454.46 381.93 55409 +2000 154 20.73 14.73 19.08 0 532.26 373.11 55492 +2000 155 20.24 14.24 18.59 0.04 517.94 281.25 55572 +2000 156 19.34 13.34 17.69 0 492.47 378.32 55648 +2000 157 17.67 11.67 16.02 0 448.04 383.67 55719 +2000 158 20.39 14.39 18.74 0.3 522.29 281.35 55786 +2000 159 22.98 16.98 21.33 0.25 602.46 274.3 55849 +2000 160 25.84 19.84 24.19 0 702.89 353.52 55908 +2000 161 22.78 16.78 21.13 0 595.92 366.77 55962 +2000 162 21.75 15.75 20.1 0.01 563.17 278.09 56011 +2000 163 22.52 16.52 20.87 0.21 587.51 276.05 56056 +2000 164 22.34 16.34 20.69 0.14 581.74 276.6 56097 +2000 165 22.59 16.59 20.94 0 589.76 367.93 56133 +2000 166 22.34 16.34 20.69 0 581.74 368.98 56165 +2000 167 23.5 17.5 21.85 0.37 619.76 273.22 56192 +2000 168 24.77 18.77 23.12 0 663.78 358.94 56214 +2000 169 23.82 17.82 22.17 0 630.61 363.05 56231 +2000 170 25.46 19.46 23.81 0.13 688.78 266.88 56244 +2000 171 22.77 16.77 21.12 0.56 595.59 275.54 56252 +2000 172 22.65 16.65 21 0.41 591.7 275.89 56256 +2000 173 26.43 20.43 24.78 0 725.28 351.3 56255 +2000 174 28.05 22.05 26.4 0.17 789.88 257.27 56249 +2000 175 22.17 16.17 20.52 0.19 576.34 277.19 56238 +2000 176 23.88 17.88 22.23 0.53 632.66 272.01 56223 +2000 177 21.74 15.74 20.09 0.35 562.86 278.31 56203 +2000 178 22.53 16.53 20.88 0 587.83 368.08 56179 +2000 179 23.41 17.41 21.76 0 616.73 364.46 56150 +2000 180 25.68 19.68 24.03 0 696.92 354.43 56116 +2000 181 27.52 21.52 25.87 0 768.23 345.38 56078 +2000 182 26.33 20.33 24.68 0 721.44 351.16 56035 +2000 183 25.53 19.53 23.88 0.23 691.36 266.06 55987 +2000 184 25.95 19.95 24.3 1.65 707.02 264.48 55935 +2000 185 23.7 17.7 22.05 0.1 626.52 271.9 55879 +2000 186 19.35 13.35 17.7 0 492.75 378.33 55818 +2000 187 19.97 13.97 18.32 0.15 510.18 282.07 55753 +2000 188 21.76 15.76 20.11 0.26 563.48 277.11 55684 +2000 189 18.42 12.42 16.77 0.29 467.55 285.48 55611 +2000 190 15.53 9.53 13.88 0.17 396.12 291.35 55533 +2000 191 15.24 9.24 13.59 0 389.5 388.93 55451 +2000 192 17.08 11.08 15.43 0.11 433.18 287.75 55366 +2000 193 20.25 14.25 18.6 0 518.22 373.48 55276 +2000 194 21.72 15.72 20.07 0.03 562.24 276.02 55182 +2000 195 22.96 16.96 21.31 0 601.8 363 55085 +2000 196 25.58 19.58 23.93 0 693.21 351.41 54984 +2000 197 27.06 21.06 25.41 0.01 749.85 257.93 54879 +2000 198 28.4 22.4 26.75 1.15 804.45 252.47 54770 +2000 199 25.05 19.05 23.4 1.57 673.83 264.46 54658 +2000 200 22.88 16.88 21.23 0.34 599.18 270.98 54542 +2000 201 22.01 16.01 20.36 0 571.29 364.19 54423 +2000 202 19.51 13.51 17.86 0.23 497.2 279.27 54301 +2000 203 17.85 11.85 16.2 0 452.65 377 54176 +2000 204 18.13 12.13 16.48 0 459.92 375.65 54047 +2000 205 21.29 15.29 19.64 1.23 549.05 273.57 53915 +2000 206 20.08 14.08 18.43 0.1 513.33 276.29 53780 +2000 207 19.66 13.66 18.01 0 501.4 369.11 53643 +2000 208 20.9 14.9 19.25 0.07 537.31 273.2 53502 +2000 209 24.43 18.43 22.78 0 651.74 350.01 53359 +2000 210 28.22 22.22 26.57 0 796.93 331.56 53213 +2000 211 27.33 21.33 25.68 0.09 760.59 251.51 53064 +2000 212 28.09 22.09 26.44 0.51 791.53 248.07 52913 +2000 213 24.23 18.23 22.58 0 644.75 347.99 52760 +2000 214 24.88 18.88 23.23 0 667.71 344.51 52604 +2000 215 25.42 19.42 23.77 0 687.31 341.49 52445 +2000 216 26.83 20.83 25.18 0.13 740.8 250.51 52285 +2000 217 24.34 18.34 22.69 0.42 648.58 258.23 52122 +2000 218 22.9 16.9 21.25 0 599.84 349.28 51958 +2000 219 21.6 15.6 19.95 0 558.54 353.07 51791 +2000 220 23.53 17.53 21.88 0 620.77 344.88 51622 +2000 221 23.61 17.61 21.96 0 623.47 343.59 51451 +2000 222 27.34 21.34 25.69 0.48 760.99 244.62 51279 +2000 223 24.76 18.76 23.11 0.64 663.42 252.57 51105 +2000 224 26.45 20.45 24.8 0.27 726.05 246.23 50929 +2000 225 23.67 17.67 22.02 0.16 625.5 254.31 50751 +2000 226 23.19 17.19 21.54 0 609.4 339.84 50572 +2000 227 21.05 15.05 19.4 0 541.8 346.31 50392 +2000 228 19.05 13.05 17.4 0 484.5 351.51 50210 +2000 229 23.98 17.98 22.33 0 636.09 333.13 50026 +2000 230 29.07 23.07 27.42 0 832.99 308.66 49842 +2000 231 23.86 17.86 22.21 0 631.98 330.95 49656 +2000 232 28.74 22.74 27.09 0 818.83 307.76 49469 +2000 233 29.53 23.53 27.88 0 853.08 302.36 49280 +2000 234 28.54 22.54 26.89 0 810.35 306.17 49091 +2000 235 33.75 27.75 32.1 0 1057.16 274.89 48900 +2000 236 26.95 20.95 25.3 0 745.51 311.09 48709 +2000 237 26.15 20.15 24.5 0 714.58 313.11 48516 +2000 238 21.95 15.95 20.3 0.47 569.41 245.88 48323 +2000 239 20.12 14.12 18.47 0.03 514.48 249.26 48128 +2000 240 19.96 13.96 18.31 0 509.9 331.09 47933 +2000 241 21.01 15.01 19.36 0.35 540.6 244.56 47737 +2000 242 19.83 13.83 18.18 0.76 506.2 246.04 47541 +2000 243 17.59 11.59 15.94 0.67 446 249.38 47343 +2000 244 16.41 10.41 14.76 0.11 416.81 250.25 47145 +2000 245 16.33 10.33 14.68 0.06 414.89 249 46947 +2000 246 16.09 10.09 14.44 0.58 409.18 247.94 46747 +2000 247 17.77 11.77 16.12 0 450.6 324.52 46547 +2000 248 18.94 12.94 17.29 0.77 481.5 239.57 46347 +2000 249 20.49 14.49 18.84 0.14 525.2 234.65 46146 +2000 250 15.56 9.56 13.91 0.82 396.81 242.93 45945 +2000 251 14.39 8.39 12.74 0.06 370.63 243.24 45743 +2000 252 13.48 7.48 11.83 0.26 351.3 242.98 45541 +2000 253 14.26 8.26 12.61 0 367.81 320.24 45339 +2000 254 17.57 11.57 15.92 0 445.49 310.55 45136 +2000 255 16.01 10.01 14.36 0.12 407.3 234 44933 +2000 256 15.15 9.15 13.5 0 387.46 311.61 44730 +2000 257 19.75 13.75 18.1 0.3 503.94 223.62 44527 +2000 258 17.18 11.18 15.53 0.01 435.66 226.87 44323 +2000 259 19.96 13.96 18.31 0.38 509.9 219.67 44119 +2000 260 22.45 16.45 20.8 0 585.26 283.14 43915 +2000 261 22.4 16.4 20.75 0.29 583.66 210.71 43711 +2000 262 21.96 15.96 20.31 0 569.72 280.04 43507 +2000 263 22.36 16.36 20.71 0.55 582.38 207.33 43303 +2000 264 22.72 16.72 21.07 0.09 593.97 204.64 43099 +2000 265 23.21 17.21 21.56 0.13 610.06 201.77 42894 +2000 266 22.01 16.01 20.36 0.23 571.29 202.8 42690 +2000 267 23.68 17.68 22.03 0 625.84 262.62 42486 +2000 268 23.57 17.57 21.92 0.36 622.12 195.42 42282 +2000 269 21.86 15.86 20.21 0 566.6 263.41 42078 +2000 270 19.31 13.31 17.66 0 491.64 267.76 41875 +2000 271 21.75 15.75 20.1 0 563.17 258.7 41671 +2000 272 14.8 8.8 13.15 0 379.63 272.34 41468 +2000 273 16.27 10.27 14.62 0.12 413.46 200.19 41265 +2000 274 15.25 9.25 13.6 0.63 389.73 199.71 41062 +2000 275 18.35 12.35 16.7 0.15 465.7 192.79 40860 +2000 276 15.53 9.53 13.88 0 396.12 260.31 40658 +2000 277 14.32 8.32 12.67 0 369.11 259.9 40456 +2000 278 16 10 14.35 0 407.06 253.93 40255 +2000 279 11.08 5.08 9.43 0.33 304.4 194.53 40054 +2000 280 11.97 5.97 10.32 0 321.12 255.39 39854 +2000 281 13.7 7.7 12.05 0 355.89 249.93 39654 +2000 282 18.29 12.29 16.64 0 464.12 238.53 39455 +2000 283 19.4 13.4 17.75 0.01 494.14 175 39256 +2000 284 17.1 11.1 15.45 0.01 433.67 176.46 39058 +2000 285 14.13 8.13 12.48 0.05 365.02 178.53 38861 +2000 286 17.49 11.49 15.84 0.17 443.46 171.93 38664 +2000 287 13.55 7.55 11.9 2.16 352.75 174.98 38468 +2000 288 11.63 5.63 9.98 0 314.64 233.34 38273 +2000 289 8.99 2.99 7.34 0.05 268.03 175.52 38079 +2000 290 15.57 9.57 13.92 0 397.04 221.81 37885 +2000 291 13.93 7.93 12.28 0 360.75 221.81 37693 +2000 292 15.49 9.49 13.84 0 395.2 216.65 37501 +2000 293 19.34 13.34 17.69 0.66 492.47 155.09 37311 +2000 294 19.95 13.95 18.3 1.2 509.61 152.05 37121 +2000 295 23.29 17.29 21.64 0.23 612.72 144.18 36933 +2000 296 24.25 18.25 22.6 0 645.44 187.36 36745 +2000 297 22.81 16.81 21.16 0 596.9 188.52 36560 +2000 298 21.41 15.41 19.76 0 552.71 189.36 36375 +2000 299 19.38 13.38 17.73 0 493.58 190.99 36191 +2000 300 16.91 10.91 15.26 0 428.97 192.96 36009 +2000 301 15.29 9.29 13.64 0.03 390.64 144.84 35829 +2000 302 10.98 4.98 9.33 0.02 302.56 147.24 35650 +2000 303 11.15 5.15 9.5 0.08 305.68 145.16 35472 +2000 304 10.54 4.54 8.89 0.57 294.62 143.85 35296 +2000 305 9.45 3.45 7.8 0 275.69 190.22 35122 +2000 306 13.11 7.11 11.46 0 343.69 183.77 34950 +2000 307 7.75 1.75 6.1 0.51 248.26 140.32 34779 +2000 308 5.22 -0.78 3.57 0.78 211.79 139.94 34610 +2000 309 0.83 -5.17 -0.82 0.29 159.38 140.36 34444 +2000 310 5.25 -0.75 3.6 0.67 212.19 136.32 34279 +2000 311 9.34 3.34 7.69 0.17 273.84 132.04 34116 +2000 312 13.57 7.57 11.92 0.59 353.17 126.57 33956 +2000 313 14.92 8.92 13.27 0.55 382.3 123.72 33797 +2000 314 13.04 7.04 11.39 0.07 342.26 124.08 33641 +2000 315 13.67 7.67 12.02 0 355.26 162.19 33488 +2000 316 13.57 7.57 11.92 0.86 353.17 120.13 33337 +2000 317 12.72 6.72 11.07 0 335.82 159.03 33188 +2000 318 13.76 7.76 12.11 0 357.15 155.53 33042 +2000 319 14.89 8.89 13.24 0 381.63 152.49 32899 +2000 320 17.7 11.7 16.05 0 448.8 146.84 32758 +2000 321 19.62 13.62 17.97 0 500.28 141.84 32620 +2000 322 16.57 10.57 14.92 0 420.67 144.7 32486 +2000 323 18.37 12.37 16.72 0 466.23 140.59 32354 +2000 324 14.46 8.46 12.81 0 372.15 143.87 32225 +2000 325 10.95 4.95 9.3 0 302.02 145.93 32100 +2000 326 9.12 3.12 7.47 0.9 270.17 109.61 31977 +2000 327 2.92 -3.08 1.27 0.73 182.73 111.45 31858 +2000 328 2.54 -3.46 0.89 0 178.28 146.83 31743 +2000 329 5.13 -0.87 3.48 0 210.58 143.79 31631 +2000 330 7.95 1.95 6.3 0 251.36 140.38 31522 +2000 331 7.97 1.97 6.32 0 251.67 139.06 31417 +2000 332 10.96 4.96 9.31 0 302.2 134.95 31316 +2000 333 14.13 8.13 12.48 0 365.02 130.73 31218 +2000 334 16.99 10.99 15.34 0.19 430.95 94.71 31125 +2000 335 7.35 1.35 5.7 0.52 242.16 100.91 31035 +2000 336 5.64 -0.36 3.99 0.03 217.5 100.97 30949 +2000 337 8.78 2.78 7.13 0.01 264.59 98.08 30867 +2000 338 5.69 -0.31 4.04 0.1 218.19 99 30790 +2000 339 10.19 4.19 8.54 0.01 288.42 95.96 30716 +2000 340 8.2 2.2 6.55 0 255.28 128.78 30647 +2000 341 8.35 2.35 6.7 0.09 257.66 95.82 30582 +2000 342 7 1 5.35 0.08 236.93 95.97 30521 +2000 343 6.24 0.24 4.59 0 225.9 127.64 30465 +2000 344 10.14 4.14 8.49 0 287.55 123.69 30413 +2000 345 11.68 5.68 10.03 0 315.59 121.97 30366 +2000 346 8.22 2.22 6.57 0 255.6 124.2 30323 +2000 347 4.97 -1.03 3.32 0 208.45 125.72 30284 +2000 348 2.94 -3.06 1.29 0 182.97 126.47 30251 +2000 349 5.23 -0.77 3.58 0 211.92 124.84 30221 +2000 350 4.14 -1.86 2.49 1.46 197.68 93.84 30197 +2000 351 5.78 -0.22 4.13 0.97 219.44 92.97 30177 +2000 352 3.52 -2.48 1.87 0.06 189.96 93.86 30162 +2000 353 -0.4 -6.4 -2.05 0.09 146.88 139.23 30151 +2000 354 1.14 -4.86 -0.51 0.03 162.67 138.57 30145 +2000 355 -0.41 -6.41 -2.06 0.14 146.78 139.51 30144 +2000 356 0.34 -5.66 -1.31 0.02 154.29 139.25 30147 +2000 357 3.56 -2.44 1.91 0.15 190.45 137.66 30156 +2000 358 10 4 8.35 0.17 285.11 90.74 30169 +2000 359 8.37 2.37 6.72 0 257.98 122.34 30186 +2000 360 6.2 0.2 4.55 0 225.33 124.16 30208 +2000 361 0.86 -5.14 -0.79 0 159.69 127.32 30235 +2000 362 -0.06 -6.06 -1.71 0.27 150.24 140.59 30267 +2000 363 -0.48 -6.48 -2.13 1.11 146.09 144.62 30303 +2000 364 2.99 -3.01 1.34 0 183.56 175.2 30343 +2000 365 1.09 -4.91 -0.56 0 162.13 176.48 30388 +2001 1 2 -10 -1.3 0 67.5 173.99 30217 +2001 2 -1 -4 -1.83 0.05 68.75 57.46 30272 +2001 3 1 -4 -0.38 0 18.75 118.03 30331 +2001 4 3 -6 0.52 0 12.5 163.04 30396 +2001 5 7 0 5.08 0 11.25 142.19 30464 +2001 6 13 4 10.53 0 442.5 155.65 30537 +2001 7 7 2 5.63 0 88.75 111.18 30614 +2001 8 5 4 4.72 0.96 52.5 22.57 30695 +2001 9 7 2 5.63 0 392.5 114.45 30781 +2001 10 5 -4 2.52 0 171.25 166.19 30870 +2001 11 3 -3 1.35 0 76.67 134.79 30964 +2001 12 3 1 2.45 0 201.11 53.72 31061 +2001 13 1 -5 -0.65 0 114.44 141.2 31162 +2001 14 -1 -6 -2.38 0 100 125.52 31268 +2001 15 -1 -9 -3.2 0 84.44 171.08 31376 +2001 16 -3 -10 -4.92 0 37.78 162.92 31489 +2001 17 -1 -4 -1.83 0 120 83.76 31605 +2001 18 2 -2 0.9 0 124.46 109.25 31724 +2001 19 1 -2 0.18 0 31 101.21 31847 +2001 20 0 -2 -0.55 0 42 62.92 31974 +2001 21 0 -2 -0.55 0 80 49.01 32103 +2001 22 0 -2 -0.55 0.04 45 50.15 32236 +2001 23 1 -1 0.45 0.06 17 38.35 32372 +2001 24 3 0 2.17 0.05 2 40.26 32510 +2001 25 3 1 2.45 0.52 12 42.31 32652 +2001 26 5 2 4.17 0.03 117.58 43.3 32797 +2001 27 9 2 7.08 0.77 241 142.28 32944 +2001 28 6 2 4.9 0 95 93.06 33094 +2001 29 4 1 3.17 0 71 70.7 33247 +2001 30 2 2 2 0.05 98 44.02 33402 +2001 31 3 1 2.45 0 267 137.75 33559 +2001 32 2 -1 1.18 0 231 157.02 33719 +2001 33 3 -4 1.08 0 163 197.42 33882 +2001 34 2 -5 0.07 0 202 160.52 34046 +2001 35 8 -3 4.97 0 448 112.53 34213 +2001 36 15 2 11.43 0 479 225.08 34382 +2001 37 14 2 10.7 0 496 226.46 34552 +2001 38 16 6 13.25 0 672 174.94 34725 +2001 39 17 11 15.35 0 775 218.7 34900 +2001 40 16 6 13.25 0 553 188.22 35076 +2001 41 10 6 8.9 0 321 217.11 35254 +2001 42 10 0 7.25 0 307 278.19 35434 +2001 43 12 -2 8.15 0 458 293.15 35615 +2001 44 10 1 7.53 0 278 178.07 35798 +2001 45 9 1 6.8 0 375 273.38 35983 +2001 46 11 -2 7.43 0 339 281.71 36169 +2001 47 12 -3 7.88 0 456 295.25 36356 +2001 48 11 -4 6.88 0 280 212.97 36544 +2001 49 12 -2 8.15 0 350 251.73 36734 +2001 50 9 2 7.08 0 457 165.62 36925 +2001 51 9 3 7.35 0 383 107.13 37117 +2001 52 12 1 8.97 0 603 224.28 37310 +2001 53 10 1 7.53 0 541.82 273.68 37505 +2001 54 7 -1 4.8 0.07 162.73 138.98 37700 +2001 55 2 -4 0.35 0 201.82 176.45 37896 +2001 56 3 -8 -0.02 0 270.91 316.21 38093 +2001 57 2 -4 0.35 0 229.09 205.7 38291 +2001 58 6 -7 2.43 0 400 287.88 38490 +2001 59 5 -3 2.8 0.81 319.09 210.5 38689 +2001 60 5 -1 3.35 0 64.55 158.82 38890 +2001 61 8 -3 4.97 0.65 246.67 306.46 39091 +2001 62 9 3 7.35 0 174.17 75.36 39292 +2001 63 19 2 14.32 0 618.33 218.18 39495 +2001 64 11 6 9.63 0.32 239.17 94.54 39697 +2001 65 6 0 4.35 0 285.83 264.44 39901 +2001 66 9 -1 6.25 0 402.5 274.9 40105 +2001 67 14 3 10.98 0 356.67 224.3 40309 +2001 68 18 8 15.25 0 627.5 290.01 40514 +2001 69 16 7 13.53 0 459.17 265.15 40719 +2001 70 19 5 15.15 0.01 815.83 313.06 40924 +2001 71 21 7 17.15 0 734.17 360.51 41130 +2001 72 10 8 9.45 1.88 123.33 49.57 41336 +2001 73 14 4 11.25 0.18 291.67 243.11 41543 +2001 74 14 2 10.7 0 356.67 232.28 41749 +2001 75 18 5 14.43 0 566.67 385.14 41956 +2001 76 19 5 15.15 0 668.33 272.1 42163 +2001 77 19 8 15.98 0 830.83 332.7 42370 +2001 78 14 7 12.07 0.7 472.5 192.26 42578 +2001 79 10 3 8.07 0 192.5 289.27 42785 +2001 80 3 1 2.45 0.02 16.67 52.42 42992 +2001 81 7 3 5.9 0.03 170.74 49.38 43200 +2001 82 15 5 12.25 0 426.67 264.56 43407 +2001 83 18 9 15.53 0 630 260.62 43615 +2001 84 18 4 14.15 0.79 458.33 326.83 43822 +2001 85 15 8 13.07 0.91 321.67 304.53 44029 +2001 86 3 1 2.45 0 161.67 126.62 44236 +2001 87 5 -2 3.08 0 210 138.53 44443 +2001 88 9 2 7.08 0 169.17 177.9 44650 +2001 89 11 5 9.35 0 179.17 137.49 44857 +2001 90 14 7 12.07 0 390.83 247.15 45063 +2001 91 16 2 12.15 0 572.08 428.92 45270 +2001 92 18 3 13.88 0 729.62 462.19 45475 +2001 93 19 2 14.32 0 863.08 421.72 45681 +2001 94 21 5 16.6 0.2 1004.62 433.87 45886 +2001 95 12 9 11.18 0.3 453.85 174.61 46091 +2001 96 17 2 12.88 0 713.57 368.41 46295 +2001 97 18 7 14.98 1.24 663.57 258.14 46499 +2001 98 9 8 8.72 1.19 57.14 48.78 46702 +2001 99 12 6 10.35 0 362.14 187.64 46905 +2001 100 14 3 10.98 0.12 429.29 360.23 47107 +2001 101 12 6 10.35 0.32 165 105.38 47309 +2001 102 14 9 12.63 0 370 286.92 47510 +2001 103 7 1 5.35 0 372.14 461.91 47710 +2001 104 7 -2 4.53 0 349.29 401.47 47910 +2001 105 10 -4 6.15 0 463.57 460.78 48108 +2001 106 13 -1 9.15 0.14 456.43 292.55 48306 +2001 107 13 5 10.8 0 408.57 239.26 48504 +2001 108 14 -1 9.88 0 578.57 389.85 48700 +2001 109 15 1 11.15 0.67 359.29 272.36 48895 +2001 110 11 4 9.07 0.13 103.57 144.88 49089 +2001 111 10 6 8.9 0.01 146.43 156.2 49282 +2001 112 12 4 9.8 0.2 245.71 237.18 49475 +2001 113 15 3 11.7 0 482.86 438.07 49666 +2001 114 19 4 14.88 0 936.43 496.52 49855 +2001 115 22 4 17.05 0.1 905 451.17 50044 +2001 116 13 10 12.18 0.13 314.29 110.02 50231 +2001 117 19 3 14.6 0 785.71 475.67 50417 +2001 118 21 5 16.6 0 1000 477.28 50601 +2001 119 24 5 18.77 0 1067.86 418.98 50784 +2001 120 25 6 19.77 0 952.14 421.74 50966 +2001 121 26 12 22.15 0 1205 477.07 51145 +2001 122 27 10 22.32 0 1517.86 501.58 51324 +2001 123 26 9 21.32 0 1388.45 480.53 51500 +2001 124 27 11 22.6 1.21 1277.14 459.2 51674 +2001 125 23 11 19.7 0.07 516 400.06 51847 +2001 126 20 13 18.07 0.03 380.67 292.17 52018 +2001 127 16 12 14.9 0.18 286 166.25 52187 +2001 128 19 11 16.8 0.56 307.33 276.77 52353 +2001 129 22 13 19.52 0.78 606.67 394.77 52518 +2001 130 22 7 17.88 0 1026.67 507.62 52680 +2001 131 22 11 18.98 0.06 715.33 382.2 52840 +2001 132 18 9 15.53 0 791.33 473.93 52998 +2001 133 18 5 14.43 0 861.33 519.96 53153 +2001 134 20 6 16.15 0 940.67 497.67 53306 +2001 135 24 6 19.05 0 850 394.93 53456 +2001 136 25 12 21.43 0 1130.67 460.14 53603 +2001 137 26 11 21.88 0 1139.33 503.89 53748 +2001 138 23 15 20.8 0.49 959.33 404.59 53889 +2001 139 20 9 16.98 0 771.33 402.42 54028 +2001 140 21 4 16.32 0 844.67 418.71 54164 +2001 141 22 7 17.88 0 752.67 282.88 54297 +2001 142 23 7 18.6 0 744.17 507.16 54426 +2001 143 22 11 18.98 0 880.85 370.96 54552 +2001 144 24 5 18.77 0 1293.68 506.51 54675 +2001 145 25 7 20.05 0 1324.37 452.07 54795 +2001 146 24 13 20.98 0 1296.25 524.29 54911 +2001 147 28 10 23.05 0 1853.13 413.52 55023 +2001 148 29 17 25.7 0 1800.63 391.35 55132 +2001 149 30 19 26.98 0 1362.84 344.28 55237 +2001 150 27 17 24.25 0.52 1091.15 250.74 55339 +2001 151 24 12 20.7 0.4 1038.59 299.29 55436 +2001 152 21 12 18.52 0 730.22 329.73 55530 +2001 153 21 5 16.6 0 1016.18 489.92 55619 +2001 154 19 10 16.52 1.95 651.84 255.26 55705 +2001 155 16 8 13.8 0 504.86 316.38 55786 +2001 156 20 6 16.15 0 845 419.58 55863 +2001 157 23 5 18.05 0.22 840 399.19 55936 +2001 158 25 15 22.25 0.16 985.63 363.38 56004 +2001 159 27 11 22.6 0 1108.13 488.63 56068 +2001 160 21 12 18.52 0 855 320.78 56128 +2001 161 28 13 23.88 0 905 407.53 56183 +2001 162 15 14 14.73 1.27 165 95.46 56234 +2001 163 21 4 16.32 0 1042.42 500.28 56280 +2001 164 22 8 18.15 0 910 497.97 56321 +2001 165 23 8 18.88 0.02 672.5 236.96 56358 +2001 166 27 11 22.6 0 1315 434.32 56390 +2001 167 29 11 24.05 0.58 1278.75 414.95 56418 +2001 168 20 15 18.63 0.4 231.88 200.52 56440 +2001 169 23 13 20.25 0 828.12 297.9 56458 +2001 170 19 15 17.9 0 744.38 210.03 56472 +2001 171 20 14 18.35 0.02 748.12 137.88 56480 +2001 172 27 14 23.43 0 1497.5 474.08 56484 +2001 173 23 12 19.98 1.7 810 289.91 56482 +2001 174 25 8 20.32 0 1055.63 465.3 56476 +2001 175 26 9 21.32 0 1378.13 498.13 56466 +2001 176 27 10 22.32 0 1445 428.08 56450 +2001 177 28 13 23.88 0 1778.75 495.89 56430 +2001 178 32 12 26.5 0 1567.5 482.89 56405 +2001 179 30 14 25.6 0.83 1048.12 348.75 56375 +2001 180 28 18 25.25 0 990.63 287.54 56341 +2001 181 30 15 25.88 0.03 1743.75 473.41 56301 +2001 182 24 15 21.52 1.33 496.25 113.54 56258 +2001 183 25 15 22.25 0.01 1209.37 415.4 56209 +2001 184 24 13 20.98 0.1 1020.63 426.75 56156 +2001 185 24 14 21.25 0.12 440.63 250.5 56099 +2001 186 26 9 21.32 0 933.12 389.4 56037 +2001 187 28 13 23.88 0 880 354.6 55971 +2001 188 33 19 29.15 0 1773.75 458.54 55900 +2001 189 29 15 25.15 1.09 1701.25 385.09 55825 +2001 190 26 17 23.52 0 855.63 313.78 55746 +2001 191 29 12 24.32 0 779.38 364.72 55663 +2001 192 31 14 26.32 0.35 1521.25 468.54 55575 +2001 193 23 16 21.07 0 769.38 213.58 55484 +2001 194 28 13 23.88 0 1173.75 402.61 55388 +2001 195 30 16 26.15 0 1610.63 439.56 55289 +2001 196 24 17 22.07 0 2006.25 450.71 55186 +2001 197 33 17 28.6 0.1 2007.81 419.95 55079 +2001 198 20 14 18.35 0.6 248.75 138.4 54968 +2001 199 27 10 22.32 0.01 775.63 388.86 54854 +2001 200 27 14 23.43 0 1278.75 422.57 54736 +2001 201 23 17 21.35 0.51 391.88 227.34 54615 +2001 202 18 15 17.18 0.48 283.75 74.51 54490 +2001 203 22 16 20.35 0 881.25 180.17 54362 +2001 204 21 18 20.18 0.14 660 67.73 54231 +2001 205 23 17 21.35 0.3 526.25 173.79 54097 +2001 206 26 16 23.25 0 1017.5 283.4 53960 +2001 207 27 18 24.52 0 1015.2 328.03 53819 +2001 208 29 17 25.7 0 1364.51 403.79 53676 +2001 209 30 15 25.88 0 1631.2 454.74 53530 +2001 210 30 16 26.15 0 1573.01 435.81 53382 +2001 211 29 17 25.7 0.09 1364.51 301.09 53230 +2001 212 33 17 28.6 0 1976.48 449.03 53076 +2001 213 31 18 27.43 0 1591.34 405.94 52920 +2001 214 31 17 27.15 0 1659.16 422.53 52761 +2001 215 34 18 29.6 0 2083.07 436.44 52600 +2001 216 35 19 30.6 0 2194.48 430.22 52437 +2001 217 26 19 24.07 0 799.95 258.18 52271 +2001 218 28 14 24.15 0 1412.02 432.74 52103 +2001 219 31 12 25.77 0 1914.12 481.71 51934 +2001 220 33 14 27.77 0 2132.05 469.5 51762 +2001 221 31 17 27.15 0 1659.16 410.58 51588 +2001 222 27 17 24.25 1.26 1091.15 255.49 51413 +2001 223 20 14 18.35 0 511.04 231.95 51235 +2001 224 23 12 19.98 0 1084.29 507.23 51057 +2001 225 28 10 23.05 0 1627.14 448.17 50876 +2001 226 30 13 25.32 0 1731.58 451.55 50694 +2001 227 31 15 26.6 0 1777.09 432.9 50510 +2001 228 32 14 27.05 0 1977.1 447.86 50325 +2001 229 32 15 27.32 0 1928.51 434.22 50138 +2001 230 33 16 28.32 0 2033.89 426.76 49951 +2001 231 33 15 28.05 0 2085.65 433.26 49761 +2001 232 33 17 28.6 0 1976.48 399.52 49571 +2001 233 27 18 24.52 0 1015.2 270.56 49380 +2001 234 27 15 23.7 0 1225.04 339.55 49187 +2001 235 28 19 25.52 0 1070.83 258.89 48993 +2001 236 27 17 24.25 0 1091.15 287.29 48798 +2001 237 31 15 26.6 0 1777.09 390.08 48603 +2001 238 33 15 28.05 0 2085.65 406.17 48406 +2001 239 34 15 28.77 0 2248.67 411.07 48208 +2001 240 24 16 21.8 0 793.41 231.93 48010 +2001 241 25 9 20.6 0 1277.93 398.16 47811 +2001 242 24 7 19.32 0 1157.86 407.91 47611 +2001 243 21 10 17.98 0.33 505 137.44 47410 +2001 244 20 13 18.07 0 513.57 258.42 47209 +2001 245 22 12 19.25 0.84 726.15 186.79 47007 +2001 246 26 9 21.32 0 1256.15 373.58 46805 +2001 247 26 11 21.88 1.98 907.69 304.8 46601 +2001 248 14 13 13.73 1.46 152.31 79.81 46398 +2001 249 16 13 15.18 0.35 448.46 34.43 46194 +2001 250 22 12 19.25 0.03 840 269.52 45989 +2001 251 19 11 16.8 2.01 401.54 119.53 45784 +2001 252 14 10 12.9 0.63 173.85 179.93 45579 +2001 253 20 6 16.15 0 623.85 354.72 45373 +2001 254 17 9 14.8 0 601.54 190.34 45167 +2001 255 20 6 16.15 0.06 633.85 248.22 44961 +2001 256 22 7 17.88 0 783.33 323.52 44755 +2001 257 22 11 18.98 3.45 722.5 152.28 44548 +2001 258 14 10 12.9 0.4 100 68.09 44341 +2001 259 18 10 15.8 0.91 365 187.69 44134 +2001 260 12 9 11.18 1.65 125.83 87.27 43927 +2001 261 17 8 14.53 0.06 441.67 244.61 43719 +2001 262 17 5 13.7 0 310.83 238.25 43512 +2001 263 22 5 17.32 0 846.67 375.47 43304 +2001 264 20 7 16.43 0 740 323.5 43097 +2001 265 20 8 16.7 0.19 609.17 291.46 42890 +2001 266 15 12 14.18 1.63 82.5 72.18 42682 +2001 267 25 14 21.98 0.61 512.5 263.89 42475 +2001 268 17 14 16.18 0.77 275 145.54 42268 +2001 269 17 12 15.63 0.04 407.5 139.85 42060 +2001 270 20 6 16.15 0 683.33 356.26 41854 +2001 271 23 8 18.88 0 799.17 354.81 41647 +2001 272 20 8 16.7 0.06 327.5 255 41440 +2001 273 18 9 15.53 0.07 197.5 137.52 41234 +2001 274 22 11 18.98 0 310.83 262.96 41028 +2001 275 24 14 21.25 0 721.82 319.12 40822 +2001 276 26 10 21.6 0 892.73 327.22 40617 +2001 277 22 9 18.43 0.27 593.64 288.51 40412 +2001 278 20 10 17.25 0 450 212.8 40208 +2001 279 22 7 17.88 0 638.18 294.37 40003 +2001 280 24 9 19.88 0 591.82 259.85 39800 +2001 281 26 12 22.15 0 990 297.35 39597 +2001 282 22 10 18.7 0 616.36 252.14 39394 +2001 283 22 10 18.7 0 385.45 167.07 39192 +2001 284 23 8 18.88 0 650.91 279.04 38991 +2001 285 23 7 18.6 0 712.73 304.47 38790 +2001 286 23 4 17.77 0 561.82 303.59 38590 +2001 287 21 6 16.88 0 478.18 280.26 38391 +2001 288 21 6 16.88 0 505.45 287.16 38193 +2001 289 21 4 16.32 0 519.09 249.89 37995 +2001 290 15 8 13.07 0.02 120.91 139.59 37799 +2001 291 13 8 11.63 0.01 50 71.26 37603 +2001 292 13 12 12.73 0 39.09 29.32 37408 +2001 293 13 12 12.73 0 78.18 38.24 37214 +2001 294 23 12 19.98 0.31 768.18 227.69 37022 +2001 295 19 11 16.8 0.02 518.18 232.45 36830 +2001 296 18 6 14.7 0 635.45 284.12 36640 +2001 297 12 9 11.18 0.24 168.18 73.62 36451 +2001 298 11 9 10.45 0.01 79.09 62.12 36263 +2001 299 11 8 10.18 0 229.09 170.98 36076 +2001 300 11 0 7.97 0 263 213.24 35891 +2001 301 13 6 11.07 0 194 144.03 35707 +2001 302 12 9 11.18 0 123 66.9 35525 +2001 303 17 10 15.07 0 308 128.52 35345 +2001 304 25 11 21.15 0 1267 245.41 35166 +2001 305 14 10 12.9 0 810 164.86 34988 +2001 306 11 5 9.35 0 564 250.62 34813 +2001 307 12 0 8.7 0 323 244.77 34639 +2001 308 12 0 8.7 0 498 246.27 34468 +2001 309 13 -2 8.88 0 438.89 213.81 34298 +2001 310 10 6 8.9 0 286.67 69.06 34130 +2001 311 11 5 9.35 0 260 138.13 33964 +2001 312 11 6 9.63 1.24 446.67 77.63 33801 +2001 313 6 5 5.72 0.31 173.33 58.76 33640 +2001 314 6 2 4.9 0 277.78 132.43 33481 +2001 315 5 2 4.17 0.05 113.33 61.73 33325 +2001 316 4 3 3.73 0.66 37.78 30.57 33171 +2001 317 6 0 4.35 0.86 36.67 35.89 33019 +2001 318 5 2 4.17 0 301.11 115.76 32871 +2001 319 6 0 4.35 0 261.11 209.26 32725 +2001 320 9 -7 4.6 0 293.33 232.17 32582 +2001 321 8 -2 5.25 0 278.89 220.34 32441 +2001 322 0 -6 -1.65 0 20 58.73 32304 +2001 323 4 -1 2.63 0 58.89 42.47 32170 +2001 324 8 2 6.35 0 341.11 158.77 32039 +2001 325 11 -2 7.43 0 450 202.77 31911 +2001 326 10 -5 5.88 0.03 284.44 210.18 31786 +2001 327 5 1 3.9 0 258.89 120.16 31665 +2001 328 6 -1 4.08 0 336.67 103.81 31547 +2001 329 6 1 4.63 0 372.22 170.46 31433 +2001 330 4 -6 1.25 0.01 147.78 124.06 31322 +2001 331 3 0 2.17 0.08 36.67 36.5 31215 +2001 332 3 1 2.45 0 36.67 58 31112 +2001 333 9 -1 6.25 0.05 173.33 143.88 31012 +2001 334 3 2 2.73 0.04 31.11 29.33 30917 +2001 335 4 -4 1.8 0 140 188.03 30825 +2001 336 -3 -7 -4.1 0 20 58.09 30738 +2001 337 -1 -4 -1.83 0 20 30.12 30654 +2001 338 0 -3 -0.82 0 15.56 16.3 30575 +2001 339 2 0 1.45 0 24.44 64.99 30500 +2001 340 3 0 2.17 0.21 43.33 43.2 30430 +2001 341 4 -1 2.63 0 114.44 65.36 30363 +2001 342 0 -3 -0.82 0 131.11 150.82 30301 +2001 343 -1 -7 -2.65 0 124.44 188.93 30244 +2001 344 2 -12 -1.85 0.01 148.89 216.22 30191 +2001 345 0 -3 -0.82 0.16 30 39.35 30143 +2001 346 1 -2 0.18 0.45 21.11 43.4 30099 +2001 347 -7 -8 -7.28 0 87.5 135.31 30060 +2001 348 -7 -13 -8.65 0 83.75 154.38 30025 +2001 349 -3 -18 -7.13 0 71.25 169.94 29995 +2001 350 -2 -7 -3.38 0 108.75 118.79 29970 +2001 351 -1 -6 -2.38 0.15 117.5 54.66 29950 +2001 352 2 -3 0.63 0.01 86.25 71.03 29934 +2001 353 3 -12 -1.13 0 132.5 189.18 29924 +2001 354 6 -13 0.78 0 195 191.45 29918 +2001 355 -1 -9 -3.2 0 153.75 161.65 29916 +2001 356 1 -5 -0.65 0.41 162.5 114.99 29920 +2001 357 1 -3 -0.1 0 58.75 67.19 29928 +2001 358 -2 -18 -6.4 0 140 200.59 29941 +2001 359 -2 -12 -4.75 0 191.25 95.4 29959 +2001 360 -4 -9 -5.38 0.13 117.5 72.04 29982 +2001 361 2 -6 -0.2 0 207.5 106.45 30009 +2001 362 1 -10 -2.02 0 186.25 93.95 30042 +2001 363 6 -1 4.08 0 330 94.89 30078 +2001 364 5 3 4.45 0.05 348.75 49.15 30120 +2001 365 -2 -5 -2.83 0.01 226.25 101.61 30166 +2002 1 2 -8 -0.75 0 265 114.78 30217 +2002 2 7 -6 3.43 0 473.75 106.37 30272 +2002 3 -2 -5 -2.83 0 231.25 179.31 30331 +2002 4 -3 -15 -6.3 0 126.25 194.04 30396 +2002 5 2 -13 -2.13 0 177.5 142.48 30464 +2002 6 8 -6 4.15 0 376.25 181.44 30537 +2002 7 7 -5 3.7 0 250 147.8 30614 +2002 8 3 -4 1.08 0 120 123.47 30695 +2002 9 4 -3 2.08 0 151.25 175.89 30781 +2002 10 -2 -6 -3.1 0 20 25.97 30870 +2002 11 -4 -4 -4 0 20 20.24 30964 +2002 12 -2 -6 -3.1 0 20 49.19 31061 +2002 13 -3 -6 -3.83 0.12 20 34.18 31162 +2002 14 -3 -4.5 -3.41 0.05 28.89 39.59 31268 +2002 15 -4 -6 -4.55 0.01 50 34.82 31376 +2002 16 -5 -5 -5 0 41.11 21.13 31489 +2002 17 -3 -5 -3.55 0 21.11 26.67 31605 +2002 18 -1 -4 -1.83 0 65.56 68.52 31724 +2002 19 1 -9 -1.75 0.01 93 161.72 31847 +2002 20 9 -4 5.43 0 197 137.2 31974 +2002 21 6 -1 4.08 0 254 28.77 32103 +2002 22 11 -1 7.7 0 342 193.52 32236 +2002 23 10 -2 6.7 0 283 198.85 32372 +2002 24 9 6 8.18 0.02 352 61.3 32510 +2002 25 10 2 7.8 0 229 158.87 32652 +2002 26 8 1 6.08 0 131 58.47 32797 +2002 27 10 0 7.25 0 400 60.34 32944 +2002 28 18 6 14.7 0 610 174.94 33094 +2002 29 20 4 15.6 0 1095 172.17 33247 +2002 30 15 2 11.43 0 614 168.05 33402 +2002 31 13 3 10.25 0 498 143.58 33559 +2002 32 13 1 9.7 0 416 164.63 33719 +2002 33 15 1 11.15 0 449 218.62 33882 +2002 34 13 2 9.97 0 368 221.71 34046 +2002 35 2 -1 1.18 0 12 78.34 34213 +2002 36 14 -2 9.6 0 367 245.81 34382 +2002 37 12 1 8.97 0.11 405 172.1 34552 +2002 38 4 2 3.45 0.56 25 38.83 34725 +2002 39 9 3 7.35 0 93 111.75 34900 +2002 40 11 0 7.97 0.05 121 123.74 35076 +2002 41 11 4 9.07 0.1 353 114.08 35254 +2002 42 14 1 10.43 0 565 216.26 35434 +2002 43 15 3 11.7 0 669 177.58 35615 +2002 44 19 3 14.6 0 491 249.39 35798 +2002 45 5 5 5 0 174 38.47 35983 +2002 46 4 -1 2.63 0 329 192.98 36169 +2002 47 3 -3 1.35 0.07 266 125.88 36356 +2002 48 6 0 4.35 1.18 144 134.16 36544 +2002 49 7 2 5.63 0.31 45 84.7 36734 +2002 50 9 2 7.08 0 216 206.36 36925 +2002 51 9 -1 6.25 0 332 81.45 37117 +2002 52 8 6 7.45 0.11 274 94.06 37310 +2002 53 4 -4 1.8 0 323.64 304.43 37505 +2002 54 9 -2 5.97 0.01 419.09 160.29 37700 +2002 55 10 -1 6.97 0 552.73 228.27 37896 +2002 56 12 -3 7.88 0 600 146.53 38093 +2002 57 14 1 10.43 0 685.45 261.68 38291 +2002 58 14 6 11.8 0 591.82 187.06 38490 +2002 59 7 6 6.72 0.79 66.36 26.56 38689 +2002 60 7 3 5.9 0.08 131.82 119.14 38890 +2002 61 7 2 5.63 0.05 73.33 69.33 39091 +2002 62 4 3 3.73 0.04 251.67 61.1 39292 +2002 63 10 -1 6.97 0 311.67 300.97 39495 +2002 64 13 -1 9.15 0 538.33 295.76 39697 +2002 65 18 3 13.88 0 714.17 208.95 39901 +2002 66 17 9 14.8 0 855.83 313.58 40105 +2002 67 15 5 12.25 0 820 331.22 40309 +2002 68 14 0 10.15 0 775.83 360.46 40514 +2002 69 15 0 10.88 0 759.17 269.55 40719 +2002 70 15 -2 10.32 0 789.17 342.18 40924 +2002 71 15 -2 10.32 0 754.17 344.2 41130 +2002 72 17 -1 12.05 0 787.5 293.46 41336 +2002 73 20 2 15.05 0 1173.33 335.33 41543 +2002 74 17 6 13.98 0 624.17 310.42 41749 +2002 75 14 4 11.25 0 317.5 256.57 41956 +2002 76 17 2 12.88 0 465 314.79 42163 +2002 77 16 1 11.88 0 522.5 329.22 42370 +2002 78 16 3 12.43 0 379.17 130.91 42578 +2002 79 16 7 13.53 0.17 410 154.28 42785 +2002 80 16 7 13.53 0.2 208.33 103.71 42992 +2002 81 16 6 13.25 0.12 459.17 255.26 43200 +2002 82 7 -2 4.53 0.07 310 324.49 43407 +2002 83 6 0 4.35 0.03 215.83 177.29 43615 +2002 84 6 1 4.63 0 285.83 176.13 43822 +2002 85 7 0 5.08 0 292.5 130.72 44029 +2002 86 8 1 6.08 0 410 327.19 44236 +2002 87 11 -3 7.15 0 480.83 400.58 44443 +2002 88 15 -3 10.05 0 696.67 393.39 44650 +2002 89 19 0 13.78 0 1093.33 416.05 44857 +2002 90 19 1 14.05 0 1130 390.66 45063 +2002 91 20 3 15.32 0 1139.17 369.66 45270 +2002 92 19 3 14.6 0 893.85 391.12 45475 +2002 93 16 5 12.98 0 755.38 333.08 45681 +2002 94 13 2 9.97 0.03 574.62 394.88 45886 +2002 95 12 4 9.8 0 601.54 352.93 46091 +2002 96 9 -2 5.97 0 474.29 309.95 46295 +2002 97 10 -3 6.43 0 439.29 367.07 46499 +2002 98 12 -3 7.88 0 652.86 312.4 46702 +2002 99 10 3 8.07 0 611.43 191.47 46905 +2002 100 4 4 4 0.26 97.86 30.33 47107 +2002 101 7 3 5.9 0.04 51.43 58.44 47309 +2002 102 7 5 6.45 1.67 44.29 35.88 47510 +2002 103 12 6 10.35 0.44 48.57 106.97 47710 +2002 104 15 8 13.07 0.09 229.29 135.96 47910 +2002 105 9 7 8.45 0.02 292.14 113.57 48108 +2002 106 13 6 11.07 0 455 198.52 48306 +2002 107 14 6 11.8 0.43 287.86 169.32 48504 +2002 108 13 7 11.35 0.31 341.45 105.51 48700 +2002 109 14 8 12.35 0.02 315.71 265.97 48895 +2002 110 12 9 11.18 0.29 210.71 172.07 49089 +2002 111 18 7 14.98 0 491.43 372.6 49282 +2002 112 19 9 16.25 0 601.43 317.06 49475 +2002 113 19 7 15.7 0.69 875 383.1 49666 +2002 114 16 9 14.07 0.21 300 195.51 49855 +2002 115 17 5 13.7 0 720 403.51 50044 +2002 116 21 7 17.15 0.23 780.71 332.07 50231 +2002 117 11 10 10.73 1.23 200.71 82.83 50417 +2002 118 17 2 12.88 0 673.57 462.69 50601 +2002 119 20 6 16.15 0.29 1015 414.29 50784 +2002 120 18 8 15.25 0 860.71 345.45 50966 +2002 121 24 6 19.05 0 1153.57 463.89 51145 +2002 122 24 12 20.7 0 1494.29 463.64 51324 +2002 123 25 11 21.15 0 1700 393.73 51500 +2002 124 26 11 21.88 0.09 1696.43 389.5 51674 +2002 125 20 11 17.52 0.02 374.67 230.42 51847 +2002 126 21 9 17.7 0 584.67 376.21 52018 +2002 127 22 7 17.88 0 786.67 366.15 52187 +2002 128 23 8 18.88 0 1150.67 414.69 52353 +2002 129 18 10 15.8 0 795.33 269.29 52518 +2002 130 23 11 19.7 0 926 390.72 52680 +2002 131 24 10 20.15 0 989.33 411.14 52840 +2002 132 25 9 20.6 0.65 941.33 390.41 52998 +2002 133 23 12 19.98 0 648 340.95 53153 +2002 134 24 9 19.88 0.76 648 384.58 53306 +2002 135 24 10 20.15 0 1176 465.72 53456 +2002 136 25 9 20.6 0 1128.67 465.28 53603 +2002 137 27 11 22.6 0 1322.67 462.47 53748 +2002 138 27 13 23.15 0 1336.92 439.6 53889 +2002 139 21 13 18.8 0 672.07 302.79 54028 +2002 140 20 13 18.07 0 664 384.58 54164 +2002 141 22 11 18.98 0 772.67 336.93 54297 +2002 142 24 12 20.7 0 765.63 344.87 54426 +2002 143 26 15 22.98 0 1286.88 403.93 54552 +2002 144 26 15 22.98 0.07 1086.25 332.37 54675 +2002 145 23 13 20.25 1.67 1075 327.32 54795 +2002 146 17 13 15.9 0 280.63 147.41 54911 +2002 147 23 12 19.98 0.17 588.75 319.25 55023 +2002 148 21 11 18.25 0.01 513.75 276.98 55132 +2002 149 23 12 19.98 0 1220.63 388.84 55237 +2002 150 23 10 19.43 0 1366.88 510.84 55339 +2002 151 24 9 19.88 0 1365.62 434.72 55436 +2002 152 23 11 19.7 0 1093.75 457.77 55530 +2002 153 21 12 18.52 0 1036.88 421.3 55619 +2002 154 24 7 19.32 0 1191.88 421.9 55705 +2002 155 26 11 21.88 0 1476.25 473.88 55786 +2002 156 23 14 20.52 0.04 708.12 237.84 55863 +2002 157 24 16 21.8 0.18 710 298.55 55936 +2002 158 17 12 15.63 0.32 456.88 201.48 56004 +2002 159 24 13 20.98 0 713.13 284.43 56068 +2002 160 21 12 18.52 0.45 492.5 222 56128 +2002 161 19 13 17.35 0.57 231.25 113.49 56183 +2002 162 25 12 21.43 0 1323.12 505.99 56234 +2002 163 25 9 20.6 0 1313.12 478.97 56280 +2002 164 28 12 23.6 0 1492.5 471.26 56321 +2002 165 31 15 26.6 0 1777.09 474.61 56358 +2002 166 32 16 27.6 0 1874.54 469.96 56390 +2002 167 31 16 26.88 0 1720.98 460.12 56418 +2002 168 29 15 25.15 0 1490.67 452.15 56440 +2002 169 32 17 27.88 0 1814.9 452.1 56458 +2002 170 32 17 27.88 0 2066.88 482.92 56472 +2002 171 32 17 27.88 0 2113.75 499.01 56480 +2002 172 33 17 28.6 0 2115.63 471.77 56484 +2002 173 33 20 29.43 0 1776.92 574.43 56482 +2002 174 34 18 29.6 0 2481.25 470.59 56476 +2002 175 33 19 29.15 0.35 1893.75 426.99 56466 +2002 176 23 15 20.8 0.09 1066.25 245.84 56450 +2002 177 26 11 21.88 0 1572.5 515.91 56430 +2002 178 28 12 23.6 0 1643.13 514.41 56405 +2002 179 23 15 20.8 1.72 379.37 114.93 56375 +2002 180 23 9 19.15 0 1073.75 338.22 56341 +2002 181 23 10 19.43 0 1169.38 475.65 56301 +2002 182 27 11 22.6 0 1433.75 486.46 56258 +2002 183 29 16 25.43 0 1594.38 412.7 56209 +2002 184 30 17 26.43 0 1560 410.77 56156 +2002 185 21 18 20.18 1.53 636.88 180.54 56099 +2002 186 24 9 19.88 0 1217.5 495.69 56037 +2002 187 28 11 23.32 0.22 1368.75 457.07 55971 +2002 188 26 15 22.98 0.02 863.75 275.76 55900 +2002 189 29 13 24.6 0 1677.5 487.02 55825 +2002 190 31 14 26.32 0 1727.5 440.24 55746 +2002 191 32 17 27.88 0 1868.75 418.18 55663 +2002 192 30 19 26.98 0 1760 480.75 55575 +2002 193 29 15 25.15 0 1816.25 390.76 55484 +2002 194 31 18 27.43 0 1311.87 342.56 55388 +2002 195 29 16 25.43 1.44 1181.25 451.6 55289 +2002 196 29 17 25.7 1.74 898.75 334.42 55186 +2002 197 28 19 25.52 0 876.88 315.83 55079 +2002 198 27 15 23.7 0 1184.37 385.12 54968 +2002 199 24 16 21.8 0.69 580 142.24 54854 +2002 200 25 15 22.25 0 1052.5 344.37 54736 +2002 201 28 14 24.15 0 1435.63 420.31 54615 +2002 202 31 13 26.05 0.12 1519.38 464.22 54490 +2002 203 25 15 22.25 0.35 500.62 234.65 54362 +2002 204 26 12 22.15 0 1095 468.66 54231 +2002 205 29 14 24.88 0.87 886.25 339.63 54097 +2002 206 24 16 21.8 0 821.25 371.79 53960 +2002 207 23 11 19.7 0 1028.75 329.66 53819 +2002 208 26 14 22.7 0 1467.5 470.2 53676 +2002 209 28 15 24.43 0 1310 333.69 53530 +2002 210 31 17 27.15 0.01 1187.14 284.87 53382 +2002 211 31 16 26.88 0.44 1619.29 402.31 53230 +2002 212 24 17 22.07 0.01 566.43 239.26 53076 +2002 213 27 16 23.98 1.1 395 236.82 52920 +2002 214 28 16 24.7 0.39 1000 333.12 52761 +2002 215 29 17 25.7 0 1412.86 389.12 52600 +2002 216 26 17 23.52 1.38 705.71 293.32 52437 +2002 217 28 16 24.7 0 1167.86 381.38 52271 +2002 218 23 17 21.35 0.95 436.43 148.42 52103 +2002 219 23 16 21.07 0.85 267.14 127.68 51934 +2002 220 24 15 21.52 0 635.71 299 51762 +2002 221 26 13 22.43 0 927.14 380.27 51588 +2002 222 25 14 21.98 0 807.86 409.56 51413 +2002 223 19 16 18.18 1.91 177.86 89.33 51235 +2002 224 20 13 18.07 0.33 412.14 159.62 51057 +2002 225 24 14 21.25 0.1 910.71 200.9 50876 +2002 226 23 14 20.52 0 753.57 166.36 50694 +2002 227 24 15 21.52 0.03 946.43 314.58 50510 +2002 228 26 16 23.25 0 909.29 350.52 50325 +2002 229 28 16 24.7 0 1140.71 407.89 50138 +2002 230 27 15 23.7 0.02 1014.29 346.09 49951 +2002 231 28 15 24.43 0 1200 351.98 49761 +2002 232 27 15 23.7 0 985 349.52 49571 +2002 233 23 14 20.52 1.01 558.57 270.22 49380 +2002 234 23 15 20.8 0.06 431.43 249.61 49187 +2002 235 26 14 22.7 0 835.71 307.28 48993 +2002 236 28 14 24.15 0 944.29 407.58 48798 +2002 237 28 14 24.15 0 1152.14 393.74 48603 +2002 238 29 15 25.15 0 1272.14 383.8 48406 +2002 239 24 15 21.52 0 491.43 250.49 48208 +2002 240 25 15 22.25 0.54 515.71 247.65 48010 +2002 241 24 15 21.52 0 709.29 239.35 47811 +2002 242 28 14 24.15 0 1117.14 386.44 47611 +2002 243 28 14 24.15 0.01 1324.29 368.38 47410 +2002 244 25 15 22.25 0.1 719.29 237.62 47209 +2002 245 23 14 20.52 0 902.31 312.77 47007 +2002 246 25 12 21.43 0 1055.38 376.73 46805 +2002 247 27 12 22.88 0 1004.62 339.38 46601 +2002 248 26 12 22.15 1.05 762.31 284.95 46398 +2002 249 25 14 21.98 0 905.38 365.45 46194 +2002 250 25 11 21.15 0 912.31 317.42 45989 +2002 251 25 12 21.43 0.87 1116.15 339.74 45784 +2002 252 26 13 22.43 0 965.38 358.28 45579 +2002 253 26 12 22.15 1.87 496.92 221.89 45373 +2002 254 22 13 19.52 0 664.62 233.99 45167 +2002 255 18 10 15.8 0 909.23 362.46 44961 +2002 256 19 4 14.88 0 812.5 291.16 44755 +2002 257 21 6 16.88 0 999.17 362.51 44548 +2002 258 17 9 14.8 0.51 526.67 142.35 44341 +2002 259 18 7 14.98 0 736.67 291.19 44134 +2002 260 21 6 16.88 0 845.83 294.88 43927 +2002 261 23 4 17.77 0 1040.83 379.96 43719 +2002 262 23 8 18.88 0.02 764.17 336.2 43512 +2002 263 22 14 19.8 0.28 437.5 231.75 43304 +2002 264 20 11 17.52 0.53 704.17 267.06 43097 +2002 265 13 11 12.45 0.61 104.17 83.15 42890 +2002 266 13 10 12.18 1.48 115 89.48 42682 +2002 267 9 9 9 0.09 55.83 41.99 42475 +2002 268 9 6 8.18 0.3 114.17 80.57 42268 +2002 269 14 4 11.25 0 405 252.5 42060 +2002 270 17 7 14.25 0 493.33 207.18 41854 +2002 271 11 4 9.07 0.01 349.17 99.13 41647 +2002 272 15 8 13.07 0 660.83 345.88 41440 +2002 273 17 3 13.15 0 618.33 349.05 41234 +2002 274 19 3 14.6 0 626.67 330.39 41028 +2002 275 18 4 14.15 0 640.91 278.26 40822 +2002 276 18 6 14.7 0 523.64 278.93 40617 +2002 277 21 9 17.7 0.42 401.82 159.37 40412 +2002 278 19 8 15.98 0 696.36 300.34 40208 +2002 279 14 5 11.53 0.07 377.27 159.11 40003 +2002 280 13 7 11.35 0 562.73 267.16 39800 +2002 281 17 0 12.32 0 643.64 337.17 39597 +2002 282 9 2 7.08 0 222.73 79.18 39394 +2002 283 10 7 9.18 0.92 149.09 72.38 39192 +2002 284 10 9 9.72 1.78 30 35.46 38991 +2002 285 7 7 7 1.73 51.82 36.46 38790 +2002 286 8 3 6.63 0 170 137.79 38590 +2002 287 14 6 11.8 0 311.82 231.87 38391 +2002 288 17 6 13.98 0 311.82 218.26 38193 +2002 289 21 7 17.15 0 421.82 218.84 37995 +2002 290 20 16 18.9 2.35 901.82 178.84 37799 +2002 291 12 9 11.18 0.6 129.09 130.64 37603 +2002 292 13 4 10.53 0.08 228.18 215.27 37408 +2002 293 14 2 10.7 0 447.27 255.45 37214 +2002 294 17 2 12.88 0 507.27 192.09 37022 +2002 295 18 12 16.35 0.1 410 125.89 36830 +2002 296 22 11 18.98 0.65 846.36 258.13 36640 +2002 297 14 8 12.35 0 447.27 210.08 36451 +2002 298 15 3 11.7 0.02 350.91 257.06 36263 +2002 299 22 10 18.7 0 925 257.15 36076 +2002 300 16 5 12.98 0 454 160.86 35891 +2002 301 15 9 13.35 0 1029 277.23 35707 +2002 302 15 3 11.7 0 763 242.12 35525 +2002 303 17 3 13.15 0 428 63.75 35345 +2002 304 7 6 6.72 0.13 59 39.89 35166 +2002 305 11 6 9.63 0.01 168 119.35 34988 +2002 306 11 7 9.9 0.02 70 54.54 34813 +2002 307 7 5 6.45 0.46 179 71.97 34639 +2002 308 7 5 6.45 0.51 34 43.47 34468 +2002 309 4 2 3.45 0.04 188.89 108.27 34298 +2002 310 3 -2 1.63 0 235.56 125.2 34130 +2002 311 4 -1 2.63 0.02 63.33 58.6 33964 +2002 312 7 -2 4.53 0 188.89 89.19 33801 +2002 313 7 -1 4.8 0.02 217.78 106.06 33640 +2002 314 11 1 8.25 0 465.56 236.91 33481 +2002 315 14 -1 9.88 0 320 80.78 33325 +2002 316 15 4 11.98 0 557.78 205.91 33171 +2002 317 14 4 11.25 0 241.11 124.42 33019 +2002 318 18 11 16.07 0 673.33 92.88 32871 +2002 319 22 11 18.98 0 1120 166.82 32725 +2002 320 21 13 18.8 0.08 1054.44 87.75 32582 +2002 321 18 12 16.35 0.35 716.67 136.6 32441 +2002 322 14 11 13.18 0.01 200 118.76 32304 +2002 323 15 7 12.8 0.04 437.78 176.94 32170 +2002 324 13 4 10.53 0 327.78 185.5 32039 +2002 325 15 2 11.43 0 448.89 166.09 31911 +2002 326 11 8 10.18 1.24 137.78 54.64 31786 +2002 327 15 5 12.25 0 304.44 165.11 31665 +2002 328 14 2 10.7 0 381.11 150.53 31547 +2002 329 16 5 12.98 0 395.56 120.28 31433 +2002 330 15 8 13.07 0 301.11 111.17 31322 +2002 331 8 5 7.17 0 57.78 81.82 31215 +2002 332 8 7 7.72 0.01 30 39.96 31112 +2002 333 7 4 6.17 0.58 22.22 40.73 31012 +2002 334 10 6 8.9 0 85.56 83.32 30917 +2002 335 8 2 6.35 0.04 76.67 90.75 30825 +2002 336 4 1 3.17 0.89 23.33 15.48 30738 +2002 337 5 1 3.9 0.4 22.22 21.07 30654 +2002 338 6 5 5.72 0.95 20 12.67 30575 +2002 339 6 5 5.72 1.37 28.89 15.21 30500 +2002 340 2 2 2 0.46 38.89 19.55 30430 +2002 341 1 1 1 0.3 25.56 12.81 30363 +2002 342 -2 -2 -2 0 104.44 36.39 30301 +2002 343 -5 -6 -5.28 0.02 84.44 76.38 30244 +2002 344 -3 -8 -4.38 0 134.44 164.75 30191 +2002 345 -4 -7 -4.83 0 97.78 80.7 30143 +2002 346 -4 -5 -4.28 0.05 55.56 47.24 30099 +2002 347 -3 -5 -3.55 0 45 32.04 30060 +2002 348 -3 -4 -3.27 0.03 27.5 32.94 30025 +2002 349 -2 -3 -2.27 0.35 20 17.83 29995 +2002 350 -2 -3 -2.27 0 20 45.03 29970 +2002 351 -1 -3 -1.55 0.1 18.75 66.17 29950 +2002 352 2 -2 0.9 0.01 73.75 80.92 29934 +2002 353 2 -5 0.07 0.01 192.5 108.7 29924 +2002 354 1 -5 -0.65 0 165 183.67 29918 +2002 355 6 -5 2.98 0 137.5 110.95 29916 +2002 356 2 -2 0.9 0 48.75 62.01 29920 +2002 357 2 -1 1.18 0.02 28.75 54.81 29928 +2002 358 -1 -1 -1 0.02 177.5 34.8 29941 +2002 359 -3 -6 -3.83 0 220 48.17 29959 +2002 360 -3 -5 -3.55 0 43.75 62.09 29982 +2002 361 0 -3 -0.82 0 21.25 42.27 30009 +2002 362 10 -1 6.97 0.46 275 49.73 30042 +2002 363 6 1 4.63 0 20 76.4 30078 +2002 364 10 2 7.8 0.01 197.5 69.22 30120 +2002 365 8 5 7.17 0.53 56.25 25.68 30166 +2003 1 -1 -6 -2.38 0 172.5 123.12 30217 +2003 2 4 -4 1.8 0 52.5 77.75 30272 +2003 3 15 1 11.15 0 395 104.79 30331 +2003 4 9 1 6.8 0.43 205 94.3 30396 +2003 5 0 0 0 0.11 122.5 60.1 30464 +2003 6 -3 -6 -3.83 0.81 103.75 68.63 30537 +2003 7 -7 -7 -7 0.7 30 33.51 30614 +2003 8 -2 -12 -4.75 0.14 113.75 187.97 30695 +2003 9 -9 -14 -10.38 0.69 36.25 62.64 30781 +2003 10 -6 -11 -7.38 0.21 86.25 94.39 30870 +2003 11 -3 -7 -4.1 0 177.78 180.14 30964 +2003 12 -4 -17 -7.57 0 101.11 241.97 31061 +2003 13 -1 -13 -4.3 0 140 170.96 31162 +2003 14 3 -5 0.8 0 185.56 88.63 31268 +2003 15 9 -2 5.97 0 220 204.75 31376 +2003 16 7 -7 3.15 0 68.89 167.07 31489 +2003 17 6 -5 2.98 0 182.22 215.29 31605 +2003 18 -1 -6 -2.38 0 20 89.75 31724 +2003 19 -1 -7 -2.65 0 22 93.48 31847 +2003 20 0 -8 -2.2 0 20 97.02 31974 +2003 21 -1 -7 -2.65 0.35 20 82.79 32103 +2003 22 1 -1 0.45 0.44 21 45.36 32236 +2003 23 10 -1 6.97 0 10 169.56 32372 +2003 24 5 -3 2.8 0 94 146.12 32510 +2003 25 4 1 3.17 0 107 91.03 32652 +2003 26 4 -2 2.35 0 66 104.04 32797 +2003 27 3 -3 1.35 0.03 154 145.1 32944 +2003 28 6 -1 4.08 0 152 79.7 33094 +2003 29 6 -2 3.8 0 212 159.37 33247 +2003 30 6 -4 3.25 0 140 217.51 33402 +2003 31 0 -2 -0.55 0.23 27 56.45 33559 +2003 32 2 -3 0.63 0 164 206.07 33719 +2003 33 0 -11 -3.02 0 151 261.66 33882 +2003 34 4 -11 -0.13 0.14 257 163.62 34046 +2003 35 0 -4 -1.1 0.8 23 33.25 34213 +2003 36 5 -2 3.08 0 288 149.63 34382 +2003 37 3 -2 1.63 0 327 195.11 34552 +2003 38 5 -6 1.98 0 254 264.14 34725 +2003 39 -1 -7 -2.65 0.04 74 128.07 34900 +2003 40 1 -8 -1.48 0 138 192.7 35076 +2003 41 1 -3 -0.1 0 112 109.05 35254 +2003 42 -2 -3 -2.27 0.09 75 86.79 35434 +2003 43 0 -6 -1.65 0 111 304.79 35615 +2003 44 -1 -11 -3.75 0 154 290 35798 +2003 45 2 -12 -1.85 0 180 308.94 35983 +2003 46 2 -9 -1.02 0.03 211 252.59 36169 +2003 47 -1 -3 -1.55 0 72 117.6 36356 +2003 48 1 -6 -0.93 0 142 271.3 36544 +2003 49 1 -12 -2.57 0 174 302.06 36734 +2003 50 1 -7 -1.2 0 142 129.37 36925 +2003 51 1 -9 -1.75 0 107 129.05 37117 +2003 52 4 -7 0.98 0 130 150.37 37310 +2003 53 4 -1 2.63 0 308.18 216.12 37505 +2003 54 5 -8 1.43 0 49.09 221.45 37700 +2003 55 10 -11 4.23 0 163.64 277.19 37896 +2003 56 7 -6 3.43 0 307.27 348.32 38093 +2003 57 5 -9 1.15 0 102.73 314.18 38291 +2003 58 10 -6 5.6 0 360 338.5 38490 +2003 59 11 -5 6.6 0 280 266.92 38689 +2003 60 14 -2 9.6 0 549.09 301.17 38890 +2003 61 11 -2 7.43 0.13 405 248.79 39091 +2003 62 6 2 4.9 0.03 75.83 107.78 39292 +2003 63 11 1 8.25 0 171.67 322.86 39495 +2003 64 9 0 6.53 0 125.83 135.28 39697 +2003 65 2 0 1.45 0 136.67 89.9 39901 +2003 66 3 -1 1.9 0 189.17 83.01 40105 +2003 67 10 -2 6.7 0 269.17 298.47 40309 +2003 68 13 0 9.43 0.02 518.33 244.5 40514 +2003 69 16 4 12.7 0 614.17 284.17 40719 +2003 70 18 1 13.32 0 707.5 243.27 40924 +2003 71 18 8 15.25 0.03 662.5 144.7 41130 +2003 72 8 3 6.63 0 429.17 283.74 41336 +2003 73 4 0 2.9 0 190 99.71 41543 +2003 74 5 0 3.63 0 230 262.64 41749 +2003 75 5 1 3.9 0 255 169.72 41956 +2003 76 13 -4 8.32 0 485.83 367.57 42163 +2003 77 10 2 7.8 0 403.33 313.79 42370 +2003 78 14 3 10.98 0 602.5 262.8 42578 +2003 79 12 1 8.97 0 376.67 320.01 42785 +2003 80 8 1 6.08 0 537.5 401.32 42992 +2003 81 5 -6 1.98 0 414.17 401.78 43200 +2003 82 11 -6 6.33 0 640 402.24 43407 +2003 83 18 -3 12.23 0 1169.17 403.9 43615 +2003 84 20 1 14.78 0 1296.67 383.94 43822 +2003 85 20 2 15.05 0 1081.67 340.17 44029 +2003 86 20 2 15.05 0 1316.67 366.36 44236 +2003 87 21 3 16.05 0 1213.33 365.08 44443 +2003 88 20 5 15.88 0 1004.17 281.91 44650 +2003 89 21 5 16.6 0 992.5 284.17 44857 +2003 90 15 9 13.35 0.14 535 193.51 45063 +2003 91 14 -1 9.88 0 805.83 441.61 45270 +2003 92 16 0 11.6 0.85 759.23 233.08 45475 +2003 93 9 4 7.63 0 350.77 89.04 45681 +2003 94 11 3 8.8 0 453.08 301.64 45886 +2003 95 13 -2 8.88 0.09 557.69 259.62 46091 +2003 96 6 -2 3.8 0.02 317.14 374.22 46295 +2003 97 2 -5 0.07 0 267.86 205.69 46499 +2003 98 6 -2 3.8 0 426.43 342.32 46702 +2003 99 10 -5 5.88 0 448.57 250.29 46905 +2003 100 12 -2 8.15 0.8 601.43 180.07 47107 +2003 101 5 1 3.9 0.36 59.29 70.72 47309 +2003 102 6 -1 4.08 0.6 91.43 105.53 47510 +2003 103 16 5 12.98 0 678.57 430.51 47710 +2003 104 15 1 11.15 0 557.14 260.8 47910 +2003 105 16 7 13.53 0 647.14 199.61 48108 +2003 106 19 5 15.15 0 947.86 434.66 48306 +2003 107 17 4 13.43 0 795.71 277.79 48504 +2003 108 17 6 13.98 0 834.29 349.82 48700 +2003 109 16 3 12.43 0 616.43 392.36 48895 +2003 110 19 3 14.6 0 887.86 419.93 49089 +2003 111 19 4 14.88 0 1100 435.1 49282 +2003 112 20 3 15.32 0 1262.14 410.89 49475 +2003 113 19 6 15.43 0.01 781.43 199.99 49666 +2003 114 18 4 14.15 0 771.43 372.45 49855 +2003 115 20 4 15.6 0 1016.43 437.99 50044 +2003 116 24 7 19.32 0.78 1484.29 424.98 50231 +2003 117 15 11 13.9 0.28 300.71 172.71 50417 +2003 118 22 5 17.32 0 815 422.8 50601 +2003 119 25 10 20.88 0 1200.71 417.29 50784 +2003 120 22 10 18.7 0 1122.86 272.22 50966 +2003 121 21 15 19.35 0 962.14 345.91 51145 +2003 122 24 11 20.43 0 1290 373.59 51324 +2003 123 20 17 19.18 0 790 194.27 51500 +2003 124 22 4 17.05 0 1271.43 478.58 51674 +2003 125 25 7 20.05 0 1648 481.04 51847 +2003 126 30 10 24.5 0 2297.33 466.49 52018 +2003 127 30 11 24.77 0 2202 472.81 52187 +2003 128 29 11 24.05 0 1539.33 405.02 52353 +2003 129 29 17 25.7 0 1991 394.25 52518 +2003 130 25 12 21.43 1.1 1154.67 381.41 52680 +2003 131 25 14 21.98 0 676.67 364.71 52840 +2003 132 28 12 23.6 0.45 986.67 433.77 52998 +2003 133 26 13 22.43 0 1194.67 412.17 53153 +2003 134 13 9 11.9 0 567.33 175.59 53306 +2003 135 17 7 14.25 0 852 380.13 53456 +2003 136 18 2 13.6 0 860.67 448.1 53603 +2003 137 21 4 16.32 0 1220 463.17 53748 +2003 138 24 6 19.05 0.01 1232 462.99 53889 +2003 139 27 10 22.32 0 1460.67 409.86 54028 +2003 140 17 13 15.9 0.87 478 82.18 54164 +2003 141 15 9 13.35 0.14 559.33 164.89 54297 +2003 142 18 8 15.25 0 723.13 242.95 54426 +2003 143 23 9 19.15 0 1234.38 486.53 54552 +2003 144 25 9 20.6 0 1268.13 455.91 54675 +2003 145 28 12 23.6 0 1513.75 436.64 54795 +2003 146 28 14 24.15 0.07 1058.13 341.85 54911 +2003 147 25 13 21.7 0 701.88 311.99 55023 +2003 148 27 14 23.43 0 903.13 398.82 55132 +2003 149 26 16 23.25 0 935.63 446.58 55237 +2003 150 27 13 23.15 0 1256.25 484.83 55339 +2003 151 28 13 23.88 0.55 1504.38 451.95 55436 +2003 152 25 15 22.25 1.42 551.88 321.43 55530 +2003 153 25 13 21.7 0 1097.86 385.03 55619 +2003 154 25 13 21.7 0 1097.86 388.85 55705 +2003 155 29 14 24.88 0 1545.43 439.67 55786 +2003 156 31 15 26.6 0 1777.09 450.87 55863 +2003 157 31 15 26.6 0 1777.09 452.4 55936 +2003 158 29 15 25.15 0 1490.67 427.15 56004 +2003 159 31 17 27.15 0 1659.16 417.7 56068 +2003 160 30 17 26.43 0.04 1509.09 300.88 56128 +2003 161 31 18 27.43 0 1591.34 395.69 56183 +2003 162 34 19 29.88 1 2015.8 316.56 56234 +2003 163 32 17 27.88 0 2059.69 452.44 56280 +2003 164 32 20 28.7 0.15 2166.88 416.02 56321 +2003 165 29 18 25.98 0 1376.87 408.62 56358 +2003 166 26 16 23.25 0.01 491.88 299.25 56390 +2003 167 25 15 22.25 0.06 779.38 358.7 56418 +2003 168 27 15 23.7 0 1516.87 372.51 56440 +2003 169 19 16 18.18 0.72 475.62 122.92 56458 +2003 170 25 14 21.98 0 1189.38 384.74 56472 +2003 171 28 14 24.15 0.05 1101.88 299.55 56480 +2003 172 25 12 21.43 0 1299.37 462.07 56484 +2003 173 27 12 22.88 0 1565.63 470.68 56482 +2003 174 33 14 27.77 0.43 1996.25 448.95 56476 +2003 175 31 17 27.15 0.08 1745 319.78 56466 +2003 176 31 16 26.88 0 1723.13 401.02 56450 +2003 177 27 13 23.15 0 1461.25 432.23 56430 +2003 178 25 16 22.52 0 1313.75 378.66 56405 +2003 179 26 16.9 23.5 0 1646.87 350.7 56375 +2003 180 24 17 22.07 0 1110 249.24 56341 +2003 181 32 14 27.05 0 1709.37 461.78 56301 +2003 182 32 18 28.15 0.29 2146.25 458.36 56258 +2003 183 24 13 20.98 0.01 1005 313.53 56209 +2003 184 25 13 21.7 1.02 657.5 283.54 56156 +2003 185 21 13 18.8 0.5 437.5 225.34 56099 +2003 186 24 13 20.98 0 1248.75 356.23 56037 +2003 187 26 14 22.7 0.02 1253.75 293.57 55971 +2003 188 26 11 21.88 0 1293.13 382.91 55900 +2003 189 25 12 21.43 0 1500.63 404.13 55825 +2003 190 26 13 22.43 0.01 1413.12 289.55 55746 +2003 191 25 13 21.7 0.36 1370.63 350.56 55663 +2003 192 27 14 23.43 0 1547.5 493.04 55575 +2003 193 30 13 25.32 0.23 1585 347.52 55484 +2003 194 25 15 22.25 0.02 1282.5 286.59 55388 +2003 195 25 11 21.15 0 1403.75 470.89 55289 +2003 196 28 12 23.6 0 1851.25 460.98 55186 +2003 197 31 15 26.6 0 1887.5 437.22 55079 +2003 198 31 19 27.7 0.96 1788.13 421.89 54968 +2003 199 29 16 25.43 0 1467.5 486.74 54854 +2003 200 29 14 24.88 0 1526.25 492.9 54736 +2003 201 31 14 26.32 0 1905 468.09 54615 +2003 202 34 16 29.05 0 2139.38 446.81 54490 +2003 203 34 19 29.88 1.56 2306.25 432.38 54362 +2003 204 25 19 23.35 0.07 482.5 146.67 54231 +2003 205 29 14 24.88 1.34 1468.75 481.31 54097 +2003 206 25 15 22.25 0 725 324.9 53960 +2003 207 30 14 25.6 0 1450 468.35 53819 +2003 208 32 16 27.6 0 1996.25 459.74 53676 +2003 209 29 19 26.25 0.48 1628.67 432.11 53530 +2003 210 24 16 21.8 0 1002.86 315.75 53382 +2003 211 24 14 21.25 0.03 944.29 151.9 53230 +2003 212 23 16 21.07 0.54 456.43 141.31 53076 +2003 213 28 17 24.98 0.07 951.43 387.06 52920 +2003 214 30 16 26.15 0 1585 425.22 52761 +2003 215 33 17 28.6 0 2283.57 426.78 52600 +2003 216 34 19 29.88 0.63 2056.43 367.44 52437 +2003 217 33 20 29.43 0 2125 399.96 52271 +2003 218 31 19 27.7 0 1913.57 344.41 52103 +2003 219 30 16 26.15 0 2167.14 466.27 51934 +2003 220 33 14 27.77 0 2558.57 456.81 51762 +2003 221 32 16 27.6 0 2528.57 421.97 51588 +2003 222 33 15 28.05 0 2557.14 436.46 51413 +2003 223 30 19 26.98 0 2262.86 468.04 51235 +2003 224 33 12 27.23 0 2481.43 454.46 51057 +2003 225 37 17 31.5 0.43 3055 340.84 50876 +2003 226 36 20 31.6 0.37 2799.29 279.88 50694 +2003 227 30 18 26.7 0.06 1227.86 337.03 50510 +2003 228 29 16 25.43 0.2 1145 386.17 50325 +2003 229 32 16 27.6 0.01 1694.29 409.99 50138 +2003 230 36 17 30.77 0.04 2431.43 378.25 49951 +2003 231 31 16 26.88 0 1917.86 300.53 49761 +2003 232 30 16 26.15 0 1905 358.47 49571 +2003 233 31 16 26.88 0 2172.86 368.16 49380 +2003 234 33 16 28.32 0.06 2430 385.88 49187 +2003 235 33 21 29.7 0 2442.86 328.13 48993 +2003 236 31 18 27.43 0 1932.14 401.7 48798 +2003 237 24 17 22.07 0 1298.57 283.57 48603 +2003 238 29 12 24.32 0 1894.29 411.86 48406 +2003 239 32 14 27.05 0 2441.43 353.88 48208 +2003 240 30 16 26.15 0 1887.5 372.42 48010 +2003 241 32 25 30.07 0.3 2116.43 235.55 47811 +2003 242 25 14 21.98 1.74 749.29 228.1 47611 +2003 243 15 14 14.73 2.15 92.14 58.79 47410 +2003 244 21 7 17.15 0.01 899.29 375.02 47209 +2003 245 20 11 17.52 0 684.62 279.2 47007 +2003 246 18 6 14.7 0 857.69 372.88 46805 +2003 247 22 5 17.32 0 1003.85 285 46601 +2003 248 23 7 18.6 0 974.62 451.24 46398 +2003 249 23 9 19.15 0 764.62 240.53 46194 +2003 250 23 10 19.43 0 1305.38 353.82 45989 +2003 251 22 14 19.8 0.02 1326.92 300.14 45784 +2003 252 17 13 15.9 1.6 412.31 125.55 45579 +2003 253 16 13 15.18 0.9 133.85 76.37 45373 +2003 254 23 9 19.15 0.23 554.62 271.18 45167 +2003 255 19 8 15.98 0.1 562.31 260.81 44961 +2003 256 15 11 13.9 0.05 208.33 59.51 44755 +2003 257 19 10 16.52 0 770.83 408.94 44548 +2003 258 21 7 17.15 0 1015 437.21 44341 +2003 259 22 6 17.6 0 1106.67 416.38 44134 +2003 260 25 8 20.32 0 1310 398.67 43927 +2003 261 26 10 21.6 0 1328.33 388.48 43719 +2003 262 26 10 21.6 0 1308.33 384.37 43512 +2003 263 27 11 22.6 0 1405.83 378.13 43304 +2003 264 28 11 23.32 0 1565.83 376.16 43097 +2003 265 28 11 23.32 0 1615.83 368.41 42890 +2003 266 27 15 23.7 0.56 1694.17 368.15 42682 +2003 267 13 11 12.45 0.03 369.17 112.89 42475 +2003 268 17 5 13.7 0 810 393.62 42268 +2003 269 18 3 13.88 0 892.5 366.86 42060 +2003 270 22 5 17.32 0 931.67 339.19 41854 +2003 271 21 6 16.88 0 845 323.29 41647 +2003 272 14 13 13.73 2.41 109.17 36.27 41440 +2003 273 18 6 14.7 0 583.33 305.77 41234 +2003 274 19 7 15.7 0 622.5 313.34 41028 +2003 275 24 10 20.15 0 851.82 319.45 40822 +2003 276 23 12 19.98 0.83 541.82 295.68 40617 +2003 277 21 14 19.07 3.19 285.45 190.73 40412 +2003 278 19 12 17.07 0.13 498.18 240.06 40208 +2003 279 15 6 12.53 0 673.64 213.92 40003 +2003 280 13 2 9.97 0.15 379.09 103.9 39800 +2003 281 14 6 11.8 0.06 480.91 189.95 39597 +2003 282 15 5 12.25 0 577.27 327.59 39394 +2003 283 19 5 15.15 0.03 599.09 219.22 39192 +2003 284 20 7 16.43 0 671.82 310.12 38991 +2003 285 14 7 12.07 0 444.55 160.49 38790 +2003 286 14 7 12.07 0 500 213.17 38590 +2003 287 11 3 8.8 0 398.18 297.94 38391 +2003 288 12 0 8.7 0 351.82 296.42 38193 +2003 289 10 1 7.53 0 333.64 174.49 37995 +2003 290 10 -2 6.7 0 327.73 262.93 37799 +2003 291 10 0 7.25 0 408.02 232.96 37603 +2003 292 9 3 7.35 0 170.91 200.63 37408 +2003 293 14 1 10.43 0.14 220.91 124.95 37214 +2003 294 16 7 13.53 0.36 180 116.43 37022 +2003 295 6 4 5.45 0 263.64 90.1 36830 +2003 296 6 0 4.35 1.81 166.36 109.76 36640 +2003 297 2 0 1.45 0.02 90.91 187.21 36451 +2003 298 4 -5 1.52 0 96.36 240.26 36263 +2003 299 8 -4 4.7 0 251.82 241.5 36076 +2003 300 9 -1 6.25 0 249 144.26 35891 +2003 301 9 -2 5.97 0 351 225.02 35707 +2003 302 8 -2 5.25 0.41 124 116.57 35525 +2003 303 8 3 6.63 0.18 70 105.8 35345 +2003 304 13 1 9.7 0.06 300 215.93 35166 +2003 305 20 10 17.25 0.94 866 145.53 34988 +2003 306 10 8 9.45 0.36 160 87.7 34813 +2003 307 13 3 10.25 0 173 211.32 34639 +2003 308 17 3 13.15 0 450 240.96 34468 +2003 309 12 2 9.25 0 461.56 201.85 34298 +2003 310 6 -1 4.08 0.18 249.58 120.65 34130 +2003 311 6 3 5.17 0.03 125.14 56.33 33964 +2003 312 9 4 7.63 0 232.21 118.68 33801 +2003 313 7 6 6.72 0 47.95 34.27 33640 +2003 314 6 4 5.45 0 86.76 54.76 33481 +2003 315 7 2.7 5.82 0 181.41 108.09 33325 +2003 316 7 1 5.35 0 236.93 142.95 33171 +2003 317 7 -3 4.25 0 337.74 196.75 33019 +2003 318 4 -2 2.35 0 195.92 142.82 32871 +2003 319 9 -2 5.97 0 405.71 199.44 32725 +2003 320 3 -1 1.9 0 132.73 99.93 32582 +2003 321 13 3 10.25 0.27 490.51 138.87 32441 +2003 322 10 2 7.8 0 352.29 163.87 32304 +2003 323 20 3 15.32 0 475.56 188.42 32170 +2003 324 16 5 12.98 0 314.44 191.66 32039 +2003 325 14 0 10.15 0 192.22 177.35 31911 +2003 326 15 1 11.15 0 273.33 176.37 31786 +2003 327 15 10 13.63 0 626.67 161.68 31665 +2003 328 17 10 15.07 0 598.89 162.14 31547 +2003 329 17 11 15.35 0 543.33 172.67 31433 +2003 330 10 8 9.45 0.1 67.78 45.01 31322 +2003 331 10 8 9.45 0.01 202.22 107.86 31215 +2003 332 7 6 6.72 0.16 254.44 49.24 31112 +2003 333 14 5 11.53 0.23 131.11 86.62 31012 +2003 334 9 6 8.18 0 48.89 43.24 30917 +2003 335 5 4 4.72 0 28.89 40.74 30825 +2003 336 5 3 4.45 0 43.33 79.98 30738 +2003 337 3 2 2.73 0.02 16.67 41.78 30654 +2003 338 2 1 1.73 0.03 10 30.76 30575 +2003 339 2 1 1.73 0 62.22 27.62 30500 +2003 340 9 1 6.8 0 42.22 69.89 30430 +2003 341 3 -2 1.63 0 218.89 168.19 30363 +2003 342 2 -6 -0.2 0 177.78 221.19 30301 +2003 343 4 -7 0.98 0 213.33 199.4 30244 +2003 344 2 -6 -0.2 0 113.33 174.1 30191 +2003 345 1 -5 -0.65 0 102.22 98.68 30143 +2003 346 7 -2 4.53 0 127.78 103.31 30099 +2003 347 6 -3 3.52 0.01 221.25 149.34 30060 +2003 348 5 0 3.63 0.28 81.25 75.81 30025 +2003 349 5 -1 3.35 0.26 157.5 112.55 29995 +2003 350 4 -3 2.08 0 167.5 121.86 29970 +2003 351 0 -4 -1.1 0 221.25 36.86 29950 +2003 352 8 -2 5.25 0 286.25 146.56 29934 +2003 353 6 -4 3.25 0 177.5 176.84 29924 +2003 354 10 -5 5.88 0 190 162.45 29918 +2003 355 9 -2 5.97 0.44 310 77.5 29916 +2003 356 3 1 2.45 0.03 36.25 56.81 29920 +2003 357 0 -2 -0.55 0 261.25 160.65 29928 +2003 358 0 -7 -1.93 0 220 167.09 29941 +2003 359 1 -13 -2.85 0 210 188.53 29959 +2003 360 1 -9 -1.75 0 241.25 122.09 29982 +2003 361 2 -9 -1.02 0 90 157.69 30009 +2003 362 8 -5 4.43 0 290 97.92 30042 +2003 363 6 5 5.72 0.23 147.5 34 30078 +2003 364 4 1 3.17 0.49 25 63.9 30120 +2003 365 4 3 3.73 1.36 28.75 17.84 30166 +2004 1 1 0 0.72 0 141.25 79.76 30217 +2004 2 -2 -3 -2.27 0 143.75 44.24 30272 +2004 3 -1 -6 -2.38 0 181.25 89.15 30331 +2004 4 -4 -9 -5.38 0 170 120.66 30396 +2004 5 4 -9 0.43 0.03 123.75 86.66 30464 +2004 6 -2 -13 -5.03 0.05 131.25 176.12 30537 +2004 7 -1 -10 -3.48 0.03 108.75 82.25 30614 +2004 8 6 -6 2.7 0 126.25 130.38 30695 +2004 9 -2 -2 -2 0.1 26.25 35.32 30781 +2004 10 4 -4 1.8 0 20 85.64 30870 +2004 11 5 -4 2.52 0.08 125.56 191.38 30964 +2004 12 7 -1 4.8 0.17 175.56 99.32 31061 +2004 13 8 1 6.08 0 315.56 80.4 31162 +2004 14 13 1 9.7 0 703.33 158.15 31268 +2004 15 5 1 3.9 0 108.89 74.4 31376 +2004 16 6 -3 3.52 0 353.33 173.02 31489 +2004 17 9 4 7.63 1.1 225.56 38.8 31605 +2004 18 1 -2 0.18 0.08 13.33 75.64 31724 +2004 19 2 -2 0.9 0 179 153.49 31847 +2004 20 4 -2 2.35 0 86 77.56 31974 +2004 21 2 -4 0.35 0 267 189.49 32103 +2004 22 -2 -5 -2.83 0 153 178.72 32236 +2004 23 -1 -11 -3.75 0 166 209.36 32372 +2004 24 1 -13 -2.85 0 181 219.9 32510 +2004 25 0 -12 -3.3 0.08 169 149.59 32652 +2004 26 3 -5 0.8 0 134 174.12 32797 +2004 27 -2 -5 -2.83 0.75 45 62.63 32944 +2004 28 -1 -4 -1.83 0 75 200.73 33094 +2004 29 -1 -10 -3.48 0 89 219.4 33247 +2004 30 4 -14 -0.95 0 305 263.97 33402 +2004 31 6 -7 2.43 0 286 223.53 33559 +2004 32 9 -3 5.7 0 356 195.11 33719 +2004 33 11 -4 6.88 0.02 371 137.6 33882 +2004 34 14 3 10.98 0 177 100.56 34046 +2004 35 18 4 14.15 0 421 129.7 34213 +2004 36 23 5 18.05 0 1142 189.22 34382 +2004 37 12 9 11.18 0 683 56.25 34552 +2004 38 14 0 10.15 0 486 198.36 34725 +2004 39 11 4 9.07 0.02 310 263.18 34900 +2004 40 8 1 6.08 0.05 431 219.77 35076 +2004 41 4 -2 2.35 0.02 186 161.34 35254 +2004 42 9 -3 5.7 0.01 208 113.85 35434 +2004 43 -1 -6 -2.38 0.01 175 210.94 35615 +2004 44 -2 -7 -3.38 0.05 83 151.46 35798 +2004 45 6 -3 3.52 0 57 85.71 35983 +2004 46 4 -2 2.35 0.06 230 111.35 36169 +2004 47 5 -1 3.35 0.07 102 106.76 36356 +2004 48 8 -4 4.7 0 267 302.66 36544 +2004 49 8 -4 4.7 0 234 207.41 36734 +2004 50 4 -1 2.63 0 248 221.28 36925 +2004 51 4 -2 2.35 0 195.92 174.69 37117 +2004 52 0 -6 -1.65 0 150.84 177.79 37310 +2004 53 0 -2 -0.55 0.07 31.82 47.93 37505 +2004 54 0 0 0 1.33 10.91 32.02 37700 +2004 55 0 -2 -0.55 0.09 131.82 120.78 37896 +2004 56 2 -5 0.07 0 173.64 328.39 38093 +2004 57 1 -4 -0.38 1.74 29.09 60.82 38291 +2004 58 2 -2 0.9 0.01 95.45 178.07 38490 +2004 59 2 -2 0.9 0.77 172.73 229.5 38689 +2004 60 4 -2 2.35 0 239.09 275.25 38890 +2004 61 1 -9 -1.75 0 155 221.65 39091 +2004 62 3 -8 -0.02 0 251.67 251.19 39292 +2004 63 9 -3 5.7 0 411.67 194.85 39495 +2004 64 4 -3 2.08 0 289.17 352.99 39697 +2004 65 2 -3 0.63 0 224.17 277.88 39901 +2004 66 1 -10 -2.02 0 200 363.42 40105 +2004 67 1 -4 -0.38 1.46 112.5 146.51 40309 +2004 68 -1 -3 -1.55 0.65 22.5 119.36 40514 +2004 69 4 -2 2.35 0 165 182.66 40719 +2004 70 5 -4 2.52 0 273.33 338.08 40924 +2004 71 5 -5 2.25 0 145.83 294.77 41130 +2004 72 6 0 4.35 0 170 210.3 41336 +2004 73 9 -1 6.25 0 253.33 262.39 41543 +2004 74 9 2 7.08 0 236.67 197.54 41749 +2004 75 16 -1 11.32 0 385 361.36 41956 +2004 76 19 1 14.05 0 782.5 339.76 42163 +2004 77 23 5 18.05 0 1080.83 353.4 42370 +2004 78 23 5 18.05 0 1162.5 369.57 42578 +2004 79 24 5 18.77 0 1478.33 327.97 42785 +2004 80 20 7 16.43 0 891.67 229 42992 +2004 81 19 9 16.25 1.4 734.17 284.78 43200 +2004 82 8 5 7.17 0.4 148.33 122.92 43407 +2004 83 4 4 4 2.34 74.17 38.13 43615 +2004 84 6 3 5.17 1.68 95 42.92 43822 +2004 85 5 3 4.45 0.69 82.5 75.88 44029 +2004 86 5 0 3.63 0.06 220.83 284.7 44236 +2004 87 5 -1 3.35 0.01 128.33 154.28 44443 +2004 88 7 0 5.08 0 270 169.25 44650 +2004 89 12 0 8.7 0 456.67 373.28 44857 +2004 90 10 -1 6.97 0 435.83 374.72 45063 +2004 91 13 -1 9.15 0 513.33 377.28 45270 +2004 92 13 1 9.7 0 295.38 184.58 45475 +2004 93 16 7 13.53 0 746.15 291.63 45681 +2004 94 19 4 14.88 0 715.38 362.31 45886 +2004 95 21 8 17.43 0.73 770 337.67 46091 +2004 96 12 9 11.18 0.92 155 52.34 46295 +2004 97 8 4 6.9 1.48 132.14 138.32 46499 +2004 98 9 4 7.63 0.06 187.14 163.47 46702 +2004 99 14 -1 9.88 0 640.71 407.99 46905 +2004 100 11 0 7.97 0 415.71 222.82 47107 +2004 101 8 4 6.9 0.07 210.71 83.94 47309 +2004 102 15 1 11.15 0 387.14 320 47510 +2004 103 11 2 8.53 0.16 427.14 191.18 47710 +2004 104 10 5 8.63 0.35 434.29 83.41 47910 +2004 105 11 6 9.63 0.02 377.14 129.24 48108 +2004 106 12 2 9.25 0 447.14 267.7 48306 +2004 107 17 5 13.7 0.12 543.57 366.04 48504 +2004 108 14 8 12.35 0.03 151.43 110.03 48700 +2004 109 18 9 15.53 0.03 354.29 223.12 48895 +2004 110 18 9 15.53 1.25 540.71 312.67 49089 +2004 111 9 7 8.45 0.47 102.86 47.43 49282 +2004 112 19 8 15.98 0 743.57 397.69 49475 +2004 113 22 6 17.6 0 1040.71 399.68 49666 +2004 114 22 10 18.7 0.52 1115.71 444.35 49855 +2004 115 13 11 12.45 0.1 369.29 145.88 50044 +2004 116 13 5 10.8 0 420.71 264.1 50231 +2004 117 17 6 13.98 0 617.14 305.51 50417 +2004 118 17 4 13.43 0 620.71 470.82 50601 +2004 119 20 5 15.88 0 945.71 484.32 50784 +2004 120 24 8 19.6 0 1147.86 467.36 50966 +2004 121 20 9 16.98 0 886.43 290.18 51145 +2004 122 21 10 17.98 0 810.71 339.68 51324 +2004 123 20 8 16.7 0.12 585.71 325.03 51500 +2004 124 21 6 16.88 0 866.43 418.33 51674 +2004 125 18 9 15.53 0.16 590 247.13 51847 +2004 126 19 8 15.98 1.13 550.67 322.61 52018 +2004 127 16 10 14.35 0.35 366 248.42 52187 +2004 128 15 4 11.98 0.69 288.67 222.49 52353 +2004 129 12 5 10.07 0.26 126.67 157.51 52518 +2004 130 16 3 12.43 0.04 490.67 408.04 52680 +2004 131 16 7 13.53 0 568 354.7 52840 +2004 132 17 6 13.98 0.22 786 383.12 52998 +2004 133 22 7 17.88 0.1 944 443.93 53153 +2004 134 15 9 13.35 0.21 241.33 144.49 53306 +2004 135 16 8 13.8 0 629.33 437.03 53456 +2004 136 19 3 14.6 1.16 858 426.97 53603 +2004 137 15 8 13.07 0.01 463.33 374.83 53748 +2004 138 12 5 10.07 0 410 181.52 53889 +2004 139 21 5 16.6 0 803.33 415.54 54028 +2004 140 24 9 19.88 0 813.33 348.2 54164 +2004 141 26 10 21.6 0 1480 472.21 54297 +2004 142 26 10 21.6 0 813.75 385.45 54426 +2004 143 12 12 12 0.6 177.5 173.88 54552 +2004 144 14 6 11.8 0.09 400.63 279.44 54675 +2004 145 16 1 11.88 0 796.87 427.48 54795 +2004 146 18 5 14.43 0 820.63 396.95 54911 +2004 147 22 5 17.32 0 1283.75 496.3 55023 +2004 148 20 11 17.52 0.4 610.63 366.92 55132 +2004 149 12 10 11.45 0.25 156.25 105.15 55237 +2004 150 15 8 13.07 0 375.62 192.11 55339 +2004 151 21 8 17.43 0 935 491.55 55436 +2004 152 24 7 19.32 0 1268.13 486.33 55530 +2004 153 20 11 17.52 0.13 525.63 303.82 55619 +2004 154 17 13 15.9 1.96 186.25 160.59 55705 +2004 155 19 8 15.98 0.17 300.63 222.6 55786 +2004 156 16 13 15.18 0.04 273.75 108.6 55863 +2004 157 15 12 14.18 0.4 156.88 101.06 55936 +2004 158 20 11 17.52 0 578.13 286.71 56004 +2004 159 24 10 20.15 0 1140 466.91 56068 +2004 160 27 11 22.6 0 1379.38 481.31 56128 +2004 161 30 14 25.6 0.1 1751.87 438.8 56183 +2004 162 30 15 25.88 0.09 1291.88 369.43 56234 +2004 163 29 18 25.98 1.68 948.12 313.81 56280 +2004 164 24 16 21.8 2.57 501.87 246.46 56321 +2004 165 17 11 15.35 0.08 437.5 151.31 56358 +2004 166 22 12 19.25 0 919.38 489.25 56390 +2004 167 24 11 20.43 0.11 1181.25 472.76 56418 +2004 168 19 13 17.35 0 481.25 249.04 56440 +2004 169 22 8 18.15 0 935.62 405.37 56458 +2004 170 25 10 20.88 0.57 591.25 296.88 56472 +2004 171 23 14 20.52 0.49 578.13 311.13 56480 +2004 172 18 13 16.63 2.23 248.75 183.99 56484 +2004 173 21 12 18.52 0 568.12 307.42 56482 +2004 174 24 12 20.7 0.64 868.75 457.21 56476 +2004 175 25 10 20.88 0 790.63 476.78 56466 +2004 176 25 15 22.25 1.05 1039.38 352.88 56450 +2004 177 15 15 15 3.22 143.13 82.81 56430 +2004 178 23 9 19.15 0 848.13 426.63 56405 +2004 179 26 11 21.88 0 953.75 430.19 56375 +2004 180 28 16 24.7 0.4 881.25 308.34 56341 +2004 181 20 14 18.35 0.06 561.88 292.65 56301 +2004 182 23 11 19.7 0 711.87 358.05 56258 +2004 183 27 12 22.88 0.53 1099.38 434.77 56209 +2004 184 18 15 17.18 0.69 185.62 88.38 56156 +2004 185 24 10 20.15 0 934.37 482.34 56099 +2004 186 24 14 21.25 0 978.13 408.74 56037 +2004 187 29 13 24.6 0 1208.13 457.88 55971 +2004 188 25 16 22.52 0.24 666.25 348.38 55900 +2004 189 23 15 20.8 0 595 334.34 55825 +2004 190 29 13 24.6 0 961.25 374.34 55746 +2004 191 23 17 21.35 0 998.75 305.81 55663 +2004 192 22 10 18.7 0 975 449.92 55575 +2004 193 19 9 16.25 0.1 418.75 192.94 55484 +2004 194 21 6 16.88 0 710.63 349.76 55388 +2004 195 21 9 17.7 0 819.38 318.44 55289 +2004 196 19 12 17.07 0.08 630 184.97 55186 +2004 197 22 10 18.7 0.13 484.38 161.91 55079 +2004 198 28 15 24.43 0 979.38 404.08 54968 +2004 199 29 14 24.88 0 1133.13 420.99 54854 +2004 200 31 15 26.6 0 1410 471.76 54736 +2004 201 29 15 25.15 0.04 1211.25 393.38 54615 +2004 202 31 15 26.6 0 1240 439.84 54490 +2004 203 31 16 26.88 0 1660.63 462.94 54362 +2004 204 33 16 28.32 0.07 1296.87 386.05 54231 +2004 205 29 15 25.15 0 1148.13 384.35 54097 +2004 206 28 16 24.7 0 1131.87 361.98 53960 +2004 207 26 20 24.35 0 1070.63 278.22 53819 +2004 208 25 14 21.98 0.06 1175.63 283.54 53676 +2004 209 23 16 21.07 0 956 224.18 53530 +2004 210 19 15 17.9 0.19 775.71 180.52 53382 +2004 211 19 15 17.9 0.01 606.43 89.25 53230 +2004 212 25 12 21.43 0 792.86 230.56 53076 +2004 213 29 13 24.6 0 1806.43 483.49 52920 +2004 214 28 12 23.6 0.52 1061.43 327.56 52761 +2004 215 27 12 22.88 0.45 1273.57 362.75 52600 +2004 216 28 13 23.88 0.5 887.14 338.18 52437 +2004 217 29 12 24.32 0 1362.86 390.24 52271 +2004 218 30 12 25.05 0 1520 401.71 52103 +2004 219 28 16 24.7 0.43 1013.57 325.85 51934 +2004 220 25 16 22.52 1.26 384.29 171.71 51762 +2004 221 26 15 22.98 0 797.14 416.55 51588 +2004 222 27 13 23.15 0.5 805 320.53 51413 +2004 223 28 13 23.88 0 1100 430.68 51235 +2004 224 29 12 24.32 0 1135.71 426.06 51057 +2004 225 30 14 25.6 0 981.43 402.41 50876 +2004 226 23 19 21.9 0.52 835 139.07 50694 +2004 227 25 15 22.25 0 1025 402.86 50510 +2004 228 25 16 22.52 0 1190.71 414.87 50325 +2004 229 27 11 22.6 0 1165 450.69 50138 +2004 230 28 12 23.6 0 1193.57 446.19 49951 +2004 231 33 15 28.05 0 2058.57 445.76 49761 +2004 232 32 14 27.05 0 2087.14 428.85 49571 +2004 233 29 17 25.7 0.7 1127.14 353.65 49380 +2004 234 25 15 22.25 1.6 736.43 292.62 49187 +2004 235 22 14 19.8 0 1000 399.22 48993 +2004 236 25 10 20.88 0 960 410.75 48798 +2004 237 27 12 22.88 0.03 986.43 337.31 48603 +2004 238 23 16 21.07 0.23 912.86 251.38 48406 +2004 239 17 15 16.45 0.78 179.29 56.5 48208 +2004 240 23 11 19.7 0 1032.86 379.9 48010 +2004 241 26 9 21.32 0 1072.14 443.94 47811 +2004 242 27 11 22.6 0 1099.29 415.13 47611 +2004 243 27 12 22.88 0 956.43 402.76 47410 +2004 244 16 16 16 0.29 340 57.88 47209 +2004 245 21 13 18.8 0.01 480.77 186.13 47007 +2004 246 20 7 16.43 0 446.15 180.22 46805 +2004 247 24 9 19.88 0 691.54 333.16 46601 +2004 248 26 10 21.6 0 1066.15 370.2 46398 +2004 249 23 15 20.8 0 972.31 295.2 46194 +2004 250 26 12 22.15 0 1033.08 384.26 45989 +2004 251 25 8 20.32 0 1100.77 343.13 45784 +2004 252 25 9 20.6 0 1233.85 354.21 45579 +2004 253 18 12 16.35 0 1027.69 437.07 45373 +2004 254 20 4 15.6 0 892.31 417.6 45167 +2004 255 22 7 17.88 0 1050 397.53 44961 +2004 256 25 7 20.05 0.34 1017.5 315.74 44755 +2004 257 24 11 20.43 0 856.67 394.21 44548 +2004 258 27 9 22.05 0 1031.67 405.07 44341 +2004 259 20 16 18.9 0.34 308.33 84.5 44134 +2004 260 18 13 16.63 0 730 149.07 43927 +2004 261 19 10 16.52 0 1065 402.39 43719 +2004 262 21 2 15.78 0 950 399.81 43512 +2004 263 21 3 16.05 0 558.33 315.78 43304 +2004 264 24 10 20.15 0 645 309.02 43097 +2004 265 23 8 18.88 0.16 621.67 267.44 42890 +2004 266 18 10 15.8 0.33 345 301.13 42682 +2004 267 17 10 15.07 0.08 377.5 304.98 42475 +2004 268 12 10 11.45 0.45 126.67 48.76 42268 +2004 269 16 9 14.07 0 549.17 205.53 42060 +2004 270 16 10 14.35 0 627.5 218.61 41854 +2004 271 17 9 14.8 0 673.33 184.27 41647 +2004 272 20 11 17.52 0 563.33 193.35 41440 +2004 273 22 11 18.98 0.05 728.33 312.26 41234 +2004 274 19 11 16.8 0 400 253.49 41028 +2004 275 18 9 15.53 0.21 406.36 184.14 40822 +2004 276 17 10 15.07 0 202.73 151.97 40617 +2004 277 19 9 16.25 0.03 398.18 178.65 40412 +2004 278 21 8 17.43 0 740 321.13 40208 +2004 279 23 9 19.15 0 518.18 298.99 40003 +2004 280 23 7 18.6 0 650 314.45 39800 +2004 281 21 10 17.98 0.01 409.09 201.76 39597 +2004 282 23 8 18.88 0 555.45 304.88 39394 +2004 283 15 10 13.63 0.88 216.36 173.21 39192 +2004 284 10 8 9.45 2.08 99.09 46.41 38991 +2004 285 12 6 10.35 0 335.45 166.68 38790 +2004 286 10 3 8.07 0.16 327.27 243.34 38590 +2004 287 6 5 5.72 0.09 169.09 37.26 38391 +2004 288 7 4 6.17 0.16 64.55 36.33 38193 +2004 289 9 6 8.18 0.3 49.09 53.5 37995 +2004 290 13 7 11.35 1.62 341.45 133.7 37799 +2004 291 11 4 9.07 0.76 131.82 138.44 37603 +2004 292 15 1 11.15 0 380.91 273.63 37408 +2004 293 15 2 11.43 0 266.36 211.26 37214 +2004 294 17 5 13.7 0 368.18 228.12 37022 +2004 295 17 11 15.35 0.49 270.91 157.89 36830 +2004 296 15 13 14.45 0.71 96.36 56.66 36640 +2004 297 15 12 14.18 0 110 68.7 36451 +2004 298 18 9 15.53 0 298.18 222.17 36263 +2004 299 15 7 12.8 0 199.09 236.76 36076 +2004 300 17 6 13.98 0 502 233.47 35891 +2004 301 18 10 15.8 0 548 218.62 35707 +2004 302 21 9 17.7 0 739 230.86 35525 +2004 303 20 13 18.07 0 771 163.78 35345 +2004 304 20 15 18.63 0.18 650 109.83 35166 +2004 305 13 11 12.45 0.19 200 89.21 34988 +2004 306 14 7 12.07 0 260 121.55 34813 +2004 307 16 13 15.18 0.02 110 63.59 34639 +2004 308 13 11 12.45 0.03 60 37.17 34468 +2004 309 15 13 14.45 0 174.44 116.42 34298 +2004 310 13 6 11.07 0 286.67 116.21 34130 +2004 311 12 7 10.63 0 507.78 181.51 33964 +2004 312 9 3 7.35 0 268.89 127.6 33801 +2004 313 7 0 5.08 0.64 214.44 88.54 33640 +2004 314 3 2 2.73 1.53 31.11 49.33 33481 +2004 315 6 -1 4.08 0.24 57.78 84.44 33325 +2004 316 9 4 7.63 0 70 47.58 33171 +2004 317 12 4 9.8 0 120 49.29 33019 +2004 318 8 7 7.72 1.45 102.22 28.64 32871 +2004 319 5 4 4.72 0 290 71.59 32725 +2004 320 4 2 3.45 0.01 231.11 53.64 32582 +2004 321 5 -3 2.8 0 217.78 103.78 32441 +2004 322 12 1 8.97 0 471.11 124.82 32304 +2004 323 12 2 9.25 0 587.78 186.2 32170 +2004 324 10 2 7.8 0.12 427.78 74.72 32039 +2004 325 5 -2 3.08 0 263.33 183.16 31911 +2004 326 5 -3 2.8 0 356.67 176.98 31786 +2004 327 2 -4 0.35 0 225.56 58.29 31665 +2004 328 12 1 8.97 0.04 590 136.63 31547 +2004 329 6 3 5.17 0 533.33 212.53 31433 +2004 330 4 -2 2.35 0 384.44 206.29 31322 +2004 331 7 -6 3.43 0 376.67 192.34 31215 +2004 332 5 -5 2.25 0 193.33 71.67 31112 +2004 333 9 -3 5.7 0 220 162.48 31012 +2004 334 5 -1 3.35 0 86.67 79.68 30917 +2004 335 3 2 2.73 0.3 30 17.74 30825 +2004 336 5 3 4.45 0 30 34.59 30738 +2004 337 10 4 8.35 0 84.44 109.35 30654 +2004 338 7 0 5.08 0 90 82.93 30575 +2004 339 6 -2 3.8 0 82.22 87.92 30500 +2004 340 4 -1 2.63 0.12 32.22 61.61 30430 +2004 341 6 1 4.63 0 66.67 98.17 30363 +2004 342 5 -4 2.52 0 90 162.11 30301 +2004 343 2 1 1.73 0 84.44 20.83 30244 +2004 344 1 1 1 0 144.44 34.53 30191 +2004 345 0 -1 -0.28 0 114.44 28.83 30143 +2004 346 0 -2 -0.55 0 81.11 79.16 30099 +2004 347 -2 -4 -2.55 0 22.5 19.54 30060 +2004 348 -2 -3 -2.27 0 30 14.81 30025 +2004 349 -3 -3 -3 0 30 18.6 29995 +2004 350 -3 -4 -3.27 0 30 19.48 29970 +2004 351 -4 -4 -4 0.04 30 15.91 29950 +2004 352 -1 -4 -1.83 0.5 30 20.61 29934 +2004 353 6 -1 4.08 0.03 26.25 54.24 29924 +2004 354 3 -5 0.8 0 210 130.18 29918 +2004 355 2 -1 1.18 0 277.5 183.28 29916 +2004 356 2 -8 -0.75 0 180 171.01 29920 +2004 357 -4 -9 -5.38 0 31.25 62.92 29928 +2004 358 0 -7 -1.93 0 127.5 69.29 29941 +2004 359 6 -3 3.52 0 431.25 141.12 29959 +2004 360 10 -2 6.7 0 326.25 148.47 29982 +2004 361 7 5 6.45 0.91 150 24.07 30009 +2004 362 4 0 2.9 0.78 38.75 20.24 30042 +2004 363 3 1 2.45 0.55 47.5 28.98 30078 +2004 364 7 1 5.35 0 276.25 150.96 30120 +2004 365 4 1 3.17 0 246.25 65.02 30166 +2005 1 7 -2.9 4.28 0 197.5 66.13 30217 +2005 2 9.4 -1.7 6.35 0 306.25 127.21 30272 +2005 3 8.1 -2.7 5.13 0 482.5 198.32 30331 +2005 4 10.3 -1.5 7.06 0 456.25 71.18 30396 +2005 5 10.8 -3.9 6.76 0 483.75 156.02 30464 +2005 6 12.5 -2.8 8.29 0 450 128.02 30537 +2005 7 11.4 -2.4 7.61 0 437.5 143.02 30614 +2005 8 12.6 -3.2 8.25 0 477.5 178.61 30695 +2005 9 6.1 -3.1 3.57 0 201.25 112.78 30781 +2005 10 11.6 -3.9 7.34 0 327.5 177.51 30870 +2005 11 7.4 -4.1 4.24 0 132.22 132.57 30964 +2005 12 8.8 -5.1 4.98 0 306.67 194.08 31061 +2005 13 2.7 -4.5 0.72 0.01 108.89 61.85 31162 +2005 14 5.5 -5.4 2.5 0 284.44 126.84 31268 +2005 15 6.1 -3 3.6 0 316.67 151.47 31376 +2005 16 4.6 -7 1.41 0 290 217.2 31489 +2005 17 3.5 -8.5 0.2 0 241.11 203.91 31605 +2005 18 -0.3 -10 -2.97 0.01 44.44 49.64 31724 +2005 19 1.8 -3.6 0.32 0 99 99.65 31847 +2005 20 3.8 -8.5 0.42 0.02 219 82.34 31974 +2005 21 8.3 -0.2 5.96 0.02 311 150.04 32103 +2005 22 7.1 -5.4 3.66 0 365 175.08 32236 +2005 23 5.6 -6.4 2.3 0 255 145.21 32372 +2005 24 0.6 -6.6 -1.38 0.44 86 72.68 32510 +2005 25 0.4 -2.3 -0.34 0 149 185.01 32652 +2005 26 -2.2 -3.4 -2.53 0.02 60 65.06 32797 +2005 27 -1.5 -5.6 -2.63 0 147 155.4 32944 +2005 28 -2.3 -13.9 -5.49 0 125 208.28 33094 +2005 29 -2 -7 -3.38 0 130 146.11 33247 +2005 30 0.8 -14 -3.27 0 206 245.96 33402 +2005 31 3.8 -13.5 -0.96 0 234 104.58 33559 +2005 32 7.1 -1.7 4.68 0.02 247 154.14 33719 +2005 33 4.6 -4.7 2.04 0.97 294 127.69 33882 +2005 34 1.1 -0.7 0.61 1 30 41.64 34046 +2005 35 3.9 -8.7 0.44 0 134 138.15 34213 +2005 36 -2.2 -17 -6.27 0 89 275.53 34382 +2005 37 1 -19.7 -4.69 0 96 324.06 34552 +2005 38 -3 -20.4 -7.79 0 51 193.1 34725 +2005 39 -1.9 -22 -7.43 0 123 324.81 34900 +2005 40 -1.6 -23.5 -7.62 0 131 286.66 35076 +2005 41 1.3 -21.1 -4.86 0 171 300.13 35254 +2005 42 5.5 -4.5 2.75 0 299 154.64 35434 +2005 43 6.4 0 4.64 0.02 229 108.19 35615 +2005 44 9.6 0.9 7.21 0 367 169.18 35798 +2005 45 8.1 -2.5 5.18 0 337 256.29 35983 +2005 46 2.3 -2.4 1.01 0.03 224 142.75 36169 +2005 47 3.4 -0.8 2.25 0 149 59.95 36356 +2005 48 5.1 -1 3.42 0 243 136.77 36544 +2005 49 3.5 -1.4 2.15 0 230 169 36734 +2005 50 0.8 -4.4 -0.63 0 166 70.38 36925 +2005 51 4.1 -6 1.32 0.01 224 235.53 37117 +2005 52 1.3 -2.5 0.26 1.91 40 94.55 37310 +2005 53 2.8 -1.9 1.51 0.03 51.82 220.67 37505 +2005 54 3.8 -1.5 2.34 1.19 96.36 160.79 37700 +2005 55 6.3 -1 4.29 0 177.27 253.38 37896 +2005 56 0.2 -8.7 -2.25 0.47 30.91 109.9 38093 +2005 57 2.7 -2.4 1.3 0 192.73 286.3 38291 +2005 58 0.5 -5.4 -1.12 0 190.91 176.55 38490 +2005 59 -1.9 -14.5 -5.37 0 189.09 346.96 38689 +2005 60 -1 -20 -6.22 0 234.55 378.23 38890 +2005 61 -1.3 -21.5 -6.86 0 193.33 382.57 39091 +2005 62 -0.3 -18.2 -5.22 0.73 180.83 351.47 39292 +2005 63 -0.8 -7.1 -2.53 0.13 45 124.01 39495 +2005 64 0.1 -7.6 -2.02 0 135 255.37 39697 +2005 65 2.4 -16.3 -2.74 0 229.17 272.51 39901 +2005 66 4.2 -16.4 -1.46 0 293.33 371.45 40105 +2005 67 5.1 -3.6 2.71 0 266.67 161.77 40309 +2005 68 5.6 -2.9 3.26 0.29 141.67 132.1 40514 +2005 69 -0.1 -4.6 -1.34 0 210 380.28 40719 +2005 70 4.4 -15.2 -0.99 0 281.67 301.54 40924 +2005 71 10.3 -9.9 4.75 0.02 377.5 279.33 41130 +2005 72 11.5 -1.6 7.9 0 468.33 383.07 41336 +2005 73 11.8 -6.4 6.8 0 425.83 368.46 41543 +2005 74 12.5 -3.9 7.99 0 484.17 333.7 41749 +2005 75 19.2 -2 13.37 0 779.17 361.54 41956 +2005 76 23 -1.4 16.29 0 1274.17 368.38 42163 +2005 77 22.3 3.1 17.02 0 1217.5 314.42 42370 +2005 78 13.1 3.7 10.52 0.24 262.5 108.98 42578 +2005 79 6.5 -2 4.16 0 301.67 341.76 42785 +2005 80 9.5 -4.2 5.73 0 352.5 320.32 42992 +2005 81 12.5 -1.4 8.68 0 551.67 368.7 43200 +2005 82 14.5 -2 9.96 0 696.67 316.55 43407 +2005 83 18.3 -0.5 13.13 0 668.33 361.94 43615 +2005 84 16.1 0.6 11.84 0.15 393.33 219.37 43822 +2005 85 17.8 8 15.11 0 445.83 267.52 44029 +2005 86 18 3.7 14.07 0.32 510.83 307.37 44236 +2005 87 18.5 10.3 16.25 0.3 558.33 308.86 44443 +2005 88 16.1 6.9 13.57 0.28 555 285.65 44650 +2005 89 11.2 5 9.49 0.02 170.83 96.11 44857 +2005 90 12.3 5 10.29 0 605 352.23 45063 +2005 91 11.6 -2.2 7.8 0 591.67 438.41 45270 +2005 92 14.5 -2.6 9.8 0 693.08 447.16 45475 +2005 93 16.3 -3.1 10.97 0 850.77 441.39 45681 +2005 94 18 -2.5 12.36 0 1040.77 423.74 45886 +2005 95 20 -1.4 14.12 0 1245.38 433.37 46091 +2005 96 20.6 0.7 15.13 0 1225.71 402.43 46295 +2005 97 18.6 2 14.04 0 1127.86 327.7 46499 +2005 98 18.6 11.4 16.62 0 1060.71 389.6 46702 +2005 99 15.1 7.4 12.98 2.45 117.14 59.17 46905 +2005 100 9.5 6.1 8.56 0.2 286.43 132.92 47107 +2005 101 8.7 6.3 8.04 0.25 296.43 71.12 47309 +2005 102 12 5.9 10.32 0.23 420.71 108.4 47510 +2005 103 14.4 7.6 12.53 0.08 310 178.07 47710 +2005 104 20.5 6.3 16.59 0 771.43 322.56 47910 +2005 105 22.1 4.1 17.15 0 1031.43 436.17 48108 +2005 106 21.7 4.6 17 0.08 1047.14 437.18 48306 +2005 107 17.4 8.8 15.04 0 490.71 219.21 48504 +2005 108 14.1 4.1 11.35 0.28 451.43 114.46 48700 +2005 109 14.3 9.9 13.09 0.84 172.86 77.05 48895 +2005 110 10.6 5.5 9.2 1.05 87.86 84.69 49089 +2005 111 9.7 4 8.13 0 538.57 452.34 49282 +2005 112 13.4 -2.1 9.14 0 712.86 486.12 49475 +2005 113 18.3 -2 12.72 0 928.57 471.47 49666 +2005 114 20 4 15.6 0 824.29 428.77 49855 +2005 115 19.2 11 16.95 0.15 566.43 352.03 50044 +2005 116 19 9.4 16.36 0.03 631.43 210.48 50231 +2005 117 24.1 6.6 19.29 0.31 1155 403.21 50417 +2005 118 20.6 9 17.41 0 869.29 392.73 50601 +2005 119 20.5 2 15.41 0 899.29 475.14 50784 +2005 120 21.1 5.9 16.92 0 937.14 331.78 50966 +2005 121 25.5 5.1 19.89 0 1219.29 467.08 51145 +2005 122 29.5 7.9 23.56 0 1729.29 453.31 51324 +2005 123 28.5 10.9 23.66 2.72 1615 370.82 51500 +2005 124 23.2 13.5 20.53 0.93 509.29 271.9 51674 +2005 125 18.3 11.2 16.35 0.06 529.33 222.5 51847 +2005 126 18.9 9.4 16.29 0.02 718 394.74 52018 +2005 127 17.8 4.5 14.14 0.38 826.67 379.89 52187 +2005 128 16.6 7.8 14.18 0 562.67 321.93 52353 +2005 129 13 3.3 10.33 0.08 407.33 223.87 52518 +2005 130 13.3 0.5 9.78 0 388 306.5 52680 +2005 131 16.3 7.5 13.88 0 736.67 403.68 52840 +2005 132 18 0.4 13.16 0 830 433.31 52998 +2005 133 20 0.6 14.67 0 958 485.52 53153 +2005 134 22.7 3.7 17.48 0 1028.67 411.32 53306 +2005 135 20.3 12.7 18.21 0.05 647.33 234.1 53456 +2005 136 21.5 12.1 18.91 0.02 559.33 288.6 53603 +2005 137 22.6 14 20.23 0.5 814 298.78 53748 +2005 138 15.6 10.9 14.31 1.31 112.67 55 53889 +2005 139 13.6 8.5 12.2 0.02 327.33 118.13 54028 +2005 140 18.6 4.5 14.72 0 818.67 552.05 54164 +2005 141 23.6 3.1 17.96 0 1073.33 509.23 54297 +2005 142 24.9 7.5 20.11 0 1159.38 450.91 54426 +2005 143 27.3 10.3 22.63 0.08 1147.5 372.23 54552 +2005 144 22.3 12.4 19.58 0 1000.63 463.37 54675 +2005 145 23.7 7.5 19.25 0 1189.38 520.79 54795 +2005 146 26 9.2 21.38 0 1316.25 508.9 54911 +2005 147 28.6 9.5 23.35 0 1517.5 504.72 55023 +2005 148 30.5 11 25.14 0 1740 483.73 55132 +2005 149 31 12.6 25.94 0 1812.5 480.01 55237 +2005 150 31.7 13.5 26.7 0.12 2053.75 504.51 55339 +2005 151 27.2 16 24.12 0 892.5 348.72 55436 +2005 152 21.7 7 17.66 0 1105.62 422.91 55530 +2005 153 23.1 8 18.95 0 1155.63 391.18 55619 +2005 154 25.5 7.9 20.66 0 1385.63 486.41 55705 +2005 155 27.1 13.2 23.28 0.64 1305.63 383.55 55786 +2005 156 20.5 14.2 18.77 0.05 452.5 287.34 55863 +2005 157 22.6 10 19.14 0.01 705 295.13 55936 +2005 158 17.3 7.8 14.69 0.82 461.88 193.22 56004 +2005 159 15.2 5.9 12.64 0 583.13 231.25 56068 +2005 160 13.3 9 12.12 0.06 475.62 138.72 56128 +2005 161 18.1 9.1 15.63 0 660.63 194.37 56183 +2005 162 22.3 5.9 17.79 0.27 963.75 311.78 56234 +2005 163 22.9 11.5 19.77 0.01 576.88 259.19 56280 +2005 164 26.6 8.6 21.65 0 1217.5 490.26 56321 +2005 165 27.1 10.6 22.56 0 1308.75 420.78 56358 +2005 166 26.6 17 23.96 0.2 1029.38 301.4 56390 +2005 167 27.1 16 24.05 0 997.5 401.09 56418 +2005 168 28.6 13.6 24.48 0 1455.62 398.84 56440 +2005 169 28.5 16 25.06 0 1231.88 265.68 56458 +2005 170 24.7 14 21.76 0 1198.75 493.88 56472 +2005 171 26.9 9.5 22.11 0 1366.87 435.38 56480 +2005 172 27.9 9.8 22.92 0 1698.75 498.79 56484 +2005 173 29.9 10.5 24.56 0.27 1233.13 363.39 56482 +2005 174 27.8 15.9 24.53 0 1475 475.9 56476 +2005 175 28.4 11 23.61 0 1356.25 481.2 56466 +2005 176 31 14.9 26.57 0 1470.62 450.44 56450 +2005 177 27.3 17.2 24.52 0.14 890.63 215.73 56430 +2005 178 28 15.1 24.45 2.98 743.13 314.69 56405 +2005 179 30.7 16.3 26.74 0.16 695 339.31 56375 +2005 180 29.7 13.9 25.36 1.8 908.13 316.36 56341 +2005 181 27.6 16.7 24.6 1.2 497.5 273.41 56301 +2005 182 20.1 15.1 18.73 4.37 150 79.3 56258 +2005 183 19.4 13.2 17.69 0.16 622.5 164.87 56209 +2005 184 26.4 14.9 23.24 0 1357.5 430.77 56156 +2005 185 26.7 10.6 22.27 0 1179.37 481.8 56099 +2005 186 23.5 12.6 20.5 2.24 364.38 121.31 56037 +2005 187 23.3 8 19.09 0 1013.75 498.04 55971 +2005 188 24.4 9.5 20.3 0.7 872.5 361.48 55900 +2005 189 21.6 14.2 19.57 1.19 157.5 131.34 55825 +2005 190 17.4 13.2 16.24 0.23 193.75 139.11 55746 +2005 191 23 11.4 19.81 0 538.12 283.4 55663 +2005 192 22.4 15.7 20.56 1.67 310.63 206.68 55575 +2005 193 19.5 15.4 18.37 1.22 142.5 66.34 55484 +2005 194 26.5 15 23.34 0.06 918.13 426.87 55388 +2005 195 28.1 13.5 24.09 0 1186.88 470.6 55289 +2005 196 28.9 12 24.25 0 1396.25 472.09 55186 +2005 197 29.8 17.2 26.34 0.4 1376.25 356.73 55079 +2005 198 30.4 15 26.16 0 1173.13 395.38 54968 +2005 199 31.4 16.1 27.19 0 982.5 430.91 54854 +2005 200 26.9 18.9 24.7 0.23 940 278.4 54736 +2005 201 26.4 12.8 22.66 0.05 1292.5 476.19 54615 +2005 202 23 15.3 20.88 0.17 578.75 302.9 54490 +2005 203 26.4 10 21.89 0.51 540 348.55 54362 +2005 204 21.7 14.9 19.83 0.21 410 254.12 54231 +2005 205 25.6 14.8 22.63 0.01 728.75 372.46 54097 +2005 206 28.6 16.3 25.22 0.05 898.75 423.08 53960 +2005 207 27.1 16.3 24.13 0.09 816.88 326.44 53819 +2005 208 30.2 17.9 26.82 0 993.75 442.02 53676 +2005 209 32.7 17.5 28.52 0 1176 442.97 53530 +2005 210 33 18.5 29.01 0 1310.71 443.18 53382 +2005 211 32.2 21.4 29.23 0 1347.14 395.06 53230 +2005 212 28.4 20.2 26.14 0 1219.29 453.91 53076 +2005 213 29.3 16.3 25.73 0 1670 458.02 52920 +2005 214 29.4 12.8 24.84 0 1641.43 440.32 52761 +2005 215 23.5 15.4 21.27 2.76 346.43 130.11 52600 +2005 216 19.5 15.6 18.43 0.08 543.57 108.05 52437 +2005 217 22.3 16 20.57 0 979.29 342.17 52271 +2005 218 25.3 7.9 20.52 0.3 1046.43 344.18 52103 +2005 219 18.7 12 16.86 0.12 344.29 130.27 51934 +2005 220 20.8 8 17.28 0 879.29 421.51 51762 +2005 221 23.1 5.5 18.26 0 1030 442.75 51588 +2005 222 26 8 21.05 0.12 998.57 440.17 51413 +2005 223 24.1 12.2 20.83 0.03 707.86 365.84 51235 +2005 224 21.9 16.2 20.33 0 685.71 166.13 51057 +2005 225 25.6 8.1 20.79 0.93 931.43 405.96 50876 +2005 226 24.1 15.3 21.68 4.79 879.29 386.81 50694 +2005 227 19.7 12.5 17.72 0.08 285.71 141.42 50510 +2005 228 17.6 13 16.34 1.25 222.86 142.96 50325 +2005 229 18.1 14.5 17.11 0.89 135 63.98 50138 +2005 230 25.1 14 22.05 0 811.43 391.85 49951 +2005 231 26.6 13 22.86 0 784.29 333.21 49761 +2005 232 25.7 13.3 22.29 0.38 652.86 290.8 49571 +2005 233 21.4 17.2 20.24 1.38 165 107.28 49380 +2005 234 21.1 15 19.42 1.13 281.43 271.96 49187 +2005 235 23.7 12.6 20.65 0.1 412.86 298.38 48993 +2005 236 24.6 14.8 21.91 0 695 291.19 48798 +2005 237 26.1 10.8 21.89 0.01 940.71 436.54 48603 +2005 238 21.7 15.9 20.11 0.1 614.29 150.45 48406 +2005 239 18.6 15.1 17.64 0.63 375 157.86 48208 +2005 240 21.2 15.3 19.58 0 300 216.25 48010 +2005 241 25.5 13.1 22.09 0 790 413.13 47811 +2005 242 26.5 13.4 22.9 0 743.57 359.28 47611 +2005 243 26.2 14.5 22.98 0 775.71 337.83 47410 +2005 244 27.4 13.5 23.58 0 798.57 315.21 47209 +2005 245 25.9 15 22.9 0 585.38 316.86 47007 +2005 246 24.1 13.3 21.13 0 816.15 394.26 46805 +2005 247 22.2 12.6 19.56 0 725.38 290.49 46601 +2005 248 23.9 7.9 19.5 0 851.54 421.2 46398 +2005 249 23.9 7.9 19.5 0 916.92 424.75 46194 +2005 250 25.1 8 20.4 0 872.31 396.15 45989 +2005 251 26.9 11 22.53 0 925.38 413.63 45784 +2005 252 26.3 16.8 23.69 0.12 897.69 311.1 45579 +2005 253 24.8 18 22.93 0.06 456.92 265.09 45373 +2005 254 24.4 15 21.81 0 350.77 184.63 45167 +2005 255 26.8 13 23 0 1050 424.53 44961 +2005 256 25.7 10.5 21.52 0.67 851.67 345.29 44755 +2005 257 23.5 10.6 19.95 0 702.5 342.77 44548 +2005 258 24.6 9.5 20.45 0 735 320.73 44341 +2005 259 25.4 10.9 21.41 1.48 1035.83 388.1 44134 +2005 260 20.2 12.1 17.97 0.2 215 82.06 43927 +2005 261 12.1 9.7 11.44 0.33 215 85.54 43719 +2005 262 11.6 9 10.89 1.78 165 72.28 43512 +2005 263 11.2 9.2 10.65 0.03 211.67 93.15 43304 +2005 264 15.1 9.9 13.67 0.1 340 145.19 43097 +2005 265 17.1 12 15.7 0 310.83 124.67 42890 +2005 266 20.6 9 17.41 0 565 260.1 42682 +2005 267 21.6 6 17.31 0 629.17 320.93 42475 +2005 268 22.2 7.5 18.16 0 636.67 328.89 42268 +2005 269 22.5 7 18.24 0 518.33 346.58 42060 +2005 270 21.4 8.7 17.91 0.37 448.33 246.46 41854 +2005 271 19.2 12.2 17.27 0 216.67 194.24 41647 +2005 272 14.3 8.9 12.82 1.96 67.5 53.07 41440 +2005 273 17.1 6.4 14.16 0 545.83 317.92 41234 +2005 274 16.6 3.4 12.97 0 575 365.9 41028 +2005 275 17.1 4.6 13.66 0.19 540.91 264.71 40822 +2005 276 14.9 11.5 13.97 0.05 100 59.62 40617 +2005 277 18.7 14.5 17.55 0 258.18 109.35 40412 +2005 278 19.1 12.5 17.29 0 469.09 150 40208 +2005 279 20 6.7 16.34 0 565.45 253.64 40003 +2005 280 18.5 6 15.06 0 503.64 280.07 39800 +2005 281 15.6 5.6 12.85 0 500.91 170.43 39597 +2005 282 17.8 5.5 14.42 0 359.09 198.12 39394 +2005 283 19.2 3.4 14.85 0 630 315.66 39192 +2005 284 15.2 3 11.84 0 345.45 160.85 38991 +2005 285 15.9 5 12.9 0 520 308.17 38790 +2005 286 16 2.5 12.29 0 320.91 206.24 38590 +2005 287 16.3 4.2 12.97 0 308.86 207.02 38391 +2005 288 16.1 4.9 13.02 0 633.02 267.88 38193 +2005 289 14.3 2.5 11.06 0 505.45 325.85 37995 +2005 290 12.6 2 9.68 0 496.36 237.55 37799 +2005 291 13.8 -1.2 9.68 0 437.27 312.74 37603 +2005 292 12.1 -3.3 7.87 0 340.91 301.08 37408 +2005 293 14.1 -1.4 9.84 0 286.36 210.98 37214 +2005 294 18.1 9 15.6 0 320.91 153.8 37022 +2005 295 20.6 4 16.04 0 507.27 215.71 36830 +2005 296 22.4 3.5 17.2 0.2 505.45 185.98 36640 +2005 297 18.6 8.1 15.71 0 350.91 215.2 36451 +2005 298 19.5 7.1 16.09 0 431.82 222.97 36263 +2005 299 20.1 3.8 15.62 0 632.73 223.55 36076 +2005 300 21.4 4.3 16.7 0 668 273.54 35891 +2005 301 18.1 6.1 14.8 0 368 237.62 35707 +2005 302 15.3 6.2 12.8 0 647 256.38 35525 +2005 303 11.6 1.8 8.9 0 317 265.95 35345 +2005 304 9.3 2.6 7.46 0 248 174.23 35166 +2005 305 8.6 -2.5 5.55 0 209 129.6 34988 +2005 306 13.1 5 10.87 0 184 101.4 34813 +2005 307 11.7 4.4 9.69 0.04 161 68.81 34639 +2005 308 11.9 5.3 10.09 0 237 144.24 34468 +2005 309 12.5 4.5 10.3 0 242.22 97.82 34298 +2005 310 11.1 6.8 9.92 0 210 71.99 34130 +2005 311 11.2 5.2 9.55 0.21 235.56 99.36 33964 +2005 312 13.2 5.5 11.08 0 208.89 175.53 33801 +2005 313 12.7 0 9.21 0 264.44 205.55 33640 +2005 314 6.6 1.4 5.17 0 37.78 42.9 33481 +2005 315 7.7 4.9 6.93 0 35.56 73.87 33325 +2005 316 6.7 5 6.23 0.07 111.11 36.18 33171 +2005 317 5.4 4.4 5.13 0.05 72.22 22.86 33019 +2005 318 4.4 2.9 3.99 0.07 106.67 32.86 32871 +2005 319 10.3 2.8 8.24 0 108.89 118.04 32725 +2005 320 5 -0.3 3.54 0.49 31.11 87.08 32582 +2005 321 10.1 1.2 7.65 0 443.33 209.78 32441 +2005 322 7.6 -3.6 4.52 0.03 253.33 212.6 32304 +2005 323 4.3 -3.4 2.18 0 251.11 191.23 32170 +2005 324 3.9 -4.1 1.7 0.05 234.44 142.61 32039 +2005 325 4.3 -1.9 2.59 0 168.89 84.74 31911 +2005 326 1.8 -2.8 0.54 0.16 120 64.9 31786 +2005 327 0.2 -2.2 -0.46 0.3 106.67 180.35 31665 +2005 328 -1 -3 -1.55 0.21 43.33 45.32 31547 +2005 329 1.2 -3 0.05 1.65 102.22 142.62 31433 +2005 330 1.4 -1.2 0.68 0.99 30 61.24 31322 +2005 331 1.4 0.3 1.1 1.88 31.11 34.17 31215 +2005 332 2.9 -1.9 1.58 0.09 35.56 53.84 31112 +2005 333 1.6 -3.6 0.17 0.19 38.89 105.7 31012 +2005 334 1.6 -0.5 1.02 0 55.56 58.2 30917 +2005 335 1.3 -3.8 -0.1 0.01 177.78 68.29 30825 +2005 336 0.7 -2 -0.04 0 33.33 59.17 30738 +2005 337 9.1 -2.9 5.8 0.01 323.33 90.18 30654 +2005 338 9.8 -0.1 7.08 0 110 148.07 30575 +2005 339 9 4 7.63 1.3 136.67 30.88 30500 +2005 340 4.7 2.7 4.15 2.25 46.67 20.05 30430 +2005 341 10.1 0.5 7.46 0 346.67 168.76 30363 +2005 342 8.5 -1.8 5.67 0 218.89 159.8 30301 +2005 343 7.3 -2.6 4.58 0 203.33 188.45 30244 +2005 344 3 -1.1 1.87 0 206.67 145.55 30191 +2005 345 0.9 -7.3 -1.35 0 138.89 200.21 30143 +2005 346 2.7 -8.5 -0.38 0.25 130 162.47 30099 +2005 347 0.8 -1.5 0.17 0 66.25 58.66 30060 +2005 348 1.6 -0.5 1.02 0 150 56.3 30025 +2005 349 6.6 -3.1 3.93 0 287.5 145.94 29995 +2005 350 6.1 -1.7 3.95 0.02 287.5 51.21 29970 +2005 351 5.5 -2 3.44 0 262.5 161.7 29950 +2005 352 3.8 -3.1 1.9 0 298.75 177.75 29934 +2005 353 6.1 -6.6 2.61 0 400 117.18 29924 +2005 354 6.3 -2.8 3.8 0 361.25 107.46 29918 +2005 355 4.2 -2.7 2.3 0 241.25 154.03 29916 +2005 356 1.3 -6.5 -0.84 0 158.75 38.07 29920 +2005 357 4.6 -5.3 1.88 0.01 321.25 143.43 29928 +2005 358 5.5 -1.6 3.55 0 215 57.12 29941 +2005 359 7.4 -4.4 4.16 0 280 174.15 29959 +2005 360 1.7 -3 0.41 0.04 112.5 73.45 29982 +2005 361 0 -2.3 -0.63 1.17 35 50.87 30009 +2005 362 -0.1 -2.4 -0.73 1.31 30 58.25 30042 +2005 363 -0.9 -3.2 -1.53 1.43 36.25 48.47 30078 +2005 364 0.5 -8.2 -1.89 0 108.75 99.17 30120 +2005 365 1.7 -17.6 -3.61 0.13 150 100.21 30166 +2006 1 1.7 -7.5 -0.83 1.92 45 49.43 30217 +2006 2 2 0.4 1.56 1.66 30 32.31 30272 +2006 3 3.1 -0.2 2.19 0 80 78.84 30331 +2006 4 2.2 -0.5 1.46 0.18 93.75 45.93 30396 +2006 5 1.2 0.3 0.95 0.9 30 53.26 30464 +2006 6 2 0.3 1.53 0.16 30 45.55 30537 +2006 7 2.7 -0.5 1.82 0 33.75 97.75 30614 +2006 8 0.8 -4.3 -0.6 0 77.5 77.17 30695 +2006 9 1.7 -10.6 -1.68 0 90 244.84 30781 +2006 10 -1.3 -12.3 -4.33 0 112.5 97.67 30870 +2006 11 0 -12 -3.3 0 82.22 234.14 30964 +2006 12 -0.3 -11.5 -3.38 0 66.67 153.47 31061 +2006 13 -3 -10 -4.92 0 30 62.05 31162 +2006 14 -1.9 -4.2 -2.53 0 96.67 85 31268 +2006 15 -0.2 -6.6 -1.96 0 147.78 126.37 31376 +2006 16 -2.1 -7.6 -3.61 0 124.44 84.86 31489 +2006 17 -3.9 -12 -6.13 0 48.89 98.91 31605 +2006 18 -0.1 -6.1 -1.75 0 120 69.25 31724 +2006 19 0.5 -6.5 -1.43 0 138 195.46 31847 +2006 20 1.7 -11.5 -1.93 0 80 140.43 31974 +2006 21 6.8 -8.4 2.62 0 200 242.36 32103 +2006 22 5.1 -7.6 1.61 0 163 159.68 32236 +2006 23 -7.6 -13.7 -9.28 0 92 197.04 32372 +2006 24 -7.5 -20 -10.94 0 100 271.93 32510 +2006 25 -6.2 -21 -10.27 0 114 250.65 32652 +2006 26 -6 -17.7 -9.22 0 96 199.88 32797 +2006 27 -5.2 -18.2 -8.77 0 83 134.66 32944 +2006 28 -1 -12.9 -4.27 0 147 196.91 33094 +2006 29 -2.5 -11 -4.84 0 114 86.52 33247 +2006 30 -0.1 -3.4 -1.01 0 51 97.98 33402 +2006 31 0.7 -4 -0.59 0 92 209.5 33559 +2006 32 -0.2 -5 -1.52 0 30 133.72 33719 +2006 33 -2.7 -5.4 -3.44 0 30 105.48 33882 +2006 34 -3.6 -7.5 -4.67 0 30 82.15 34046 +2006 35 -1.3 -7 -2.87 0.03 30 95.95 34213 +2006 36 -3.3 -8.7 -4.79 0 171 291.28 34382 +2006 37 -2 -13.2 -5.08 0 166 272.1 34552 +2006 38 -0.4 -17.4 -5.07 0 167 145.52 34725 +2006 39 5.8 -2.4 3.54 0.01 265 167.16 34900 +2006 40 8.2 -4 4.84 0.03 348 292.82 35076 +2006 41 5.2 -6.5 1.98 0 266 184.49 35254 +2006 42 4.5 -6 1.61 0 243 206.61 35434 +2006 43 4.3 -5.5 1.61 0 251 213.79 35615 +2006 44 2.6 -6 0.24 0 179 160.27 35798 +2006 45 4.1 -9 0.5 0 234 204.93 35983 +2006 46 5 -6 1.98 0 222 169.41 36169 +2006 47 9.1 0 6.6 0.02 231 130.28 36356 +2006 48 7.7 -1.4 5.2 0.1 62 117.64 36544 +2006 49 11.3 -1.6 7.75 0.2 306 245.39 36734 +2006 50 12.4 -1.1 8.69 0 367 264.28 36925 +2006 51 12.2 5 10.22 0.54 541 215.68 37117 +2006 52 10.3 -1.1 7.17 0 222 274.12 37310 +2006 53 5.1 -0.2 3.64 0 191.82 155.03 37505 +2006 54 3.6 0.4 2.72 0 190 135.1 37700 +2006 55 3.1 1 2.52 0.58 141.82 61.06 37896 +2006 56 2.3 -1.2 1.34 0.85 30 136.81 38093 +2006 57 1.1 -1.8 0.3 0.09 99.09 203.29 38291 +2006 58 2 -3.6 0.46 0 231.82 313.48 38490 +2006 59 1.6 -10.6 -1.75 0 251.82 384.8 38689 +2006 60 5.1 -10.5 0.81 0 298.18 350.32 38890 +2006 61 2.4 -5.6 0.2 0 227.5 155.51 39091 +2006 62 6.6 -8.1 2.56 0 235.83 306.74 39292 +2006 63 8.6 2.4 6.89 0.11 268.32 155.69 39495 +2006 64 2.4 -1.1 1.44 0.82 114.03 96.26 39697 +2006 65 4.1 -9.1 0.47 0 324.95 342.11 39901 +2006 66 4.9 -8.8 1.13 0 260.83 377.49 40105 +2006 67 4.6 -5.9 1.71 0 300 343.18 40309 +2006 68 8.4 0 6.09 0 316.67 138.01 40514 +2006 69 6.6 0.6 4.95 0.97 118.33 52.37 40719 +2006 70 10.1 0.4 7.43 0 324.17 263.02 40924 +2006 71 4.3 -3.4 2.18 0.14 255 200.15 41130 +2006 72 1 -2 0.18 0.02 290 148.85 41336 +2006 73 1.4 -2.2 0.41 0.01 170.83 128.01 41543 +2006 74 1.2 -1.5 0.46 0.01 195 144.03 41749 +2006 75 2.3 -1.3 1.31 0.06 108.33 134.16 41956 +2006 76 4.4 -0.2 3.14 0 190 175.45 42163 +2006 77 5.1 -1.9 3.17 0 194.17 155.54 42370 +2006 78 10.3 -4.5 6.23 0 360 393.84 42578 +2006 79 13.9 -4.2 8.92 0 590.83 406.98 42785 +2006 80 14.1 -3.1 9.37 0 628.33 335.21 42992 +2006 81 15.6 3.5 12.27 0 560 333.91 43200 +2006 82 10.8 2.7 8.57 0 448.33 317.2 43407 +2006 83 10 -4 6.15 0 471.67 407.69 43615 +2006 84 12.7 -1.3 8.85 0.01 542.5 250.86 43822 +2006 85 15.1 0 10.95 0 515 158.52 44029 +2006 86 20.7 3.7 16.02 0 801.67 344.43 44236 +2006 87 18.7 4 14.66 1.24 636.67 327.34 44443 +2006 88 15.7 6.5 13.17 0.05 510.83 243.75 44650 +2006 89 17.6 1.9 13.28 0 1015 346.56 44857 +2006 90 16.6 6.4 13.8 0.14 515.83 161.57 45063 +2006 91 20.1 2.6 15.29 0 850.83 364.47 45270 +2006 92 19.1 4 14.95 0.01 806.92 386.35 45475 +2006 93 15 5.5 12.39 0.48 461.54 138.9 45681 +2006 94 14.8 1.2 11.06 0 591.54 321.22 45886 +2006 95 12.8 0.2 9.34 0.06 440 138.99 46091 +2006 96 10.7 3.3 8.66 0.01 435.71 172.57 46295 +2006 97 12.5 -1.5 8.65 0 611.43 456.92 46499 +2006 98 16.1 -3.5 10.71 0 775 453.77 46702 +2006 99 18.6 -1 13.21 0 938.57 416.07 46905 +2006 100 19.4 5.4 15.55 0.85 943.57 340.32 47107 +2006 101 15.3 4.5 12.33 1 217.14 192.77 47309 +2006 102 10.5 4.4 8.82 0 578.57 197.76 47510 +2006 103 13.5 3 10.61 0 639.29 274.87 47710 +2006 104 18.4 2.8 14.11 0 693.57 227.1 47910 +2006 105 17.2 0.4 12.58 0 539.29 330.87 48108 +2006 106 13.7 6.3 11.66 1.16 320 107.09 48306 +2006 107 18.1 5.8 14.72 0 656.43 359.76 48504 +2006 108 17.9 5.6 14.52 0.01 577.14 255.82 48700 +2006 109 19.6 8.2 16.47 0.01 989.29 398.59 48895 +2006 110 20.3 7.8 16.86 0 1092.14 428.17 49089 +2006 111 21.3 2.6 16.16 0 1036.43 439.67 49282 +2006 112 22.6 3 17.21 0 1035 333.87 49475 +2006 113 23.9 4 18.43 0.91 1104.29 432.71 49666 +2006 114 23.6 6.1 18.79 0 1087.86 462.29 49855 +2006 115 24.9 7.1 20 0 1357.86 385.46 50044 +2006 116 25 7.2 20.11 0.12 1185 359.8 50231 +2006 117 19.2 12.2 17.27 1.17 212.86 110.61 50417 +2006 118 14.9 12.2 14.16 1.15 117.86 86.86 50601 +2006 119 13.5 7.7 11.9 3.13 98.57 43.02 50784 +2006 120 7.7 5 6.96 1.32 77.14 68.46 50966 +2006 121 14.9 5.6 12.34 0.21 319.29 299.73 51145 +2006 122 17.6 4.5 14 0 367.14 341.92 51324 +2006 123 19.6 5.5 15.72 0 587.14 426.32 51500 +2006 124 18.1 4.5 14.36 0 820 467.39 51674 +2006 125 21 2.6 15.94 0 861.33 389.66 51847 +2006 126 20.6 3.6 15.93 0.09 842.67 423.01 52018 +2006 127 17.5 6.7 14.53 0.06 384.67 245.3 52187 +2006 128 19.8 5.8 15.95 0 674.67 418.84 52353 +2006 129 21.7 3.9 16.81 0 803.33 498.53 52518 +2006 130 21.6 7.1 17.61 0 1060.67 469.25 52680 +2006 131 20.6 4.8 16.26 0 956.67 456.91 52840 +2006 132 23.5 4.5 18.27 0 1217.33 475.32 52998 +2006 133 25.6 6.7 20.4 0.18 1093.33 398.84 53153 +2006 134 21.7 9.1 18.23 1.29 498.67 293.62 53306 +2006 135 22.1 8.1 18.25 0 870.67 476.89 53456 +2006 136 26.1 10.4 21.78 0.2 1018.67 406.36 53603 +2006 137 23.9 13.2 20.96 0.45 509.33 323.19 53748 +2006 138 25.7 7.8 20.78 0.19 848 464.25 53889 +2006 139 23.4 14.2 20.87 1.02 220 100.98 54028 +2006 140 19 12.2 17.13 0.08 362.67 280.95 54164 +2006 141 17.3 13.3 16.2 0.44 266 144.18 54297 +2006 142 25.8 12.3 22.09 0 841.88 468.37 54426 +2006 143 23.1 14 20.6 0.93 960 451.59 54552 +2006 144 16.3 10.4 14.68 1.48 218.75 69.26 54675 +2006 145 20.3 7.9 16.89 0 787.5 437.37 54795 +2006 146 22.7 9.5 19.07 0.05 729.38 335.18 54911 +2006 147 24.7 13.5 21.62 0 898.75 279.8 55023 +2006 148 24.5 12.9 21.31 1.48 388.75 188.3 55132 +2006 149 16.5 10.4 14.82 2.48 120.63 118.17 55237 +2006 150 11.6 9.2 10.94 1.27 113.12 55.98 55339 +2006 151 16.8 4.4 13.39 0.01 585 396.72 55436 +2006 152 17.7 3.1 13.69 0.25 525.63 326 55530 +2006 153 12.1 4.9 10.12 1.26 225.63 86.54 55619 +2006 154 13.4 9.4 12.3 0.21 178.75 95.52 55705 +2006 155 18.4 9.9 16.06 0.26 566.88 314.12 55786 +2006 156 18.2 5 14.57 0.07 655.63 336.42 55863 +2006 157 15.9 9.8 14.22 1.96 315.62 196.02 55936 +2006 158 18.9 7.8 15.85 0 615.62 411.95 56004 +2006 159 20.2 5.6 16.18 0 850.63 489.83 56068 +2006 160 20.7 6.1 16.68 0.36 938.75 478.51 56128 +2006 161 19 10.4 16.63 0.79 381.25 226.95 56183 +2006 162 20.2 10.4 17.5 0 593.75 328.13 56234 +2006 163 25 9.1 20.63 0 1045.63 486.08 56280 +2006 164 25.8 11.5 21.87 0.01 977.5 486.48 56321 +2006 165 25.6 12.5 22 0 1020 469.8 56358 +2006 166 27.2 11.6 22.91 0 1398.13 511.85 56390 +2006 167 29.7 14 25.38 0 1043.13 378.16 56418 +2006 168 28.7 16.1 25.23 0.14 1070 415.34 56440 +2006 169 29.7 17.6 26.37 0 1016.88 381.36 56458 +2006 170 31.7 16.8 27.6 0 1316.88 470.62 56472 +2006 171 31.7 18.8 28.15 0 1660.63 434.8 56480 +2006 172 31.7 17.2 27.71 0 1088.75 373.03 56484 +2006 173 29.4 19.5 26.68 0.48 1311.25 464.44 56482 +2006 174 27.1 17.3 24.41 0 901.87 455.22 56476 +2006 175 29.7 16.3 26.02 0 1258.75 475.97 56466 +2006 176 30.7 16 26.66 0 1287.5 466.74 56450 +2006 177 33.8 20 30 0 1537.5 455.24 56430 +2006 178 31.3 19.5 28.06 0.13 1227.5 456.13 56405 +2006 179 30.9 16.4 26.91 0 1361.87 464.25 56375 +2006 180 28.5 16.5 25.2 3.05 310 201.75 56341 +2006 181 26.4 17.5 23.95 0 672.5 408.64 56301 +2006 182 23.9 16.2 21.78 0.4 625.63 195.71 56258 +2006 183 21.4 15.9 19.89 0.05 431.25 197.86 56209 +2006 184 19.3 17 18.67 0.01 263.75 107.2 56156 +2006 185 24.7 15 22.03 0 850 410.4 56099 +2006 186 26.7 10.4 22.22 0 1257.5 504.61 56037 +2006 187 28.7 12.3 24.19 0 1436.25 487.68 55971 +2006 188 30.5 14.1 25.99 0.27 1431.88 446.38 55900 +2006 189 29.9 18 26.63 0.05 1165 480.33 55825 +2006 190 30.7 15.6 26.55 0 1175 418.4 55746 +2006 191 30.3 16 26.37 0 1203.13 444.56 55663 +2006 192 32.3 17.9 28.34 0 1468.13 459.81 55575 +2006 193 30.9 16.5 26.94 1.29 1270.71 438.32 55484 +2006 194 29.2 16.2 25.63 0 1445.91 407.41 55388 +2006 195 31.3 16.2 27.15 0 1754.68 437.69 55289 +2006 196 25.7 19 23.86 0 761.06 242.76 55186 +2006 197 24.6 12 21.14 0 1104.75 420.55 55079 +2006 198 26.2 9.2 21.52 0 1404.12 487.84 54968 +2006 199 29.1 10 23.85 0 1728.25 499.34 54854 +2006 200 31.5 11.3 25.95 0 2011.06 499.25 54736 +2006 201 32.3 12.6 26.88 0 2081.61 488.68 54615 +2006 202 34 13.8 28.45 0 2301.03 484.34 54490 +2006 203 34.3 16.8 29.49 0 2206.93 446.62 54362 +2006 204 32.7 16.9 28.36 0.03 1933.46 318.24 54231 +2006 205 32.3 17 28.09 1.52 1862.75 311.84 54097 +2006 206 31.5 18.5 27.93 0 1633.87 373.58 53960 +2006 207 32.5 17.9 28.48 0 1837.18 400.95 53819 +2006 208 33.6 17.4 29.15 0 2052.26 421.67 53676 +2006 209 32.9 16 28.25 0.3 2017.69 325.76 53530 +2006 210 31.7 18.3 28.02 0.07 1680.18 280.6 53382 +2006 211 31.3 18.4 27.75 0 1609.49 362.14 53230 +2006 212 31.6 15.6 27.2 0 1835.03 416.86 53076 +2006 213 26.3 17 23.74 0.37 1000.26 211.37 52920 +2006 214 22.2 18.5 21.18 0.01 385.18 91.51 52761 +2006 215 20.4 12.5 18.23 1.43 643.93 191.21 52600 +2006 216 19.2 13.5 17.63 0.4 469.1 143.71 52437 +2006 217 23.3 13.3 20.55 0.14 891.36 237.3 52271 +2006 218 23.8 14.4 21.22 0.48 879.21 226 52103 +2006 219 20.7 15.1 19.16 1.11 502.89 144.01 51934 +2006 220 25.4 15.2 22.59 0.01 1013.7 242.47 51762 +2006 221 24.9 11 21.08 0 1185.7 409.48 51588 +2006 222 24.7 11 20.93 0 1163.55 405.28 51413 +2006 223 22.7 12.1 19.79 0.21 895.14 256.3 51235 +2006 224 16.1 10.8 14.64 2.84 370.9 145.28 51057 +2006 225 19.9 12.2 17.78 0 614.47 270.97 50876 +2006 226 22.4 9.1 18.74 0.88 1005.99 304.09 50694 +2006 227 24.7 11.7 21.13 0 1130.69 391.13 50510 +2006 228 25.7 11.6 21.82 0 1249.04 409.16 50325 +2006 229 29.2 14.3 25.1 0 1556.97 411.03 50138 +2006 230 29.6 19.4 26.8 0 1269.97 314.14 49951 +2006 231 26.9 14 23.35 0 1271.01 388.77 49761 +2006 232 28.4 16 24.99 0.21 1347.48 281.74 49571 +2006 233 24.2 14.1 21.42 0.48 943 255.03 49380 +2006 234 24.2 11.6 20.73 0.12 1080.4 297.68 49187 +2006 235 23.9 12.3 20.71 0 1012.13 377.68 48993 +2006 236 24.8 10.1 20.76 2.08 1213.48 320.77 48798 +2006 237 20.2 14.3 18.58 1.32 509.94 167.21 48603 +2006 238 23.3 10.5 19.78 0 1036.45 403.55 48406 +2006 239 23.3 10.3 19.73 0.86 1045.44 305.3 48208 +2006 240 22.4 11.1 19.29 0.5 915.94 282.11 48010 +2006 241 21.6 14 19.51 0.26 669.44 210.85 47811 +2006 242 18.2 11.4 16.33 0.49 508.67 200.11 47611 +2006 243 21.7 8.4 18.04 0 966.64 414.04 47410 +2006 244 23.7 5 18.56 0 1264.41 458.03 47209 +2006 245 24.9 7.9 20.22 0 1304.94 436.05 47007 +2006 246 26.9 10.8 22.47 0 1425.2 310.62 46805 +2006 247 30.1 14.9 25.92 0 1651.04 334.9 46601 +2006 248 28.3 15 24.64 0 1395.41 361.03 46398 +2006 249 25.2 13.8 22.07 0 1076.15 329.8 46194 +2006 250 26.7 13.6 23.1 0.09 1268.17 265.7 45989 +2006 251 21.8 14.9 19.9 0.04 629.6 165.86 45784 +2006 252 21.7 6.3 17.47 0 1040.24 399.62 45579 +2006 253 22.9 5.2 18.03 0 1182.94 416.2 45373 +2006 254 22.9 5 17.98 0 1188.04 411.25 45167 +2006 255 23.6 6.9 19.01 0 1202.77 391.43 44961 +2006 256 23.7 5.5 18.7 0 1251.98 402 44755 +2006 257 25.2 6.3 20 0 1383.22 400.3 44548 +2006 258 21.5 12.1 18.91 0.17 773.59 193.98 44341 +2006 259 18.2 15.2 17.38 0.31 256.73 70.81 44134 +2006 260 23 12.7 20.17 0.02 893.67 207.95 43927 +2006 261 19.7 15.3 18.49 2.32 389.74 98.32 43719 +2006 262 19.6 15 18.34 0.3 402.37 103.68 43512 +2006 263 24.5 14 21.61 0 983.24 278.49 43304 +2006 264 22.7 8.9 18.91 0 1043.55 338.02 43097 +2006 265 23.1 9 19.22 0 1079.49 337.34 42890 +2006 266 22.8 7.7 18.65 0 1097.9 347.9 42682 +2006 267 23.2 7.1 18.77 0 1157.01 351.66 42475 +2006 268 23.2 8 19.02 0 1126.78 337.28 42268 +2006 269 24 9.5 20.01 0 1152.15 322.72 42060 +2006 270 22.9 8.8 19.02 0.01 1067.3 236.84 41854 +2006 271 24.2 10.7 20.49 0.2 1122.56 224.26 41647 +2006 272 23.6 8.5 19.45 0 1149.07 315.82 41440 +2006 273 23.7 9.8 19.88 0 1108.5 296.42 41234 +2006 274 24.8 10.1 20.76 0 1213.48 302.95 41028 +2006 275 23.1 11.1 19.8 0 987.6 266.51 40822 +2006 276 25.2 15 22.4 0.16 1002.68 172.09 40617 +2006 277 21.2 13.2 19 0.66 679.64 144.99 40412 +2006 278 18.4 10.4 16.2 0 580.05 198.16 40208 +2006 279 19.6 3.4 15.15 0 941.11 319.36 40003 +2006 280 19.5 3.5 15.1 0.33 930.61 234.78 39800 +2006 281 18.7 7.6 15.65 0 784.09 396.42 39597 +2006 282 19.3 1.9 14.52 0 640.91 358.06 39394 +2006 283 20.1 2.6 15.29 0 586.36 336.29 39192 +2006 284 20 3.3 15.41 0 566.36 295.4 38991 +2006 285 19.7 4.4 15.49 0 542.73 324.66 38790 +2006 286 18.8 5.3 15.09 0 411.82 234.88 38590 +2006 287 19.2 8.8 16.34 0 508.18 226.2 38391 +2006 288 19.1 4.5 15.09 0 278.18 301.34 38193 +2006 289 15.6 4.9 12.66 0 580.91 320.72 37995 +2006 290 14.8 -2 10.18 0 475.45 324.57 37799 +2006 291 15.2 -2.5 10.33 0 486.36 319.77 37603 +2006 292 17.5 -1.5 12.28 0 443.64 226.11 37408 +2006 293 17.7 8.6 15.2 0 508.18 144.1 37214 +2006 294 22.2 5.7 17.66 0 602.73 242.6 37022 +2006 295 20.5 8.6 17.23 0 491.82 254.39 36830 +2006 296 22.3 10.1 18.95 0 753.64 239.08 36640 +2006 297 20.8 14.3 19.01 1.62 442.73 53.54 36451 +2006 298 19.3 8.5 16.33 0 333.64 221.42 36263 +2006 299 20.7 8.1 17.23 0.03 439.09 253.39 36076 +2006 300 13.9 8.2 12.33 0.02 27 96.89 35891 +2006 301 17.7 8.7 15.23 0.01 277 111.58 35707 +2006 302 21.4 11 18.54 0.04 282 84.79 35525 +2006 303 18.4 3.1 14.19 0 393 298.81 35345 +2006 304 12.3 -2.5 8.23 0 421 277.62 35166 +2006 305 8.3 4.5 7.26 0.96 138 52.49 34988 +2006 306 6.1 -1.9 3.9 0 360 271.74 34813 +2006 307 4.7 -5.8 1.81 0.05 112 169.71 34639 +2006 308 6.2 -6 2.85 0 174 120.12 34468 +2006 309 13.2 -0.2 9.52 0 720 133.27 34298 +2006 310 12.7 2.6 9.92 0 545.56 71.95 34130 +2006 311 14.2 -2.3 9.66 0 403.33 247.07 33964 +2006 312 13.9 -2.9 9.28 0 334.44 236.02 33801 +2006 313 18.4 -1.1 13.04 0 646.67 150 33640 +2006 314 11.9 0.9 8.88 0 588.89 225.83 33481 +2006 315 9.1 -3.9 5.53 0 297.78 125.58 33325 +2006 316 10.6 1 7.96 0.12 202.22 106.94 33171 +2006 317 10.6 -0.8 7.46 0 328.89 125.68 33019 +2006 318 12 2.9 9.5 0 428.89 98.4 32871 +2006 319 17.4 2 13.16 0 365.56 175.04 32725 +2006 320 19.7 -0.5 14.15 0 583.33 216.92 32582 +2006 321 14.3 2.3 11 0 135.56 197.23 32441 +2006 322 19.1 3.9 14.92 0 488.89 143.04 32304 +2006 323 13.5 4.7 11.08 0.01 137.78 135.34 32170 +2006 324 9.4 3 7.64 0.58 41.11 32.6 32039 +2006 325 9.6 3.5 7.92 0.28 68.89 116.13 31911 +2006 326 7.7 5.1 6.99 2.24 32.22 21.53 31786 +2006 327 12.6 5.4 10.62 0 352.22 105.46 31665 +2006 328 12 0.4 8.81 0 207.78 175.21 31547 +2006 329 17.9 0.9 13.22 0 491.11 171.05 31433 +2006 330 14.3 4.4 11.58 0.07 23.33 46.53 31322 +2006 331 9.2 7.8 8.81 0.06 34.44 28.49 31215 +2006 332 9 6.8 8.39 0.01 20 42.33 31112 +2006 333 8.6 6.8 8.1 0.01 34.44 34.6 31012 +2006 334 10 6.6 9.07 0 115.56 42.84 30917 +2006 335 8.6 6.1 7.91 0 152.22 65.99 30825 +2006 336 7.2 -0.1 5.19 0 208.89 39.44 30738 +2006 337 6.7 -0.5 4.72 0 73.33 137.92 30654 +2006 338 5.7 -0.6 3.97 0 44.44 62.77 30575 +2006 339 10.3 -0.1 7.44 0 161.11 106.42 30500 +2006 340 16.4 0.4 12 0 392.22 164.81 30430 +2006 341 13.6 6.5 11.65 0 276.67 127.73 30363 +2006 342 16.2 0.9 11.99 0 470 156.38 30301 +2006 343 15.2 9.8 13.72 0.7 401.11 75.75 30244 +2006 344 10.7 4.9 9.11 0.47 91.11 52.69 30191 +2006 345 8.6 1.1 6.54 0 64.44 122.74 30143 +2006 346 5.2 -2.5 3.08 0 77.78 130.83 30099 +2006 347 4.7 -2.6 2.69 0 11.25 95.7 30060 +2006 348 3.7 -1.8 2.19 0 10 113.42 30025 +2006 349 0.3 -1.9 -0.3 0 10 41.85 29995 +2006 350 0.6 -0.9 0.19 0 10 34.95 29970 +2006 351 1 -0.6 0.56 0.58 10 17.51 29950 +2006 352 5.1 1 3.97 0 128.75 43.77 29934 +2006 353 3.7 1.7 3.15 0 213.75 72.58 29924 +2006 354 6.7 -3 4.03 0.01 232.5 138.57 29918 +2006 355 5.9 1 4.55 0.01 137.5 72.95 29916 +2006 356 7.2 -0.4 5.11 0 233.75 108.32 29920 +2006 357 5.7 -3.4 3.2 0 93.75 119.08 29928 +2006 358 1.7 -2.6 0.52 0 27.5 18.62 29941 +2006 359 6.9 -0.4 4.89 0 212.5 111.71 29959 +2006 360 5.5 -2.3 3.36 0 253.75 157.03 29982 +2006 361 4.7 -6 1.76 0 147.5 187.85 30009 +2006 362 -0.2 -6.2 -1.85 0 20 64.18 30042 +2006 363 4.7 -3.9 2.34 0 95 103.96 30078 +2006 364 1.9 -5.5 -0.14 0 85 161.17 30120 +2006 365 2.1 -1.6 1.08 0 10 61.05 30166 +2007 1 6.9 -2.6 4.29 0.08 193.75 37.3 30217 +2007 2 9.2 -0.3 6.59 0 137.5 70.17 30272 +2007 3 9.5 -3 6.06 0 342.5 104.96 30331 +2007 4 7.2 -2 4.67 0.14 355 83.05 30396 +2007 5 11.2 -1.6 7.68 0 308.75 95.59 30464 +2007 6 11.5 0.9 8.59 0 461.25 90.86 30537 +2007 7 14.4 -0.1 10.41 0 445 142.72 30614 +2007 8 9.2 -3 5.84 0 142.5 129.1 30695 +2007 9 11.2 -1.7 7.65 0.02 245 119.59 30781 +2007 10 13.8 1.4 10.39 0 377.5 146.28 30870 +2007 11 16 1 11.88 0.01 500 172.59 30964 +2007 12 12.4 4 10.09 0 651.11 185.24 31061 +2007 13 13.8 -0.7 9.81 0 745.56 157.79 31162 +2007 14 15.1 -2.3 10.32 0 411.11 164.25 31268 +2007 15 11.9 -2.8 7.86 0 387.78 184.71 31376 +2007 16 6.7 -4.5 3.62 0 152.22 173 31489 +2007 17 10.7 -2.5 7.07 0 298.89 170.35 31605 +2007 18 11.9 -2.1 8.05 0.01 356.67 97.03 31724 +2007 19 11.3 7.6 10.28 1.51 88 40.76 31847 +2007 20 8.4 2.7 6.83 0.02 83 67.19 31974 +2007 21 11.8 0.1 8.58 0 117 167.52 32103 +2007 22 8.5 3.8 7.21 0.1 84 35.09 32236 +2007 23 3.8 1.3 3.11 1.28 17 11.54 32372 +2007 24 4.4 -1.1 2.89 0.92 29 81.99 32510 +2007 25 1.1 -4 -0.3 0 48 157.82 32652 +2007 26 0.9 -7.4 -1.38 0 146 213.21 32797 +2007 27 5 -9.4 1.04 0.06 181 193.92 32944 +2007 28 7.7 -4.5 4.35 0 181 155.37 33094 +2007 29 11.1 -2.9 7.25 0 468 118.01 33247 +2007 30 13.1 -1.6 9.06 0 283 208.1 33402 +2007 31 10 -3.4 6.31 0 298 220.66 33559 +2007 32 12.9 -1.4 8.97 0 605 232.64 33719 +2007 33 10.2 -3.5 6.43 0 386 217.86 33882 +2007 34 10.1 -0.8 7.1 0.06 449 207.74 34046 +2007 35 9.7 -3.5 6.07 0 406 235.6 34213 +2007 36 12.5 -5.2 7.63 0 507 245.37 34382 +2007 37 9.9 -1.3 6.82 0.8 287 216.04 34552 +2007 38 6.3 3.2 5.45 0.03 60 68.64 34725 +2007 39 13 1.5 9.84 0 386 246.68 34900 +2007 40 11.2 4.4 9.33 0.08 220 155.8 35076 +2007 41 12.2 -0.1 8.82 0 73.75 251.58 35254 +2007 42 8.7 -0.6 6.14 0 146 157.33 35434 +2007 43 12.7 0.3 9.29 1.1 290 182.91 35615 +2007 44 13.6 5.3 11.32 0 295 111.44 35798 +2007 45 13.7 -1.1 9.63 0 589 286.59 35983 +2007 46 10.2 3.5 8.36 0.26 170 100 36169 +2007 47 6.7 1.8 5.35 0 188 52.15 36356 +2007 48 8.6 1.4 6.62 0 249 183.08 36544 +2007 49 6 -1.6 3.91 0 202 222.09 36734 +2007 50 4.4 -2.8 2.42 0 36 142.21 36925 +2007 51 12.4 -1.5 8.58 0 270 266.01 37117 +2007 52 4.8 -1.9 2.96 0 14 92.25 37310 +2007 53 10.7 4 8.86 0 121.82 161.55 37505 +2007 54 11.8 1.7 9.02 0 303.64 177.47 37700 +2007 55 9.2 2.9 7.47 0 167.27 157.49 37896 +2007 56 6.2 -0.1 4.47 1.7 162.73 137.82 38093 +2007 57 6.4 0.5 4.78 0.02 60 92.16 38291 +2007 58 11 0.1 8 0.04 295.45 255.99 38490 +2007 59 11.5 3.6 9.33 0.01 244.55 121.38 38689 +2007 60 15.4 2 11.72 0 400 146.2 38890 +2007 61 13 5.2 10.86 0.1 129.17 64.1 39091 +2007 62 9.3 0.9 6.99 0.03 79.17 78.16 39292 +2007 63 12.9 0.9 9.6 0 555 332.36 39495 +2007 64 15.4 -2.8 10.4 0 525.83 350.84 39697 +2007 65 16.9 1.6 12.69 0 587.5 319.14 39901 +2007 66 16.9 7.2 14.23 0.02 660.83 235.8 40105 +2007 67 12.8 5.7 10.85 1.25 60.83 53.16 40309 +2007 68 11.6 6.8 10.28 0 275.83 134.03 40514 +2007 69 13.4 2.9 10.51 0 415 216.58 40719 +2007 70 13 4.9 10.77 0 530 341.51 40924 +2007 71 15.8 -2.4 10.8 0 524.17 369.74 41130 +2007 72 18.3 -1 12.99 0 631.67 356.11 41336 +2007 73 19.7 -0.3 14.2 0 715.83 359.67 41543 +2007 74 14.7 5.3 12.12 0 614.17 386.01 41749 +2007 75 16.4 -1.6 11.45 0 616.67 355.71 41956 +2007 76 19.6 -1.1 13.91 0 766.67 292.52 42163 +2007 77 19.5 2.4 14.8 0.05 959.17 342.17 42370 +2007 78 15.3 1.6 11.53 4.37 40 42.96 42578 +2007 79 4 0.4 3.01 0.3 45.83 147.06 42785 +2007 80 5.7 -2.1 3.56 0 192.5 144.93 42992 +2007 81 8.7 -2.5 5.62 0 370 297.01 43200 +2007 82 10.5 -0.5 7.47 1.83 360.83 141.28 43407 +2007 83 6.8 4.3 6.11 0.5 68.33 52.25 43615 +2007 84 14.2 3.2 11.17 0 415 360.5 43822 +2007 85 13.9 -0.1 10.05 0 503.33 275.79 44029 +2007 86 13.3 1.4 10.03 0 555.83 335.87 44236 +2007 87 13.6 -1.6 9.42 0.01 599.17 334.95 44443 +2007 88 12 5.5 10.21 0 235 217.92 44650 +2007 89 13.4 -0.8 9.5 0 377.5 316.59 44857 +2007 90 15.5 6.3 12.97 0 693.33 313.06 45063 +2007 91 17 1.1 12.63 0 748.33 310.98 45270 +2007 92 17.4 3.7 13.63 0 921.54 422.46 45475 +2007 93 18.6 1 13.76 0.31 706.92 358.74 45681 +2007 94 12.1 5.8 10.37 0 364.62 250.86 45886 +2007 95 15.4 -2.1 10.59 0 726.15 454.67 46091 +2007 96 19.8 -0.3 14.27 0 940.71 424.47 46295 +2007 97 19.6 7.2 16.19 0 862.14 408.77 46499 +2007 98 17.7 7 14.76 0 808.57 438.68 46702 +2007 99 21.2 0.1 15.4 0 875.71 405.71 46905 +2007 100 23.2 2.5 17.51 0 1151.43 345.99 47107 +2007 101 19.9 4.1 15.56 0 792.14 407.53 47309 +2007 102 23.2 3.1 17.67 0 951.43 444.65 47510 +2007 103 24.5 3.9 18.84 0 1165 453.56 47710 +2007 104 24.4 4.6 18.95 0 1283.57 447.83 47910 +2007 105 22.2 3.3 17 0 1173.57 478.19 48108 +2007 106 19.6 2.9 15.01 0 1036.43 472.54 48306 +2007 107 22.2 1.7 16.56 0 1271.43 467.79 48504 +2007 108 18.4 3.7 14.36 0 629.29 225.05 48700 +2007 109 17.1 2.4 13.06 0 815 433.28 48895 +2007 110 22.7 1.1 16.76 0 1036.43 455.28 49089 +2007 111 17.9 6.6 14.79 0 750.71 456.25 49282 +2007 112 19.7 0.9 14.53 0 943.57 470.74 49475 +2007 113 23.7 1.4 17.57 0 1362.14 463.65 49666 +2007 114 21.1 7.7 17.41 0 934.29 216.47 49855 +2007 115 21.4 5.8 17.11 0 928.57 447.66 50044 +2007 116 22.7 3.4 17.39 0 984.29 426.32 50231 +2007 117 23.7 4 18.28 0 1332.14 456.99 50417 +2007 118 24.6 3 18.66 0 1575.71 487.58 50601 +2007 119 25.1 5.2 19.63 0 1190 451.73 50784 +2007 120 18.2 8.7 15.59 0 830.71 383.03 50966 +2007 121 17.9 0.6 13.14 0 896.43 475.5 51145 +2007 122 17.6 6.8 14.63 0 915.71 452.71 51324 +2007 123 21.2 2.5 16.06 0.86 960 336.31 51500 +2007 124 18.2 11.9 16.47 1.24 562.14 285.03 51674 +2007 125 20.2 12.2 18 0.54 317.33 283.4 51847 +2007 126 20.5 11.9 18.13 0.01 330.67 298.94 52018 +2007 127 24.2 10.9 20.54 0 971.33 479.31 52187 +2007 128 23.2 10.2 19.63 1.34 633.33 272.85 52353 +2007 129 17.5 12.6 16.15 0.12 159.33 180.92 52518 +2007 130 23.1 12.3 20.13 0 696.67 408.32 52680 +2007 131 27.8 10.7 23.1 0.5 1278.67 497.09 52840 +2007 132 23.3 12.7 20.39 0.09 370 290.75 52998 +2007 133 26.2 11.5 22.16 0 884 441.22 53153 +2007 134 29.6 16.6 26.03 0 1619.33 486.66 53306 +2007 135 25.6 12.8 22.08 1 404.67 102.01 53456 +2007 136 15.9 6 13.18 0.12 433.33 256.53 53603 +2007 137 19.1 5 15.22 0.44 490.67 402.78 53748 +2007 138 17.7 7 14.76 0 732 503.05 53889 +2007 139 21.2 4.5 16.61 0 745.33 373.16 54028 +2007 140 25.2 9.3 20.83 0 712.67 399.24 54164 +2007 141 27.1 10.6 22.56 0 994.67 457.72 54297 +2007 142 30.3 12.3 25.35 0 1402.5 470.58 54426 +2007 143 28.7 15.2 24.99 0 1190.62 475.37 54552 +2007 144 28.7 15.3 25.02 0 1085.62 444.23 54675 +2007 145 30.7 14.3 26.19 0 1440 459.73 54795 +2007 146 29.6 15.2 25.64 0 1277.5 458.05 54911 +2007 147 28.2 15 24.57 0 1225 413.09 55023 +2007 148 23.2 14.6 20.83 1.1 601.88 249.59 55132 +2007 149 21.1 11 18.32 0.25 536.87 346.33 55237 +2007 150 14.8 10.5 13.62 0.01 316.25 121.06 55339 +2007 151 21.4 8 17.72 0 838.75 385.98 55436 +2007 152 24.7 6.4 19.67 0 971.88 430.4 55530 +2007 153 22.8 12.9 20.08 0.22 426.88 281.44 55619 +2007 154 25 11.1 21.18 0.77 676.88 368.37 55705 +2007 155 24 15.5 21.66 0.85 451.25 283.78 55786 +2007 156 23.7 16 21.58 0.33 758.93 211.05 55863 +2007 157 25 14.6 22.14 0.14 439.38 260.34 55936 +2007 158 25.8 13.7 22.47 0.17 745 429.77 56004 +2007 159 26.9 12.6 22.97 0.01 723.12 343.52 56068 +2007 160 28.6 12.4 24.15 0 1183.75 410.96 56128 +2007 161 28.8 13.5 24.59 0 1138.13 389.75 56183 +2007 162 28.8 16.5 25.42 0 1289.38 438.46 56234 +2007 163 28.1 17.9 25.3 0 938.75 327.01 56280 +2007 164 28.7 13.4 24.49 0 1271.25 455.33 56321 +2007 165 29.7 13.9 25.36 0 1225 468.13 56358 +2007 166 30.2 15.5 26.16 0 1289.38 453.08 56390 +2007 167 27.7 17.6 24.92 0 1270 434.68 56418 +2007 168 28.4 14.1 24.47 0 1112.5 381.97 56440 +2007 169 29.6 15.6 25.75 0.41 1385.63 404.18 56458 +2007 170 29.8 18.1 26.58 0.02 1170.63 406.16 56472 +2007 171 32.5 14.5 27.55 0 1501.25 439.76 56480 +2007 172 33.9 19.1 29.83 0 1723.13 432.73 56484 +2007 173 31.2 16.3 27.1 0.04 1480.62 384.87 56482 +2007 174 28.7 13.1 24.41 0.02 995 256.11 56476 +2007 175 29.2 15.8 25.52 0 1397.5 382.87 56466 +2007 176 32.7 14.5 27.7 0 2018.75 463.25 56450 +2007 177 30 17.1 26.45 0 1099.37 268.84 56430 +2007 178 20 13.5 18.21 0.5 436.88 153.22 56405 +2007 179 22 12.7 19.44 0 650 340.84 56375 +2007 180 25.2 10.1 21.05 0.01 1046.25 348.7 56341 +2007 181 25.4 14.7 22.46 0.03 955.63 325.52 56301 +2007 182 29.4 12 24.61 0 1591.25 467.97 56258 +2007 183 31.5 14.4 26.8 0.07 1837.5 447.11 56209 +2007 184 28.2 13.8 24.24 0 1041.88 415.4 56156 +2007 185 25.2 13.1 21.87 1.27 283.75 63.48 56099 +2007 186 23.9 11.5 20.49 0 1028.13 428.09 56037 +2007 187 26.4 10.9 22.14 0 1391.25 319.72 55971 +2007 188 28.8 11.6 24.07 0.05 1460.62 444.62 55900 +2007 189 29.2 17 25.84 0.19 1520.63 408.23 55825 +2007 190 31.3 16.2 27.15 2.95 1565 403.79 55746 +2007 191 26.9 12 22.8 0.31 340 214.83 55663 +2007 192 21.4 7.1 17.47 0.04 688.12 324.22 55575 +2007 193 23.7 8.4 19.49 0 943.75 295.43 55484 +2007 194 27 11.5 22.74 0 1347.5 391.98 55388 +2007 195 31.2 11.8 25.87 0 1611.88 479.37 55289 +2007 196 33.2 15 28.2 0 1751.87 470.96 55186 +2007 197 34.5 17.6 29.85 0 2331.87 499.11 55079 +2007 198 37.2 14.7 31.01 0 2902.5 480.61 54968 +2007 199 37.1 15.4 31.13 0 2647.5 468.23 54854 +2007 200 36.2 18.8 31.42 0 2468.12 450.45 54736 +2007 201 38.5 17.5 32.73 0 2975 473.89 54615 +2007 202 35 16.3 29.86 0 2425 470.8 54490 +2007 203 34.7 20.5 30.8 0 2460 487.16 54362 +2007 204 31.9 11.5 26.29 0 1942.5 487.4 54231 +2007 205 29.8 16.4 26.12 0.61 1393.12 252.09 54097 +2007 206 27.9 12 23.53 0 1416.88 420.2 53960 +2007 207 28.8 10 23.63 0 1720 513.95 53819 +2007 208 32.2 11.1 26.4 0.04 1592.5 424.44 53676 +2007 209 32.7 18.9 28.91 0.58 1348.67 367.93 53530 +2007 210 28.2 18 25.4 1.66 1148.57 334.91 53382 +2007 211 24.8 13.9 21.8 1.46 130.71 61.7 53230 +2007 212 23.2 7.9 18.99 0 970.71 417.34 53076 +2007 213 24 8.5 19.74 0 1263.57 502.88 52920 +2007 214 27.6 7.5 22.07 0 1537.86 479.02 52761 +2007 215 24.5 12.1 21.09 0.16 539.29 131.78 52600 +2007 216 24.7 12.1 21.23 0 1334.29 452.59 52437 +2007 217 26.2 10.5 21.88 0 1454.29 474.58 52271 +2007 218 29.2 10.1 23.95 0 1590.71 438.49 52103 +2007 219 31 12.5 25.91 0.29 1851.43 435.58 51934 +2007 220 29.6 15 25.59 0 1395.71 346.88 51762 +2007 221 30.5 15.2 26.29 1.7 1456.07 330.99 51588 +2007 222 22.5 15.3 20.52 0.14 545.71 273.38 51413 +2007 223 21.3 15.5 19.7 0.62 353.57 167.48 51235 +2007 224 25.2 16 22.67 0.02 459.29 228.34 51057 +2007 225 28.6 13.9 24.56 0 1075 421.39 50876 +2007 226 28.9 12.9 24.5 0 1361.43 468.94 50694 +2007 227 30.5 14.1 25.99 0 1365 475.27 50510 +2007 228 32.2 16.1 27.77 0 1769.29 456.32 50325 +2007 229 27.6 19.7 25.43 0.23 1183.57 450.1 50138 +2007 230 26.4 12.6 22.61 0 1246.43 455.57 49951 +2007 231 25.8 15.2 22.89 0 563.57 240.32 49761 +2007 232 23 13.7 20.44 3.84 237.86 147.35 49571 +2007 233 25.7 14.3 22.57 0.22 919.29 412.31 49380 +2007 234 27.2 16.5 24.26 0.17 812.86 372.67 49187 +2007 235 29.3 17.5 26.06 0.27 1083.57 399.38 48993 +2007 236 28.7 15.3 25.02 0 1006.43 430.14 48798 +2007 237 28.8 16.9 25.53 0 1394.29 376.98 48603 +2007 238 29.8 14.7 25.65 0 1489.29 358.34 48406 +2007 239 30.1 14.1 25.7 0 1735.71 469.85 48208 +2007 240 23.1 15.3 20.96 0.01 877.14 334.8 48010 +2007 241 19.8 14.5 18.34 2.83 161.43 95.5 47811 +2007 242 15.9 12.2 14.88 0.3 120.71 69.06 47611 +2007 243 21.2 9.4 17.95 0 485.71 294.53 47410 +2007 244 24 9.7 20.07 0 701.43 243.51 47209 +2007 245 22.3 9.8 18.86 0 783.08 367.94 47007 +2007 246 24.6 11.8 21.08 1.84 960 379.1 46805 +2007 247 19.6 11.4 17.34 0 293.08 119.45 46601 +2007 248 14.5 7.6 12.6 0.56 408.46 226.87 46398 +2007 249 11.3 8 10.39 2.45 140.77 68.09 46194 +2007 250 12.7 8.9 11.65 2.27 72.31 64.11 45989 +2007 251 18.6 11.6 16.68 0 558.46 194.52 45784 +2007 252 21.2 9.3 17.93 0 496.15 146.35 45579 +2007 253 20.4 6.5 16.58 0.4 560 237.4 45373 +2007 254 19.4 11.9 17.34 0.22 496.92 328.46 45167 +2007 255 20.9 6.5 16.94 0 550.77 198.1 44961 +2007 256 20.5 8.6 17.23 0 789.17 366.08 44755 +2007 257 22.6 6.1 18.06 0.02 785 415.79 44548 +2007 258 23.1 10.4 19.61 0 747.5 275.97 44341 +2007 259 23.4 8.1 19.19 0 773.33 354.45 44134 +2007 260 25.5 8.9 20.93 0 755.83 315.75 43927 +2007 261 21.7 12 19.03 3.86 303.33 73.6 43719 +2007 262 17.6 6.3 14.49 0 598.33 397.44 43512 +2007 263 17.1 1.7 12.87 0 609.17 406.1 43304 +2007 264 18.7 2 14.11 0 685.83 439.28 43097 +2007 265 20 2 15.05 0 753.33 427.27 42890 +2007 266 20.4 3.4 15.72 0 725.83 355.86 42682 +2007 267 21.2 4.8 16.69 0 790.83 392.69 42475 +2007 268 21 5.3 16.68 0 590.83 329.44 42268 +2007 269 16.7 12.3 15.49 0.25 401.67 184.18 42060 +2007 270 15.7 11.4 14.52 3.89 155.83 131.57 41854 +2007 271 17.5 10.1 15.47 0.27 385 341.85 41647 +2007 272 20.6 9.2 17.47 0 681.67 363.93 41440 +2007 273 21.9 4.4 17.09 0 723.33 377.86 41234 +2007 274 22.2 4.5 17.33 0 745 364.03 41028 +2007 275 21.9 5.3 17.34 0 712.73 303.58 40822 +2007 276 22.8 8.9 18.98 0 405.45 264.39 40617 +2007 277 18.5 11.2 16.49 0 168.18 135.84 40412 +2007 278 18.5 9.6 16.05 0.43 133.64 119.63 40208 +2007 279 16 11.1 14.65 0 321.82 146.94 40003 +2007 280 17 6.5 14.11 0 409.09 309.62 39800 +2007 281 18.7 1.7 14.02 0 563.64 370.51 39597 +2007 282 17.6 2.9 13.56 0 430.91 326.98 39394 +2007 283 15.2 3.7 12.04 0 325.45 240.46 39192 +2007 284 16.7 7.9 14.28 0 491.82 246.49 38991 +2007 285 17.9 2.9 13.77 0.08 432.73 253.04 38790 +2007 286 13.9 6.5 11.87 0 491.82 224.09 38590 +2007 287 12.9 -1.6 8.91 0 578.18 357.19 38391 +2007 288 14.5 -2.5 9.82 0 621.82 343.2 38193 +2007 289 17.1 -1.7 11.93 0 596.36 321.68 37995 +2007 290 17.9 0.1 13 0 610.91 316.83 37799 +2007 291 10.5 1.9 8.13 0.49 193.64 67.16 37603 +2007 292 12.3 2.2 9.52 0 567.27 257.49 37408 +2007 293 6.5 -2.8 3.94 0.05 231.82 92.3 37214 +2007 294 7.2 1.2 5.55 0.03 203.64 89.53 37022 +2007 295 7.5 4 6.54 1.56 252.73 58.24 36830 +2007 296 6.9 4.7 6.3 1.7 175.45 46.39 36640 +2007 297 7.6 4.3 6.69 0.07 93.64 53.82 36451 +2007 298 9.9 6.7 9.02 0.1 149.09 60.95 36263 +2007 299 8.3 5.6 7.56 0.31 131.23 39.07 36076 +2007 300 10 6 8.9 0.09 205.05 77.54 35891 +2007 301 8.2 7.1 7.9 1.53 56.5 22.77 35707 +2007 302 13 7.7 11.54 0 309.53 82.83 35525 +2007 303 10.2 7.7 9.51 0.34 137.27 65.95 35345 +2007 304 13.9 7.3 12.09 0 387.48 263.19 35166 +2007 305 12.8 0.5 9.42 0 546.98 281.13 34988 +2007 306 15.3 -0.8 10.87 0 724.87 216.53 34813 +2007 307 15.3 7.8 13.24 0 462.63 135.2 34639 +2007 308 12 6.5 10.49 0.22 300.45 90.08 34468 +2007 309 10.6 2.2 8.29 0 378.01 216.1 34298 +2007 310 6.6 -2.2 4.18 0 221.11 98.32 34130 +2007 311 10.1 -1.8 6.83 0.02 514.44 184.46 33964 +2007 312 13.9 -0.3 10 0.01 503.33 90.99 33801 +2007 313 8.6 1 6.51 0.72 173.33 23.34 33640 +2007 314 10.5 -1.5 7.2 0 518.89 167.46 33481 +2007 315 11.2 0.2 8.17 0.34 274.44 136.77 33325 +2007 316 10.1 -0.3 7.24 0 537.78 229.26 33171 +2007 317 7.8 -1.6 5.21 0 240 193.75 33019 +2007 318 5.7 -0.7 3.94 0 176.67 82.85 32871 +2007 319 3.4 1.9 2.99 0 257.78 57.03 32725 +2007 320 3.1 0.4 2.36 0 255.56 73.84 32582 +2007 321 2.7 -0.7 1.77 0.32 194.44 85.72 32441 +2007 322 3.2 0 2.32 0.78 70 58.96 32304 +2007 323 2.7 0.4 2.07 0 92.22 127.99 32170 +2007 324 1.5 -1.6 0.65 0 140 82.81 32039 +2007 325 8.2 -0.6 5.78 0 241.11 175.12 31911 +2007 326 14.6 -0.6 10.42 0 348.89 175.19 31786 +2007 327 16.2 10.9 14.74 0 685.56 140.65 31665 +2007 328 13.8 6.2 11.71 0 323.33 148.96 31547 +2007 329 7.5 3.5 6.4 0.8 172.22 31.58 31433 +2007 330 8.3 0.4 6.13 0 412.22 178.61 31322 +2007 331 5.1 -2.3 3.06 0 191.11 93.55 31215 +2007 332 5.1 -5.1 2.29 0 262.22 199.42 31112 +2007 333 4.2 -8.9 0.6 0 278.89 214.31 31012 +2007 334 4.7 -5.4 1.92 0 178.89 133.97 30917 +2007 335 8.5 -1.6 5.72 0.01 282.22 168.24 30825 +2007 336 8.6 -1.7 5.77 0.05 186.67 133.45 30738 +2007 337 11.2 0.8 8.34 0.44 377.78 26.38 30654 +2007 338 4.5 -1.9 2.74 0.02 236.67 59.68 30575 +2007 339 8.4 -3 5.27 0 361.11 150.03 30500 +2007 340 9.3 -1.5 6.33 0 365.56 152.58 30430 +2007 341 4.2 -1.1 2.74 1.71 330 70.54 30363 +2007 342 8.9 2.2 7.06 0 243.33 96.5 30301 +2007 343 5.8 -1.8 3.71 0.28 232.22 101.34 30244 +2007 344 5.6 1.9 4.58 0 128.89 55.81 30191 +2007 345 7.8 0.3 5.74 0.56 191.11 61.33 30143 +2007 346 6 3.9 5.42 0.82 167.78 22.87 30099 +2007 347 6.1 2.5 5.11 0 346.25 101.13 30060 +2007 348 2.5 -1.9 1.29 0.33 120 46.98 30025 +2007 349 0.8 -3.5 -0.38 0.09 162.5 100.09 29995 +2007 350 0.7 -1.3 0.15 0.03 126.25 85.6 29970 +2007 351 -0.7 -2.6 -1.22 0.02 145 56.13 29950 +2007 352 -2.2 -7.8 -3.74 0 65 61.84 29934 +2007 353 -2 -11.2 -4.53 0 96.25 74.46 29924 +2007 354 -2.5 -4.6 -3.08 0 60 49.14 29918 +2007 355 -4.4 -5.9 -4.81 0 60 46.53 29916 +2007 356 -4.7 -6.1 -5.09 0 60 40.07 29920 +2007 357 -4.2 -5.1 -4.45 0 60 34.69 29928 +2007 358 -2.3 -5.5 -3.18 0 60 32.75 29941 +2007 359 -2.2 -4.6 -2.86 0.03 63.75 50.43 29959 +2007 360 -1.3 -4.5 -2.18 0 70 37.29 29982 +2007 361 -1.4 -2.5 -1.7 0 70 31.62 30009 +2007 362 -2.5 -4 -2.91 0 62.5 28.88 30042 +2007 363 -3.3 -4.4 -3.6 0 60 26.18 30078 +2007 364 -4.1 -5.1 -4.38 0 60 29.42 30120 +2007 365 -0.2 -4.8 -1.47 0.02 71.25 47.86 30166 +2008 1 1.3 -4.8 -0.38 0.04 166.45 59.32 30217 +2008 2 -0.2 -3.8 -1.19 0 98.64 55.81 30272 +2008 3 -1.1 -2.7 -1.54 0 44.9 35.64 30331 +2008 4 -2.7 -5.7 -3.53 0 71.39 44.72 30396 +2008 5 -2.7 -6 -3.61 0.03 77.54 70.3 30464 +2008 6 0.9 -3.9 -0.42 0.02 134.56 59.82 30537 +2008 7 3.4 -6 0.82 0.01 257.5 110.99 30614 +2008 8 7.6 -4.7 4.22 0 394.56 198.02 30695 +2008 9 2.1 -4.7 0.23 0 190.05 158.47 30781 +2008 10 -0.3 -2 -0.77 0 50.06 71.23 30870 +2008 11 5.1 -1.7 3.23 0 230.77 81.09 30964 +2008 12 14.1 3.9 11.3 0 530.7 129.86 31061 +2008 13 9.2 0.6 6.83 0.21 352.25 48.84 31162 +2008 14 7.3 -0.3 5.21 0 287.32 72.9 31268 +2008 15 9 -0.3 6.44 0 366.22 144.17 31376 +2008 16 10.7 3.5 8.72 0 341.15 126.35 31489 +2008 17 8.7 5 7.68 0 177.33 36.95 31605 +2008 18 9.4 1.8 7.31 0 327.49 89.41 31724 +2008 19 7.7 2.2 6.19 0.1 231.3 54.29 31847 +2008 20 17.5 2.4 13.35 0 805.44 242.77 31974 +2008 21 13.2 1 9.84 0 558.08 212.01 32103 +2008 22 7 -1.2 4.75 0 297.16 51.77 32236 +2008 23 5.7 -1 3.86 0 237.17 169.22 32372 +2008 24 7.6 -5 4.13 0 399.47 215.77 32510 +2008 25 9.1 -2.6 5.88 0 422.7 175.89 32652 +2008 26 8.5 -5.2 4.73 0 440.92 222.91 32797 +2008 27 13 -2.2 8.82 0 613.97 62.27 32944 +2008 28 10.7 3.7 8.77 0 334.19 67.18 33094 +2008 29 10.1 -1.1 7.02 0 439.24 154.88 33247 +2008 30 7.3 0.2 5.35 0 273.7 167.17 33402 +2008 31 7.5 -1.8 4.94 0 333.24 166.67 33559 +2008 32 10.2 0.2 7.45 0 413.12 171.73 33719 +2008 33 10.2 4.2 8.55 0.8 288.6 26.92 33882 +2008 34 6.2 -0.6 4.33 0.02 247.48 155.8 34046 +2008 35 10.8 2.2 8.44 0.06 388.83 172.26 34213 +2008 36 9.3 2.9 7.54 0.05 286.96 97.93 34382 +2008 37 9.6 -0.7 6.77 0.01 405.23 136.8 34552 +2008 38 9.9 -0.9 6.93 0 424.73 264.76 34725 +2008 39 8.7 0.4 6.42 0 333.37 222.98 34900 +2008 40 8.4 -4.6 4.83 0 329 273.42 35076 +2008 41 8.4 -4.6 4.83 0 291 254.77 35254 +2008 42 6.6 -3.2 3.9 0 263 199.86 35434 +2008 43 6.2 -4.4 3.29 0 288 260.39 35615 +2008 44 8.4 -6.8 4.22 0 350 302.46 35798 +2008 45 3.8 -3.5 1.79 0 199 161.53 35983 +2008 46 3.8 -0.1 2.73 0 327 194.45 36169 +2008 47 0.8 -3.6 -0.41 0 338 253.25 36356 +2008 48 0.9 -11.5 -2.51 0 331 295.36 36544 +2008 49 11.9 -7.4 6.59 0 595 150.98 36734 +2008 50 12.2 -3.9 7.77 0 583 275.27 36925 +2008 51 12.9 -5.5 7.84 0 519 299.53 37117 +2008 52 14 -3.6 9.16 0 604 249.32 37310 +2008 53 16.6 1 12.31 0.04 741.82 206.65 37505 +2008 54 17.5 2.7 13.43 0 710.91 259.32 37700 +2008 55 17.7 -1.4 12.45 0 820.91 304.28 37896 +2008 56 19.6 -1 13.94 0 980.91 313.06 38093 +2008 57 18.6 -1.3 13.13 0 805.45 312.37 38291 +2008 58 17.2 -0.6 12.31 0 782.73 232.66 38490 +2008 59 12.1 -0.5 8.63 0 500.91 205.59 38689 +2008 60 15.1 -0.5 10.81 0 600.91 226.62 38890 +2008 61 15.7 6.8 13.25 0.22 660.83 106.52 39091 +2008 62 18.7 3.8 14.6 0 889.17 274.81 39292 +2008 63 18.6 1.9 14.01 0.8 690 184.49 39495 +2008 64 14 3.8 11.2 0 389.17 100.43 39697 +2008 65 6.1 1.6 4.86 0 342.5 158.41 39901 +2008 66 4.5 -2.4 2.6 0 387.5 214.27 40105 +2008 67 6.6 0.8 5 0.3 416.67 103.56 40309 +2008 68 6.5 2.6 5.43 0.4 105 94.4 40514 +2008 69 12.6 0.1 9.16 0 300 293 40719 +2008 70 15 -1 10.6 0 647.5 360.34 40924 +2008 71 10.7 6.6 9.57 0.34 324.17 98.92 41130 +2008 72 16.7 0.5 12.24 0.14 480 191.14 41336 +2008 73 14.4 0.5 10.58 0 890.83 322.94 41543 +2008 74 13.4 -0.9 9.47 0 577.5 142.12 41749 +2008 75 14.8 4 11.83 0 605.83 279.92 41956 +2008 76 19.5 7.3 16.15 0.15 903.33 271.36 42163 +2008 77 16.8 4.5 13.42 0 568.33 277.03 42370 +2008 78 7.7 2.3 6.21 0.1 185 155.57 42578 +2008 79 9 -4 5.43 0 397.5 356.74 42785 +2008 80 8.6 -3.7 5.22 0 385 394.22 42992 +2008 81 9.9 -1.6 6.74 0.62 510 196.12 43200 +2008 82 7.5 0.9 5.69 0.19 246.67 207.91 43407 +2008 83 6.6 0.1 4.81 2.2 200.83 108.54 43615 +2008 84 7.6 0.6 5.67 0.02 285.83 184.89 43822 +2008 85 7.6 -1.6 5.07 0 458.33 315.18 44029 +2008 86 10 -3.4 6.31 0 530.83 322.95 44236 +2008 87 11.9 -0.1 8.6 0 424.17 201.15 44443 +2008 88 12.4 4.5 10.23 0 413.33 279.68 44650 +2008 89 15.2 5.7 12.59 0 475.83 273.37 44857 +2008 90 16.8 -1.2 11.85 0 851.67 439.69 45063 +2008 91 18.4 1.8 13.83 0 956.67 447.07 45270 +2008 92 19.2 2.3 14.55 0 905.38 406 45475 +2008 93 14.7 7 12.58 0.43 573.08 155.89 45681 +2008 94 13.2 -0.1 9.54 0 532.31 345.02 45886 +2008 95 12.7 5.9 10.83 0 586.15 298.81 46091 +2008 96 14.9 -0.1 10.78 0 620 353.37 46295 +2008 97 16.3 -1.7 11.35 0.05 828.57 397.94 46499 +2008 98 16.4 4.2 13.04 0.15 676.89 285.93 46702 +2008 99 9.8 3.4 8.04 0 295.89 241.15 46905 +2008 100 19.3 1 14.27 0 969.12 460.2 47107 +2008 101 21.1 11.6 18.49 0.01 761.76 235.84 47309 +2008 102 20.7 13.7 18.77 0 598.75 248.46 47510 +2008 103 16.6 8.9 14.48 0.38 508.7 213.52 47710 +2008 104 16.6 5.2 13.47 0 658.9 387.15 47910 +2008 105 17.7 0.7 13.02 0 856.92 466.7 48108 +2008 106 14.2 2.9 11.09 0.76 567.94 292.6 48306 +2008 107 15.5 1.7 11.71 0.15 684.32 326.82 48504 +2008 108 14.4 0.2 10.5 0.04 479.29 291.23 48700 +2008 109 18.4 2.6 14.06 0.03 707.86 295.73 48895 +2008 110 20.4 10.1 17.57 0.08 720 340.79 49089 +2008 111 21.9 4.1 17 0 1188.57 422.78 49282 +2008 112 23 6.5 18.46 0.5 865 360.08 49475 +2008 113 18.1 8.4 15.43 0.41 559.29 333.95 49666 +2008 114 15.6 9.1 13.81 0 547.86 345.25 49855 +2008 115 17 2.9 13.12 0 858.57 488.49 50044 +2008 116 17.7 2 13.38 0.07 627.86 276.67 50231 +2008 117 18.2 6 14.84 0.18 655.71 439.26 50417 +2008 118 20.1 3.8 15.62 0 1047.86 496.35 50601 +2008 119 21.7 1.1 16.04 0 1284.29 505.93 50784 +2008 120 18.7 6.6 15.37 0 804.29 330.99 50966 +2008 121 19.7 10.1 17.06 0 725 352.97 51145 +2008 122 19.2 10.6 16.83 1.35 531.43 234.92 51324 +2008 123 20.2 6.9 16.54 0.35 941.43 406.06 51500 +2008 124 19.9 5.3 15.89 0 980.71 508.28 51674 +2008 125 19.2 4.5 15.16 0.01 953.33 506.14 51847 +2008 126 17.7 3.4 13.77 0 564 365.07 52018 +2008 127 20.2 11.1 17.7 0.05 642.67 233.1 52187 +2008 128 20.1 5 15.95 0 960.67 492.58 52353 +2008 129 21.7 3.4 16.67 0 1141.33 517.62 52518 +2008 130 22 7.2 17.93 0 1078.67 426.96 52680 +2008 131 21.2 4.1 16.5 0 971.33 411.61 52840 +2008 132 20.7 5.7 16.57 0 1161.33 509.58 52998 +2008 133 23.2 2.9 17.62 0 1325.33 448.33 53153 +2008 134 24.2 4 18.65 0 1486 456.16 53306 +2008 135 24.4 5.7 19.26 0 1297.33 402.37 53456 +2008 136 26.7 6.5 21.15 0 1370.67 423.42 53603 +2008 137 25.5 9.7 21.16 0.56 1018 326.65 53748 +2008 138 24.8 13 21.56 0 1161.33 379.52 53889 +2008 139 22.8 17 21.2 0.2 868 203.2 54028 +2008 140 22 11.2 19.03 1.4 564 352.94 54164 +2008 141 13.7 9.2 12.46 0.23 206.67 115.28 54297 +2008 142 16.3 9.4 14.4 1.2 393.44 326.59 54426 +2008 143 19.5 10.6 17.05 0 667.19 305.15 54552 +2008 144 19.8 11.9 17.63 0.1 748.75 300.92 54675 +2008 145 24.3 12.9 21.17 0 883.13 410.7 54795 +2008 146 23.2 9.4 19.41 0 820.63 436.62 54911 +2008 147 27.3 12.7 23.29 0 925.63 396.58 55023 +2008 148 32.8 12.8 27.3 0 1761.25 493.98 55132 +2008 149 33 12.9 27.47 0 2338.13 468.06 55237 +2008 150 28.5 16.1 25.09 0 1465.62 441.3 55339 +2008 151 27.5 11.9 23.21 0.03 1256.25 435.05 55436 +2008 152 27.1 13.6 23.39 0 1433.13 498.86 55530 +2008 153 29.9 10.8 24.65 0.2 1520 458.11 55619 +2008 154 27.4 16.5 24.4 0.13 1317.5 425.46 55705 +2008 155 27 13.3 23.23 2.37 935.33 339.69 55786 +2008 156 23.1 16.2 21.2 0.37 676.3 177.72 55863 +2008 157 19.7 16.3 18.77 1.76 311.86 95.8 55936 +2008 158 23.5 15.1 21.19 0.4 799.6 218.83 56004 +2008 159 20.3 12.9 18.27 0.95 610.36 204.87 56068 +2008 160 22.7 14.9 20.56 0.06 725.21 213.7 56128 +2008 161 25.2 15 22.4 0 1002.68 356.7 56183 +2008 162 26.6 11.6 22.48 0 1355.03 460.74 56234 +2008 163 26.8 13.5 23.14 1.15 1285.97 323.9 56280 +2008 164 21.1 14.2 19.2 0 605.61 274.21 56321 +2008 165 20 12 17.8 0 635.31 323.74 56358 +2008 166 18.8 9 16.11 0.1 682.05 294.51 56390 +2008 167 20.9 10 17.9 0 822.98 421.02 56418 +2008 168 22.1 8 18.22 0.01 1019.72 362.55 56440 +2008 169 23.1 12.6 20.21 0.1 909.85 299.11 56458 +2008 170 24.9 15.2 22.23 0.05 953.98 277.98 56472 +2008 171 27.5 10.3 22.77 0 1517.22 502.08 56480 +2008 172 29.1 14 24.95 0 1559.05 463.13 56484 +2008 173 30.3 14 25.82 0 1726.55 473.18 56482 +2008 174 32 15.5 27.46 0 1902.22 464.92 56476 +2008 175 32.1 17.1 27.98 0.08 1824.53 328.69 56466 +2008 176 31.7 17 27.66 0.7 1767.57 325.7 56450 +2008 177 30.3 16 26.37 0 1616.82 433.34 56430 +2008 178 30.1 17.9 26.75 0.88 1603.75 295.38 56405 +2008 179 27.4 17.3 24.62 0.15 988.12 312.07 56375 +2008 180 27.2 16.2 24.18 0 1344.37 383.19 56341 +2008 181 29.4 14.5 25.3 0 1637.5 457.61 56301 +2008 182 27.2 16.6 24.29 0.96 823.75 224.02 56258 +2008 183 28.6 14.4 24.7 0 1647.5 452.34 56209 +2008 184 30.2 14.5 25.88 0 1724.38 467.65 56156 +2008 185 30.4 16.3 26.52 0 1735.63 439.59 56099 +2008 186 28.6 19.7 26.15 0.01 1485.63 237.51 56037 +2008 187 28 15.8 24.65 0 1778.13 416.02 55971 +2008 188 28.5 11.3 23.77 0.09 1548.13 454.65 55900 +2008 189 30.5 18.1 27.09 1.45 1608.13 385.58 55825 +2008 190 22.4 14.4 20.2 0.11 357.5 114.67 55746 +2008 191 25.1 10.3 21.03 0 1231.88 455.98 55663 +2008 192 27 15.9 23.95 0 1121.25 317.61 55575 +2008 193 30.8 14 26.18 0 1935.63 466 55484 +2008 194 31.2 15.8 26.97 0 1910.63 437.96 55388 +2008 195 29.8 16.5 26.14 3.23 1200.63 299.07 55289 +2008 196 20.6 14.4 18.9 4.06 326.88 146.33 55186 +2008 197 24.7 12.4 21.32 0 1171.88 397.21 55079 +2008 198 25.3 13.3 22 0 1556.88 388.86 54968 +2008 199 27.2 14.1 23.6 0.75 856.88 304.17 54854 +2008 200 23.2 14.9 20.92 0.01 691.88 277.48 54736 +2008 201 25.8 13.9 22.53 0 1266.25 385.98 54615 +2008 202 27.8 14.5 24.14 2.63 1226.87 308.02 54490 +2008 203 22.2 15.6 20.38 0.02 622.06 182.49 54362 +2008 204 21.5 12.9 19.13 0 727.67 312.13 54231 +2008 205 17.7 10.3 15.66 1.65 526.57 60.07 54097 +2008 206 20.3 14.5 18.7 0 505.86 110.32 53960 +2008 207 24.4 17.5 22.5 0.05 725.9 152.32 53819 +2008 208 26.8 15.9 23.8 0 1141.85 386.36 53676 +2008 209 28.9 16.1 25.38 0 1410.15 413.44 53530 +2008 210 26 15.5 23.11 0 1067.39 416.62 53382 +2008 211 29 15.2 25.21 0 1479.08 436.08 53230 +2008 212 28.1 16.5 24.91 0 1273.55 279.91 53076 +2008 213 29.8 16.2 26.06 0 1531.67 385.48 52920 +2008 214 30.1 17.1 26.53 0 1517.15 358.02 52761 +2008 215 29.7 15.9 25.91 0 1535.82 374.8 52600 +2008 216 30.6 15.3 26.39 0 1701.58 430.89 52437 +2008 217 30.8 15.6 26.62 0.51 1714.22 379.06 52271 +2008 218 24.8 18.6 23.1 0.38 682.4 292.87 52103 +2008 219 26.8 12.6 22.9 0 1332.25 450.98 51934 +2008 220 28 14.1 24.18 0 1406.59 427.78 51762 +2008 221 26.8 14.9 23.53 1.5 1205.71 297.87 51588 +2008 222 24.8 15.1 22.13 0.01 948.78 369.23 51413 +2008 223 25.3 9.7 21.01 0 1284.51 429.46 51235 +2008 224 26.6 11.9 22.56 0 1341.37 464.92 51057 +2008 225 29.3 13 24.82 0 1635.44 434.04 50876 +2008 226 27.1 16.8 24.27 0.01 1118.74 421.03 50694 +2008 227 27.9 16.3 24.71 0 1259.92 411.99 50510 +2008 228 30.9 16.1 26.83 3.46 1699.99 324.7 50325 +2008 229 25.6 13.6 22.3 0.23 1134.78 252.12 50138 +2008 230 22.3 8.1 18.4 0 1035.16 376.3 49951 +2008 231 25.8 9.8 21.4 0 1336.64 426.18 49761 +2008 232 27.4 11.4 23 0 1460.98 463.72 49571 +2008 233 26.2 12 22.3 0.02 1288.88 414.71 49380 +2008 234 26.8 16.4 23.94 0 1107.78 402.95 49187 +2008 235 28.3 12.5 23.95 0 1526.03 405.36 48993 +2008 236 24.3 15.1 21.77 2.83 890.51 254.53 48798 +2008 237 22.1 13.8 19.82 0.11 733.76 332.6 48603 +2008 238 23.3 8.8 19.31 0 1107.41 389.31 48406 +2008 239 25.6 12.5 22 0 1193.68 399.55 48208 +2008 240 27.1 13.3 23.31 0 1333.95 405.16 48010 +2008 241 28.4 12 23.89 0 1561.33 390.12 47811 +2008 242 26.2 14 22.84 0 1184.32 333.89 47611 +2008 243 23.4 14 20.81 0 860.01 229.27 47410 +2008 244 23.8 9.2 19.79 0 1143.14 403.05 47209 +2008 245 23.9 8.5 19.66 0 1179.8 338.57 47007 +2008 246 26.2 10.8 21.97 0 1342.46 372.01 46805 +2008 247 27.8 12.4 23.57 0 1466.54 394.34 46601 +2008 248 28.3 15.5 24.78 0 1614.62 330.96 46398 +2008 249 28.6 19 25.96 0 1641.54 260 46194 +2008 250 29.7 20.7 27.22 0 1833.08 241.9 45989 +2008 251 30 19.8 27.2 0.52 1736.15 201.71 45784 +2008 252 23.9 15.5 21.59 0 1121.54 242.06 45579 +2008 253 25.3 9.8 21.04 0 1306.92 377.87 45373 +2008 254 27.2 10.1 22.5 0 1358.46 388.74 45167 +2008 255 28.3 15.5 24.78 0 1524.62 197.64 44961 +2008 256 26.5 15 23.34 0.41 1045.83 172.99 44755 +2008 257 19.9 12.7 17.92 0.03 715.83 155.56 44548 +2008 258 12.7 9.6 11.85 1.32 441.67 90.49 44341 +2008 259 10.9 7.9 10.08 0.18 226.67 72.16 44134 +2008 260 10.3 8.7 9.86 0 355.83 67.07 43927 +2008 261 15.1 7.8 13.09 0 661.67 223.46 43719 +2008 262 15.3 2.9 11.89 0 679.17 208.2 43512 +2008 263 15.3 4 12.19 0 647.5 214.21 43304 +2008 264 13.4 10.1 12.49 0.09 528.33 78.56 43097 +2008 265 13.6 8.6 12.23 0.11 439.17 89.05 42890 +2008 266 13.2 8.6 11.93 0.24 415 166.12 42682 +2008 267 15.4 7.9 13.34 0 558.33 145.68 42475 +2008 268 17.3 6.2 14.25 0.06 603.33 195.06 42268 +2008 269 15.1 9.1 13.45 0.95 259.17 104.53 42060 +2008 270 14.6 8 12.79 0 500.83 207.79 41854 +2008 271 15.1 8.4 13.26 0 573.33 157.83 41647 +2008 272 17.1 6.3 14.13 0 612.5 174.32 41440 +2008 273 18 1.6 13.49 0 845 369.41 41234 +2008 274 19 3.3 14.68 0 766.67 359.13 41028 +2008 275 19.8 7.5 16.42 0 761.82 191.38 40822 +2008 276 21.7 5.9 17.36 0 767.27 168.04 40617 +2008 277 17 10.2 15.13 0.93 284.55 54.02 40412 +2008 278 12.1 7.4 10.81 0.03 366.36 100.02 40208 +2008 279 16 -0.4 11.49 0 727.27 352.26 40003 +2008 280 20 1.3 14.86 0.02 781.82 209.41 39800 +2008 281 19.9 6.8 16.3 0.05 532.73 169.21 39597 +2008 282 19.8 5.2 15.79 0 567.27 211.45 39394 +2008 283 21.1 6.7 17.14 0.17 490 181.06 39192 +2008 284 20.2 9.3 17.2 0 457.27 199.73 38991 +2008 285 20.4 6 16.44 0 562.73 306.28 38790 +2008 286 21.5 6.1 17.27 0 609.09 307.29 38590 +2008 287 22.5 6.4 18.07 0 747.27 223.61 38391 +2008 288 22.5 4.7 17.61 0 825.45 170.78 38193 +2008 289 22.5 6.8 18.18 0 780.91 192.84 37995 +2008 290 22.6 8.5 18.72 0.32 717.27 200.18 37799 +2008 291 18 6.1 14.73 0 333.64 73.39 37603 +2008 292 14 -0.2 10.1 0 446.36 271.42 37408 +2008 293 16.3 -0.9 11.57 0 535.45 201.88 37214 +2008 294 17.7 -0.6 12.67 0 523.64 284.72 37022 +2008 295 16.8 2.3 12.81 0 374.55 251.75 36830 +2008 296 19.2 2 14.47 0 390.91 186.23 36640 +2008 297 13.7 8.6 12.3 0 419.09 112.15 36451 +2008 298 13.3 1.8 10.14 0 379.09 165.85 36263 +2008 299 10.2 1.9 7.92 0 248.18 90.06 36076 +2008 300 10.4 7.2 9.52 0 345 112.47 35891 +2008 301 10.9 1.3 8.26 0 269 169.75 35707 +2008 302 20.7 1.5 15.42 0.3 678 189.33 35525 +2008 303 22.6 11.8 19.63 0.76 859 179.6 35345 +2008 304 20.3 11.3 17.82 0 754 191.32 35166 +2008 305 18.6 7.4 15.52 0.02 824 173.91 34988 +2008 306 16.8 10.5 15.07 0.64 273 135.2 34813 +2008 307 12.9 7.8 11.5 0.01 143 41.3 34639 +2008 308 20.9 9.3 17.71 0 722 136.17 34468 +2008 309 19.7 7.3 16.29 0 402.22 148.95 34298 +2008 310 18.7 9.4 16.14 0.03 416.67 147.48 34130 +2008 311 17.8 8.6 15.27 0.18 447.78 124.64 33964 +2008 312 14 11.9 13.42 1.08 74.44 34.99 33801 +2008 313 13.2 9.6 12.21 0.25 75.56 15.13 33640 +2008 314 13.5 6.8 11.66 0 186.67 100.36 33481 +2008 315 9.8 5.9 8.73 0 81.11 59.53 33325 +2008 316 9.1 6.8 8.47 0 130 44.81 33171 +2008 317 7.8 6.3 7.39 0.02 81.11 32.64 33019 +2008 318 8.8 7.2 8.36 0.57 118.89 39.94 32871 +2008 319 8.9 7.4 8.49 0 100 22.35 32725 +2008 320 11.8 6.3 10.29 0 294.44 92.11 32582 +2008 321 6.4 0.6 4.8 0.23 44.44 87.26 32441 +2008 322 9.9 2.4 7.84 0 472.22 186.94 32304 +2008 323 6.3 -4 3.47 0 281.11 182.84 32170 +2008 324 7.5 -4.2 4.28 0 288.89 145.06 32039 +2008 325 12.9 0.5 9.49 0 535.56 143.99 31911 +2008 326 6.3 -0.7 4.38 0.23 151.11 44.4 31786 +2008 327 5.3 -2.8 3.07 0.04 278.89 145.02 31665 +2008 328 5.2 -4.4 2.56 0 365.56 181.42 31547 +2008 329 4.9 -2.3 2.92 0.05 325.56 41.21 31433 +2008 330 2.8 -1.2 1.7 0 88.89 51.96 31322 +2008 331 6 -2.5 3.66 0 262.22 154.67 31215 +2008 332 6.9 -2.3 4.37 0 346.67 186.96 31112 +2008 333 3.6 -5.5 1.1 0.53 197.78 169.23 31012 +2008 334 2 -0.5 1.31 0 45.56 42.11 30917 +2008 335 8.3 -0.2 5.96 0.16 191.11 61.89 30825 +2008 336 10.9 2.3 8.54 0.4 270 74.15 30738 +2008 337 7 -0.8 4.86 0.47 193.33 101.07 30654 +2008 338 5 2.8 4.39 0.1 61.11 42.02 30575 +2008 339 5 0.2 3.68 0.06 37.78 43.62 30500 +2008 340 10.1 -0.1 7.29 0.06 275.56 51.57 30430 +2008 341 9.9 1.3 7.54 0.18 68.89 61.81 30363 +2008 342 7.4 0.1 5.39 0 226.67 68.24 30301 +2008 343 4.8 -1.1 3.18 0 172.22 46.28 30244 +2008 344 5.4 -5.1 2.51 0 190 178.25 30191 +2008 345 8.5 -3.1 5.31 0 364.44 87.63 30143 +2008 346 5.9 3.4 5.21 0.33 125.56 53.06 30099 +2008 347 4.6 2.3 3.97 0.78 76.25 10.81 30060 +2008 348 4.3 2.3 3.75 0.08 62.5 15.35 30025 +2008 349 5.2 3.3 4.68 0.01 60 32.3 29995 +2008 350 5.1 3.3 4.6 0.07 96.25 35.99 29970 +2008 351 4.9 3.9 4.63 0.3 50 19.56 29950 +2008 352 5.8 4.8 5.52 1.44 43.75 19.6 29934 +2008 353 5.7 0.8 4.35 1.63 88.75 22.2 29924 +2008 354 4.8 2.7 4.22 0.26 103.75 28.07 29918 +2008 355 5.1 -1.1 3.39 0.04 197.5 95.08 29916 +2008 356 9.1 -0.8 6.38 0.11 411.25 191.14 29920 +2008 357 8.1 -1.1 5.57 0 187.5 120.01 29928 +2008 358 8.9 -1.8 5.96 0 385 160.25 29941 +2008 359 5.2 0 3.77 0.01 212.5 56.06 29959 +2008 360 3.6 -0.7 2.42 0.06 90 45.09 29982 +2008 361 0.3 -5.9 -1.41 0 153.75 80.31 30009 +2008 362 -0.1 -1.2 -0.4 0 100 50.53 30042 +2008 363 -0.7 -4.4 -1.72 0 118.75 143.73 30078 +2008 364 -2.4 -8.6 -4.11 0 113.75 67.21 30120 +2008 365 -4 -10.1 -5.68 0 67.5 32.09 30166 +2009 1 -3.7 -4.9 -4.03 0 72.5 36.85 30217 +2009 2 -1.5 -4.2 -2.24 0 112.5 45.58 30272 +2009 3 -0.3 -6.9 -2.12 0 180 203.63 30331 +2009 4 0.4 -12.8 -3.23 0 155 205.4 30396 +2009 5 -1.5 -9.1 -3.59 0 102.5 111.48 30464 +2009 6 -2 -10.2 -4.25 0 90 69.99 30537 +2009 7 -3 -5.6 -3.71 0 100 43.77 30614 +2009 8 -0.1 -11.6 -3.26 0 191.25 184.49 30695 +2009 9 -0.8 -14.2 -4.48 0 167.5 226.71 30781 +2009 10 -4 -14.4 -6.86 0 40 72.76 30870 +2009 11 -7.3 -9.5 -7.91 0 40 40.07 30964 +2009 12 -6.3 -7.9 -6.74 0 40 20.58 31061 +2009 13 -6.4 -7.4 -6.68 0.02 40 31.25 31162 +2009 14 -2.7 -7.4 -3.99 0.86 40 25.74 31268 +2009 15 1.4 -2.8 0.24 0.01 53.33 88.56 31376 +2009 16 4.7 -3.1 2.56 0 75.56 175.9 31489 +2009 17 3.6 -4 1.51 0 133.33 213.48 31605 +2009 18 1.3 -5.4 -0.54 0.01 40 74.21 31724 +2009 19 8 -4 4.7 0 169 186.49 31847 +2009 20 13.9 3 10.9 0 476 166.97 31974 +2009 21 9.8 1.1 7.41 2.35 92 39.63 32103 +2009 22 6.4 -0.3 4.56 0 129 163.76 32236 +2009 23 3.5 -1.1 2.23 1.6 89 80.57 32372 +2009 24 2.6 -0.1 1.86 0.02 53 144.23 32510 +2009 25 5 0 3.63 0 225 101.51 32652 +2009 26 5.1 -2.2 3.09 0.03 207 123.64 32797 +2009 27 1.6 -1.1 0.86 3.85 40 29.04 32944 +2009 28 2.8 0.6 2.19 0.54 88 62.04 33094 +2009 29 3 0.8 2.4 0 183 119.63 33247 +2009 30 1.7 0 1.23 0 194 140.17 33402 +2009 31 2 -1.1 1.15 0.01 164 134.52 33559 +2009 32 0.2 -2.7 -0.6 0.44 67 77.94 33719 +2009 33 1.2 -0.8 0.65 1.05 61 67.23 33882 +2009 34 1.9 0.5 1.51 0.34 38 62.03 34046 +2009 35 3.5 0.8 2.76 0 39 91.59 34213 +2009 36 9.2 -1.1 6.37 0 81 205.86 34382 +2009 37 13.6 -2.6 9.14 0 427 225.47 34552 +2009 38 12.5 0.4 9.17 0.19 410 150.35 34725 +2009 39 9.8 3.4 8.04 1.62 79 37.65 34900 +2009 40 7.3 0.4 5.4 0 408 235.92 35076 +2009 41 10.1 -3.1 6.47 0.01 350 120.23 35254 +2009 42 8.6 1.1 6.54 0 308 185.37 35434 +2009 43 5.4 -5.3 2.46 0 248 197.97 35615 +2009 44 4.2 -3.3 2.14 0 373 234.5 35798 +2009 45 3.4 -0.8 2.25 0 391 200.35 35983 +2009 46 2.8 -1.5 1.62 0 311 233.67 36169 +2009 47 4.4 -4.1 2.06 0 342 201.49 36356 +2009 48 2.2 -3.6 0.61 0.11 233 77.35 36544 +2009 49 1.9 -5.3 -0.08 0 255 222.77 36734 +2009 50 1.9 -3.8 0.33 0 285 290.21 36925 +2009 51 4.7 -7.8 1.26 0 340 215.11 37117 +2009 52 4.2 -2.2 2.44 0.04 147 111.77 37310 +2009 53 0.2 -3 -0.68 0.28 133.64 124.74 37505 +2009 54 4.9 -1.2 3.22 0.02 106.36 137.24 37700 +2009 55 5 -1.1 3.32 0.29 127.27 159.82 37896 +2009 56 6 -0.8 4.13 0 290 225.89 38093 +2009 57 9 -1.9 6 0 364.55 202.92 38291 +2009 58 11 -1.7 7.51 0 312.73 166.8 38490 +2009 59 15.5 1 11.51 0 527.27 279.24 38689 +2009 60 12.5 -1.2 8.73 0 338.18 290.46 38890 +2009 61 6.9 2.7 5.75 0.23 105 75.45 39091 +2009 62 8.6 3.9 7.31 0.02 111.67 97.73 39292 +2009 63 9.8 4.8 8.43 0.09 140.83 107.4 39495 +2009 64 9.3 5.2 8.17 1.78 120 37.55 39697 +2009 65 7.3 5.7 6.86 0.56 93.33 71.89 39901 +2009 66 8.9 0.8 6.67 0.02 395 39.62 40105 +2009 67 13.5 -0.3 9.71 0 595.83 335.72 40309 +2009 68 9.3 2.4 7.4 0 457.5 114.06 40514 +2009 69 12 -1.7 8.23 0 665.83 323.99 40719 +2009 70 11.5 3.5 9.3 0.06 455.83 163.02 40924 +2009 71 10.4 -1.6 7.1 0.04 496.67 303.65 41130 +2009 72 13.2 1.6 10.01 0 533.33 263.19 41336 +2009 73 13.1 1.6 9.94 0 439.17 269.53 41543 +2009 74 13 -0.1 9.4 0 350.83 168.39 41749 +2009 75 12.8 2.3 9.91 0 520 201.53 41956 +2009 76 10 1.3 7.61 0 422.5 210.99 42163 +2009 77 11.5 -0.8 8.12 0.22 679.17 365.69 42370 +2009 78 5.9 0.3 4.36 0.48 63.33 151.83 42578 +2009 79 5 -2 3.08 0 260.83 262.38 42785 +2009 80 6 0.5 4.49 0 334.17 358.97 42992 +2009 81 13.8 -5.6 8.46 0 619.17 398.76 43200 +2009 82 15.4 -0.2 11.11 0 821.67 256.73 43407 +2009 83 9.8 2.3 7.74 0 476.67 165.39 43615 +2009 84 8 -2 5.25 0 486.67 322.41 43822 +2009 85 11.5 -0.9 8.09 0 428.33 295.04 44029 +2009 86 15.1 2.3 11.58 0 660 271.17 44236 +2009 87 16 7.3 13.61 0 768.33 330.76 44443 +2009 88 13.8 8.6 12.37 2.4 310.83 77.02 44650 +2009 89 10.6 5.8 9.28 0.01 296.67 270.03 44857 +2009 90 11.4 3.9 9.34 0.22 321.67 171.5 45063 +2009 91 12.6 7.6 11.23 0.05 288.37 162.16 45270 +2009 92 19 9.4 16.36 0 955.38 360.8 45475 +2009 93 19.1 3.2 14.73 0 627.69 364.61 45681 +2009 94 21.9 3.9 16.95 0 1003.08 430.84 45886 +2009 95 22.4 3.9 17.31 0 1028.46 404.29 46091 +2009 96 22.1 4.5 17.26 0 1065 360.53 46295 +2009 97 23.5 3.3 17.95 0 1343.57 424.47 46499 +2009 98 24 3.8 18.45 0 1487.86 442.12 46702 +2009 99 23.8 4.3 18.44 0 1350.71 413.15 46905 +2009 100 23.5 3.5 18 0 1555.71 426.18 47107 +2009 101 23.8 3.3 18.16 0 1595 434.7 47309 +2009 102 23.2 3.6 17.81 0 1571.43 441.5 47510 +2009 103 21.2 3.8 16.41 0 984.29 438.57 47710 +2009 104 21.2 2.7 16.11 0 927.86 442.68 47910 +2009 105 22.9 1.8 17.1 0 1260.71 451.09 48108 +2009 106 23.2 3.9 17.89 0 1375.71 385.9 48306 +2009 107 19.8 9.5 16.97 0 960 329.86 48504 +2009 108 21.5 3.1 16.44 0 929.29 417.59 48700 +2009 109 19 2.8 14.55 0.26 749.29 245.89 48895 +2009 110 21 10 17.98 0.12 752.14 354.2 49089 +2009 111 21.1 9.5 17.91 0 1056.43 366.54 49282 +2009 112 20.8 1.8 15.58 0.12 1229.29 486.96 49475 +2009 113 16.1 6.1 13.35 0.33 420.71 103.41 49666 +2009 114 19 5.4 15.26 0 862.14 447.18 49855 +2009 115 21 1.9 15.75 0 1087.79 463.53 50044 +2009 116 20.3 6.5 16.51 0 909.23 385.22 50231 +2009 117 20.5 9.9 17.59 0 790.57 312.64 50417 +2009 118 18.6 11.4 16.62 0.17 739.29 261.88 50601 +2009 119 18 9.5 15.66 0.56 347.14 250.39 50784 +2009 120 20.3 9.1 17.22 0.3 597.14 399.44 50966 +2009 121 23.8 8.3 19.54 0 1173.57 431.55 51145 +2009 122 17.9 8.3 15.26 0 961.43 248.01 51324 +2009 123 20.8 8.3 17.36 0 1014.29 395.38 51500 +2009 124 22.3 5.3 17.63 0.05 755 327.11 51674 +2009 125 17.5 8.3 14.97 0 866.67 438.08 51847 +2009 126 20.5 6.9 16.76 0 856.67 259.98 52018 +2009 127 22.2 10.7 19.04 0 1012.67 413.29 52187 +2009 128 25.9 5.7 20.34 0 1294.67 448.49 52353 +2009 129 25.4 8.2 20.67 0 1243.33 459.47 52518 +2009 130 27.4 10.4 22.72 0 1311.33 444.44 52680 +2009 131 28.3 9.6 23.16 2.77 1350 429.34 52840 +2009 132 24.3 12.6 21.08 1.15 369.33 360.34 52998 +2009 133 15.7 10.8 14.35 0.13 252.67 149.17 53153 +2009 134 14 11.2 13.23 0 129.33 88.76 53306 +2009 135 20.8 10.3 17.91 0 393.33 278.19 53456 +2009 136 22.9 11.4 19.74 0.03 702.67 360.15 53603 +2009 137 25.4 10.2 21.22 0 886.67 466.32 53748 +2009 138 27 12 22.88 0.04 809.33 393.64 53889 +2009 139 24.8 14.4 21.94 0 830 475.64 54028 +2009 140 25.5 13.9 22.31 0 1197.33 521.85 54164 +2009 141 27.5 9.4 22.52 0 1440 490.32 54297 +2009 142 27.3 14.2 23.7 1.68 1310.43 309.27 54426 +2009 143 22.4 12.3 19.62 0.02 853.3 265.93 54552 +2009 144 23.4 16 21.36 0.05 724.85 203.13 54675 +2009 145 28.3 14.4 24.48 0 1240.63 445.58 54795 +2009 146 28.5 16.2 25.12 0.31 1126.87 403.08 54911 +2009 147 25.4 15.3 22.62 1.1 313.75 110.94 55023 +2009 148 21.6 9.3 18.22 0.2 1031.88 386.58 55132 +2009 149 18.8 7.7 15.75 0.1 707.5 377.62 55237 +2009 150 13.1 7.7 11.62 0.89 201.87 151.72 55339 +2009 151 19.4 3.9 15.14 0 655.62 349.57 55436 +2009 152 18.6 10.3 16.32 0 520.63 269.62 55530 +2009 153 20.1 5.8 16.17 0.03 676.25 369.76 55619 +2009 154 25.1 10.8 21.17 0 1327.5 396.36 55705 +2009 155 20.5 9.6 17.5 0 576.88 324.58 55786 +2009 156 18.4 7.9 15.51 0 316.87 253.35 55863 +2009 157 26.3 14.3 23 0 1080 340.98 55936 +2009 158 23.8 14 21.11 0.44 380 188.17 56004 +2009 159 24.9 8.3 20.34 0 862.5 458.9 56068 +2009 160 27.3 13.6 23.53 0 1390.63 491.32 56128 +2009 161 26.2 11.5 22.16 0 1014.38 358.17 56183 +2009 162 25.4 10.3 21.25 0.82 691.25 321.31 56234 +2009 163 24.2 8.3 19.83 0.01 1323.13 470.34 56280 +2009 164 24.9 10.8 21.02 0 930 420.75 56321 +2009 165 27.2 8.8 22.14 0 1367.5 498.02 56358 +2009 166 27.7 16 24.48 0 1088.75 311.15 56390 +2009 167 28.8 17.8 25.78 0.65 1107.5 259.99 56418 +2009 168 24.2 14.6 21.56 0 1001.87 417.6 56440 +2009 169 27.9 10.3 23.06 0 1238.75 487.67 56458 +2009 170 31.2 13.4 26.31 0 1653.75 496.23 56472 +2009 171 24.9 12.9 21.6 1.2 270.63 59.29 56480 +2009 172 21.8 8.4 18.12 0 922.5 479.98 56484 +2009 173 18.9 10.4 16.56 2.59 313.12 73.6 56482 +2009 174 14.5 12.2 13.87 3.59 133.12 51.08 56476 +2009 175 18.5 13.7 17.18 0.94 185 192.73 56466 +2009 176 24.9 13.8 21.85 0.01 775.63 448.51 56450 +2009 177 24.7 12.4 21.32 6.24 433.75 264.95 56430 +2009 178 25 13.1 21.73 0 683.13 354.45 56405 +2009 179 22.7 16.6 21.02 4.72 365.63 167.53 56375 +2009 180 24 15.3 21.61 3.62 503.13 300 56341 +2009 181 28.2 14.2 24.35 0 1034.38 433.95 56301 +2009 182 28.2 17.2 25.18 1.34 751.25 352.55 56258 +2009 183 28.1 15.5 24.64 0 876.25 393.21 56209 +2009 184 28.8 16.2 25.34 0 986.88 423.58 56156 +2009 185 27.9 18.1 25.2 0.14 1005 384.76 56099 +2009 186 27 16 23.98 0.1 893.13 381.3 56037 +2009 187 27.2 15 23.84 0 788.13 341.28 55971 +2009 188 26.1 14 22.77 0.43 746.25 363.36 55900 +2009 189 22.3 15.4 20.4 0.63 251.88 187.4 55825 +2009 190 23.5 12.2 20.39 0.26 659.38 327.57 55746 +2009 191 21.1 15 19.42 0.5 244.38 128.98 55663 +2009 192 22.9 10 19.35 0.02 804.38 368.21 55575 +2009 193 24.8 10.8 20.95 0 1131.88 480.95 55484 +2009 194 28.9 14 24.8 0 1276.25 426.5 55388 +2009 195 30.6 16.2 26.64 0 1229.37 470.8 55289 +2009 196 31.4 17.4 27.55 0.61 1128.13 414.24 55186 +2009 197 30.8 18 27.28 0 1401.87 416.34 55079 +2009 198 30.7 16.5 26.8 0 1463.13 440.81 54968 +2009 199 28.4 15.2 24.77 0.51 405.63 159.23 54854 +2009 200 24 10.3 20.23 0 1122.5 495.38 54736 +2009 201 26.2 9.8 21.69 0 1090.63 430.72 54615 +2009 202 29 12.5 24.46 0 1230.62 481.09 54490 +2009 203 30.7 14.1 26.13 0 1445 486.82 54362 +2009 204 33 16.7 28.52 0 1899.38 460.38 54231 +2009 205 30.1 16.1 26.25 1.3 1508.75 479.6 54097 +2009 206 27.1 15.7 23.97 0.01 829.38 300.04 53960 +2009 207 25 9.7 20.79 0 1175 412.53 53819 +2009 208 27 9.7 22.24 0 1265.63 492.03 53676 +2009 209 27.5 12.1 23.27 0 1200.67 391.01 53530 +2009 210 29 13.6 24.77 0 1551.43 516.79 53382 +2009 211 31.2 13.6 26.36 0 1610.71 446.84 53230 +2009 212 27.4 17.4 24.65 0 1735.71 384.72 53076 +2009 213 29.5 13.4 25.07 0 1590.71 479.88 52920 +2009 214 32.5 16.6 28.13 0.01 1975.71 485.67 52761 +2009 215 29.3 14.9 25.34 0.22 1432.14 365.38 52600 +2009 216 21.2 16.8 19.99 3.52 275 89.08 52437 +2009 217 23.8 16.8 21.88 0 814.29 272.57 52271 +2009 218 26.7 15 23.48 0 1022.86 414.34 52103 +2009 219 27.1 14.9 23.75 0 1185.71 397.39 51934 +2009 220 27.9 14.5 24.22 0 1199.29 396.61 51762 +2009 221 24 17.5 22.21 0 1040.71 217.24 51588 +2009 222 28 16.5 24.84 1.12 1348.57 413.94 51413 +2009 223 27.8 16.3 24.64 0.04 815 327.35 51235 +2009 224 27.8 14.1 24.03 0.01 1243.57 402.58 51057 +2009 225 24.9 14.1 21.93 0.71 685 188.57 50876 +2009 226 23.4 17.1 21.67 0.68 578.57 314.78 50694 +2009 227 26.6 11.8 22.53 0 912.14 449.66 50510 +2009 228 28.7 14 24.66 0 1219.29 470.73 50325 +2009 229 31.5 15.5 27.1 0 1483.57 443.58 50138 +2009 230 30.7 15.6 26.55 0 1455 420.81 49951 +2009 231 27.4 14.7 23.91 0 1182.86 257.78 49761 +2009 232 28.9 16 25.35 0 1191.43 419.82 49571 +2009 233 29.3 14.7 25.29 0 1596.43 456.15 49380 +2009 234 26.9 18.4 24.56 0.96 884.29 274.82 49187 +2009 235 24.3 15.4 21.85 0 927.86 428.6 48993 +2009 236 24.5 9.9 20.48 0 854.29 399.01 48798 +2009 237 26.4 10.8 22.11 0.2 1365.87 313.18 48603 +2009 238 28.7 11.3 23.91 0 1212.5 431.21 48406 +2009 239 29.9 15 25.8 0.01 1261.43 439.97 48208 +2009 240 30.6 16 26.59 0.01 1412.86 437.65 48010 +2009 241 25.3 15.8 22.69 1.33 447.14 64.31 47811 +2009 242 23.4 12.9 20.51 0 1147.14 456.04 47611 +2009 243 24.7 7.3 19.91 0.02 1071.43 472.3 47410 +2009 244 26.5 8 21.41 0 1141.43 451.32 47209 +2009 245 27.3 11.1 22.84 0.01 986.92 348.41 47007 +2009 246 29.2 13.9 24.99 0.61 1160.77 399.05 46805 +2009 247 25 15.1 22.28 3.93 182.31 66.79 46601 +2009 248 20.7 11.5 18.17 0.01 611.54 308.95 46398 +2009 249 21.1 6.5 17.09 0 798.46 445.8 46194 +2009 250 21.5 7.1 17.54 0 848.46 365.3 45989 +2009 251 22.1 7.6 18.11 0 816.92 462.79 45784 +2009 252 23 9.8 19.37 0 797.69 378.55 45579 +2009 253 25.4 11.8 21.66 0.11 1060.77 417.12 45373 +2009 254 21.2 11.9 18.64 0.29 573.85 155.49 45167 +2009 255 23.3 14.1 20.77 0 700.77 421.79 44961 +2009 256 22.4 9.8 18.93 0.16 990 416.04 44755 +2009 257 19.3 12.4 17.4 0.01 340.83 161.78 44548 +2009 258 23.4 12.9 20.51 0 434.17 266.98 44341 +2009 259 25.1 12.4 21.61 0.1 860.83 322.59 44134 +2009 260 22.6 17 21.06 1.55 563.33 267.35 43927 +2009 261 22.2 17.1 20.8 0.17 495 162.68 43719 +2009 262 22.3 14.5 20.16 0 593.33 307.54 43512 +2009 263 24.3 13.4 21.3 0 1013.33 368.21 43304 +2009 264 25 11.3 21.23 0 1027.5 361.77 43097 +2009 265 25.6 11.1 21.61 0 1132.5 403.53 42890 +2009 266 25.4 8.7 20.81 0 1164.17 388.31 42682 +2009 267 25.8 9.4 21.29 0 1043.33 371.54 42475 +2009 268 22.3 12.4 19.58 0 834.17 385.27 42268 +2009 269 21.5 7.8 17.73 0 956.67 387.86 42060 +2009 270 23.3 6.4 18.65 0 1024.17 378.81 41854 +2009 271 24.3 7.6 19.71 0 1028.33 328.87 41647 +2009 272 23.5 10 19.79 0 970.83 272.26 41440 +2009 273 22.6 8.8 18.81 0 860.83 307.26 41234 +2009 274 23.3 9.1 19.4 0.7 700 254.12 41028 +2009 275 19.2 11.1 16.97 0.01 211.82 58.54 40822 +2009 276 17.3 5.2 13.97 0 620 328.16 40617 +2009 277 21.3 4.2 16.6 0.02 784.55 393.82 40412 +2009 278 21.2 4.7 16.66 0 840 372.09 40208 +2009 279 26 10.5 21.74 0 1111.82 363.83 40003 +2009 280 25.4 12.9 21.96 0 1020 304.39 39800 +2009 281 25.3 9.6 20.98 0 866.36 325.18 39597 +2009 282 18.3 12.3 16.65 0.1 325.45 120.52 39394 +2009 283 16 11.2 14.68 1.83 251.82 153.78 39192 +2009 284 20.6 10.3 17.77 0.36 604.55 267.81 38991 +2009 285 11.6 8.8 10.83 0.94 207.27 36.75 38790 +2009 286 11.3 6.4 9.95 0 531.82 270.95 38590 +2009 287 9.2 0.7 6.86 0 430.91 175.23 38391 +2009 288 9.8 1.5 7.52 0 481.82 178.92 38193 +2009 289 9.2 0.5 6.81 0 453.64 178.48 37995 +2009 290 9.4 1.8 7.31 0 281.82 166.86 37799 +2009 291 9.8 3.1 7.96 0.05 246.36 184.36 37603 +2009 292 9.3 -2.2 6.14 0 292.73 226.05 37408 +2009 293 11.2 3.2 9 0 353.64 181.79 37214 +2009 294 15.8 -2.8 10.69 0 454.55 277.34 37022 +2009 295 19 11.8 17.02 0.09 684.55 184.97 36830 +2009 296 16.7 9.8 14.8 0.21 247.27 142.88 36640 +2009 297 11.6 9.3 10.97 0.5 246.36 42.75 36451 +2009 298 17 3.1 13.18 0 400 259.77 36263 +2009 299 15.3 6 12.74 0 190 78.85 36076 +2009 300 18.7 7.6 15.65 0.01 632 261.81 35891 +2009 301 16.3 2.8 12.59 0 593 237.67 35707 +2009 302 13.5 3.5 10.75 0.18 262 143.04 35525 +2009 303 10.1 1.6 7.76 0 311 268.36 35345 +2009 304 9.6 -3.1 6.11 0 244 234.26 35166 +2009 305 6.1 -0.7 4.23 0 37 123.09 34988 +2009 306 4.9 -0.7 3.36 0.45 147 146.46 34813 +2009 307 3.9 1.3 3.19 0.56 72 88.55 34639 +2009 308 4.2 0.8 3.27 0.48 104 84.08 34468 +2009 309 11.5 2.8 9.11 0.17 138.89 152.97 34298 +2009 310 5.6 4.5 5.3 1 40 20.89 34130 +2009 311 7.8 2.6 6.37 0.23 70 53.21 33964 +2009 312 7.3 1.8 5.79 0.61 40 28.49 33801 +2009 313 9.9 4.4 8.39 0.02 115.56 121.86 33640 +2009 314 9 2.3 7.16 0.86 141.11 42.37 33481 +2009 315 9.2 4.2 7.82 0.02 315.56 69.48 33325 +2009 316 12.8 -1.4 8.89 0.25 419.44 240 33171 +2009 317 13.3 -0.7 9.45 0 381.11 220.93 33019 +2009 318 16 -0.8 11.38 0 345.56 198.49 32871 +2009 319 15.3 3.3 12 0 292.22 156.28 32725 +2009 320 13.8 4.1 11.13 0.01 260 167.35 32582 +2009 321 17.9 3.3 13.89 0.01 363.33 227.41 32441 +2009 322 12.1 3.6 9.76 0.08 277.78 58.75 32304 +2009 323 16.8 1.5 12.59 0.01 368.89 221.29 32170 +2009 324 15.5 -0.7 11.05 0 418.89 217.74 32039 +2009 325 5.4 1.6 4.36 0.02 40 51.45 31911 +2009 326 5.4 2.6 4.63 0.01 34.44 53.97 31786 +2009 327 10 3.6 8.24 0.09 38.89 69.73 31665 +2009 328 15.1 1.7 11.41 0.02 212.22 150.85 31547 +2009 329 14 0.5 10.29 0 373.33 202.16 31433 +2009 330 8.3 -0.2 5.96 0 194.44 91.35 31322 +2009 331 13 -0.1 9.4 0 321.11 111.2 31215 +2009 332 8.6 2.6 6.95 0.4 72.22 52.23 31112 +2009 333 12.4 -1.2 8.66 0.01 306.67 79.9 31012 +2009 334 14.9 9.4 13.39 0 452.22 110.11 30917 +2009 335 15.1 6.4 12.71 0.84 126.67 65.29 30825 +2009 336 6.5 1.8 5.21 0.28 47.78 125.6 30738 +2009 337 5.6 1.8 4.55 0 57.78 88.36 30654 +2009 338 5.1 1 3.97 0.02 67.78 20.75 30575 +2009 339 7.2 -1 4.95 0 101.11 112.79 30500 +2009 340 4.5 -0.1 3.24 0 46.67 81.13 30430 +2009 341 5 -1.1 3.32 0.26 93.33 118.21 30363 +2009 342 5.2 1.1 4.07 1.48 45.56 17.67 30301 +2009 343 9 4 7.63 0 362.22 51.27 30244 +2009 344 9.2 1.1 6.97 0.09 263.33 155.7 30191 +2009 345 6.4 2.2 5.25 0.35 117.78 61.95 30143 +2009 346 5.4 1.4 4.3 0.04 115.56 29.77 30099 +2009 347 1.4 -1.3 0.66 0 147.5 38.1 30060 +2009 348 -1.3 -3.3 -1.85 0.41 73.75 39.65 30025 +2009 349 -0.7 -3.9 -1.58 0 107.5 83.18 29995 +2009 350 -1.1 -3.9 -1.87 0.03 127.5 63.4 29970 +2009 351 -1.2 -6.1 -2.55 0 119.04 97.26 29950 +2009 352 -2.8 -10.5 -4.92 0 102.5 93.09 29934 +2009 353 -7.7 -14 -9.43 1.21 38.75 24.92 29924 +2009 354 -6.8 -20.1 -10.46 0 50 146.02 29918 +2009 355 -0.3 -20.4 -5.83 0 80 152.77 29916 +2009 356 6.9 -0.3 4.92 0.01 207.5 94.86 29920 +2009 357 15.9 4.5 12.77 0.03 338.75 92.65 29928 +2009 358 13.5 2.3 10.42 0 311.25 99.85 29941 +2009 359 17.4 7.5 14.68 1.4 541.25 101.09 29959 +2009 360 9.6 -0.6 6.79 0 505 161.15 29982 +2009 361 4 -1.2 2.57 0.21 57.5 54.79 30009 +2009 362 5.7 -1.9 3.61 0 181.25 174.64 30042 +2009 363 2.5 -4.4 0.6 0 90 128.16 30078 +2009 364 6.5 -1.1 4.41 0.01 128.75 108.17 30120 +2009 365 5.7 -0.6 3.97 0 37.5 86.12 30166 +2010 1 4.2 1.3 3.4 0.02 30 36.53 30217 +2010 2 5.1 1.7 4.17 0 215 64.19 30272 +2010 3 3.8 -5.2 1.32 0 303.75 142.58 30331 +2010 4 0.8 -8.8 -1.84 0.02 168.75 203.03 30396 +2010 5 0.1 -2.1 -0.5 0.72 48.75 43.33 30464 +2010 6 0.2 -2.9 -0.65 0.24 35 86.13 30537 +2010 7 0.1 -1.8 -0.42 0.22 57.5 54.95 30614 +2010 8 0.3 -1.4 -0.17 1.95 30 31.84 30695 +2010 9 0.8 0.3 0.66 0.97 30 26.84 30781 +2010 10 1.5 0.5 1.23 0.09 30 51.28 30870 +2010 11 0.5 -0.5 0.23 0 91.11 52.63 30964 +2010 12 0 -1.3 -0.36 0 128.89 129.42 31061 +2010 13 -0.3 -1.5 -0.63 0 70 43.01 31162 +2010 14 -0.3 -1.5 -0.63 0 80 34.14 31268 +2010 15 1 -1.1 0.42 0 131.11 82.16 31376 +2010 16 3.2 -2.7 1.58 0 180 176.37 31489 +2010 17 -0.7 -3.5 -1.47 0.37 30 56.27 31605 +2010 18 2.5 -2.1 1.23 0.27 65.56 122.02 31724 +2010 19 3.5 -0.4 2.43 0 56 131.02 31847 +2010 20 3 -2.1 1.6 0 91 132.31 31974 +2010 21 0.3 -5.3 -1.24 0.46 44 71.55 32103 +2010 22 -3.6 -5.7 -4.18 0 99 71.79 32236 +2010 23 -4 -7 -4.83 0 85 93.11 32372 +2010 24 -3.1 -5.5 -3.76 0.01 88 98.53 32510 +2010 25 -2.2 -5.8 -3.19 0 124 164.53 32652 +2010 26 -4.2 -8.4 -5.36 0 114 150.41 32797 +2010 27 -4.2 -16.4 -7.55 0 145 294.23 32944 +2010 28 -2.3 -14.1 -5.54 0 113 125.56 33094 +2010 29 1.7 -10.2 -1.57 0 173 113.93 33247 +2010 30 2.7 -1.1 1.66 0.12 144 76.71 33402 +2010 31 1.4 -3.9 -0.06 0 219 105.54 33559 +2010 32 3.9 -12.4 -0.58 0 310 255.78 33719 +2010 33 5.3 -8.3 1.56 0 284 238.35 33882 +2010 34 7.3 -4.6 4.03 0 371 110.04 34046 +2010 35 7.1 -2.2 4.54 0 200 237.85 34213 +2010 36 6 -5.6 2.81 0.11 112 117.62 34382 +2010 37 3.3 -0.9 2.14 0.75 35 71.96 34552 +2010 38 -0.5 -5 -1.74 0 126 139.05 34725 +2010 39 -2.1 -13.8 -5.32 0 122 135.19 34900 +2010 40 -3.1 -5.1 -3.65 0.04 109 86.84 35076 +2010 41 -0.2 -4 -1.25 0.72 96 111.61 35254 +2010 42 -0.6 -2.5 -1.12 0.48 36 95.17 35434 +2010 43 0.1 -3.1 -0.78 0 124 119.19 35615 +2010 44 5.6 -5.4 2.57 0 276 253.55 35798 +2010 45 2.3 -11.4 -1.47 0 214 193.04 35983 +2010 46 1.1 -4 -0.3 0 134 117.51 36169 +2010 47 2.3 -9.4 -0.92 0 134 261.18 36356 +2010 48 6.1 -2 3.87 0 142 212.39 36544 +2010 49 9.4 -4.5 5.58 0 178 195.49 36734 +2010 50 9.8 -3.7 6.09 0.71 127 147.6 36925 +2010 51 5.6 1.6 4.5 0.11 214 107.88 37117 +2010 52 8.9 -3.4 5.52 0 479 283.51 37310 +2010 53 10.2 -0.3 7.31 0 363.64 240.55 37505 +2010 54 13.2 2.8 10.34 0 442.73 219.43 37700 +2010 55 14 -1 9.88 0 415.45 234.87 37896 +2010 56 14.5 -1 10.24 0 390 285.08 38093 +2010 57 12.2 3.7 9.86 0.81 289.09 94.84 38291 +2010 58 13.4 1.9 10.24 0 796.36 341.7 38490 +2010 59 14.7 1.3 11.02 0.02 703.64 211.07 38689 +2010 60 16.8 4.5 13.42 0 424.55 274.29 38890 +2010 61 11.4 3.8 9.31 0 370.13 225.05 39091 +2010 62 8 -0.3 5.72 0 319.09 117.19 39292 +2010 63 4.3 0.8 3.34 0 175.83 76.89 39495 +2010 64 4.2 -1.1 2.74 0 341.67 333.54 39697 +2010 65 3.1 -6.7 0.41 0.01 278.33 286.58 39901 +2010 66 0.2 -3.5 -0.82 0 201.67 166.18 40105 +2010 67 1 -9.7 -1.94 0 252.5 345.38 40309 +2010 68 2.2 -3.1 0.74 0 286.67 218.11 40514 +2010 69 1.3 -3.1 0.09 1.01 165.83 114.52 40719 +2010 70 1.6 -2.1 0.58 0 61.67 113.36 40924 +2010 71 6.5 -7 2.79 0 248.33 259.96 41130 +2010 72 10 -2.3 6.62 0 473.33 215.42 41336 +2010 73 11.5 -1.8 7.84 0 611.67 267.54 41543 +2010 74 6.2 -2.7 3.75 0.03 333.33 231.09 41749 +2010 75 11.4 -2.3 7.63 0.05 290 209.14 41956 +2010 76 11.5 0.9 8.59 0.03 352.5 315.15 42163 +2010 77 15.8 -2.4 10.8 0 630 355.17 42370 +2010 78 17.5 -1.1 12.39 0 721.67 279.52 42578 +2010 79 18.5 0.7 13.61 0 776.67 322.39 42785 +2010 80 20 7.3 16.51 0 790.83 302.88 42992 +2010 81 14.2 7.1 12.25 0.47 206.67 112.6 43200 +2010 82 16.8 3.4 13.12 0.01 330.83 330.67 43407 +2010 83 17.2 1.2 12.8 0.02 485 277.13 43615 +2010 84 17.3 9.6 15.18 0 503.33 299.41 43822 +2010 85 18.7 10.5 16.45 0 771.67 318.32 44029 +2010 86 16.3 7.2 13.8 0.09 614.17 284.13 44236 +2010 87 17.5 1.1 12.99 0 785 342.44 44443 +2010 88 20.2 2.7 15.39 0 1040 377.55 44650 +2010 89 19 11.6 16.97 0.09 941.67 283.05 44857 +2010 90 13.9 6.6 11.89 0.93 205 101.47 45063 +2010 91 16.5 1.7 12.43 0.6 717.5 428.59 45270 +2010 92 12.3 3.6 9.91 0 366.15 258.54 45475 +2010 93 16.2 -1.3 11.39 0.01 644.62 438.55 45681 +2010 94 14.2 8.9 12.74 0 686.92 151.04 45886 +2010 95 12.7 6.8 11.08 1.63 256.92 77.83 46091 +2010 96 14.6 5.8 12.18 0 685.71 450.53 46295 +2010 97 15.5 -1.6 10.8 0 582.14 461.63 46499 +2010 98 18.2 -1.1 12.89 0.01 677.14 356.06 46702 +2010 99 19.2 1.2 14.25 0 814.29 410.45 46905 +2010 100 14.3 6.9 12.27 0.15 519.29 250.33 47107 +2010 101 9.7 1.8 7.53 0.16 261.43 228.97 47309 +2010 102 7.4 4.2 6.52 0.98 88.57 83.17 47510 +2010 103 10.2 5.7 8.96 0.46 105 86.44 47710 +2010 104 13.9 6.5 11.87 0.11 240 241.23 47910 +2010 105 15.3 6.7 12.94 0.81 350 249.61 48108 +2010 106 16.7 6.5 13.9 0 474.29 367.82 48306 +2010 107 15.1 3.7 11.97 0 639.29 506.92 48504 +2010 108 15.7 -0.8 11.16 0.06 455.71 258.35 48700 +2010 109 19.6 3.1 15.06 0 691.43 364.4 48895 +2010 110 22.1 2.6 16.74 0.05 1005 364.55 49089 +2010 111 20.6 5.3 16.39 0.02 991.43 380.77 49282 +2010 112 13.2 6.3 11.3 0.1 437.14 132.84 49475 +2010 113 15.2 7.4 13.06 0 417.86 203.42 49666 +2010 114 20.8 5.4 16.57 0.02 987.35 346.1 49855 +2010 115 21.8 5.1 17.21 0 1036.43 406.49 50044 +2010 116 24.3 4.7 18.91 0 1141.43 453.31 50231 +2010 117 20.5 12.1 18.19 0 840 343.2 50417 +2010 118 19.4 5.4 15.55 0 905 483.33 50601 +2010 119 22.2 2.9 16.89 0 1151.43 493.76 50784 +2010 120 27.2 5.9 21.34 0 1447.86 461.64 50966 +2010 121 23.9 10.5 20.22 0 1098.57 385.92 51145 +2010 122 22.1 9.8 18.72 0 785.71 287.95 51324 +2010 123 22 13.7 19.72 0 719.29 248.52 51500 +2010 124 20.8 9.9 17.8 0.22 443.57 254.53 51674 +2010 125 16.2 12.2 15.1 0.28 72.67 84.28 51847 +2010 126 20 11.9 17.77 0.35 651.33 477.63 52018 +2010 127 20.4 4.9 16.14 0 832 452.33 52187 +2010 128 18.4 4.4 14.55 0 528.67 294.11 52353 +2010 129 21.1 9.2 17.83 0 670 308.14 52518 +2010 130 22.1 10.1 18.8 0 837.33 397.46 52680 +2010 131 22.7 6.5 18.25 0 759.33 394.03 52840 +2010 132 19.3 12.7 17.48 0 462.67 282.84 52998 +2010 133 16.7 8.9 14.56 0.72 186 148.12 53153 +2010 134 19.1 9.3 16.41 0.68 170 212.36 53306 +2010 135 13.8 8.7 12.4 0.97 212.67 148.99 53456 +2010 136 11.2 7.4 10.15 1.14 313.33 58.66 53603 +2010 137 16.7 8.1 14.33 0.06 619.33 151.41 53748 +2010 138 18.3 8.7 15.66 0 630.67 244.97 53889 +2010 139 18.2 4.8 14.52 0 690.67 395.22 54028 +2010 140 16.2 8.6 14.11 0.17 398.67 191.66 54164 +2010 141 20.2 11.9 17.92 0.44 434.67 192.23 54297 +2010 142 23 11.3 19.78 0 706.88 407.3 54426 +2010 143 22.9 8.8 19.02 0 931.25 403.09 54552 +2010 144 26.2 9.4 21.58 0 1241.25 424.54 54675 +2010 145 28.9 12.5 24.39 0.02 1355 435.62 54795 +2010 146 26.8 13.7 23.2 0.04 1041.88 441.32 54911 +2010 147 27 11.5 22.74 0.17 935 427.63 55023 +2010 148 24.5 10.9 20.76 0 920 445.29 55132 +2010 149 23.5 14.5 21.02 0.14 718.13 380.19 55237 +2010 150 22.5 14.9 20.41 0.31 495.63 269.24 55339 +2010 151 16 11.7 14.82 0.22 395 116.43 55436 +2010 152 16 8.4 13.91 0.75 483.75 134.5 55530 +2010 153 13.4 10.2 12.52 4.37 91.88 91.55 55619 +2010 154 17.7 11.4 15.97 0.77 243.75 165.96 55705 +2010 155 21 12.9 18.77 0.52 503.12 174.38 55786 +2010 156 23.9 8.5 19.66 0 1096.25 513.64 55863 +2010 157 25.9 8.7 21.17 0.01 975 514.03 55936 +2010 158 27 10.9 22.57 0 938.75 467.22 56004 +2010 159 28.9 14.4 24.91 0 1119.37 459.7 56068 +2010 160 30 17.4 26.54 0 1453.12 493.52 56128 +2010 161 30.2 18.8 27.07 0 1746.88 435.44 56183 +2010 162 32.9 20.3 29.43 0 2296.88 470.14 56234 +2010 163 33 16.5 28.46 0 2157.5 480.71 56280 +2010 164 29.4 19.9 26.79 0 1207.5 466.4 56321 +2010 165 26.5 16.3 23.7 0.16 514.38 363.21 56358 +2010 166 27.4 12.2 23.22 0.03 1031.25 470.51 56390 +2010 167 23.5 15 21.16 3.02 116.88 60.8 56418 +2010 168 21 15.5 19.49 0.46 269.38 178.97 56440 +2010 169 25.9 14.7 22.82 1.53 639.38 354.12 56458 +2010 170 21 14.4 19.18 0 420.63 261.57 56472 +2010 171 17.2 13.6 16.21 0.51 300 111.03 56480 +2010 172 15.5 11.7 14.46 2.11 290 92.43 56484 +2010 173 20.5 13.9 18.68 0 790.62 287.25 56482 +2010 174 22.4 13.4 19.92 0 1066.88 509.88 56476 +2010 175 23.8 10.2 20.06 0 1135.63 426.05 56466 +2010 176 23.5 10.4 19.9 0.42 641.88 258.82 56450 +2010 177 22.1 13 19.6 0.03 685 144.23 56430 +2010 178 25.9 13.5 22.49 0 1236.87 498.88 56405 +2010 179 26.9 9.9 22.22 0.01 1164.38 494.91 56375 +2010 180 29 14.2 24.93 0 1436.25 489.8 56341 +2010 181 30.2 12.9 25.44 0 1648.75 503.54 56301 +2010 182 30.2 14.3 25.83 0 1645.62 438.72 56258 +2010 183 30.1 14.3 25.76 0.39 1461.25 439.02 56209 +2010 184 32 15.5 27.46 0.01 1605 460.52 56156 +2010 185 28.4 14.9 24.69 0.01 1473.13 446.32 56099 +2010 186 29 15.6 25.32 0 1273.75 320.39 56037 +2010 187 28 16.8 24.92 0.03 1116.88 277.58 55971 +2010 188 25 15 22.25 0 1281.88 368.81 55900 +2010 189 27.2 8.4 22.03 0 1388.13 491.18 55825 +2010 190 29 9.7 23.69 0 1807.5 486.83 55746 +2010 191 30.6 11.4 25.32 0 1993.75 496.86 55663 +2010 192 32.3 13.2 27.05 0.01 1930.62 477.3 55575 +2010 193 32.9 15.2 28.03 0 1901.25 466.62 55484 +2010 194 32.7 17.3 28.47 0.01 1213.12 346.51 55388 +2010 195 33.4 16.7 28.81 0 1858.12 479.4 55289 +2010 196 34 18.9 29.85 0 1628.13 433.41 55186 +2010 197 32.9 19.9 29.32 0 1758.08 428.47 55079 +2010 198 33.2 19.4 29.41 1.75 1847.96 437.66 54968 +2010 199 28.1 18 25.32 0 1165.13 368.13 54854 +2010 200 25 13.2 21.76 0 1086.9 450.95 54736 +2010 201 27.9 13.4 23.91 0 1430.57 370.91 54615 +2010 202 30.5 16.9 26.76 0 1589.98 444.6 54490 +2010 203 32.3 16.8 28.04 0 1875.02 464.56 54362 +2010 204 29.8 18.7 26.75 0.28 1356.35 380.29 54231 +2010 205 24.2 16.4 22.06 1.94 787.38 198.2 54097 +2010 206 18.7 13.9 17.38 0.04 396.45 132.4 53960 +2010 207 20.3 10.9 17.72 0.01 722.91 234.62 53819 +2010 208 25.3 13.7 22.11 0 1093.66 345.75 53676 +2010 209 27.3 15.6 24.08 0 1226.2 408.23 53530 +2010 210 26.1 13.9 22.75 2.5 1177.85 296.76 53382 +2010 211 19.5 13.7 17.91 0.22 483.74 115.37 53230 +2010 212 24.3 14.5 21.61 0 929.47 339.25 53076 +2010 213 27.7 12.4 23.49 0 1453.87 493.62 52920 +2010 214 29.2 13.6 24.91 0 1593 478.01 52761 +2010 215 26 15.9 23.22 2.23 1040.59 258.32 52600 +2010 216 25.3 14.7 22.39 0 1033.68 437.3 52437 +2010 217 25 11.7 21.34 1.79 1164.34 380.68 52271 +2010 218 22.7 16.4 20.97 1.02 616.63 198.52 52103 +2010 219 20.5 14.6 18.88 0.18 518.54 139.3 51934 +2010 220 26.7 14.5 23.34 0 1217.13 429.76 51762 +2010 221 23.6 16.1 21.54 0.13 740.2 198.8 51588 +2010 222 26.9 11.4 22.64 0 1399.96 348.32 51413 +2010 223 27.8 14.1 24.03 0 1380.48 446.81 51235 +2010 224 27.9 12.9 23.77 0 1455.52 415.53 51057 +2010 225 28.3 15.2 24.7 1.72 1383.54 404.86 50876 +2010 226 27.2 16 24.12 0.8 1187.03 368.78 50694 +2010 227 26.8 18 24.38 0.09 988.61 341.61 50510 +2010 228 25.3 14 22.19 0.03 1076.22 294.24 50325 +2010 229 25 13.7 21.89 0.3 1058.61 400.37 50138 +2010 230 23.1 14.6 20.76 0.11 788.79 285.75 49951 +2010 231 25.8 16.6 23.27 0 966.35 340.44 49761 +2010 232 25.5 16.1 22.91 0 964.92 315.36 49571 +2010 233 27.8 16.9 24.8 0 1205.13 422.04 49380 +2010 234 27.8 14.1 24.03 0 1380.48 448.07 49187 +2010 235 28.1 13.3 24.03 0 1461.57 459 48993 +2010 236 24.1 15.7 21.79 0.07 826.35 150.13 48798 +2010 237 19.5 16.7 18.73 0 259.37 180.65 48603 +2010 238 27 12.7 23.07 0 1351.94 430.94 48406 +2010 239 30.1 16.1 26.25 1.93 1581.45 342.89 48208 +2010 240 21.3 15.7 19.76 0.12 519.87 102.88 48010 +2010 241 20.6 7.4 16.97 0.01 903.8 358.93 47811 +2010 242 15.3 9 13.57 0.23 405.96 94.11 47611 +2010 243 14.9 7.4 12.84 0.21 451.89 216.65 47410 +2010 244 20.9 11.8 18.4 0 731.63 392.35 47209 +2010 245 21.4 6.6 17.33 0.05 1003.35 328.54 47007 +2010 246 18.6 10.2 16.29 0.04 607.38 236.83 46805 +2010 247 18.6 11.8 16.73 0.6 520.38 151.64 46601 +2010 248 18.2 8.9 15.64 0 636.46 383.92 46398 +2010 249 16.7 9.9 14.83 0.08 466.73 248.71 46194 +2010 250 12.7 6.4 10.97 0.05 348.29 85.9 45989 +2010 251 16.1 12.1 15 0.34 293.34 76.4 45784 +2010 252 20.4 14.7 18.83 0.26 501.66 231.98 45579 +2010 253 19.9 12.3 17.81 0 608.62 162.49 45373 +2010 254 21 13.6 18.97 0 634.77 185.43 45167 +2010 255 21.1 10.2 18.1 0 832.39 222.21 44961 +2010 256 21.8 8.5 18.14 0 972.18 342.95 44755 +2010 257 22.4 10.5 19.13 0 944.78 433.52 44548 +2010 258 23.1 13.2 20.38 0 875.69 320.79 44341 +2010 259 18.9 14.3 17.64 1.24 386.94 90.38 44134 +2010 260 15.9 14.2 15.43 3.42 133.88 74.82 43927 +2010 261 14.7 10.9 13.65 1.95 258.99 142.4 43719 +2010 262 16.7 10.3 14.94 0.13 445.63 232.97 43512 +2010 263 19.8 3.5 15.32 0 954.76 406.8 43304 +2010 264 20.9 4.4 16.36 0 1023.69 417.01 43097 +2010 265 21.6 5 17.04 0 1069.04 427.44 42890 +2010 266 21.4 4.9 16.86 0 1053.99 419.37 42682 +2010 267 22.5 7.3 18.32 0 1082.6 374.13 42475 +2010 268 17.5 10.9 15.68 4.48 477.74 124.44 42268 +2010 269 15.2 11.2 14.1 1.35 278.57 57.04 42060 +2010 270 14.9 8.1 13.03 0 420.32 163.07 41854 +2010 271 19.9 9.6 17.07 0.02 750.19 263.23 41647 +2010 272 17 7.5 14.39 0.37 602.07 255.11 41440 +2010 273 12.5 8.5 11.4 0 238 148.64 41234 +2010 274 12.7 8.7 11.6 0 240.82 149.01 41028 +2010 275 14.2 9.6 12.93 0 295.78 171.15 40822 +2010 276 13.2 10.1 12.35 0 198.68 119.74 40617 +2010 277 18.5 10.5 16.3 0 583.38 260.99 40412 +2010 278 18.4 11.9 16.61 0.76 497.06 166.26 40208 +2010 279 12 10.1 11.48 0.13 118.67 58.42 40003 +2010 280 16.6 7.3 14.04 0 579.94 265.58 39800 +2010 281 14.2 4.1 11.42 0 530.61 215.76 39597 +2010 282 15.2 0.5 11.16 0 692.56 304.62 39394 +2010 283 15.8 2 12.01 0 696.82 323.16 39192 +2010 284 15.3 0.2 11.15 0 705.3 327.4 38991 +2010 285 16.1 -0.1 11.65 0 763.07 258.04 38790 +2010 286 14.5 1.9 11.04 0 614.66 184.16 38590 +2010 287 15.1 4.3 12.13 0 583.59 291.47 38391 +2010 288 13.2 2.3 10.2 0 523.35 254.45 38193 +2010 289 13.2 6.7 11.41 0 367.46 175.09 37995 +2010 290 9.5 2.5 7.58 1.59 310.54 58.21 37799 +2010 291 8.8 6.5 8.17 0.45 117 48.98 37603 +2010 292 8.5 6.8 8.03 0.04 86.89 40.22 37408 +2010 293 7.2 4.5 6.46 0.62 122.71 52.89 37214 +2010 294 12.9 2.5 10.04 0 499.54 278.46 37022 +2010 295 13.5 -2 9.24 0 638.64 341.14 36830 +2010 296 14.6 -0.5 10.45 0 675.77 261.24 36640 +2010 297 17.5 5 14.06 0.38 732.26 244.85 36451 +2010 298 10 5.2 8.68 0.83 238.71 23.86 36263 +2010 299 8.4 3.7 7.11 0 212.84 81.08 36076 +2010 300 9.2 -1.9 6.15 0 412.99 311.54 35891 +2010 301 10 -4 6.15 0 490.15 299.71 35707 +2010 302 13 -2.5 8.74 0 619.1 309.66 35525 +2010 303 16.9 -1.4 11.87 0 838.36 295.29 35345 +2010 304 16.9 8.6 14.62 0 546.05 213.31 35166 +2010 305 17.4 5.6 14.15 0 704.73 151.33 34988 +2010 306 14.9 7.3 12.81 0 456.25 120.28 34813 +2010 307 11.5 6.3 10.07 0.09 278.8 76.98 34639 +2010 308 17.3 6 14.19 0 683.1 219.98 34468 +2010 309 20.3 3 15.54 0 1007.35 247.78 34298 +2010 310 15.6 2 11.86 0 683.47 222.73 34130 +2010 311 16.2 3.3 12.65 0 689.47 188.8 33964 +2010 312 13.4 8 11.91 0.71 321.72 39.86 33801 +2010 313 14 7.2 12.13 0.48 398.64 98.91 33640 +2010 314 11.1 7 9.97 0.42 223.67 63.97 33481 +2010 315 12.3 2.7 9.66 0 458.09 202.58 33325 +2010 316 16.2 2.7 12.49 0 705.95 133.09 33171 +2010 317 18.2 4.1 14.32 0 812.78 191.88 33019 +2010 318 18.5 1.1 13.72 0 907.11 237.92 32871 +2010 319 19.8 4.8 15.68 0 920.05 204.02 32725 +2010 320 14.6 6.1 12.26 0 485.06 121.98 32582 +2010 321 11.3 7.9 10.37 0.44 192.69 57.48 32441 +2010 322 12.9 8.3 11.64 0.18 274.08 93.8 32304 +2010 323 8.6 4.4 7.45 1.24 196.27 21.3 32170 +2010 324 7.8 5.1 7.06 0 127.29 57.27 32039 +2010 325 7.2 5.1 6.62 1.07 97.68 51.87 31911 +2010 326 10 6.9 9.15 0.24 164.42 49.68 31786 +2010 327 9.1 2.4 7.26 0 293.35 111.55 31665 +2010 328 9 -0.8 6.3 0 378.55 205.32 31547 +2010 329 8.5 -3.6 5.17 0 414.36 231.49 31433 +2010 330 2.1 -4.2 0.37 0.76 179.7 129.04 31322 +2010 331 5 -0.7 3.43 0 200.78 214.87 31215 +2010 332 0.4 -2.6 -0.43 2.17 87.64 31.95 31112 +2010 333 2.4 -1 1.46 0 111.22 76.52 31012 +2010 334 -0.6 -5.6 -1.97 0.2 125.9 93.33 30917 +2010 335 -1.7 -2.9 -2.03 1.09 32.92 44.23 30825 +2010 336 -0.1 -1.8 -0.57 1.03 50.71 37.58 30738 +2010 337 -0.6 -2.2 -1.04 1.07 46.39 62.65 30654 +2010 338 -1.8 -9.1 -3.81 0 153.99 99.78 30575 +2010 339 -2.2 -9.3 -4.15 0 146.97 74.2 30500 +2010 340 7.2 -4 4.12 0 365.55 132.7 30430 +2010 341 13.5 4 10.89 0.02 489.27 98.48 30363 +2010 342 15.3 3.1 11.95 0.12 633.82 77.93 30301 +2010 343 14 -0.1 10.12 0.52 631.17 18.62 30244 +2010 344 1.3 -5.8 -0.65 0.32 185.96 145.51 30191 +2010 345 2 -9 -1.02 0 257.29 79.95 30143 +2010 346 5.6 -5.5 2.55 0 328.01 79 30099 +2010 347 1 -4 -0.38 0 139.94 133.86 30060 +2010 348 0.7 -10.8 -2.46 0 241.33 151.36 30025 +2010 349 0.2 -5.3 -1.31 0 143.05 112.92 29995 +2010 350 -2.5 -10.2 -4.62 0 152.23 141.44 29970 +2010 351 -3.8 -11.5 -5.92 0.93 139.15 84.76 29950 +2010 352 -4.6 -8.2 -5.59 0.16 73.42 97.42 29934 +2010 353 -1.4 -15.8 -5.36 0 231.44 115.84 29924 +2010 354 3.6 -10.2 -0.19 0 320.69 173.97 29918 +2010 355 6.1 -8.5 2.09 0 388.03 156.62 29916 +2010 356 9.2 1 6.94 0 341.06 49.3 29920 +2010 357 12.8 2.6 10 0.08 490.62 113.02 29928 +2010 358 11.6 0.5 8.55 0.66 479.62 130.06 29941 +2010 359 5 0.5 3.76 0.17 166.22 49.83 29959 +2010 360 1.3 -2.9 0.15 0 123.86 75.77 29982 +2010 361 1 -6 -0.93 0 180.47 180.44 30009 +2010 362 0.3 -8.4 -2.09 0 199.54 92.44 30042 +2010 363 -1.8 -9.5 -3.92 0 159.71 129.29 30078 +2010 364 -3.9 -10.5 -5.71 0 124.17 52.55 30120 +2010 365 -4.7 -6.2 -5.11 0 33.25 25.02 30166 +2011 1 -3.7 -5.6 -4.22 0 44.3 37.7 30217 +2011 2 -1.6 -4.7 -2.45 0.09 79.06 23.52 30272 +2011 3 1.4 -8.8 -1.41 0 236.8 99.21 30331 +2011 4 -3.6 -11 -5.63 0 137.35 59.2 30396 +2011 5 -3.5 -4.6 -3.8 0 26.89 29.83 30464 +2011 6 -2.7 -5.9 -3.58 0 75.51 180.81 30537 +2011 7 12.5 -4 7.96 0 615.21 146.34 30614 +2011 8 11.9 0.6 8.79 0 493.64 58.79 30695 +2011 9 14.4 -2.6 9.73 0 700.46 154.65 30781 +2011 10 9.6 -1.1 6.66 0.05 414.56 60.47 30870 +2011 11 3.9 1.6 3.27 0 86.5 40.22 30964 +2011 12 6 -0.2 4.29 0.04 228.12 76.72 31061 +2011 13 6 -0.7 4.16 0.07 241.72 64.17 31162 +2011 14 11.3 2.6 8.91 0 404.04 80.69 31268 +2011 15 13.3 -0.4 9.53 0 596.25 141.11 31376 +2011 16 12.5 -0.8 8.84 0 559.27 159.75 31489 +2011 17 2.3 -2.9 0.87 0 157.13 84.97 31605 +2011 18 3.1 -1.8 1.75 0 157.82 96.47 31724 +2011 19 3 -2.5 1.49 0.82 171.8 27.13 31847 +2011 20 3.3 -0.9 2.14 0 140.93 111.58 31974 +2011 21 1.8 -0.7 1.11 0 81.61 124.8 32103 +2011 22 0.4 -2.1 -0.29 0 74.55 83.57 32236 +2011 23 1.4 -8.2 -1.24 0.16 228.43 224 32372 +2011 24 1.4 -3.9 -0.06 0.03 150.41 284.53 32510 +2011 25 0.5 -6.2 -1.34 0 169.17 95.69 32652 +2011 26 2.3 -4.6 0.4 0.03 194.6 98.88 32797 +2011 27 0.7 -2.6 -0.21 0.06 97.1 46.92 32944 +2011 28 -0.6 -5.3 -1.89 0 119.83 104.33 33094 +2011 29 -0.8 -7.5 -2.64 0 155.08 118.91 33247 +2011 30 -1.9 -5.9 -3 0 96.29 70.66 33402 +2011 31 -2 -3.3 -2.36 0 34.81 59.57 33559 +2011 32 -0.8 -5.7 -2.15 0 122.26 162.4 33719 +2011 33 -1.5 -5.8 -2.68 0 104.99 149.27 33882 +2011 34 3.6 -10.5 -0.28 0 323.71 222.7 34046 +2011 35 7 -4.9 3.73 0 373.06 241.09 34213 +2011 36 14.3 -3.2 9.49 0 703.44 259.99 34382 +2011 37 11 -3.6 6.99 0 532.21 229.84 34552 +2011 38 18.5 -4.5 12.18 0 980.57 282.01 34725 +2011 39 12.3 -4.5 7.68 0 611.61 263.46 34900 +2011 40 9 -3.8 5.48 0 440.42 249.39 35076 +2011 41 9.1 -4.6 5.33 0 458.19 278.06 35254 +2011 42 12 -3.1 7.85 0.05 575.17 161.96 35434 +2011 43 4.6 1.1 3.64 0.01 131.16 80.93 35615 +2011 44 4 -0.3 2.82 0.03 150.27 94.66 35798 +2011 45 0.8 -0.5 0.44 0 41.78 32.23 35983 +2011 46 -0.5 -2 -0.91 0.08 43.96 42.19 36169 +2011 47 1.1 -2.1 0.22 0.29 97.04 45.1 36356 +2011 48 0.7 -0.3 0.42 0.12 32.33 49.59 36544 +2011 49 2.9 0.5 2.24 0.01 84.39 62.89 36734 +2011 50 6.9 -0.1 4.98 0 264.18 126.35 36925 +2011 51 2.7 -0.8 1.74 0 116.24 88.41 37117 +2011 52 -0.2 -4.8 -1.47 0.03 120.94 132.32 37310 +2011 53 -2.7 -5.5 -3.47 0.01 67.2 104.81 37505 +2011 54 -0.2 -8.6 -2.51 0 188.61 295.12 37700 +2011 55 1.4 -8.7 -1.38 0 235.44 327.23 37896 +2011 56 1.7 -10.7 -1.71 0 268.37 305.28 38093 +2011 57 2.1 -5.2 0.09 0 199.91 178.75 38291 +2011 58 -0.3 -7.9 -2.39 0 175.24 103.59 38490 +2011 59 3.9 -2 2.28 0 192.19 232.22 38689 +2011 60 0.5 -4.9 -0.99 0.05 143.86 60.91 38890 +2011 61 2.1 -7.3 -0.48 0.17 236.3 200.44 39091 +2011 62 0 -2.1 -0.58 0.01 62.02 78.09 39292 +2011 63 5.1 -6.5 1.91 0 325.25 244.37 39495 +2011 64 7.2 -5.9 3.6 0 396.89 367.39 39697 +2011 65 6.9 -4.8 3.68 0 367.3 331.27 39901 +2011 66 3.7 -2.6 1.97 0 199.37 319.48 40105 +2011 67 5.9 -9.4 1.69 0 390.31 391.53 40309 +2011 68 9.2 -7.4 4.63 0 499.54 337.08 40514 +2011 69 12.7 -4.1 8.08 0 627.21 190.12 40719 +2011 70 14.5 -4 9.41 0 725.54 339.43 40924 +2011 71 15.6 -4 10.21 0 790.4 353.72 41130 +2011 72 17 7.9 14.5 0 585.08 302.73 41336 +2011 73 18.9 7.9 15.87 0 737.88 270.55 41543 +2011 74 20.1 2.1 15.15 0 1010.44 351.35 41749 +2011 75 11.6 3.4 9.35 1.1 395.21 72.92 41956 +2011 76 16 8.7 13.99 0.15 472.52 157.18 42163 +2011 77 12.6 5.8 10.73 0.23 366.81 85.45 42370 +2011 78 7.8 3.4 6.59 0 194.28 67.33 42578 +2011 79 10 3.2 8.13 0 313.44 338.2 42785 +2011 80 10.1 -1.3 6.96 0 443.68 366.02 42992 +2011 81 14.6 -3.6 9.59 0 726.26 397.67 43200 +2011 82 16.1 -1.5 11.26 0 787.66 393.59 43407 +2011 83 20 -1 14.23 0 1053.53 410.5 43615 +2011 84 21.5 -1 15.31 0 1171.33 402.79 43822 +2011 85 21.4 1.4 15.9 1.01 1129.99 330.12 44029 +2011 86 11.1 4.6 9.31 0.03 324 44.59 44236 +2011 87 10.3 3 8.29 0 336.27 166.17 44443 +2011 88 16.5 1 12.24 0 767.35 413.1 44650 +2011 89 18.2 -1.1 12.89 0 922.93 441.54 44857 +2011 90 20.1 -0.3 14.49 0.02 1051.75 359.66 45063 +2011 91 18.6 6 15.14 0 784.59 180.23 45270 +2011 92 20.7 3.1 15.86 0 1038.21 468.73 45475 +2011 93 22.3 3 16.99 0 1178.26 391.41 45681 +2011 94 23.1 4 17.85 1.18 1230.26 328.4 45886 +2011 95 16.3 5.2 13.25 0 637.16 395.01 46091 +2011 96 18.2 1 13.47 0 887.04 220.53 46295 +2011 97 26.4 8.7 21.53 0 1443.93 418.59 46499 +2011 98 21.3 12.2 18.8 0 748.29 312.76 46702 +2011 99 21.5 5 16.96 0 1060.14 472.39 46905 +2011 100 19.8 4.5 15.59 0 928.53 461.85 47107 +2011 101 19.1 8.9 16.3 0 712.08 343.99 47309 +2011 102 20.4 6 16.44 0.91 934.32 250.62 47510 +2011 103 12.6 3 9.96 0 466.52 346.07 47710 +2011 104 12.2 4 9.95 0 409.84 202.34 47910 +2011 105 12.8 -0.1 9.25 0 560.93 296.59 48108 +2011 106 13.5 4.7 11.08 0 465.13 231.06 48306 +2011 107 16.5 0.7 12.15 0 773.71 343.7 48504 +2011 108 18.2 0.4 13.31 0 898.4 354.11 48700 +2011 109 20.3 0 14.72 0 1062.97 404.63 48895 +2011 110 22.3 1.9 16.69 0 1198.56 485.54 49089 +2011 111 24.3 2.1 18.2 0 1377.85 480.69 49282 +2011 112 24.2 3.3 18.45 0 1348.57 473.54 49475 +2011 113 24.4 3.6 18.68 0 1362.44 474.35 49666 +2011 114 24.4 8.5 20.03 0 1231.83 425.82 49855 +2011 115 21 7.5 17.29 1.98 935.99 374.03 50044 +2011 116 13.1 10 12.25 1.29 197.52 68.3 50231 +2011 117 17.7 5.7 14.4 0.52 724.21 261.01 50417 +2011 118 17.8 6.5 14.69 0.13 703.42 331.85 50601 +2011 119 18 10.2 15.86 0.53 556.68 267.79 50784 +2011 120 18.5 9 15.89 0.11 656.81 309.8 50966 +2011 121 18.2 6.7 15.04 0.52 727.58 265.3 51145 +2011 122 18.8 5 15.01 0 833.01 441.63 51324 +2011 123 22.1 8.3 18.31 0.55 1008.48 333.6 51500 +2011 124 13.3 1 9.92 0 564 535.67 51674 +2011 125 14.6 0.4 10.7 0 656.97 541.72 51847 +2011 126 18.1 -1 12.85 0 914.4 553.08 52018 +2011 127 21.1 1.8 15.79 0 1097.94 537.03 52187 +2011 128 18.1 3.4 14.06 0.3 824.42 172.19 52353 +2011 129 19.5 1.5 14.55 0 975.05 494.84 52518 +2011 130 24.3 5 18.99 0 1323.3 525.48 52680 +2011 131 24.4 7 19.61 0 1280.61 521.76 52840 +2011 132 26.8 7 21.36 0.43 1539.2 493.23 52998 +2011 133 22 12.5 19.39 0 801.27 519.18 53153 +2011 134 24.9 9.7 20.72 0.8 1240.53 412.02 53306 +2011 135 18.1 10.7 16.07 0.94 538.78 126.22 53456 +2011 136 17.9 10.2 15.78 0 548.34 427.55 53603 +2011 137 19.7 7.2 16.26 0 832.78 421.07 53748 +2011 138 23.4 6.4 18.72 0 1197.99 481.98 53889 +2011 139 25.9 8 20.98 0 1410.17 487.93 54028 +2011 140 26.9 9.2 22.03 0 1484.94 508.93 54164 +2011 141 27 10.8 22.54 0 1437.21 414.66 54297 +2011 142 27 10.6 22.49 0 1445.23 493.65 54426 +2011 143 27 11.4 22.71 0 1412.07 391.71 54552 +2011 144 28.7 11.9 24.08 0 1604.55 512.42 54675 +2011 145 23.3 13.5 20.61 0 879.53 511.56 54795 +2011 146 26.3 6.7 20.91 0 1491.18 517.64 54911 +2011 147 29.4 10.4 24.17 0.13 1753.67 496.15 55023 +2011 148 19.9 10.4 17.29 0.59 711.67 217.25 55132 +2011 149 23.4 5.4 18.45 0 1225.43 454.84 55237 +2011 150 25.3 7.3 20.35 0 1366.08 515.62 55339 +2011 151 28.4 9.4 23.17 0 1659.31 507.54 55436 +2011 152 25.5 12.6 21.95 0.1 1176.89 276.31 55530 +2011 153 24.3 13.4 21.3 0.05 995.86 344.29 55619 +2011 154 26.7 15.4 23.59 0.02 1161.75 395.19 55705 +2011 155 26.6 13.2 22.91 1.11 1277.22 396.96 55786 +2011 156 26.5 13.2 22.84 0 1264.98 399.02 55863 +2011 157 26.8 14.2 23.34 0 1247.13 424.09 55936 +2011 158 28.1 13.5 24.09 2.1 1451.42 430.2 56004 +2011 159 25.3 14.7 22.39 1.41 1033.68 375.01 56068 +2011 160 20.9 15.7 19.47 0.5 478.77 245.75 56128 +2011 161 22.8 12.9 20.08 0 861.2 518.27 56183 +2011 162 24.4 9.1 20.19 0 1209.9 541.61 56234 +2011 163 24.4 9.9 20.41 0 1178.39 470.82 56280 +2011 164 25.4 11.9 21.69 0 1200.24 451.45 56321 +2011 165 25.2 15 22.4 0.08 1002.68 289.78 56358 +2011 166 27.6 14.4 23.97 0 1337.73 500.57 56390 +2011 167 28.8 11.6 24.07 0 1630.08 490.06 56418 +2011 168 25.5 14.4 22.45 0 1076.07 371.97 56440 +2011 169 28.4 18.1 25.57 2.62 1199.44 281.41 56458 +2011 170 24.3 11.1 20.67 0.6 1115.13 167.14 56472 +2011 171 23.8 7.9 19.43 0 1190.6 495.5 56480 +2011 172 27.5 11.3 23.04 0 1477.53 497.85 56484 +2011 173 29.5 13.1 24.99 0 1658.01 505.84 56482 +2011 174 27.5 17.5 24.75 2.79 1120.86 446.23 56476 +2011 175 23.2 14.7 20.86 0.49 793.15 213.47 56466 +2011 176 23.3 9.5 19.5 0 1079.65 434.92 56450 +2011 177 23.6 13.4 20.8 0.08 918.14 251.29 56430 +2011 178 25.3 13.4 22.03 0 1110.63 454.02 56405 +2011 179 26.3 13.9 22.89 0 1202.25 545.28 56375 +2011 180 28.5 12.5 24.1 0 1552.05 543.93 56341 +2011 181 30.1 13.3 25.48 0 1731.82 429.51 56301 +2011 182 23.3 12.3 20.28 0.04 947.47 451.84 56258 +2011 183 19 11.2 16.86 0.19 589.42 369.13 56209 +2011 184 20.6 7 16.86 0 918.19 233.07 56156 +2011 185 25.9 12.7 22.27 0.09 1218.77 320 56099 +2011 186 23.1 11.9 20.02 0.12 947.46 255.2 56037 +2011 187 28.8 13.1 24.48 0.01 1563.53 461.63 55971 +2011 188 31.9 13.9 26.95 0 1966.52 510.87 55900 +2011 189 32.4 19.9 28.96 0 1673.51 435.79 55825 +2011 190 33.7 13.9 28.26 0 2248.16 509.47 55746 +2011 191 32.7 16.2 28.16 0 1974.31 506.78 55663 +2011 192 30.4 16.6 26.61 0 1594.39 477.65 55575 +2011 193 30.2 14.5 25.88 0 1686.78 503.71 55484 +2011 194 33.5 15.5 28.55 0 2141.78 399.48 55388 +2011 195 30.6 19.4 27.52 3.46 1422.91 389.31 55289 +2011 196 23.6 14.4 21.07 0 856.89 297.95 55186 +2011 197 25.4 12.7 21.91 0 1160.07 446 55079 +2011 198 29.2 12.5 24.61 0.02 1644.65 507.52 54968 +2011 199 26.9 16.9 24.15 0.04 1085.29 418.22 54854 +2011 200 26.9 12.1 22.83 0.2 1368.45 390.68 54736 +2011 201 23.4 15.1 21.12 0.47 788.44 195.75 54615 +2011 202 26 14 22.7 0.12 1159.97 357.51 54490 +2011 203 25.8 13 22.28 0.32 1191.28 320.28 54362 +2011 204 19.1 14.7 17.89 0.91 376.92 115.02 54231 +2011 205 16.3 12.6 15.28 1.95 277.43 66.22 54097 +2011 206 15.9 11.6 14.72 0.04 308.4 118.97 53960 +2011 207 18.6 13.1 17.09 0 440.7 82.84 53819 +2011 208 25.8 12.7 22.2 0.03 1206.94 497.8 53676 +2011 209 21.7 15 19.86 3.2 612.19 47.84 53530 +2011 210 24.5 14.6 21.78 0 946.11 379.28 53382 +2011 211 25.6 11.2 21.64 0.02 1255.75 276.44 53230 +2011 212 23.7 14.2 21.09 0 880.67 246.83 53076 +2011 213 24.4 12.8 21.21 0.06 1040.63 308.38 52920 +2011 214 27.3 15.9 24.17 0 1206.73 473.24 52761 +2011 215 27.9 12.8 23.75 0.86 1460.37 374.56 52600 +2011 216 23.9 17.7 22.19 1.05 650.04 92.34 52437 +2011 217 26.7 14.5 23.34 0 1217.13 452.26 52271 +2011 218 26.5 13.9 23.04 0 1226.84 380.6 52103 +2011 219 30.5 16.4 26.62 0 1621.86 445.55 51934 +2011 220 24.3 15.3 21.82 1.41 877.08 258.79 51762 +2011 221 23 13.4 20.36 0.46 853.19 362.47 51588 +2011 222 21.4 11 18.54 0 822.02 353.76 51413 +2011 223 24.1 6.2 19.18 0 1273.02 517.59 51235 +2011 224 26.4 9.1 21.64 0 1430.45 442 51057 +2011 225 25.9 15.5 23.04 0 1055.02 307.52 50876 +2011 226 28.5 13.2 24.29 0 1518.93 474.66 50694 +2011 227 30 14.3 25.68 1.28 1668.69 460.87 50510 +2011 228 25.5 14.7 22.53 0 1057.62 459.57 50325 +2011 229 27.7 13.4 23.77 0 1404.81 465.7 50138 +2011 230 29.8 14.4 25.57 0 1635.21 457.55 49951 +2011 231 30.8 14.9 26.43 1.58 1752.83 359.33 49761 +2011 232 27 14.7 23.62 0 1243.17 450.57 49571 +2011 233 29.1 15.8 25.44 0 1456.93 429.77 49380 +2011 234 32 17.3 27.96 0 1795.86 433.39 49187 +2011 235 33.2 18 29.02 0 1946.62 451.94 48993 +2011 236 34 16.4 29.16 0 2177.85 462.5 48798 +2011 237 31.3 16.7 27.29 0 1724.25 445.46 48603 +2011 238 33.5 16 28.69 0 2115.79 446.39 48406 +2011 239 31.8 16.9 27.7 0.71 1789.56 432.02 48208 +2011 240 22.8 12.5 19.97 0 883.76 391.15 48010 +2011 241 26.3 10.1 21.84 0 1382.33 440.34 47811 +2011 242 24.5 12.5 21.2 0 1067.88 387.15 47611 +2011 243 25.8 13.3 22.36 0 1175.17 425.78 47410 +2011 244 28.8 12.5 24.32 0.31 1591.43 401.06 47209 +2011 245 26.6 13.4 22.97 0.09 1266.61 393.99 47007 +2011 246 27.8 13.4 23.84 0 1417.66 478.24 46805 +2011 247 30.1 13.4 25.51 0 1727.15 426.52 46601 +2011 248 28.3 17.9 25.44 0.11 1200.69 382.72 46398 +2011 249 24.6 14.1 21.71 0 988.67 413.72 46194 +2011 250 25.9 8.9 21.22 0 1380.68 374.31 45989 +2011 251 21.9 14.7 19.92 0.02 653.82 178.57 45784 +2011 252 21.5 14.4 19.55 0 632.78 182.48 45579 +2011 253 28.8 13.4 24.57 0 1548.92 424.04 45373 +2011 254 30.2 12.4 25.31 0 1785.49 428.87 45167 +2011 255 28.2 14.9 24.54 0.22 1387.87 299.06 44961 +2011 256 28.1 13 23.95 0 1476.43 407.23 44755 +2011 257 29.1 13.8 24.89 0.04 1569.33 377.41 44548 +2011 258 21.4 11.1 18.57 0 816.95 230.49 44341 +2011 259 25 12.4 21.54 0 1129.55 362.26 44134 +2011 260 26.6 10.3 22.12 0 1409.56 362.77 43927 +2011 261 28.4 10.5 23.48 0.23 1621.41 376.81 43719 +2011 262 20.6 10.2 17.74 2.37 785.56 243.52 43512 +2011 263 17.7 10 15.58 0 542.08 124.93 43304 +2011 264 22.1 11.3 19.13 0 875.76 350.06 43097 +2011 265 23.6 12.2 20.47 0 984.9 315.25 42890 +2011 266 23.3 10.4 19.75 0 1040.97 364.36 42682 +2011 267 22.4 10.2 19.04 0 958.6 311.2 42475 +2011 268 23.6 7.2 19.09 0 1193.43 379.82 42268 +2011 269 24.6 6.5 19.62 0 1315.53 375.16 42060 +2011 270 25.6 7 20.48 0 1406.87 351.21 41854 +2011 271 24.3 7.9 19.79 0 1241.96 352.42 41647 +2011 272 23.6 5.3 18.57 0 1247.33 378.73 41440 +2011 273 24.5 8.2 20.02 0 1252.75 363.85 41234 +2011 274 26.3 7.3 21.08 0 1475.13 362.51 41028 +2011 275 25.6 7.9 20.73 0 1380.32 363.99 40822 +2011 276 25.6 6.3 20.29 0 1425.53 351.85 40617 +2011 277 26.3 6.3 20.8 0 1501.18 339.76 40412 +2011 278 25.4 7 20.34 0 1385.41 339 40208 +2011 279 24.3 8.4 19.93 0 1224.87 299.77 40003 +2011 280 18.6 6 15.14 3.88 784.59 26.13 39800 +2011 281 15.1 0.1 10.98 0 694.69 252.18 39597 +2011 282 12.4 -0.5 8.85 0 547.26 228.65 39394 +2011 283 9.3 -1.3 6.38 0.08 404.58 115.1 39192 +2011 284 23.4 7.2 18.95 0 1173.54 254.92 38991 +2011 285 19.7 8.7 16.68 0.07 340.91 203.99 38790 +2011 286 13.3 8.6 12.01 0 391.82 165.99 38590 +2011 287 11.5 0.9 8.59 0 431.82 302.34 38391 +2011 288 12.9 -2.2 8.75 0 404.55 357.78 38193 +2011 289 10.8 -0.7 7.64 0 510 352.76 37995 +2011 290 12.2 -4.5 7.61 0 525.45 350.44 37799 +2011 291 14.4 -3.6 9.45 0 600 329.07 37603 +2011 292 20.4 -2.1 14.21 1.42 758.18 297.87 37408 +2011 293 15 5.2 12.31 0.39 208.18 75.38 37214 +2011 294 10.7 1.9 8.28 0 375.45 250.76 37022 +2011 295 9.8 -3.1 6.25 0 276.36 229.01 36830 +2011 296 7.9 4.8 7.05 0.73 70 40.34 36640 +2011 297 9.4 6.7 8.66 0.59 28.18 33.67 36451 +2011 298 10.7 7 9.68 0.01 50.91 60.38 36263 +2011 299 10.4 8.2 9.79 0.31 117.27 69.64 36076 +2011 300 9.6 7.9 9.13 0.06 76 53.39 35891 +2011 301 12.2 8.9 11.29 0 92 80.89 35707 +2011 302 11.8 8.9 11 0 208 80.12 35525 +2011 303 13.8 6.8 11.88 0 400 195.03 35345 +2011 304 15 1.9 11.4 0 218 256.84 35166 +2011 305 7.2 2.4 5.88 0.05 25 45.47 34988 +2011 306 7.2 6.4 6.98 0.01 53 52.73 34813 +2011 307 9.1 5 7.97 0.01 70 63.39 34639 +2011 308 18.8 5 15.01 0 488 233.18 34468 +2011 309 20.1 13 18.15 0 678.89 192.31 34298 +2011 310 15.3 5 12.47 0 300 144.54 34130 +2011 311 10.7 1.8 8.25 0 194.44 145.7 33964 +2011 312 12.2 5 10.22 0 196.67 201.43 33801 +2011 313 8.8 3.1 7.23 0.03 20 65.27 33640 +2011 314 8.5 6.4 7.92 0 16.67 44.67 33481 +2011 315 7.6 -0.5 5.37 0 312.22 229.61 33325 +2011 316 8.7 -2.8 5.54 0 243.33 207.79 33171 +2011 317 9.7 -4.6 5.77 0 298.89 234.68 33019 +2011 318 8.2 -4.4 4.73 0 175 195.39 32871 +2011 319 5 -3.9 2.55 0 86.67 196.29 32725 +2011 320 -0.1 -3.6 -1.06 0 18.89 63.75 32582 +2011 321 1.7 -2.9 0.43 0 15.56 56.75 32441 +2011 322 0.9 -1.3 0.3 0 10 53.41 32304 +2011 323 -0.5 -2 -0.91 0 20 28.98 32170 +2011 324 -0.8 -1.7 -1.05 0.03 20 21.52 32039 +2011 325 -1.7 -3.7 -2.25 0 20 22.36 31911 +2011 326 -2.7 -3.9 -3.03 0 20 22.92 31786 +2011 327 -0.4 -3.8 -1.34 0 20 27.65 31665 +2011 328 0.2 -1.1 -0.16 0.05 14.44 28.29 31547 +2011 329 0.2 -1.2 -0.19 0.01 10 20.62 31433 +2011 330 2 0 1.45 0 10 38.36 31322 +2011 331 1.1 -0.9 0.55 0 10 62.18 31215 +2011 332 11.2 -2.7 7.38 0 158.89 199.06 31112 +2011 333 3.2 -3.9 1.25 0 12.22 99.18 31012 +2011 334 0.7 -1.3 0.15 0.01 10 35.42 30917 +2011 335 0.8 -1.7 0.11 0 10 58.28 30825 +2011 336 0.5 -1.7 -0.1 0.02 10 30.55 30738 +2011 337 1.5 -0.3 1 0.03 10 31.19 30654 +2011 338 9.2 1.1 6.97 0 65.56 116.63 30575 +2011 339 12.9 3.1 10.21 0.14 505.56 18.87 30500 +2011 340 7 -1.7 4.61 0 267.78 110.25 30430 +2011 341 4.9 -2.9 2.76 0.04 166.67 91.62 30363 +2011 342 9.1 -1.2 6.27 0 545.56 194.96 30301 +2011 343 4.1 -3.5 2.01 0 301.11 65.94 30244 +2011 344 7.8 -0.1 5.63 0 283.33 96.04 30191 +2011 345 5.5 -0.4 3.88 0 202.22 43.43 30143 +2011 346 10 3.2 8.13 0.73 112.22 102.13 30099 +2011 347 8.9 -0.8 6.23 0 66.25 128.07 30060 +2011 348 12 -1.7 8.23 0.43 215 143.31 30025 +2011 349 10.3 4.3 8.65 0.82 42.5 18.54 29995 +2011 350 9.3 -1.1 6.44 1.71 115 93.23 29970 +2011 351 10.2 1 7.67 0 381.25 67.07 29950 +2011 352 7.5 -3.9 4.37 0 386.25 180.79 29934 +2011 353 1.9 -3.7 0.36 0 117.5 41.49 29924 +2011 354 3.7 -7.1 0.73 0.01 271.25 182.13 29918 +2011 355 3.2 -7.7 0.2 0 136.25 70.58 29916 +2011 356 5.5 -4.1 2.86 0 201.25 131.52 29920 +2011 357 4.9 -2.5 2.87 0.03 60 61.63 29928 +2011 358 4.8 -2.9 2.68 0 132.5 128.63 29941 +2011 359 8.7 -3.3 5.4 0 433.75 169.15 29959 +2011 360 5.2 -0.1 3.74 0 270 40.49 29982 +2011 361 8.2 0 5.94 0 157.5 79.64 30009 +2011 362 2.2 -0.6 1.43 0 13.75 32.01 30042 +2011 363 1.9 -0.9 1.13 0 26.25 29.42 30078 +2011 364 3 -0.6 2.01 0 82.5 52.87 30120 +2011 365 8.5 -3.9 5.09 0 378.75 189.57 30166 +2012 1 6 -0.6 4.19 0 166.25 71.59 30217 +2012 2 12.1 -2.4 8.11 0.44 405 150.32 30272 +2012 3 8.5 2.7 6.9 0 60 63.96 30331 +2012 4 5.9 -1.6 3.84 0.07 92.5 91.83 30396 +2012 5 6.3 -1.7 4.1 0 203.75 42.67 30464 +2012 6 8.8 -1.6 5.94 0 503.75 189.6 30537 +2012 7 8.2 -3.5 4.98 0 361.25 141.91 30614 +2012 8 8.4 -2 5.54 0 312.5 127.47 30695 +2012 9 8.3 -1.1 5.72 0.06 318.75 112.87 30781 +2012 10 8.8 -1 6.11 0.03 281.25 117.68 30870 +2012 11 9.1 -3.3 5.69 0 333.33 156.74 30964 +2012 12 10.2 -2.5 6.71 0 443.33 195.25 31061 +2012 13 9.7 -2.5 6.34 0 487.78 198.96 31162 +2012 14 5.4 -3.1 3.06 0 288.89 172.29 31268 +2012 15 4.1 -5.6 1.43 0 201.11 130.49 31376 +2012 16 3 -4 1.08 0 282.22 193.22 31489 +2012 17 4.4 -5 1.82 0 315.56 99.1 31605 +2012 18 8.2 -1.5 5.53 0 492.22 184.39 31724 +2012 19 7.8 -4 4.55 0.01 331 63.9 31847 +2012 20 5.4 -0.6 3.75 0.1 90 30.36 31974 +2012 21 5.6 -4.4 2.85 0 256 173.14 32103 +2012 22 12 -0.5 8.56 0 499 201.96 32236 +2012 23 9.6 -2.9 6.16 0.08 460 116.34 32372 +2012 24 5.9 -0.2 4.22 0.01 125 95.8 32510 +2012 25 4.2 -2.6 2.33 0 252 237.42 32652 +2012 26 2.5 -3.1 0.96 0 232 238.99 32797 +2012 27 3.1 -9.8 -0.45 0 206 268.94 32944 +2012 28 2.6 -9.2 -0.64 0 174 243.12 33094 +2012 29 -1.1 -3.8 -1.84 0 136 98.73 33247 +2012 30 0.8 -9.7 -2.09 0 171 236.79 33402 +2012 31 -2.1 -13.5 -5.23 0 182 268.76 33559 +2012 32 -2.7 -10.7 -4.9 0 138 165.19 33719 +2012 33 -4.8 -11.7 -6.7 0 154 180.51 33882 +2012 34 -8.3 -13.5 -9.73 0 108 113.64 34046 +2012 35 -7.9 -9.5 -8.34 0 186 71.69 34213 +2012 36 -6.3 -9.9 -7.29 0 159 196.35 34382 +2012 37 -7.7 -11.3 -8.69 0.49 117 91.79 34552 +2012 38 -7.3 -10.3 -8.13 0.23 80 98.33 34725 +2012 39 -3.6 -21.4 -8.5 0 149 255.29 34900 +2012 40 -3.2 -18.5 -7.41 0.1 158 250.6 35076 +2012 41 -6.8 -11.4 -8.06 0 101 194.15 35254 +2012 42 -8.3 -19.4 -11.35 0.22 67 111.04 35434 +2012 43 -6.6 -11.6 -7.97 0 126 139.25 35615 +2012 44 -0.7 -10.4 -3.37 0 224 215.21 35798 +2012 45 2.2 -14.6 -2.42 0 249 270.86 35983 +2012 46 6 -11.1 1.3 0.15 300 153.74 36169 +2012 47 4.9 -4.3 2.37 0 338 266.86 36356 +2012 48 9.7 -8.4 4.72 0 409 162.5 36544 +2012 49 9 0.2 6.58 0 417 137.58 36734 +2012 50 9.8 -5.6 5.57 0.45 408 247.94 36925 +2012 51 6.2 0.1 4.52 0 304 175.96 37117 +2012 52 6.8 -5.2 3.5 0 378 327.89 37310 +2012 53 10 -6.2 5.54 0 420.91 299.79 37505 +2012 54 9.4 -4.9 5.47 0.01 362.73 209.94 37700 +2012 55 20 0.2 14.56 0 894.55 313.92 37896 +2012 56 17.2 0.3 12.55 0.03 876.36 291.53 38093 +2012 57 10.5 -0.6 7.45 0.01 387.27 180.39 38291 +2012 58 7.5 -4.4 4.23 0 466.36 329.71 38490 +2012 59 9.1 -2 6.05 0.04 207.27 110.65 38689 +2012 60 16.5 4.2 13.12 0 584.55 185.81 38890 +2012 61 14 8.7 12.54 0 264.17 129.39 39091 +2012 62 17.7 0.3 12.91 0 440.83 292.45 39292 +2012 63 11.7 1.2 8.81 0 649.17 361.72 39495 +2012 64 9 -5.4 5.04 0 513.33 311.94 39697 +2012 65 10 -1.6 6.81 0 522.5 334.21 39901 +2012 66 7.5 -5 4.06 0 395.83 370.38 40105 +2012 67 6.5 -7.9 2.54 0 393.33 368.17 40309 +2012 68 9.2 -2.8 5.9 0 520 262.12 40514 +2012 69 10.2 -2.3 6.76 0 500 312.1 40719 +2012 70 11.2 -5.5 6.61 0 513.33 393.58 40924 +2012 71 10.6 -3 6.86 0.01 399.17 77.12 41130 +2012 72 10.6 6.5 9.47 0 236.67 54.07 41336 +2012 73 13.7 6.9 11.83 0 461.67 245.03 41543 +2012 74 13.8 -2.6 9.29 0 515 357.18 41749 +2012 75 14.6 -1 10.31 0 597.5 381.33 41956 +2012 76 20.1 -3.1 13.72 0 846.67 398.84 42163 +2012 77 22.9 -1.9 16.08 0 1335.83 395.16 42370 +2012 78 18.2 5.9 14.82 0 850.83 367.56 42578 +2012 79 14.4 4.3 11.62 0.03 519.17 243.53 42785 +2012 80 14.3 5.1 11.77 0 727.5 313.34 42992 +2012 81 19.6 -1.6 13.77 0 872.5 385.07 43200 +2012 82 20.3 -0.7 14.53 0 1005 396.42 43407 +2012 83 22.1 -0.7 15.83 0 1200 369.46 43615 +2012 84 21.8 1.2 16.14 0 1170.83 377.45 43822 +2012 85 22.3 5.2 17.6 0 1200.83 412 44029 +2012 86 17.2 2.8 13.24 0 1016.67 451.58 44236 +2012 87 19.8 -2.5 13.67 0 1143.33 422.46 44443 +2012 88 21.4 7.6 17.61 0 1065.83 397.78 44650 +2012 89 19.9 1.9 14.95 0 1207.5 136.14 44857 +2012 90 15.8 4.7 12.75 0 418.33 176.73 45063 +2012 91 21.7 -0.8 15.51 0 1192.5 395.64 45270 +2012 92 16 2.5 12.29 0 621.54 447.83 45475 +2012 93 18.3 -4.6 12 0 919.23 455.18 45681 +2012 94 21.1 -0.6 15.13 0 1053.85 465.03 45886 +2012 95 23.1 11.3 19.86 0 1065.38 401.02 46091 +2012 96 23.4 5.4 18.45 1.21 1000.71 364.52 46295 +2012 97 16.8 7.3 14.19 0.06 144.29 112.16 46499 +2012 98 10.2 8.3 9.68 0.41 69.29 70.37 46702 +2012 99 8.5 2.4 6.82 0 396.43 367.14 46905 +2012 100 10.2 -2.3 6.76 0 546.43 489.44 47107 +2012 101 15 -3.5 9.91 0 793.57 424.76 47309 +2012 102 16.9 8.8 14.67 1.52 767.14 369.73 47510 +2012 103 15.2 6.5 12.81 0.06 297.86 174.71 47710 +2012 104 17.3 0.2 12.6 0.15 402.86 351.32 47910 +2012 105 12.4 7.6 11.08 0 296.43 111.53 48108 +2012 106 13 7.6 11.52 0 315 186.26 48306 +2012 107 12.9 3.5 10.32 0.03 337.14 137.34 48504 +2012 108 11.7 5.7 10.05 0 527.86 380.99 48700 +2012 109 11.3 3.7 9.21 0.07 504.29 207.07 48895 +2012 110 18.6 1.6 13.93 0 711.43 470.42 49089 +2012 111 19.2 4.1 15.05 0 795 414.75 49282 +2012 112 17.1 3.2 13.28 0.16 432.86 258.85 49475 +2012 113 16.8 6.9 14.08 1.3 367.14 168.44 49666 +2012 114 14.4 4 11.54 0 417.86 299.25 49855 +2012 115 17.2 7.3 14.48 0.16 426.43 247.49 50044 +2012 116 19 4.8 15.1 0 738.57 485.35 50231 +2012 117 23.1 8.6 19.11 0 1307.86 525.66 50417 +2012 118 24.9 3.9 19.13 0 1205 500.85 50601 +2012 119 28.5 6.1 22.34 0 1582.86 510.75 50784 +2012 120 29.3 15.5 25.5 0 2016.43 489.95 50966 +2012 121 29.1 11.6 24.29 0 2012.86 507.12 51145 +2012 122 29.5 9.2 23.92 0 1951.43 496.58 51324 +2012 123 29.7 10.4 24.39 0 1850 471.58 51500 +2012 124 23.4 14.3 20.9 1.42 758.57 279.2 51674 +2012 125 19.8 12.5 17.79 0.72 331.33 231.2 51847 +2012 126 23.1 9.9 19.47 0 1014 511.57 52018 +2012 127 23.1 8.1 18.98 0.09 937.33 496.37 52187 +2012 128 18.2 12.1 16.52 0.04 494.67 186.95 52353 +2012 129 22 6.2 17.66 0 896.67 500.64 52518 +2012 130 24.4 7.6 19.78 0 1156 516.77 52680 +2012 131 26.1 9.1 21.43 0 1477.33 482.73 52840 +2012 132 27.5 8.3 22.22 0 1486 487.54 52998 +2012 133 28.1 10.6 23.29 1.55 1064 375.57 53153 +2012 134 14.2 7.6 12.38 0 621.33 403.37 53306 +2012 135 12.9 7.7 11.47 0 434.67 211.15 53456 +2012 136 18.8 7.7 15.75 0 696 408.43 53603 +2012 137 15.8 6.3 13.19 0 584.67 234.61 53748 +2012 138 16.7 8.8 14.53 0 796 564.66 53889 +2012 139 17.3 -1.3 12.19 0 834.67 549.33 54028 +2012 140 22.4 1.1 16.54 0 1052 541.22 54164 +2012 141 25.3 4.3 19.53 0 1192.67 515.23 54297 +2012 142 22.2 10.2 18.9 0.19 611.25 202.74 54426 +2012 143 18.5 13.6 17.15 3.57 115.63 86.96 54552 +2012 144 26.8 12.6 22.9 0.13 668.75 407.89 54675 +2012 145 26.3 14.3 23 0.18 1141.88 415.58 54795 +2012 146 22.8 10.7 19.47 0 1189.38 428.95 54911 +2012 147 20.8 7.3 17.09 0 1088.13 376.42 55023 +2012 148 22.8 5.6 18.07 0 1171.88 509.18 55132 +2012 149 23.2 5.3 18.28 0.03 776.25 289.59 55237 +2012 150 24.1 10 20.22 0.01 1100.63 440.36 55339 +2012 151 27.1 12.2 23 0.52 969.38 407.07 55436 +2012 152 22.2 11.2 19.18 0.55 531.25 309 55530 +2012 153 25.2 13.5 21.98 0 772.5 361.82 55619 +2012 154 21.4 13.5 19.23 0 456.25 214.12 55705 +2012 155 28.2 12.2 23.8 0 1072.5 485.33 55786 +2012 156 23.1 14 20.6 0.66 623.13 327.85 55863 +2012 157 22.4 12.5 19.68 0 841.87 453.99 55936 +2012 158 22.1 3.8 17.07 0 749.38 436.72 56004 +2012 159 26.9 9.8 22.2 0 1097.5 446.08 56068 +2012 160 30.7 14.5 26.25 0 1501.87 445.99 56128 +2012 161 26.3 15.4 23.3 1.22 398.75 171.51 56183 +2012 162 24.7 14.4 21.87 0.46 463.13 271.23 56234 +2012 163 22.6 13.3 20.04 0.48 212.5 207.46 56280 +2012 164 19.2 13.7 17.69 0.11 138.75 155.83 56321 +2012 165 21.9 10.7 18.82 0.17 520 262.26 56358 +2012 166 24.3 9.8 20.31 0.02 879.38 397.68 56390 +2012 167 26.9 11.2 22.58 0 968.75 481.92 56418 +2012 168 29.5 12.1 24.72 0 1520 556.72 56440 +2012 169 31.7 13.1 26.59 0 1758.75 523.77 56458 +2012 170 32.2 13.4 27.03 0 1793.13 540.45 56472 +2012 171 32.5 14.2 27.47 0 1897.5 490.9 56480 +2012 172 32.9 15.8 28.2 0 1776.87 483.4 56484 +2012 173 32.9 17.5 28.66 0 1575 488.47 56482 +2012 174 27.9 17.8 25.12 0 1412.5 320.75 56476 +2012 175 27 14.3 23.51 0 1535.63 444.6 56466 +2012 176 29.9 11.8 24.92 0.28 1591.88 496.62 56450 +2012 177 26.6 16.3 23.77 0.99 428.75 108.77 56430 +2012 178 26.2 12.2 22.35 0 1095.63 458.3 56405 +2012 179 27.7 10.3 22.91 0 1310.63 481.29 56375 +2012 180 31.8 12.2 26.41 0 1664.38 414.84 56341 +2012 181 33.5 15.1 28.44 0 1753.13 449.8 56301 +2012 182 35.7 16.9 30.53 0 2033.75 501.34 56258 +2012 183 35.3 19.3 30.9 0 2240 483.09 56209 +2012 184 35.4 20.8 31.39 0 2162.5 493.8 56156 +2012 185 35.5 17.1 30.44 0.04 2374.38 461.62 56099 +2012 186 33.7 19.2 29.71 0 1738.12 483.47 56037 +2012 187 35.5 17.3 30.49 0 1950.63 419.58 55971 +2012 188 35.4 15.9 30.04 0 2046.25 436.23 55900 +2012 189 34.5 14.3 28.95 0 2060.63 489.73 55825 +2012 190 34.1 18.4 29.78 0 2156.25 513.46 55746 +2012 191 31.6 18 27.86 0.62 1789.38 457.42 55663 +2012 192 30.9 16.6 26.97 0.02 1315 468.42 55575 +2012 193 31.8 15.8 27.4 1.15 1198.13 468.23 55484 +2012 194 23.3 17.4 21.68 0 905.63 309.73 55388 +2012 195 20.6 15.4 19.17 0.03 357.5 173.45 55289 +2012 196 30.2 12.5 25.33 2.19 878.13 394.49 55186 +2012 197 20.6 13.9 18.76 0.14 298.13 173.32 55079 +2012 198 24.2 11.1 20.6 0.01 903.13 315.86 54968 +2012 199 26 7.4 20.88 0 1170 302.12 54854 +2012 200 27.4 10 22.61 0 1328.13 309.35 54736 +2012 201 32.1 14.2 27.18 0.65 1766.25 367.93 54615 +2012 202 26.6 16.2 23.74 0 1024.38 446.94 54490 +2012 203 22.8 15.5 20.79 0.57 185 115.34 54362 +2012 204 19.5 11.3 17.25 0 584.38 255.27 54231 +2012 205 24.3 14.4 21.58 0 1070 414.63 54097 +2012 206 27.7 12 23.38 2.15 748.75 309.52 53960 +2012 207 25.7 17.5 23.45 0.08 391.88 239.34 53819 +2012 208 29.2 16.2 25.63 0.42 731.25 353.41 53676 +2012 209 30.4 15.4 26.27 0 1200.67 473.37 53530 +2012 210 32 16.3 27.68 0 1580 500.59 53382 +2012 211 30.5 17.3 26.87 1.42 797.14 384.94 53230 +2012 212 25.5 13.9 22.31 0.02 1102.14 448.25 53076 +2012 213 27.1 15.4 23.88 0 1115 379.65 52920 +2012 214 29.3 13.5 24.95 0 1684.29 543.52 52761 +2012 215 31.2 13 26.2 0 1782.14 506.98 52600 +2012 216 29.2 15.4 25.41 1.91 965.71 394.88 52437 +2012 217 30.5 17.3 26.87 0 1222.14 483.69 52271 +2012 218 33.6 17.7 29.23 0 1702.86 484.93 52103 +2012 219 34.2 16.2 29.25 0 2585 467.95 51934 +2012 220 30.1 17.8 26.72 0 1399.29 354.81 51762 +2012 221 25.8 14.9 22.8 0 1004.29 312.55 51588 +2012 222 25.8 13.3 22.36 0.1 900.71 264.52 51413 +2012 223 25.4 11.4 21.55 0.08 980.71 381.71 51235 +2012 224 21.1 13.2 18.93 0.24 563.57 206.84 51057 +2012 225 23.2 6.8 18.69 0 963.57 394.26 50876 +2012 226 24.7 9.8 20.6 0 1070.71 342.83 50694 +2012 227 26.2 11.2 22.07 0 1378.57 447.53 50510 +2012 228 30 11.2 24.83 0 1665 431.11 50325 +2012 229 29.6 11.7 24.68 0 1725.71 422.19 50138 +2012 230 30.7 16.5 26.8 0 1430.71 449.13 49951 +2012 231 29.4 14.1 25.19 0 1616.43 447.88 49761 +2012 232 32.2 13 26.92 0 2080.71 443.73 49571 +2012 233 35 11.5 28.54 0 2562.14 492.84 49380 +2012 234 34 12.2 28.01 0 1847.86 385.24 49187 +2012 235 36 15.3 30.31 0.04 2380.71 393.59 48993 +2012 236 33.5 19 29.51 0.01 1780 353.99 48798 +2012 237 36.2 16.1 30.67 0 2552.14 436.46 48603 +2012 238 33 16.8 28.54 0 2142.86 435.27 48406 +2012 239 27.5 14.7 23.98 0.54 889.23 260.96 48208 +2012 240 25.1 10.6 21.11 0 1225.55 359.94 48010 +2012 241 28.6 7.3 22.74 0 1742.61 436.44 47811 +2012 242 29 11.6 24.22 0 1656.25 385.72 47611 +2012 243 31.3 11 25.72 0 1992.63 409.95 47410 +2012 244 25 13.4 21.81 0.38 1075.73 215.65 47209 +2012 245 17.8 13.5 16.62 0.62 343.62 91.75 47007 +2012 246 26 14.5 22.84 0 1130.47 286 46805 +2012 247 27.9 13.1 23.83 0 1445.69 341.78 46601 +2012 248 26.1 15.5 23.19 0 1079.81 263.87 46398 +2012 249 28.4 12.6 24.06 0 1534.41 354.94 46194 +2012 250 23.1 15.8 21.09 0 904.62 355.86 45989 +2012 251 25.2 6.1 19.95 0 1090.77 426.42 45784 +2012 252 29.2 8.8 23.59 0 1680 437.57 45579 +2012 253 29.6 8.7 23.85 0 1640.77 427.25 45373 +2012 254 30.1 9.2 24.35 0 1851.54 413.92 45167 +2012 255 31.1 9.6 25.19 0 1854.62 401.62 44961 +2012 256 28.1 11.2 23.45 3.48 1378.33 289.21 44755 +2012 257 16.9 8.5 14.59 0.43 188.33 84.77 44548 +2012 258 15.8 10.8 14.43 0 610.83 138.17 44341 +2012 259 21.6 10.9 18.66 0 837.5 219.45 44134 +2012 260 20.5 7.7 16.98 0 810 314.8 43927 +2012 261 24 5.4 18.88 0 767.5 410.85 43719 +2012 262 24.7 7.7 20.02 0 843.33 410.39 43512 +2012 263 21.9 9.2 18.41 0.46 496.67 221.2 43304 +2012 264 17.7 9.3 15.39 0 838.33 363.11 43097 +2012 265 19.3 1 14.27 0 815 398.98 42890 +2012 266 23.4 6.8 18.84 0 910.83 357.29 42682 +2012 267 21.4 10.7 18.46 0 800 356.06 42475 +2012 268 25.1 8.4 20.51 2.17 1040.83 344.73 42268 +2012 269 23.9 11.5 20.49 0 875.83 398.57 42060 +2012 270 25.2 16.7 22.86 0 1120 307.04 41854 +2012 271 24.5 13.7 21.53 0 895.83 184.45 41647 +2012 272 21.3 7.7 17.56 0.01 765.83 347.44 41440 +2012 273 20.9 10.8 18.12 0.01 422.5 190.77 41234 +2012 274 20.4 13.4 18.47 0.03 688.33 240.16 41028 +2012 275 24 12 20.7 0.57 558.18 287.82 40822 +2012 276 16.8 12.5 15.62 0.06 216.36 73.87 40617 +2012 277 22.1 9.6 18.66 0 368.18 292.31 40412 +2012 278 22.8 5.6 18.07 0 579.09 325.12 40208 +2012 279 20.1 7.3 16.58 0 647.27 294.31 40003 +2012 280 22.7 5.7 18.02 0 634.55 333.1 39800 +2012 281 23 10.5 19.56 0.12 458.18 252.17 39597 +2012 282 15.8 2.2 12.06 0 555.45 321.67 39394 +2012 283 17.6 3 13.59 0.02 553.64 264.16 39192 +2012 284 10.7 8 9.96 0.19 280.91 54.86 38991 +2012 285 14.7 4.6 11.92 0 282.73 217.62 38790 +2012 286 12.7 7.9 11.38 0.09 200.91 74.18 38590 +2012 287 12.9 9.4 11.94 0.52 217.27 107.18 38391 +2012 288 13 7.4 11.46 0 164.55 147.69 38193 +2012 289 20.4 11.3 17.9 1.19 475.45 275.56 37995 +2012 290 14.3 7.1 12.32 1.37 60.91 58 37799 +2012 291 17.5 3.2 13.57 0 175.45 238.74 37603 +2012 292 20.8 3.2 15.96 0 530.91 290.76 37408 +2012 293 21.7 4.8 17.05 0 532.73 317.93 37214 +2012 294 17 4.7 13.62 0.03 193.64 231.93 37022 +2012 295 18.4 5.4 14.82 0.05 168.18 223.71 36830 +2012 296 19.1 5.8 15.44 0.05 333.64 279.1 36640 +2012 297 10.9 4.7 9.2 0.03 19.09 95.36 36451 +2012 298 10.2 8.9 9.84 0.04 72.73 38.39 36263 +2012 299 9.3 8.2 9 0 104.55 40.46 36076 +2012 300 10.5 7.4 9.65 1.8 88 58.65 35891 +2012 301 16.7 7.3 14.12 2.89 101 129.85 35707 +2012 302 7.3 0.6 5.46 1.07 227 76 35525 +2012 303 4.5 0.2 3.32 0 116 176.39 35345 +2012 304 8.2 -3.6 4.96 0 239 290.72 35166 +2012 305 13.2 -4.4 8.36 0.79 319 300.6 34988 +2012 306 7.8 3.3 6.56 0.22 20 29.77 34813 +2012 307 10.5 1.3 7.97 0.05 165 130.41 34639 +2012 308 16.8 0.2 12.23 0 381 237.64 34468 +2012 309 19 10.9 16.77 0.05 618.89 194.88 34298 +2012 310 16.5 7.1 13.92 4.16 58.89 44.2 34130 +2012 311 9.9 0.9 7.43 0 221.11 139.71 33964 +2012 312 12.6 -1.4 8.75 0 385.56 198.12 33801 +2012 313 13.8 0.6 10.17 0 494.44 254.81 33640 +2012 314 11.9 0.8 8.85 0 275.56 213.67 33481 +2012 315 12.5 -1.2 8.73 0 302.22 132.48 33325 +2012 316 14.3 3 11.19 0.27 245.56 139.57 33171 +2012 317 10.3 6.9 9.37 1 58.89 31.17 33019 +2012 318 12.4 7.8 11.14 0 218.89 89.64 32871 +2012 319 9.5 1 7.16 0 248.89 133.77 32725 +2012 320 10 -0.5 7.11 0 194.44 193.3 32582 +2012 321 8.3 5.4 7.5 0 167.78 61.91 32441 +2012 322 9.3 3.5 7.71 0 170 103.17 32304 +2012 323 8.1 1.7 6.34 0.03 20 45.89 32170 +2012 324 7.9 6.6 7.54 0.04 15.56 35.03 32039 +2012 325 9 6.1 8.2 0.02 16.67 138.25 31911 +2012 326 8.5 6.1 7.84 0.01 36.67 38.4 31786 +2012 327 7.8 6.8 7.52 0.04 46.67 38.61 31665 +2012 328 8.4 6.3 7.82 0.01 48.89 44.05 31547 +2012 329 10.5 7.3 9.62 0 111.11 87.83 31433 +2012 330 9.4 3.9 7.89 0 87.78 38.61 31322 +2012 331 10.1 3 8.15 0 65.56 81.74 31215 +2012 332 14.4 3.9 11.51 0 566.67 99.03 31112 +2012 333 17 10.4 15.18 0.62 572.22 144.53 31012 +2012 334 12.8 7.5 11.34 0.35 275.56 120.14 30917 +2012 335 7.5 3.2 6.32 0 265.56 68.04 30825 +2012 336 4.3 -0.2 3.06 0 195.56 90.03 30738 +2012 337 2.5 0.5 1.95 0.27 50 41.12 30654 +2012 338 5.8 -1.1 3.9 0 236.67 168.11 30575 +2012 339 3.6 -2.4 1.95 0.15 143.33 56.47 30500 +2012 340 5.3 -0.8 3.62 0 95.56 95.72 30430 +2012 341 1.3 -3.1 0.09 0 14.44 59.37 30363 +2012 342 1.7 -6 -0.42 0.55 145.56 139.76 30301 +2012 343 -1 -4.6 -1.99 0.11 76.67 52.38 30244 +2012 344 3 -10 -0.57 0 271.11 200.32 30191 +2012 345 1.9 -9 -1.1 0 205.56 167.93 30143 +2012 346 2.7 -8.9 -0.49 0 140 124.85 30099 +2012 347 1.5 -10.5 -1.8 0 241.25 194.55 30060 +2012 348 -0.6 -14.7 -4.48 0 152.5 198.89 30025 +2012 349 5 -11.6 0.44 0.01 202.5 67.58 29995 +2012 350 11 3.1 8.83 0.39 228.75 39.19 29970 +2012 351 7.4 2 5.92 0 10 85.41 29950 +2012 352 4 2.9 3.7 0 10 28.95 29934 +2012 353 3 1.3 2.53 0.15 11.25 38.55 29924 +2012 354 5.8 0.3 4.29 0.02 87.5 67.1 29918 +2012 355 4.4 -0.6 3.03 0 98.75 74.43 29916 +2012 356 0.9 -0.6 0.49 0.04 17.5 29 29920 +2012 357 1.8 -0.5 1.17 0 33.75 46.93 29928 +2012 358 1.7 -0.5 1.1 0.02 51.25 41.31 29941 +2012 359 10.8 0.1 7.86 0 215 171.64 29959 +2012 360 11.7 -1.8 7.99 0 372.5 82.55 29982 +2012 361 11.9 2.6 9.34 0.83 82.5 32.34 30009 +2012 362 9.8 -1 6.83 0.13 217.5 161.03 30042 +2012 363 7.2 1.7 5.69 0 152.5 50.92 30078 +2012 364 5.3 -4.3 2.66 0 152.5 170.07 30120 +2012 365 3 -5.3 0.72 0 142.5 185 30166 +2013 1 6.59 -4.73 3.48 0 63.75 172.69 30217 +2013 2 2.37 -3.11 0.86 0 12.5 41.3 30272 +2013 3 -0.28 -3.23 -1.09 0 200 124.23 30331 +2013 4 6.92 -1.95 4.48 0.01 333.75 116.26 30396 +2013 5 10.31 0.57 7.63 0.4 378.75 69.14 30464 +2013 6 10.97 3.94 9.04 0.08 77.5 33.14 30537 +2013 7 7.16 2.71 5.94 0.88 28.75 57.31 30614 +2013 8 5.72 -0.85 3.91 0.3 28.75 42.76 30695 +2013 9 0.12 -1.99 -0.46 0.28 36.25 53.03 30781 +2013 10 4.67 -0.21 3.33 0.03 31.25 59.58 30870 +2013 11 3.82 1.43 3.16 0 57.5 63.57 30964 +2013 12 3.4 -1.03 2.18 0 213.33 128.34 31061 +2013 13 1.6 -5.33 -0.31 0 37.78 62.33 31162 +2013 14 -0.96 -2.99 -1.52 1.78 20 51.45 31268 +2013 15 -1.52 -3.41 -2.04 1.07 32.22 92.46 31376 +2013 16 0.33 -2.58 -0.47 0.04 86.67 112.82 31489 +2013 17 0.22 -1.89 -0.36 1.23 47.78 80.72 31605 +2013 18 -0.28 -1.62 -0.65 0.24 37.78 66.94 31724 +2013 19 -1.14 -3.88 -1.89 0.35 98.89 71.99 31847 +2013 20 -1.91 -4.58 -2.64 0 83 125.07 31974 +2013 21 3.43 -4.71 1.19 0.05 15 70.98 32103 +2013 22 4.41 -0.91 2.95 0.87 34 73.66 32236 +2013 23 0.85 -0.98 0.35 0.35 10 64.51 32372 +2013 24 0.34 -1.75 -0.23 0 10 34.98 32510 +2013 25 -0.35 -1.94 -0.79 0.07 119 177.03 32652 +2013 26 -0.73 -5.21 -1.96 0 106 181.89 32797 +2013 27 -3.16 -9.83 -4.99 0 100 171.05 32944 +2013 28 -1.52 -13.28 -4.75 0 46 85.69 33094 +2013 29 -0.33 -3.59 -1.23 0.3 64 95.75 33247 +2013 30 2.47 -5.47 0.29 0.14 313 204.34 33402 +2013 31 8.44 0.3 6.2 0 880 258.66 33559 +2013 32 8.44 0.05 6.13 0 491 133.99 33719 +2013 33 6.77 2.7 5.65 1.88 74 20.72 33882 +2013 34 5.15 0.4 3.84 0 429 179.25 34046 +2013 35 4.49 -2.68 2.52 0 317 93.96 34213 +2013 36 6.42 0.05 4.67 0.26 270 65.81 34382 +2013 37 3.78 -0.68 2.55 0.23 21 64.71 34552 +2013 38 5.15 -1.39 3.35 0 284 278.58 34725 +2013 39 3.29 -3.69 1.37 0 238 248.28 34900 +2013 40 0.43 -2.35 -0.33 0.17 209 138.66 35076 +2013 41 -0.73 -3.34 -1.45 0.21 66 117.41 35254 +2013 42 1.23 -8.44 -1.43 0.48 188 221.38 35434 +2013 43 -0.03 -3.22 -0.91 0.61 27 100.01 35615 +2013 44 -0.31 -1.78 -0.71 0.58 52 83.19 35798 +2013 45 0.62 -1.44 0.05 0.43 82 106.86 35983 +2013 46 3.38 -1.18 2.13 0 108 166.44 36169 +2013 47 4.82 -1.09 3.19 0 214 258.11 36356 +2013 48 4.19 -0.74 2.83 0 153 157.98 36544 +2013 49 4.43 -0.78 3 0 185 205.28 36734 +2013 50 5.23 -1.68 3.33 0 257 237.83 36925 +2013 51 3.78 -1.36 2.37 0.01 276 168.58 37117 +2013 52 0.97 -5.01 -0.67 0.26 203 282.07 37310 +2013 53 -1.54 -5.46 -2.62 1.46 77 160.78 37505 +2013 54 1.6 -3.94 0.08 1.31 50.91 149.42 37700 +2013 55 2.88 -0.94 1.83 0.27 10 90.93 37896 +2013 56 4.16 0.74 3.22 2.29 30.91 168.99 38093 +2013 57 3.73 1.09 3 0.51 22.73 47.84 38291 +2013 58 4.78 1.24 3.81 0.05 149.09 62.78 38490 +2013 59 -0.84 -3.05 -1.45 0.1 223.64 233.39 38689 +2013 60 8.75 2.15 6.94 0 45.45 83.3 38890 +2013 61 4.76 -1.11 3.15 0 373.64 371.38 39091 +2013 62 6.74 -0.27 4.81 0 430 389.12 39292 +2013 63 9.9 -3.68 6.17 0 385.83 379.38 39495 +2013 64 8.21 -1.35 5.58 0 480.83 364.56 39697 +2013 65 10.87 -2.07 7.31 0 480.83 213.26 39901 +2013 66 13.64 4.29 11.07 0 495.83 310.07 40105 +2013 67 16.83 7.96 14.39 0 569.17 294.94 40309 +2013 68 18.13 6.44 14.92 0 292.5 242.51 40514 +2013 69 14.15 5.3 11.72 0.67 53.33 81.72 40719 +2013 70 10.64 7.65 9.82 0.55 290 303.47 40924 +2013 71 13.9 1.03 10.36 0.01 188.33 151.16 41130 +2013 72 8.66 2.09 6.85 0.01 274.17 192.22 41336 +2013 73 9.59 2.92 7.76 0.21 130.83 85.29 41543 +2013 74 7.06 -2.73 4.37 0.07 353.33 235.4 41749 +2013 75 1.1 -2.86 0.01 0 336.67 313.14 41956 +2013 76 2.89 -4.14 0.96 0 360.83 310 42163 +2013 77 4.62 -5.16 1.93 0 130.83 74.61 42370 +2013 78 3.62 0.21 2.68 1.05 484.17 258.32 42578 +2013 79 12.75 1.61 9.69 0 560.42 291.29 42785 +2013 80 14.01 -1.29 9.8 0.03 509.17 215.76 42992 +2013 81 10.33 4.87 8.83 0 391.67 457.61 43200 +2013 82 7.33 -1.28 4.96 0 200.83 207.28 43407 +2013 83 1.99 -2.62 0.72 0.04 68.33 124.35 43615 +2013 84 0.43 -4.02 -0.79 0.41 61.67 106.98 43822 +2013 85 -2.26 -4.19 -2.79 0.89 72.5 136.87 44029 +2013 86 -2.34 -4.32 -2.88 0.4 222.5 396.18 44236 +2013 87 2.66 -5.03 0.55 0 264.17 457.91 44443 +2013 88 5.82 -6.6 2.4 0.13 27.5 58.42 44650 +2013 89 3.44 1.39 2.88 0.82 60.83 107.53 44857 +2013 90 5.23 1.43 4.19 3.21 57.5 70.49 45063 +2013 91 4.34 0.3 3.23 0.94 181.67 168.67 45270 +2013 92 4.22 -0.49 2.92 0.06 14.17 59.33 45475 +2013 93 2.86 0.3 2.16 2.25 86.92 113.44 45681 +2013 94 2.08 -0.25 1.44 0.3 283.08 323.02 45886 +2013 95 9 0.33 6.62 0 85.38 114.58 46091 +2013 96 6.55 2.08 5.32 0.12 247.69 217.35 46295 +2013 97 7.47 3.01 6.24 0 217.86 244.22 46499 +2013 98 7.21 2.23 5.84 0 425.71 466.02 46702 +2013 99 10.32 -0.97 7.22 0 481.43 390.59 46905 +2013 100 14.49 1.84 11.01 0 479.29 277.02 47107 +2013 101 15.36 5.56 12.66 0.11 625.71 390.84 47309 +2013 102 17.73 2.42 13.52 0 611.43 341.18 47510 +2013 103 18.9 8.89 16.15 0.55 742.14 360.73 47710 +2013 104 17.72 5.49 14.36 0 886.43 476.88 47910 +2013 105 18.95 5.19 15.17 0 970 492.22 48108 +2013 106 18.43 5.56 14.89 0 1100 518.62 48306 +2013 107 19.41 4.08 15.19 0 931.43 313.59 48504 +2013 108 22.02 5.5 17.48 0 1241.43 444.88 48700 +2013 109 24.16 7.88 19.68 0 921.43 405.65 48895 +2013 110 22.7 9.63 19.11 0 437.14 309.51 49089 +2013 111 17.83 9.46 15.53 0 740.71 447.18 49282 +2013 112 20.86 7.04 17.06 0.01 721.43 333.79 49475 +2013 113 21.39 9.27 18.06 0.71 663.57 350.89 49666 +2013 114 20.81 8.41 17.4 0 1303.57 513.77 49855 +2013 115 23.45 6.54 18.8 0 1363.57 485.21 50044 +2013 116 25.44 7.19 20.42 0 1633.57 486.35 50231 +2013 117 26.89 9.31 22.06 0 1006.43 308.7 50417 +2013 118 23.14 14.46 20.75 0 1101.43 487.96 50601 +2013 119 24.53 12.94 21.34 0 1193.57 403.46 50784 +2013 120 25.26 11.12 21.37 0 1267.86 431.24 50966 +2013 121 26.99 11.39 22.7 0 1045 457.2 51145 +2013 122 26.2 12.49 22.43 0.05 349.29 211.94 51324 +2013 123 21.38 14.84 19.58 0.73 480.71 356.03 51500 +2013 124 22.62 12.76 19.91 0.04 567.86 318.97 51674 +2013 125 21.37 9.6 18.13 0.01 368.57 170.15 51847 +2013 126 18.16 12.29 16.55 0.74 282 208.36 52018 +2013 127 20.64 12.93 18.52 0.03 595.33 374.15 52187 +2013 128 22.66 14.12 20.31 0 690.67 414.18 52353 +2013 129 22.64 11.68 19.63 0.02 970 404.19 52518 +2013 130 24.47 10.82 20.72 0.01 1070.67 469.6 52680 +2013 131 24.64 8.99 20.34 0.49 240.67 131.74 52840 +2013 132 18.14 11.99 16.45 0.4 698.67 400.24 52998 +2013 133 18.38 10.73 16.28 0 934.67 474.95 53153 +2013 134 17.97 8.49 15.36 0.03 636.11 264.87 53306 +2013 135 20.5 7.38 16.89 0 1096 556.58 53456 +2013 136 23.16 6.99 18.71 0 862.67 383.97 53603 +2013 137 23.82 11.04 20.31 0.02 276.67 228.83 53748 +2013 138 20.77 11.12 18.12 1.14 996.67 553.51 53889 +2013 139 22.11 10.48 18.91 0 1209.33 488.86 54028 +2013 140 25.91 10.09 21.56 0.32 708.67 423.06 54164 +2013 141 20.81 10.1 17.86 0.2 969.33 484.49 54297 +2013 142 21.24 8.75 17.81 0 652.67 432.61 54426 +2013 143 19.33 7.09 15.96 0.49 601.88 356.93 54552 +2013 144 15.98 8.7 13.98 0 721.88 393.92 54675 +2013 145 15.8 7.32 13.47 0 280 215.62 54795 +2013 146 14.26 8.05 12.55 0.62 561.25 355.26 54911 +2013 147 16.57 7.78 14.15 0.25 290 197.47 55023 +2013 148 15.37 7.28 13.15 0.11 592.5 397.34 55132 +2013 149 20.45 7.97 17.02 0 923.75 397.61 55237 +2013 150 23.22 9.83 19.54 0.01 143.75 68.96 55339 +2013 151 18.41 9.36 15.92 1.6 210.62 176.9 55436 +2013 152 13.08 8.04 11.69 0.3 196.87 217.67 55530 +2013 153 16.53 8.1 14.21 0.87 155.63 189.13 55619 +2013 154 15.87 8.61 13.87 0.44 508.75 253.96 55705 +2013 155 17.87 8.57 15.31 0.03 298.13 106.68 55786 +2013 156 16.56 9.8 14.7 0.27 303.75 203.37 55863 +2013 157 18.18 12.15 16.52 0.05 523.75 372.95 55936 +2013 158 20.88 10.33 17.98 0 643.75 466.46 56004 +2013 159 23.07 11.95 20.01 0 880.63 456.02 56068 +2013 160 25.88 12.58 22.22 0.17 1120 474.35 56128 +2013 161 26.99 12.25 22.94 0 886.88 409.69 56183 +2013 162 24.48 14.7 21.79 0.47 248.75 183.45 56234 +2013 163 18.78 13.21 17.25 0.58 1026.88 450.34 56280 +2013 164 22.6 10.08 19.16 0 1295 426.5 56321 +2013 165 25.28 11.3 21.44 0 1157.5 516.04 56358 +2013 166 25.52 11.51 21.67 0 1298.75 473.3 56390 +2013 167 27.99 12.76 23.8 0 1220 370.22 56418 +2013 168 28.82 16.35 25.39 0 1546.25 488.57 56440 +2013 169 31.4 17.02 27.45 0 1706.25 486.18 56458 +2013 170 32.39 17.8 28.38 0 1653.75 481.24 56472 +2013 171 33.08 18.48 29.07 0 1667.5 469.96 56480 +2013 172 33.35 19.65 29.58 0 2202.5 512.53 56484 +2013 173 32.09 19.77 28.7 0 1278.75 465.01 56482 +2013 174 29.83 17.09 26.33 0.35 1165.63 450.76 56476 +2013 175 27.73 16.75 24.71 0.12 201.25 67.52 56466 +2013 176 22.27 11.96 19.43 1.98 516.88 182.02 56450 +2013 177 18.08 12.05 16.42 0 703.75 323.38 56430 +2013 178 19.33 8.44 16.34 0 898.75 535.53 56405 +2013 179 18.91 6.25 15.43 0 843.13 404.95 56375 +2013 180 20.38 6.66 16.61 0 984.37 425.68 56341 +2013 181 22.33 9.12 18.7 0 958.13 471.17 56301 +2013 182 22.24 10.18 18.92 0.01 1183.75 504.25 56258 +2013 183 23.98 7.91 19.56 0 1185 497.05 56209 +2013 184 26.88 10.58 22.4 0 1541.25 464.8 56156 +2013 185 27.95 12.08 23.59 0 1308.13 496.71 56099 +2013 186 28.3 13.98 24.36 0 1379.38 492.35 56037 +2013 187 28.13 15.91 24.77 0.11 941.88 468.11 55971 +2013 188 26.89 17.76 24.38 0.18 1103.75 472 55900 +2013 189 27.65 17.19 24.77 0.01 1376.87 499.54 55825 +2013 190 27.06 16.93 24.27 0 1496.25 488.63 55746 +2013 191 28.29 15.55 24.79 0 1655 463.36 55663 +2013 192 28.96 14.59 25.01 0.02 572.5 212.82 55575 +2013 193 24.64 15.57 22.15 0.24 1206.88 448.15 55484 +2013 194 24.57 10.24 20.63 0 1177.5 351.58 55388 +2013 195 25.33 11.57 21.55 0 1480.63 457.6 55289 +2013 196 26.31 12.86 22.61 0 1001.25 380.92 55186 +2013 197 26.3 13.67 22.83 0.57 1266.88 461.33 55079 +2013 198 25.74 12.03 21.97 0 1660 511 54968 +2013 199 28.33 11.28 23.64 0 1818.13 448.59 54854 +2013 200 29.57 12.8 24.96 0 1730.63 412.32 54736 +2013 201 30.31 14.24 25.89 0 1665 464.4 54615 +2013 202 29.41 16.21 25.78 0 1601.25 509.58 54490 +2013 203 27.25 14.72 23.8 0 1885 509.65 54362 +2013 204 29.87 11.7 24.87 0 2279.38 498.04 54231 +2013 205 32.02 13.8 27.01 0 1893.75 441.45 54097 +2013 206 32.02 15.44 27.46 0 1449.37 352.91 53960 +2013 207 29.83 17.02 26.31 0 1946.25 408.55 53819 +2013 208 32.97 16.28 28.38 0 2231.88 459.52 53676 +2013 209 34.4 18.16 29.93 0 2060 466.42 53530 +2013 210 35.43 19.18 30.96 0 3151.33 480.67 53382 +2013 211 37.4 20.94 32.87 0 1683.57 361.49 53230 +2013 212 28.59 18.56 25.83 0 1755 384.44 53076 +2013 213 29.53 13.39 25.09 0 1921.43 507.29 52920 +2013 214 30.6 14.77 26.25 0 2355 508.06 52761 +2013 215 33.99 14.4 28.6 0 2690 489.46 52600 +2013 216 35.96 16.72 30.67 0 2891.43 466 52437 +2013 217 35.94 18.3 31.09 0.04 1829.29 500.23 52271 +2013 218 33.01 17.39 28.71 0 2780 472.57 52103 +2013 219 36.02 18.11 31.09 0 2815 469.56 51934 +2013 220 36.02 19.99 31.61 0 3570 467.6 51762 +2013 221 38.78 18.74 33.27 0 2026.43 445.09 51588 +2013 222 34.07 19.91 30.18 1.19 1055 258.16 51413 +2013 223 25.8 16.71 23.3 0 1623.57 481.69 51235 +2013 224 28.33 12.32 23.93 0 1756.43 390.84 51057 +2013 225 29.57 16.23 25.9 0 1336.43 422.28 50876 +2013 226 28.86 14.43 24.89 0.33 304.29 89.99 50694 +2013 227 18.85 15.56 17.95 0.1 1404.29 510.44 50510 +2013 228 24.66 12.07 21.2 0 1632.14 482.65 50325 +2013 229 26.71 8.83 21.79 0 1859.29 483.31 50138 +2013 230 29.07 10.24 23.89 0 2010 471.28 49951 +2013 231 31.22 12.36 26.03 0 2069.29 427.01 49761 +2013 232 31.95 14.47 27.14 0.01 1014.29 291.26 49571 +2013 233 24.31 17.31 22.38 0.09 1122.86 372.7 49380 +2013 234 23.9 16.03 21.74 0 1352.14 424.47 49187 +2013 235 25.2 13.35 21.94 0 1265 356.65 48993 +2013 236 26.71 11.96 22.65 0.54 212.14 124.83 48798 +2013 237 21.25 15.18 19.58 0.67 138.57 119.06 48603 +2013 238 18.47 11.85 16.65 0.26 328.57 178.56 48406 +2013 239 20.8 14.03 18.94 0.21 397.14 209.94 48208 +2013 240 22.8 14.66 20.56 1.1 335.71 229.25 48010 +2013 241 20.7 15.15 19.17 0.01 1169.29 477.02 47811 +2013 242 23.65 13.62 20.89 0 1246.43 452.51 47611 +2013 243 24.13 10.02 20.25 0 1360.71 395.76 47410 +2013 244 26.04 9.43 21.47 0 590 219.45 47209 +2013 245 23.82 12.26 20.64 0.15 749.29 365.04 47007 +2013 246 20.85 9.91 17.84 0 1174.62 245.75 46805 +2013 247 23.8 14.35 21.2 0 763.08 298.94 46601 +2013 248 24.25 13.32 21.24 0 899.23 269.71 46398 +2013 249 24.96 14.11 21.98 0 1157.69 397.66 46194 +2013 250 25.42 13.89 22.25 0 1320.77 419.42 45989 +2013 251 25.75 11.15 21.73 0 1581.54 408.25 45784 +2013 252 26.29 10.18 21.86 0.01 274.62 107.52 45579 +2013 253 19.4 13.28 17.72 0.85 470 272.55 45373 +2013 254 21.54 13.73 19.39 2.7 497.69 267.17 45167 +2013 255 17.82 10.71 15.86 0.07 637.69 345.66 44961 +2013 256 18.94 10.44 16.6 0.49 437.69 335.4 44755 +2013 257 17.46 7.98 14.85 0.06 812.5 160.35 44548 +2013 258 20.41 10.14 17.59 0.02 627.5 286.93 44341 +2013 259 22.29 9.05 18.65 0 695.83 339.77 44134 +2013 260 23.12 10.48 19.64 1.35 155 105.67 43927 +2013 261 16.97 8.54 14.65 0.8 334.17 162.99 43719 +2013 262 16.04 4.96 12.99 0.15 640 302.45 43512 +2013 263 17.73 10.42 15.72 0 686.67 322.44 43304 +2013 264 19.81 6.47 16.14 0.01 768.33 254.33 43097 +2013 265 19.33 10.41 16.88 0 716.67 378.93 42890 +2013 266 18.81 9.15 16.15 0 859.17 383.94 42682 +2013 267 22.29 7.38 18.19 0 783.33 410.78 42475 +2013 268 21.77 7.92 17.96 0 566.67 381.1 42268 +2013 269 21.07 7.77 17.41 0 581.67 221.6 42060 +2013 270 22.59 10.88 19.37 0.18 221.67 71.12 41854 +2013 271 16.31 9.54 14.45 0.06 397.5 146.97 41647 +2013 272 14.17 7.58 12.36 0.01 80.83 41.93 41440 +2013 273 11.87 8.31 10.89 2.65 46.67 50.1 41234 +2013 274 9.21 7.36 8.7 0.89 465.83 326.5 41028 +2013 275 15.44 7.43 13.24 0 411.67 262.31 40822 +2013 276 12.16 4.93 10.17 0 477.27 323.06 40617 +2013 277 11.09 -0.42 7.92 0 487.27 369.2 40412 +2013 278 11.78 -1.3 8.18 0 389.09 143.03 40208 +2013 279 10.76 -0.85 7.57 0.02 102.73 100.48 40003 +2013 280 12.18 7.44 10.88 0.08 375.45 254.93 39800 +2013 281 16.57 9.18 14.54 0 794.55 367.39 39597 +2013 282 19.06 5.15 15.23 0 513.64 187.73 39394 +2013 283 17.09 8.81 14.81 0.04 282.73 191.01 39192 +2013 284 18.54 11.15 16.51 0.01 265.45 126.9 38991 +2013 285 18.86 10.34 16.52 0.54 297.27 282.54 38790 +2013 286 18.22 8.07 15.43 0.37 354.55 282.15 38590 +2013 287 18.17 9.42 15.76 0 396.36 323.29 38391 +2013 288 17.16 5.5 13.95 0 237.27 266.57 38193 +2013 289 17.3 7.08 14.49 0.23 346.36 173.72 37995 +2013 290 13.62 8.03 12.08 0.11 752.73 337.23 37799 +2013 291 17.08 5.74 13.96 0 571.82 279.11 37603 +2013 292 17.8 4.27 14.08 0.01 531.82 323.35 37408 +2013 293 16.87 3.16 13.1 0 506.36 284.1 37214 +2013 294 20.88 7.21 17.12 0 619.09 245.54 37022 +2013 295 22.49 10.61 19.22 0 580 252.11 36830 +2013 296 21.31 8.49 17.78 0 978.18 293.49 36640 +2013 297 24.02 12.43 20.83 0 576.36 178.83 36451 +2013 298 20.29 12.64 18.19 0 591.82 273.91 36263 +2013 299 22.1 8.08 18.24 0 1016.75 251.81 36076 +2013 300 20.1 8.59 16.93 0 812.62 229.78 35891 +2013 301 20.95 7.9 17.36 0 916.53 238.12 35707 +2013 302 23.05 11.64 19.91 0 955.6 213.55 35525 +2013 303 19.16 9.35 16.46 0.73 696.78 146.68 35345 +2013 304 13.06 8.36 11.77 0 281.64 106.71 35166 +2013 305 14.7 3.33 11.57 0 587.41 213.48 34988 +2013 306 16.06 5.24 13.08 0 618.58 201.12 34813 +2013 307 16.75 5.31 13.6 0 666.13 204.73 34639 +2013 308 18.31 8.12 15.51 1.62 679.9 139.81 34468 +2013 309 10.74 7.83 9.94 0.95 84 39.35 34298 +2013 310 11.07 7.32 10.04 1.26 123.33 114.54 34130 +2013 311 10.73 2.49 8.46 0.01 344.44 230.55 33964 +2013 312 15.71 5.94 13.02 0 285.56 219.23 33801 +2013 313 16.82 3.7 13.21 0 165.56 26.75 33640 +2013 314 14.19 7.1 12.24 2.74 110 87.69 33481 +2013 315 9.55 4.8 8.24 1.17 215.56 49.26 33325 +2013 316 8.54 4.82 7.52 0.21 282.22 105.75 33171 +2013 317 8.53 4.74 7.49 0 117.78 26.01 33019 +2013 318 7.61 5.89 7.14 0.19 155.56 81.1 32871 +2013 319 7.32 3.1 6.16 0.2 47.78 28.37 32725 +2013 320 6.97 4.35 6.25 0 60 169.73 32582 +2013 321 10.44 0.62 7.74 0 92.22 191.61 32441 +2013 322 10.11 0.16 7.37 0 106.67 86.6 32304 +2013 323 7.75 3.56 6.6 0 73.33 54.52 32170 +2013 324 7.54 4.81 6.79 0.39 16.67 26.81 32039 +2013 325 7.76 6.03 7.28 0.99 15.56 42.27 31911 +2013 326 7.89 3.88 6.79 0.19 45.56 37.14 31786 +2013 327 7.15 4.95 6.55 0.86 46.67 53.9 31665 +2013 328 8.91 5.83 8.06 2.29 28.89 29.67 31547 +2013 329 8 6.13 7.49 1.69 300 59.4 31433 +2013 330 6.29 0.47 4.69 0 235.56 201.9 31322 +2013 331 2.78 -0.37 1.91 0.01 216.67 151.52 31215 +2013 332 2.55 -1.29 1.49 0 284.44 241.36 31112 +2013 333 4.01 -5.33 1.44 0 364.44 189.4 31012 +2013 334 7.64 -3.49 4.58 0 168.89 106.08 30917 +2013 335 5.51 -1.01 3.72 0 217.78 231.55 30825 +2013 336 6.89 -3.57 4.01 0 223.33 169.72 30738 +2013 337 7.12 -2.9 4.36 0 153.33 193.61 30654 +2013 338 4.84 -4.75 2.2 0 147.78 214.61 30575 +2013 339 3.81 -4.76 1.45 0 130 155.94 30500 +2013 340 4.88 -4.61 2.27 0 374.44 194.59 30430 +2013 341 7.39 -1.27 5.01 0 230 143.76 30363 +2013 342 4.63 -2.14 2.77 0.01 223.21 100.73 30301 +2013 343 8.06 -0.91 5.59 0 337.28 153.96 30244 +2013 344 7.28 -2.16 4.68 0 195.56 92.4 30191 +2013 345 9.71 3.7 8.06 0.01 264.44 57.58 30143 +2013 346 4.89 -0.25 3.48 0 152.22 48.16 30099 +2013 347 3.59 0.25 2.67 0 10 27.05 30060 +2013 348 1.79 -1.27 0.95 0.01 97.58 27.47 30025 +2013 349 0.14 -1.47 -0.3 0 48.96 50.58 29995 +2013 350 0.02 -2.01 -0.54 0 5 64.22 29970 +2013 351 -0.17 -3.41 -1.06 0 10 33.81 29950 +2013 352 -2.11 -3.84 -2.59 0 10 15.87 29934 +2013 353 -2.26 -3.45 -2.59 0 6.25 82.51 29924 +2013 354 -0.01 -4.72 -1.31 0 124.82 93.44 29918 +2013 355 2.16 -2.77 0.8 0 149.25 115.46 29916 +2013 356 4.79 -2.07 2.9 0.01 227.69 32.86 29920 +2013 357 4.49 0.43 3.37 0.01 147.77 69.86 29928 +2013 358 3.16 -0.1 2.26 0 112.58 177.49 29941 +2013 359 11.86 -0.35 8.5 0 514.15 83.97 29959 +2013 360 12.64 6.98 11.08 0 319.29 51.73 29982 +2013 361 11.3 7.25 10.19 0.97 224.01 80.89 30009 +2013 362 8.34 4.32 7.23 0.01 186.18 165.86 30042 +2013 363 10.29 1 7.74 0 396.52 57.32 30078 +2013 364 7.75 2.41 6.28 0.08 226.67 92.02 30120 +2013 365 6.99 3.28 5.97 0.03 160.05 40.67 30166 +2014 1 4.97 2.58 4.31 0.02 95.78 16.86 30217 +2014 2 4.85 3.08 4.36 0 72.14 139.42 30272 +2014 3 8.89 2.5 7.13 0 279.49 183.19 30331 +2014 4 11.6 -0.17 8.36 0 495.88 96.46 30396 +2014 5 8.57 -0.85 5.98 0.04 359.42 49.36 30464 +2014 6 11.55 6.91 10.27 0.28 254.81 161.95 30537 +2014 7 10.09 3.13 8.18 0 320.63 52.91 30614 +2014 8 5.85 1.84 4.75 0.01 159.29 37.94 30695 +2014 9 4.2 1.99 3.59 0.01 85 59.68 30781 +2014 10 4.3 0.47 3.25 0.01 139 105.29 30870 +2014 11 7.82 1.88 6.19 0 247.42 43.98 30964 +2014 12 6.09 0.99 4.69 0 197.05 218.8 31061 +2014 13 9.03 -0.42 6.43 0 370.68 215.94 31162 +2014 14 7.58 -2.24 4.88 0 346.56 58.23 31268 +2014 15 8.75 -0.56 6.19 0.36 360.78 126.67 31376 +2014 16 7.27 2.05 5.83 0 216.08 157.85 31489 +2014 17 8.4 -0.27 6.02 0 336.92 123.46 31605 +2014 18 12.08 4.25 9.93 0 393.94 118.45 31724 +2014 19 13 3.65 10.43 0 469.86 78.67 31847 +2014 20 11.93 5.75 10.23 0.28 327.75 79.3 31974 +2014 21 11.23 5.61 9.68 0.01 291.85 137.15 32103 +2014 22 9.45 3.85 7.91 0 261.27 67.89 32236 +2014 23 5.03 1.95 4.18 0 120.56 40.83 32372 +2014 24 3.5 0.41 2.65 0.06 109.79 36.06 32510 +2014 25 0.82 -1.63 0.15 1.18 75.23 244.67 32652 +2014 26 -0.01 -5.16 -1.43 0 134.02 109.95 32797 +2014 27 -4.27 -10.5 -5.98 0.03 116.08 98.26 32944 +2014 28 -3.63 -7.73 -4.76 0.03 87.45 77.64 33094 +2014 29 -1.62 -4.67 -2.46 0.18 77.85 105.8 33247 +2014 30 -1.02 -3.99 -1.84 0.06 79.14 70.84 33402 +2014 31 -0.9 -5.64 -2.2 0.1 118.27 74.6 33559 +2014 32 -2.39 -5.23 -3.17 0.41 69.47 70.53 33719 +2014 33 -0.5 -2.95 -1.17 0.89 69.03 53.81 33882 +2014 34 -0.25 -3.27 -1.08 0 84.48 60.47 34046 +2014 35 -0.8 -2.73 -1.33 0 54.48 48.44 34213 +2014 36 0.3 -2.72 -0.53 0 87.58 87.02 34382 +2014 37 2.16 -1.36 1.19 0.01 112.83 89.49 34552 +2014 38 9.33 -2.05 6.2 0.63 422.32 215.63 34725 +2014 39 7.97 2.74 6.53 0.23 226 89.32 34900 +2014 40 9.48 1.47 7.28 1.59 341.47 49.87 35076 +2014 41 7.89 -1.23 5.38 0.08 337.29 200.3 35254 +2014 42 7.88 4.88 7.05 1.16 140.5 47.88 35434 +2014 43 5.66 0.61 4.27 0.47 190.29 65.06 35615 +2014 44 8.54 -2.84 5.41 0.63 401.74 252.58 35798 +2014 45 9.76 2.95 7.89 0 309.21 222.83 35983 +2014 46 12.15 0.38 8.91 0 513 279.15 36169 +2014 47 12.31 3.46 9.88 1.79 434.59 161.49 36356 +2014 48 6 2.42 5.02 0.62 145.99 66.02 36544 +2014 49 5.67 -0.12 4.08 0 212.04 92.9 36734 +2014 50 9.87 4.42 8.37 0.65 262.36 61.68 36925 +2014 51 10.71 4.22 8.93 0 316.07 163.25 37117 +2014 52 9.13 3.44 7.57 0.02 259.43 71.6 37310 +2014 53 7.37 4.47 6.57 0.55 132.15 56.04 37505 +2014 54 9.14 3.23 7.51 0.04 267.37 68.56 37700 +2014 55 11.55 0.93 8.63 0 465.83 275.43 37896 +2014 56 8.87 -0.2 6.38 0 357.42 221.9 38093 +2014 57 12.81 -0.28 9.21 0 565.51 211.13 38291 +2014 58 12.06 2.23 9.36 0 458.29 277.8 38490 +2014 59 11.2 2.57 8.83 0.01 399.4 255.25 38689 +2014 60 13.52 0.4 9.91 0 591.42 257.07 38890 +2014 61 10.22 2.78 8.17 0 339.24 198.76 39091 +2014 62 7.82 1.8 6.16 0.47 249.98 143.79 39292 +2014 63 9.39 4.11 7.94 0 248.45 117.01 39495 +2014 64 11.78 4.92 9.89 0.01 351.49 144.73 39697 +2014 65 9.9 5.35 8.65 0 227.06 134.72 39901 +2014 66 9.93 2.97 8.02 0 317.51 295.62 40105 +2014 67 12.44 1.42 9.41 0 502.89 267.36 40309 +2014 68 12.05 1.64 9.19 0 474.59 371.75 40514 +2014 69 11.14 1.28 8.43 0 434 277.69 40719 +2014 70 14.79 -0.86 10.49 0 694.34 403.36 40924 +2014 71 15.34 2.04 11.68 0 665.27 363.22 41130 +2014 72 16.07 0.25 11.72 0 754.21 379.56 41336 +2014 73 18.76 0.18 13.65 0 943.12 389.2 41543 +2014 74 17.1 2.54 13.1 0 773.22 156.71 41749 +2014 75 19.5 6.29 15.87 0 848.32 207.6 41956 +2014 76 21.5 5.76 17.17 0 1038.56 401.98 42163 +2014 77 19.43 3.64 15.09 0 921.47 380.35 42370 +2014 78 17.41 7.82 14.77 0 620.46 334.12 42578 +2014 79 20.22 3.05 15.5 0 999.66 428.74 42785 +2014 80 21.47 4.97 16.93 0 1058.3 404.17 42992 +2014 81 19.38 7.86 16.21 0 779.99 356.68 43200 +2014 82 15.69 10.07 14.14 0.75 379.68 151.01 43407 +2014 83 12.8 3.43 10.22 0.01 464.86 216.76 43615 +2014 84 10.44 -0.53 7.42 0.03 443.31 286.38 43822 +2014 85 12.37 0.95 9.23 0 511.2 294.3 44029 +2014 86 13.99 1.39 10.53 0 595.91 223.45 44236 +2014 87 17.16 5.05 13.83 0 705.16 398 44443 +2014 88 19.36 3 14.86 0 931.7 419.23 44650 +2014 89 21 3.21 16.11 0 1060.98 430.87 44857 +2014 90 20.26 3.9 15.76 0 982.48 310.1 45063 +2014 91 19.52 6.62 15.97 0 838.54 388.54 45270 +2014 92 19.99 5.24 15.93 0 922.96 395.24 45475 +2014 93 20.36 5.47 16.27 0 947.36 328.82 45681 +2014 94 19.92 7.49 16.5 0 840.8 339.59 45886 +2014 95 18.43 9.94 16.1 0.01 606 266.62 46091 +2014 96 19.52 9.39 16.73 0.74 726.26 264.15 46295 +2014 97 20.52 6.83 16.76 0 917.09 440.47 46499 +2014 98 23.74 7.34 19.23 0.37 1203 416.4 46702 +2014 99 18.02 7.65 15.17 0 676.01 338.89 46905 +2014 100 12.71 2.6 9.93 0.36 485.26 141.55 47107 +2014 101 14.75 2 11.24 0 627.98 490.32 47309 +2014 102 15.29 2.14 11.67 0 659.4 346.26 47510 +2014 103 16.58 2.44 12.69 0.06 739.06 289.45 47710 +2014 104 19.25 4.31 15.14 0.42 889.14 289.03 47910 +2014 105 10.36 3.48 8.47 0.01 323.2 264.82 48108 +2014 106 11.68 3.77 9.5 0.01 387.29 270.74 48306 +2014 107 11.89 3.88 9.69 0 395.72 199.61 48504 +2014 108 18.53 2.48 14.12 0 879.79 486.66 48700 +2014 109 18.4 8.51 15.68 0.62 670.46 314.95 48895 +2014 110 14.76 7.56 12.78 0.38 435 196.81 49089 +2014 111 18.32 8.33 15.57 0.78 671.72 217.55 49282 +2014 112 19.69 9.98 17.02 0 713.45 341.37 49475 +2014 113 19.94 9.1 16.96 0 776.42 370.25 49666 +2014 114 20.59 12.06 18.24 0.43 687.46 316.14 49855 +2014 115 17.16 12.3 15.82 1.8 367.14 67.08 50044 +2014 116 17.27 11.33 15.64 0.01 434.47 170.46 50231 +2014 117 20.63 7.14 16.92 0 915.87 473.94 50417 +2014 118 20.74 9.02 17.52 0.05 852.05 335 50601 +2014 119 19.19 8.96 16.38 0.04 717.12 344.05 50784 +2014 120 21.72 8.86 18.18 0.05 950.17 488.57 50966 +2014 121 21.86 8.14 18.09 0 991.72 476.93 51145 +2014 122 22.28 7 18.08 0.04 1071.67 361.45 51324 +2014 123 14.88 8.29 13.07 0.07 410 149.54 51500 +2014 124 15.18 6.16 12.7 0.01 522.68 495.34 51674 +2014 125 15.73 4.15 12.55 0 631.45 527.01 51847 +2014 126 20.15 2.9 15.41 0 997.35 491.27 52018 +2014 127 21.33 7.31 17.47 0.85 972.82 383.75 52187 +2014 128 20.65 9.42 17.56 0.1 826.31 394.62 52353 +2014 129 22.76 7.79 18.64 0.69 1090.85 419.39 52518 +2014 130 22.02 11.47 19.12 0.22 859.05 445.41 52680 +2014 131 19.2 8.5 16.26 2.38 738.11 132.63 52840 +2014 132 17.99 5.78 14.63 0.58 743.91 378.3 52998 +2014 133 12.46 8.06 11.25 1.23 257.34 132.05 53153 +2014 134 14.77 6.54 12.51 0.09 479.12 329.23 53306 +2014 135 11.87 7.59 10.69 0.86 242.8 136.11 53456 +2014 136 10.77 8.46 10.13 0.6 132.15 47.34 53603 +2014 137 14.76 7.81 12.85 0.31 423.75 205.89 53748 +2014 138 18.51 9.53 16.04 0.92 632.81 300.1 53889 +2014 139 22.8 7.86 18.69 0.01 1092.29 373.07 54028 +2014 140 24.19 8.99 20.01 0 1191.89 493.69 54164 +2014 141 25.67 9.99 21.36 0 1314.57 493.3 54297 +2014 142 27.1 12.93 23.2 0 1352.89 485.93 54426 +2014 143 28.18 14.23 24.34 0.16 1423.18 342.33 54552 +2014 144 26.51 15.45 23.47 0.02 1134.46 457.22 54675 +2014 145 25.13 14.75 22.28 0.01 1010.32 430.1 54795 +2014 146 25.81 13.08 22.31 0.13 1188.21 336.1 54911 +2014 147 24.78 12.98 21.54 0.18 1073.76 466.77 55023 +2014 148 19.59 11.38 17.33 0.04 632.34 234.02 55132 +2014 149 19.89 11.32 17.53 0.13 662.96 234.89 55237 +2014 150 16.04 8.99 14.1 0 461.55 308.8 55339 +2014 151 17.45 7.17 14.62 0.02 650.34 242.01 55436 +2014 152 20.66 10.13 17.76 0 794.48 213.39 55530 +2014 153 21.14 9.31 17.89 0.01 876.55 408.3 55619 +2014 154 21.08 8.56 17.64 0.59 902.47 349.54 55705 +2014 155 23.46 7.6 19.1 0 1166.43 503.36 55786 +2014 156 22.04 11.38 19.11 0.01 865.68 315.61 55863 +2014 157 25.82 9.83 21.42 0 1337.75 500.01 55936 +2014 158 28.35 11.29 23.66 0 1584.63 501.59 56004 +2014 159 30.16 13.89 25.69 0 1712.07 501.98 56068 +2014 160 31.18 14.72 26.65 0 1818.56 480.38 56128 +2014 161 32.33 15.17 27.61 0 1971.06 397.62 56183 +2014 162 33.27 16.04 28.53 0 2075.77 500.28 56234 +2014 163 29.21 18.69 26.32 0.11 1269.75 358.09 56280 +2014 164 25.89 16.07 23.19 0.1 1015.2 327.19 56321 +2014 165 23.39 14.42 20.92 0.01 832.35 416.04 56358 +2014 166 22.84 10.51 19.45 0 988.73 468.31 56390 +2014 167 22.41 10.58 19.16 0 942.03 462.93 56418 +2014 168 19.67 12.94 17.82 0 548.5 165.08 56440 +2014 169 24.98 11.79 21.35 0.05 1157.74 449.83 56458 +2014 170 26.19 10.61 21.91 0.04 1349.19 443.35 56472 +2014 171 21.46 12.53 19 0.31 745.32 294.58 56480 +2014 172 22.07 9.3 18.56 0 965.53 410.35 56484 +2014 173 26.64 9.89 22.03 0 1429.91 511.24 56482 +2014 174 27.12 13.81 23.46 1.8 1309.23 450.99 56476 +2014 175 23.62 15.48 21.38 0.39 786.92 133.58 56466 +2014 176 19.33 13 17.59 0.23 513.28 175.04 56450 +2014 177 21.93 9.66 18.56 0 936.49 532.86 56430 +2014 178 24.49 11.57 20.94 0 1113.69 458.2 56405 +2014 179 27.09 12.19 22.99 0.01 1387.54 343.73 56375 +2014 180 29.71 15.34 25.76 2.5 1570.54 502.41 56341 +2014 181 23.71 12.51 20.63 0.86 980.25 251.99 56301 +2014 182 23.38 9.36 19.52 0 1093.53 454.35 56258 +2014 183 26.44 11.28 22.27 0.53 1350.13 429.28 56209 +2014 184 25.46 13.3 22.12 0 1134.94 490.49 56156 +2014 185 26.15 11.3 22.07 0 1315.06 511.04 56099 +2014 186 26.29 14.68 23.1 0.17 1155.23 341.78 56037 +2014 187 29.6 14.65 25.49 0 1593.71 495.59 55971 +2014 188 31.07 15.46 26.78 0 1762.45 512.73 55900 +2014 189 27.56 18.06 24.95 0.03 1086.06 420.86 55825 +2014 190 22.75 14.9 20.59 0.67 730.63 285.4 55746 +2014 191 17.74 12.24 16.23 1.02 419.74 142.76 55663 +2014 192 20.53 13.18 18.51 0.28 615.19 152.96 55575 +2014 193 26.73 13.88 23.2 0.06 1256.47 384.4 55484 +2014 194 25.29 13.98 22.18 0.24 1076.22 417.42 55388 +2014 195 25.7 13.61 22.38 0.62 1146.11 368.49 55289 +2014 196 28.31 15.26 24.72 0.02 1381.28 487.4 55186 +2014 197 29.34 17.28 26.02 0 1393.72 413.14 55079 +2014 198 29.59 17.22 26.19 0.04 1434.11 482.93 54968 +2014 199 29.25 14.95 25.32 0 1528.15 484.71 54854 +2014 200 30.31 16.1 26.4 0 1612.23 468.4 54736 +2014 201 30.94 16.46 26.96 0 1684.18 469.07 54615 +2014 202 29.7 18.28 26.56 0 1373.69 311.34 54490 +2014 203 22.82 15.29 20.75 1.42 711.31 132.43 54362 +2014 204 26.91 17.54 24.33 0.03 1039 471.66 54231 +2014 205 26.76 14.37 23.35 0 1232.29 479.02 54097 +2014 206 26.91 16.26 23.98 0.16 1131.71 302.48 53960 +2014 207 28.43 15.45 24.86 0.01 1386.01 423.45 53819 +2014 208 25.73 15.87 23.02 0.59 1009.16 276.26 53676 +2014 209 24.11 17.59 22.32 0.82 683.96 181.11 53530 +2014 210 27.08 16.68 24.22 0.01 624 280.33 53382 +2014 211 27.74 16.18 24.56 2.78 582.14 279.41 53230 +2014 212 25.42 16.56 22.98 0.23 514.29 239.43 53076 +2014 213 26.31 17.9 24 0 762.86 359.63 52920 +2014 214 28.69 16.63 25.37 0 1085.71 402.27 52761 +2014 215 29.09 17.16 25.81 0 1061.43 450.67 52600 +2014 216 26.79 15.46 23.67 0.05 831.43 370.91 52437 +2014 217 25.26 16.1 22.74 0.02 968.57 360 52271 +2014 218 23.35 17.71 21.8 0 937.14 214.79 52103 +2014 219 25.5 17.23 23.23 0 1166.43 365.09 51934 +2014 220 28.25 13.63 24.23 0 1423.57 483.07 51762 +2014 221 29.9 14.94 25.79 1.22 1278.57 440.36 51588 +2014 222 28.62 16.63 25.32 0 1020 435.41 51413 +2014 223 29.78 17.22 26.33 1.31 1147.14 443.02 51235 +2014 224 22.01 16.6 20.52 1.6 505.71 183.37 51057 +2014 225 25.6 14.66 22.59 3.26 565 334.25 50876 +2014 226 22.37 13.69 19.98 2.64 233.57 147.27 50694 +2014 227 21.64 13.43 19.38 0.17 575 209.71 50510 +2014 228 21.84 10.88 18.83 0 837.14 360.78 50325 +2014 229 22.9 9.73 19.28 0 1016.43 455.16 50138 +2014 230 24.38 10.29 20.51 0 987.14 461.93 49951 +2014 231 23.87 11.88 20.57 0.02 685 307.2 49761 +2014 232 19.89 14.75 18.48 1.88 355 194.85 49571 +2014 233 21.42 12.15 18.87 0.09 732.86 443.05 49380 +2014 234 21.86 11.08 18.9 0 608.57 264.49 49187 +2014 235 21.45 12.51 18.99 0.96 373.57 218.25 48993 +2014 236 21.29 13.17 19.06 0.13 779.29 312.52 48798 +2014 237 20.51 8.83 17.3 0 801.43 420.49 48603 +2014 238 21.46 10.82 18.53 0.03 583.57 208.77 48406 +2014 239 23.23 14.53 20.84 0.12 466.43 272.13 48208 +2014 240 22.34 7.85 18.36 0 977.14 438.44 48010 +2014 241 23.37 8.81 19.37 0 915.71 450.11 47811 +2014 242 24.52 10.79 20.74 0.02 840 373.4 47611 +2014 243 22.42 14.69 20.29 2.26 472.86 216.32 47410 +2014 244 18.96 11.98 17.04 1.81 151.43 60.92 47209 +2014 245 15.23 13.16 14.66 2.53 190.71 47.74 47007 +2014 246 20.01 13.89 18.33 0.03 454.62 262.62 46805 +2014 247 22.69 15.59 20.74 0.34 575.38 189.87 46601 +2014 248 24.49 16.19 22.21 0.57 609.23 323.99 46398 +2014 249 20.8 16.23 19.54 0.06 306.15 136.04 46194 +2014 250 21.61 14.97 19.78 0 501.54 221.72 45989 +2014 251 24.62 12.6 21.31 0 786.92 393.66 45784 +2014 252 25.97 13.37 22.5 0.32 676.15 346.91 45579 +2014 253 19.1 15.17 18.02 0.31 289.23 118.29 45373 +2014 254 15.95 12.83 15.09 2.76 158.46 45.96 45167 +2014 255 15.4 12.23 14.53 3.74 158.46 114.55 44961 +2014 256 20.22 12.85 18.19 0.09 381.54 224.6 44755 +2014 257 17.77 13.44 16.58 0.72 146.67 108.02 44548 +2014 258 19.59 13.61 17.95 0.09 265.83 170.37 44341 +2014 259 20.66 13.33 18.64 0.08 430.83 231.16 44134 +2014 260 21.36 11 18.51 0 665.83 366.53 43927 +2014 261 21.33 8.41 17.78 0 751.67 409.68 43719 +2014 262 23.96 11.17 20.44 0 733.33 378.19 43512 +2014 263 24.01 13.09 21.01 0 573.33 302.16 43304 +2014 264 25.73 15.36 22.88 1.91 905 398.95 43097 +2014 265 18.49 11.78 16.64 0.01 680.83 255.05 42890 +2014 266 16.62 7.4 14.08 0 689.17 279.91 42682 +2014 267 18.25 5.35 14.7 0 616.67 400.53 42475 +2014 268 15.71 7.6 13.48 0.07 275 155.85 42268 +2014 269 14.02 8.46 12.49 0.2 227.5 47.57 42060 +2014 270 18.19 11.48 16.34 0.01 300.83 174.7 41854 +2014 271 20.9 8.22 17.41 0 671.67 405.42 41647 +2014 272 21.51 8.46 17.92 0 683.33 392.59 41440 +2014 273 17.32 8.52 14.9 0 92.5 120.88 41234 +2014 274 18.62 10.51 16.39 0.12 215.83 152.81 41028 +2014 275 18.07 13.23 16.74 0.2 312.5 118.11 40822 +2014 276 17.79 10.61 15.82 0 349.09 251.45 40617 +2014 277 15.49 8.96 13.69 0.05 200.91 94.67 40412 +2014 278 17.85 10.41 15.8 0.01 500 266.23 40208 +2014 279 17.82 6.06 14.59 0 470.91 311.16 40003 +2014 280 18.1 8.63 15.5 0 273.64 209.83 39800 +2014 281 22.22 10.71 19.05 0 580 250.91 39597 +2014 282 24.76 13.96 21.79 0 1025.45 376.59 39394 +2014 283 24.06 12.59 20.91 0 777.27 372.39 39192 +2014 284 25.1 11.19 21.27 0 925.45 355.51 38991 +2014 285 22.85 11.19 19.64 0 648.18 332.8 38790 +2014 286 25.03 11.85 21.41 0 976.36 340.59 38590 +2014 287 24.28 14.14 21.49 0.01 1117.27 306.96 38391 +2014 288 18.73 11.45 16.73 0.05 292.73 158.62 38193 +2014 289 22.09 11.87 19.28 0.12 548.18 289.71 37995 +2014 290 19.05 12.75 17.32 0.17 141.82 101.3 37799 +2014 291 20.09 7.96 16.75 0 623.64 308.52 37603 +2014 292 20.85 8.11 17.35 0 708.18 338.79 37408 +2014 293 23.36 8.81 19.36 0 753.64 311.01 37214 +2014 294 17.63 12.54 16.23 6.07 145.45 97.43 37022 +2014 295 14.68 6.15 12.33 0.31 230 117.09 36830 +2014 296 9.48 5.96 8.51 0.5 184.55 47.67 36640 +2014 297 9.27 6.99 8.64 0.18 259.09 30.28 36451 +2014 298 7.96 5.08 7.17 0.02 80.91 41.54 36263 +2014 299 8.59 3.5 7.19 0 120.91 104.14 36076 +2014 300 8.88 3.41 7.38 0 168.18 64.38 35891 +2014 301 9.59 -0.53 6.81 0 213 293.95 35707 +2014 302 9.39 -0.76 6.6 0 210 194.79 35525 +2014 303 9.18 3.79 7.7 0 257 60.57 35345 +2014 304 11.56 3.58 9.37 0 242 87.42 35166 +2014 305 14.52 3.48 11.48 0 423 263.69 34988 +2014 306 13.56 3.12 10.69 0 382 277.86 34813 +2014 307 10.93 2.65 8.65 0 168 138.03 34639 +2014 308 17.82 7.44 14.97 0 706 240.1 34468 +2014 309 19.98 9.37 17.06 0.29 887 208.51 34298 +2014 310 16.43 11.32 15.02 0.13 201.11 87.89 34130 +2014 311 16.76 10.06 14.92 0.44 205.56 112.78 33964 +2014 312 14.99 9.07 13.36 0.03 270 74.55 33801 +2014 313 12.96 8.17 11.64 0 204.44 127.81 33640 +2014 314 18.15 8.48 15.49 0 505.56 255.57 33481 +2014 315 18.07 9.56 15.73 0 636.67 199.62 33325 +2014 316 14.5 8.14 12.75 0.02 206.67 132.42 33171 +2014 317 11.66 8.09 10.68 0.01 160 62.95 33019 +2014 318 13.99 9.86 12.85 0 230 105.12 32871 +2014 319 12.69 9.35 11.77 0.03 181.11 92.96 32725 +2014 320 14.05 8.13 12.42 0 220 199.75 32582 +2014 321 10.4 7.92 9.72 1.41 37.78 65.35 32441 +2014 322 13.95 7.28 12.12 0.01 344.44 170.47 32304 +2014 323 12.44 5.2 10.45 0.02 354.44 207.97 32170 +2014 324 10.92 4.65 9.2 0 308.89 209.77 32039 +2014 325 8.59 2.16 6.82 0 305.56 134.02 31911 +2014 326 9.1 0.02 6.6 0 261.11 198.6 31786 +2014 327 7.38 -0.28 5.27 0 205.56 180.38 31665 +2014 328 4.98 1.5 4.02 0.02 135.56 33.86 31547 +2014 329 4.79 1.52 3.89 0.01 96.67 42.74 31433 +2014 330 5.17 1.14 4.06 0 205.56 93.98 31322 +2014 331 3.36 0.69 2.63 0 191.11 76.62 31215 +2014 332 2.43 0.71 1.96 0.1 20 28.61 31112 +2014 333 2.9 2 2.65 0.08 10 25.69 31012 +2014 334 3.17 2.18 2.9 0.35 10 30.82 30917 +2014 335 2.58 1.39 2.25 0.92 21.11 10.2 30825 +2014 336 1.86 0.22 1.41 0.24 21.11 22.72 30738 +2014 337 3.69 1.15 2.99 0.1 28.89 23.8 30654 +2014 338 4.48 3.12 4.11 0.15 65.56 28.96 30575 +2014 339 5 3.56 4.6 0.09 44.44 36.85 30500 +2014 340 5.24 4.04 4.91 1.66 20 13.5 30430 +2014 341 5.4 4.13 5.05 1.04 76.67 32.36 30363 +2014 342 6.55 3.03 5.58 0.01 148.89 103.73 30301 +2014 343 4.28 1.81 3.6 0 250 73.83 30244 +2014 344 4.01 -1.79 2.42 0 252.22 198.49 30191 +2014 345 5.32 -2.47 3.18 0 292.22 111.57 30143 +2014 346 7.73 -1.64 5.15 0 334.44 200.95 30099 +2014 347 11 0.37 8.08 0 592.22 163.49 30060 +2014 348 7.4 -0.32 5.28 0 118.75 65.99 30025 +2014 349 4.44 -2.09 2.64 0 345 62.21 29995 +2014 350 4.72 -1.79 2.93 0.28 237.5 55.59 29970 +2014 351 8.21 1.86 6.46 0 247.5 159.61 29950 +2014 352 9.41 1.64 7.27 0 816.25 122.9 29934 +2014 353 13.45 3.66 10.76 0 886.25 188.94 29924 +2014 354 11.92 2.98 9.46 0.01 858.75 189.15 29918 +2014 355 9.58 0.89 7.19 0 1036.25 202.43 29916 +2014 356 8.34 -2.06 5.48 0 948.75 117.89 29920 +2014 357 12.32 2.34 9.58 0 1206.25 132.03 29928 +2014 358 8.82 -1.92 5.87 0 795 160.93 29941 +2014 359 8.49 -2.18 5.56 0 580 173.78 29959 +2014 360 5.66 -1.27 3.75 0.23 605 151.72 29982 +2014 361 0.55 -3.87 -0.67 0.28 235 108.45 30009 +2014 362 0 -5.57 -1.53 0.07 90 56.99 30042 +2014 363 -1.12 -6.59 -2.62 0 288.75 182.77 30078 +2014 364 -2.55 -8.65 -4.23 0 165 86.89 30120 +2014 365 -3.86 -14.07 -6.67 0 163.75 247.17 30166 +2015 1 0.1 -6.4 -1.69 0 161.14 63.15 30217 +2015 2 6.1 -3.2 3.54 0.28 212.5 133.17 30272 +2015 3 5.8 -1.5 3.79 0.11 177.5 143.03 30331 +2015 4 6.9 -0.6 4.84 0.33 367.5 209.28 30396 +2015 5 3.5 -0.4 2.43 0 206.25 70.11 30464 +2015 6 5.2 -0.6 3.61 0 228.75 185.36 30537 +2015 7 -1 -3.8 -1.77 0 160 93.68 30614 +2015 8 0.6 -4.1 -0.69 0 111.25 99.18 30695 +2015 9 6 -2.3 3.72 0.02 158.75 64.27 30781 +2015 10 14 1.1 10.45 0 578.75 160.15 30870 +2015 11 6.4 2 5.19 0.58 165 14.49 30964 +2015 12 8.7 0.6 6.47 0 464.44 173.84 31061 +2015 13 11.7 -1.3 8.13 0 541.11 207.09 31162 +2015 14 7.5 -1.5 5.03 0.09 256.67 187.79 31268 +2015 15 8.6 -0.8 6.01 0 248.89 186.14 31376 +2015 16 13.6 -0.5 9.72 0 600 190.64 31489 +2015 17 11.4 6 9.91 0.02 610 56.68 31605 +2015 18 9.4 1.4 7.2 0 154.44 70.84 31724 +2015 19 6.5 1 4.99 0 62.22 101.09 31847 +2015 20 4.8 0.2 3.54 0.24 91 80.61 31974 +2015 21 3.8 2 3.3 0.02 46 60.44 32103 +2015 22 6.4 3.5 5.6 0.02 69 53.16 32236 +2015 23 6.9 5.3 6.46 0.87 153 29.56 32372 +2015 24 5.6 1.3 4.42 0.36 70 27.78 32510 +2015 25 4.1 1.5 3.38 0 195 56.5 32652 +2015 26 3.2 -1.3 1.96 0 242 193.86 32797 +2015 27 1.7 -2.7 0.49 0.05 103 57.22 32944 +2015 28 5.8 -3.9 3.13 0 238 263.36 33094 +2015 29 0.8 -1.8 0.09 0.2 75 35.77 33247 +2015 30 1.9 -4.2 0.22 1.61 28 23.48 33402 +2015 31 5.4 -6.6 2.1 0 166 276.61 33559 +2015 32 2 -7.3 -0.56 0.62 71 101.09 33719 +2015 33 5.1 -6.9 1.8 0.01 139 300.56 33882 +2015 34 1.3 -8 -1.26 0.01 128 204.18 34046 +2015 35 1.5 -0.3 1 0 75 50.48 34213 +2015 36 1.3 -2 0.39 0.03 119 112.34 34382 +2015 37 0.4 -2 -0.26 0 169 75.3 34552 +2015 38 1.3 -4.6 -0.32 0 205 275.35 34725 +2015 39 2.9 -6.8 0.23 0.02 198 167.07 34900 +2015 40 0.8 -1.6 0.14 0.31 110 63.33 35076 +2015 41 4.6 -1.1 3.03 0.02 284 77.83 35254 +2015 42 5 0.9 3.87 0 174 126.94 35434 +2015 43 6.1 0.4 4.53 0 195 200.24 35615 +2015 44 5.7 -2.8 3.36 0 228 302.05 35798 +2015 45 6.5 -2.3 4.08 0 189 97.33 35983 +2015 46 11.1 -0.3 7.96 0 353 187.96 36169 +2015 47 10.4 -2.1 6.96 0 364 316.51 36356 +2015 48 5.1 -2.6 2.98 0 188 231.05 36544 +2015 49 5 -0.1 3.6 0 228 187.3 36734 +2015 50 8.5 -2 5.61 0 335 297.12 36925 +2015 51 11.1 -2.6 7.33 0 465 315.7 37117 +2015 52 11.8 -0.9 8.31 0 612 320.45 37310 +2015 53 8 2.2 6.4 1.12 297 66.41 37505 +2015 54 6.8 3.5 5.89 0.22 80 71.13 37700 +2015 55 5.9 4.5 5.52 1.61 47.27 48.07 37896 +2015 56 7.7 4.6 6.85 0 342.73 100.95 38093 +2015 57 10.4 5.2 8.97 0 369.09 205.43 38291 +2015 58 10.1 -2 6.77 0 270.91 255.51 38490 +2015 59 9.8 -0.7 6.91 0 356.36 239.02 38689 +2015 60 10.5 -2.5 6.93 0 388.18 250 38890 +2015 61 11.8 2.4 9.21 0.44 400.91 98.88 39091 +2015 62 11.8 0.2 8.61 0 689.17 340.77 39292 +2015 63 11 -2.1 7.4 0 453.33 230.4 39495 +2015 64 8 2.8 6.57 0 381.67 244.63 39697 +2015 65 7.3 1.5 5.71 0 408.33 302.72 39901 +2015 66 10.2 -0.1 7.37 0 395 385.96 40105 +2015 67 10.8 -4.5 6.59 0 528.33 398.38 40309 +2015 68 11 -2.1 7.4 0 542.5 353.2 40514 +2015 69 14 -3.1 9.3 0 676.67 380.98 40719 +2015 70 9.4 -1.1 6.51 0.14 305.83 136.62 40924 +2015 71 8.5 3.3 7.07 0 435 198.48 41130 +2015 72 6.4 4.4 5.85 0 290.83 85.83 41336 +2015 73 8.8 3.8 7.43 0 306.67 147.96 41543 +2015 74 8.5 -0.1 6.13 0.1 225 126.38 41749 +2015 75 12.7 1.4 9.59 0 402.5 305.58 41956 +2015 76 13.3 3 10.47 0 528.33 310.03 42163 +2015 77 12.8 -1.5 8.87 0 623.33 392.35 42370 +2015 78 12 -2.5 8.01 0 533.33 380.32 42578 +2015 79 13 -3.1 8.57 0 560.83 349.98 42785 +2015 80 17.1 -1.8 11.9 0 823.33 405.64 42992 +2015 81 13.3 3.6 10.63 0 506.67 341.21 43200 +2015 82 13 -2.2 8.82 0 531.67 396.12 43407 +2015 83 15.7 -1.6 10.94 0 690 374.45 43615 +2015 84 15.2 1.4 11.4 0.9 560.83 182.8 43822 +2015 85 18.8 7.9 15.8 0.38 618.33 353.34 44029 +2015 86 12.8 8 11.48 0.12 387.5 87.96 44236 +2015 87 12.2 7.3 10.85 0 657.5 341.16 44443 +2015 88 15.6 0.6 11.48 0 723.33 337.51 44650 +2015 89 15.6 7.5 13.37 0.2 532.5 194.65 44857 +2015 90 18.6 0.7 13.68 0.02 753.33 262.22 45063 +2015 91 13.6 3.7 10.88 0 627.5 445.2 45270 +2015 92 13.2 0.8 9.79 0 747.5 228.52 45475 +2015 93 11.1 -1.1 7.75 0 676.15 376.93 45681 +2015 94 9.5 -0.5 6.75 0 474.62 198 45886 +2015 95 9.4 2.4 7.48 0 456.15 354.63 46091 +2015 96 8.5 1.1 6.46 0 545.38 428.59 46295 +2015 97 9.1 2.4 7.26 0 504.29 254.87 46499 +2015 98 10.2 5.5 8.91 0.02 435 67.4 46702 +2015 99 13.9 7.4 12.11 0 590.71 283.43 46905 +2015 100 18.8 2 14.18 0 922.14 473.21 47107 +2015 101 21.1 2.8 16.07 0.37 1034.29 428.33 47309 +2015 102 20.7 8 17.21 0 1043.57 426.27 47510 +2015 103 23.7 4 18.28 0 1295.71 448.78 47710 +2015 104 18 8.3 15.33 0 928.57 432.58 47910 +2015 105 24.8 4.9 19.33 0 1575 463.2 48108 +2015 106 27.7 4 21.18 0 1846.43 448.23 48306 +2015 107 21.9 7 17.8 0.69 936.43 236.59 48504 +2015 108 12.6 6.8 11 0 435.71 229.21 48700 +2015 109 13.6 0.8 10.08 0 608.57 450.69 48895 +2015 110 19.5 1.5 14.55 0 909.29 524.28 49089 +2015 111 21.5 8.2 17.84 0 1177.14 515.47 49282 +2015 112 20.8 8.2 17.34 0 1227.14 458.89 49475 +2015 113 23.2 3.2 17.7 0 1394.29 466.12 49666 +2015 114 19.6 7 16.14 0 910 314.11 49855 +2015 115 23.1 5.9 18.37 0 1087.86 498.44 50044 +2015 116 22.9 8.5 18.94 0 1159.29 374.28 50231 +2015 117 23.2 7.7 18.94 0 1196.43 463.69 50417 +2015 118 19.1 9.5 16.46 1.06 207.86 112.71 50601 +2015 119 16.5 8.8 14.38 0 867.14 539.6 50784 +2015 120 18.5 1.5 13.82 0.15 970 389.1 50966 +2015 121 18.2 5.8 14.79 0.42 646.43 295.8 51145 +2015 122 18.9 10.6 16.62 0.18 451.43 350.11 51324 +2015 123 18 9.4 15.64 0.09 320 176.04 51500 +2015 124 24.7 12.2 21.26 0 812.86 410.06 51674 +2015 125 28.3 11.7 23.73 0 1329.29 422.28 51847 +2015 126 26.8 13.8 23.23 0.07 964.67 409.05 52018 +2015 127 22.7 9.1 18.96 0 1034 548.77 52187 +2015 128 24.4 13.2 21.32 0 1203.33 486.81 52353 +2015 129 24.3 9.4 20.2 0.06 732 298.32 52518 +2015 130 22.9 11.7 19.82 0 1154.67 454.08 52680 +2015 131 20.6 10.5 17.82 0 1018 539.81 52840 +2015 132 24.5 4.5 19 0 1296 514.77 52998 +2015 133 24.8 11.4 21.12 0.71 928 436.63 53153 +2015 134 24.1 13.4 21.16 0.01 666.67 350.4 53306 +2015 135 18.1 11.5 16.29 0.5 236 118.29 53456 +2015 136 20.3 11.9 17.99 0 395.33 275.61 53603 +2015 137 20.5 10.9 17.86 0 700 405.36 53748 +2015 138 23.3 10.9 19.89 0 842.67 403.72 53889 +2015 139 28.3 10.4 23.38 0.02 1067.33 439.46 54028 +2015 140 25.4 11.3 21.52 1.98 888.67 462.8 54164 +2015 141 13.5 10.1 12.57 0.41 235.33 102.52 54297 +2015 142 13 11.1 12.48 4.42 160 58.23 54426 +2015 143 13.4 10.6 12.63 0.24 126.88 99.81 54552 +2015 144 18.3 6 14.92 0 393.13 407.01 54675 +2015 145 18.7 12.6 17.02 0.12 456.25 137.68 54795 +2015 146 17.1 13.7 16.16 0.37 298.13 161.56 54911 +2015 147 16.8 11.3 15.29 0 685.63 316.95 55023 +2015 148 17.6 8.3 15.04 0 707.5 405.38 55132 +2015 149 23.4 5.5 18.48 0 988.13 504.03 55237 +2015 150 24.7 8.3 20.19 0.12 924.38 526 55339 +2015 151 22.3 13.8 19.96 0 663.75 351.21 55436 +2015 152 26.3 11 22.09 0 1038.75 459.99 55530 +2015 153 28.6 12.8 24.26 0 1370 492.81 55619 +2015 154 30 13.1 25.35 0 1597.5 492.99 55705 +2015 155 27.9 16.7 24.82 0 1289.38 510.86 55786 +2015 156 26.8 15.8 23.78 0 1195 449.99 55863 +2015 157 29.4 11.6 24.5 0 1366.87 510.19 55936 +2015 158 29.6 14.3 25.39 0 1565 476.21 56004 +2015 159 29.7 12.6 25 0 1696.88 505.68 56068 +2015 160 26.7 16.5 23.9 0 1050 499.6 56128 +2015 161 27.1 14.1 23.53 0 990 510.8 56183 +2015 162 28.6 15.4 24.97 0 1287.5 501.27 56234 +2015 163 31 14.6 26.49 0 1628.75 489.73 56280 +2015 164 32 16.5 27.74 0 1997.5 489.61 56321 +2015 165 31.8 14 26.91 0.05 1838.75 420.71 56358 +2015 166 25.7 14 22.48 0.13 704.38 276.2 56390 +2015 167 22.2 15.7 20.41 0.03 947.5 357.85 56418 +2015 168 21.2 14.2 19.27 0 1005 405.19 56440 +2015 169 24 10.9 20.4 0 1187.5 418.65 56458 +2015 170 20.8 15.8 19.43 0.21 666.88 184.52 56472 +2015 171 20.6 9.3 17.49 0.22 591.25 339.25 56480 +2015 172 20 5.8 16.09 0 833.13 391.31 56484 +2015 173 25.4 8.4 20.72 0 1143.75 464.15 56482 +2015 174 23.2 11.4 19.95 2.67 138.13 66.53 56476 +2015 175 20.6 11.2 18.02 0 735.31 348.24 56466 +2015 176 23.5 7.9 19.21 0 1160.27 475.58 56450 +2015 177 25.6 14.6 22.58 0 1370 533.84 56430 +2015 178 25.7 15.3 22.84 0.24 797.5 211.97 56405 +2015 179 25.7 16.1 23.06 0 1018.13 429.72 56375 +2015 180 25 12.9 21.67 0 1110 371.74 56341 +2015 181 27.2 11.1 22.77 0 1398.75 464.42 56301 +2015 182 30.3 14 25.82 0 1623.75 459.22 56258 +2015 183 31.7 15.9 27.36 0 1828.75 499.83 56209 +2015 184 30.4 17.6 26.88 0 1801.88 497.85 56156 +2015 185 31.6 15 27.04 0 2052.5 523.19 56099 +2015 186 33.4 14.5 28.2 0 2082.5 513.05 56037 +2015 187 34.6 15.6 29.38 0 2108.13 466.5 55971 +2015 188 36.9 18.9 31.95 0 2431.88 478.24 55900 +2015 189 33.2 18.9 29.27 4.57 1217.5 297.43 55825 +2015 190 24.9 16 22.45 0.29 559.38 316.63 55746 +2015 191 24.5 11.4 20.9 0 1177.5 507.94 55663 +2015 192 27.6 13.3 23.67 0.1 1318.75 481.58 55575 +2015 193 31 14.2 26.38 1.71 1583.13 431.27 55484 +2015 194 27.3 18 24.74 0.1 410 179.82 55388 +2015 195 26.8 16.7 24.02 0 895 319.04 55289 +2015 196 29.6 18.8 26.63 0 1298.13 442.17 55186 +2015 197 32 18.3 28.23 0 1355 376.82 55079 +2015 198 34.8 19.2 30.51 0 1853.13 461.42 54968 +2015 199 32.3 19.4 28.75 0.63 1643.75 350.13 54854 +2015 200 35.5 18.7 30.88 0 1916.88 465.74 54736 +2015 201 32.1 19.9 28.75 0 1782.5 450.58 54615 +2015 202 34.1 18.5 29.81 0 1841.88 369.82 54490 +2015 203 35.7 19 31.11 0 2141.25 474.7 54362 +2015 204 33.4 19.5 29.58 0.3 1826.25 374.78 54231 +2015 205 34 21.7 30.62 0.12 1751.25 452.86 54097 +2015 206 32.9 18.1 28.83 2.89 1127.5 370.23 53960 +2015 207 21.5 14.7 19.63 0 590.63 170.92 53819 +2015 208 20.6 13.9 18.76 0.09 420.63 157.37 53676 +2015 209 24.2 16.3 22.03 0 788.13 271.28 53530 +2015 210 20.8 14.1 18.96 0.45 328.67 101.23 53382 +2015 211 20.4 14.8 18.86 0.08 561.43 174.87 53230 +2015 212 24.6 16 22.23 0 1270 371.65 53076 +2015 213 26.6 9 21.76 0.02 1351.43 491.91 52920 +2015 214 26.1 16.2 23.38 0.4 1182.14 350.71 52761 +2015 215 28.9 17.1 25.66 0 1195.71 426.81 52600 +2015 216 31.2 16.2 27.07 0 1473.57 395.8 52437 +2015 217 32.2 18.1 28.32 0 2064.29 480.9 52271 +2015 218 34 17.3 29.41 0 2191.43 442.06 52103 +2015 219 35.2 18.1 30.5 0 2453.57 479.18 51934 +2015 220 35.4 18.1 30.64 0 2487.86 453.94 51762 +2015 221 35.3 16.8 30.21 0 2542.14 463.4 51588 +2015 222 34.4 15.2 29.12 0 2699.29 453.25 51413 +2015 223 34.3 15.2 29.05 0 2616.43 437.78 51235 +2015 224 36.1 15.4 30.41 0 3033.57 446.12 51057 +2015 225 36.2 15.4 30.48 0 2750.71 406.28 50876 +2015 226 35.8 16.6 30.52 0 2414.29 417.12 50694 +2015 227 34.4 17.2 29.67 0.02 2207.14 396.02 50510 +2015 228 30.2 18.6 27.01 1.8 1462.86 316.94 50325 +2015 229 26.1 17.9 23.84 0.21 342.14 160.75 50138 +2015 230 22.8 16.3 21.01 0 735.71 359.58 49951 +2015 231 23.7 13.9 21 0 729.29 289.65 49761 +2015 232 19 15.1 17.93 0.02 345.71 153.84 49571 +2015 233 23.3 11.8 20.14 0 847.14 303.07 49380 +2015 234 24.4 10.2 20.49 0 869.29 432.23 49187 +2015 235 24.1 12.4 20.88 0.04 672.86 285.12 48993 +2015 236 27.5 12.1 23.27 0 1290.71 403.57 48798 +2015 237 23.2 16.3 21.3 0.26 722.14 128.11 48603 +2015 238 26.9 10.2 22.31 0 1509.29 468.65 48406 +2015 239 29.3 12.5 24.68 0 971.43 461.14 48208 +2015 240 32.7 16.2 28.16 0 1818.57 494.12 48010 +2015 241 33.6 14.3 28.29 0 2062.86 450.44 47811 +2015 242 34.7 14 29.01 0 2049.29 445.38 47611 +2015 243 34 14.9 28.75 0 2142.14 453.51 47410 +2015 244 34 15.3 28.86 0 2232.14 450.18 47209 +2015 245 28.2 14.1 24.32 0.06 1050 303.51 47007 +2015 246 25.2 15.7 22.59 0.31 930 303.78 46805 +2015 247 23.4 15.1 21.12 1.41 813.85 192.23 46601 +2015 248 19.3 13.9 17.82 0.84 134.62 86.84 46398 +2015 249 18.6 11.5 16.65 0.36 570 340.9 46194 +2015 250 20 6.1 16.18 0.02 978.46 400.6 45989 +2015 251 20.3 12.6 18.18 0 977.69 367.39 45784 +2015 252 20.2 5.2 16.07 0 866.92 386.79 45579 +2015 253 20 10.6 17.41 0.05 716.15 337.79 45373 +2015 254 20.7 12.2 18.36 0.46 321.54 188.64 45167 +2015 255 24.1 7.2 19.45 0 708.46 453.64 44961 +2015 256 24.3 8.4 19.93 0 852.31 314.93 44755 +2015 257 27.7 14.5 24.07 0 1368.33 329.73 44548 +2015 258 26.1 13.6 22.66 0 818.33 212.53 44341 +2015 259 28 18.6 25.41 0 1208.33 277.65 44134 +2015 260 32.1 21.1 29.08 0 1818.33 387.98 43927 +2015 261 27.4 15.4 24.1 0.01 1550.83 338.43 43719 +2015 262 23.2 16.5 21.36 0.1 1048.33 165.4 43512 +2015 263 21.8 15 19.93 0 1110 322.53 43304 +2015 264 20.4 7.8 16.93 0 1118.33 423.21 43097 +2015 265 22.1 3.9 17.09 0 958.33 396.89 42890 +2015 266 23.1 6.5 18.54 0.34 950 315.03 42682 +2015 267 17.7 13.2 16.46 0.64 690.83 185.83 42475 +2015 268 17 12.3 15.71 3.42 227.5 39.89 42268 +2015 269 16.8 13 15.76 0.04 487.5 169.57 42060 +2015 270 17.1 12 15.7 0 653.33 244.35 41854 +2015 271 17 9.7 14.99 0 652.5 283.79 41647 +2015 272 17.3 9 15.02 0 702.5 314.15 41440 +2015 273 14.8 9.6 13.37 0 580 199.52 41234 +2015 274 17.5 5.8 14.28 0 627.5 327.36 41028 +2015 275 18.9 2.4 14.36 0 718.33 352.29 40822 +2015 276 21.8 6.2 17.51 0 593.64 295.89 40617 +2015 277 22.8 6.9 18.43 0.02 850 294.1 40412 +2015 278 21.7 11.9 19 0 569.09 290 40208 +2015 279 20.3 8 16.92 0 432.73 238.78 40003 +2015 280 17 13.5 16.04 0.51 97.27 60.31 39800 +2015 281 16.6 12.3 15.42 0.15 215.45 110 39597 +2015 282 16.5 12.4 15.37 0.07 142.73 87.61 39394 +2015 283 14.6 9.5 13.2 1.37 175.45 65.52 39192 +2015 284 10.1 5.3 8.78 1.98 76.36 55.84 38991 +2015 285 8.5 2.9 6.96 0 341.82 211.38 38790 +2015 286 8 4.6 7.06 0.99 111.82 61.27 38590 +2015 287 9.5 7.8 9.03 2.66 37.27 45.13 38391 +2015 288 11.8 8.1 10.78 2.43 213.6 26.14 38193 +2015 289 13.9 10.8 13.05 0.37 90 151.87 37995 +2015 290 11.6 5.5 9.92 0.02 207.27 165.79 37799 +2015 291 12.4 5.7 10.56 2.91 105.45 128.58 37603 +2015 292 9.4 7.1 8.77 0 77.27 33.42 37408 +2015 293 12 5.4 10.18 0 363.64 199.55 37214 +2015 294 12.2 2 9.39 0 307.27 128.38 37022 +2015 295 12.7 4.2 10.36 0 398.18 239.09 36830 +2015 296 14.5 1.6 10.95 0 353.64 176.45 36640 +2015 297 15.3 2.5 11.78 0 370.91 343.5 36451 +2015 298 14.5 1.6 10.95 0 292.73 271.87 36263 +2015 299 13.8 4.4 11.22 0 322.73 247.61 36076 +2015 300 14.3 6.9 12.27 0 336.36 295.64 35891 +2015 301 9.2 4 7.77 0.03 95 45.87 35707 +2015 302 11.1 7.2 10.03 0.06 76 79.41 35525 +2015 303 16.3 6.3 13.55 0 522 309.39 35345 +2015 304 14.8 0 10.73 0 409 296.27 35166 +2015 305 12.2 0.9 9.09 0 533 320.67 34988 +2015 306 12 -2.4 8.04 0 453 286.85 34813 +2015 307 13.1 -1.8 9 0 430 296.76 34639 +2015 308 10.6 -0.2 7.63 0 130.25 232.18 34468 +2015 309 13.8 -2 9.46 0 313 243.09 34298 +2015 310 15 -0.5 10.74 0 336.67 265.97 34130 +2015 311 15.9 3.3 12.44 0 461.11 151.71 33964 +2015 312 21 6.5 17.01 0 744.44 242.98 33801 +2015 313 14.4 3.6 11.43 0 363.33 158.33 33640 +2015 314 21.8 10.9 18.8 0 1054.44 161.6 33481 +2015 315 21.9 6.6 17.69 0 886.67 226.28 33325 +2015 316 18.1 3.2 14 0 516.67 243.33 33171 +2015 317 15.6 4 12.41 0 393.33 234.47 33019 +2015 318 14.7 3.8 11.7 0 472.22 176.65 32871 +2015 319 12.2 3.8 9.89 0 398.89 102.75 32725 +2015 320 19.6 6 15.86 0 882.22 226.73 32582 +2015 321 11.6 1.4 8.79 0 288.89 136.88 32441 +2015 322 18.1 7.4 15.16 0 703.33 239.88 32304 +2015 323 16.3 0.3 11.9 0 336.67 236.04 32170 +2015 324 12 6.7 10.54 0.48 410 95.77 32039 +2015 325 11 4.4 9.19 0.03 227.78 33.09 31911 +2015 326 7.2 2.7 5.96 0 271.11 88.57 31786 +2015 327 5.7 -2.8 3.36 0 171.11 221.62 31665 +2015 328 4.8 -1.8 2.98 0 210 155.64 31547 +2015 329 2.2 -2.6 0.88 0.03 138.89 57.98 31433 +2015 330 3.8 -0.2 2.7 0 131.11 92.65 31322 +2015 331 4.1 2.8 3.74 0 216.67 73.68 31215 +2015 332 5.4 -1.7 3.45 0 186.67 160.38 31112 +2015 333 9.9 -2.8 6.41 0 398.89 192.1 31012 +2015 334 12.7 0.2 9.26 0 537.78 140.22 30917 +2015 335 15.7 4.7 12.67 0.06 747.78 149.59 30825 +2015 336 11.1 4.8 9.37 0 220 167.15 30738 +2015 337 9 0.7 6.72 0 45.56 58.55 30654 +2015 338 7.6 3.1 6.36 0 120 34.65 30575 +2015 339 9.7 0.2 7.09 0.01 74.44 198.1 30500 +2015 340 3.3 2.1 2.97 0 45.4 31.62 30430 +2015 341 2.7 0.1 1.99 0 89.54 71.44 30363 +2015 342 2.2 0.3 1.68 0.08 65.19 30.78 30301 +2015 343 3 1.4 2.56 0.02 1.11 36.84 30244 +2015 344 8.7 0.3 6.39 0 411.11 177.1 30191 +2015 345 6.1 -3.3 3.51 0 203.33 212.82 30143 +2015 346 2.1 -2.3 0.89 0 5.56 65.28 30099 +2015 347 3.2 -3.7 1.3 0 14.44 115.84 30060 +2015 348 6.3 -2.8 3.8 0.02 155 123.68 30025 +2015 349 4.1 0.9 3.22 0.02 8.75 47.46 29995 +2015 350 6.1 1 4.7 0 77.5 109.61 29970 +2015 351 3.4 1.8 2.96 0.01 59.96 36.08 29950 +2015 352 2.3 0.3 1.75 0 68.79 57.72 29934 +2015 353 8.8 0.6 6.54 0 51.25 147.56 29924 +2015 354 3.9 -0.1 2.8 0.01 140.58 35.27 29918 +2015 355 2.9 1.2 2.43 0 61.48 41.31 29916 +2015 356 9.6 -0.5 6.82 0 168.75 204.21 29920 +2015 357 3.7 -1.2 2.35 0 52.5 167.86 29928 +2015 358 9.5 -1.1 6.59 0 246.25 155.33 29941 +2015 359 8.8 1.4 6.77 0 108.75 183.58 29959 +2015 360 8.3 -2.8 5.25 0 297.5 218.81 29982 +2015 361 1.6 -2.3 0.53 0 7.5 99.17 30009 +2015 362 8.5 -4 5.06 0 172.5 215.71 30042 +2015 363 3.3 -1.4 2.01 0 38.75 42.53 30078 +2015 364 3.4 -2.4 1.8 0 212.5 133.39 30120 +2015 365 -1.4 -8.4 -3.33 0 85 103.83 30166 +2016 1 1.6 -6.7 -0.68 0 117.5 78.08 30217 +2016 2 -1 -6.2 -2.43 0.05 40 13.87 30272 +2016 3 -3.9 -5.9 -4.45 0 68.75 65.89 30331 +2016 4 -5.9 -7.6 -6.37 0.1 60 67.32 30396 +2016 5 -3.4 -7.6 -4.55 0.07 30 70.03 30464 +2016 6 -0.7 -4.2 -1.66 0.32 20 41.37 30537 +2016 7 2.5 -7.4 -0.22 0 11.25 187.43 30614 +2016 8 3.3 -2.3 1.76 0 26.25 95.98 30695 +2016 9 2.2 0.2 1.65 0.72 68.35 64.91 30781 +2016 10 3.5 0.4 2.65 0 110.1 91.67 30870 +2016 11 12.3 -0.6 8.75 2.32 277.5 68.45 30964 +2016 12 10.1 -2.7 6.58 0 235.56 184.35 31061 +2016 13 9.5 -3 6.06 0 295.56 148.13 31162 +2016 14 8.4 -2.9 5.29 0 423.33 140.42 31268 +2016 15 5.2 -4.3 2.59 0 218.89 64.07 31376 +2016 16 3.7 -5.5 1.17 0 200 155.24 31489 +2016 17 2.1 -4 0.42 0 160 151.44 31605 +2016 18 1.3 -8.8 -1.48 0 235.56 219.53 31724 +2016 19 1.2 -10.6 -2.04 0 157.78 174.89 31847 +2016 20 3.7 -9.8 -0.01 0 183 216.13 31974 +2016 21 2.6 -9.8 -0.81 0 186 217.84 32103 +2016 22 3.4 -10.7 -0.48 0 203 265.35 32236 +2016 23 -1.6 -11.1 -4.21 0.22 95 63.07 32372 +2016 24 6.9 -7.9 2.83 0 274 202.84 32510 +2016 25 2.8 -3 1.2 0.02 111 86.98 32652 +2016 26 12.6 -2.4 8.47 0 427 198.17 32797 +2016 27 10.7 -2.8 6.99 0 324 192.18 32944 +2016 28 16.7 0 12.11 0 555 232.58 33094 +2016 29 12.6 -2.4 8.47 0 298 190.33 33247 +2016 30 9.6 -3.7 5.94 0 216 168.17 33402 +2016 31 7.4 -0.8 5.15 0.07 250 52.97 33559 +2016 32 14.8 2.6 11.45 0 401 116.01 33719 +2016 33 9.3 0.5 6.88 0 164 71.13 33882 +2016 34 8 -0.6 5.63 2.03 23 51.85 34046 +2016 35 11.1 -0.6 7.88 0 452 210.32 34213 +2016 36 9.6 -2.9 6.16 0 331 271.79 34382 +2016 37 12.7 -2 8.66 0 442 268.28 34552 +2016 38 13.5 -1.9 9.27 0 490 175.7 34725 +2016 39 14.9 2.7 11.55 0 540 125.89 34900 +2016 40 15 -1.1 10.57 2.11 531 216.95 35076 +2016 41 9.6 0.4 7.07 1.47 46 83.15 35254 +2016 42 11.8 -2.9 7.76 0 436 261.77 35434 +2016 43 5.7 -4.3 2.95 1.12 163 121.33 35615 +2016 44 10 -1.3 6.89 0.64 60 82.88 35798 +2016 45 11 -2 7.43 0.76 191 161.57 35983 +2016 46 7.6 3.1 6.36 1.14 150 48.65 36169 +2016 47 6.7 3.2 5.74 0.1 238 77.59 36356 +2016 48 4.5 2.5 3.95 0.04 26 40.01 36544 +2016 49 7.1 3.4 6.08 1.16 160.77 43.01 36734 +2016 50 7.5 0.8 5.66 0.67 73 89.77 36925 +2016 51 11 -0.4 7.87 0.14 168 241.89 37117 +2016 52 17.1 3.5 13.36 0.08 558 200.28 37310 +2016 53 18.4 3.6 14.33 0.03 624 254.54 37505 +2016 54 15.9 4.3 12.71 0.15 510 113.52 37700 +2016 55 13.1 -1.7 9.03 0 545.45 292.9 37896 +2016 56 7.4 -2.9 4.57 0.14 187.27 124.15 38093 +2016 57 8.5 0.8 6.38 0 359.09 163.63 38291 +2016 58 10.8 -4.4 6.62 0 374.55 294.78 38490 +2016 59 11.4 0.8 8.48 0.17 174.55 133.7 38689 +2016 60 10.1 4 8.42 0.67 52.73 65.79 38890 +2016 61 11.6 3.2 9.29 0 249.09 140.02 39091 +2016 62 12.6 -3.3 8.23 0.27 258.33 222.24 39292 +2016 63 5.2 2.2 4.38 0.84 84.17 70.76 39495 +2016 64 10.4 -1.4 7.16 0 421.67 313.43 39697 +2016 65 12.1 -1.6 8.33 0 470.83 223.25 39901 +2016 66 14.7 2.1 11.23 0.45 320.83 183.92 40105 +2016 67 5.2 1.3 4.13 0.64 78.33 64.25 40309 +2016 68 10.9 0.4 8.01 0 200.83 198.38 40514 +2016 69 12.4 -2.4 8.33 0 289.17 358.05 40719 +2016 70 14 -2.1 9.57 0.06 389.17 370.48 40924 +2016 71 8.6 5.7 7.8 0.14 220 103.12 41130 +2016 72 9.4 4 7.92 0.03 255.83 133.56 41336 +2016 73 11 3.5 8.94 0 169.17 137.24 41543 +2016 74 10.9 -0.8 7.68 0 390 419.01 41749 +2016 75 7.3 0.6 5.46 0.42 170 104.76 41956 +2016 76 10 0.9 7.5 0 149.17 172.05 42163 +2016 77 15.2 -1.8 10.52 0 458.33 398.82 42370 +2016 78 17.1 -3.5 11.44 0 517.5 430.15 42578 +2016 79 12.1 1.9 9.29 0 361.67 400.56 42785 +2016 80 17.5 -0.9 12.44 0 554.17 427.28 42992 +2016 81 16.4 2.2 12.49 0 395.42 272.06 43200 +2016 82 14 0.8 10.37 0.06 453.33 258.8 43407 +2016 83 11.7 2.8 9.25 0 372.5 177.39 43615 +2016 84 12.2 -0.5 8.71 0.02 404.17 301.19 43822 +2016 85 12.4 -2.8 8.22 0 524.17 159.64 44029 +2016 86 12.7 1.3 9.56 0.08 301.67 188.23 44236 +2016 87 18.1 -2.3 12.49 0 580.83 406.22 44443 +2016 88 19.3 -0.1 13.97 0 505.83 349.6 44650 +2016 89 18.6 1.1 13.79 0.98 502.5 254.7 44857 +2016 90 21.1 1.2 15.63 0.01 552.5 299.31 45063 +2016 91 25.4 1.5 18.83 0 1018.33 416.09 45270 +2016 92 21.9 8 18.08 0 785 266.57 45475 +2016 93 17.9 1.6 13.42 0 668.46 330.75 45681 +2016 94 23.6 -0.2 17.06 0 1123.08 422.09 45886 +2016 95 26.4 7.2 21.12 0 1403.08 385.12 46091 +2016 96 27 6 21.23 0 1559.23 383.02 46295 +2016 97 21.8 6.1 17.48 0 950 414.94 46499 +2016 98 22.6 4.3 17.57 0 775.71 365.91 46702 +2016 99 12.3 8.3 11.2 0.53 281.43 85.15 46905 +2016 100 14.5 7.2 12.49 0 355 312.41 47107 +2016 101 16.6 3.5 13 0 520.71 359.69 47309 +2016 102 20.6 2.7 15.68 0 636.43 480.94 47510 +2016 103 22.4 1.8 16.73 0 555 448.65 47710 +2016 104 25.9 3.4 19.71 0 1005.71 419.4 47910 +2016 105 16.5 3.1 12.82 0.04 442.14 127.63 48108 +2016 106 22.1 1 16.3 0 987.14 423.15 48306 +2016 107 24.5 2.7 18.5 0 1390 502.56 48504 +2016 108 24.3 11.9 20.89 0 1318.57 358.11 48700 +2016 109 15.3 8.9 13.54 0 403.57 316.88 48895 +2016 110 17.5 7.9 14.86 0 782.86 387.17 49089 +2016 111 18.9 0.9 13.95 0 847.86 362.16 49282 +2016 112 23.3 -0.8 16.67 0 1026.43 502.52 49475 +2016 113 22.5 1.4 16.7 0 1015.71 495.92 49666 +2016 114 24.1 8 19.67 0.37 882.14 370.8 49855 +2016 115 10.5 4.9 8.96 0 501.43 224.78 50044 +2016 116 13.2 -1.6 9.13 0 540.71 346.18 50231 +2016 117 18.8 -2.3 13 0 797.86 470.69 50417 +2016 118 8.4 1.2 6.42 0.87 125 64.02 50601 +2016 119 16.7 -1.3 11.75 0 202.86 167.38 50784 +2016 120 21 -1.9 14.7 0 672.14 560.34 50966 +2016 121 23.1 -0.8 16.53 0 818.57 507.68 51145 +2016 122 15.4 3.5 12.13 1.56 130.71 109.84 51324 +2016 123 17.2 9.8 15.16 0.73 88.57 100.94 51500 +2016 124 20.5 10.7 17.81 0.38 635.71 367.39 51674 +2016 125 16.8 9.2 14.71 0 449.29 145.78 51847 +2016 126 20.5 8.2 17.12 0 463.33 445.07 52018 +2016 127 25.2 6.3 20 0 872 506.57 52187 +2016 128 26.7 3.8 20.4 0 990 499.78 52353 +2016 129 23.6 5.5 18.62 0 688.67 429.75 52518 +2016 130 24.6 4.6 19.1 0 779.33 441.85 52680 +2016 131 21.6 5.8 17.26 0 404 277.63 52840 +2016 132 18.3 12.3 16.65 1.17 244 127.06 52998 +2016 133 17.5 12.5 16.13 1.58 58 67.18 53153 +2016 134 24 9.8 20.09 1.26 566.67 379.74 53306 +2016 135 22.4 11.6 19.43 0.82 385.33 213.2 53456 +2016 136 16.8 2.2 12.79 0.04 529.33 243.66 53603 +2016 137 18.6 -0.1 13.46 0.12 634.67 409.66 53748 +2016 138 19.5 3.1 14.99 0 640.67 399.72 53889 +2016 139 22.7 6.6 18.27 0 724 320.76 54028 +2016 140 24.8 3.7 19 1.26 852.67 493.58 54164 +2016 141 23.5 6.9 18.93 0 660.67 388.99 54297 +2016 142 27 4.8 20.9 0 1128 493.64 54426 +2016 143 27.2 6.9 21.62 0 1336.88 530.56 54552 +2016 144 28 7.1 22.25 2.18 1279.38 517.57 54675 +2016 145 22.3 10.7 19.11 0 256.88 176.13 54795 +2016 146 24.3 8.1 19.84 0 791.88 483.84 54911 +2016 147 26.9 8.2 21.76 0 725 457.54 55023 +2016 148 28.4 9.7 23.26 0 1168.75 443.73 55132 +2016 149 30 15.5 26.01 0 1418.75 440.04 55237 +2016 150 30.5 12.6 25.58 0.21 1441.25 457.48 55339 +2016 151 27.8 12.3 23.54 0 1038.75 517.19 55436 +2016 152 28.8 8.9 23.33 0.04 1035.63 515.15 55530 +2016 153 26.5 9.9 21.93 0 850.63 396.67 55619 +2016 154 28.9 11.2 24.03 0 566.25 359.04 55705 +2016 155 28.5 12.2 24.02 0 730 366.35 55786 +2016 156 28.3 11.1 23.57 0 718.75 354.04 55863 +2016 157 27.1 11.2 22.73 0.83 392.5 214.89 55936 +2016 158 28.7 9.8 23.5 0 1026.25 484.81 56004 +2016 159 25.7 8.5 20.97 0 1216.25 500.22 56068 +2016 160 29.1 7.6 23.19 0 1136.88 464.7 56128 +2016 161 27.1 12.3 23.03 0.06 862.5 296.58 56183 +2016 162 26.5 12 22.51 0.35 427.5 300.49 56234 +2016 163 28.2 10.3 23.28 0.96 460 334.37 56280 +2016 164 25 14.6 22.14 0 431.25 246.5 56321 +2016 165 26.4 11.4 22.27 0 620.63 324.73 56358 +2016 166 28 10.6 23.22 1.23 703.75 352.75 56390 +2016 167 26.4 13.1 22.74 0.94 325 260.68 56418 +2016 168 29.6 13.4 25.15 0 1208.75 411.78 56440 +2016 169 28.6 11.7 23.95 0 1406.88 444.83 56458 +2016 170 29.8 9.8 24.3 0 977.5 477.03 56472 +2016 171 23.9 12.6 20.79 2.13 564.38 207.41 56480 +2016 172 24.5 11.8 21.01 2.54 298.13 285.77 56484 +2016 173 31.7 9.8 25.68 0 996.25 446.39 56482 +2016 174 32.5 12.5 27 0 1281.88 453.73 56476 +2016 175 34 14.2 28.56 0 1375.63 469.98 56466 +2016 176 35 16.8 29.99 0 1498.13 448.36 56450 +2016 177 33.6 18.4 29.42 0.08 1285.63 457.85 56430 +2016 178 29.2 17.3 25.93 0 1021.88 419.64 56405 +2016 179 24.1 11.6 20.66 0.16 738.75 204.72 56375 +2016 180 27.4 8.4 22.17 0 1309.38 504.8 56341 +2016 181 33.2 9.8 26.77 0 1393.13 478.93 56301 +2016 182 32 12.9 26.75 0 1456.25 449.29 56258 +2016 183 32.2 14.2 27.25 0 1396.88 409.72 56209 +2016 184 33.4 13.9 28.04 0 1361.25 447.22 56156 +2016 185 22.3 9.6 18.81 0.42 861.88 149.78 56099 +2016 186 29.5 7.9 23.56 0 1300.63 473.12 56037 +2016 187 31.1 11.3 25.66 0 1380 454.58 55971 +2016 188 30.7 14.2 26.16 0 1168.13 382.92 55900 +2016 189 29.4 9.4 23.9 0 1330.63 407.42 55825 +2016 190 30.7 11.1 25.31 0 1268.75 496.23 55746 +2016 191 32.6 14.5 27.62 0 1474.38 360.6 55663 +2016 192 34.4 13.7 28.71 0 1576.88 451.42 55575 +2016 193 35.5 14 29.59 0 1832.5 476.97 55484 +2016 194 34.7 18.6 30.27 1.51 1649.38 476.63 55388 +2016 195 28.9 17.5 25.77 0.5 807.5 392.72 55289 +2016 196 25.8 13.2 22.34 3.03 850 369.03 55186 +2016 197 23.4 10.4 19.82 0 875.63 332.58 55079 +2016 198 16.5 13.7 15.73 0.09 468.75 91.49 54968 +2016 199 25.4 13.7 22.18 0 850 205.36 54854 +2016 200 31.2 14.6 26.63 0 1181.25 406.56 54736 +2016 201 29.8 14.9 25.7 0 1271.88 462.85 54615 +2016 202 29.8 14.6 25.62 0 1181.25 440.37 54490 +2016 203 33.4 12.3 27.6 0.05 1294.38 468.95 54362 +2016 204 31.6 15.7 27.23 1.53 1055.63 456.12 54231 +2016 205 33 18.3 28.96 0 833.75 347.58 54097 +2016 206 31.5 18.3 27.87 0 1004.38 428.81 53960 +2016 207 28.4 17.7 25.46 0.72 460.63 192.87 53819 +2016 208 28.7 15.7 25.13 1.27 574.38 296.05 53676 +2016 209 32.7 15.6 28 0.05 801.88 402.05 53530 +2016 210 29.2 18.3 26.2 1.64 655.33 306.3 53382 +2016 211 20.4 14.8 18.86 0.08 1286.43 423.87 53230 +2016 212 24.6 16 22.23 0 863.57 467.18 53076 +2016 213 26.6 9 21.76 0.02 1456.86 412.35 52920 +2016 214 26.1 16.2 23.38 0.4 1032.42 221.14 52761 +2016 215 28.9 17.1 25.66 0 1343.41 333.87 52600 +2016 216 31.2 16.2 27.07 0 1739.42 395.23 52437 +2016 217 32.2 18.1 28.32 0 1774.71 375.26 52271 +2016 218 34 17.3 29.41 0 2126.43 412.71 52103 +2016 219 35.2 18.1 30.5 0 2289.18 413.27 51934 +2016 220 35.4 18.1 30.64 0 2325.51 414.99 51762 +2016 221 35.3 16.8 30.21 0 2382.18 431.1 51588 +2016 222 34.4 15.2 29.12 0 2306.29 443.13 51413 +2016 223 34.3 15.2 29.05 0 2289.43 441.83 51235 +2016 224 36.1 15.4 30.41 0 2593.88 449.07 51057 +2016 225 36.2 15.4 30.48 0 2611.94 445.66 50876 +2016 226 35.8 16.6 30.52 0 2482.59 425.37 50694 +2016 227 34.4 17.2 29.67 0.02 2201.34 300.62 50510 +2016 228 30.2 18.6 27.01 1.8 1424.39 229.15 50325 +2016 229 26.1 17.9 23.84 0.21 905.14 174.18 50138 +2016 230 22.8 16.3 21.01 0 635.34 194.76 49951 +2016 231 23.7 13.9 21 0 899.23 286.89 49761 +2016 232 19 15.1 17.93 0.02 338.11 95.8 49571 +2016 233 23.3 11.8 20.14 0 973.7 338.55 49380 +2016 234 24.4 10.2 20.49 0 1165.89 390.53 49187 +2016 235 24.1 12.4 20.88 0.04 1028.76 255.28 48993 +2016 236 27.5 12.1 23.27 0 1442.56 398.39 48798 +2016 237 23.2 16.3 21.3 0.26 680.01 159.34 48603 +2016 238 26.9 10.2 22.31 0 1448.87 415.57 48406 +2016 239 29.3 12.5 24.68 0 1658.09 407.33 48208 +2016 240 32.7 16.2 28.16 0 1974.31 386.07 48010 +2016 241 33.6 14.3 28.29 0 2214.82 411.59 47811 +2016 242 34.7 14 29.01 0 2408.91 416.6 47611 +2016 243 34 14.9 28.75 0 2253.32 399.18 47410 +2016 244 34 15.3 28.86 0 2234.4 389.27 47209 +2016 245 28.2 14.1 24.32 0.06 1432.91 253.17 47007 +2016 246 25.2 15.7 22.59 0.31 956.17 186.49 46805 +2016 247 23.4 15.1 21.12 1.41 788.44 167.82 46601 +2016 248 19.3 13.9 17.82 0.84 451.65 116.95 46398 +2016 249 18.6 11.5 16.65 0.36 537.6 155.11 46194 +2016 250 20 6.1 16.18 0.02 896.82 269.97 45989 +2016 251 20.3 12.6 18.18 0 628.48 223.55 45784 +2016 252 20.2 5.2 16.07 0 941.83 378.74 45579 +2016 253 20 10.6 17.41 0.05 710.7 203.8 45373 +2016 254 20.7 12.2 18.36 0.46 690.03 188.69 45167 +2016 255 24.1 7.2 19.45 0 1243.85 396.05 44961 +2016 256 24.3 8.4 19.93 0 1224.87 382.41 44755 +2016 257 27.7 14.5 24.07 0 1345.02 332.8 44548 +2016 258 26.1 13.6 22.66 0 1194.71 322.7 44341 +2016 259 28 18.6 25.41 0 1103.78 249.49 44134 +2016 260 32.1 21.1 29.08 0 1521.14 265.25 43927 +2016 261 27.4 15.4 24.1 0.01 1251.93 223.75 43719 +2016 262 23.2 16.5 21.36 0.1 664.82 138.37 43512 +2016 263 21.8 15 19.93 0 622.62 190.32 43304 +2016 264 20.4 7.8 16.93 0 871 320.69 43097 +2016 265 22.1 3.9 17.09 0 1141.13 379.89 42890 +2016 266 23.1 6.5 18.54 0.34 1165.82 269.61 42682 +2016 267 17.7 13.2 16.46 0.64 355.05 95.64 42475 +2016 268 17 12.3 15.71 3.42 353.85 102.07 42268 +2016 269 16.8 13 15.76 0.04 292.11 85.47 42060 +2016 270 17.1 12 15.7 0 380.68 152.72 41854 +2016 271 17 9.7 14.99 0 500.72 217.44 41647 +2016 272 17.3 9 15.02 0 558.86 246.12 41440 +2016 273 14.8 9.6 13.37 0 338.75 169.26 41234 +2016 274 17.5 5.8 14.28 0 705.41 316.58 41028 +2016 275 18.9 2.4 14.36 0 909.83 358.47 40822 +2016 276 21.8 6.2 17.51 0 1052.48 341.56 40617 +2016 277 22.8 6.9 18.43 0.02 1124.5 252.18 40412 +2016 278 21.7 11.9 19 0 804.39 254.28 40208 +2016 279 20.3 8 16.92 0 854.35 293.06 40003 +2016 280 17 13.5 16.04 0.51 275.04 77.88 39800 +2016 281 16.6 12.3 15.42 0.15 321 94.54 39597 +2016 282 16.5 12.4 15.37 0.07 306.52 92.02 39394 +2016 283 14.6 9.5 13.2 1.37 329.59 114.96 39192 +2016 284 10.1 5.3 8.78 1.98 240.16 111.73 38991 +2016 285 8.5 2.9 6.96 0 246.49 176.15 38790 +2016 286 8 4.6 7.06 0.99 157.95 85.43 38590 +2016 287 9.5 7.8 9.03 2.66 92.27 48.11 38391 +2016 288 11.8 8.1 10.78 2.43 213.6 93.33 38193 +2016 289 13.9 10.8 13.05 0.37 206.93 78.26 37995 +2016 290 11.6 5.5 9.92 0.02 318.11 147.57 37799 +2016 291 12.4 5.7 10.56 2.91 358.45 158.09 37603 +2016 292 9.4 7.1 8.77 0 121.3 82.67 37408 +2016 293 12 5.4 10.18 0 346.02 205.66 37214 +2016 294 12.2 2 9.39 0 473.01 266.57 37022 +2016 295 12.7 4.2 10.36 0 432.98 242.63 36830 +2016 296 14.5 1.6 10.95 0 622.36 282.87 36640 +2016 297 15.3 2.5 11.78 0 650.53 275.89 36451 +2016 298 14.5 1.6 10.95 0 622.36 272.37 36263 +2016 299 13.8 4.4 11.22 0 494.76 234.81 36076 +2016 300 14.3 6.9 12.27 0 431.94 197.75 35891 +2016 301 9.2 4 7.77 0.03 242.61 114.16 35707 +2016 302 11.1 7.2 10.03 0.06 214.36 86.8 35525 +2016 303 16.3 6.3 13.55 0 597.38 226.48 35345 +2016 304 14.8 0 10.73 0 677.96 258.95 35166 +2016 305 12.2 0.9 9.09 0 502.83 238.99 34988 +2016 306 12 -2.4 8.04 0 563.19 253.72 34813 +2016 307 13.1 -1.8 9 0 612.44 251.48 34639 +2016 308 10.6 -0.2 7.63 0 443.67 227.08 34468 +2016 309 13.8 -2 9.46 0 655.84 246.64 34298 +2016 310 15 -0.5 10.74 0 700.46 239.82 34130 +2016 311 15.9 3.3 12.44 0 668.73 219.95 33964 +2016 312 21 6.5 17.01 0 970.69 219.42 33801 +2016 313 14.4 3.6 11.43 0 559.62 197.43 33640 +2016 314 21.8 10.9 18.8 0 866.05 183.04 33481 +2016 315 21.9 6.6 17.69 0 1049.13 209.59 33325 +2016 316 18.1 3.2 14 0 829.66 207.91 33171 +2016 317 15.6 4 12.41 0 627.19 183.09 33019 +2016 318 14.7 3.8 11.7 0 572.95 173.26 32871 +2016 319 12.2 3.8 9.89 0 416.71 142.38 32725 +2016 320 19.6 6 15.86 0 866.41 182.52 32582 +2016 321 11.6 1.4 8.79 0 455.95 157.94 32441 +2016 322 18.1 7.4 15.16 0 692.55 152.56 32304 +2016 323 16.3 0.3 11.9 0 768.45 188.86 32170 +2016 324 12 6.7 10.54 0.48 291.69 62.9 32039 +2016 325 11 4.4 9.19 0.03 325.77 77.16 31911 +2016 326 7.2 2.7 5.96 0 190.73 74.05 31786 +2016 327 5.7 -2.8 3.36 0 280.23 131.7 31665 +2016 328 4.8 -1.8 2.98 0 221.48 107.32 31547 +2016 329 2.2 -2.6 0.88 0.03 146.46 60.86 31433 +2016 330 3.8 -0.2 2.7 0 139.68 67.75 31322 +2016 331 4.1 2.8 3.74 0 51.51 28.87 31215 +2016 332 5.4 -1.7 3.45 0 242.71 111.71 31112 +2016 333 9.9 -2.8 6.41 0 464.41 161.6 31012 +2016 334 12.7 0.2 9.26 0 548.35 156.99 30917 +2016 335 15.7 4.7 12.67 0.06 611.55 106.65 30825 +2016 336 11.1 4.8 9.37 0 316.41 95.66 30738 +2016 337 9 0.7 6.72 0 339.66 122.88 30654 +2016 338 7.6 3.1 6.36 0 195.5 72.98 30575 +2016 339 9.7 0.2 7.09 0.01 387.8 101.97 30500 +2016 340 3.3 2.1 2.97 0 45.4 27.14 30430 +2016 341 2.7 0.1 1.99 0 89.54 48.06 30363 +2016 342 2.2 0.3 1.68 0.08 65.19 28.62 30301 +2016 343 3 1.4 2.56 0.02 58.46 25.48 30244 +2016 344 8.7 0.3 6.39 0 336.09 133.47 30191 +2016 345 6.1 -3.3 3.51 0 306.86 144.76 30143 +2016 346 2.1 -2.3 0.89 0 135.57 85.05 30099 +2016 347 3.2 -3.7 1.3 0 206.36 123.15 30060 +2016 348 6.3 -2.8 3.8 0.02 304.47 107.91 30025 +2016 349 4.1 0.9 3.22 0.02 117.58 47.96 29995 +2016 350 6.1 1 4.7 0 197.17 98.57 29970 +2016 351 3.4 1.8 2.96 0.01 59.96 27.51 29950 +2016 352 2.3 0.3 1.75 0 68.79 45.4 29934 +2016 353 8.8 0.6 6.54 0 332.69 141.84 29924 +2016 354 3.9 -0.1 2.8 0.01 140.58 65.14 29918 +2016 355 2.9 1.2 2.43 0 61.48 40.98 29916 +2016 356 9.6 -0.5 6.82 0 400.42 154.13 29920 +2016 357 3.7 -1.2 2.35 0 164.01 104.34 29928 +2016 358 9.5 -1.1 6.59 0 409.69 156.73 29941 +2016 359 8.8 1.4 6.77 0 309.62 133.95 29959 +2016 360 8.3 -2.8 5.25 0 390.15 158.76 29982 +2016 361 1.6 -2.3 0.53 0 118.72 83.23 30009 +2016 362 8.5 -4 5.06 0 421.47 164.5 30042 +2016 363 3.3 -1.4 2.01 0 154.57 99.03 30078 +2016 364 3.4 -2.4 1.8 0 183.68 119.63 30120 +2016 365 -1.4 -8.4 -3.33 0 153.65 139.92 30166 diff --git a/RBBGCMuso/R/recent.soi b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.soi similarity index 68% rename from RBBGCMuso/R/recent.soi rename to RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.soi index f69f1ce..e313496 100644 --- a/RBBGCMuso/R/recent.soi +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/hhs.soi @@ -1,12 +1,12 @@ -SOILPROP FILE - lat: 60, lon: 50, created in: Mon Apr 20 10:44:56 2020 +SOILPROP FILE - hhs muso6 ---------------------------------------------------------------------------------------- NITROGEN AND DECOMPOSITION PARAMETERS 0.1 (prop.) denitrification rate per g of CO2 respiration of SOM 0.2 (prop.) nitrification coefficient 1 -0.07 (prop.) nitrification coefficient 2 +0.1 (prop.) nitrification coefficient 2 0.02 (prop.) coefficient of N2O emission of nitrification 0.1 (prop.) NH4 mobilen proportion -1.0 (prop.) NO3 mobilen proportion +1.0 denitrification related N2/N2O ratio multiplier (soil texture effect) 10 (m) e-folding depth of decomposition rate's depth scalar 0.002 (prop.) fraction of dissolved part of SOIL1 organic matter 0.002 (prop.) fraction of dissolved part of SOIL2 organic matter @@ -16,39 +16,40 @@ NITROGEN AND DECOMPOSITION PARAMETERS 0.45 (prop.) lower optimum WFPS for scalar of nitrification calculation 0.55 (prop.) higher optimum WFPS for scalar of nitrification calculation 0.2 (prop.) minimum value for saturated WFPS scalar of nitrification calculation -10 (ppm) critical value of dissolved N and C in bottom (inactive layer) +10 (ppm) C:N ratio of recaltirant SOM (slowest) ---------------------------------------------------------------------------------------- RATE SCALARS -0.35 (prop) respiration fractions for fluxes between compartments (l1s1) -0.50 (prop) respiration fractions for fluxes between compartments (l2s2) -0.26 (prop) respiration fractions for fluxes between compartments (l4s3) -0.25 (prop) respiration fractions for fluxes between compartments (s1s2) -0.41 (prop) respiration fractions for fluxes between compartments (s2s3) -0.50 (prop) respiration fractions for fluxes between compartments (s3s4) -0.7 (1/day) rate constant scalar of labile litter pool -0.07 (1/day) rate constant scalar of cellulose litter pool -0.014 (1/day) rate constant scalar of lignin litter pool -0.07 (1/day) rate constant scalar of fast microbial recycling pool -0.014 (1/day) rate constant scalar of medium microbial recycling pool -0.0014 (1/day) rate constant scalar of slow microbial recycling pool -0.0001 (1/day) rate constant scalar of recalcitrant SOM (humus) pool -0.001 (1/day) rate constant scalar of physical fragmentation of coarse woody debris +0.39 (DIM) respiration fractions for fluxes between compartments (l1s1) +0.55 (DIM) respiration fractions for fluxes between compartments (l2s2) +0.29 (DIM) respiration fractions for fluxes between compartments (l4s3) +0.28 (DIM) respiration fractions for fluxes between compartments (s1s2) +0.46 (DIM) respiration fractions for fluxes between compartments (s2s3) +0.55 (DIM) respiration fractions for fluxes between compartments (s3s4) +0.7 (DIM) rate constant scalar of labile litter pool +0.07 (DIM) rate constant scalar of cellulose litter pool +0.014 (DIM) rate constant scalar of lignin litter pool +0.07 (DIM) rate constant scalar of fast microbial recycling pool +0.014 (DIM) rate constant scalar of medium microbial recycling pool +0.0014 (DIM) rate constant scalar of slow microbial recycling pool +0.0001 (DIM) rate constant scalar of recalcitrant SOM (humus) pool +0.001 (DIM) rate constant scalar of physical fragmentation of coarse woody debris ---------------------------------------------------------------------------------------- CH4 PARAMETERS 212.5 (DIM) soil CH4 emission bulk density dependence parameter1 1.81 (DIM) soil CH4 emission bulk density dependence parameter2 -1.353 (DIM) soil CH4 emission soil water content dependence parameter1 0.2 (DIM) soil CH4 emission soil water content dependence parameter2 -2 (DIM) soil CH4 emission soil water content dependence parameter3 +1.781 (DIM) soil CH4 emission soil water content dependence parameter3 6.786 (DIM) soil CH4 emission soil water content dependence parameter4 0.010 (DIM) soil CH4 emission soil temperature dependence parameter1 ---------------------------------------------------------------------------------------- SOIL PARAMETERS 2 (m) depth of soil -6 (mm)42 42 43 47 48 49 49 49 51 51 limit of first stage evaporation -20.00 (mm) maximum height of pond water +6 (mm) limit of first stage evaporation +5.00 (mm) maximum height of pond water 1 (dimless) curvature of soil stress function --9999 (dimless) measured runoff curve number (-9999: no measured data, model estimation) +-9999 (dimless) runoff curve number (-9999: no , model estimation) +107 (s/m) aerodynamic resistance (Wallace and Holwill, 1997) ---------------------------------------------------------------------------------------- SOIL COMPOSITION AND CHARACTERISTIC VALUES (-9999: no measured data) 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 (%) sand percentage by volume in rock-free soil diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso new file mode 100644 index 0000000..276db81 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso.exe b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso.exe new file mode 100644 index 0000000..e5df82a Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso.exe differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso7.0b7.exe b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso7.0b7.exe new file mode 100644 index 0000000..e5df82a Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/muso7.0b7.exe differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/n.ini b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/n.ini new file mode 100644 index 0000000..9e84847 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/n.ini @@ -0,0 +1,147 @@ +BBGCMuSo simulation + +MET_INPUT +hhs.mtc43 (filename) met file name +4 (int) number of header lines in met file +365 (int) number of simdays in last simyear (truncated year: <= 365) + +RESTART +1 (flag) 1 = read restart; 0 = dont read restart +0 (flag) 1 = write restart; 0 = dont write restart +hhs_MuSo6.endpoint (filename) name of the input restart file +hhs_MuSo6.endpoint (filename) name of the output restart file + +TIME_DEFINE +9 (int) number of simulation years +2007 (int) first simulation year +0 (flag) 1 = spinup run; 0 = normal run +6000 (int) maximum number of spinup years + +CO2_CONTROL +1 (flag) 0=constant; 1=vary with file +395.0 (ppm) constant atmospheric CO2 concentration +CO2.txt (filename) name of the CO2 file + +NDEP_CONTROL +1 (flag) 0=constant; 1=vary with file +0.001400 (kgN/m2/yr) wet+dry atmospheric deposition of N +Ndep.txt (filename) name of the N-dep file + +SITE +248.0 (m) site elevation +46.95 (degrees) site latitude (- for S.Hem.) +0.20 (DIM) site shortwave albedo +9.00 (Celsius) mean annual air temperature +10.15 (Celsius) mean annual air temperature range +0.50 (prop.) proprortion of NH4 flux of N-deposition + +SOIL_FILE +hhs.soi (filename) SOIL filename + +EPC_FILE +c3grass_muso6.epc (filename) EPC filename + +MANAGEMENT_FILE +hhs.mgm (filename) MGM filename (or "none") + +SIMULATION_CONTROL +1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY) +1 (flag) vegper calculation method if MODEL PHENOLOGY is used (0: original, 1: GSI) +0 (flag) transferGDD flag (1= transfer calc. from GDD 0 = transfer calc. from EPC) +1 (flag) q10 flag (1 = temperature dependent q10 value; 0= constans q10 value) +1 (flag) acclimation flag of photosynthesis (1 = acclimation 0 = no acclimation) +1 (flag) acclimation flag of respiration (1 = acclimation 0 = no acclimation) +1 (flag) CO2 conductance reduction flag (0: no effect, 1: multiplier) +0 (flag) soil temperature calculation method (0: Zheng, 1: DSSAT) +1 (flag) soil hydrological calculation method (0: Richards, 1: tipping DSSAT) +0 (int) discretization level of soil hydr.calc.[Richards-method] (0: low, 1: medium, 2: high) +0 (flag) photosynthesis calculation method (0: Farquhar, 1: DSSAT) +0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor) +0 (flag) radiation calculation method (0: SWabs, 1: Rn) +0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand) + +W_STATE +0.0 (kg/m2) water stored in snowpack +1.0 (DIM) initial soil water as a proportion of field capacity + +CN_STATE +0.001 (kgC/m2) first-year maximum leaf carbon +0.001 (kgC/m2) first-year maximum fine root carbon +0.001 (kgC/m2) first-year maximum fruit carbon +0.001 (kgC/m2) first-year maximum softstem carbon +0.001 (kgC/m2) first-year maximum live woody stem carbon +0.001 (kgC/m2) first-year maximum live coarse root carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) coarse woody debris carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, unshielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, shielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, lignin pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, fast microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, medium microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, slow microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, recalcitrant SOM (slowest) +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) litter nitrogen, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NH4 pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NO3 pool + +CLIM_CHANGE +0.0 (degC) - offset for Tmax +0.0 (degC) - offset for Tmin +1.0 (degC) - multiplier for PRCP +1.0 (degC) - multiplier for VPD +1.0 (degC) - multiplier for RAD + +CONDITIONAL_MANAGEMENT_STRATEGIES +0 (flag) conditional mowing ? 0 - no, 1 - yes +0.0 (m2/m2) fixed value of the LAI before MOWING +0.0 (m2/m2) fixed value of the LAI after MOWING +0.0 (%) transported part of plant material after MOWING +0 (flag) conditional irrigation? 0 - no, 1 - yes +0.0 (prop) SMSI before cond. IRRIGATION (-9999: SWCratio is used) +0.0 (prop) SWCratio of rootzone before cond. IRRIGATION (-9999: SMSI is used) +0.0 (prop) SWCratio of rootzone after cond. IRRIGATION +0.0 (kgH2O/m2) maximum amount of irrigated water + +OUTPUT_CONTROL +hhs_MuSo6 (filename) output prefix +1 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing annual output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +1 (flag) for on-screen progress indicator + +DAILY_OUTPUT +12 number of daily output variables +2520 proj_lai +3009 daily_GPP +3014 daily_Reco +171 evapotransp +2502 n_actphen +2603 vwc00-03cm +2604 vwc03-10cm +2605 vwc10-30cm +75 GDD +2636 rooting_depth +2716 m_soilstress +671 m_vegc_to_SNSC + +ANNUAL_OUTPUT +16 number of annual output variables +3000 annprcp +3001 anntavg +3002 annrunoff +3003 annoutflow +2734 annmax_lai +3031 cum_Closs_MGM +3032 cum_Cplus_MGM +3045 cum_Closs_SNSC +3046 cum_Cplus_STDB +3058 vegc +3064 totalc +3066 SOM_C_top30 +3070 SOM_C_30to60 +3071 SOM_C_60to90 +3068 NH4_top30 +3069 NO3_top30 + +END_INIT diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/parameters.csv b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/parameters.csv new file mode 100644 index 0000000..fd2dee0 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/parameters.csv @@ -0,0 +1,15 @@ +ABREVIATION,INDEX,min,max MuSo6 +TRANSFERGROWTHP,11,0.1,1 +T_BASE,13,0,8 +WPM,25,0,0.1 +CN_leaf,26,14.3,58.8 +CWIC,49,0.01,0.07 +CLEC,50,0.3,0.8 +FLNR,56,0.1,0.2 +MSTOMACOND,58,0.001,0.007 +ROOTDEPTH,64,0.5,3 +ROOTDISTRIB,65,0.2,5 +RELSWCCRIT1,96,0.97,1 +RELSWCCRIT2,97,0.4,1 +SENESCENCABG,101,0,0.1 +SLA,137.60,10,60 diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/s.ini b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/s.ini new file mode 100644 index 0000000..b3bfa7f --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/examples/hhs/s.ini @@ -0,0 +1,147 @@ +BBGCMuSo simulation + +MET_INPUT +hhs.mtc43 (filename) met file name +4 (int) number of header lines in met file +365 (int) number of simdays in last simyear (truncated year: <= 365) + +RESTART +0 (flag) 1 = read restart; 0 = dont read restart +1 (flag) 1 = write restart; 0 = dont write restart +hhs_MuSo6.endpoint (filename) name of the input restart file +hhs_MuSo6.endpoint (filename) name of the output restart file + +TIME_DEFINE +54 (int) number of simulation years +1961 (int) first simulation year +1 (flag) 1 = spinup run; 0 = normal run +6000 (int) maximum number of spinup years + +CO2_CONTROL +1 (flag) 0=constant; 1=vary with file +290.0 (ppm) constant atmospheric CO2 concentration +CO2.txt (filename) name of the CO2 file + +NDEP_CONTROL +1 (flag) 0=constant; 1=vary with file +0.000200 (kgN/m2/yr) wet+dry atmospheric deposition of N +Ndep.txt (filename) name of the N-dep file + +SITE +248.0 (m) site elevation +46.95 (degrees) site latitude (- for S.Hem.) +0.20 (DIM) site shortwave albedo +9.00 (Celsius) mean annual air temperature +10.15 (Celsius) mean annual air temperature range +0.50 (prop.) proprortion of NH4 flux of N-deposition + +SOIL_FILE +hhs.soi (filename) SOIL filename + +EPC_FILE +c3grass_muso6.epc (filename) EPC filename + +MANAGEMENT_FILE +none (filename) MGM filename (or "none") + +SIMULATION_CONTROL +1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY) +1 (flag) vegper calculation method if MODEL PHENOLOGY is used (0: original, 1: GSI) +0 (flag) transferGDD flag (1= transfer calc. from GDD 0 = transfer calc. from EPC) +1 (flag) q10 flag (1 = temperature dependent q10 value; 0= constans q10 value) +1 (flag) acclimation flag of photosynthesis (1 = acclimation 0 = no acclimation) +1 (flag) acclimation flag of respiration (1 = acclimation 0 = no acclimation) +1 (flag) CO2 conductance reduction flag (0: no effect, 1: multiplier) +0 (flag) soil temperature calculation method (0: Zheng, 1: DSSAT) +1 (flag) soil hydrological calculation method (0: Richards, 1: tipping DSSAT) +0 (int) discretization level of soil hydr.calc.[Richards-method] (0: low, 1: medium, 2: high) +0 (flag) photosynthesis calculation method (0: Farquhar, 1: DSSAT) +0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor) +0 (flag) radiation calculation method (0: SWabs, 1: Rn) +0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand) + +W_STATE +0.0 (kg/m2) water stored in snowpack +1.0 (DIM) initial soil water as a proportion of field capacity + +CN_STATE +0.001 (kgC/m2) first-year maximum leaf carbon +0.001 (kgC/m2) first-year maximum fine root carbon +0.001 (kgC/m2) first-year maximum fruit carbon +0.001 (kgC/m2) first-year maximum softstem carbon +0.001 (kgC/m2) first-year maximum live woody stem carbon +0.001 (kgC/m2) first-year maximum live coarse root carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) coarse woody debris carbon +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, unshielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, shielded cellulose pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, lignin pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, fast microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, medium microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, slow microbial recycling pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, recalcitrant SOM (slowest) +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) litter nitrogen, labile pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NH4 pool +0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NO3 pool + +CLIM_CHANGE +0.0 (degC) - offset for Tmax +0.0 (degC) - offset for Tmin +1.0 (degC) - multiplier for PRCP +1.0 (degC) - multiplier for VPD +1.0 (degC) - multiplier for RAD + +CONDITIONAL_MANAGEMENT_STRATEGIES +0 (flag) conditional mowing ? 0 - no, 1 - yes +0.0 (m2/m2) fixed value of the LAI before MOWING +0.0 (m2/m2) fixed value of the LAI after MOWING +0.0 (%) transported part of plant material after MOWING +0 (flag) conditional irrigation? 0 - no, 1 - yes +0.0 (prop) SMSI before cond. IRRIGATION (-9999: SWCratio is used) +0.0 (prop) SWCratio of rootzone before cond. IRRIGATION (-9999: SMSI is used) +0.0 (prop) SWCratio of rootzone after cond. IRRIGATION +0.0 (kgH2O/m2) maximum amount of irrigated water + +OUTPUT_CONTROL +hhs_MuSo6_Spinup (filename) output prefix +0 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +2 (flag) writing annual output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) +1 (flag) for on-screen progress indicator + +DAILY_OUTPUT +12 number of daily output variables +2502 n_actphen +2603 vwc00-03cm +2604 vwc03-10cm +2605 vwc10-30cm +75 GDD +2636 rooting_depth +2716 m_soilstress +671 m_vegc_to_SNSC +171 evapotransp +3009 daily_gpp +3014 daily_tr +2520 proj_lai + +ANNUAL_OUTPUT +16 number of annual output variables +3000 annprcp +3001 anntavg +3002 annrunoff +3003 annoutflow +2734 annmax_lai +3031 cum_Closs_MGM +3032 cum_Cplus_MGM +3045 cum_Closs_SNSC +3046 cum_Cplus_STDB +3058 vegc +3064 totalc +3066 SOM_C_top30 +3070 SOM_C_30to60 +3071 SOM_C_60to90 +3068 NH4_top30 +3069 NO3_top30 + +END_INIT diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/help/AnIndex b/RBBGCMuso.Rcheck/RBBGCMuso/help/AnIndex new file mode 100644 index 0000000..000e912 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/help/AnIndex @@ -0,0 +1,56 @@ +alignData alignData +calibMuso calibMuso +calibrateMuso calibrateMuso +changemulline changemulline +checkFileSystem checkFileSystem +checkMeteoBGC checkMeteoBGC +cleanupMuso cleanupMuso +compareCalibratedWithOriginal compareCalibratedWithOriginal +compareMuso compareMuso +copyMusoExampleTo copyMusoExampleTo +corrigMuso corrigMuso +createSoilFile createSoilFile +dynRound dynRound +fextension fextension +flatMuso flatMuso +getAnnualOutputList getAnnualOutputList +getConstMatrix getConstMatrix +getDailyOutputList getDailyOutputList +getFilePath getFilePath +getFilesFromIni getFilesFromIni +getLogs getLogs +getOutFiles getOutFiles +getSoilDataFull getSoilDataFull +getyearlycum getyearlycum +getyearlymax getyearlymax +multiSiteCalib multiSiteCalib +multiSiteThread multiSiteThread +musoDate musoDate +musoGlue musoGlue +musoMapping musoMapping +musoMappingFind musoMappingFind +musoMonte musoMonte +musoQuickEffect musoQuickEffect +musoRand musoRand +musoSensi musoSensi +normalMuso normalMuso +numcut numcut +numcutall numcutall +optiMuso optiMuso +paramSweep paramSweep +plotMuso plotMuso +plotMusoWithData plotMusoWithData +postProcMuso postProcMuso +putOutVars putOutVars +randEpc randEpc +readErrors readErrors +readObservedData readObservedData +rungetMuso rungetMuso +runMuso runMuso +saveAllMusoPlots saveAllMusoPlots +setupMuso setupMuso +spinupMuso spinupMuso +stamp stamp +stampAndDir stampAndDir +supportedMuso supportedMuso +updateMusoMapping updateMusoMapping diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/help/RBBGCMuso.rdb b/RBBGCMuso.Rcheck/RBBGCMuso/help/RBBGCMuso.rdb new file mode 100644 index 0000000..5a0ee74 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/help/RBBGCMuso.rdb differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/help/RBBGCMuso.rdx b/RBBGCMuso.Rcheck/RBBGCMuso/help/RBBGCMuso.rdx new file mode 100644 index 0000000..e5e0720 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/help/RBBGCMuso.rdx differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/help/aliases.rds b/RBBGCMuso.Rcheck/RBBGCMuso/help/aliases.rds new file mode 100644 index 0000000..0239528 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/help/aliases.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/help/paths.rds b/RBBGCMuso.Rcheck/RBBGCMuso/help/paths.rds new file mode 100644 index 0000000..851b53a Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/help/paths.rds differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/html/00Index.html b/RBBGCMuso.Rcheck/RBBGCMuso/html/00Index.html new file mode 100644 index 0000000..94b5f56 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/html/00Index.html @@ -0,0 +1,116 @@ + + +R: An R package for BiomeBGC-MuSo ecosystem modelling + + + +
+

An R package for BiomeBGC-MuSo ecosystem modelling + +

+
+
+[Up] +[Top] +

Documentation for package ‘RBBGCMuso’ version 0.7.1

+ + + +

Help Pages

+ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
calibMusocalibMuso
calibrateMusocalibrateMuso
changemullinechangemulline
checkFileSystemcheckFileSystem
checkMeteoBGCcheckMeteoBGC
cleanupMusocleanupMuso
compareCalibratedWithOriginalcompareCalibratedWithOriginal
compareMusocompareMuso
copyMusoExampleTocopyMusoExampleTo
corrigMusocorrigMuso
createSoilFilecreateSoilFile
fextensionfextension
flatMusoflatMuso
getAnnualOutputListgetAnnualOutputList
getConstMatrixgetConstMatrix
getDailyOutputListgetDailyOutputList
getFilePathgetFilePath
getFilesFromInigetFilesFromIni
getSoilDataFullgetSoilDataFull
getyearlycumgetyearlycum
getyearlymaxgetyearlymax
multiSiteCalibmultiSiteCalib
multiSiteThreadmultiSiteThread
musoDatemusoDate
musoGluemusoGlue
musoMappingmusoMapping
musoMappingFindmusoMappingFind
musoMontemusoMonte
musoQuickEffectmusoQuickEffect
musoRandmusoRand
musoSensimusoSensi
normalMusonormalMuso
optiMusooptiMuso
paramSweepparamSweep
plotMusoplot the Biome-BGCMuSo output
plotMusoWithDataplot the Biome-BGCMuSo model output with observation data
randEpcrandEpc
readObservedDatareadMeasuredMuso
rungetMusorungetMuso
runMusorunMuso
saveAllMusoPlotssaveAllMusoPlots
setupMusosetupMuso
spinupMusoRuns the Biome-BGCMuSo model in spinup phase (execution of normal phase is possible with normalMuso) with debugging features.
supportedMusosupportedMuso
updateMusoMappingupdateMusoMapping
+
diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/html/R.css b/RBBGCMuso.Rcheck/RBBGCMuso/html/R.css new file mode 100644 index 0000000..2ef6cd6 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/html/R.css @@ -0,0 +1,120 @@ +@media screen { + .container { + padding-right: 10px; + padding-left: 10px; + margin-right: auto; + margin-left: auto; + max-width: 900px; + } +} + +.rimage img { /* from knitr - for examples and demos */ + width: 96%; + margin-left: 2%; +} + +.katex { font-size: 1.1em; } + +code { + color: inherit; + background: inherit; +} + +body { + line-height: 1.4; + background: white; + color: black; +} + +a:link { + background: white; + color: blue; +} + +a:visited { + background: white; + color: rgb(50%, 0%, 50%); +} + +h1 { + background: white; + color: rgb(55%, 55%, 55%); + font-family: monospace; + font-size: 1.4em; /* x-large; */ + text-align: center; +} + +h2 { + background: white; + color: rgb(40%, 40%, 40%); + font-family: monospace; + font-size: 1.2em; /* large; */ + text-align: center; +} + +h3 { + background: white; + color: rgb(40%, 40%, 40%); + font-family: monospace; + font-size: 1.2em; /* large; */ +} + +h4 { + background: white; + color: rgb(40%, 40%, 40%); + font-family: monospace; + font-style: italic; + font-size: 1.2em; /* large; */ +} + +h5 { + background: white; + color: rgb(40%, 40%, 40%); + font-family: monospace; +} + +h6 { + background: white; + color: rgb(40%, 40%, 40%); + font-family: monospace; + font-style: italic; +} + +img.toplogo { + width: 4em; + vertical-align: middle; +} + +img.arrow { + width: 30px; + height: 30px; + border: 0; +} + +span.acronym { + font-size: small; +} + +span.env { + font-family: monospace; +} + +span.file { + font-family: monospace; +} + +span.option{ + font-family: monospace; +} + +span.pkg { + font-weight: bold; +} + +span.samp{ + font-family: monospace; +} + +div.vignettes a:hover { + background: rgb(85%, 85%, 85%); +} diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/markdowns/parameterSweep.rmd b/RBBGCMuso.Rcheck/RBBGCMuso/markdowns/parameterSweep.rmd new file mode 100644 index 0000000..0651036 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/markdowns/parameterSweep.rmd @@ -0,0 +1,115 @@ +--- +title: "ParameterSweep" +auth or: "" +date: "`r format(Sys.time(), '%d %B, %Y')`" +output: html_document +--- + +```{r setup, include=FALSE} +knitr::opts_chunk$set(echo = TRUE) +``` + +```{r,echo=FALSE} +library("RBBGCMuso") + +quickAndDirty <- function(settings, parameters, inputDir= "./", outLoc, iterations=2, outVar=8,){ + + + + outLocPlain <- basename(outLoc) + currDir <- getwd() + inputDir <- normalizePath(inputDir) + tmp <- file.path(outLoc,"tmp/") + + if(!dir.exists(outLoc)){ + dir.create(outLoc) + warning(paste(outLoc," is not exists, so it was created")) + } + + if(dir.exists(tmp)){ + stop("There is a tmp directory inside the output location, please replace it. tmp is an important temporary directory for the function") + } + dir.create(tmp) + outLoc <- normalizePath(outLoc) + tmp <- normalizePath(tmp) + + inputFiles <- file.path(inputDir,grep(basename(outLoc),list.files(inputDir),invert = TRUE,value = TRUE)) + + + for(i in inputFiles){ + file.copy(i,tmp) + } + + setwd(tmp) + + if(is.null(settings)){ + settings <- setupMuso() + } + + + + file.copy(settings$epcInput[2],"epc-save",overwrite = TRUE) + calibrationPar <- matrix[,"INDEX"] + npar <- nrow(matrix) + paramMatrices <- list() + parameters <- matrix(nrow = npar,ncol = iterations) + paramtest <- parameters + rownames(paramtest) <- matrix[,1] + + for(i in 1:npar){ + parameters[i,] <- seq(from=matrix[i,5],to=matrix[i,6],length=iterations) + #print(parameters[i,]) + settings$calibrationPar <- calibrationPar[i] + for(j in 1:iterations){ + p <- try(calibMuso(settings,parameters =parameters[i,j],silent=TRUE)) + + if(length(p)>1){ + paramtest[i,j] <- max(p[,outVar]) + # print(paramtest) + } else { + paramtest[i,j] <- NA + # print(paramtest) + } + } + file.copy("epc-save",settings$epcInput[2],overwrite = TRUE) + } + + print("###################################################") + paramMatrices <- (function(){ + for(i in 1:nrow(paramtest)){ + matrx <- matrix(ncol = 2,nrow=iterations) + matrx[,1] <- parameters[i,] + matrx[,2] <- paramtest[i,] + paramMatrices[[i]] <- matrx + names(paramMatrices)[i] <- rownames(paramtest)[i] + } + return(paramMatrices) + })() + + + return(list(paramtest,paramMatrices)) + + +} + +``` + + +```{r, echo=FALSE,cache=TRUE} +parconstrains <- read.csv("parconstrains_extended.csv") +settings <- setupMuso() +parSeq<-quickAndDirty(settings = settings,matrix = parconstrains,outVar = 8,iterations = 5) +``` + +```{r} +parSeq +``` + +```{r,echo=FALSE} + parlist<-parSeq[[2]] + lparlist<-length(parlist) + for(i in 1:lparlist){ + title<-names(parlist)[i] + plot(x = parlist[[i]][,1], y= parlist[[i]][,2], ylim=c(0,15), main=title,ylab="LAI") + } +``` diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/markdowns/parameters.csv b/RBBGCMuso.Rcheck/RBBGCMuso/markdowns/parameters.csv new file mode 100644 index 0000000..6848451 --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/markdowns/parameters.csv @@ -0,0 +1,14 @@ +NAME,INDEX,MIN,MAX +BASETEMP,25,3,9 +WPM,36,0,0.1 +CN_lv,38,10,50 +CN_li,39,32,70 +CN_root,40,20,70 +CN_fruit,41,10.50,70 +CN_stem,42,0,70 +CLEC,55,0.4,0.8 +FLNR,61,0.05,0.8 +STOMA,63,0.003,0.015 +ROOTDEPTH,74,0.3,2. +SWCGERMIN,87,0.2,0.9 +NH4MOBILEPROP,120,0.05,0.7 diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/mtclim43 b/RBBGCMuso.Rcheck/RBBGCMuso/mtclim43 new file mode 100644 index 0000000..8c6f896 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/mtclim43 differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/mtclim43.exe b/RBBGCMuso.Rcheck/RBBGCMuso/mtclim43.exe new file mode 100644 index 0000000..43bf1c1 Binary files /dev/null and b/RBBGCMuso.Rcheck/RBBGCMuso/mtclim43.exe differ diff --git a/RBBGCMuso.Rcheck/RBBGCMuso/tests/test_postProcMuso.R b/RBBGCMuso.Rcheck/RBBGCMuso/tests/test_postProcMuso.R new file mode 100644 index 0000000..1234d0f --- /dev/null +++ b/RBBGCMuso.Rcheck/RBBGCMuso/tests/test_postProcMuso.R @@ -0,0 +1,21 @@ +context("Post processing") +library(testthat) +library(RBBGCMuso) +setwd(system.file("examples/hhs","",package = "RBBGCMuso")) + +test_that("Post processing string",{ + testMatrix1 <- data.frame(first = rep(1,5), second = rep(2,5), third = rep(3,5)) + testMatrix1c <- testMatrix1 + testMatrix1c[,"newCol"] <- testMatrix1c[,2] + 3 * testMatrix1c[,3] + expect_equal(postProcMuso(testMatrix1,"newCol <- @2 + 3*@3"),testMatrix1c) +}) + +test_that("calibMuso with postprocessing",{ + model <- calibMuso(skipSpinup = FALSE, silent = TRUE) + modelc<- model + newCol <- modelc[,1] + modelc<- cbind.data.frame(modelc,newCol) + modelc[,"newCol"]<- model[,5]+3*model[,7] + expect_equal(calibMuso(skipSpinup = FALSE,silent = TRUE, postProcString = "newCol <- @5 + 3* @7"), modelc) +}) + diff --git a/RBBGCMuso/DESCRIPTION b/RBBGCMuso/DESCRIPTION index 450f974..8007001 100644 --- a/RBBGCMuso/DESCRIPTION +++ b/RBBGCMuso/DESCRIPTION @@ -1,6 +1,6 @@ Package: RBBGCMuso -Title: An R package for BiomeBGC-MuSo ecosystem modelling -Version: 0.7.1 +Title: An R package for Biome-BGCMuSo ecosystem modelling +Version: 1.0.0 Authors@R: person("Roland", "Hollo's", , "hollorol@gmail.com", role = c("aut", "cre")) Description: What the package does (one paragraph). Depends: R (>= 3.3.2) @@ -22,6 +22,10 @@ Imports: rmarkdown, tibble, tidyr, + glue, + openxlsx, + jsonlite, + scales, tcltk, digest, jsonlite, @@ -36,10 +40,12 @@ Imports: Boruta, rpart, plotly, + shiny, rpart.plot Maintainer: Roland Hollo's -RoxygenNote: 7.2.3 Suggests: knitr, rmarkdown, VignetteBuilder: knitr ByteCompile: true +RoxygenNote: 7.2.3 +Encoding: UTF-8 diff --git a/RBBGCMuso/NAMESPACE b/RBBGCMuso/NAMESPACE index 355ad67..0919211 100644 --- a/RBBGCMuso/NAMESPACE +++ b/RBBGCMuso/NAMESPACE @@ -10,6 +10,7 @@ export(compareMuso) export(copyMusoExampleTo) export(corrigMuso) export(createSoilFile) +export(fixAlloc) export(flatMuso) export(genEpc) export(getAnnualOutputList) @@ -37,6 +38,7 @@ export(plotMuso) export(plotMusoWithData) export(randEpc) export(readObservedData) +export(readValuesFromFile) export(runMuso) export(rungetMuso) export(saveAllMusoPlots) diff --git a/RBBGCMuso/R/assistantFunctions.R b/RBBGCMuso/R/assistantFunctions.R index 5cc50af..ad32f2a 100644 --- a/RBBGCMuso/R/assistantFunctions.R +++ b/RBBGCMuso/R/assistantFunctions.R @@ -125,21 +125,32 @@ dynRound <- function(x,y,seqLen){ } -readValuesFromFile <- function(epc, linums){ - epcFile <- readLines(epc) +#' readValuesFromFile +#' +#' read Muso values from file +#' +#' @param filename The name of the +#' @usage readValuesFromFile(filename, linums) +#' @export + +readValuesFromFile <- function(filename, linums){ rows <- numeric(2) values <- sapply(linums, function(x){ rows[1] <- as.integer(x) rows[2] <- as.integer(round(100*x)) %% 10 + 1 - epcFile <- readLines(epc) - selRow <- unlist(strsplit(epcFile[rows[1]], split= "[\t ]")) + fromFile <- readLines(filename) + selRow <- unlist(strsplit(fromFile[rows[1]], split= "[\t ]")) selRow <- selRow[selRow!=""] - return(as.numeric(selRow[rows[2]])) - + ret <- suppressWarnings(as.numeric(selRow[rows[2]])) + if( is.na(ret) ){ + return(selRow[rows[2]]) + } + return(ret) }) return(values) } + #' readMeasuredMuso #' #' MuSo data reader diff --git a/RBBGCMuso/R/atStart.R b/RBBGCMuso/R/atStart.R index 4c35a70..df8ebc0 100644 --- a/RBBGCMuso/R/atStart.R +++ b/RBBGCMuso/R/atStart.R @@ -1,6 +1,18 @@ + +printback <- function(text,color){ + cat(sprintf("\033[%dm%s\033[0m\n",color,text)) +} +colorText <- function(text,color){ + sprintf("\033[%dm%s\033[0m",color,text) +} + .onLoad <- function(libname,pkgname){ - print("This is RBBGCMuso version 0.7") - RMuso_version <- 6 + RMuso_version <- 7 + cat(sprintf('This is RBBGCMuso version 1.0\nDefault Biome-BGCMuSo version: %d\n', + RMuso_version)) + cat(sprintf('For quick tutorial visit %s\n', colorText('https://github.com/hollorol/RBBGCMuso',104))) + cat(sprintf('For help, issue the command: %s\n',colorText('help(package="RBBGCMuso")',104))) + cat(sprintf('In order to get a sample simulation package use the %s command\n',colorText('copyMusoExampleTo()',104))) RMuso_constMatrix <- list(epc=NULL,soil=NULL) RMuso_varTable <- list() #___________________________ diff --git a/RBBGCMuso/R/calibMuso.R b/RBBGCMuso/R/calibMuso.R index f0826f7..7366f19 100644 --- a/RBBGCMuso/R/calibMuso.R +++ b/RBBGCMuso/R/calibMuso.R @@ -33,13 +33,21 @@ calibMuso <- function(settings=setupMuso(), calibrationPar=NULL, binaryPlace = "./", fileToChange = "epc", skipSpinup = TRUE, modifyOriginal = FALSE, prettyOut = FALSE, postProcString = NULL, - doBackup=TRUE + doBackup=TRUE, + backupDir="bck", + fixAlloc=FALSE ){ # ######################################################################## ###########################Set local variables and places############### ######################################################################## if(doBackup){ - file.copy(eval(parse(text = sprintf("settings$%sInput[2]", fileToChange))),file.path(settings$inputLoc),overwrite=FALSE) + for(epc in settings$epcInput){ + file.copy(epc, file.path(settings$inputLoc, backupDir), overwrite=FALSE) + } + + for(soi in settings$soilFile){ + file.copy(soi, file.path(settings$inputLoc, backupDir), overwrite=FALSE) + } } bck <- file.path(settings$inputLoc, "bck", @@ -121,6 +129,9 @@ calibMuso <- function(settings=setupMuso(), calibrationPar=NULL, } else { NULL }) + if(fixAlloc){ + fixAlloc(settings) + } # fileToChange = fileToChange,) } diff --git a/RBBGCMuso/R/calibrateMuso.R b/RBBGCMuso/R/calibrateMuso.R index 87a9ee5..6b6ef20 100644 --- a/RBBGCMuso/R/calibrateMuso.R +++ b/RBBGCMuso/R/calibrateMuso.R @@ -12,6 +12,7 @@ calibrateMuso <- function(measuredData, parameters =read.csv("parameters.csv", s skipSpinup = TRUE, plotName = "calib.jpg", modifyOriginal=TRUE, likelihood, uncertainity = NULL, naVal = NULL, postProcString = NULL, + sourceFile=NULL, # bases for musoRand if dependecy group is not fully defined by parameters.csv thread_prefix="thread", numCores = max(c(parallel::detectCores()-1,1)), pb = txtProgressBar(min=0, max=iterations, style=3), maxLikelihoodEpc=TRUE, pbUpdate = setTxtProgressBar, outputLoc="./", method="GLUE",lg = FALSE, w=NULL, ...){ @@ -44,6 +45,7 @@ calibrateMuso <- function(measuredData, parameters =read.csv("parameters.csv", s future({ tryCatch( musoSingleThread(measuredData, parameters, startDate, + sourceFile=settings$epc[2], # EPC SPECIFIC endDate, formatString, dataVar, outLoc, preTag, settings, @@ -52,6 +54,7 @@ calibrateMuso <- function(measuredData, parameters =read.csv("parameters.csv", s modifyOriginal, likelihood, uncertainity, naVal, postProcString, i) , error = function(e){ + # browser() writeLines(as.character(iterations),"progress.txt") }) @@ -127,6 +130,19 @@ calibrateMuso <- function(measuredData, parameters =read.csv("parameters.csv", s switch(method, "GLUE"={ musoGlue(results, parameters=parameters,settings=settings, w=w, lg=lg) + liks <- results[,sprintf("%s_likelihood",names(likelihood))] + epcIndexes <- future::value(fut[[1]], stdout = FALSE, signal=FALSE) + if(ncol(liks) == 1){ + ml_place <- which.max(liks) + } else { + ml_place <- which.max(as.matrix(liks) %*% as.matrix(w)) + } + epcVals <- results[ml_place,1:length(epcIndexes)] + epcPlace <- file.path(dirname(settings$inputFiles),settings$epc)[2] + changemulline(filePaths= epcPlace, epcIndexes, + epcVals, src =epcPlace,# settings$epcInput[2], + outFiles = file.path(outputLoc, "maxLikelihood_epc.epc")) + names(epcVals) <- epcIndexes }, "agromo"={ liks <- results[,sprintf("%s_likelihood",names(likelihood))] @@ -174,6 +190,7 @@ copyToThreadDirs <- function(prefix="thread", numcores=parallel::detectCores()-1 } musoSingleThread <- function(measuredData, parameters = NULL, startDate = NULL, + sourceFile=NULL, endDate = NULL, formatString = "%Y-%m-%d", dataVar, outLoc = "./calib", preTag = "cal-", settings = setupMuso(), @@ -234,10 +251,10 @@ musoSingleThread <- function(measuredData, parameters = NULL, startDate = NULL, ## row numbers print("optiMuso is randomizing the epc parameters now...",quote = FALSE) if(iterations < 3000){ - randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = 3000) - randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = 3000,sourceFile=sourceFile) + randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] # TODO: last not random } else { - randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations) + randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations,sourceFile=sourceFile) } origEpc <- readValuesFromFile(settings$epc[2],randVals[[1]]) diff --git a/RBBGCMuso/R/genEpc.R b/RBBGCMuso/R/genEpc.R index dd65ef2..ace59e1 100644 --- a/RBBGCMuso/R/genEpc.R +++ b/RBBGCMuso/R/genEpc.R @@ -29,7 +29,7 @@ randEpc <- function(parameterFile = "parameters.csv", location = "./epcDir", for(i in seq(iterations)){ epcOut <- gsub("\\.",paste0("-",i,"."),basename(sourceEpc)) changemulline(filePaths = basename(sourceEpc), calibrationPar = randVals[[1]], - contents = randVals[[2]][i,],fileOut = epcOut, fileToChange = "epc") + contents = randVals[[2]][i,],outFiles = epcOut) } setwd(currDir) } diff --git a/RBBGCMuso/R/multiSite.R b/RBBGCMuso/R/multiSite.R index 5627021..6013a4a 100644 --- a/RBBGCMuso/R/multiSite.R +++ b/RBBGCMuso/R/multiSite.R @@ -590,7 +590,7 @@ agroLikelihood <- function(modVector,measured){ #' compareCalibratedWithOriginal #' #' This functions compareses the likelihood and the RMSE values of the simulations and the measurements -#' @param key +#' @param key keyword compareCalibratedWithOriginal <- function(key, modOld, modNew, mes, likelihoods, alignIndexes, musoCodeToIndex, nameGroupTable, groupFun){ diff --git a/RBBGCMuso/R/musoMonte.R b/RBBGCMuso/R/musoMonte.R index d94abeb..5ce4756 100644 --- a/RBBGCMuso/R/musoMonte.R +++ b/RBBGCMuso/R/musoMonte.R @@ -18,6 +18,7 @@ musoMonte <- function(settings=NULL, parameters=NULL, + sourceFile=NULL, inputDir = "./", outLoc = "./calib", iterations = 10, @@ -100,7 +101,7 @@ musoMonte <- function(settings=NULL, ##reading the original epc file at the specified ## row numbers if(iterations < 3000){ - randVals <- musoRand(parameters = parameters,fileType="epc", iterations = 3000) + randVals <- musoRand(parameters = parameters,fileType="epc", iterations = 3000,sourceFile=sourceFile) randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),] } else { randVals <- musoRand(parameters = parameters,fileType="epc", iterations = iterations) diff --git a/RBBGCMuso/R/musoRand.R b/RBBGCMuso/R/musoRand.R index 1ed8c3a..9148af4 100644 --- a/RBBGCMuso/R/musoRand.R +++ b/RBBGCMuso/R/musoRand.R @@ -8,147 +8,182 @@ #' @importFrom limSolve xsample #' @export -musoRand <- function(parameters, iterations=3000, fileType="epc", constrains = NULL, burnin = NULL){ +musoRand <- function(parameters, iterations=3000, fileType="epc", sourceFile=NULL, constrains = NULL, burnin = NULL){ + if(is.null(constrains)){ constMatrix <- constrains constMatrix <- getOption("RMuso_constMatrix")[[fileType]][[as.character(getOption("RMuso_version"))]] } else { constMatrix <- constrains } - + parameters <- parameters[,-1] constMatrix <- constMatrix[,-1] - + depTableMaker <- function(constMatrix,parameters){ - # browser() parameters <- parameters[order(parameters[,1]),] ## BUG!!! selectedRows <- constMatrix[,"INDEX"] %in% parameters[,1] + # constMatrix[constMatrix[,"INDEX"] %in% parameters[,1],] rankList <- rank(constMatrix[selectedRows,2]) constMatrix[selectedRows,c(5,6)] <- parameters[rankList,c(2,3)] - logiConstrain <- (constMatrix[,"GROUP"] %in% constMatrix[constMatrix[,"INDEX"] %in% parameters[,1],"GROUP"] & - (constMatrix[,"GROUP"]!=0)) | ((constMatrix[,"INDEX"] %in% parameters[,1]) & (constMatrix[,"GROUP"] == 0)) - constMatrix <- constMatrix[logiConstrain,] - constMatrix <- constMatrix[order(apply(constMatrix[,7:8],1,function(x){x[1]/10+abs(x[2])})),] - constMatrix + + + + + + logiConstrain <- (constMatrix[,"GROUP"] %in% constMatrix[constMatrix[,"INDEX"] %in% parameters[,1],"GROUP"] & + (constMatrix[,"GROUP"]!=0)) | ((constMatrix[,"INDEX"] %in% parameters[,1]) & (constMatrix[,"GROUP"] == 0)) + constMatrix <- constMatrix[logiConstrain,] + constMatrix <- constMatrix[order(apply(constMatrix[,7:8],1,function(x){x[1]/10+abs(x[2])})),] + + + + paragroups <- unique(constMatrix[constMatrix[,"GROUP"] != 0,"GROUP"]) + missingMembers <- list() + for(group in paragroups){ + groupMembers <- constMatrix[constMatrix[,"GROUP"] == group,"INDEX"] + missingMemberElems <- groupMembers[is.na(match(groupMembers,parameters[,1]))] + if(length(missingMemberElems) > 0){ + missingMembers$indices <- c(missingMembers$indices, + match(missingMemberElems,constMatrix[,"INDEX"])) + if(is.null(sourceFile)){ + stop(sprintf("All group members of the group (%s) have to be in parameters if sourceFile not(epc file)",group)) + } + + missingMembers$values <- c(missingMembers$values, + suppressWarnings(readValuesFromFile(sourceFile,missingMemberElems))) + } + } + + list(depTable=constMatrix,missingMembers=missingMembers) } # browser() - genMat0 <- function(dep){ - numberOfVariable <- nrow(dep) - G <- rbind(diag(numberOfVariable), -1*diag(numberOfVariable)) - h <- c(dependences[,5], -1*dependences[,6]) - return(list(G=G,h=h)) + genMat0 <- function(dep, missingIndices){ + numberOfVariable <- nrow(dep) + if(length(missingMembers) != 0){ + dep <- dep[-missingIndices,] + } + G <- rbind(diag(numberOfVariable), -1*diag(numberOfVariable)) + h <- c(dependences[,5], -1*dependences[,6]) + return(list(G=G,h=h)) } genMat1 <- function(dep, N){ - ## Range <- sapply(list(min,max),function(x){ - ## x(as.numeric(rownames(dep))) - ## }) It is more elegant, more general, but slower - Range <- (function(x){ - c(min(x), max(x)) - })(as.numeric(dep[,"rowIndex"])) + ## Range <- sapply(list(min,max),function(x){ + ## x(as.numeric(rownames(dep))) + ## }) It is more elegant, more general, but slower + Range <- (function(x){ + c(min(x), max(x)) + })(as.numeric(dep[,"rowIndex"])) - numberOfVariables <- nrow(dep) - G<- -1*diag(numberOfVariables) + numberOfVariables <- nrow(dep) + G<- -1*diag(numberOfVariables) - for(i in 1:numberOfVariables){ - if(dep[i,4]!=0){ - G[i,dep[i,4]] <- 1 - } + for(i in 1:numberOfVariables){ + if(dep[i,4]!=0){ + G[i,dep[i,4]] <- 1 + } + + } + # browser() + G<-G[dep[,4]!=0,] - } -# browser() - G<-G[dep[,4]!=0,] - if(is.null(nrow(G))){ G<-t(as.matrix(G)) } numRowsInG <- nrow(G) - if(Range[1]==1){ - G<-cbind(G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0)) - } else{ - if(Range[2]==N){ - G<-cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G) - } else { - G <- cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0)) - } - } - return(list(G=-1*G,h=-1*rep(0,nrow(G)))) + if(Range[1]==1){ + G<-cbind(G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0)) + } else{ + if(Range[2]==N){ + G<-cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G) + } else { + G <- cbind(matrix(ncol=(Range[1]-1), + nrow=numRowsInG,data=0), + G, + matrix(ncol=(N-Range[2]), + nrow=numRowsInG,data=0)) + } + } + return(list(G=-1*G,h=-1*rep(0,nrow(G)))) } genMat2 <- function(dep, N){ - G <- rep(1,nrow(dep)) + G <- rep(1,nrow(dep)) - Range <- (function(x){ - c(min(x), max(x)) - })(as.numeric(dep[,"rowIndex"])) + Range <- (function(x){ + c(min(x), max(x)) + })(as.numeric(dep[,"rowIndex"])) - if(Range[1]==1){ - G<-c(G, numeric(N-Range[2])) - } else{ - if(Range[2]==N){ - G<-c(numeric(Range[1]-1), G) - } else { - G <- c(numeric(Range[1]-1), G, numeric(N-Range[2])) - } - } + if(Range[1]==1){ + G<-c(G, numeric(N-Range[2])) + } else{ + if(Range[2]==N){ + G<-c(numeric(Range[1]-1), G) + } else { + G <- c(numeric(Range[1]-1), G, numeric(N-Range[2])) + } + } - G <- t(matrix(sign(dep[2,4])*G)) - h <- abs(dep[1,4]) + G <- t(matrix(sign(dep[2,4])*G)) + h <- abs(dep[1,4]) if(dep[1,"TYPE"]==2){ # This is not needed, I'll have to remove the if part, and keep the content G <- G*(-1) h <- h*(-1) } - return(list(G=G,h=h)) + return(list(G=G,h=h)) } genMat3 <- function(dep, N){ - Range <- (function(x){ - c(min(x), max(x)) - })(as.numeric(dep[,"rowIndex"])) + Range <- (function(x){ + c(min(x), max(x)) + })(as.numeric(dep[,"rowIndex"])) - E <- rep(1,nrow(dep)) + E <- rep(1,nrow(dep)) - if(Range[1]==1){ - E<-c(E, numeric(N-Range[2])) - } else{ - if(Range[2]==N){ - E<-c(numeric(Range[1]-1), E) - } else { - E <- c(numeric(Range[1]-1), E, numeric(N-Range[2])) - } - } + if(Range[1]==1){ + E<-c(E, numeric(N-Range[2])) + } else{ + if(Range[2]==N){ + E<-c(numeric(Range[1]-1), E) + } else { + E <- c(numeric(Range[1]-1), E, numeric(N-Range[2])) + } + } - E <- t(matrix(E)) - f <- dep[1,4] - return(list(E=E,f=f)) + E <- t(matrix(E)) + f <- dep[1,4] + return(list(E=E,f=f)) } applyRandTypeG <- function(dep,N){ - type <- unique(dep[,"TYPE"]) - minR <- min(dep[,"rowIndex"]) - maxR <- max(dep[,"rowIndex"]) - switch(type, - invisible(Gh <- genMat1(dep, N)), - invisible(Gh <- genMat2(dep, N))) - return(Gh) + type <- unique(dep[,"TYPE"]) + minR <- min(dep[,"rowIndex"]) + maxR <- max(dep[,"rowIndex"]) + switch(type, + invisible(Gh <- genMat1(dep, N)), + invisible(Gh <- genMat2(dep, N))) + return(Gh) } applyRandTypeE <- function(dep,N){ - type <- unique(dep[,"TYPE"]) - minR <- min(dep[,"rowIndex"]) - maxR <- max(dep[,"rowIndex"]) - switch(-type, - stop("Not implemented yet"), - stop("Not implemented yet"), - invisible(Ef <- genMat3(dep, N))) - return(Ef) + type <- unique(dep[,"TYPE"]) + minR <- min(dep[,"rowIndex"]) + maxR <- max(dep[,"rowIndex"]) + switch(-type, + stop("Not implemented yet"), + stop("Not implemented yet"), + invisible(Ef <- genMat3(dep, N))) + return(Ef) } dependences <- depTableMaker(constMatrix, parameters) + missingMembers <- dependences$missingMembers + dependences <- dependences$depTable dependences <- cbind(dependences,1:nrow(dependences)) colnames(dependences)[ncol(dependences)] <- "rowIndex" # browser() @@ -167,21 +202,31 @@ musoRand <- function(parameters, iterations=3000, fileType="epc", constrains = N Ef[[i]] <- applyRandTypeE(splitedDeps[[i]],nrow(dependences)) } } - - Gh0<- genMat0(dependences) + + Gh0<- genMat0(dependences, missingMembers$indices) G <- do.call(rbind,lapply(Gh,function(x){x$G})) G<- rbind(Gh0$G,G) h <- do.call(c,lapply(Gh,function(x){x$h})) h <- c(Gh0$h,h) E <- do.call(rbind,lapply(Ef,function(x){x$E})) f <- do.call(c,lapply(Ef,function(x){x$f})) - # browser() + # browser() + if(length(missingMembers$indices)!=0){ + Ep <- matrix(data=0,ncol=numberOfVariable,nrow=length(missingMembers$indices)) + Ep[1:length(missingMembers$indices),missingMembers$indices] <- 1 + E <- rbind(E,Ep) + f <- c(f,missingMembers$values) + } + randVal <- suppressWarnings(limSolve::xsample(G=G,H=h,E=E,F=f,burninlength=burnin, iter = iterations))$X } else{ - Gh0<-genMat0(dependences) + Gh0<-genMat0(dependences,NULL) randVal <- suppressWarnings(xsample(G=Gh0$G,H=Gh0$h, iter = iterations))$X } - + if(length(missingMembers$indices)!=0){ + return(list(INDEX = dependences$INDEX[-missingMembers$indices], + randVal=randVal[,-missingMembers$indices])) + } results <- list(INDEX =dependences$INDEX, randVal=randVal) return(results) } diff --git a/RBBGCMuso/R/musoSensi.R b/RBBGCMuso/R/musoSensi.R index 4f4130b..33dec85 100644 --- a/RBBGCMuso/R/musoSensi.R +++ b/RBBGCMuso/R/musoSensi.R @@ -31,6 +31,7 @@ musoSensi <- function(monteCarloFile = NULL, plotTitle = "Sensitivity", skipSpinup = TRUE, skipZero = TRUE, + sourceFile=NULL, postProcString=NULL, modifyOut=TRUE, dpi=300){ @@ -87,6 +88,7 @@ musoSensi <- function(monteCarloFile = NULL, if(is.null(monteCarloFile)){ M <- musoMonte(parameters = parameters, settings = settings, + sourceFile=NULL, inputDir = inputDir, outLoc = outLoc, iterations = iterations, diff --git a/RBBGCMuso/R/musoTime.R b/RBBGCMuso/R/musoTime.R index 28cd2a9..d2f6974 100644 --- a/RBBGCMuso/R/musoTime.R +++ b/RBBGCMuso/R/musoTime.R @@ -2,12 +2,12 @@ #' #' This function generates MuSo compatibla dates for the data #' @author Roland HOLLOS -#' @param startYear -#' @param numYears -#' @param timestep -#' @param combined -#' @param corrigated -#' @param format +#' @param startYear Start year of the simulations +#' @param numYears Number of the years of the simulation +#' @param timestep timestep of date creation +#' @param combined using separate y m d columns or not? +#' @param corrigated If leapyear ... +#' @param format "the date format" #' @importFrom lubridate leap_year #' @export diff --git a/RBBGCMuso/R/normalMuso.R b/RBBGCMuso/R/normalMuso.R index db9e53c..4705cc4 100644 --- a/RBBGCMuso/R/normalMuso.R +++ b/RBBGCMuso/R/normalMuso.R @@ -90,9 +90,9 @@ normalMuso<- function(settings=NULL,parameters=NULL,timee="d",debugging=FALSE,lo if(!is.null(parameters)){ switch(fileToChange, - "epc" = tryCatch(changemulline(filename = epc[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R) + "epc" = tryCatch(changemulline(epc[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R) error = function (e) {stop("Cannot change the epc file")}), - "ini" = tryCatch(changemulline(filename = iniInput[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R) + "ini" = tryCatch(changemulline(iniInput[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R) error = function (e) {stop("Cannot change the ini file")}), "both" = (stop("This option is not implemented yet, please choose epc or ini")) ) diff --git a/RBBGCMuso/R/otherUsefullFunctions.R b/RBBGCMuso/R/otherUsefullFunctions.R index f70bdff..727bbad 100644 --- a/RBBGCMuso/R/otherUsefullFunctions.R +++ b/RBBGCMuso/R/otherUsefullFunctions.R @@ -183,3 +183,36 @@ return(randomNorm) getConstMatrix <- function (filetype="epc", version = as.character(getOption("RMuso_version"))) { getOption("RMuso_constMatrix")[[filetype]][[version]] } + + +#' fixAlloc +#' +#' Fix allocation parameter in the epc file +#' +#' @param settings the base RMuso settings variable +#' @param type normal or spinup depending what you want to modify +#' @usage ... +#' @export + +fixAlloc <- function(settings=NULL,type="normal"){ + if(is.null(settings)){ + settings <- setupMuso() + } + print("Need fix?") + epc_file <- settings$epcInput[type] + depTable <- options()$RMuso_constMatrix$epc[[as.character(options()$RMuso_version)]] + alloc_params<- depTable$INDEX[grep("ALLOCATION",depTable$NAME)] + alloc_groups <- round(100*(alloc_params - floor(alloc_params))) + tapply(alloc_params, alloc_groups, function(x){ + currentValues <- readValuesFromFile(epc_file,x) + difference <- 1 - sum(currentValues) + if(difference == 0){ + return(FALSE) + } + tomodiff <- currentValues[currentValues != 0] + changemulline(filePaths="c3grass_muso7.epc", + contents=(tomodiff + difference/length(tomodiff)), + calibrationPar=x[currentValues != 0]) + return(TRUE) + }) +} diff --git a/RBBGCMuso/R/outputMapping.R b/RBBGCMuso/R/outputMapping.R index 230afd0..a15fb9b 100644 --- a/RBBGCMuso/R/outputMapping.R +++ b/RBBGCMuso/R/outputMapping.R @@ -1,8 +1,8 @@ #' updateMusoMapping #' -#' This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variablesare marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order! +#' This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variables are marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order! #' @author Roland HOLLOS -#' @param excelName Name of the excelfile which contains the parameters +#' @param excelName Name of the Excel file which contains the parameters #' @importFrom openxlsx read.xlsx #' @importFrom jsonlite write_json #' @return The output code-variable matrix, and also the function changes the global variable @@ -10,36 +10,10 @@ updateMusoMapping <- function(excelName, dest="./", version=getOption("RMuso_version")){ - expandRangeRows <- function (ind) { - toExpand <- excelDF[ind,] - rangeString <- gsub(".*?(\\d*\\-\\d*).*","\\1",toExpand[2]) - interval <- as.numeric(strsplit(rangeString,split="-")[[1]]) - result <- do.call(rbind,lapply(interval[1]:interval[2],function(x){ - toExpand[2] <- x - toExpand[1] <- gsub("\\[.*?\\]",sprintf("_%s",(x-interval[1])),toExpand[1]) - toExpand - })) - result <- as.data.frame(result,stringsAsFactors = FALSE) - result[,2] <- as.numeric(result[,2]) - colnames(result) <- c("names","codes","units","descriptions") - result[,c(2,1,3,4)] - } - excelDF <- read.xlsx(excelName) excelDF <- excelDF[!is.na(excelDF[,2]),] - excelDF[,1] <- trimws(excelDF[,1]) - excelDF[,2] <- trimws(excelDF[,2]) - excelDF[,3] <- trimws(excelDF[,3]) - excelDF[,4] <- trimws(excelDF[,4]) - rangeRows <- grep("-",excelDF[,2]) - nonRangeMatrix <- excelDF[setdiff(1:nrow(excelDF),rangeRows),] - nonRangeMatrix[,2] <- as.numeric(nonRangeMatrix[,2]) - nonRangeMatrix[,1] <- trimws(nonRangeMatrix[,1]) - names(nonRangeMatrix) <- c("names","codes","units","descriptions") - outMatrix <- rbind.data.frame(do.call(rbind.data.frame,lapply(rangeRows,expandRangeRows)), - nonRangeMatrix[,c(2,1,3,4)]) - outMatrix <- outMatrix[order(outMatrix[,1]),] - rownames(outMatrix)<- NULL + outMatrix <- excelDF[,c(1,2,5,4)] + names(outMatrix) <- c("codes","names","units","descriptions") write_json(outMatrix, file.path(dest,sprintf("varTable%s.json",version)), pretty=TRUE) } diff --git a/RBBGCMuso/R/parametersweep.R b/RBBGCMuso/R/parametersweep.R index 398e89a..5e95ce4 100644 --- a/RBBGCMuso/R/parametersweep.R +++ b/RBBGCMuso/R/parametersweep.R @@ -17,8 +17,9 @@ paramSweep <- function(inputDir="./", parameters=NULL, outputDir=NULL, iterations=10, - outVar="daily_gpp", - htmlOutName = "paramsweep.html"){ + outVar="3009", + htmlOutName = "paramsweep.html", + fixAlloc=FALSE){ if(is.null(pandoc_version())){ stop("In order to use parameterSweep you have to have\n pandoc (1.12.3+) installed or run this function from Rstudio\n @@ -41,13 +42,16 @@ You can download pandoc from here: 'https://pandoc.org/',\n or Rstudio from here varNames <- musoMapping(outVar) outVarIndex<-outVar } + + if(file.exists("parameters.csv")){ + parameters <- read.csv("parameters.csv") + } - - if(is.null(parameters)){ + if(is.null(parameters) ){ parameters <- tcltk::tk_choose.files(caption = "Please select a file with the parameters and the ranges") } - rmdFile <- "---\ntitle: \"ParameterSweep basic\"\n---\n```{r setup, include=FALSE}\nknitr::opts_chunk$set(echo = TRUE)\n```\n```{r, echo=FALSE}\nsuppressWarnings(library(RBBGCMuso))\n```\n```{r, echo=FALSE}\nparameters <- read.csv(\"parameters.csv\")\n```\n```{r,fig.width=10, fig.height=3, echo=FALSE}\nnumPar\nfor(i in 1:numPar){\n suppressWarnings(musoQuickEffect(calibrationPar=parameters[i,2],startVal = parameters[i,3], endVal = parameters[i,4],\nnSteps = 9,\noutVar = \"daily_gpp\",\nparName = parameters[i,1]))\n}\n```" + rmdFile <- sprintf("---\ntitle: \"ParameterSweep basic\"\n---\n```{r setup, include=FALSE}\nknitr::opts_chunk$set(echo = TRUE)\n```\n```{r, echo=FALSE}\nsuppressWarnings(library(RBBGCMuso))\n```\n```{r, echo=FALSE}\nparameters <- read.csv(\"parameters.csv\")\n```\n```{r,fig.width=10, fig.height=3, echo=FALSE}\nnumPar\nfor(i in 1:numPar){\n suppressWarnings(musoQuickEffect(calibrationPar=parameters[i,2],startVal = parameters[i,3], endVal = parameters[i,4],\nnSteps = 9,\noutVar = \"daily_gpp\",\nparName = parameters[i,1],fixAlloc=%s))\n}\n```",fixAlloc) rmdVec <- unlist(strsplit(rmdFile,"\n")) rmdVec[11] <- paste0("parameters <- read.csv(\"",parameters,"\", stringsAsFactor = FALSE)") rmdVec[14] <- "numPar <- nrow(parameters)" diff --git a/RBBGCMuso/R/plotMuso.R b/RBBGCMuso/R/plotMuso.R index a6c6863..8dc9ba0 100644 --- a/RBBGCMuso/R/plotMuso.R +++ b/RBBGCMuso/R/plotMuso.R @@ -68,9 +68,9 @@ plotMuso <- function(settings = NULL, variable = "all", stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")}) colnames(Reva) <- unlist(settings$outputVars[[1]]) rownames(Reva) <- NULL - musoData <- cbind(musoDate(startYear = startYear,numYears = numberOfYears,combined = TRUE,corrigated=FALSE), + musoData <- cbind(musoDate(startYear = startYear,numYears = numberOfYears,combined = TRUE), rep(1:365,numberOfYears), - musoDate(startYear = startYear,numYears = numberOfYears,combined = FALSE,corrigated=FALSE),as.data.frame(Reva)) + musoDate(startYear = startYear,numYears = numberOfYears,combined = FALSE),as.data.frame(Reva)) colnames(musoData)[1:5]<-c("date","yearDay","year","day","month") musoData <-musoData %>% mutate(date=as.Date(as.character(date),"%d.%m.%Y")) diff --git a/RBBGCMuso/R/quickeffect.R b/RBBGCMuso/R/quickeffect.R index 3c1e2b5..677b14f 100644 --- a/RBBGCMuso/R/quickeffect.R +++ b/RBBGCMuso/R/quickeffect.R @@ -15,7 +15,7 @@ #' @importFrom tidyr separate #' @export -musoQuickEffect <- function(settings = setupMuso(), calibrationPar = NULL, startVal, endVal, nSteps = 1, fileToChange="epc",modifyOriginal=TRUE, outVar, parName = "parVal", yearNum=1, year=(settings$startYear + yearNum -1)){ +musoQuickEffect <- function(settings = setupMuso(), calibrationPar = NULL, startVal, endVal, nSteps = 1, fileToChange="epc",modifyOriginal=TRUE, outVar, parName = "parVal", yearNum=1, year=(settings$startYear + yearNum -1),fixAlloc=FALSE){ if(is.character(outVar)){ varNames <- as.data.frame(musoMappingFind(outVar)) @@ -45,7 +45,7 @@ musoQuickEffect <- function(settings = setupMuso(), calibrationPar = NULL, star parameters = parVal, outVars = outVarIndex, silent = TRUE, - fileToChange = fileToChange), error = function(e){NULL}) + fileToChange = fileToChange,fixAlloc=fixAlloc), error = function(e){NULL}) if(is.null(calResult)){ b <- cbind(rep(NA,365),parVal) rownames(b) <- musoDate(startYear = year, numYears = 1) diff --git a/RBBGCMuso/R/rungetMuso.R b/RBBGCMuso/R/rungetMuso.R index 07dbc84..4fa5e79 100644 --- a/RBBGCMuso/R/rungetMuso.R +++ b/RBBGCMuso/R/rungetMuso.R @@ -254,7 +254,7 @@ rungetMuso <- function(settings, timee="d", debugging=FALSE, logfilename=NULL, k Reva <- corrigMuso(settings,Reva) rownames(Reva) <- musoDate(settings$startYear, settings$numYears) } else { - rownames(Reva) <- musoDate(settings$startYear, settings$numYears, corrigated=FALSE) + rownames(Reva) <- musoDate(settings$startYear, settings$numYears) # TODO: Need fix } if(export!=FALSE){ diff --git a/RBBGCMuso/R/setupMuso.R b/RBBGCMuso/R/setupMuso.R index ef50220..15892b1 100644 --- a/RBBGCMuso/R/setupMuso.R +++ b/RBBGCMuso/R/setupMuso.R @@ -16,7 +16,7 @@ #' @param grazInput Via the grazInput parameter, the user can specify the location of the file that contains the grazing information. By default the package reads this information from the INI files. #' @param harvInput Via the harvInput parameter, the user can specify the location of the file that contains the harvesting information. By default the package reads this information from the INI files. #' @param plougInput Via the plougInput parameter, the user can specify the location of the file that contains the ploughing information. By default the package reads this information from the INI files. -#' @param fertInput Via the fertInput parameter, ythe user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files. +#' @param fertInput Via the fertInput parameter, the user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files. #' @param irrInput Via the irrInput parameter, the user can specify the location of the file that contains the irrigation information. By default the package reads this information from the INI files. #' @param nitInput Via the nitInput parameter, the user can specify the location of the file that contains the nitrogen deposition data. By default the package reads this information from the INI files. #' @param iniInput Via the iniInput parameter, the user can specify the location of the INI files. By default the package reads the INI files from the working directory. diff --git a/RBBGCMuso/R/soilQuery.R b/RBBGCMuso/R/soilQuery.R index 6c4e189..02476fe 100644 --- a/RBBGCMuso/R/soilQuery.R +++ b/RBBGCMuso/R/soilQuery.R @@ -9,7 +9,7 @@ getSoilDataFull <- function(lat, lon, apiURL) { if(missing(apiURL)){ - apiURL <- "https://81.169.232.36" + apiURL <- "https://rest.isric.org/soilgrids/v2.0/properties" } apiString <- glue("{apiURL}/query?lon={lon}&lat={lat}") soilREST <- #with_config(config(ssl_verifypeer=0L, ssl_verifyhost=0L), @@ -31,9 +31,9 @@ getSoilDataFull <- function(lat, lon, apiURL) { createSoilFile <- function(lat,lon, outputFile="recent.soi", method="constant",apiURL, - template=system.file("examples/hhs/hhs.soi",package="RBBGCMuso")) { + template=system.file("examples/hhs/hhs_MuSo7.soi",package="RBBGCMuso")) { if(missing(apiURL)){ - apiURL <- "https://rest.soilgrids.org/soilgrids/v2.0/properties" + apiURL <- "https://rest.isric.org/soilgrids/v2.0/properties" } outFile <- suppressWarnings(readLines(template)) outFile[1] <- sprintf("SOILPROP FILE - lat: %s, lon: %s, created in: %s",lat,lon,date()) @@ -50,11 +50,11 @@ createSoilFile <- function(lat,lon, } soilDepth <- tryCatch(getMeanSoil(rest,"bdod")/100,error=function(e){stop("There is no data for the given coordinates")}) - outFile[55] <- sprintf("%s (%%) percentage of sand by volume in rock free soil", + outFile[90] <- sprintf("%s (%%) percentage of sand by volume in rock free soil", paste(createMusoLayers(getMeanSoil(rest,"sand")/10), collapse="\t")) - outFile[56] <- sprintf("%s (%%) percentage of silt by volume in rock free soil", + outFile[91] <- sprintf("%s (%%) percentage of silt by volume in rock free soil", paste(createMusoLayers(getMeanSoil(rest,"silt")/10), collapse="\t")) - outFile[57] <- sprintf("%s (dimless) soil PH", + outFile[92] <- sprintf("%s (dimless) soil PH", paste(createMusoLayers(getMeanSoil(rest,"phh2o")/10), collapse="\t")) # outFile[58] <- sprintf("%s (%%) bulk density",paste(createMusoLayers(soilDepth),collapse="\t")) writeLines(outFile,outputFile) diff --git a/RBBGCMuso/R/spinupMuso.R b/RBBGCMuso/R/spinupMuso.R index 3392c97..a867e68 100644 --- a/RBBGCMuso/R/spinupMuso.R +++ b/RBBGCMuso/R/spinupMuso.R @@ -52,9 +52,9 @@ spinupMuso <- function(settings=NULL, parameters=NULL, debugging=FALSE, logfilen if(!is.null(parameters)){ switch(fileToChange, - "epc" = tryCatch(changemulline(filename = epc[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R) + "epc" = tryCatch(changemulline(filePaths = epc[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R) error = function (e) {stop("Cannot change the epc file")}), - "ini" = tryCatch(changemulline(filename = iniInput[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R) + "ini" = tryCatch(changemulline(filePaths = iniInput[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R) error = function (e) {stop("Cannot change the ini file")}), "both" = (stop("This option is not implemented yet, please choose epc or ini")) ) diff --git a/RBBGCMuso/R/tuner.R b/RBBGCMuso/R/tuner.R index 62336bb..8ce54c2 100644 --- a/RBBGCMuso/R/tuner.R +++ b/RBBGCMuso/R/tuner.R @@ -1,6 +1,6 @@ #' tuneMusoUI #' -#' This is a simple parameter tuner function which works great in a flat directory systemj +#' This is a simple parameter tuner function which works great in a flat directory system #' #' @param parameterFile optional, the parameter csv file #' @importFrom plotly plotlyOutput diff --git a/RBBGCMuso/inst/data/depTree.csv b/RBBGCMuso/inst/data/depTree.csv index afa513a..c3c6fbb 100644 --- a/RBBGCMuso/inst/data/depTree.csv +++ b/RBBGCMuso/inst/data/depTree.csv @@ -15,4 +15,6 @@ "cul","mgm",1,"cultivation" "frz","mgm",1,"fertilization" "irr","mgm",1,"irrigation" +"mul","mgm",1,"mulching" +"cwe","mgm",1,"cwdextract" "epc","plt",0,"plantEpc" diff --git a/RBBGCMuso/inst/data/epcConstMatrix7.json b/RBBGCMuso/inst/data/epcConstMatrix7.json new file mode 100644 index 0000000..d7b5510 --- /dev/null +++ b/RBBGCMuso/inst/data/epcConstMatrix7.json @@ -0,0 +1,2017 @@ +[ + { + "X": 1, + "NAME": "yearday to start new growth", + "INDEX": 9, + "UNIT": "yday", + "MIN": 0, + "MAX": 364, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 2, + "NAME": "yearday to end new growth", + "INDEX": 10, + "UNIT": "yday", + "MIN": 0, + "MAX": 364, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 3, + "NAME": "transfer growth period as fraction of growing season", + "INDEX": 11, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 4, + "NAME": "litterfall as fraction of growing season", + "INDEX": 12, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 5, + "NAME": "base temperature", + "INDEX": 13, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 12, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 6, + "NAME": "minimum temperature for growth displayed on current day", + "INDEX": 14, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 0, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 7, + "NAME": "optimal1 temperature for growth displayed on current day", + "INDEX": 15, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 1, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 8, + "NAME": "optimal2 temperature for growth displayed on current day", + "INDEX": 16, + "UNIT": "Celsius", + "MIN": 20, + "MAX": 40, + "DEPENDENCE": 2, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 9, + "NAME": "maxmimum temperature for growth displayed on current day", + "INDEX": 17, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 3, + "GROUP": 1, + "TYPE": 1 + }, + { + "X": 10, + "NAME": "minimum temperature for carbon assimilation displayed on current day", + "INDEX": 18, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 0, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 11, + "NAME": "optimal1 temperature for carbon assimilation displayed on current day", + "INDEX": 19, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 1, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 12, + "NAME": "optimal2 temperature for carbon assimilation displayed on current day", + "INDEX": 20, + "UNIT": "Celsius", + "MIN": 20, + "MAX": 40, + "DEPENDENCE": 2, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 13, + "NAME": "maxmimum temperature for carbon assimilation displayed on current day", + "INDEX": 21, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 3, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 14, + "NAME": "threshold temperature for ET-calculation for the PT method", + "INDEX": 22, + "UNIT": "Celsiusr", + "MIN": 0, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 15, + "NAME": "annual leaf and fine root turnover fraction", + "INDEX": 23, + "UNIT": "1/yr", + "MIN": 0.1, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 16, + "NAME": "annual live wood turnover fraction", + "INDEX": 24, + "UNIT": "1/yr", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 17, + "NAME": "annual fire mortality fraction", + "INDEX": 25, + "UNIT": "1/yr", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 18, + "NAME": "whole-plant mortality paramter for vegetation period", + "INDEX": 26, + "UNIT": "1/vegper", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 19, + "NAME": "dead stem biomass combustion proportion", + "INDEX": 27, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 20, + "NAME": "coarse woody biomass combustion proportion", + "INDEX": 28, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 21, + "NAME": "C:N of leaves", + "INDEX": 29, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 100, + "DEPENDENCE": 0, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 22, + "NAME": "C:N of leaf litter", + "INDEX": 30, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 23, + "NAME": "C:N of fine roots", + "INDEX": 31, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 24, + "NAME": "C:N of fruit", + "INDEX": 32, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 25, + "NAME": "C:N of softstem", + "INDEX": 33, + "UNIT": "kgC/kgN", + "MIN": 10, + "MAX": 60, + "DEPENDENCE": 1, + "GROUP": 3, + "TYPE": 1 + }, + { + "X": 26, + "NAME": "C:N of live wood", + "INDEX": 34, + "UNIT": "kgC/kgN", + "MIN": 50, + "MAX": 100, + "DEPENDENCE": 0, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 27, + "NAME": "C:N of dead wood", + "INDEX": 35, + "UNIT": "kgC/kgN", + "MIN": 300, + "MAX": 800, + "DEPENDENCE": 1, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 28, + "NAME": "dry matter content of leaves", + "INDEX": 36, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 29, + "NAME": "dry matter content of leaf litter", + "INDEX": 37, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 30, + "NAME": "dry matter content of fine roots", + "INDEX": 38, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 31, + "NAME": "dry matter content of fruit", + "INDEX": 39, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 32, + "NAME": "dry matter content of softstem", + "INDEX": 40, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 33, + "NAME": "dry matter content of live wood", + "INDEX": 41, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 34, + "NAME": "dry matter content of dead wood", + "INDEX": 42, + "UNIT": "kgC/kgDM", + "MIN": 0.2, + "MAX": 0.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 35, + "NAME": "leaf litter labile proportion", + "INDEX": 43, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 36, + "NAME": "leaf litter cellulose proportion", + "INDEX": 44, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 37, + "NAME": "fine root labile proportion", + "INDEX": 45, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 6, + "TYPE": 2 + }, + { + "X": 38, + "NAME": "fine root cellulose proportion", + "INDEX": 46, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 6, + "TYPE": 2 + }, + { + "X": 39, + "NAME": "fruit labile proportion", + "INDEX": 47, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 40, + "NAME": "fruit cellulose proportion", + "INDEX": 48, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 41, + "NAME": "softstem labile proportion", + "INDEX": 49, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 8, + "TYPE": 2 + }, + { + "X": 42, + "NAME": "softstem cellulose proportion", + "INDEX": 50, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.6, + "DEPENDENCE": 1, + "GROUP": 8, + "TYPE": 2 + }, + { + "X": 43, + "NAME": "dead wood cellulose proportion", + "INDEX": 51, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 0.9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "canopy water interception coefficient", + "INDEX": 52, + "UNIT": "1/LAI/d", + "MIN": 0.01, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 45, + "NAME": "canopy light extinction coefficient", + "INDEX": 53, + "UNIT": "dimless", + "MIN": 0.2, + "MAX": 0.8, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 46, + "NAME": "potential radiation use efficiency", + "INDEX": 54, + "UNIT": "g/MJ", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "radiation parameter1 (Jiang et al.2015)", + "INDEX": 55, + "UNIT": "dimless", + "MIN": 0.781, + "MAX": 0.781, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "radiation parameter1 (Jiang et al.2015)", + "INDEX": 56, + "UNIT": "dimless", + "MIN": -13.596, + "MAX": -13.596, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 49, + "NAME": "all-sided to projected leaf area ratio", + "INDEX": 57, + "UNIT": "dimless", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 50, + "NAME": "ratio of shaded SLA:sunlit SLA", + "INDEX": 58, + "UNIT": "dimless", + "MIN": 2, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 51, + "NAME": "fraction of leaf N in Rubisco", + "INDEX": 59, + "UNIT": "dimless", + "MIN": 0.01, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 52, + "NAME": "fraction of leaf N in PeP", + "INDEX": 60, + "UNIT": "dimless", + "MIN": 0.0424, + "MAX": 0.0424, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "maximum stomatal conductance", + "INDEX": 61, + "UNIT": "m/s", + "MIN": 0.001, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 54, + "NAME": "cuticular conductance", + "INDEX": 62, + "UNIT": "m/s", + "MIN": 1e-05, + "MAX": 0.0001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 55, + "NAME": "boundary layer conductance", + "INDEX": 63, + "UNIT": "m/s", + "MIN": 0.01, + "MAX": 0.09, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 56, + "NAME": "maximum height of plant", + "INDEX": 64, + "UNIT": "m", + "MIN": 0.1, + "MAX": 30, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 57, + "NAME": "stem weight corresponding to maximum height", + "INDEX": 65, + "UNIT": "kgC", + "MIN": 0.1, + "MAX": 100, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 58, + "NAME": "plant height function shape parameter (slope)", + "INDEX": 66, + "UNIT": "dimless", + "MIN": 0.5, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 59, + "NAME": "maximum depth of rooting zone", + "INDEX": 67, + "UNIT": "m", + "MIN": 0.1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 60, + "NAME": "root distribution parameter", + "INDEX": 68, + "UNIT": "prop", + "MIN": 3.67, + "MAX": 3.67, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 61, + "NAME": "root weight corresponding to max root depth", + "INDEX": 69, + "UNIT": "kgC/m2", + "MIN": 0.4, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 62, + "NAME": "root depth function shape parameter (slope)", + "INDEX": 70, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 63, + "NAME": "root weight to rooth length conversion factor", + "INDEX": 71, + "UNIT": "m/kg", + "MIN": 1000, + "MAX": 1000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 64, + "NAME": "growth resp per unit of C grown", + "INDEX": 72, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 65, + "NAME": "maintenance respiration in kgC/day per kg of tissue N", + "INDEX": 73, + "UNIT": "kgC/kgN/d", + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 66, + "NAME": "theoretical maximum prop. of non-structural and structural carbohydrates", + "INDEX": 74, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 67, + "NAME": "prop. of non-structural carbohydrates available for maintanance resp", + "INDEX": 75, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 68, + "NAME": "symbiotic+asymbiotic fixation of N", + "INDEX": 76, + "UNIT": "kgN/m2/yr", + "MIN": 0, + "MAX": 0.001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 69, + "NAME": "time delay for temperature in photosynthesis acclimation", + "INDEX": 77, + "UNIT": "day", + "MIN": 0, + "MAX": 50, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 70, + "NAME": "critical VWCratio (prop. to FC-WP) in germination", + "INDEX": 82, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 71, + "NAME": "critical photoslow daylength", + "INDEX": 84, + "UNIT": "hour", + "MIN": 14, + "MAX": 18, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 72, + "NAME": "slope of relative photoslow development rate", + "INDEX": 85, + "UNIT": "dimless", + "MIN": 0.005, + "MAX": 0.005, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 73, + "NAME": "critical vernalization temperature 1", + "INDEX": 87, + "UNIT": "Celsius", + "MIN": -5, + "MAX": 5, + "DEPENDENCE": 0, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 74, + "NAME": "critical vernalization temperature 2", + "INDEX": 88, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 1, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 75, + "NAME": "critical vernalization temperature 3", + "INDEX": 89, + "UNIT": "Celsius", + "MIN": 5, + "MAX": 15, + "DEPENDENCE": 2, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 76, + "NAME": "critical vernalization temperature 4", + "INDEX": 90, + "UNIT": "Celsius", + "MIN": 10, + "MAX": 20, + "DEPENDENCE": 3, + "GROUP": 9, + "TYPE": 1 + }, + { + "X": 77, + "NAME": "slope of relative vernalization development rate", + "INDEX": 91, + "UNIT": "dimless", + "MIN": 0.04, + "MAX": 0.04, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 78, + "NAME": "required vernalization days (in vernalization development rate)", + "INDEX": 92, + "UNIT": "dimless", + "MIN": 30, + "MAX": 70, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 79, + "NAME": "critical flowering heat stress temperature 1", + "INDEX": 94, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 40, + "DEPENDENCE": 0, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 80, + "NAME": "critical flowering heat stress temperature 2", + "INDEX": 95, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "DEPENDENCE": 1, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 81, + "NAME": "theoretical maximum of flowering thermal stress mortality", + "INDEX": 96, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.4, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 82, + "NAME": "VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)", + "INDEX": 99, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 83, + "NAME": "VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)", + "INDEX": 100, + "UNIT": "prop", + "MIN": 0.5, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 84, + "NAME": "minimum of soil moisture limit2 multiplicator (full anoxic stress value)", + "INDEX": 101, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 85, + "NAME": "vapor pressure deficit: start of conductance reduction", + "INDEX": 102, + "UNIT": "Pa", + "MIN": 500, + "MAX": 1500, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 86, + "NAME": "vapor pressure deficit: complete conductance reduction", + "INDEX": 103, + "UNIT": "Pa", + "MIN": 1500, + "MAX": 3500, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 87, + "NAME": "maximum senescence mortality coefficient of aboveground plant material", + "INDEX": 104, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "DEPENDENCE": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 88, + "NAME": "maximum senescence mortality coefficient of belowground plant material", + "INDEX": 105, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "DEPENDENCE": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 89, + "NAME": "maximum senescence mortality coefficient of non-structured plant material", + "INDEX": 106, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 90, + "NAME": "lower limit extreme high temperature effect on senescence mortality", + "INDEX": 107, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 91, + "NAME": "upper limit extreme high temperature effect on senescence mortality", + "INDEX": 108, + "UNIT": "Celsius", + "MIN": 30, + "MAX": 50, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 92, + "NAME": "turnover rate of wilted standing biomass to litter", + "INDEX": 109, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 93, + "NAME": "turnover rate of cut-down non-woody biomass to litter", + "INDEX": 110, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 94, + "NAME": "turnover rate of cut-down woody biomass to litter", + "INDEX": 111, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 95, + "NAME": "drought tolerance parameter (critical value of day since water stress)", + "INDEX": 112, + "UNIT": "n_day", + "MIN": 0, + "MAX": 100, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 96, + "NAME": "effect of soilstress factor on photosynthesis", + "INDEX": 113, + "UNIT": "dimless", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 97, + "NAME": "crit. amount of snow limiting photosyn.", + "INDEX": 116, + "UNIT": "kg/m2", + "MIN": 0, + "MAX": 20, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 98, + "NAME": "limit1 (under:full constrained) of HEATSUM index", + "INDEX": 117, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 50, + "DEPENDENCE": 0, + "GROUP": 11, + "TYPE": 1 + }, + { + "X": 99, + "NAME": "limit2 (above:unconstrained) of HEATSUM index", + "INDEX": 118, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 100, + "DEPENDENCE": 1, + "GROUP": 11, + "TYPE": 1 + }, + { + "X": 100, + "NAME": "limit1 (under:full constrained) of TMIN index", + "INDEX": 119, + "UNIT": "Celsius", + "MIN": -5, + "MAX": 5, + "DEPENDENCE": 0, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 101, + "NAME": "limit2 (above:unconstrained) of TMIN index", + "INDEX": 120, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10, + "DEPENDENCE": 1, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 102, + "NAME": "limit1 (above:full constrained) of VPD index", + "INDEX": 121, + "UNIT": "Pa", + "MIN": 2000, + "MAX": 600, + "DEPENDENCE": 0, + "GROUP": 13, + "TYPE": 1 + }, + { + "X": 103, + "NAME": "limit2 (under:unconstrained) of VPD index", + "INDEX": 122, + "UNIT": "Pa", + "MIN": 500, + "MAX": 1500, + "DEPENDENCE": 1, + "GROUP": 13, + "TYPE": 1 + }, + { + "X": 104, + "NAME": "limit1 (under:full constrained) of DAYLENGTH index", + "INDEX": 123, + "UNIT": "s", + "MIN": 0, + "MAX": 0, + "DEPENDENCE": 0, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 105, + "NAME": "limit2 (above:unconstrained) of DAYLENGTH index", + "INDEX": 124, + "UNIT": "s", + "MIN": 0, + "MAX": 0, + "DEPENDENCE": 1, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 106, + "NAME": "moving average (to avoid the effects of extreme events)", + "INDEX": 125, + "UNIT": "n_day", + "MIN": 2, + "MAX": 20, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 107, + "NAME": "GSI limit1 (greater that limit -> start of vegper)", + "INDEX": 126, + "UNIT": "dimless", + "MIN": 0, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 108, + "NAME": "GSI limit2 (less that limit -> end of vegper)", + "INDEX": 127, + "UNIT": "dimless", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 109, + "NAME": "length of phenophase (GDD)-0", + "INDEX": 131.6, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 110, + "NAME": "leaf ALLOCATION -0", + "INDEX": 132.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 111, + "NAME": "fine root ALLOCATION-0", + "INDEX": 133.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 112, + "NAME": "fruit ALLOCATION -0", + "INDEX": 134.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 113, + "NAME": "soft stem ALLOCATION-0", + "INDEX": 135.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 114, + "NAME": "live woody stem ALLOCATION -0", + "INDEX": 136.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 115, + "NAME": "dead woody stem ALLOCATION -0", + "INDEX": 137.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 116, + "NAME": "live coarse root ALLOCATION-0", + "INDEX": 138.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 117, + "NAME": "dead coarse root ALLOCATION -0", + "INDEX": 139.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 15, + "TYPE": -3 + }, + { + "X": 118, + "NAME": "canopy average specific leaf area-0", + "INDEX": 140.6, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 119, + "NAME": "current growth proportion-0", + "INDEX": 141.6, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 120, + "NAME": "maximal lifetime of plant tissue-0", + "INDEX": 142.6, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 121, + "NAME": "length of phenophase (GDD)-1", + "INDEX": 131.61, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 122, + "NAME": "leaf ALLOCATION -1", + "INDEX": 132.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 123, + "NAME": "fine root ALLOCATION-1", + "INDEX": 133.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 124, + "NAME": "fruit ALLOCATION -1", + "INDEX": 134.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 125, + "NAME": "soft stem ALLOCATION-1", + "INDEX": 135.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 126, + "NAME": "live woody stem ALLOCATION -1", + "INDEX": 136.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 127, + "NAME": "dead woody stem ALLOCATION -1", + "INDEX": 137.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 128, + "NAME": "live coarse root ALLOCATION-1", + "INDEX": 138.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 129, + "NAME": "dead coarse root ALLOCATION -1", + "INDEX": 139.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 16, + "TYPE": -3 + }, + { + "X": 130, + "NAME": "canopy average specific leaf area-1", + "INDEX": 140.61, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 131, + "NAME": "current growth proportion-1", + "INDEX": 141.61, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 132, + "NAME": "maximal lifetime of plant tissue-1", + "INDEX": 142.61, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 133, + "NAME": "length of phenophase (GDD)-2", + "INDEX": 131.62, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 134, + "NAME": "leaf ALLOCATION -2", + "INDEX": 132.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 135, + "NAME": "fine root ALLOCATION-2", + "INDEX": 133.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 136, + "NAME": "fruit ALLOCATION -2", + "INDEX": 134.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 137, + "NAME": "soft stem ALLOCATION-2", + "INDEX": 135.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 138, + "NAME": "live woody stem ALLOCATION -2", + "INDEX": 136.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 139, + "NAME": "dead woody stem ALLOCATION -2", + "INDEX": 137.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 140, + "NAME": "live coarse root ALLOCATION-2", + "INDEX": 138.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 141, + "NAME": "dead coarse root ALLOCATION -2", + "INDEX": 139.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 17, + "TYPE": -3 + }, + { + "X": 142, + "NAME": "canopy average specific leaf area-2", + "INDEX": 140.62, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 143, + "NAME": "current growth proportion-2", + "INDEX": 141.62, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 144, + "NAME": "maximal lifetime of plant tissue-2", + "INDEX": 142.62, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 145, + "NAME": "length of phenophase (GDD)-3", + "INDEX": 131.63, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 146, + "NAME": "leaf ALLOCATION -3", + "INDEX": 132.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 147, + "NAME": "fine root ALLOCATION-3", + "INDEX": 133.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 148, + "NAME": "fruit ALLOCATION -3", + "INDEX": 134.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 149, + "NAME": "soft stem ALLOCATION-3", + "INDEX": 135.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 150, + "NAME": "live woody stem ALLOCATION -3", + "INDEX": 136.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 151, + "NAME": "dead woody stem ALLOCATION -3", + "INDEX": 137.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 152, + "NAME": "live coarse root ALLOCATION-3", + "INDEX": 138.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 153, + "NAME": "dead coarse root ALLOCATION -3", + "INDEX": 139.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 18, + "TYPE": -3 + }, + { + "X": 154, + "NAME": "canopy average specific leaf area-3", + "INDEX": 140.63, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 155, + "NAME": "current growth proportion-3", + "INDEX": 141.63, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 156, + "NAME": "maximal lifetime of plant tissue-3", + "INDEX": 142.63, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 157, + "NAME": "length of phenophase (GDD)-4", + "INDEX": 131.64, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 158, + "NAME": "leaf ALLOCATION -4", + "INDEX": 132.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 159, + "NAME": "fine root ALLOCATION-4", + "INDEX": 133.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 160, + "NAME": "fruit ALLOCATION -4", + "INDEX": 134.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 161, + "NAME": "soft stem ALLOCATION-4", + "INDEX": 135.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 162, + "NAME": "live woody stem ALLOCATION -4", + "INDEX": 136.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 163, + "NAME": "dead woody stem ALLOCATION -4", + "INDEX": 137.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 164, + "NAME": "live coarse root ALLOCATION-4", + "INDEX": 138.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 165, + "NAME": "dead coarse root ALLOCATION -4", + "INDEX": 139.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 19, + "TYPE": -3 + }, + { + "X": 166, + "NAME": "canopy average specific leaf area-4", + "INDEX": 140.64, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 167, + "NAME": "current growth proportion-4", + "INDEX": 141.64, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 168, + "NAME": "maximal lifetime of plant tissue-4", + "INDEX": 142.64, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 169, + "NAME": "length of phenophase (GDD)-5", + "INDEX": 131.65, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 170, + "NAME": "leaf ALLOCATION -5", + "INDEX": 132.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 171, + "NAME": "fine root ALLOCATION-5", + "INDEX": 133.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 172, + "NAME": "fruit ALLOCATION -5", + "INDEX": 134.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 173, + "NAME": "soft stem ALLOCATION-5", + "INDEX": 135.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 174, + "NAME": "live woody stem ALLOCATION -5", + "INDEX": 136.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 175, + "NAME": "dead woody stem ALLOCATION -5", + "INDEX": 137.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 176, + "NAME": "live coarse root ALLOCATION-5", + "INDEX": 138.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 177, + "NAME": "dead coarse root ALLOCATION -5", + "INDEX": 139.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 20, + "TYPE": -3 + }, + { + "X": 178, + "NAME": "canopy average specific leaf area-5", + "INDEX": 140.65, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 179, + "NAME": "current growth proportion-5", + "INDEX": 141.65, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 180, + "NAME": "maximal lifetime of plant tissue-5", + "INDEX": 142.65, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 181, + "NAME": "length of phenophase (GDD)-6", + "INDEX": 131.66, + "UNIT": "Celsius", + "MIN": 0, + "MAX": 10000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 182, + "NAME": "leaf ALLOCATION -6", + "INDEX": 132.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 183, + "NAME": "fine root ALLOCATION-6", + "INDEX": 133.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 184, + "NAME": "fruit ALLOCATION -6", + "INDEX": 134.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 185, + "NAME": "soft stem ALLOCATION-6", + "INDEX": 135.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 186, + "NAME": "live woody stem ALLOCATION -6", + "INDEX": 136.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 187, + "NAME": "dead woody stem ALLOCATION -6", + "INDEX": 137.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 188, + "NAME": "live coarse root ALLOCATION-6", + "INDEX": 138.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 189, + "NAME": "dead coarse root ALLOCATION -6", + "INDEX": 139.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": -3 + }, + { + "X": 190, + "NAME": "canopy average specific leaf area-6", + "INDEX": 140.66, + "UNIT": "m2/kg", + "MIN": 0, + "MAX": 2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 191, + "NAME": "current growth proportion-6", + "INDEX": 141.66, + "UNIT": "prop", + "MIN": 0, + "MAX": 0, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 192, + "NAME": "maximal lifetime of plant tissue-6", + "INDEX": 142.66, + "UNIT": "Celsius", + "MIN": 1, + "MAX": 20000, + "GROUP": 0, + "TYPE": 0 + } +] diff --git a/RBBGCMuso/inst/data/soilConstMatrix7.json b/RBBGCMuso/inst/data/soilConstMatrix7.json new file mode 100644 index 0000000..891f0f1 --- /dev/null +++ b/RBBGCMuso/inst/data/soilConstMatrix7.json @@ -0,0 +1,1495 @@ +[ + { + "X": 1, + "NAME": "denitrification rate per g of CO2 respiration of SOM", + "INDEX": 4, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 2, + "NAME": "nitrification coefficient 1 ", + "INDEX": 5, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 3, + "NAME": "nitrification coefficient 2", + "INDEX": 6, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 4, + "NAME": "coefficient of N2O emission of nitrification", + "INDEX": 7, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 5, + "NAME": "NH4 mobilen proportion", + "INDEX": 8, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 6, + "NAME": "NO3 mobilen proportion", + "INDEX": 9, + "UNIT": "prop", + "MIN": 0.8, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 7, + "NAME": "e-folding depth of decomposition rate's depth scalar", + "INDEX": 10, + "UNIT": "m", + "MIN": 6, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 8, + "NAME": "fraction of dissolved part of SOIL1 organic matter", + "INDEX": 11, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 9, + "NAME": "fraction of dissolved part of SOIL2 organic matter", + "INDEX": 12, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 10, + "NAME": "fraction of dissolved part of SOIL3organic matter", + "INDEX": 13, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 11, + "NAME": "fraction of dissolved part of SOIL4 organic matter", + "INDEX": 14, + "UNIT": "prop", + "MIN": 0, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 12, + "NAME": "minimum WFPS for scalar of nitrification calculation", + "INDEX": 15, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 0, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 13, + "NAME": "lower optimum WFPS for scalar of nitrification calculation", + "INDEX": 16, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 1, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 14, + "NAME": "higher optimum WFPS for scalar of nitrification calculation", + "INDEX": 17, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "DEPENDENCE": 2, + "GROUP": 21, + "TYPE": 1 + }, + { + "X": 15, + "NAME": "minimum value for saturated WFPS scalar of nitrification calculation", + "INDEX": 18, + "UNIT": "prop", + "MIN": 0, + "MAX": 1, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 16, + "NAME": "critical value of dissolved N and C in bottom (inactive layer)", + "INDEX": 19, + "UNIT": "ppm", + "MIN": 0, + "MAX": 1000, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 17, + "NAME": "respiration fractions for fluxes between compartments (l1s1)", + "INDEX": 22, + "UNIT": "prop", + "MIN": 0.1, + "MAX": 0.9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 18, + "NAME": "respiration fractions for fluxes between compartments (l2s2)", + "INDEX": 23, + "UNIT": "prop", + "MIN": 0.55, + "MAX": 0.55, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 19, + "NAME": "respiration fractions for fluxes between compartments (l4s3)", + "INDEX": 24, + "UNIT": "prop", + "MIN": 0.29, + "MAX": 0.29, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 20, + "NAME": "respiration fractions for fluxes between compartments (s1s2)", + "INDEX": 25, + "UNIT": "prop", + "MIN": 0.28, + "MAX": 0.28, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 21, + "NAME": "respiration fractions for fluxes between compartments (s2s3)", + "INDEX": 26, + "UNIT": "prop", + "MIN": 0.46, + "MAX": 0.46, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 22, + "NAME": "respiration fractions for fluxes between compartments (s3s4)", + "INDEX": 27, + "UNIT": "prop", + "MIN": 0.55, + "MAX": 0.55, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 23, + "NAME": "rate constant scalar of labile litter pool", + "INDEX": 28, + "UNIT": "1/day", + "MIN": 0.7, + "MAX": 0.7, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 24, + "NAME": "rate constant scalar of cellulose litter pool", + "INDEX": 29, + "UNIT": "1/day", + "MIN": 0.07, + "MAX": 0.07, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 25, + "NAME": "rate constant scalar of lignin litter pool", + "INDEX": 30, + "UNIT": "1/day", + "MIN": 0.014, + "MAX": 0.014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 26, + "NAME": "rate constant scalar of fast microbial recycling pool", + "INDEX": 31, + "UNIT": "1/day", + "MIN": 0.07, + "MAX": 0.07, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 27, + "NAME": "rate constant scalar of medium microbial recycling pool", + "INDEX": 32, + "UNIT": "1/day", + "MIN": 0.014, + "MAX": 0.014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 28, + "NAME": "rate constant scalar of slow microbial recycling pool", + "INDEX": 33, + "UNIT": "1/day", + "MIN": 0.0014, + "MAX": 0.0014, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 29, + "NAME": "rate constant scalar of recalcitrant SOM (humus) pool", + "INDEX": 34, + "UNIT": "1/day", + "MIN": 0.0001, + "MAX": 0.0001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 30, + "NAME": "rate constant scalar of physical fragmentation of coarse woody debris", + "INDEX": 35, + "UNIT": "1/day", + "MIN": 0.001, + "MAX": 0.001, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 31, + "NAME": "param1 for CH4 calculations (empirical function of BD)", + "INDEX": 38, + "UNIT": "dimless", + "MIN": 212.5, + "MAX": 212.5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 32, + "NAME": "param2 for CH4 calculations (empirical function of BD)", + "INDEX": 39, + "UNIT": "dimless", + "MIN": 1.81, + "MAX": 1.81, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 33, + "NAME": "param1 for CH4 calculations (empirical function of VWC)", + "INDEX": 40, + "UNIT": "dimless", + "MIN": -1.353, + "MAX": -1.353, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 34, + "NAME": "param2 for CH4 calculations (empirical function of VWC)", + "INDEX": 41, + "UNIT": "dimless", + "MIN": 0.2, + "MAX": 0.2, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 35, + "NAME": "param3 for CH4 calculations (empirical function of VWC)", + "INDEX": 42, + "UNIT": "dimless", + "MIN": 1.781, + "MAX": 1.781, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 36, + "NAME": "param4 for CH4 calculations (empirical function of VWC)", + "INDEX": 43, + "UNIT": "dimless", + "MIN": 6.786, + "MAX": 6.786, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 37, + "NAME": "param1 for CH4 calculations (empirical function of Tsoil)", + "INDEX": 44, + "UNIT": "dimless", + "MIN": 0.01, + "MAX": 0.01, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 38, + "NAME": "depth of soil", + "INDEX": 47, + "UNIT": "m", + "MIN": 1, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 39, + "NAME": "limit of first stage evaporation", + "INDEX": 48, + "UNIT": "prop", + "MIN": 1, + "MAX": 9, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 40, + "NAME": "maximum height of pond water", + "INDEX": 49, + "UNIT": "mm", + "MIN": 0, + "MAX": 40, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 41, + "NAME": "curvature of soil stress functionr", + "INDEX": 50, + "UNIT": "dimless", + "MIN": 0.1, + "MAX": 5, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 42, + "NAME": "runoff curve parameter", + "INDEX": 51, + "UNIT": "dimless", + "MIN": 10, + "MAX": 90, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 43, + "NAME": "aerodynamic resistance", + "INDEX": 52, + "UNIT": "s/m", + "MIN": 60, + "MAX": 200, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-0", + "INDEX": 55.9, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 1, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-0", + "INDEX": 56.9, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 1, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-0", + "INDEX": 57.9, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-0", + "INDEX": 58.9, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-0", + "INDEX": 59.9, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-0", + "INDEX": 60.9, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-0", + "INDEX": 61.9, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-0", + "INDEX": 62.9, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 2, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-0", + "INDEX": 63.9, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-0", + "INDEX": 64.9, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-1", + "INDEX": 55.91, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 3, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-1", + "INDEX": 56.91, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 3, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-1", + "INDEX": 57.91, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-1", + "INDEX": 58.91, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-1", + "INDEX": 59.91, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-1", + "INDEX": 60.91, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-1", + "INDEX": 61.91, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-1", + "INDEX": 62.91, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 4, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-1", + "INDEX": 63.91, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-1", + "INDEX": 64.91, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-2", + "INDEX": 55.92, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-2", + "INDEX": 56.92, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 5, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-2", + "INDEX": 57.92, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-2", + "INDEX": 58.92, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-2", + "INDEX": 59.92, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-2", + "INDEX": 60.92, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-2", + "INDEX": 61.92, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-2", + "INDEX": 62.92, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 6, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-2", + "INDEX": 63.92, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-2", + "INDEX": 64.92, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-3", + "INDEX": 55.93, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-3", + "INDEX": 56.93, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 7, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-3", + "INDEX": 57.93, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-3", + "INDEX": 58.93, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-3", + "INDEX": 59.93, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-3", + "INDEX": 60.93, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-3", + "INDEX": 61.93, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-3", + "INDEX": 62.93, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 8, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-3", + "INDEX": 63.93, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-3", + "INDEX": 64.93, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-4", + "INDEX": 55.94, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 9, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-4", + "INDEX": 56.94, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 9, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-4", + "INDEX": 57.94, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-4", + "INDEX": 58.94, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-4", + "INDEX": 59.94, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-4", + "INDEX": 60.94, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-4", + "INDEX": 61.94, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-4", + "INDEX": 62.94, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 10, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-4", + "INDEX": 63.94, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-4", + "INDEX": 64.94, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-5", + "INDEX": 55.95, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 11, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-5", + "INDEX": 56.95, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 11, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-5", + "INDEX": 57.95, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-5", + "INDEX": 58.95, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-5", + "INDEX": 59.95, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-5", + "INDEX": 60.95, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-5", + "INDEX": 61.95, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-5", + "INDEX": 62.95, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 12, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-5", + "INDEX": 63.95, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-5", + "INDEX": 64.95, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-6", + "INDEX": 55.96, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 13, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-6", + "INDEX": 56.96, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 13, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-6", + "INDEX": 57.96, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-6", + "INDEX": 58.96, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-6", + "INDEX": 59.96, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-6", + "INDEX": 60.96, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-6", + "INDEX": 61.96, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-6", + "INDEX": 62.96, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 14, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-6", + "INDEX": 63.96, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-6", + "INDEX": 64.96, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-7", + "INDEX": 55.97, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 15, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-7", + "INDEX": 56.97, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 15, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-7", + "INDEX": 57.97, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-7", + "INDEX": 58.97, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-7", + "INDEX": 59.97, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-7", + "INDEX": 60.97, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-7", + "INDEX": 61.97, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-7", + "INDEX": 62.97, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 16, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-7", + "INDEX": 63.97, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-7", + "INDEX": 64.97, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-8", + "INDEX": 55.98, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 17, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-8", + "INDEX": 56.98, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 17, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-8", + "INDEX": 57.98, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-8", + "INDEX": 58.98, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-8", + "INDEX": 59.98, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-8", + "INDEX": 60.98, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-8", + "INDEX": 61.98, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-8", + "INDEX": 62.98, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 18, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-8", + "INDEX": 63.98, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-8", + "INDEX": 64.98, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 44, + "NAME": "sand percentage-9", + "INDEX": 55.99, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 19, + "TYPE": 2 + }, + { + "X": 45, + "NAME": "silt percentage-9", + "INDEX": 56.99, + "UNIT": "%", + "DEPENDENCE": 100, + "MIN": 0, + "MAX": 100, + "GROUP": 19, + "TYPE": 2 + }, + { + "X": 46, + "NAME": "ph-9", + "INDEX": 57.99, + "UNIT": "dimless", + "MIN": 1, + "MAX": 14, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 47, + "NAME": "bulk density-9", + "INDEX": 58.99, + "UNIT": "g/cm3", + "MIN": 1.2, + "MAX": 1.6, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 48, + "NAME": "SWC at saturation-9", + "INDEX": 59.99, + "UNIT": "m3/m3", + "DEPENDENCE": 2, + "MIN": 0.4, + "MAX": 0.6, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 49, + "NAME": "SWC at field capacity-9", + "INDEX": 60.99, + "UNIT": "m3/m3", + "DEPENDENCE": 3, + "MIN": 0.1, + "MAX": 0.5, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 50, + "NAME": "SWC at wilting point-9", + "INDEX": 61.99, + "UNIT": "m3/m3", + "DEPENDENCE": 4, + "MIN": 0.02, + "MAX": 0.3, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 51, + "NAME": "SWC at hygroscopic water content-9", + "INDEX": 62.99, + "UNIT": "m3/m3", + "DEPENDENCE": 0, + "MIN": 0.01, + "MAX": 0.05, + "GROUP": 20, + "TYPE": 1 + }, + { + "X": 52, + "NAME": "drainage coefficient-9", + "INDEX": 63.99, + "UNIT": "dimless", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + }, + { + "X": 53, + "NAME": "hydraulic condictivity at saturation-9", + "INDEX": 64.99, + "UNIT": "cm/day", + "MIN": 0, + "MAX": 10, + "GROUP": 0, + "TYPE": 0 + } +] diff --git a/RBBGCMuso/inst/data/varTable7.json b/RBBGCMuso/inst/data/varTable7.json new file mode 100644 index 0000000..fb8b4f3 --- /dev/null +++ b/RBBGCMuso/inst/data/varTable7.json @@ -0,0 +1,16081 @@ +[ + { + "codes": 0, + "names": "remdays_curgrowth", + "units": "n", + "descriptions": "Remaining days current growth season" + }, + { + "codes": 1, + "names": "remdays_transfer", + "units": "n", + "descriptions": "Remaining days transfer period" + }, + { + "codes": 2, + "names": "remdays_litfall", + "units": "n", + "descriptions": "Remaining days litterfall" + }, + { + "codes": 3, + "names": "predays_transfer", + "units": "n", + "descriptions": "Previous days transfer period" + }, + { + "codes": 4, + "names": "predays_litfall", + "units": "n", + "descriptions": "Previous days litterfall" + }, + { + "codes": 5, + "names": "n_growthday", + "units": "n", + "descriptions": "Number of growing days" + }, + { + "codes": 6, + "names": "n_transferday", + "units": "n", + "descriptions": "Number of transfer days" + }, + { + "codes": 7, + "names": "n_litfallday", + "units": "n", + "descriptions": "Number of litterfall days" + }, + { + "codes": 8, + "names": "yday_total", + "units": "dimless", + "descriptions": "Counter for simdays of the whole simulation" + }, + { + "codes": 9, + "names": "phpsl_dev_rate", + "units": "dimless", + "descriptions": "Photoslowing effect rel. development" + }, + { + "codes": 10, + "names": "vern_dev_rate", + "units": "dimless", + "descriptions": "Vernalization rel. development" + }, + { + "codes": 11, + "names": "vern_days", + "units": "n", + "descriptions": "Vernalization days" + }, + { + "codes": 12, + "names": "GDD_limit", + "units": "Celsius", + "descriptions": "Lower limit of GDD in given phen.phase" + }, + { + "codes": 13, + "names": "GDD_crit_0", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 1" + }, + { + "codes": 14, + "names": "GDD_crit_1", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 2" + }, + { + "codes": 15, + "names": "GDD_crit_2", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 3" + }, + { + "codes": 16, + "names": "GDD_crit_3", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 4" + }, + { + "codes": 17, + "names": "GDD_crit_4", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 5" + }, + { + "codes": 18, + "names": "GDD_crit_5", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 6" + }, + { + "codes": 19, + "names": "GDD_crit_6", + "units": "Celsius", + "descriptions": "Critical GDD phen.phase 7" + }, + { + "codes": 20, + "names": "GDD_emergSTART", + "units": "Celsius", + "descriptions": "GDD at start of emergence period" + }, + { + "codes": 21, + "names": "GDD_emergEND", + "units": "Celsius", + "descriptions": "GDD at end of emergence period" + }, + { + "codes": 22, + "names": "ondayANN", + "units": "dimless", + "descriptions": "Actual onday value" + }, + { + "codes": 23, + "names": "offdayANN", + "units": "dimless", + "descriptions": "Actual offday value" + }, + { + "codes": 24, + "names": "planttype", + "units": "dimless", + "descriptions": "Plant type (maize:1,wheat:2,barley:3,...)" + }, + { + "codes": 25, + "names": "Tmin_index", + "units": "dimless", + "descriptions": "Part index of GSI" + }, + { + "codes": 26, + "names": "vpd_index", + "units": "dimless", + "descriptions": "Part index of GSI" + }, + { + "codes": 27, + "names": "dayl_index", + "units": "dimless", + "descriptions": "Part index of GSI" + }, + { + "codes": 28, + "names": "gsi_indexAVG", + "units": "dimless", + "descriptions": "Part index of GSI" + }, + { + "codes": 29, + "names": "heatsum_index", + "units": "dimless", + "descriptions": "Part index of GSI" + }, + { + "codes": 30, + "names": "heatsum", + "units": "Celsius", + "descriptions": "n-day heatsum" + }, + { + "codes": 40, + "names": "tACCLIM", + "units": "Celsius", + "descriptions": "Acclimation temperature" + }, + { + "codes": 41, + "names": "tnight", + "units": "Celsius", + "descriptions": "Nighttime temperature" + }, + { + "codes": 42, + "names": "TavgRA11", + "units": "Celsius", + "descriptions": "11-day running average temperature" + }, + { + "codes": 43, + "names": "TavgRA10", + "units": "Celsius", + "descriptions": "10-day running average temperature" + }, + { + "codes": 44, + "names": "TavgRA30", + "units": "Celsius", + "descriptions": "30-day running average temperature" + }, + { + "codes": 45, + "names": "tempradF", + "units": "dimless", + "descriptions": "Soil temperature factor (air temperature and radiation)" + }, + { + "codes": 46, + "names": "tempradFra", + "units": "dimless", + "descriptions": "5-day running average soil temperature factor" + }, + { + "codes": 47, + "names": "tsoil_surface", + "units": "Celsius", + "descriptions": "Soil surface temperature" + }, + { + "codes": 48, + "names": "tsoil_surface_pre", + "units": "Celsius", + "descriptions": "Soil surface temperature of previous day" + }, + { + "codes": 49, + "names": "tsoil_avg", + "units": "Celsius", + "descriptions": "Average soil temperature" + }, + { + "codes": 50, + "names": "tsoil_0", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 1 (0 - 3 cm)" + }, + { + "codes": 51, + "names": "tsoil_1", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 2 (3 - 10 cm)" + }, + { + "codes": 52, + "names": "tsoil_2", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 3 (10 - 30 cm cm)" + }, + { + "codes": 53, + "names": "tsoil_3", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 4 (30 - 60 cm)" + }, + { + "codes": 54, + "names": "tsoil_4", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 5 (60 - 90 cm)" + }, + { + "codes": 55, + "names": "tsoil_5", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 6 (90 - 120 cm)" + }, + { + "codes": 56, + "names": "tsoil_6", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 7 (120 - 150 cm)" + }, + { + "codes": 57, + "names": "tsoil_7", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 8 (150 - 200 cm)" + }, + { + "codes": 58, + "names": "tsoil_8", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 9 (200 - 400 cm)" + }, + { + "codes": 59, + "names": "tsoil_9", + "units": "Celsius", + "descriptions": "Daily temperature of soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 60, + "names": "swRADnet", + "units": "Wm-2", + "descriptions": "Net shortwave radiation" + }, + { + "codes": 61, + "names": "lwRADnet", + "units": "Wm-2", + "descriptions": "Net outgoing longwave radiation" + }, + { + "codes": 62, + "names": "RADnet", + "units": "Wm-2", + "descriptions": "Daylight average net radiation flux" + }, + { + "codes": 63, + "names": "RADnet_per_plaisun", + "units": "Wm-2", + "descriptions": "Daylight avg. net radiation flux sunshade proj. leaf area index" + }, + { + "codes": 64, + "names": "RADnet_per_plaishade", + "units": "Wm-2", + "descriptions": "Daylight avg. net radiation flux sunlit proj. leaf area index" + }, + { + "codes": 65, + "names": "swavgfd", + "units": "Wm-2", + "descriptions": "Daylight average shortwave flux" + }, + { + "codes": 66, + "names": "swabs", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux" + }, + { + "codes": 67, + "names": "swtrans", + "units": "Wm-2", + "descriptions": "Transmitted shortwave flux" + }, + { + "codes": 68, + "names": "swabs_per_plaisun", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux sunlit prof. leaf area index" + }, + { + "codes": 69, + "names": "swabs_per_plaishade", + "units": "Wm-2", + "descriptions": "Canopy absorbed shortwave flux sunshade prof. leaf area index" + }, + { + "codes": 70, + "names": "ppfd_per_plaisun", + "units": "µmolm-2s-1", + "descriptions": "PPFD sunlit proj. leaf area index" + }, + { + "codes": 71, + "names": "ppfd_per_plaishade", + "units": "µmolm-2s-1", + "descriptions": "PPFD sunshade proj. leaf area index" + }, + { + "codes": 72, + "names": "parabs", + "units": "Wm-2", + "descriptions": "Canopy absorbed PAR" + }, + { + "codes": 73, + "names": "parabs_plaisun", + "units": "Wm-2", + "descriptions": "PAR absorbed by sunlit canopy fraction" + }, + { + "codes": 74, + "names": "parabs_plaishade", + "units": "Wm-2", + "descriptions": "PAR absorbed by sunshade canopy fraction" + }, + { + "codes": 75, + "names": "GDD", + "units": "Celsius", + "descriptions": "GDD" + }, + { + "codes": 76, + "names": "GDD_wMOD", + "units": "Celsius", + "descriptions": "GDD modified by vern. and photop. effect" + }, + { + "codes": 77, + "names": "annTavgRA", + "units": "Celsius", + "descriptions": "10-year running average of mean annual air temperature" + }, + { + "codes": 78, + "names": "annTrangeRA", + "units": "Celsius", + "descriptions": "10-year running average of mean annual air temperature range" + }, + { + "codes": 79, + "names": "pa", + "units": "Pa", + "descriptions": "Atmospheric pressure" + }, + { + "codes": 80, + "names": "soilw_0", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 1 (0 - 3 cm)" + }, + { + "codes": 81, + "names": "soilw_1", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 2 (3 - 10 cm)" + }, + { + "codes": 82, + "names": "soilw_2", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 3 (10 - 30 cm cm)" + }, + { + "codes": 83, + "names": "soilw_3", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 4 (30 - 60 cm)" + }, + { + "codes": 84, + "names": "soilw_4", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 5 (60 - 90 cm)" + }, + { + "codes": 85, + "names": "soilw_5", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 6 (90 - 120 cm)" + }, + { + "codes": 86, + "names": "soilw_6", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 7 (120 - 150 cm)" + }, + { + "codes": 87, + "names": "soilw_7", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 8 (150 - 200 cm)" + }, + { + "codes": 88, + "names": "soilw_8", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 9 (200 - 400 cm)" + }, + { + "codes": 89, + "names": "soilw_9", + "units": "kgH2Om-2", + "descriptions": "SWC of soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 90, + "names": "soilw_SUM", + "units": "kgH2Om-2", + "descriptions": "SWC" + }, + { + "codes": 91, + "names": "pondw", + "units": "kgH2Om-2", + "descriptions": "Pond water" + }, + { + "codes": 92, + "names": "snoww", + "units": "kgH2Om-2", + "descriptions": "Snow water" + }, + { + "codes": 93, + "names": "canopyw", + "units": "kgH2Om-2", + "descriptions": "Canopy water" + }, + { + "codes": 94, + "names": "prcp_src", + "units": "kgH2Om-2", + "descriptions": "Precipitation" + }, + { + "codes": 95, + "names": "soilEVP_snk", + "units": "kgH2Om-2", + "descriptions": "Soil water evaporation" + }, + { + "codes": 96, + "names": "snowSUBL_snk", + "units": "kgH2Om-2", + "descriptions": "Snow sublimation" + }, + { + "codes": 97, + "names": "canopywEVP_snk", + "units": "kgH2Om-2", + "descriptions": "Canopy evaporation" + }, + { + "codes": 98, + "names": "pondEVP_snk", + "units": "kgH2Om-2", + "descriptions": "Pond water decrease" + }, + { + "codes": 99, + "names": "TRP_snk", + "units": "kgH2Om-2", + "descriptions": "transpiration" + }, + { + "codes": 100, + "names": "runoff_snk", + "units": "kgH2Om-2", + "descriptions": "Runoff" + }, + { + "codes": 101, + "names": "deeppercolation_snk", + "units": "kgH2Om-2", + "descriptions": "Deep percolation" + }, + { + "codes": 102, + "names": "groundwater_src", + "units": "kgH2Om-2", + "descriptions": "Water plus from groundwater" + }, + { + "codes": 103, + "names": "canopyw_THNsnk", + "units": "kgH2Om-2", + "descriptions": "Canopy water loss thinning" + }, + { + "codes": 104, + "names": "canopyw_MOWsnk", + "units": "kgH2Om-2", + "descriptions": "Canopy water loss mowing" + }, + { + "codes": 105, + "names": "canopyw_HRVsnk", + "units": "kgH2Om-2", + "descriptions": "Canopy water loss harvesting" + }, + { + "codes": 106, + "names": "canopyw_PLGsnk", + "units": "kgH2Om-2", + "descriptions": "Canopy water loss ploughing" + }, + { + "codes": 107, + "names": "canopyw_GRZsnk", + "units": "kgH2Om-2", + "descriptions": "Canopy water loss grazing" + }, + { + "codes": 108, + "names": "IRGsrc_W", + "units": "kgH2Om-2", + "descriptions": "Water income from irrigation" + }, + { + "codes": 109, + "names": "FRZsrc_W", + "units": "kgH2Om-2", + "descriptions": "Water income from fertilizers" + }, + { + "codes": 110, + "names": "WbalanceERR", + "units": "kgH2Om-2", + "descriptions": "Water balance error" + }, + { + "codes": 111, + "names": "inW", + "units": "kgH2Om-2", + "descriptions": "SUM of water input" + }, + { + "codes": 112, + "names": "outW", + "units": "kgH2Om-2", + "descriptions": "SUM of water output" + }, + { + "codes": 113, + "names": "storeW", + "units": "kgH2Om-2", + "descriptions": "SUM of water storage" + }, + { + "codes": 114, + "names": "cumEVPsoil1", + "units": "kgH2Om-2", + "descriptions": "Cumulated soil evaporation in first evaporation phase (no limit)" + }, + { + "codes": 115, + "names": "cumEVPsoil2", + "units": "kgH2Om-2", + "descriptions": "Cumulated soil evaporation in second evaporation phase (DSR limit)" + }, + { + "codes": 116, + "names": "soilw_2m", + "units": "kgH2Om-2", + "descriptions": "SWC in 0-2 m" + }, + { + "codes": 117, + "names": "soilw_RZ", + "units": "kgH2Om-2", + "descriptions": "SWC in rootzone" + }, + { + "codes": 118, + "names": "soilw_RZ_avail", + "units": "kgH2Om-2", + "descriptions": "SWC in rootzone available for plants" + }, + { + "codes": 119, + "names": "soilw_avail_0", + "units": "kgH2Om-2", + "descriptions": "Available soil water 1 (0 - 3 cm)" + }, + { + "codes": 120, + "names": "soilw_avail_1", + "units": "kgH2Om-2", + "descriptions": "Available soil water 2 (3 - 10 cm)" + }, + { + "codes": 121, + "names": "soilw_avail_2", + "units": "kgH2Om-2", + "descriptions": "Available soil water 3 (10 - 30 cm cm)" + }, + { + "codes": 122, + "names": "soilw_avail_3", + "units": "kgH2Om-2", + "descriptions": "Available soil water 4 (30 - 60 cm)" + }, + { + "codes": 123, + "names": "soilw_avail_4", + "units": "kgH2Om-2", + "descriptions": "Available soil water 5 (60 - 90 cm)" + }, + { + "codes": 124, + "names": "soilw_avail_5", + "units": "kgH2Om-2", + "descriptions": "Available soil water 6 (90 - 120 cm)" + }, + { + "codes": 125, + "names": "soilw_avail_6", + "units": "kgH2Om-2", + "descriptions": "Available soil water 7 (120 - 150 cm)" + }, + { + "codes": 126, + "names": "soilw_avail_7", + "units": "kgH2Om-2", + "descriptions": "Available soil water 8 (150 - 200 cm)" + }, + { + "codes": 127, + "names": "soilw_avail_8", + "units": "kgH2Om-2", + "descriptions": "Available soil water 9 (200 - 400 cm)" + }, + { + "codes": 128, + "names": "soilw_avail_9", + "units": "kgH2Om-2", + "descriptions": "Available soil water 10 (400 - 1000 cm)" + }, + { + "codes": 129, + "names": "groundwater_snk", + "units": "kgH2Om-2", + "descriptions": "SUM of water loss to groundwater (recharge)" + }, + { + "codes": 130, + "names": "timestepRichards", + "units": "n", + "descriptions": "Number of iteration step using Richards-method" + }, + { + "codes": 131, + "names": "condIRGsrc", + "units": "kgH2Om-2", + "descriptions": "Cumulative amount of conditional irrigation" + }, + { + "codes": 132, + "names": "cumGWchange", + "units": "kgH2Om-2", + "descriptions": "Cumulative net change in water content of soil column due to groundwater" + }, + { + "codes": 133, + "names": "FLDsrc", + "units": "kgH2Om-2", + "descriptions": "Water plus from flooding" + }, + { + "codes": 150, + "names": "prcp_to_canopyw", + "units": "kgH2Om-2day-1", + "descriptions": "Interception on canopy" + }, + { + "codes": 151, + "names": "prcp_to_soilSurface", + "units": "kgH2Om-2day-1", + "descriptions": "Precipitation entering soilwater pool" + }, + { + "codes": 152, + "names": "prcp_to_snoww", + "units": "kgH2Om-2day-1", + "descriptions": "Snowpack accumulation" + }, + { + "codes": 153, + "names": "prcp_to_runoff", + "units": "kgH2Om-2day-1", + "descriptions": "Hortonian runoff flux" + }, + { + "codes": 154, + "names": "canopywEVP", + "units": "kgH2Om-2day-1", + "descriptions": "evaporation from canopy" + }, + { + "codes": 155, + "names": "canopyw_to_soilw", + "units": "kgH2Om-2day-1", + "descriptions": "Canopy drip and stemflow" + }, + { + "codes": 156, + "names": "pondwEVP", + "units": "kgH2Om-2day-1", + "descriptions": "Pond water evaporation" + }, + { + "codes": 157, + "names": "snowwSUBL", + "units": "kgH2Om-2day-1", + "descriptions": "Sublimation from snowpack" + }, + { + "codes": 158, + "names": "snoww_to_soilw", + "units": "kgH2Om-2day-1", + "descriptions": "Melt from snowpack" + }, + { + "codes": 159, + "names": "soilwEVP", + "units": "kgH2Om-2day-1", + "descriptions": "evaporation from soil" + }, + { + "codes": 160, + "names": "soilwTRP_0", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 1 (0 - 3 cm)" + }, + { + "codes": 161, + "names": "soilwTRP_1", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 2 (3 - 10 cm)" + }, + { + "codes": 162, + "names": "soilwTRP_2", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 3 (10 - 30 cm cm)" + }, + { + "codes": 163, + "names": "soilwTRP_3", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 4 (30 - 60 cm)" + }, + { + "codes": 164, + "names": "soilwTRP_4", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 5 (60 - 90 cm)" + }, + { + "codes": 165, + "names": "soilwTRP_5", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 6 (90 - 120 cm)" + }, + { + "codes": 166, + "names": "soilwTRP_6", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 7 (120 - 150 cm)" + }, + { + "codes": 167, + "names": "soilwTRP_7", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 8 (150 - 200 cm)" + }, + { + "codes": 168, + "names": "soilwTRP_8", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 9 (200 - 400 cm)" + }, + { + "codes": 169, + "names": "soilwTRP_9", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration from soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 170, + "names": "soilwTRP_SUM", + "units": "kgH2Om-2day-1", + "descriptions": "SUM of transpiration from the soil layers" + }, + { + "codes": 171, + "names": "ET", + "units": "kgH2Om-2day-1", + "descriptions": "evapotranspiration (EVP+TRP+subl)" + }, + { + "codes": 172, + "names": "pondw_to_soilw", + "units": "kgH2Om-2day-1", + "descriptions": "Water flux from pond to soil" + }, + { + "codes": 173, + "names": "soilw_to_pondw", + "units": "kgH2Om-2day-1", + "descriptions": "Water flux from soil to pond" + }, + { + "codes": 174, + "names": "soilwFlux_0", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 1 (0-3 cm)" + }, + { + "codes": 175, + "names": "soilwFlux_1", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 2 (3-10 cm)" + }, + { + "codes": 176, + "names": "soilwFlux_2", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 3 (10-30 cm)" + }, + { + "codes": 177, + "names": "soilwFlux_3", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 4 (30-60 cm)" + }, + { + "codes": 178, + "names": "soilwFlux_4", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 5 (60-90 cm)" + }, + { + "codes": 179, + "names": "soilwFlux_5", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 6 (90-120 cm)" + }, + { + "codes": 180, + "names": "soilwFlux_6", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 7 (120-150 cm)" + }, + { + "codes": 181, + "names": "soilwFlux_7", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 8 (150-200 cm)" + }, + { + "codes": 182, + "names": "soilwFlux_8", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 9 (200-400 cm)" + }, + { + "codes": 183, + "names": "soilwFlux_9", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water flux in soil layer 10 (400-1000 cm)" + }, + { + "codes": 184, + "names": "GWmovchange_0", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 1 (0-3 cm)" + }, + { + "codes": 185, + "names": "GWmovchange_1", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 2 (3-10 cm)" + }, + { + "codes": 186, + "names": "GWmovchange_2", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 3 (10-30 cm)" + }, + { + "codes": 187, + "names": "GWmovchange_3", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 4 (30-60 cm)" + }, + { + "codes": 188, + "names": "GWmovchange_4", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 5 (60-90 cm)" + }, + { + "codes": 189, + "names": "GWmovchange_5", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 6 (90-120 cm)" + }, + { + "codes": 190, + "names": "GWmovchange_6", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 7 (120-150 cm)" + }, + { + "codes": 191, + "names": "GWmovchange_7", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 8 (150-200 cm)" + }, + { + "codes": 192, + "names": "GWmovchange_8", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 9 (200-400 cm)" + }, + { + "codes": 193, + "names": "GWmovchange_9", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water change due to the movement of groundwater table in soil layer 10 (400-1000 cm)" + }, + { + "codes": 194, + "names": "GWdischarge_0", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 1 (0-3 cm)" + }, + { + "codes": 195, + "names": "GWdischarge_1", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 2 (3-10 cm)" + }, + { + "codes": 196, + "names": "GWdischarge_2", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 3 (10-30 cm)" + }, + { + "codes": 197, + "names": "GWdischarge_3", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 4 (30-60 cm)" + }, + { + "codes": 198, + "names": "GWdischarge_4", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 5 (60-90 cm)" + }, + { + "codes": 199, + "names": "GWdischarge_5", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 6 (90-120 cm)" + }, + { + "codes": 200, + "names": "GWdischarge_6", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 7 (120-150 cm)" + }, + { + "codes": 201, + "names": "GWdischarge_7", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 8 (150-200 cm)" + }, + { + "codes": 202, + "names": "GWdischarge_8", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 9 (200-400 cm)" + }, + { + "codes": 203, + "names": "GWdischarge_9", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water from groundwater in soil layer 10 (400-1000 cm)" + }, + { + "codes": 204, + "names": "soilwLeach_RZ", + "units": "kgH2Om-2day-1", + "descriptions": "Soil water leached from rootzone (perc+diff)" + }, + { + "codes": 205, + "names": "canopyw_to_THN", + "units": "kgH2Om-2day-1", + "descriptions": "Canopy water loss thinning" + }, + { + "codes": 206, + "names": "canopyw_to_MOW", + "units": "kgH2Om-2day-1", + "descriptions": "Canopy water loss mowing" + }, + { + "codes": 207, + "names": "canopyw_to_HRV", + "units": "kgH2Om-2day-1", + "descriptions": "Canopy water loss harvesting" + }, + { + "codes": 208, + "names": "canopyw_to_PLG", + "units": "kgH2Om-2day-1", + "descriptions": "Canopy water loss ploughing" + }, + { + "codes": 209, + "names": "canopyw_to_GRZ", + "units": "kgH2Om-2day-1", + "descriptions": "Canopy water loss grazing" + }, + { + "codes": 210, + "names": "IRG_to_prcp", + "units": "kgH2Om-2day-1", + "descriptions": "Irrigated water amount (above canopy height)" + }, + { + "codes": 211, + "names": "FRZ_to_soilw", + "units": "kgH2Om-2day-1", + "descriptions": "Water flux from fertilization" + }, + { + "codes": 212, + "names": "potEVPandSUBLsurface", + "units": "kgH2Om-2day-1", + "descriptions": "Potential evaporation (including sublimation) of surface" + }, + { + "codes": 213, + "names": "infiltPOT", + "units": "kgH2Om-2day-1", + "descriptions": "Potential infiltration" + }, + { + "codes": 214, + "names": "soilwTRPdemand_0", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 1 (0 - 3 cm)" + }, + { + "codes": 215, + "names": "soilwTRPdemand_1", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 2 (3 - 10 cm)" + }, + { + "codes": 216, + "names": "soilwTRPdemand_2", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 3 (10 - 30 cm cm)" + }, + { + "codes": 217, + "names": "soilwTRPdemand_3", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 4 (30 - 60 cm)" + }, + { + "codes": 218, + "names": "soilwTRPdemand_4", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 5 (60 - 90 cm)" + }, + { + "codes": 219, + "names": "soilwTRPdemand_5", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 6 (90 - 120 cm)" + }, + { + "codes": 220, + "names": "soilwTRPdemand_6", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 7 (120 - 150 cm)" + }, + { + "codes": 221, + "names": "soilwTRPdemand_7", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 8 (150 - 200 cm)" + }, + { + "codes": 222, + "names": "soilwTRPdemand_8", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 9 (200 - 400 cm)" + }, + { + "codes": 223, + "names": "soilwTRPdemand_9", + "units": "kgH2Om-2day-1", + "descriptions": "transpiration demand from soil layer 10 (400 - 1000 cm)" + }, + { + "codes": 224, + "names": "ET_Elimit", + "units": "kgH2Om-2day-1", + "descriptions": "Energy limit of evapotranspiration" + }, + { + "codes": 225, + "names": "soilwTRP_POT", + "units": "kgH2Om-2day-1", + "descriptions": "Potential transpiration (no SWC limit)" + }, + { + "codes": 226, + "names": "PET", + "units": "kgH2Om-2day-1", + "descriptions": "Potential evapotranspiration" + }, + { + "codes": 227, + "names": "GWrecharge_0", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 1 (0-3 cm)" + }, + { + "codes": 228, + "names": "GWrecharge_1", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 2 (3-10 cm)" + }, + { + "codes": 229, + "names": "GWrecharge_2", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 3 (10-30 cm)" + }, + { + "codes": 230, + "names": "GWrecharge_3", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 4 (30-60 cm)" + }, + { + "codes": 231, + "names": "GWrecharge_4", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 5 (60-90 cm)" + }, + { + "codes": 232, + "names": "GWrecharge_5", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 6 (90-120 cm)" + }, + { + "codes": 233, + "names": "GWrecharge_6", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 7 (120-150 cm)" + }, + { + "codes": 234, + "names": "GWrecharge_7", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 8 (150-200 cm)" + }, + { + "codes": 235, + "names": "GWrecharge_8", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 9 (200-400 cm)" + }, + { + "codes": 236, + "names": "GWrecharge_9", + "units": "kgH2Om-2day-1", + "descriptions": "Groundwater recharge in soil layer 10 (400-1000 cm)" + }, + { + "codes": 237, + "names": "IRG_to_prcp", + "units": "kgH2Om-2day-1", + "descriptions": "Water from irrigation (below canopy height)" + }, + { + "codes": 238, + "names": "GW_to_pondw", + "units": "kgH2Om-2day-1", + "descriptions": "Water flux from GW to pond water (GW above surface)" + }, + { + "codes": 239, + "names": "surfaceEVP", + "units": "kgH2Om-2day-1", + "descriptions": "SUM of soilw and pond water evaporation" + }, + { + "codes": 240, + "names": "pondw_to_runoff", + "units": "kgH2Om-2day-1", + "descriptions": "Dunnian runoff flux (from pond water)" + }, + { + "codes": 241, + "names": "prcp_to_pondw", + "units": "kgH2Om-2day-1", + "descriptions": "Precipitation entering pond" + }, + { + "codes": 242, + "names": "infilt_to_soilw", + "units": "kgH2Om-2day-1", + "descriptions": "Infiltration flux from prcp to soilw (Richards-method)" + }, + { + "codes": 243, + "names": "potETcanopy", + "units": "kgH2Om-2day-1", + "descriptions": "Potential evaporation and transpiration of canopy" + }, + { + "codes": 244, + "names": "potEVPsurface", + "units": "kgH2Om-2day-1", + "descriptions": "Potential evaporation of surface" + }, + { + "codes": 245, + "names": "FLD_to_pondw", + "units": "kgH2Om-2day-1", + "descriptions": "Water flux from flooding to pondw" + }, + { + "codes": 246, + "names": "FLD_to_soilw", + "units": "kgH2Om-2day-1", + "descriptions": "Water flux from flooding to soilw" + }, + { + "codes": 300, + "names": "leafcSUM_phenphase_0", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 1" + }, + { + "codes": 301, + "names": "leafcSUM_phenphase_1", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 2" + }, + { + "codes": 302, + "names": "leafcSUM_phenphase_2", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 3" + }, + { + "codes": 303, + "names": "leafcSUM_phenphase_3", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 4" + }, + { + "codes": 304, + "names": "leafcSUM_phenphase_4", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 5" + }, + { + "codes": 305, + "names": "leafcSUM_phenphase_5", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 6" + }, + { + "codes": 306, + "names": "leafcSUM_phenphase_6", + "units": "kgCm-2", + "descriptions": "SUM of leaf C content in phen.phase 7" + }, + { + "codes": 307, + "names": "leafc", + "units": "kgCm-2", + "descriptions": "Actual C content of leaf pool" + }, + { + "codes": 308, + "names": "leafc_storage", + "units": "kgCm-2", + "descriptions": "C content of leaf storage pool" + }, + { + "codes": 309, + "names": "leafc_transfer", + "units": "kgCm-2", + "descriptions": "C content of leaf transfer pool" + }, + { + "codes": 310, + "names": "frootc", + "units": "kgCm-2", + "descriptions": "Actual C content of fine root pool" + }, + { + "codes": 311, + "names": "frootc_storage", + "units": "kgCm-2", + "descriptions": "C content of fine root storage pool" + }, + { + "codes": 312, + "names": "frootc_transfer", + "units": "kgCm-2", + "descriptions": "C content of fine root storage pool" + }, + { + "codes": 313, + "names": "yieldc", + "units": "kgCm-2", + "descriptions": "Actual C content of yield pool" + }, + { + "codes": 314, + "names": "yieldc_storage", + "units": "kgCm-2", + "descriptions": "C content of yield storage pool" + }, + { + "codes": 315, + "names": "yieldc_transfer", + "units": "kgCm-2", + "descriptions": "C content of yield transfer pool" + }, + { + "codes": 316, + "names": "softstemc", + "units": "kgCm-2", + "descriptions": "Actual C content of softstem pool" + }, + { + "codes": 317, + "names": "softstemc_storage", + "units": "kgCm-2", + "descriptions": "C content of softstem storage pool" + }, + { + "codes": 318, + "names": "softstemc_transfer", + "units": "kgCm-2", + "descriptions": "C content of softstem transfer pool" + }, + { + "codes": 319, + "names": "livestemc", + "units": "kgCm-2", + "descriptions": "Actual C content of live stem pool" + }, + { + "codes": 320, + "names": "livestemc_storage", + "units": "kgCm-2", + "descriptions": "C content of live stem storage pool" + }, + { + "codes": 321, + "names": "livestemc_transfer", + "units": "kgCm-2", + "descriptions": "C content of live stem transfer pool" + }, + { + "codes": 322, + "names": "deadstemc", + "units": "kgCm-2", + "descriptions": "Actual C content of dead stem pool" + }, + { + "codes": 323, + "names": "deadstemc_storage", + "units": "kgCm-2", + "descriptions": "C content of dead stem storage pool" + }, + { + "codes": 324, + "names": "deadstemc_transfer", + "units": "kgCm-2", + "descriptions": "C content of dead stem transfer pool" + }, + { + "codes": 325, + "names": "livecrootc", + "units": "kgCm-2", + "descriptions": "Actual C content of live coarse root pool" + }, + { + "codes": 326, + "names": "livecrootc_storage", + "units": "kgCm-2", + "descriptions": "C content of live coarse root storge pool" + }, + { + "codes": 327, + "names": "livecrootc_transfer", + "units": "kgCm-2", + "descriptions": "C content of live coarse root transfer pool" + }, + { + "codes": 328, + "names": "deadcrootc", + "units": "kgCm-2", + "descriptions": "Actual C content of dead coarse root pool" + }, + { + "codes": 329, + "names": "deadcrootc_storage", + "units": "kgCm-2", + "descriptions": "C content of dead coarse root storage pool" + }, + { + "codes": 330, + "names": "deadcrootc_transfer", + "units": "kgCm-2", + "descriptions": "C content of dead coarse root transfer pool" + }, + { + "codes": 331, + "names": "gresp_storage", + "units": "kgCm-2", + "descriptions": "growth respiration storage pool" + }, + { + "codes": 332, + "names": "gresp_transfer", + "units": "kgCm-2", + "descriptions": "growth respiration transfer pool" + }, + { + "codes": 333, + "names": "nsc_w", + "units": "kgCm-2", + "descriptions": "Non-structured woody carbohydrate pool" + }, + { + "codes": 334, + "names": "nsc_nw", + "units": "kgCm-2", + "descriptions": "Non-structured non-woody carbohydrate pool" + }, + { + "codes": 335, + "names": "sc_w", + "units": "kgCm-2", + "descriptions": "Structured woody carbohydrate pool" + }, + { + "codes": 336, + "names": "sc_nw", + "units": "kgCm-2", + "descriptions": "Structured non-woody carbohydrate pool" + }, + { + "codes": 337, + "names": "cwdc_0", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 1 (0-3 cm)" + }, + { + "codes": 338, + "names": "cwdc_1", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 2 (3-10 cm)" + }, + { + "codes": 339, + "names": "cwdc_2", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 3 (10-30 cm)" + }, + { + "codes": 340, + "names": "cwdc_3", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 4 (30-60 cm)" + }, + { + "codes": 341, + "names": "cwdc_4", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 5 (60-90 cm)" + }, + { + "codes": 342, + "names": "cwdc_5", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 6 (90-120 cm)" + }, + { + "codes": 343, + "names": "cwdc_6", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 7 (120-150 cm)" + }, + { + "codes": 344, + "names": "cwdc_7", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 8 (150-200 cm)" + }, + { + "codes": 345, + "names": "cwdc_8", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 9 (200-400 cm)" + }, + { + "codes": 346, + "names": "cwdc_9", + "units": "kgCm-2", + "descriptions": "Coarse woody debris in soil layer 10 (400-1000 cm)" + }, + { + "codes": 347, + "names": "litr1c_0", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 348, + "names": "litr1c_1", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 349, + "names": "litr1c_2", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 350, + "names": "litr1c_3", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 351, + "names": "litr1c_4", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 5 (60-90 c" + }, + { + "codes": 352, + "names": "litr1c_5", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 353, + "names": "litr1c_6", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 354, + "names": "litr1c_7", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 355, + "names": "litr1c_8", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 356, + "names": "litr1c_9", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 357, + "names": "litr2c_0", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 358, + "names": "litr2c_1", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 359, + "names": "litr2c_2", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 360, + "names": "litr2c_3", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 361, + "names": "litr2c_4", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 362, + "names": "litr2c_5", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 363, + "names": "litr2c_6", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 364, + "names": "litr2c_7", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 365, + "names": "litr2c_8", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 366, + "names": "litr2c_9", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 367, + "names": "litr3c_0", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 368, + "names": "litr3c_1", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 369, + "names": "litr3c_2", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 370, + "names": "litr3c_3", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 371, + "names": "litr3c_4", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 372, + "names": "litr3c_5", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 373, + "names": "litr3c_6", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 374, + "names": "litr3c_7", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 375, + "names": "litr3c_8", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 376, + "names": "litr3c_9", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 377, + "names": "litr4c_0", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 378, + "names": "litr4c_1", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 379, + "names": "litr4c_2", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 380, + "names": "litr4c_3", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 381, + "names": "litr4c_4", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 382, + "names": "litr4c_5", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 383, + "names": "litr4c_6", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 384, + "names": "litr4c_7", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 385, + "names": "litr4c_8", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 386, + "names": "litr4c_9", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 387, + "names": "litrC_0", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 1 (0-3 cm)" + }, + { + "codes": 388, + "names": "litrC_1", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 2 (3-10 cm)" + }, + { + "codes": 389, + "names": "litrC_2", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 3 (10-30 cm)" + }, + { + "codes": 390, + "names": "litrC_3", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 4 (30-60 cm)" + }, + { + "codes": 391, + "names": "litrC_4", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 5 (60-90 cm)" + }, + { + "codes": 392, + "names": "litrC_5", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 6 (90-120 cm)" + }, + { + "codes": 393, + "names": "litrC_6", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 7 (120-150 cm)" + }, + { + "codes": 394, + "names": "litrC_7", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 8 (150-200 cm)" + }, + { + "codes": 395, + "names": "litrC_8", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 9 (200-400 cm)" + }, + { + "codes": 396, + "names": "litrC_9", + "units": "kgCm-2", + "descriptions": "Total litter content in soil layer 10 (400-1000 cm)" + }, + { + "codes": 397, + "names": "litr1c_total", + "units": "kgCm-2", + "descriptions": "Labile C proportion of litter" + }, + { + "codes": 398, + "names": "litr2c_total", + "units": "kgCm-2", + "descriptions": "Unshielded cellulose proportion of litter" + }, + { + "codes": 399, + "names": "litr3c_total", + "units": "kgCm-2", + "descriptions": "Shielded cellulose proportion of litter" + }, + { + "codes": 400, + "names": "litr4c_total", + "units": "kgCm-2", + "descriptions": "Lignin proportion of litter" + }, + { + "codes": 401, + "names": "cwdc_total", + "units": "kgCm-2", + "descriptions": "Total C content of coarse woody debris" + }, + { + "codes": 402, + "names": "STDBc_leaf", + "units": "kgCm-2", + "descriptions": "Wilted leaf biomass" + }, + { + "codes": 403, + "names": "STDBc_froot", + "units": "kgCm-2", + "descriptions": "Wilted fine root biomass" + }, + { + "codes": 404, + "names": "STDBc_yield", + "units": "kgCm-2", + "descriptions": "Wilted yield biomass" + }, + { + "codes": 405, + "names": "STDBc_softstem", + "units": "kgCm-2", + "descriptions": "Wilted softstem biomass" + }, + { + "codes": 406, + "names": "CWEsnk_C", + "units": "kgCm-2", + "descriptions": "C content of CWD-extract (sink)" + }, + { + "codes": 407, + "names": "STDBc_above", + "units": "kgCm-2", + "descriptions": "Wilted aboveground plant biomass" + }, + { + "codes": 408, + "names": "STDBc_below", + "units": "kgCm-2", + "descriptions": "Wilted belowground plant biomass" + }, + { + "codes": 409, + "names": "CTDBc_leaf", + "units": "kgCm-2", + "descriptions": "Cut-down leaf biomass" + }, + { + "codes": 410, + "names": "CTDBc_froot", + "units": "kgCm-2", + "descriptions": "Cut-down fineroot biomass" + }, + { + "codes": 411, + "names": "CTDBc_yield", + "units": "kgCm-2", + "descriptions": "Cut-down yield biomass" + }, + { + "codes": 412, + "names": "CTDBc_softstem", + "units": "kgCm-2", + "descriptions": "Cut-down softstem biomass" + }, + { + "codes": 413, + "names": "MULsrc_C", + "units": "kgCm-2", + "descriptions": "C content of mulched material" + }, + { + "codes": 414, + "names": "CTDBc_cstem", + "units": "kgCm-2", + "descriptions": "Cut-down coarse stem biomass" + }, + { + "codes": 415, + "names": "CTDBc_croot", + "units": "kgCm-2", + "descriptions": "Cut-down coarse root biomass" + }, + { + "codes": 416, + "names": "CTDBc_above", + "units": "kgCm-2", + "descriptions": "Cut-down aboveground plant biomass" + }, + { + "codes": 417, + "names": "CTDBc_below", + "units": "kgCm-2", + "descriptions": "Cut-down belowground plant biomass" + }, + { + "codes": 418, + "names": "soil1c_0", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 419, + "names": "soil1c_1", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 420, + "names": "soil1c_2", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 421, + "names": "soil1c_3", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 422, + "names": "soil1c_4", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 423, + "names": "soil1c_5", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 424, + "names": "soil1c_6", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 425, + "names": "soil1c_7", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 426, + "names": "soil1c_8", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 427, + "names": "soil1c_9", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 428, + "names": "soil2c_0", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 429, + "names": "soil2c_1", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 430, + "names": "soil2c_2", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 431, + "names": "soil2c_3", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 432, + "names": "soil2c_4", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 433, + "names": "soil2c_5", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 434, + "names": "soil2c_6", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 435, + "names": "soil2c_7", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 436, + "names": "soil2c_8", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 437, + "names": "soil2c_9", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 438, + "names": "soil3c_0", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 439, + "names": "soil3c_1", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 440, + "names": "soil3c_2", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 441, + "names": "soil3c_3", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 442, + "names": "soil3c_4", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 443, + "names": "soil3c_5", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 444, + "names": "soil3c_6", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 445, + "names": "soil3c_7", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 446, + "names": "soil3c_8", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 447, + "names": "soil3c_9", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 448, + "names": "soil4c_0", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 449, + "names": "soil4c_1", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 450, + "names": "soil4c_2", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 451, + "names": "soil4c_3", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 452, + "names": "soil4c_4", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 453, + "names": "soil4c_5", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 454, + "names": "soil4c_6", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 455, + "names": "soil4c_7", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 456, + "names": "soil4c_8", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 457, + "names": "soil4c_9", + "units": "kgCm-2", + "descriptions": "C content of SOM pool in soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 458, + "names": "soilC_0", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 1 (0-3 cm)" + }, + { + "codes": 459, + "names": "soilC_1", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 2 (3-10 cm)" + }, + { + "codes": 460, + "names": "soilC_2", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 3 (10-30 cm)" + }, + { + "codes": 461, + "names": "soilC_3", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 4 (30-60 cm)" + }, + { + "codes": 462, + "names": "soilC_4", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 5 (60-90 cm)" + }, + { + "codes": 463, + "names": "soilC_5", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 6 (90-120 cm)" + }, + { + "codes": 464, + "names": "soilC_6", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 7 (120-150 cm)" + }, + { + "codes": 465, + "names": "soilC_7", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 8 (150-200 cm)" + }, + { + "codes": 466, + "names": "soilC_8", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 9 (200-400 cm)" + }, + { + "codes": 467, + "names": "soilC_9", + "units": "kgCm-2", + "descriptions": "Total C content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 468, + "names": "soil1DOC_0", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 469, + "names": "soil1DOC_1", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 470, + "names": "soil1DOC_2", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 471, + "names": "soil1DOC_3", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 472, + "names": "soil1DOC_4", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 473, + "names": "soil1DOC_5", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 474, + "names": "soil1DOC_6", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 475, + "names": "soil1DOC_7", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 476, + "names": "soil1DOC_8", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 477, + "names": "soil1DOC_9", + "units": "kgCm-2", + "descriptions": "Dissolved C content of labile SOM pool in soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 478, + "names": "soil2DOC_0", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 479, + "names": "soil2DOC_1", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 480, + "names": "soil2DOC_2", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 481, + "names": "soil2DOC_3", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 482, + "names": "soil2DOC_4", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 483, + "names": "soil2DOC_5", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 484, + "names": "soil2DOC_6", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 485, + "names": "soil2DOC_7", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 486, + "names": "soil2DOC_8", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 487, + "names": "soil2DOC_9", + "units": "kgCm-2", + "descriptions": "Dissolved C content of fast SOM pool in soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 488, + "names": "soil3DOC_0", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 489, + "names": "soil3DOC_1", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 490, + "names": "soil3DOC_2", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 491, + "names": "soil3DOC_3", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 492, + "names": "soil3DOC_4", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 493, + "names": "soil3DOC_5", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 494, + "names": "soil3DOC_6", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 495, + "names": "soil3DOC_7", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 496, + "names": "soil3DOC_8", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 497, + "names": "soil3DOC_9", + "units": "kgCm-2", + "descriptions": "Dissolved C content of slow SOM pool in soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 498, + "names": "soil4DOC_0", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 499, + "names": "soil4DOC_1", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 500, + "names": "soil4DOC_2", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 501, + "names": "soil4DOC_3", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 502, + "names": "soil4DOC_4", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 503, + "names": "soil4DOC_5", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 504, + "names": "soil4DOC_6", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 505, + "names": "soil4DOC_7", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 506, + "names": "soil4DOC_8", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 507, + "names": "soil4DOC_9", + "units": "kgCm-2", + "descriptions": "Dissolved C content of stable SOM pool in soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 508, + "names": "soilDOC_0", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 509, + "names": "soilDOC_1", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 510, + "names": "soilDOC_2", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 511, + "names": "soilDOC_3", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 512, + "names": "soilDOC_4", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 513, + "names": "soilDOC_5", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 514, + "names": "soilDOC_6", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 515, + "names": "soilDOC_7", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 516, + "names": "soilDOC_8", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 517, + "names": "soilDOC_9", + "units": "kgCm-2", + "descriptions": "Dissolved C content of total SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 518, + "names": "soil1c_total", + "units": "kgCm-2", + "descriptions": "C content of SOM (labile)" + }, + { + "codes": 519, + "names": "soil2c_total", + "units": "kgCm-2", + "descriptions": "C content of SOM (fast)" + }, + { + "codes": 520, + "names": "soil3c_total", + "units": "kgCm-2", + "descriptions": "C content of SOM (slow)" + }, + { + "codes": 521, + "names": "soil4c_total", + "units": "kgCm-2", + "descriptions": "C content of SOM (stable)" + }, + { + "codes": 522, + "names": "cpool", + "units": "kgCm-2", + "descriptions": "Temporary photosynthate C pool" + }, + { + "codes": 523, + "names": "psnsun_src", + "units": "kgCm-2", + "descriptions": "gross photosynthesis from sunlit canopy" + }, + { + "codes": 524, + "names": "psnshade_src", + "units": "kgCm-2", + "descriptions": "gross photosynthesis from shaded canopy" + }, + { + "codes": 525, + "names": "NSC_MR_snk", + "units": "kgCm-2", + "descriptions": "Non-structured carbohydrate MR loss" + }, + { + "codes": 526, + "names": "actC_MR_snk", + "units": "kgCm-2", + "descriptions": "MR loss from actual C pool" + }, + { + "codes": 527, + "names": "leaf_MR_snk", + "units": "kgCm-2", + "descriptions": "Leaf maintenance respiration" + }, + { + "codes": 528, + "names": "froot_MR_snk", + "units": "kgCm-2", + "descriptions": "Fine root maintenance respiration" + }, + { + "codes": 529, + "names": "yield_MR_snk", + "units": "kgCm-2", + "descriptions": "yield maintenance respiration" + }, + { + "codes": 530, + "names": "softstem_MR_snk", + "units": "kgCm-2", + "descriptions": "Softstem maintenance respiration" + }, + { + "codes": 531, + "names": "livestem_MR_snk", + "units": "kgCm-2", + "descriptions": "Live stem maintenance respiration" + }, + { + "codes": 532, + "names": "livecroot_MR_snk", + "units": "kgCm-2", + "descriptions": "Live coarse root maintenance respiration" + }, + { + "codes": 533, + "names": "leaf_GR_snk", + "units": "kgCm-2", + "descriptions": "Leaf growth respiration" + }, + { + "codes": 534, + "names": "froot_GR_snk", + "units": "kgCm-2", + "descriptions": "Fine root growth respiration" + }, + { + "codes": 535, + "names": "yield_GR_snk", + "units": "kgCm-2", + "descriptions": "yield growth respiration" + }, + { + "codes": 536, + "names": "softstem_GR_snk", + "units": "kgCm-2", + "descriptions": "Softstem growth respiration" + }, + { + "codes": 537, + "names": "livestem_GR_snk", + "units": "kgCm-2", + "descriptions": "Live stem growth respiration" + }, + { + "codes": 538, + "names": "livecroot_GR_snk", + "units": "kgCm-2", + "descriptions": "Live coarse root growth respiration" + }, + { + "codes": 539, + "names": "deadstem_GR_snk", + "units": "kgCm-2", + "descriptions": "Dead stem growth respiration" + }, + { + "codes": 540, + "names": "deadcroot_GR_snk", + "units": "kgCm-2", + "descriptions": "Dead coarse root growth respiration" + }, + { + "codes": 541, + "names": "litr1_hr_snk", + "units": "kgCm-2", + "descriptions": "Labile litter microbial respiration" + }, + { + "codes": 542, + "names": "litr2_hr_snk", + "units": "kgCm-2", + "descriptions": "Cellulose litter microbial respiration" + }, + { + "codes": 543, + "names": "litr4_hr_snk", + "units": "kgCm-2", + "descriptions": "Lignin litter microbial respiration" + }, + { + "codes": 544, + "names": "soil1_hr_snk", + "units": "kgCm-2", + "descriptions": "Respiration of labile SOM" + }, + { + "codes": 545, + "names": "soil2_hr_snk", + "units": "kgCm-2", + "descriptions": "Respiration of fast SOM" + }, + { + "codes": 546, + "names": "soil3_hr_snk", + "units": "kgCm-2", + "descriptions": "Respiration of slow SOM" + }, + { + "codes": 547, + "names": "soil4_hr_snk", + "units": "kgCm-2", + "descriptions": "Respiration of stable SOM" + }, + { + "codes": 548, + "names": "FIREsnk_C", + "units": "kgCm-2", + "descriptions": "Fire C losses" + }, + { + "codes": 549, + "names": "SNSCsnk_C", + "units": "kgCm-2", + "descriptions": "Senescence C losses" + }, + { + "codes": 550, + "names": "PLTsrc_C", + "units": "kgCm-2", + "descriptions": "C content of planted plant material" + }, + { + "codes": 551, + "names": "THN_transportC", + "units": "kgCm-2", + "descriptions": "C content of thinned and transported plant material" + }, + { + "codes": 552, + "names": "HRV_transportC", + "units": "kgCm-2", + "descriptions": "C content of harvested and transported plant material" + }, + { + "codes": 553, + "names": "MOW_transportC", + "units": "kgCm-2", + "descriptions": "C content of mowed and transported plant material" + }, + { + "codes": 554, + "names": "GRZsnk_C", + "units": "kgCm-2", + "descriptions": "C content of grazed leaf" + }, + { + "codes": 555, + "names": "GRZsrc_C", + "units": "kgCm-2", + "descriptions": "Added C from fertilizer" + }, + { + "codes": 556, + "names": "FRZsrc_C", + "units": "kgCm-2", + "descriptions": "C content of fertilizer return to the litter pool" + }, + { + "codes": 557, + "names": "yieldC_HRV", + "units": "kgCm-2", + "descriptions": "C content of havested yield in a year" + }, + { + "codes": 558, + "names": "vegC_HRV", + "units": "kgCm-2", + "descriptions": "C content of havested plant (leaf+stem+yield) in a year" + }, + { + "codes": 559, + "names": "CbalanceERR", + "units": "kgCm-2", + "descriptions": "C balance error" + }, + { + "codes": 560, + "names": "inC", + "units": "kgCm-2", + "descriptions": "C input" + }, + { + "codes": 561, + "names": "outC", + "units": "kgCm-2", + "descriptions": "C output" + }, + { + "codes": 562, + "names": "storeC", + "units": "kgCm-2", + "descriptions": "C store" + }, + { + "codes": 563, + "names": "Cdeepleach_snk", + "units": "kgCm-2", + "descriptions": "SUM of C deep leaching" + }, + { + "codes": 564, + "names": "cwdc_above", + "units": "kgCm-2", + "descriptions": "C content of aboveground coarse woody debris" + }, + { + "codes": 565, + "names": "litrc_above", + "units": "kgCm-2", + "descriptions": "C content of aboveground litter" + }, + { + "codes": 566, + "names": "CNratioERR", + "units": "kgCm-2", + "descriptions": "CN ratio error" + }, + { + "codes": 567, + "names": "flowHSsnk_C", + "units": "kgCm-2", + "descriptions": "C loss due to flower heat stress" + }, + { + "codes": 600, + "names": "m_leafc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from leaf to labile litter" + }, + { + "codes": 601, + "names": "m_leafc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from leaf to unshielded cellulose portion of litter" + }, + { + "codes": 602, + "names": "m_leafc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from leaf to shielded cellulose portion of litter" + }, + { + "codes": 603, + "names": "m_leafc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from leaf to lignin portion of litter" + }, + { + "codes": 604, + "names": "m_frootc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from fine root to labile litter" + }, + { + "codes": 605, + "names": "m_frootc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 606, + "names": "m_frootc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 607, + "names": "m_frootc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from fine root to lignin portion of litter" + }, + { + "codes": 608, + "names": "m_yieldc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from yield to labile litter" + }, + { + "codes": 609, + "names": "m_yieldc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from yield to unshielded cellulose portion of litter" + }, + { + "codes": 610, + "names": "m_yieldc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from yield to shielded cellulose portion of litter" + }, + { + "codes": 611, + "names": "m_yieldc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from yield to lignin portion of litter" + }, + { + "codes": 612, + "names": "m_softstemc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from softstem to labile litter" + }, + { + "codes": 613, + "names": "m_softstemc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 614, + "names": "m_softstemc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 615, + "names": "m_softstemc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from softstem to lignin portion of litter" + }, + { + "codes": 616, + "names": "m_leafc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from leaf storage pool to labile litter" + }, + { + "codes": 617, + "names": "m_frootc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from fine root storage pool to labile litter" + }, + { + "codes": 618, + "names": "m_softstemc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from softstem storage pool to labile litter" + }, + { + "codes": 619, + "names": "m_yieldc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from yield storage pool to labile litter" + }, + { + "codes": 620, + "names": "m_livestemc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from live stem storage pool to labile litter" + }, + { + "codes": 621, + "names": "m_deadstemc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from dead stem storage pool to labile litter" + }, + { + "codes": 622, + "names": "m_livecrootc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from live coarse root storage pool to labile litter" + }, + { + "codes": 623, + "names": "m_deadcrootc_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from dead coarse root storage pool to labile litter" + }, + { + "codes": 624, + "names": "m_leafc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from leaf transfer pool to labile litter" + }, + { + "codes": 625, + "names": "m_frootc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from fine root transfer pool to labile litter" + }, + { + "codes": 626, + "names": "m_yieldc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from yield transfer pool to labile litter" + }, + { + "codes": 627, + "names": "m_softstemc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from softstem transfer pool to labile litter" + }, + { + "codes": 628, + "names": "m_livestemc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from live stem transfer pool to labile litter" + }, + { + "codes": 629, + "names": "m_deadstemc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from dead stem transfer pool to labile litter" + }, + { + "codes": 630, + "names": "m_livecrootc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from live coarse root transfer pool to labile litter" + }, + { + "codes": 631, + "names": "m_deadcrootc_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from dead coarse root transfer pool to labile litter" + }, + { + "codes": 632, + "names": "m_livestemc_to_cwdc", + "units": "kgCm-2 day-1", + "descriptions": "Moartality C flux from live stem to coarse woody debris" + }, + { + "codes": 633, + "names": "m_deadstemc_to_cwdc", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from dead stem to coarse woody debris" + }, + { + "codes": 634, + "names": "m_livecrootc_to_cwdc", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from live coarse root to coarse woody debris" + }, + { + "codes": 635, + "names": "m_deadcrootc_to_cwdc", + "units": "kgCm-2 day-1", + "descriptions": "Moartality C flux from dead coarse root to coarse woody debris" + }, + { + "codes": 636, + "names": "m_gresp_storage_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from growth respiration storage pool to labile litter" + }, + { + "codes": 637, + "names": "m_gresp_transfer_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Mortality C flux from growth respiration transfer pool to labile litter" + }, + { + "codes": 638, + "names": "m_leafc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Leaf fire C flux" + }, + { + "codes": 639, + "names": "m_frootc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Fine root fire C flux" + }, + { + "codes": 640, + "names": "m_yieldc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "yield fire C flux" + }, + { + "codes": 641, + "names": "m_softstemc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Softstem fire C flux" + }, + { + "codes": 642, + "names": "m_STDBc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Wilted plant biomass fire C flux" + }, + { + "codes": 643, + "names": "m_CTDBc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down plant biomass fire C flux" + }, + { + "codes": 644, + "names": "m_leafc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Leaf storage pool fire C flux" + }, + { + "codes": 645, + "names": "m_frootc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Fine root storage pool fire C flux" + }, + { + "codes": 646, + "names": "m_yieldc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "yield storage pool fire C flux" + }, + { + "codes": 647, + "names": "m_softstemc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Softstem storage pool fire C flux" + }, + { + "codes": 648, + "names": "m_livestemc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Live stem storage pool fire C flux" + }, + { + "codes": 649, + "names": "m_deadstemc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Dead stem storage pool fire C flux" + }, + { + "codes": 650, + "names": "m_livecrootc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Live coarse root storage pool fire C flux" + }, + { + "codes": 651, + "names": "m_deadcrootc_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Dead coarse root storage pool fire C flux" + }, + { + "codes": 652, + "names": "m_leafc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Leaf transfer pool fire C flux" + }, + { + "codes": 653, + "names": "m_frootc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Fine root transfer pool fire C flux" + }, + { + "codes": 654, + "names": "m_yieldc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "yield transfer pool fire C flux" + }, + { + "codes": 655, + "names": "m_softstemc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Softstem transfer pool fire C flux" + }, + { + "codes": 656, + "names": "m_livestemc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Live stem transfer pool fire C flux" + }, + { + "codes": 657, + "names": "m_deadstemc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Dead stem transfer pool fire C flux" + }, + { + "codes": 658, + "names": "m_livecrootc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Live coarse root transfer pool fire C flux" + }, + { + "codes": 659, + "names": "m_deadcrootc_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Dead coarse root transfer pool fire C flux" + }, + { + "codes": 660, + "names": "m_livestemc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Live stem fire C flux" + }, + { + "codes": 661, + "names": "m_deadstemc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Dead stem fire C flux" + }, + { + "codes": 662, + "names": "m_livecrootc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Live coarse root fire C flux" + }, + { + "codes": 663, + "names": "m_deadcrootc_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "Dead coarse root fire C flux" + }, + { + "codes": 664, + "names": "m_gresp_storage_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "growth respiration storage pool fire C flux" + }, + { + "codes": 665, + "names": "m_gresp_transfer_to_fire", + "units": "kgCm-2 day-1", + "descriptions": "growth respiration transfer pool fire C flux" + }, + { + "codes": 666, + "names": "m_litr1c_to_fire_total", + "units": "kgCm-2 day-1", + "descriptions": "labile litter fire C flux" + }, + { + "codes": 667, + "names": "m_litr2c_to_fire_total", + "units": "kgCm-2 day-1", + "descriptions": "Unshielded cellulose portion of litter fire C flux" + }, + { + "codes": 668, + "names": "m_litr3c_to_fire_total", + "units": "kgCm-2 day-1", + "descriptions": "Shielded cellulose portion of litter fire C flux" + }, + { + "codes": 669, + "names": "m_litr4c_to_fire_total", + "units": "kgCm-2 day-1", + "descriptions": "Lignin portion of litter fire C flux" + }, + { + "codes": 670, + "names": "m_cwdc_to_fire_total", + "units": "kgCm-2 day-1", + "descriptions": "Coarse woody debris fire C flux" + }, + { + "codes": 671, + "names": "m_vegc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Total vegetation senescence C flux" + }, + { + "codes": 672, + "names": "m_leafc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Leaf senescence C flux" + }, + { + "codes": 673, + "names": "m_leafc_to_SNSCgenprog", + "units": "kgCm-2 day-1", + "descriptions": "Leaf gen. prog. scenescene C flux" + }, + { + "codes": 674, + "names": "m_frootc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Fine root senescene C flux" + }, + { + "codes": 675, + "names": "m_yieldc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "yield senescence C flux" + }, + { + "codes": 676, + "names": "m_softstemc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Softstem senescence C flux" + }, + { + "codes": 677, + "names": "m_leafc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Leaf storage pool senescence C flux" + }, + { + "codes": 678, + "names": "m_frootc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Fine root storage pool senescence C flux" + }, + { + "codes": 679, + "names": "m_leafc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Leaf transfer pool senescence C flux" + }, + { + "codes": 680, + "names": "m_frootc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Fine root transfer pool senescence C flux" + }, + { + "codes": 681, + "names": "m_yieldc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "yield storage pool senescence C flux" + }, + { + "codes": 682, + "names": "m_yieldc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "yield transfer pool senescence C flux" + }, + { + "codes": 683, + "names": "m_softstemc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Softstem storage pool senescence C flux" + }, + { + "codes": 684, + "names": "m_softstemc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Softstem transfer pool senescence C flux" + }, + { + "codes": 685, + "names": "m_gresp_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "growth respiration storage pool senescence C flux" + }, + { + "codes": 686, + "names": "m_gresp_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "growth respiration transfer pool senescence C flux" + }, + { + "codes": 687, + "names": "HRV_leafc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested leaf storage pool senescence C flux" + }, + { + "codes": 688, + "names": "HRV_leafc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested leaf transfer pool senescence C flux" + }, + { + "codes": 689, + "names": "HRV_yieldc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested yield storage pool senescence C flux" + }, + { + "codes": 690, + "names": "HRV_yieldc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested yield transfer pool senescence C flux" + }, + { + "codes": 691, + "names": "HRV_frootc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested fine root senescence C flux" + }, + { + "codes": 692, + "names": "HRV_softstemc_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested softstem senscence C flux" + }, + { + "codes": 693, + "names": "HRV_frootc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested fine root storage senescence C flux" + }, + { + "codes": 694, + "names": "HRV_frootc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested fine root transfer senescence C flux" + }, + { + "codes": 695, + "names": "HRV_softstemc_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested softstem storage senescence C flux" + }, + { + "codes": 696, + "names": "HRV_softstemc_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested softstem transfer senescence C flux" + }, + { + "codes": 697, + "names": "HRV_gresp_storage_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested growth respiration storage pool senescence C flux" + }, + { + "codes": 698, + "names": "HRV_gresp_transfer_to_SNSC", + "units": "kgCm-2 day-1", + "descriptions": "Harvested growth respiration transfer pool senescence C flux" + }, + { + "codes": 699, + "names": "yieldc_to_flowHS", + "units": "kgCm-2 day-1", + "descriptions": "C flux from yield flowering heat stress" + }, + { + "codes": 700, + "names": "STDBc_leaf_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Leaf standing dead biomass C flux to litter" + }, + { + "codes": 701, + "names": "STDBc_froot_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Fine root standing dead biomass C flux to litter" + }, + { + "codes": 702, + "names": "STDBc_yield_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "yield standing dead biomass C flux to litter" + }, + { + "codes": 703, + "names": "STDBc_softstem_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Softstem standing dead biomass C flux to litter" + }, + { + "codes": 705, + "names": "STDBc_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Standing dead biomass C flux to litter" + }, + { + "codes": 706, + "names": "CTDBc_leaf_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down leaf dead biomass C flux to litter" + }, + { + "codes": 707, + "names": "CTDBc_froot_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down fine root dead biomass C flux to litter" + }, + { + "codes": 708, + "names": "CTDBc_yield_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down yield dead biomass C flux to litter" + }, + { + "codes": 709, + "names": "CTDBc_softstem_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down softstem dead biomass C flux to litter" + }, + { + "codes": 711, + "names": "CTDBc_cstem_to_cwd", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down coarse stem dead biomass C flux to coarse woody debris" + }, + { + "codes": 712, + "names": "CTDBc_croot_to_cwd", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down coarse root dead biomass C flux to coarse woody debris" + }, + { + "codes": 713, + "names": "CTDBc_to_litr", + "units": "kgCm-2 day-1", + "descriptions": "Cut-down dead biomass C flux to litter" + }, + { + "codes": 714, + "names": "leafc_transfer_to_leafc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from leaf transfer pool to leaf" + }, + { + "codes": 715, + "names": "frootc_transfer_to_frootc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from fine root transfer pool to fine root" + }, + { + "codes": 716, + "names": "yieldc_transfer_to_yield", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from yield transfer pool to yield" + }, + { + "codes": 717, + "names": "softstemc_transfer_to_softstemc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from softstem transfer pool to softstem" + }, + { + "codes": 718, + "names": "livestemc_transfer_to_livestemc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from live stem transfer pool to live stem" + }, + { + "codes": 719, + "names": "deadstemc_transfer_to_deadstemc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from dead stem transfer to dead stem" + }, + { + "codes": 720, + "names": "livecrootc_transfer_to_livecrootc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from live coarse root transfer pool to live coarse root" + }, + { + "codes": 721, + "names": "deadcrootc_transfer_to_deadcrootc", + "units": "kgCm-2 day-1", + "descriptions": "Phenology C flux from dead coarse root transfer pool to dead coarse root" + }, + { + "codes": 722, + "names": "leafc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from leaf to labile litter" + }, + { + "codes": 723, + "names": "leafc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from leaf to unshielded cellulose portion of litter" + }, + { + "codes": 724, + "names": "leafc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from leaf to shielded cellulose portion of litter" + }, + { + "codes": 725, + "names": "leafc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from leaf to lignin portion of litter" + }, + { + "codes": 726, + "names": "frootc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fine root to labile litter" + }, + { + "codes": 727, + "names": "frootc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 728, + "names": "frootc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 729, + "names": "frootc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fine root to lignin portion of litter" + }, + { + "codes": 730, + "names": "yieldc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from yield to labile litter" + }, + { + "codes": 731, + "names": "yieldc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from yield to unshielded cellulose portion of litter" + }, + { + "codes": 732, + "names": "yieldc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from yield to shielded cellulose portion of litter" + }, + { + "codes": 733, + "names": "yieldc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from yield to lignin portion of litter" + }, + { + "codes": 734, + "names": "softstemc_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from softstem to labile litter" + }, + { + "codes": 735, + "names": "softstemc_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 736, + "names": "softstemc_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 737, + "names": "softstemc_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "C flux from softstem to lignin portion of litter" + }, + { + "codes": 738, + "names": "leaf_day_MR", + "units": "kgCm-2 day-1", + "descriptions": "Leaf daylight maintenance respiration" + }, + { + "codes": 739, + "names": "leaf_night_MR", + "units": "kgCm-2 day-1", + "descriptions": "Leaf night maintenance respiration" + }, + { + "codes": 740, + "names": "froot_MR", + "units": "kgCm-2 day-1", + "descriptions": "Fine root maintenance respiration" + }, + { + "codes": 741, + "names": "yield_MR", + "units": "kgCm-2 day-1", + "descriptions": "yield maintenance repsiration" + }, + { + "codes": 742, + "names": "softstem_MR", + "units": "kgCm-2 day-1", + "descriptions": "Softstem maintenance respiration" + }, + { + "codes": 743, + "names": "livestem_MR", + "units": "kgCm-2 day-1", + "descriptions": "Live stem maintenance respiration" + }, + { + "codes": 744, + "names": "livecroot_MR", + "units": "kgCm-2 day-1", + "descriptions": "Live coarse root maintenance respiration" + }, + { + "codes": 745, + "names": "psnsun_to_cpool", + "units": "kgCm-2 day-1", + "descriptions": "C flux to temporary photosynthate C pool by sunlight" + }, + { + "codes": 746, + "names": "psnshade_to_cpool", + "units": "kgCm-2 day-1", + "descriptions": "C flux to temporary photosynthate C pool by sunshade" + }, + { + "codes": 747, + "names": "cwdc_to_litr2c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose part of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 748, + "names": "cwdc_to_litr2c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 749, + "names": "cwdc_to_litr2c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 750, + "names": "cwdc_to_litr2c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 751, + "names": "cwdc_to_litr2c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 752, + "names": "cwdc_to_litr2c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 753, + "names": "cwdc_to_litr2c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 754, + "names": "cwdc_to_litr2c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 755, + "names": "cwdc_to_litr2c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 756, + "names": "cwdc_to_litr2c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to unshielded cellulose portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 757, + "names": "cwdc_to_litr3c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 758, + "names": "cwdc_to_litr3c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 759, + "names": "cwdc_to_litr3c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 760, + "names": "cwdc_to_litr3c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 761, + "names": "cwdc_to_litr3c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 762, + "names": "cwdc_to_litr3c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 763, + "names": "cwdc_to_litr3c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 764, + "names": "cwdc_to_litr3c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 765, + "names": "cwdc_to_litr3c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 766, + "names": "cwdc_to_litr3c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to shielded cellulose portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 767, + "names": "cwdc_to_litr4c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 768, + "names": "cwdc_to_litr4c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 769, + "names": "cwdc_to_litr4c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 770, + "names": "cwdc_to_litr4c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 771, + "names": "cwdc_to_litr4c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 772, + "names": "cwdc_to_litr4c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 773, + "names": "cwdc_to_litr4c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 774, + "names": "cwdc_to_litr4c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 775, + "names": "cwdc_to_litr4c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 776, + "names": "cwdc_to_litr4c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from coarse woody debris to lignin portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 777, + "names": "litr1_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 778, + "names": "litr1_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 779, + "names": "litr1_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 780, + "names": "litr1_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 781, + "names": "litr1_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 782, + "names": "litr1_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 783, + "names": "litr1_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 784, + "names": "litr1_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 785, + "names": "litr1_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 786, + "names": "litr1_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 787, + "names": "litr1c_to_soil1c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 788, + "names": "litr1c_to_soil1c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 789, + "names": "litr1c_to_soil1c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 790, + "names": "litr1c_to_soil1c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 791, + "names": "litr1c_to_soil1c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 792, + "names": "litr1c_to_soil1c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 793, + "names": "litr1c_to_soil1c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 794, + "names": "litr1c_to_soil1c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 795, + "names": "litr1c_to_soil1c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 796, + "names": "litr1c_to_soil1c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile litter to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 797, + "names": "litr2_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose soil layer 1 (0-3 cm)" + }, + { + "codes": 798, + "names": "litr2_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 2 (3-10 cm)" + }, + { + "codes": 799, + "names": "litr2_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 3 (10-30 cm)" + }, + { + "codes": 800, + "names": "litr2_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 4 (30-60 cm)" + }, + { + "codes": 801, + "names": "litr2_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 5 (60-90 cm)" + }, + { + "codes": 802, + "names": "litr2_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 6 (90-120 cm)" + }, + { + "codes": 803, + "names": "litr2_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 7 (120-150 cm)" + }, + { + "codes": 804, + "names": "litr2_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 8 (150-200 cm)" + }, + { + "codes": 805, + "names": "litr2_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 9 (200-400 cm)" + }, + { + "codes": 806, + "names": "litr2_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose in soil layer 10 (400-1000 cm)" + }, + { + "codes": 807, + "names": "litr2c_to_soil2c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 808, + "names": "litr2c_to_soil2c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 809, + "names": "litr2c_to_soil2c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 810, + "names": "litr2c_to_soil2c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 811, + "names": "litr2c_to_soil2c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 812, + "names": "litr2c_to_soil2c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 813, + "names": "litr2c_to_soil2c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 814, + "names": "litr2c_to_soil2c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 815, + "names": "litr2c_to_soil2c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 816, + "names": "litr2c_to_soil2c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from unshielded cellulose portion of litter to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 817, + "names": "litr3c_to_litr2c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 818, + "names": "litr3c_to_litr2c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 819, + "names": "litr3c_to_litr2c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 820, + "names": "litr3c_to_litr2c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 821, + "names": "litr3c_to_litr2c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 822, + "names": "litr3c_to_litr2c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 823, + "names": "litr3c_to_litr2c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 824, + "names": "litr3c_to_litr2c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 825, + "names": "litr3c_to_litr2c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 826, + "names": "litr3c_to_litr2c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 827, + "names": "litr4_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 828, + "names": "litr4_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 829, + "names": "litr4_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 830, + "names": "litr4_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 831, + "names": "litr4_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 832, + "names": "litr4_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 833, + "names": "litr4_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 834, + "names": "litr4_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 835, + "names": "litr4_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 836, + "names": "litr4_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 837, + "names": "litr4c_to_soil3c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 838, + "names": "litr4c_to_soil3c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 839, + "names": "litr4c_to_soil3c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 840, + "names": "litr4c_to_soil3c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 841, + "names": "litr4c_to_soil3c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 842, + "names": "litr4c_to_soil3c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 843, + "names": "litr4c_to_soil3c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 844, + "names": "litr4c_to_soil3c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 845, + "names": "litr4c_to_soil3c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 846, + "names": "litr4c_to_soil3c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from lignin portion of litter to shielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 847, + "names": "soil1_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 848, + "names": "soil1_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 849, + "names": "soil1_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 850, + "names": "soil1_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 851, + "names": "soil1_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 852, + "names": "soil1_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 853, + "names": "soil1_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 854, + "names": "soil1_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 855, + "names": "soil1_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 856, + "names": "soil1_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 857, + "names": "soil1c_to_soil2c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 858, + "names": "soil1c_to_soil2c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 859, + "names": "soil1c_to_soil2c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 860, + "names": "soil1c_to_soil2c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 861, + "names": "soil1c_to_soil2c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 862, + "names": "soil1c_to_soil2c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 863, + "names": "soil1c_to_soil2c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 864, + "names": "soil1c_to_soil2c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 865, + "names": "soil1c_to_soil2c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 866, + "names": "soil1c_to_soil2c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from labile to fast SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 867, + "names": "soil2_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 868, + "names": "soil2_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer (3-10 cm)" + }, + { + "codes": 869, + "names": "soil2_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 870, + "names": "soil2_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 871, + "names": "soil2_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 872, + "names": "soil2_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 873, + "names": "soil2_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 874, + "names": "soil2_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 875, + "names": "soil2_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 876, + "names": "soil2_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil layer 1 (400-1000 cm)" + }, + { + "codes": 877, + "names": "soil2c_to_soil3c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 878, + "names": "soil2c_to_soil3c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 879, + "names": "soil2c_to_soil3c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 880, + "names": "soil2c_to_soil3c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 881, + "names": "soil2c_to_soil3c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 882, + "names": "soil2c_to_soil3c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 883, + "names": "soil2c_to_soil3c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 884, + "names": "soil2c_to_soil3c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 885, + "names": "soil2c_to_soil3c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 886, + "names": "soil2c_to_soil3c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from fast to slow SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 887, + "names": "soil3_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 888, + "names": "soil3_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer (3-10 cm)" + }, + { + "codes": 889, + "names": "soil3_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 890, + "names": "soil3_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 891, + "names": "soil3_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 892, + "names": "soil3_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 893, + "names": "soil3_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 894, + "names": "soil3_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 895, + "names": "soil3_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 896, + "names": "soil3_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 897, + "names": "soil3c_to_soil4c_0", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 898, + "names": "soil3c_to_soil4c_1", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 2 (3-10 cm)" + }, + { + "codes": 899, + "names": "soil3c_to_soil4c_2", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 3 (10-30 cm)" + }, + { + "codes": 900, + "names": "soil3c_to_soil4c_3", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 4 (30-60 cm)" + }, + { + "codes": 901, + "names": "soil3c_to_soil4c_4", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 5 (60-90 cm)" + }, + { + "codes": 902, + "names": "soil3c_to_soil4c_5", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 6 (90-120 cm)" + }, + { + "codes": 903, + "names": "soil3c_to_soil4c_6", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 7 (120-150 cm)" + }, + { + "codes": 904, + "names": "soil3c_to_soil4c_7", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 8 (150-200 cm)" + }, + { + "codes": 905, + "names": "soil3c_to_soil4c_8", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 9 (200-400 cm)" + }, + { + "codes": 906, + "names": "soil3c_to_soil4c_9", + "units": "kgCm-2 day-1", + "descriptions": "C flux from slow to stable SOM in soil layer 10 (400-1000 cm)" + }, + { + "codes": 907, + "names": "soil4_hr_0", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 1 (0-3 cm)" + }, + { + "codes": 908, + "names": "soil4_hr_1", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 2 (3-10 cm)" + }, + { + "codes": 909, + "names": "soil4_hr_2", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 3 (10-30 cm)" + }, + { + "codes": 910, + "names": "soil4_hr_3", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 4 (30-60 cm)" + }, + { + "codes": 911, + "names": "soil4_hr_4", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 5 (60-90 cm)" + }, + { + "codes": 912, + "names": "soil4_hr_5", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 6 (90-120 cm)" + }, + { + "codes": 913, + "names": "soil4_hr_6", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 7 (120-150 cm)" + }, + { + "codes": 914, + "names": "soil4_hr_7", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 8 (150-200 cm)" + }, + { + "codes": 915, + "names": "soil4_hr_8", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 9 (200-400 cm)" + }, + { + "codes": 916, + "names": "soil4_hr_9", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 917, + "names": "soil1DOC_leach_0", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 918, + "names": "soil1DOC_leach_1", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 919, + "names": "soil1DOC_leach_2", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 920, + "names": "soil1DOC_leach_3", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 921, + "names": "soil1DOC_leach_4", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 922, + "names": "soil1DOC_leach_5", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 923, + "names": "soil1DOC_leach_6", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 924, + "names": "soil1DOC_leach_7", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 925, + "names": "soil1DOC_leach_8", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 926, + "names": "soil1DOC_leach_9", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 927, + "names": "soil2DOC_leach_0", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 928, + "names": "soil2DOC_leach_1", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 929, + "names": "soil2DOC_leach_2", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 930, + "names": "soil2DOC_leach_3", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 931, + "names": "soil2DOC_leach_4", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 932, + "names": "soil2DOC_leach_5", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 933, + "names": "soil2DOC_leach_6", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 934, + "names": "soil2DOC_leach_7", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 935, + "names": "soil2DOC_leach_8", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 936, + "names": "soil2DOC_leach_9", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 937, + "names": "soil3DOC_leach_0", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 938, + "names": "soil3DOC_leach_1", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 939, + "names": "soil3DOC_leach_2", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 940, + "names": "soil3DOC_leach_3", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 941, + "names": "soil3DOC_leach_4", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 942, + "names": "soil3DOC_leach_5", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 943, + "names": "soil3DOC_leach_6", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 944, + "names": "soil3DOC_leach_7", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 945, + "names": "soil3DOC_leach_8", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 946, + "names": "soil3DOC_leach_9", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 947, + "names": "soil4DOC_leach_0", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 948, + "names": "soil4DOC_leach_1", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 949, + "names": "soil4DOC_leach_2", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 950, + "names": "soil4DOC_leach_3", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 951, + "names": "soil4DOC_leach_4", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 952, + "names": "soil4DOC_leach_5", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 953, + "names": "soil4DOC_leach_6", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 954, + "names": "soil4DOC_leach_7", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 955, + "names": "soil4DOC_leach_8", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 956, + "names": "soil4DOC_leach_9", + "units": "kgCm-2 day-1", + "descriptions": "Leached C flux from DOC of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 957, + "names": "soilDOC_leachCUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 958, + "names": "soilDOC_leachCUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 959, + "names": "soilDOC_leachCUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 960, + "names": "soilDOC_leachCUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 961, + "names": "soilDOC_leachCUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 962, + "names": "soilDOC_leachCUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 963, + "names": "soilDOC_leachCUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 964, + "names": "soilDOC_leachCUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 965, + "names": "soilDOC_leachCUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 966, + "names": "soilDOC_leachCUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DOC of total SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 967, + "names": "DOC_leachRZ", + "units": "kgCm-2 day-1", + "descriptions": "Leached DOC from rootzone" + }, + { + "codes": 998, + "names": "cpool_to_leafc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to leaf" + }, + { + "codes": 999, + "names": "cpool_to_leafc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Dail allocation C flux from current GPP to leaf storage pool" + }, + { + "codes": 1000, + "names": "cpool_to_frootc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fine root" + }, + { + "codes": 1001, + "names": "cpool_to_frootc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to fine root storage pool" + }, + { + "codes": 1002, + "names": "cpool_to_yield", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to yield" + }, + { + "codes": 1003, + "names": "cpool_to_yieldc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to yield storage pool" + }, + { + "codes": 1004, + "names": "cpool_to_softstemc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to softstem" + }, + { + "codes": 1005, + "names": "cpool_to_softstemc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to softstem storage pool" + }, + { + "codes": 1006, + "names": "cpool_to_livestemc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live stem" + }, + { + "codes": 1007, + "names": "cpool_to_livestemc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily alloaction C flux from current GPP to live stem storage pool" + }, + { + "codes": 1008, + "names": "cpool_to_deadstemc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead stem" + }, + { + "codes": 1009, + "names": "cpool_to_deadstemc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead stem storage pool" + }, + { + "codes": 1010, + "names": "cpool_to_livecrootc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live coarse root" + }, + { + "codes": 1011, + "names": "cpool_to_livecrootc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to live coarse root storage pool" + }, + { + "codes": 1012, + "names": "cpool_to_deadcrootc", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead coarse root" + }, + { + "codes": 1013, + "names": "cpool_to_deadcrootc_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to dead coarse root storage pool" + }, + { + "codes": 1014, + "names": "cpool_to_gresp_storage", + "units": "kgCm-2 day-1", + "descriptions": "Daily allocation C flux from current GPP to growth respiration storage pool" + }, + { + "codes": 1015, + "names": "cpool_leaf_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily leaf growth respiration flux" + }, + { + "codes": 1016, + "names": "cpool_leaf_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily leaf storage pool growth respiration flux" + }, + { + "codes": 1017, + "names": "transfer_leaf_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily leaf transfer pool respiration flux" + }, + { + "codes": 1018, + "names": "cpool_froot_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily fine root growth respiration flux" + }, + { + "codes": 1019, + "names": "cpool_froot_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily fine root storage pool growth respiration flux" + }, + { + "codes": 1020, + "names": "transfer_froot_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily fine root transfer pool growth respiration flux" + }, + { + "codes": 1021, + "names": "cpool_yield_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily yield growth respiration flux" + }, + { + "codes": 1022, + "names": "cpool_yieldc_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily yield storage pool growth respiration flux" + }, + { + "codes": 1023, + "names": "transfer_yield_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily yield transfer pool gowth respiration flux" + }, + { + "codes": 1024, + "names": "cpool_softstem_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily softstem growth respiration flux" + }, + { + "codes": 1025, + "names": "cpool_softstem_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily softstem storage pool growth respiration flux" + }, + { + "codes": 1026, + "names": "transfer_softstem_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily softstem transfer pool growth respiration flux" + }, + { + "codes": 1027, + "names": "cpool_livestem_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily live stem growth respiration flux" + }, + { + "codes": 1028, + "names": "cpool_livestem_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily live stem storage pool growth respiration flux" + }, + { + "codes": 1029, + "names": "transfer_livestem_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily live stem transfer pool growth respiration flux" + }, + { + "codes": 1030, + "names": "cpool_deadstem_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily dead stem growth respiration flux" + }, + { + "codes": 1031, + "names": "cpool_deadstem_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily dead stem storage pool growth respiration flux" + }, + { + "codes": 1032, + "names": "transfer_deadstem_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily dead stem transfer pool growth respiration flux" + }, + { + "codes": 1033, + "names": "cpool_livecroot_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily live coarse root growth respiration flux" + }, + { + "codes": 1034, + "names": "cpool_livecroot_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily live coarse root storage pool growth respiration flux" + }, + { + "codes": 1035, + "names": "transfer_livecroot_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily live coarse root transfer pool growth respiration flux" + }, + { + "codes": 1036, + "names": "cpool_deadcroot_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily dead coarse root growth respiration flux" + }, + { + "codes": 1037, + "names": "cpool_deadcroot_storage_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily dead coarse root storage pool respiration flux" + }, + { + "codes": 1038, + "names": "transfer_deadcroot_GR", + "units": "kgCm-2 day-1", + "descriptions": "Daily dead coarse root transfer pool respiration flux" + }, + { + "codes": 1039, + "names": "leafc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf storage pool" + }, + { + "codes": 1040, + "names": "frootc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root storage pool" + }, + { + "codes": 1041, + "names": "yieldc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from yield storage pool" + }, + { + "codes": 1042, + "names": "softstemc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem storage pool" + }, + { + "codes": 1043, + "names": "livestemc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem storage pool" + }, + { + "codes": 1044, + "names": "livecrootc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root storage pool" + }, + { + "codes": 1045, + "names": "deadstemc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead stem storage pool" + }, + { + "codes": 1046, + "names": "deadcrootc_storage_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead coarse root storage pool" + }, + { + "codes": 1047, + "names": "leafc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf transfer pool" + }, + { + "codes": 1048, + "names": "frootc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root transfer pool" + }, + { + "codes": 1049, + "names": "yieldc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from yield transfer pool" + }, + { + "codes": 1050, + "names": "softstemc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem transfer pool" + }, + { + "codes": 1051, + "names": "livestemc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem transfer pool" + }, + { + "codes": 1052, + "names": "livecrootc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root transfer pool" + }, + { + "codes": 1053, + "names": "deadstemc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead stem transfer pool" + }, + { + "codes": 1054, + "names": "deadcrootc_transfer_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from dead coarse root transfer pool" + }, + { + "codes": 1055, + "names": "leafc_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from leaf" + }, + { + "codes": 1056, + "names": "frootc_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from fine root" + }, + { + "codes": 1057, + "names": "yieldc_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from yield" + }, + { + "codes": 1058, + "names": "softstemc_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from softstem" + }, + { + "codes": 1059, + "names": "livestemc_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live stem" + }, + { + "codes": 1060, + "names": "livecrootc_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from live coarse root" + }, + { + "codes": 1061, + "names": "NSC_nw_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-structured non-woody carbohydrates" + }, + { + "codes": 1062, + "names": "actC_nw_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-woody portion ofactual C pool" + }, + { + "codes": 1063, + "names": "NSC_w_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from non-structured woody carbohydrates" + }, + { + "codes": 1064, + "names": "actC_w_to_maintresp", + "units": "kgCm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring flux from woody portion ofactual C pool" + }, + { + "codes": 1065, + "names": "leafc_storage_to_leafc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of leaf storage to transfer pool" + }, + { + "codes": 1066, + "names": "frootc_storage_to_frootc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of fine root storage to transfer pool" + }, + { + "codes": 1067, + "names": "yieldc_storage_to_yieldc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of yield storage to transfer pool" + }, + { + "codes": 1068, + "names": "softstemc_storage_to_softstemc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of softstem storage to transfer pool" + }, + { + "codes": 1069, + "names": "livestemc_storage_to_livestemc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of live stem storage to transfer pool" + }, + { + "codes": 1070, + "names": "deadstemc_storage_to_deadstemc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of dead stem storage to transfer pool" + }, + { + "codes": 1071, + "names": "livecrootc_storage_to_livecrootc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of live coarse root storage to transfer pool" + }, + { + "codes": 1072, + "names": "deadcrootc_storage_to_deadcrootc_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of dead coarse root storage to transfer pool" + }, + { + "codes": 1073, + "names": "gresp_storage_to_gresp_transfer", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of growth respiration storage to transfer pool" + }, + { + "codes": 1074, + "names": "livestemc_to_deadstemc", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of live stem to dead stem" + }, + { + "codes": 1075, + "names": "livecrootc_to_deadcrootc", + "units": "kgCm-2 day-1", + "descriptions": "Annual turnover of live coarse root to dead coarse root" + }, + { + "codes": 1076, + "names": "leafc_transfer_from_PLT", + "units": "kgCm-2 day-1", + "descriptions": "Leaf transfer pool C flux from planting" + }, + { + "codes": 1077, + "names": "frootc_transfer_from_PLT", + "units": "kgCm-2 day-1", + "descriptions": "Fine root transfer pool C flux from planting" + }, + { + "codes": 1078, + "names": "yieldc_transfer_from_PLT", + "units": "kgCm-2 day-1", + "descriptions": "yield transfer pool C flux from planting" + }, + { + "codes": 1079, + "names": "softstemc_transfer_from_PLT", + "units": "kgCm-2 day-1", + "descriptions": "Softstem transfer pool C flux from planting" + }, + { + "codes": 1080, + "names": "leafc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from leaf" + }, + { + "codes": 1081, + "names": "leafc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from leaf storage pool" + }, + { + "codes": 1082, + "names": "leafc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from leaf transfer pool" + }, + { + "codes": 1083, + "names": "yieldc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from yield" + }, + { + "codes": 1084, + "names": "yieldc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from yield storage pool" + }, + { + "codes": 1085, + "names": "yieldc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from yield transfer pool" + }, + { + "codes": 1086, + "names": "livestemc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from live stem" + }, + { + "codes": 1087, + "names": "livestemc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from live stem storage pool" + }, + { + "codes": 1088, + "names": "livestemc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from live stem transfer pool" + }, + { + "codes": 1089, + "names": "deadstemc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from dead stem" + }, + { + "codes": 1090, + "names": "deadstemc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from dead stem storage pool" + }, + { + "codes": 1091, + "names": "deadstemc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from dead stem transfer pool" + }, + { + "codes": 1092, + "names": "gresp_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from growth respiration storage pool" + }, + { + "codes": 1093, + "names": "gresp_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from growth respiration transfer pool" + }, + { + "codes": 1094, + "names": "THN_to_CTDBc_leaf", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux to cut-down leaf biomass" + }, + { + "codes": 1095, + "names": "THN_to_CTDBc_yield", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux to cut-down yield biomass" + }, + { + "codes": 1097, + "names": "THN_to_CTDBc_cstem", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux to cut-down coarse stem biomass" + }, + { + "codes": 1098, + "names": "STDBc_leaf_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from wilted leaf biomass" + }, + { + "codes": 1099, + "names": "STDBc_yield_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from wilted yield biomass" + }, + { + "codes": 1100, + "names": "litrc_to_release_total", + "units": "kgCm-2 day-1", + "descriptions": "Sum of direct decomposition carbon flux of litter pools" + }, + { + "codes": 1101, + "names": "leafc_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from leaf" + }, + { + "codes": 1102, + "names": "leafc_storage_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from leaf storage pool" + }, + { + "codes": 1103, + "names": "leafc_transfer_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from leaf transfer pool" + }, + { + "codes": 1104, + "names": "yieldc_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from yield" + }, + { + "codes": 1105, + "names": "yieldc_storage_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from yield storage pool" + }, + { + "codes": 1106, + "names": "yieldc_transfer_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from yield transfer pool" + }, + { + "codes": 1107, + "names": "softstemc_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from softstem" + }, + { + "codes": 1108, + "names": "softstemc_storage_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from softstem storage pool" + }, + { + "codes": 1109, + "names": "softstemc_transfer_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from softstem transfer pool" + }, + { + "codes": 1110, + "names": "gresp_storage_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from growth respiration storage pool" + }, + { + "codes": 1111, + "names": "gresp_transfer_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from growth respiration transfer pool" + }, + { + "codes": 1112, + "names": "MOW_to_CTDBc_leaf", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux to cut-down leaf biomass" + }, + { + "codes": 1113, + "names": "MOW_to_CTDBc_yield", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux to cut-down yield biomass" + }, + { + "codes": 1114, + "names": "MOW_to_CTDBc_softstem", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux to cut-down softstem biomass" + }, + { + "codes": 1116, + "names": "STDBc_leaf_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from wilted leaf biomass" + }, + { + "codes": 1117, + "names": "STDBc_yield_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from wilted yield biomass" + }, + { + "codes": 1118, + "names": "STDBc_softstem_to_MOW", + "units": "kgCm-2 day-1", + "descriptions": "Mowing C flux from wilted softstem biomass" + }, + { + "codes": 1120, + "names": "leafc_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from leaf" + }, + { + "codes": 1121, + "names": "leafc_storage_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from leaf storage pool" + }, + { + "codes": 1122, + "names": "leafc_transfer_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from leaf transfer pool" + }, + { + "codes": 1123, + "names": "yieldc_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from yield" + }, + { + "codes": 1124, + "names": "yieldc_storage_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from yield storage pool" + }, + { + "codes": 1125, + "names": "yieldc_transfer_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from yield transfer pool" + }, + { + "codes": 1126, + "names": "softstemc_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from softstem" + }, + { + "codes": 1127, + "names": "softstemc_storage_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from softstem storage pool" + }, + { + "codes": 1128, + "names": "softstemc_transfer_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from softstem transfer pool" + }, + { + "codes": 1129, + "names": "gresp_storage_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from growth respiration storage pool" + }, + { + "codes": 1130, + "names": "gresp_transfer_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from growth respiration transfer pool" + }, + { + "codes": 1131, + "names": "HRV_to_CTDBc_leaf", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux to cut-down leaf biomass" + }, + { + "codes": 1132, + "names": "HRV_to_CTDBc_yield", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux to cut-down yield biomass" + }, + { + "codes": 1133, + "names": "HRV_to_CTDBc_softstem", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux to cut-down softstem biomass" + }, + { + "codes": 1135, + "names": "STDBc_leaf_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from wilted leaf biomass" + }, + { + "codes": 1136, + "names": "STDBc_yield_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from wilted yield biomass" + }, + { + "codes": 1137, + "names": "STDBc_softstem_to_HRV", + "units": "kgCm-2 day-1", + "descriptions": "Harvesting C flux from wilted softstem biomass" + }, + { + "codes": 1139, + "names": "leafc_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from leaf" + }, + { + "codes": 1140, + "names": "leafc_storage_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from leaf storage pool" + }, + { + "codes": 1141, + "names": "leafc_transfer_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from leaf transfer pool" + }, + { + "codes": 1142, + "names": "frootc_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from fine root" + }, + { + "codes": 1143, + "names": "frootc_storage_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from fine root storage pool" + }, + { + "codes": 1144, + "names": "frootc_transfer_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from fine root transfer pool" + }, + { + "codes": 1145, + "names": "yieldc_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from yield" + }, + { + "codes": 1146, + "names": "yieldc_storage_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from yield storage pool" + }, + { + "codes": 1147, + "names": "yieldc_transfer_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from yield transfer pool" + }, + { + "codes": 1148, + "names": "softstemc_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from softstem" + }, + { + "codes": 1149, + "names": "softstemc_storage_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from softstem storage pool" + }, + { + "codes": 1150, + "names": "softstemc_transfer_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from softstem transfer pool" + }, + { + "codes": 1151, + "names": "gresp_storage_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from growth respiration storage pool" + }, + { + "codes": 1152, + "names": "gresp_transfer_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from growth respiration transfer pool" + }, + { + "codes": 1153, + "names": "STDBc_leaf_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from wilted leaf biomass" + }, + { + "codes": 1154, + "names": "STDBc_froot_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from wilted fine root biomass" + }, + { + "codes": 1155, + "names": "STDBc_yield_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from wilted yield biomass" + }, + { + "codes": 1156, + "names": "STDBc_softstem_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from wilted softstem biomass" + }, + { + "codes": 1158, + "names": "CTDBc_leaf_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from cut-down leaf biomass" + }, + { + "codes": 1159, + "names": "CTDBc_yield_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from cut-down yield biomass" + }, + { + "codes": 1160, + "names": "CTDBc_softstem_to_PLG", + "units": "kgCm-2 day-1", + "descriptions": "Ploughing C flux from cut-down softstem biomass" + }, + { + "codes": 1161, + "names": "leafc_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from leaf" + }, + { + "codes": 1162, + "names": "leafc_storage_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazig C flux from leaf storage pool" + }, + { + "codes": 1163, + "names": "leafc_transfer_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux fromleaf transfer pool" + }, + { + "codes": 1164, + "names": "yieldc_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from yield" + }, + { + "codes": 1165, + "names": "yieldc_storage_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from yield storage pool" + }, + { + "codes": 1166, + "names": "yieldc_transfer_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from yield transfer pool" + }, + { + "codes": 1167, + "names": "softstemc_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from softstem" + }, + { + "codes": 1168, + "names": "softstemc_storage_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from softstem storage pool" + }, + { + "codes": 1169, + "names": "softstemc_transfer_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from softstem transfer pool" + }, + { + "codes": 1170, + "names": "gresp_storage_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from growth respiration storage pool" + }, + { + "codes": 1171, + "names": "gresp_transfer_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from growth respiration transfer pool" + }, + { + "codes": 1172, + "names": "STDBc_leaf_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from wilted leaf biomass" + }, + { + "codes": 1173, + "names": "STDBc_yield_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux from wilted yield biomass" + }, + { + "codes": 1174, + "names": "STDBc_softstem_to_GRZ", + "units": "kgCm-2 day-1", + "descriptions": "grazing flux from wilted softstem biomass" + }, + { + "codes": 1176, + "names": "GRZ_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux to labile litter" + }, + { + "codes": 1177, + "names": "GRZ_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux to unshielded cellulose portion of litter" + }, + { + "codes": 1178, + "names": "GRZ_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux to shielded cellulose portion of litter" + }, + { + "codes": 1179, + "names": "GRZ_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "grazing C flux to lignin portion of litter" + }, + { + "codes": 1180, + "names": "FRZ_to_litr1c", + "units": "kgCm-2 day-1", + "descriptions": "Fertilizing C flux to labile litter" + }, + { + "codes": 1181, + "names": "FRZ_to_litr2c", + "units": "kgCm-2 day-1", + "descriptions": "Fertilizing C flux to unshielded cellulose portion of litter" + }, + { + "codes": 1182, + "names": "FRZ_to_litr3c", + "units": "kgCm-2 day-1", + "descriptions": "Fertilizing C flux to shielded cellulose portion of litter" + }, + { + "codes": 1183, + "names": "FRZ_to_litr4c", + "units": "kgCm-2 day-1", + "descriptions": "Fertilizing C flux to lignin portion of litter" + }, + { + "codes": 1184, + "names": "CH4flux_soil", + "units": "kgCm-2 day-1", + "descriptions": "Estimated CH4 flux from soil" + }, + { + "codes": 1185, + "names": "CH4flux_manure", + "units": "kgCm-2 day-1", + "descriptions": "Estimated CH4 flux from manure" + }, + { + "codes": 1186, + "names": "CH4flux_animal", + "units": "kgCm-2 day-1", + "descriptions": "Estimated CH4 flux from animals" + }, + { + "codes": 1187, + "names": "frootc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from fine root" + }, + { + "codes": 1188, + "names": "frootc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from fine root storage pool" + }, + { + "codes": 1189, + "names": "frootc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from fine root transfer pool" + }, + { + "codes": 1190, + "names": "livecrootc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from live coarse root" + }, + { + "codes": 1191, + "names": "livecrootc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux live from coarse root storage pool" + }, + { + "codes": 1192, + "names": "livecrootc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux live from coarse root transfer pool" + }, + { + "codes": 1193, + "names": "deadcrootc_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from dead coarse root" + }, + { + "codes": 1194, + "names": "deadcrootc_storage_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux dead from coarse root storage pool" + }, + { + "codes": 1195, + "names": "deadcrootc_transfer_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux dead from coarse root transfer pool" + }, + { + "codes": 1196, + "names": "THN_to_CTDBc_froot", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux to cut-down fine root biomass" + }, + { + "codes": 1197, + "names": "THN_to_CTDBc_croot", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux to cut-down coarse root biomass" + }, + { + "codes": 1198, + "names": "STDBc_froot_to_THN", + "units": "kgCm-2 day-1", + "descriptions": "Thinning C flux from wilted fine root biomass" + }, + { + "codes": 1300, + "names": "leafn", + "units": "kgNm-2", + "descriptions": "Actual N content of leaf pool" + }, + { + "codes": 1301, + "names": "leafn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of leaf storage pool" + }, + { + "codes": 1302, + "names": "leafn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of leaf transfer pool" + }, + { + "codes": 1303, + "names": "frootn", + "units": "kgNm-2", + "descriptions": "Actual N content of fine root pool" + }, + { + "codes": 1304, + "names": "frootn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of fine root storage pool" + }, + { + "codes": 1305, + "names": "frootn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of fine root storage pool" + }, + { + "codes": 1306, + "names": "yieldn", + "units": "kgNm-2", + "descriptions": "Actual N content of yield pool" + }, + { + "codes": 1307, + "names": "yieldn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of yield storage pool" + }, + { + "codes": 1308, + "names": "yieldn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of yield transfer pool" + }, + { + "codes": 1309, + "names": "softstemn", + "units": "kgNm-2", + "descriptions": "Actual N content of softstem pool" + }, + { + "codes": 1310, + "names": "softstemn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of softstem storage pool" + }, + { + "codes": 1311, + "names": "softstemn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of softstem transfer pool" + }, + { + "codes": 1312, + "names": "livestemn", + "units": "kgNm-2", + "descriptions": "Actual N content of live stem pool" + }, + { + "codes": 1313, + "names": "livestemn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of live stem storage pool" + }, + { + "codes": 1314, + "names": "livestemn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of live stem transfer pool" + }, + { + "codes": 1315, + "names": "deadstemn", + "units": "kgNm-2", + "descriptions": "Actual N content of dead stem pool" + }, + { + "codes": 1316, + "names": "deadstemn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of dead stem storage pool" + }, + { + "codes": 1317, + "names": "deadstemn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of dead stem transfer pool" + }, + { + "codes": 1318, + "names": "livecrootn", + "units": "kgNm-2", + "descriptions": "Actual N content of live coarse root pool" + }, + { + "codes": 1319, + "names": "livecrootn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of live coarse root storage pool" + }, + { + "codes": 1320, + "names": "livecrootn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of live coarse root transfer pool" + }, + { + "codes": 1321, + "names": "deadcrootn", + "units": "kgNm-2", + "descriptions": "Actual N content of dead coarse root pool" + }, + { + "codes": 1322, + "names": "deadcrootn_storage", + "units": "kgNm-2", + "descriptions": "Nitrogen content of dead coarse root storage pool" + }, + { + "codes": 1323, + "names": "deadcrootn_transfer", + "units": "kgNm-2", + "descriptions": "Nitrogen content of dead coarse root transfer pool" + }, + { + "codes": 1324, + "names": "npool", + "units": "kgNm-2", + "descriptions": "Temporary plant N pool" + }, + { + "codes": 1325, + "names": "cwdn_0", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 1 (0-3 cm)" + }, + { + "codes": 1326, + "names": "cwdn_1", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 2 (3-10 cm)" + }, + { + "codes": 1327, + "names": "cwdn_2", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 3 (10-30 cm)" + }, + { + "codes": 1328, + "names": "cwdn_3", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 4 (30-60 cm)" + }, + { + "codes": 1329, + "names": "cwdn_4", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 5 (60-90 cm)" + }, + { + "codes": 1330, + "names": "cwdn_5", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 6 (90-120 cm)" + }, + { + "codes": 1331, + "names": "cwdn_6", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 7 (120-150 cm)" + }, + { + "codes": 1332, + "names": "cwdn_7", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 8 (150-200 cm)" + }, + { + "codes": 1333, + "names": "cwdn_8", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 9 (200-400 cm)" + }, + { + "codes": 1334, + "names": "cwdn_9", + "units": "kgNm-2", + "descriptions": "Coarse woody debris N content in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1335, + "names": "litr1n_0", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1336, + "names": "litr1n_1", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1337, + "names": "litr1n_2", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1338, + "names": "litr1n_3", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1339, + "names": "litr1n_4", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 5 (60-90 c" + }, + { + "codes": 1340, + "names": "litr1n_5", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1341, + "names": "litr1n_6", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1342, + "names": "litr1n_7", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1343, + "names": "litr1n_8", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1344, + "names": "litr1n_9", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1345, + "names": "litr2n_0", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1346, + "names": "litr2n_1", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1347, + "names": "litr2n_2", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1348, + "names": "litr2n_3", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1349, + "names": "litr2n_4", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1350, + "names": "litr2n_5", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1351, + "names": "litr2n_6", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1352, + "names": "litr2n_7", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1353, + "names": "litr2n_8", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1354, + "names": "litr2n_9", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1355, + "names": "litr3n_0", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1356, + "names": "litr3n_1", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1357, + "names": "litr3n_2", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1358, + "names": "litr3n_3", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1359, + "names": "litr3n_4", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1360, + "names": "litr3n_5", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1361, + "names": "litr3n_6", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1362, + "names": "litr3n_7", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1363, + "names": "litr3n_8", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1364, + "names": "litr3n_9", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1365, + "names": "litr4n_0", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1366, + "names": "litr4n_1", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1367, + "names": "litr4n_2", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1368, + "names": "litr4n_3", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1369, + "names": "litr4n_4", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1370, + "names": "litr4n_5", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1371, + "names": "litr4n_6", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1372, + "names": "litr4n_7", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1373, + "names": "litr4n_8", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1374, + "names": "litr4n_9", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1375, + "names": "litrN_0", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1376, + "names": "litrN_1", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1377, + "names": "litrN_2", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1378, + "names": "litrN_3", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1379, + "names": "litrN_4", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1380, + "names": "litrN_5", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1381, + "names": "litrN_6", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1382, + "names": "litrN_7", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1383, + "names": "litrN_8", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1384, + "names": "litrN_9", + "units": "kgNm-2", + "descriptions": "Total N content of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1385, + "names": "litr1n_total", + "units": "kgNm-2", + "descriptions": "Labile N proportion of litter" + }, + { + "codes": 1386, + "names": "litr2n_total", + "units": "kgNm-2", + "descriptions": "N content of unshielded cellulose proportion of litter" + }, + { + "codes": 1387, + "names": "litr3n_total", + "units": "kgNm-2", + "descriptions": "N content of shielded cellulose proportion of litter" + }, + { + "codes": 1388, + "names": "litr4n_total", + "units": "kgNm-2", + "descriptions": "N content of lignin proportion of litter" + }, + { + "codes": 1389, + "names": "cwdn_total", + "units": "kgNm-2", + "descriptions": "Total N content of coarse woody debris" + }, + { + "codes": 1390, + "names": "STDBn_leaf", + "units": "kgNm-2", + "descriptions": "N content of wilted leaf biomass" + }, + { + "codes": 1391, + "names": "STDBn_froot", + "units": "kgNm-2", + "descriptions": "N content of wilted fine root biomass" + }, + { + "codes": 1392, + "names": "STDBn_yield", + "units": "kgNm-2", + "descriptions": "N content of wilted yield biomass" + }, + { + "codes": 1393, + "names": "STDBn_softstem", + "units": "kgNm-2", + "descriptions": "N content of wilted softstem biomass" + }, + { + "codes": 1394, + "names": "CWEsnk_N", + "units": "kgCm-2", + "descriptions": "N content of CWD-extract (sink)" + }, + { + "codes": 1395, + "names": "STDBn_above", + "units": "kgNm-2", + "descriptions": "N content of wilted aboveground plant biomass" + }, + { + "codes": 1396, + "names": "STDBn_below", + "units": "kgNm-2", + "descriptions": "N content of wilted belowground plant biomass" + }, + { + "codes": 1397, + "names": "CTDBn_leaf", + "units": "kgNm-2", + "descriptions": "N content of cut-down leaf biomass" + }, + { + "codes": 1398, + "names": "CTDBn_froot", + "units": "kgNm-2", + "descriptions": "N content of cut-down fineroot biomass" + }, + { + "codes": 1399, + "names": "CTDBn_yield", + "units": "kgNm-2", + "descriptions": "N content of cut-down yield biomass" + }, + { + "codes": 1400, + "names": "CTDBn_softstem", + "units": "kgNm-2", + "descriptions": "N content of cut-down softstem biomass" + }, + { + "codes": 1401, + "names": "MULsrc_N", + "units": "kgCm-2", + "descriptions": "N content of mulched material" + }, + { + "codes": 1402, + "names": "CTDBn_cstem", + "units": "kgNm-2", + "descriptions": "N content of cut-down coarse stem biomass" + }, + { + "codes": 1403, + "names": "CTDBn_croot", + "units": "kgNm-2", + "descriptions": "N content of cut-down coarse root biomass" + }, + { + "codes": 1404, + "names": "CTDBn_above", + "units": "kgNm-2", + "descriptions": "N content of cut-down aboveground plant biomass" + }, + { + "codes": 1405, + "names": "CTDBn_below", + "units": "kgNm-2", + "descriptions": "N content of cut-down belowground plant biomass" + }, + { + "codes": 1406, + "names": "soil1n_0", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 1407, + "names": "soil1n_1", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 1408, + "names": "soil1n_2", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 1409, + "names": "soil1n_3", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 1410, + "names": "soil1n_4", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 1411, + "names": "soil1n_5", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 1412, + "names": "soil1n_6", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 1413, + "names": "soil1n_7", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 1414, + "names": "soil1n_8", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 1415, + "names": "soil1n_9", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 1416, + "names": "soil2n_0", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 1417, + "names": "soil2n_1", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 1418, + "names": "soil2n_2", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 1419, + "names": "soil2n_3", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 1420, + "names": "soil2n_4", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 1421, + "names": "soil2n_5", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 1422, + "names": "soil2n_6", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 1423, + "names": "soil2n_7", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 1424, + "names": "soil2n_8", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 1425, + "names": "soil2n_9", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 1426, + "names": "soil3n_0", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 1427, + "names": "soil3n_1", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 1428, + "names": "soil3n_2", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 1429, + "names": "soil3n_3", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 1430, + "names": "soil3n_4", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 1431, + "names": "soil3n_5", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 1432, + "names": "soil3n_6", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 1433, + "names": "soil3n_7", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 1434, + "names": "soil3n_8", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 1435, + "names": "soil3n_9", + "units": "kgNm-2", + "descriptions": "C content of SOM pool N content of soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 1436, + "names": "soil4n_0", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 1437, + "names": "soil4n_1", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 1438, + "names": "soil4n_2", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 1439, + "names": "soil4n_3", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 1440, + "names": "soil4n_4", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 1441, + "names": "soil4n_5", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 1442, + "names": "soil4n_6", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 1443, + "names": "soil4n_7", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 1444, + "names": "soil4n_8", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 1445, + "names": "soil4n_9", + "units": "kgNm-2", + "descriptions": "stable soil organic matter N content of soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 1446, + "names": "soilN_0", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1447, + "names": "soilN_1", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1448, + "names": "soilN_2", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1449, + "names": "soilN_3", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1450, + "names": "soilN_4", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1451, + "names": "soilN_5", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1452, + "names": "soilN_6", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1453, + "names": "soilN_7", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1454, + "names": "soilN_8", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1455, + "names": "soilN_9", + "units": "kgNm-2", + "descriptions": "Total N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1456, + "names": "soil1DON_0", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 1 (0-3 cm) (labile)" + }, + { + "codes": 1457, + "names": "soil1DON_1", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 2 (3-10 cm) (labile)" + }, + { + "codes": 1458, + "names": "soil1DON_2", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 3 (10-30 cm) (labile)" + }, + { + "codes": 1459, + "names": "soil1DON_3", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 4 (30-60 cm) (labile)" + }, + { + "codes": 1460, + "names": "soil1DON_4", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 5 (60-90 cm) (labile)" + }, + { + "codes": 1461, + "names": "soil1DON_5", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 6 (90-120 cm) (labile)" + }, + { + "codes": 1462, + "names": "soil1DON_6", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 7 (120-150 cm) (labile)" + }, + { + "codes": 1463, + "names": "soil1DON_7", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 8 (150-200 cm) (labile)" + }, + { + "codes": 1464, + "names": "soil1DON_8", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 9 (200-400 cm) (labile)" + }, + { + "codes": 1465, + "names": "soil1DON_9", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 10 (400-1000 cm) (labile)" + }, + { + "codes": 1466, + "names": "soil2DON_0", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 1 (0-3 cm) (fast)" + }, + { + "codes": 1467, + "names": "soil2DON_1", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 2 (3-10 cm) (fast)" + }, + { + "codes": 1468, + "names": "soil2DON_2", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 3 (10-30 cm) (fast)" + }, + { + "codes": 1469, + "names": "soil2DON_3", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 4 (30-60 cm) (fast)" + }, + { + "codes": 1470, + "names": "soil2DON_4", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 5 (60-90 cm) (fast)" + }, + { + "codes": 1471, + "names": "soil2DON_5", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 6 (90-120 cm) (fast)" + }, + { + "codes": 1472, + "names": "soil2DON_6", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 7 (120-150 cm) (fast)" + }, + { + "codes": 1473, + "names": "soil2DON_7", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 8 (150-200 cm) (fast)" + }, + { + "codes": 1474, + "names": "soil2DON_8", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 9 (200-400 cm) (fast)" + }, + { + "codes": 1475, + "names": "soil2DON_9", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 10 (400-1000 cm) (fast)" + }, + { + "codes": 1476, + "names": "soil3DON_0", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 1 (0-3 cm) (slow)" + }, + { + "codes": 1477, + "names": "soil3DON_1", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 2 (3-10 cm) (slow)" + }, + { + "codes": 1478, + "names": "soil3DON_2", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 3 (10-30 cm) (slow)" + }, + { + "codes": 1479, + "names": "soil3DON_3", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 4 (30-60 cm) (slow)" + }, + { + "codes": 1480, + "names": "soil3DON_4", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 5 (60-90 cm) (slow)" + }, + { + "codes": 1481, + "names": "soil3DON_5", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 6 (90-120 cm) (slow)" + }, + { + "codes": 1482, + "names": "soil3DON_6", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 7 (120-150 cm) (slow)" + }, + { + "codes": 1483, + "names": "soil3DON_7", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 8 (150-200 cm) (slow)" + }, + { + "codes": 1484, + "names": "soil3DON_8", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 9 (200-400 cm) (slow)" + }, + { + "codes": 1485, + "names": "soil3DON_9", + "units": "kgNm-2", + "descriptions": "Dissolved C content of SOM pool N content of soil layer 10 (400-1000 cm) (slow)" + }, + { + "codes": 1486, + "names": "soil4DON_0", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 1 (0-3 cm) (stable)" + }, + { + "codes": 1487, + "names": "soil4DON_1", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 2 (3-10 cm) (stable)" + }, + { + "codes": 1488, + "names": "soil4DON_2", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 3 (10-30 cm) (stable)" + }, + { + "codes": 1489, + "names": "soil4DON_3", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 4 (30-60 cm) (stable)" + }, + { + "codes": 1490, + "names": "soil4DON_4", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 5 (60-90 cm) (stable)" + }, + { + "codes": 1491, + "names": "soil4DON_5", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 6 (90-120 cm) (stable)" + }, + { + "codes": 1492, + "names": "soil4DON_6", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 7 (120-150 cm) (stable)" + }, + { + "codes": 1493, + "names": "soil4DON_7", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 8 (150-200 cm) (stable)" + }, + { + "codes": 1494, + "names": "soil4DON_8", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 9 (200-400 cm) (stable)" + }, + { + "codes": 1495, + "names": "soil4DON_9", + "units": "kgNm-2", + "descriptions": "Dissolved part of stable soil organic matter N content of soil layer 10 (400-1000 cm) (stable)" + }, + { + "codes": 1496, + "names": "soilDON_0", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1497, + "names": "soilDON_1", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1498, + "names": "soilDON_2", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1499, + "names": "soilDON_3", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1500, + "names": "soilDON_4", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1501, + "names": "soilDON_5", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1502, + "names": "soilDON_6", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1503, + "names": "soilDON_7", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1504, + "names": "soilDON_8", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1505, + "names": "soilDON_9", + "units": "kgNm-2", + "descriptions": "Dissolved part of total soil N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1506, + "names": "soil1n_total", + "units": "kgNm-2", + "descriptions": "Labile SOM N pool" + }, + { + "codes": 1507, + "names": "soil2n_total", + "units": "kgNm-2", + "descriptions": "Fast decomposing SOM N pool (fast)" + }, + { + "codes": 1508, + "names": "soil3n_total", + "units": "kgNm-2", + "descriptions": "Slow decomposing SOM N pool" + }, + { + "codes": 1509, + "names": "soil4n_total", + "units": "kgNm-2", + "descriptions": "Stable SOM N pool" + }, + { + "codes": 1510, + "names": "retransn", + "units": "kgNm-2", + "descriptions": "Plant pool of retranslocated N" + }, + { + "codes": 1511, + "names": "sminNH4_0", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1512, + "names": "sminNH4_1", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1513, + "names": "sminNH4_2", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1514, + "names": "sminNH4_3", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1515, + "names": "sminNH4_4", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1516, + "names": "sminNH4_5", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1517, + "names": "sminNH4_6", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1518, + "names": "sminNH4_7", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1519, + "names": "sminNH4_8", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1520, + "names": "sminNH4_9", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1521, + "names": "sminNO3_0", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 1 (0-3 cm)" + }, + { + "codes": 1522, + "names": "sminNO3_1", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 2 (3-10 cm)" + }, + { + "codes": 1523, + "names": "sminNO3_2", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 3 (10-30 cm)" + }, + { + "codes": 1524, + "names": "sminNO3_3", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 4 (30-60 cm)" + }, + { + "codes": 1525, + "names": "sminNO3_4", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 5 (60-90 cm)" + }, + { + "codes": 1526, + "names": "sminNO3_5", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 6 (90-120 cm)" + }, + { + "codes": 1527, + "names": "sminNO3_6", + "units": "kg outputmap_1527 = &ns->smin", + "descriptions": "Mineral NO3-N content of soil layer 7 (120-150 cm)" + }, + { + "codes": 1528, + "names": "sminNO3_7", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 8 (150-200 cm)" + }, + { + "codes": 1529, + "names": "sminNO3_8", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 9 (200-400 cm)" + }, + { + "codes": 1530, + "names": "sminNO3_9", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 1531, + "names": "sminNH4_total", + "units": "kgNm-2", + "descriptions": "Mineral NH4-N content of soil" + }, + { + "codes": 1532, + "names": "sminNO3_total", + "units": "kgNm-2", + "descriptions": "Mineral NO3-N content of soil" + }, + { + "codes": 1533, + "names": "Nfix_src", + "units": "kgNm-2", + "descriptions": "SUM of biological N fixation" + }, + { + "codes": 1534, + "names": "Ndep_src", + "units": "kgNm-2", + "descriptions": "SUM of N deposition inputs" + }, + { + "codes": 1535, + "names": "Ndeepleach_snk", + "units": "kgNm-2", + "descriptions": "SUM of N deep leaching" + }, + { + "codes": 1536, + "names": "Nvol_snk", + "units": "kgNm-2", + "descriptions": "SUM of N lost to volatilization" + }, + { + "codes": 1537, + "names": "FIREsnk_N", + "units": "kgNm-2", + "descriptions": "SUM of N lost to fire" + }, + { + "codes": 1538, + "names": "Nprec_snk", + "units": "kgNm-2", + "descriptions": "SUM of N lost to precision control" + }, + { + "codes": 1539, + "names": "SNSCsnk_N", + "units": "kgNm-2", + "descriptions": "SUM of senescence N losses" + }, + { + "codes": 1540, + "names": "FRZsrc_N", + "units": "kgNm-2", + "descriptions": "SUM of N fertilization inputs" + }, + { + "codes": 1541, + "names": "PLTsrc_N", + "units": "kgNm-2", + "descriptions": "SUM of planted leaf N" + }, + { + "codes": 1542, + "names": "THN_transportN", + "units": "kgNm-2", + "descriptions": "SUM N content of thinned and transported plant material" + }, + { + "codes": 1543, + "names": "HRV_transportN", + "units": "kgNm-2", + "descriptions": "SUM of N content of harvested and transported plant material" + }, + { + "codes": 1544, + "names": "MOW_transportN", + "units": "kgNm-2", + "descriptions": "SUM of N content of mowed and transported plant material" + }, + { + "codes": 1545, + "names": "GRZsnk_N", + "units": "kgNm-2", + "descriptions": "SUM of grazed leaf N content" + }, + { + "codes": 1546, + "names": "GRZsrc_N", + "units": "kgNm-2", + "descriptions": "SUM of leaf N from grazing" + }, + { + "codes": 1548, + "names": "SPINUPsrc", + "units": "kgNm-2", + "descriptions": "SUM of leaf N from spinup" + }, + { + "codes": 1550, + "names": "NbalanceERR", + "units": "kgNm-2", + "descriptions": "SUM of N balance error" + }, + { + "codes": 1551, + "names": "inN", + "units": "kgNm-2", + "descriptions": "SUM of N input" + }, + { + "codes": 1552, + "names": "outN", + "units": "kgNm-2", + "descriptions": "SUM of N output" + }, + { + "codes": 1553, + "names": "storeN", + "units": "kgNm-2", + "descriptions": "SUM of N store" + }, + { + "codes": 1700, + "names": "m_leafn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from leaf to labile N portion of litter" + }, + { + "codes": 1701, + "names": "m_leafn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from leaf to unshielded cellulose N portion of litter" + }, + { + "codes": 1702, + "names": "m_leafn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from leaf to shielded cellulose N portion of litter" + }, + { + "codes": 1703, + "names": "m_leafn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from leaf to lignin N portion of litter" + }, + { + "codes": 1704, + "names": "m_frootn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from fine root to labile N portion of litter" + }, + { + "codes": 1705, + "names": "m_frootn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from fine root to unshielded cellulose N portion of litter" + }, + { + "codes": 1706, + "names": "m_frootn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from fine root to shielded cellulose portion N of litter" + }, + { + "codes": 1707, + "names": "m_frootn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from fine root to lignin N portion of litter" + }, + { + "codes": 1708, + "names": "m_yieldn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from yield to labile N portion of litter" + }, + { + "codes": 1709, + "names": "m_yieldn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from yield to unshielded cellulose N portion of litter" + }, + { + "codes": 1710, + "names": "m_yieldn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from yield to shielded cellulose N portion of litter" + }, + { + "codes": 1711, + "names": "m_yieldn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from yield to lignin N portion of litter" + }, + { + "codes": 1712, + "names": "m_softstemn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from softstem to labile N portion of litter" + }, + { + "codes": 1713, + "names": "m_softstemn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from softstem to unshielded cellulose N portion of litter" + }, + { + "codes": 1714, + "names": "m_softstemn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from softstem to shielded cellulose N portion of litter" + }, + { + "codes": 1715, + "names": "m_softstemn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from softstem to lignin N portion of litter" + }, + { + "codes": 1716, + "names": "m_leafn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from leaf storage pool to labile N portion of litter" + }, + { + "codes": 1717, + "names": "m_frootn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from fine root storage pool to labile N portion of litter" + }, + { + "codes": 1718, + "names": "m_yieldn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from yield storage pool to labile N portion of litter" + }, + { + "codes": 1719, + "names": "m_yieldn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from yield transfer pool to labile N portion of litter" + }, + { + "codes": 1720, + "names": "m_softstemn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from softstem storage pool to labile N portion of litter" + }, + { + "codes": 1721, + "names": "m_softstemn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from softstem transfer pool to labile N portion of litter" + }, + { + "codes": 1722, + "names": "m_livestemn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live stem storage pool to labile N portion of litter" + }, + { + "codes": 1723, + "names": "m_deadstemn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from dead stem storage pool to labile N portion of litter" + }, + { + "codes": 1724, + "names": "m_livecrootn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live coarse root storage pool to labile N portion of litter" + }, + { + "codes": 1725, + "names": "m_deadcrootn_storage_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from dead coarse root storage pool to labile N portion of litter" + }, + { + "codes": 1726, + "names": "m_leafn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from leaf transfer pool to labile N portion of litter" + }, + { + "codes": 1727, + "names": "m_frootn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from fine root transfer pool to labile N portion of litter" + }, + { + "codes": 1728, + "names": "m_livestemn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live stem transfer pool to labile N portion of litter" + }, + { + "codes": 1729, + "names": "m_deadstemn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from dead stem transfer pool to labile N portion of litter" + }, + { + "codes": 1730, + "names": "m_livecrootn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live coarse root transfer pool to labile N portion of litter" + }, + { + "codes": 1731, + "names": "m_deadcrootn_transfer_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from dead coarse root transfer pool to labile N portion of litter" + }, + { + "codes": 1732, + "names": "m_livestemn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live stem to labile N portion of litter" + }, + { + "codes": 1733, + "names": "m_livestemn_to_cwdn", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live stem to coarse woody debris" + }, + { + "codes": 1734, + "names": "m_deadstemn_to_cwdn", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from dead stem to coarse woody debris" + }, + { + "codes": 1735, + "names": "m_livecrootn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live coarse root ro labile N portion of litter" + }, + { + "codes": 1736, + "names": "m_livecrootn_to_cwdn", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from live coarse root to coarse woody debris" + }, + { + "codes": 1737, + "names": "m_deadcrootn_to_cwdn", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from dead coarse root to coarse woody debris" + }, + { + "codes": 1738, + "names": "m_retransn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Mortality N flux from retranslocated N to labile N portion of litter" + }, + { + "codes": 1739, + "names": "m_vegn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Total vegetation senescence N flux" + }, + { + "codes": 1740, + "names": "m_leafn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Leaf senescence N flux" + }, + { + "codes": 1741, + "names": "m_leafn_to_SNSCgenprog", + "units": "kgNm-2 day-1", + "descriptions": "Leaf gen. prog. scenescene N flux" + }, + { + "codes": 1742, + "names": "m_frootn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Fine root senescene N flux" + }, + { + "codes": 1743, + "names": "m_leafn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Leaf storage pool senescence N flux" + }, + { + "codes": 1744, + "names": "m_frootn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Fine root storage pool senescence N flux" + }, + { + "codes": 1745, + "names": "m_leafn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Leaf transfer pool senescence N flux" + }, + { + "codes": 1746, + "names": "m_frootn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Fine root transfer pool senescence N flux" + }, + { + "codes": 1747, + "names": "m_yieldn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "yield senescence N flux" + }, + { + "codes": 1748, + "names": "m_yieldn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "yield storage pool senescence N flux" + }, + { + "codes": 1749, + "names": "m_yieldn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "yield transfer pool senescence N flux" + }, + { + "codes": 1750, + "names": "m_softstemn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Softstem senescence N flux" + }, + { + "codes": 1751, + "names": "m_softstemn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Softstem storage pool senescence N flux" + }, + { + "codes": 1752, + "names": "m_softstemn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Softstem transfer pool senescence N flux" + }, + { + "codes": 1753, + "names": "m_retransn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Retranslocated N senescene N flux" + }, + { + "codes": 1754, + "names": "HRV_leafn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested leaf storage pool senescence N flux" + }, + { + "codes": 1755, + "names": "HRV_leafn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested leaf transfer pool senescence N flux" + }, + { + "codes": 1756, + "names": "HRV_yieldn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested yield storage pool senescence N flux" + }, + { + "codes": 1757, + "names": "HRV_yieldn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested yield transfer pool senescence N flux" + }, + { + "codes": 1758, + "names": "HRV_frootn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested fine root senescence N flux" + }, + { + "codes": 1759, + "names": "HRV_softstemn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested softstem senscence N flux" + }, + { + "codes": 1760, + "names": "HRV_frootn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested fine root storage senescence N flux" + }, + { + "codes": 1761, + "names": "HRV_frootn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested fine root transfer senescence N flux" + }, + { + "codes": 1762, + "names": "HRV_softstemn_storage_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested softstem storage senescence N flux" + }, + { + "codes": 1763, + "names": "HRV_softstemn_transfer_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested softstem transfer senescence N flux" + }, + { + "codes": 1764, + "names": "HRV_retransn_to_SNSC", + "units": "kgNm-2 day-1", + "descriptions": "Harvested retranslocated N senescence N flux" + }, + { + "codes": 1765, + "names": "yieldn_to_flowHS", + "units": "kgNm-2 day-1", + "descriptions": "N flux from yield flowering heat stress" + }, + { + "codes": 1766, + "names": "STDBn_leaf_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Leaf standing dead biomass N flux to litter" + }, + { + "codes": 1767, + "names": "STDBn_froot_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Fine root standing dead biomass N flux to litter" + }, + { + "codes": 1768, + "names": "STDBn_yield_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "yield standing dead biomass N flux to litter" + }, + { + "codes": 1769, + "names": "STDBn_softstem_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Softstem standing dead biomass N flux to litter" + }, + { + "codes": 1770, + "names": "litrn_to_release_total", + "units": "kgNm-2 day-1", + "descriptions": "Sum of direct decomposition nitrogen flux of litter pools" + }, + { + "codes": 1771, + "names": "STDBn_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Standing dead biomass N flux to litter" + }, + { + "codes": 1772, + "names": "CTDBn_leaf_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down leaf dead biomass N flux to litter" + }, + { + "codes": 1773, + "names": "CTDBn_froot_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down fine root dead biomass N flux to litter" + }, + { + "codes": 1774, + "names": "CTDBn_yield_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down yield dead biomass N flux to litter" + }, + { + "codes": 1775, + "names": "CTDBn_softstem_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down softstem dead biomass N flux to litter" + }, + { + "codes": 1777, + "names": "CTDBn_cstem_to_cwd", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down coarse stem dead biomass N flux to coarse woody debris" + }, + { + "codes": 1778, + "names": "CTDBn_croot_to_cwd", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down coarse root dead biomass N flux to coarse woody debris" + }, + { + "codes": 1779, + "names": "CTDBn_to_litr", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down dead biomass N flux to litter" + }, + { + "codes": 1780, + "names": "m_leafn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Leaf fire N flux" + }, + { + "codes": 1781, + "names": "m_frootn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Fine root fire N flux" + }, + { + "codes": 1782, + "names": "m_yieldn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "yield fire N flux" + }, + { + "codes": 1783, + "names": "m_softstemn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Softstem fire N flux" + }, + { + "codes": 1784, + "names": "m_STDBn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Wilted plant biomass fire N flux" + }, + { + "codes": 1785, + "names": "m_CTDBn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Cut-down plant biomass fire N flux" + }, + { + "codes": 1786, + "names": "m_leafn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Leaf storage pool fire N flux" + }, + { + "codes": 1787, + "names": "m_frootn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Fine root storage pool fire N flux" + }, + { + "codes": 1788, + "names": "m_yieldn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "yield storage pool fire N flux" + }, + { + "codes": 1789, + "names": "m_yieldn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "yield transfer pool fire N flux" + }, + { + "codes": 1790, + "names": "m_softstemn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Softstem storage pool fire N flux" + }, + { + "codes": 1791, + "names": "m_softstemn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Softstem transfer pool fire N flux" + }, + { + "codes": 1792, + "names": "m_livestemn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Live stem storage pool fire N flux" + }, + { + "codes": 1793, + "names": "m_deadstemn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Dead stem storage pool fire N flux" + }, + { + "codes": 1794, + "names": "m_livecrootn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Live coarse root storage pool fire N flux" + }, + { + "codes": 1795, + "names": "m_deadcrootn_storage_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Dead coarse root storage pool fire N flux" + }, + { + "codes": 1796, + "names": "m_leafn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Leaf transfer pool fire N flux" + }, + { + "codes": 1797, + "names": "m_frootn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Fine root transfer pool fire N flux" + }, + { + "codes": 1798, + "names": "m_livestemn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Live stem transfer pool fire N flux" + }, + { + "codes": 1799, + "names": "m_deadstemn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Dead stem transfer pool fire N flux" + }, + { + "codes": 1800, + "names": "m_livecrootn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Live coarse root transfer pool fire N flux" + }, + { + "codes": 1801, + "names": "m_deadcrootn_transfer_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Dead coarse root transfer pool fire N flux" + }, + { + "codes": 1802, + "names": "m_livestemn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Live stem fire N flux" + }, + { + "codes": 1803, + "names": "m_deadstemn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Dead stem fire N flux" + }, + { + "codes": 1804, + "names": "m_livecrootn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Live coarse root fire N flux" + }, + { + "codes": 1805, + "names": "m_deadcrootn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Dead coarse root fire N flux" + }, + { + "codes": 1806, + "names": "m_retransn_to_fire", + "units": "kgNm-2 day-1", + "descriptions": "Retranslocated N fire N flux" + }, + { + "codes": 1807, + "names": "m_litr1n_to_fire_total", + "units": "kgNm-2 day-1", + "descriptions": "Labile N portion of litter fire N flux" + }, + { + "codes": 1808, + "names": "m_litr2n_to_fire_total", + "units": "kgNm-2 day-1", + "descriptions": "Unshielded cellulose portion N of litter fire N flux" + }, + { + "codes": 1809, + "names": "m_litr3n_to_fire_total", + "units": "kgNm-2 day-1", + "descriptions": "Shielded cellulose portion N of litter fire N flux" + }, + { + "codes": 1810, + "names": "m_litr4n_to_fire_total", + "units": "kgNm-2 day-1", + "descriptions": "Lignin N portion of litter fire N flux" + }, + { + "codes": 1811, + "names": "m_cwdn_to_fire_total", + "units": "kgNm-2 day-1", + "descriptions": "Coarse woody debris fire N flux" + }, + { + "codes": 1812, + "names": "leafn_transfer_to_leafn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from leaf transfer pool to leaf" + }, + { + "codes": 1813, + "names": "frootn_transfer_to_frootn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from fine root transfer pool to fine root" + }, + { + "codes": 1814, + "names": "yieldn_transfer_to_yieldn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from yield transfer pool to yield" + }, + { + "codes": 1815, + "names": "softstemn_transfer_to_softstemn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from softstem transfer pool to softstem" + }, + { + "codes": 1816, + "names": "livestemn_transfer_to_livestemn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from live stem transfer pool to live stem" + }, + { + "codes": 1817, + "names": "deadstemn_transfer_to_deadstemn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from dead stem transfer to dead stem" + }, + { + "codes": 1818, + "names": "livecrootn_transfer_to_livecrootn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from live coarse root transfer pool to live coarse root" + }, + { + "codes": 1819, + "names": "deadcrootn_transfer_to_deadcrootn", + "units": "kgNm-2 day-1", + "descriptions": "Phenology N flux from dead coarse root transfer pool to dead coarse root" + }, + { + "codes": 1820, + "names": "leafn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from leaf to labile N portion of litter" + }, + { + "codes": 1821, + "names": "leafn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from leaf to unshielded cellulose N portion of litter" + }, + { + "codes": 1822, + "names": "leafn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from leaf to shielded cellulose N portion of litter" + }, + { + "codes": 1823, + "names": "leafn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from leaf to lignin N portion of litter" + }, + { + "codes": 1824, + "names": "leafn_to_retransn", + "units": "kgNm-2 day-1", + "descriptions": "N flux from leaf to retranslocated N" + }, + { + "codes": 1825, + "names": "frootn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fine root to labile N portion of litter" + }, + { + "codes": 1826, + "names": "frootn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fine root to unshielded cellulose portion of litter" + }, + { + "codes": 1827, + "names": "frootn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fine root to shielded cellulose portion of litter" + }, + { + "codes": 1828, + "names": "frootn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fine root to lignin N portion of litter" + }, + { + "codes": 1829, + "names": "yieldn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from yield to labile N portion of litter" + }, + { + "codes": 1830, + "names": "yieldn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from yield to unshielded cellulose portion of litter" + }, + { + "codes": 1831, + "names": "yieldn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from yield to shielded cellulose portion of litter" + }, + { + "codes": 1832, + "names": "yieldn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from yield to lignin N portion of litter" + }, + { + "codes": 1833, + "names": "softstemn_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from softstem to labile N portion of litter" + }, + { + "codes": 1834, + "names": "softstemn_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from softstem to unshielded cellulose portion of litter" + }, + { + "codes": 1835, + "names": "softstemn_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from softstem to shielded cellulose portion of litter" + }, + { + "codes": 1836, + "names": "softstemn_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "N flux from softstem to lignin N portion of litter" + }, + { + "codes": 1837, + "names": "ndep_to_sminn_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from N deposition to soil mineral N" + }, + { + "codes": 1838, + "names": "nfix_to_sminn_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from N fixation to soil mineral N" + }, + { + "codes": 1839, + "names": "cwdn_to_litr2n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1840, + "names": "cwdn_to_litr2n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1841, + "names": "cwdn_to_litr2n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1842, + "names": "cwdn_to_litr2n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1843, + "names": "cwdn_to_litr2n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1844, + "names": "cwdn_to_litr2n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1845, + "names": "cwdn_to_litr2n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1846, + "names": "cwdn_to_litr2n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1847, + "names": "cwdn_to_litr2n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1848, + "names": "cwdn_to_litr2n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1849, + "names": "cwdn_to_litr3n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1850, + "names": "cwdn_to_litr3n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1851, + "names": "cwdn_to_litr3n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1852, + "names": "cwdn_to_litr3n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1853, + "names": "cwdn_to_litr3n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1854, + "names": "cwdn_to_litr3n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1855, + "names": "cwdn_to_litr3n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1856, + "names": "cwdn_to_litr3n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1857, + "names": "cwdn_to_litr3n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1858, + "names": "cwdn_to_litr3n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1859, + "names": "cwdn_to_litr4n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 1 (0-3 cm)" + }, + { + "codes": 1860, + "names": "cwdn_to_litr4n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 2 (3-10 cm)" + }, + { + "codes": 1861, + "names": "cwdn_to_litr4n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 3 (10-30 cm)" + }, + { + "codes": 1862, + "names": "cwdn_to_litr4n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 4 (30-60 cm)" + }, + { + "codes": 1863, + "names": "cwdn_to_litr4n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 5 (60-90 cm)" + }, + { + "codes": 1864, + "names": "cwdn_to_litr4n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 6 (90-120 cm)" + }, + { + "codes": 1865, + "names": "cwdn_to_litr4n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 7 (120-150 cm)" + }, + { + "codes": 1866, + "names": "cwdn_to_litr4n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 8 (150-200 cm)" + }, + { + "codes": 1867, + "names": "cwdn_to_litr4n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 9 (200-400 cm)" + }, + { + "codes": 1868, + "names": "cwdn_to_litr4n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1869, + "names": "litr1n_to_soil1n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1870, + "names": "litr1n_to_soil1n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1871, + "names": "litr1n_to_soil1n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1872, + "names": "litr1n_to_soil1n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1873, + "names": "litr1n_to_soil1n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1874, + "names": "litr1n_to_soil1n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1875, + "names": "litr1n_to_soil1n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1876, + "names": "litr1n_to_soil1n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1877, + "names": "litr1n_to_soil1n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1878, + "names": "litr1n_to_soil1n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1879, + "names": "litr2n_to_soil2n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1880, + "names": "litr2n_to_soil2n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1881, + "names": "litr2n_to_soil2n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1882, + "names": "litr2n_to_soil2n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1883, + "names": "litr2n_to_soil2n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1884, + "names": "litr2n_to_soil2n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1885, + "names": "litr2n_to_soil2n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1886, + "names": "litr2n_to_soil2n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1887, + "names": "litr2n_to_soil2n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1888, + "names": "litr2n_to_soil2n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1889, + "names": "litr3n_to_litr2n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1890, + "names": "litr3n_to_litr2n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1891, + "names": "litr3n_to_litr2n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1892, + "names": "litr3n_to_litr2n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1893, + "names": "litr3n_to_litr2n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1894, + "names": "litr3n_to_litr2n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1895, + "names": "litr3n_to_litr2n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1896, + "names": "litr3n_to_litr2n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1897, + "names": "litr3n_to_litr2n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1898, + "names": "litr3n_to_litr2n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1899, + "names": "litr4n_to_soil3n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1900, + "names": "litr4n_to_soil3n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1901, + "names": "litr4n_to_soil3n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1902, + "names": "litr4n_to_soil3n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1903, + "names": "litr4n_to_soil3n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1904, + "names": "litr4n_to_soil3n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1905, + "names": "litr4n_to_soil3n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1906, + "names": "litr4n_to_soil3n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1907, + "names": "litr4n_to_soil3n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1908, + "names": "litr4n_to_soil3n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1909, + "names": "soil1n_to_soil2n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1910, + "names": "soil1n_to_soil2n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1911, + "names": "soil1n_to_soil2n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1912, + "names": "soil1n_to_soil2n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1913, + "names": "soil1n_to_soil2n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1914, + "names": "soil1n_to_soil2n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1915, + "names": "soil1n_to_soil2n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1916, + "names": "soil1n_to_soil2n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1917, + "names": "soil1n_to_soil2n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1918, + "names": "soil1n_to_soil2n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1919, + "names": "soil2n_to_soil3n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 1920, + "names": "soil2n_to_soil3n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 1921, + "names": "soil2n_to_soil3n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 1922, + "names": "soil2n_to_soil3n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 1923, + "names": "soil2n_to_soil3n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 1924, + "names": "soil2n_to_soil3n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 1925, + "names": "soil2n_to_soil3n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 1926, + "names": "soil2n_to_soil3n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 1927, + "names": "soil2n_to_soil3n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 1928, + "names": "soil2n_to_soil3n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1929, + "names": "soil3n_to_soil4n_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 1 (0-3 cm)" + }, + { + "codes": 1930, + "names": "soil3n_to_soil4n_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 2 (3-10 cm)" + }, + { + "codes": 1931, + "names": "soil3n_to_soil4n_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 3 (10-30 cm)" + }, + { + "codes": 1932, + "names": "soil3n_to_soil4n_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 4 (30-60 cm)" + }, + { + "codes": 1933, + "names": "soil3n_to_soil4n_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 5 (60-90 cm)" + }, + { + "codes": 1934, + "names": "soil3n_to_soil4n_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 6 (90-120 cm)" + }, + { + "codes": 1935, + "names": "soil3n_to_soil4n_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 7 (120-150 cm)" + }, + { + "codes": 1936, + "names": "soil3n_to_soil4n_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 8 (150-200 cm)" + }, + { + "codes": 1937, + "names": "soil3n_to_soil4n_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 9 (200-400 cm)" + }, + { + "codes": 1938, + "names": "soil3n_to_soil4n_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1939, + "names": "soil4n_to_sminn_0", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 1 (0-3 cm)" + }, + { + "codes": 1940, + "names": "soil4n_to_sminn_1", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer (3-10 cm)" + }, + { + "codes": 1941, + "names": "soil4n_to_sminn_2", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 3 (10-30 cm)" + }, + { + "codes": 1942, + "names": "soil4n_to_sminn_3", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 4 (30-60 cm)" + }, + { + "codes": 1943, + "names": "soil4n_to_sminn_4", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 5 (60-90 cm)" + }, + { + "codes": 1944, + "names": "soil4n_to_sminn_5", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 6 (90-120 cm)" + }, + { + "codes": 1945, + "names": "soil4n_to_sminn_6", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 7 (120-150 cm)" + }, + { + "codes": 1946, + "names": "soil4n_to_sminn_7", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 8 (150-200 cm)" + }, + { + "codes": 1947, + "names": "soil4n_to_sminn_8", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 9 (200-400 cm)" + }, + { + "codes": 1948, + "names": "soil4n_to_sminn_9", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4 in soil layer 1 (400-1000 cm)" + }, + { + "codes": 1949, + "names": "soil4n_to_sminn_total", + "units": "kgNm-2 day-1", + "descriptions": "Mineralization N flux from stable SOM pool (stable) to soil mineral NH4" + }, + { + "codes": 1950, + "names": "sminn_to_soil_SUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 1 (0-3 cm)" + }, + { + "codes": 1951, + "names": "sminn_to_soil_SUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 2 (3-10 cm)" + }, + { + "codes": 1952, + "names": "sminn_to_soil_SUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 3 (10-30 cm)" + }, + { + "codes": 1953, + "names": "sminn_to_soil_SUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 4 (30-60 cm)" + }, + { + "codes": 1954, + "names": "sminn_to_soil_SUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 5 (60-90 cm)" + }, + { + "codes": 1955, + "names": "sminn_to_soil_SUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 6 (90-120 cm)" + }, + { + "codes": 1956, + "names": "sminn_to_soil_SUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 7 (120-150 cm)" + }, + { + "codes": 1957, + "names": "sminn_to_soil_SUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 8 (150-200 cm)" + }, + { + "codes": 1958, + "names": "sminn_to_soil_SUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 9 (200-400 cm)" + }, + { + "codes": 1959, + "names": "sminn_to_soil_SUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1960, + "names": "sminNH4_to_soil_SUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 1 (0-3 cm)" + }, + { + "codes": 1961, + "names": "sminNH4_to_soil_SUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 2 (3-10 cm)" + }, + { + "codes": 1962, + "names": "sminNH4_to_soil_SUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 3 (10-30 cm)" + }, + { + "codes": 1963, + "names": "sminNH4_to_soil_SUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 4 (30-60 cm)" + }, + { + "codes": 1964, + "names": "sminNH4_to_soil_SUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 5 (60-90 cm)" + }, + { + "codes": 1965, + "names": "sminNH4_to_soil_SUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 6 (90-120 cm)" + }, + { + "codes": 1966, + "names": "sminNH4_to_soil_SUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 7 (120-150 cm)" + }, + { + "codes": 1967, + "names": "sminNH4_to_soil_SUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 8 (150-200 cm)" + }, + { + "codes": 1968, + "names": "sminNH4_to_soil_SUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 9 (200-400 cm)" + }, + { + "codes": 1969, + "names": "sminNH4_to_soil_SUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NH4 to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1970, + "names": "sminNO3_to_soil_SUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 1 (0-3 cm)" + }, + { + "codes": 1971, + "names": "sminNO3_to_soil_SUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 2 (3-10 cm)" + }, + { + "codes": 1972, + "names": "sminNO3_to_soil_SUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 3 (10-30 cm)" + }, + { + "codes": 1973, + "names": "sminNO3_to_soil_SUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 4 (30-60 cm)" + }, + { + "codes": 1974, + "names": "sminNO3_to_soil_SUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 5 (60-90 cm)" + }, + { + "codes": 1975, + "names": "sminNO3_to_soil_SUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 6 (90-120 cm)" + }, + { + "codes": 1976, + "names": "sminNO3_to_soil_SUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 7 (120-150 cm)" + }, + { + "codes": 1977, + "names": "sminNO3_to_soil_SUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 8 (150-200 cm)" + }, + { + "codes": 1978, + "names": "sminNO3_to_soil_SUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 9 (200-400 cm)" + }, + { + "codes": 1979, + "names": "sminNO3_to_soil_SUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil NO3 to soil layer 10 (400-1000 cm)" + }, + { + "codes": 1980, + "names": "sminn_to_soil1n_l1_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1981, + "names": "sminn_to_soil1n_l1_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1982, + "names": "sminn_to_soil1n_l1_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1983, + "names": "sminn_to_soil1n_l1_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1984, + "names": "sminn_to_soil1n_l1_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1985, + "names": "sminn_to_soil1n_l1_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1986, + "names": "sminn_to_soil1n_l1_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1987, + "names": "sminn_to_soil1n_l1_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1988, + "names": "sminn_to_soil1n_l1_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1989, + "names": "sminn_to_soil1n_l1_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 1990, + "names": "sminn_to_soil2n_l2_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 1991, + "names": "sminn_to_soil2n_l2_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 1992, + "names": "sminn_to_soil2n_l2_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 1993, + "names": "sminn_to_soil2n_l2_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 1994, + "names": "sminn_to_soil2n_l2_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 1995, + "names": "sminn_to_soil2n_l2_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 1996, + "names": "sminn_to_soil2n_l2_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 1997, + "names": "sminn_to_soil2n_l2_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 1998, + "names": "sminn_to_soil2n_l2_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 1999, + "names": "sminn_to_soil2n_l2_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2000, + "names": "sminn_to_soil3n_l4_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2001, + "names": "sminn_to_soil3n_l4_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2002, + "names": "sminn_to_soil3n_l4_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2003, + "names": "sminn_to_soil3n_l4_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2004, + "names": "sminn_to_soil3n_l4_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2005, + "names": "sminn_to_soil3n_l4_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2006, + "names": "sminn_to_soil3n_l4_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2007, + "names": "sminn_to_soil3n_l4_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2008, + "names": "sminn_to_soil3n_l4_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2009, + "names": "sminn_to_soil3n_l4_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2010, + "names": "sminn_to_soil2n_s1_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2011, + "names": "sminn_to_soil2n_s1_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2012, + "names": "sminn_to_soil2n_s1_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2013, + "names": "sminn_to_soil2n_s1_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2014, + "names": "sminn_to_soil2n_s1_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2015, + "names": "sminn_to_soil2n_s1_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2016, + "names": "sminn_to_soil2n_s1_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2017, + "names": "sminn_to_soil2n_s1_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2018, + "names": "sminn_to_soil2n_s1_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2019, + "names": "sminn_to_soil2n_s1_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2022, + "names": "sminn_to_soil3n_s2_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2021, + "names": "sminn_to_soil3n_s2_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2022, + "names": "sminn_to_soil3n_s2_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2023, + "names": "sminn_to_soil3n_s2_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2024, + "names": "sminn_to_soil3n_s2_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2025, + "names": "sminn_to_soil3n_s2_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2026, + "names": "sminn_to_soil3n_s2_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2027, + "names": "sminn_to_soil3n_s2_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2028, + "names": "sminn_to_soil3n_s2_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2029, + "names": "sminn_to_soil3n_s2_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2030, + "names": "sminn_to_soil4n_s3_0", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2031, + "names": "sminn_to_soil4n_s3_1", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2032, + "names": "sminn_to_soil4n_s3_2", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2033, + "names": "sminn_to_soil4n_s3_3", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2034, + "names": "sminn_to_soil4n_s3_4", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2035, + "names": "sminn_to_soil4n_s3_5", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2036, + "names": "sminn_to_soil4n_s3_6", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2037, + "names": "sminn_to_soil4n_s3_7", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2038, + "names": "sminn_to_soil4n_s3_8", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2039, + "names": "sminn_to_soil4n_s3_9", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2040, + "names": "sminn_to_soil_SUM_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to soil" + }, + { + "codes": 2041, + "names": "sminNH4_to_soil_SUM_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux srom soil mineral NH4 to soil" + }, + { + "codes": 2042, + "names": "sminNO3_to_soil_SUM_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral NO3 to soil" + }, + { + "codes": 2043, + "names": "sminNO3_to_denitr_0", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2044, + "names": "sminNO3_to_denitr_1", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2045, + "names": "sminNO3_to_denitr_2", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2046, + "names": "sminNO3_to_denitr_3", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2047, + "names": "sminNO3_to_denitr_4", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2048, + "names": "sminNO3_to_denitr_5", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2049, + "names": "sminNO3_to_denitr_6", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2050, + "names": "sminNO3_to_denitr_7", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2051, + "names": "sminNO3_to_denitr_8", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2052, + "names": "sminNO3_to_denitr_9", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2053, + "names": "sminNH4_to_nitrif_0", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2054, + "names": "sminNH4_to_nitrif_1", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2055, + "names": "sminNH4_to_nitrif_2", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2056, + "names": "sminNH4_to_nitrif_3", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2057, + "names": "sminNH4_to_nitrif_4", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2058, + "names": "sminNH4_to_nitrif_5", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2059, + "names": "sminNH4_to_nitrif_6", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2060, + "names": "sminNH4_to_nitrif_7", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2061, + "names": "sminNH4_to_nitrif_8", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2062, + "names": "sminNH4_to_nitrif_9", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2063, + "names": "N2_flux_DENITR_0", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 1 (1-2 cm)" + }, + { + "codes": 2064, + "names": "N2_flux_DENITR_1", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 2 (3-10 cm)" + }, + { + "codes": 2065, + "names": "N2_flux_DENITR_2", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 3 (10-30 cm)" + }, + { + "codes": 2066, + "names": "N2_flux_DENITR_3", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 4 (30-60 cm)" + }, + { + "codes": 2067, + "names": "N2_flux_DENITR_4", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 5 (60-90 cm)" + }, + { + "codes": 2068, + "names": "N2_flux_DENITR_5", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 6 (90-120 cm)" + }, + { + "codes": 2069, + "names": "N2_flux_DENITR_6", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 7 (120-150 cm)" + }, + { + "codes": 2070, + "names": "N2_flux_DENITR_7", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 8 (150-200 cm)" + }, + { + "codes": 2071, + "names": "N2_flux_DENITR_8", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 9 (200-400 cm)" + }, + { + "codes": 2072, + "names": "N2_flux_DENITR_9", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2 in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2073, + "names": "N2O_flux_NITRIF_0", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 1 (1-2 cm)" + }, + { + "codes": 2074, + "names": "N2O_flux_NITRIF_1", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 2 (3-10 cm)" + }, + { + "codes": 2075, + "names": "N2O_flux_NITRIF_2", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 3 (10-30 cm)" + }, + { + "codes": 2076, + "names": "N2O_flux_NITRIF_3", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 4 (30-60 cm)" + }, + { + "codes": 2077, + "names": "N2O_flux_NITRIF_4", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 5 (60-90 cm)" + }, + { + "codes": 2078, + "names": "N2O_flux_NITRIF_5", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 6 (90-120 cm)" + }, + { + "codes": 2079, + "names": "N2O_flux_NITRIF_6", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 7 (120-150 cm)" + }, + { + "codes": 2080, + "names": "N2O_flux_NITRIF_7", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 8 (150-200 cm)" + }, + { + "codes": 2081, + "names": "N2O_flux_NITRIF_8", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 9 (200-400 cm)" + }, + { + "codes": 2082, + "names": "N2O_flux_NITRIF_9", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2083, + "names": "N2O_flux_DENITR_0", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 1 (1-2 cm)" + }, + { + "codes": 2084, + "names": "N2O_flux_DENITR_1", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 2 (3-10 cm)" + }, + { + "codes": 2085, + "names": "N2O_flux_DENITR_2", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 3 (10-30 cm)" + }, + { + "codes": 2086, + "names": "N2O_flux_DENITR_3", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 4 (30-60 cm)" + }, + { + "codes": 2087, + "names": "N2O_flux_DENITR_4", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 5 (60-90 cm)" + }, + { + "codes": 2088, + "names": "N2O_flux_DENITR_5", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 6 (90-120 cm)" + }, + { + "codes": 2089, + "names": "N2O_flux_DENITR_6", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 7 (120-150 cm)" + }, + { + "codes": 2090, + "names": "N2O_flux_DENITR_7", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 8 (150-200 cm)" + }, + { + "codes": 2091, + "names": "N2O_flux_DENITR_8", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 9 (200-400 cm)" + }, + { + "codes": 2092, + "names": "N2O_flux_DENITR_9", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2093, + "names": "sminNO3_to_denitr_total", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of soil mineral NO3" + }, + { + "codes": 2094, + "names": "sminNH4_to_nitrif_total", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of soil mineral NH4" + }, + { + "codes": 2095, + "names": "N2_flux_DENITR_total", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2" + }, + { + "codes": 2096, + "names": "N2O_flux_NITRIF_total", + "units": "kgNm-2 day-1", + "descriptions": "Nitrification flux of N2O" + }, + { + "codes": 2097, + "names": "N2O_flux_DENITR_total", + "units": "kgNm-2 day-1", + "descriptions": "Denitrification flux of N2O" + }, + { + "codes": 2098, + "names": "sminNH4_to_npool_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 1 (1-2 cm)" + }, + { + "codes": 2099, + "names": "sminNH4_to_npool_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2100, + "names": "sminNH4_to_npool_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2101, + "names": "sminNH4_to_npool_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2102, + "names": "sminNH4_to_npool_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2103, + "names": "sminNH4_to_npool_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2104, + "names": "sminNH4_to_npool_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2105, + "names": "sminNH4_to_npool_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2106, + "names": "sminNH4_to_npool_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2107, + "names": "sminNH4_to_npool_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2108, + "names": "sminNO3_to_npool_0", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 1 (1-2 cm)" + }, + { + "codes": 2109, + "names": "sminNO3_to_npool_1", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2110, + "names": "sminNO3_to_npool_2", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2111, + "names": "sminNO3_to_npool_3", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2112, + "names": "sminNO3_to_npool_4", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2113, + "names": "sminNO3_to_npool_5", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2114, + "names": "sminNO3_to_npool_6", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2115, + "names": "sminNO3_to_npool_7", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2116, + "names": "sminNO3_to_npool_8", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2117, + "names": "sminNO3_to_npool_9", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2118, + "names": "sminNH4_to_npool_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NH4 to temporary plant N pool" + }, + { + "codes": 2119, + "names": "sminNO3_to_npool_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral NO3 to temporary plant N pool" + }, + { + "codes": 2120, + "names": "sminn_to_npool_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from soil mineral N to temporary plant N pool" + }, + { + "codes": 2121, + "names": "sminNH4_leach_0", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2122, + "names": "sminNH4_leach_1", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2123, + "names": "sminNH4_leach_2", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2124, + "names": "sminNH4_leach_3", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2125, + "names": "sminNH4_leach_4", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2126, + "names": "sminNH4_leach_5", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2127, + "names": "sminNH4_leach_6", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2128, + "names": "sminNH4_leach_7", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2129, + "names": "sminNH4_leach_8", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2130, + "names": "sminNH4_leach_9", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NH4 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2131, + "names": "sminNH4_leachCUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2132, + "names": "sminNH4_leachCUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2133, + "names": "sminNH4_leachCUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2134, + "names": "sminNH4_leachCUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2135, + "names": "sminNH4_leachCUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2136, + "names": "sminNH4_leachCUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2137, + "names": "sminNH4_leachCUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2138, + "names": "sminNH4_leachCUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2139, + "names": "sminNH4_leachCUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2140, + "names": "sminNH4_leachCUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NH4 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2141, + "names": "sminNO3_leach_0", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2142, + "names": "sminNO3_leach_1", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2143, + "names": "sminNO3_leach_2", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2144, + "names": "sminNO3_leach_3", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2145, + "names": "sminNO3_leach_4", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2146, + "names": "sminNO3_leach_5", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2147, + "names": "sminNO3_leach_6", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2148, + "names": "sminNO3_leach_7", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2149, + "names": "sminNO3_leach_8", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2150, + "names": "sminNO3_leach_9", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral NO3 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2151, + "names": "sminNO3_leachCUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 1 (0-3 cm)" + }, + { + "codes": 2152, + "names": "sminNO3_leachCUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 2 (3-10 cm)" + }, + { + "codes": 2153, + "names": "sminNO3_leachCUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 3 (10-30 cm)" + }, + { + "codes": 2154, + "names": "sminNO3_leachCUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 4 (30-60 cm)" + }, + { + "codes": 2155, + "names": "sminNO3_leachCUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 5 (60-90 cm)" + }, + { + "codes": 2156, + "names": "sminNO3_leachCUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 6 (90-120 cm)" + }, + { + "codes": 2157, + "names": "sminNO3_leachCUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 7 (120-150 cm)" + }, + { + "codes": 2158, + "names": "sminNO3_leachCUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 8 (150-200 cm)" + }, + { + "codes": 2159, + "names": "sminNO3_leachCUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 9 (200-400 cm)" + }, + { + "codes": 2160, + "names": "sminNO3_leachCUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached soil mineral NO3 from soil layer 10 (400-1000 cm)" + }, + { + "codes": 2161, + "names": "sminN_leachRZ", + "units": "kgNm-2 day-1", + "descriptions": "Leached soil mineral N from rootzone" + }, + { + "codes": 2162, + "names": "soil1DON_leach_0", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2163, + "names": "soil1DON_leach_1", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2164, + "names": "soil1DON_leach_2", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2165, + "names": "soil1DON_leach_3", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2166, + "names": "soil1DON_leach_4", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2167, + "names": "soil1DON_leach_5", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2168, + "names": "soil1DON_leach_6", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2169, + "names": "soil1DON_leach_7", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2170, + "names": "soil1DON_leach_8", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2171, + "names": "soil1DON_leach_9", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of labile SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2172, + "names": "soil2DON_leach_0", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2173, + "names": "soil2DON_leach_1", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2174, + "names": "soil2DON_leach_2", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2175, + "names": "soil2DON_leach_3", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2176, + "names": "soil2DON_leach_4", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2177, + "names": "soil2DON_leach_5", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2178, + "names": "soil2DON_leach_6", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2179, + "names": "soil2DON_leach_7", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2180, + "names": "soil2DON_leach_8", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2181, + "names": "soil2DON_leach_9", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of fast decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2182, + "names": "soil3DON_leach_0", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2183, + "names": "soil3DON_leach_1", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2184, + "names": "soil3DON_leach_2", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2185, + "names": "soil3DON_leach_3", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2186, + "names": "soil3DON_leach_4", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2187, + "names": "soil3DON_leach_5", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2188, + "names": "soil3DON_leach_6", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2189, + "names": "soil3DON_leach_7", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2190, + "names": "soil3DON_leach_8", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2191, + "names": "soil3DON_leach_9", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of slow decomposing SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2192, + "names": "soil4DON_leach_0", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 1 (0-3 cm)" + }, + { + "codes": 2193, + "names": "soil4DON_leach_1", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 2 (3-10 cm)" + }, + { + "codes": 2194, + "names": "soil4DON_leach_2", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 3 (10-30 cm)" + }, + { + "codes": 2195, + "names": "soil4DON_leach_3", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 4 (30-60 cm)" + }, + { + "codes": 2196, + "names": "soil4DON_leach_4", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 5 (60-90 cm)" + }, + { + "codes": 2197, + "names": "soil4DON_leach_5", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 6 (90-120 cm)" + }, + { + "codes": 2198, + "names": "soil4DON_leach_6", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 7 (120-150 cm)" + }, + { + "codes": 2199, + "names": "soil4DON_leach_7", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 8 (150-200 cm)" + }, + { + "codes": 2200, + "names": "soil4DON_leach_8", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 9 (200-400 cm)" + }, + { + "codes": 2201, + "names": "soil4DON_leach_9", + "units": "kgNm-2 day-1", + "descriptions": "Leached N flux from DON of stable SOM of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2202, + "names": "soilDON_leachCUM_0", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 1 (0-3 cm)" + }, + { + "codes": 2203, + "names": "soilDON_leachCUM_1", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 2 (3-10 cm)" + }, + { + "codes": 2204, + "names": "soilDON_leachCUM_2", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 3 (10-30 cm)" + }, + { + "codes": 2205, + "names": "soilDON_leachCUM_3", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 4 (30-60 cm)" + }, + { + "codes": 2206, + "names": "soilDON_leachCUM_4", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 5 (60-90 cm)" + }, + { + "codes": 2207, + "names": "soilDON_leachCUM_5", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 6 (90-120 cm)" + }, + { + "codes": 2208, + "names": "soilDON_leachCUM_6", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 7 (120-150 cm)" + }, + { + "codes": 2209, + "names": "soilDON_leachCUM_7", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 8 (150-200 cm)" + }, + { + "codes": 2210, + "names": "soilDON_leachCUM_8", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 9 (200-400 cm)" + }, + { + "codes": 2211, + "names": "soilDON_leachCUM_9", + "units": "kgNm-2 day-1", + "descriptions": "Cumulated leached N flux from DON of total SOM pool in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2212, + "names": "DON_leachRZ", + "units": "kgNm-2 day-1", + "descriptions": "Leached DON from rootzone" + }, + { + "codes": 2243, + "names": "retransn_to_npool_total", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from retransclocated N to temporary plant N pool" + }, + { + "codes": 2244, + "names": "npool_to_leafn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to leaf" + }, + { + "codes": 2245, + "names": "npool_to_leafn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Dail allocation N flux from temporary plant N pool to leaf storage pool" + }, + { + "codes": 2246, + "names": "npool_to_frootn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fine root" + }, + { + "codes": 2247, + "names": "npool_to_frootn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to fine root storage pool" + }, + { + "codes": 2248, + "names": "npool_to_yieldn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to yield" + }, + { + "codes": 2249, + "names": "npool_to_yieldn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to yield storage pool" + }, + { + "codes": 2250, + "names": "npool_to_softstemn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to softstem" + }, + { + "codes": 2251, + "names": "npool_to_softstemn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to softstem storage pool" + }, + { + "codes": 2252, + "names": "npool_to_livestemn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live stem" + }, + { + "codes": 2253, + "names": "npool_to_livestemn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily alloaction N flux from temporary plant N pool to live stem storage pool" + }, + { + "codes": 2254, + "names": "npool_to_deadstemn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead stem" + }, + { + "codes": 2255, + "names": "npool_to_deadstemn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead stem storage pool" + }, + { + "codes": 2256, + "names": "npool_to_livecrootn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live coarse root" + }, + { + "codes": 2257, + "names": "npool_to_livecrootn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to live coarse root storage pool" + }, + { + "codes": 2258, + "names": "npool_to_deadcrootn", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead coarse root" + }, + { + "codes": 2259, + "names": "npool_to_deadcrootn_storage", + "units": "kgNm-2 day-1", + "descriptions": "Daily allocation N flux from temporary plant N pool to dead coarse root storage pool" + }, + { + "codes": 2260, + "names": "leafn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf storage pool" + }, + { + "codes": 2261, + "names": "frootn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root storage pool" + }, + { + "codes": 2262, + "names": "yieldn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from yield storage pool" + }, + { + "codes": 2263, + "names": "softstemn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem storage pool" + }, + { + "codes": 2264, + "names": "livestemn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem storage pool" + }, + { + "codes": 2265, + "names": "livecrootn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root storage pool" + }, + { + "codes": 2266, + "names": "deadstemn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead stem storage pool" + }, + { + "codes": 2267, + "names": "deadcrootn_storage_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead coarse root storage pool" + }, + { + "codes": 2268, + "names": "leafn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf transfer pool" + }, + { + "codes": 2269, + "names": "frootn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root transfer pool" + }, + { + "codes": 2270, + "names": "yieldn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from yield transfer pool" + }, + { + "codes": 2271, + "names": "softstemn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem transfer pool" + }, + { + "codes": 2272, + "names": "livestemn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem transfer pool" + }, + { + "codes": 2273, + "names": "livecrootn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root transfer pool" + }, + { + "codes": 2274, + "names": "deadstemn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead stem transfer pool" + }, + { + "codes": 2275, + "names": "deadcrootn_transfer_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from dead coarse root transfer pool" + }, + { + "codes": 2276, + "names": "leafn_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from leaf" + }, + { + "codes": 2277, + "names": "frootn_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from fine root" + }, + { + "codes": 2278, + "names": "yieldn_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from yield" + }, + { + "codes": 2279, + "names": "softstemn_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from softstem" + }, + { + "codes": 2280, + "names": "livestemn_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live stem" + }, + { + "codes": 2281, + "names": "livecrootn_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from live coarse root" + }, + { + "codes": 2282, + "names": "NSN_nw_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-structured non-woody N" + }, + { + "codes": 2283, + "names": "actN_nw_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-woody portion of actual N pool" + }, + { + "codes": 2284, + "names": "NSN_w_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from non-structured woody N" + }, + { + "codes": 2285, + "names": "actN_w_to_maintresp", + "units": "kgNm-2 day-1", + "descriptions": "Daily maintenance respiration ensuring N flux from woody portion ofactual N pool" + }, + { + "codes": 2286, + "names": "leafn_storage_to_leafn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of leaf storage to transfer pool" + }, + { + "codes": 2287, + "names": "frootn_storage_to_frootn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of fine root storage to transfer pool" + }, + { + "codes": 2288, + "names": "livestemn_storage_to_livestemn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of live stem storage to transfer pool" + }, + { + "codes": 2289, + "names": "deadstemn_storage_to_deadstemn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of dead stem storage to transfer pool" + }, + { + "codes": 2290, + "names": "livecrootn_storage_to_livecrootn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of live coarse root storage to transfer pool" + }, + { + "codes": 2291, + "names": "deadcrootn_storage_to_deadcrootn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of dead coarse root storage to transfer pool" + }, + { + "codes": 2292, + "names": "yieldn_storage_to_yieldn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of yield storage to transfer pool" + }, + { + "codes": 2293, + "names": "softstemn_storage_to_softstemn_transfer", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of softstem storage to transfer pool" + }, + { + "codes": 2294, + "names": "livestemn_to_deadstemn", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of live stem to dead stem" + }, + { + "codes": 2295, + "names": "livestemn_to_retransn", + "units": "kgNm-2 day-1", + "descriptions": "Annual N trunover of live stem to retranslocated N" + }, + { + "codes": 2296, + "names": "livecrootn_to_deadcrootn", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of live coarse root to dead coarse root" + }, + { + "codes": 2297, + "names": "livecrootn_to_retransn", + "units": "kgNm-2 day-1", + "descriptions": "Annual N turnover of live coarse root to retranslocated N" + }, + { + "codes": 2298, + "names": "leafn_transfer_from_PLT", + "units": "kgNm-2 day-1", + "descriptions": "Leaf transfer pool N flux from planting" + }, + { + "codes": 2299, + "names": "frootn_transfer_from_PLT", + "units": "kgNm-2 day-1", + "descriptions": "Fine root transfer pool N flux from planting" + }, + { + "codes": 2300, + "names": "yieldn_transfer_from_PLT", + "units": "kgNm-2 day-1", + "descriptions": "yield transfer pool N flux from planting" + }, + { + "codes": 2301, + "names": "softstemn_transfer_from_PLT", + "units": "kgNm-2 day-1", + "descriptions": "Softstem transfer pool N flux from planting" + }, + { + "codes": 2302, + "names": "leafn_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from leaf" + }, + { + "codes": 2303, + "names": "leafn_storage_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from leaf storage pool" + }, + { + "codes": 2304, + "names": "leafn_transfer_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from leaf transfer pool" + }, + { + "codes": 2305, + "names": "yieldn_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from yield" + }, + { + "codes": 2306, + "names": "yieldn_storage_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from yield storage pool" + }, + { + "codes": 2307, + "names": "yieldn_transfer_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from yield transfer pool" + }, + { + "codes": 2308, + "names": "livestemn_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from live stem" + }, + { + "codes": 2309, + "names": "livestemn_storage_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from live stem storage pool" + }, + { + "codes": 2310, + "names": "livestemn_transfer_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from live stem transfer pool" + }, + { + "codes": 2311, + "names": "deadstemn_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from dead stem" + }, + { + "codes": 2312, + "names": "deadstemn_storage_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from dead stem storage pool" + }, + { + "codes": 2313, + "names": "deadstemn_transfer_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from dead stem transfer pool" + }, + { + "codes": 2314, + "names": "retransn_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from retranslocated N" + }, + { + "codes": 2315, + "names": "THN_to_CTDBn_leaf", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux to cut-down leaf biomass" + }, + { + "codes": 2316, + "names": "THN_to_CTDBn_yield", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux to cut-down yield biomass" + }, + { + "codes": 2318, + "names": "THN_to_CTDBn_cstem", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux to cut-down coarse stem biomass" + }, + { + "codes": 2319, + "names": "STDBn_leaf_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from wilted leaf biomass" + }, + { + "codes": 2320, + "names": "STDBn_yield_to_THN", + "units": "kgNm-2 day-1", + "descriptions": "Thinning N flux from wilted yield biomass" + }, + { + "codes": 2322, + "names": "leafn_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from leaf" + }, + { + "codes": 2323, + "names": "leafn_storage_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from leaf storage pool" + }, + { + "codes": 2324, + "names": "leafn_transfer_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from leaf transfer pool" + }, + { + "codes": 2325, + "names": "yieldn_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from yield" + }, + { + "codes": 2326, + "names": "yieldn_storage_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from yield storage pool" + }, + { + "codes": 2327, + "names": "yieldn_transfer_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from yield transfer pool" + }, + { + "codes": 2328, + "names": "softstemn_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from softstem" + }, + { + "codes": 2329, + "names": "softstemn_storage_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from softstem storage pool" + }, + { + "codes": 2330, + "names": "softstemn_transfer_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from softstem transfer pool" + }, + { + "codes": 2332, + "names": "MOW_to_CTDBn_leaf", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux to cut-down leaf biomass" + }, + { + "codes": 2333, + "names": "MOW_to_CTDBn_yield", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux to cut-down yield biomass" + }, + { + "codes": 2334, + "names": "MOW_to_CTDBn_softstem", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux to cut-down softstem biomass" + }, + { + "codes": 2336, + "names": "STDBn_leaf_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from wilted leaf biomass" + }, + { + "codes": 2337, + "names": "STDBn_yield_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from wilted yield biomass" + }, + { + "codes": 2338, + "names": "STDBn_softstem_to_MOW", + "units": "kgNm-2 day-1", + "descriptions": "Mowing N flux from wilted softstem biomass" + }, + { + "codes": 2340, + "names": "leafn_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from leaf" + }, + { + "codes": 2341, + "names": "leafn_storage_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from leaf storage pool" + }, + { + "codes": 2342, + "names": "leafn_transfer_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from leaf transfer pool" + }, + { + "codes": 2343, + "names": "yieldn_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from yield" + }, + { + "codes": 2344, + "names": "yieldn_storage_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from yield storage pool" + }, + { + "codes": 2345, + "names": "yieldn_transfer_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from yield transfer pool" + }, + { + "codes": 2346, + "names": "softstemn_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from softstem" + }, + { + "codes": 2347, + "names": "softstemn_storage_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from softstem storage pool" + }, + { + "codes": 2348, + "names": "softstemn_transfer_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from softstem transfer pool" + }, + { + "codes": 2349, + "names": "retransn_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from retranslocated N" + }, + { + "codes": 2350, + "names": "HRV_to_CTDBn_leaf", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux to cut-down leaf biomass" + }, + { + "codes": 2351, + "names": "HRV_to_CTDBn_yield", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux to cut-down yield biomass" + }, + { + "codes": 2352, + "names": "HRV_to_CTDBn_softstem", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux to cut-down softstem biomass" + }, + { + "codes": 2354, + "names": "STDBn_leaf_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from wilted leaf biomass" + }, + { + "codes": 2355, + "names": "STDBn_yield_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from wilted yield biomass" + }, + { + "codes": 2356, + "names": "STDBn_softstem_to_HRV", + "units": "kgNm-2 day-1", + "descriptions": "Harvesting N flux from wilted softstem biomass" + }, + { + "codes": 2358, + "names": "leafn_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from leaf" + }, + { + "codes": 2359, + "names": "leafn_storage_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from leaf storage pool" + }, + { + "codes": 2360, + "names": "leafn_transfer_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from leaf transfer pool" + }, + { + "codes": 2361, + "names": "frootn_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from fine root" + }, + { + "codes": 2362, + "names": "frootn_storage_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from fine root storage pool" + }, + { + "codes": 2363, + "names": "frootn_transfer_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from fine root transfer pool" + }, + { + "codes": 2364, + "names": "yieldn_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from yield" + }, + { + "codes": 2365, + "names": "yieldn_storage_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from yield storage pool" + }, + { + "codes": 2366, + "names": "yieldn_transfer_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from yield transfer pool" + }, + { + "codes": 2367, + "names": "softstemn_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from softstem" + }, + { + "codes": 2368, + "names": "softstemn_storage_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from softstem storage pool" + }, + { + "codes": 2369, + "names": "softstemn_transfer_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from softstem transfer pool" + }, + { + "codes": 2370, + "names": "retransn_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from retranslocated N" + }, + { + "codes": 2371, + "names": "STDBn_leaf_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from wilted leaf biomass" + }, + { + "codes": 2372, + "names": "STDBn_froot_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from wilted fine root biomass" + }, + { + "codes": 2373, + "names": "STDBn_yield_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from wilted yield biomass" + }, + { + "codes": 2374, + "names": "STDBn_softstem_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from wilted softstem biomass" + }, + { + "codes": 2376, + "names": "CTDBn_leaf_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from cut-down leaf biomass" + }, + { + "codes": 2377, + "names": "CTDBn_yield_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from cut-down yield biomass" + }, + { + "codes": 2378, + "names": "CTDBn_softstem_to_PLG", + "units": "kgNm-2 day-1", + "descriptions": "Ploughing N flux from cut-down softstem biomass" + }, + { + "codes": 2379, + "names": "leafn_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from leaf" + }, + { + "codes": 2380, + "names": "leafn_storage_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazig N flux from leaf storage pool" + }, + { + "codes": 2381, + "names": "leafn_transfer_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux fromleaf transfer pool" + }, + { + "codes": 2382, + "names": "yieldn_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from yield" + }, + { + "codes": 2383, + "names": "yieldn_storage_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from yield storage pool" + }, + { + "codes": 2384, + "names": "yieldn_transfer_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from yield transfer pool" + }, + { + "codes": 2385, + "names": "softstemn_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from softstem" + }, + { + "codes": 2386, + "names": "softstemn_storage_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from softstem storage pool" + }, + { + "codes": 2387, + "names": "softstemn_transfer_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from softstem transfer pool" + }, + { + "codes": 2388, + "names": "STDBn_leaf_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from wilted leaf biomass" + }, + { + "codes": 2389, + "names": "STDBn_yield_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux from wilted yield biomass" + }, + { + "codes": 2390, + "names": "STDBn_softstem_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing flux from wilted softstem biomass" + }, + { + "codes": 2392, + "names": "retransn_to_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "grazing flux from retranslocated N" + }, + { + "codes": 2393, + "names": "GRZ_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux to labile N portion of litter" + }, + { + "codes": 2394, + "names": "GRZ_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux to unshielded cellulose N portion of litter" + }, + { + "codes": 2395, + "names": "GRZ_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux to shielded cellulose N portion of litter" + }, + { + "codes": 2396, + "names": "GRZ_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "grazing N flux to lignin N portion of litter" + }, + { + "codes": 2397, + "names": "FRZ_to_sminNH4", + "units": "kgNm-2 day-1", + "descriptions": "Fertilizing N flux to soil mineral NH4" + }, + { + "codes": 2398, + "names": "FRZ_to_sminNO3", + "units": "kgNm-2 day-1", + "descriptions": "Fertilizing N flux to soil mineral NO3" + }, + { + "codes": 2399, + "names": "FRZ_to_litr1n", + "units": "kgNm-2 day-1", + "descriptions": "Fertilizing N flux to labile N portion of litter" + }, + { + "codes": 2400, + "names": "FRZ_to_litr2n", + "units": "kgNm-2 day-1", + "descriptions": "Fertilizing N flux to unshielded cellulose N portion of litter" + }, + { + "codes": 2401, + "names": "FRZ_to_litr3n", + "units": "kgNm-2 day-1", + "descriptions": "Fertilizing N flux to shielded cellulose N portion of litter" + }, + { + "codes": 2402, + "names": "FRZ_to_litr4n", + "units": "kgNm-2 day-1", + "descriptions": "Fertilizing N flux to lignin N portion of litter" + }, + { + "codes": 2403, + "names": "N2O_flux_GRZ", + "units": "kgNm-2 day-1", + "descriptions": "Estimated N2O flux from grazing" + }, + { + "codes": 2404, + "names": "N2O_flux_FRZ", + "units": "kgNm-2 day-1", + "descriptions": "Estimated N2O flux from fertilizing" + }, + { + "codes": 2405, + "names": "cwdn_to_litr2n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to unshielded cellulose N portion of litter in total soil" + }, + { + "codes": 2406, + "names": "cwdn_to_litr3n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to shielded cellulose N portion of litter in total soil" + }, + { + "codes": 2407, + "names": "cwdn_to_litr4n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from coarse woody debris to lignin N portion of litter in total soil" + }, + { + "codes": 2408, + "names": "litr1n_to_soil1n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile N portion of litter to SOM pool (labile) in total soil" + }, + { + "codes": 2409, + "names": "litr2n_to_soil2n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from unshielded cellulose N portion of litter to SOM pool (fast) in total soil" + }, + { + "codes": 2410, + "names": "litr3n_to_litr2n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from shielded cellulose portion of litter to unshielded cellulose pool in total soil" + }, + { + "codes": 2411, + "names": "litr4n_to_soil3n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from lignin portion of litter to shielded cellulose pool in total soil" + }, + { + "codes": 2412, + "names": "soil1n_to_soil2n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from labile to fast decomposing SOM pool in total soil" + }, + { + "codes": 2413, + "names": "soil2n_to_soil3n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from fast to slow decomposing SOM pool in total soil" + }, + { + "codes": 2414, + "names": "soil3n_to_soil4n_total", + "units": "kgNm-2 day-1", + "descriptions": "N flux from slow to stable SOM C content of SOM pool in total soil" + }, + { + "codes": 2415, + "names": "sminn_to_soil1n_l1_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2416, + "names": "sminn_to_soil2n_l2_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2417, + "names": "sminn_to_soil3n_l4_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2418, + "names": "sminn_to_soil2n_s1_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2419, + "names": "sminn_to_soil3n_s2_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2420, + "names": "sminn_to_soil4n_s3_total", + "units": "kgNm-2 day-1", + "descriptions": "Immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2421, + "names": "frootn_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux from fine root" + }, + { + "codes": 2422, + "names": "frootn_storage_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux from fine root storage pool" + }, + { + "codes": 2423, + "names": "frootn_transfer_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux from fine root transfer pool" + }, + { + "codes": 2424, + "names": "livecrootn_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux from live coarse root" + }, + { + "codes": 2425, + "names": "livecrootn_storage_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux live from coarse root storage pool" + }, + { + "codes": 2426, + "names": "livecrootn_transfer_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux live from coarse root transfer pool" + }, + { + "codes": 2427, + "names": "deadcrootn_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux from dead coarse root" + }, + { + "codes": 2428, + "names": "deadcrootn_storage_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux dead from coarse root storage pool" + }, + { + "codes": 2429, + "names": "deadcrootn_transfer_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux dead from coarse root transfer pool" + }, + { + "codes": 2430, + "names": "THN_to_CTDBn_froot", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux to nut-down fine root biomass" + }, + { + "codes": 2431, + "names": "THN_to_CTDBn_croot", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux to nut-down coarse root biomass" + }, + { + "codes": 2432, + "names": "STDBn_froot_to_THN", + "units": "kgnm-2 day-1", + "descriptions": "Thinning N flux from wilted fine root biomass" + }, + { + "codes": 2433, + "names": "SNSC_to_retrans", + "units": "kgnm-2 day-1", + "descriptions": "N flux to retranslocation pool during senescence" + }, + { + "codes": 2434, + "names": "leafSNSCgenprog_to_retrans", + "units": "kgnm-2 day-1", + "descriptions": "N flux to retranslocation pool during senescence" + }, + { + "codes": 2435, + "names": "sminn_to_soil1n_l1_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2436, + "names": "sminn_to_soil2n_l2_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2437, + "names": "sminn_to_soil3n_l4_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2438, + "names": "sminn_to_soil2n_s1_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative immobilization N flux from soil mineral N to SOM pool (labile) in total soil column" + }, + { + "codes": 2439, + "names": "sminn_to_soil3n_s2_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative immobilization N flux from soil mineral N to SOM pool (fast) in total soil column" + }, + { + "codes": 2440, + "names": "sminn_to_soil4n_s3_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative immobilization N flux from soil mineral N to SOM pool (slow) in total soil column" + }, + { + "codes": 2441, + "names": "soil4n_to_sminn_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative mineralization N flux from stable SOM pool (stable) to soil mineral NH4" + }, + { + "codes": 2442, + "names": "netMINER_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative sum of net mineralization flux" + }, + { + "codes": 2443, + "names": "sminn_to_npool_totalCUM", + "units": "kgNm-2 day-1", + "descriptions": "Cumulative N flux from soil mineral N to temporary plant N pool" + }, + { + "codes": 2498, + "names": "VWC_maxRZ", + "units": "m3m-3", + "descriptions": "Average value of VWC (maximum of rooting zone)" + }, + { + "codes": 2499, + "names": "winterEnd_date", + "units": "day of year", + "descriptions": "Date of end of wintering" + }, + { + "codes": 2500, + "names": "thermal_time", + "units": "Celsius", + "descriptions": "Difference between avg. temp. and base temperature" + }, + { + "codes": 2501, + "names": "leafday", + "units": "n", + "descriptions": "Counter for days when leaves are on" + }, + { + "codes": 2502, + "names": "n_actphen", + "units": "n", + "descriptions": "Number of the actual phenophase" + }, + { + "codes": 2503, + "names": "leafday_lastmort", + "units": "n", + "descriptions": "Last day of genetical mortality" + }, + { + "codes": 2504, + "names": "flowHS_mort", + "units": "prop", + "descriptions": "Mortality coefficient of flowering heat stress" + }, + { + "codes": 2505, + "names": "transfer_ratio", + "units": "prop", + "descriptions": "Transfer proportion on actual day" + }, + { + "codes": 2506, + "names": "day_leafc_litfall_increment", + "units": "kgCm-2 day-1", + "descriptions": "Daily rate of leaf litterfall" + }, + { + "codes": 2507, + "names": "day_yield_litfall_increment", + "units": "kgCm-2 day-1", + "descriptions": "Daily rate of yield litterfall" + }, + { + "codes": 2508, + "names": "day_softstemc_litfall_increment", + "units": "kgCm-2 day-1", + "descriptions": "Daily rate of softstem litterfall" + }, + { + "codes": 2509, + "names": "day_frootc_litfall_increment", + "units": "kgCm-2 day-1", + "descriptions": "Daily rate of fineroot litterfall" + }, + { + "codes": 2510, + "names": "day_livestemc_turnover_increment", + "units": "kgCm-2 day-1", + "descriptions": "Daily rate of livestem turnover" + }, + { + "codes": 2511, + "names": "day_livecrootc_turnover_increment", + "units": "kgCm-2 day-1", + "descriptions": "Daily rate of live coarse root turnover" + }, + { + "codes": 2512, + "names": "annmax_leafc", + "units": "kgCm-2", + "descriptions": "Annual maximum daily leaf C content" + }, + { + "codes": 2513, + "names": "annmax_yieldc", + "units": "kgCm-2", + "descriptions": "Annual maximum daily yield C content" + }, + { + "codes": 2514, + "names": "annmax_softstemc", + "units": "kgCm-2", + "descriptions": "Annual maximum daily softstem C content" + }, + { + "codes": 2515, + "names": "annmax_frootc", + "units": "kgCm-2", + "descriptions": "Annual maximum daily fine root C content" + }, + { + "codes": 2516, + "names": "annmax_livestemc", + "units": "kgCm-2", + "descriptions": "Annual maximum daily livestem C content" + }, + { + "codes": 2517, + "names": "annmax_livecrootc", + "units": "kgCm-2", + "descriptions": "Annual maximum daily live coarse root C content" + }, + { + "codes": 2518, + "names": "DSR", + "units": "n", + "descriptions": "Number of days since rain" + }, + { + "codes": 2519, + "names": "cumSWCstress", + "units": "n", + "descriptions": "Cumulative soil water stress" + }, + { + "codes": 2520, + "names": "proj_lai", + "units": "m2m-2", + "descriptions": "Live projected leaf area index" + }, + { + "codes": 2521, + "names": "all_lai", + "units": "m2m-2", + "descriptions": "Live all-sided leaf area index" + }, + { + "codes": 2522, + "names": "sla_avg", + "units": "m2m-2", + "descriptions": "Canopy average proj. SLA" + }, + { + "codes": 2523, + "names": "plaisun", + "units": "m2m-2", + "descriptions": "Sunlit projected leaf area index" + }, + { + "codes": 2524, + "names": "plaishade", + "units": "m2m-2", + "descriptions": "Shaded projected leaf area index" + }, + { + "codes": 2525, + "names": "sun_proj_sla", + "units": "m2kgC-1", + "descriptions": "Sunlit projected SLA" + }, + { + "codes": 2526, + "names": "shade_proj_sla", + "units": "m2kgC-1", + "descriptions": "Shaded projected SLA" + }, + { + "codes": 2527, + "names": "plantHeight", + "units": "m", + "descriptions": "Height of plant (based on stemw and" + }, + { + "codes": 2528, + "names": "NDVI", + "units": "ratio", + "descriptions": "Normalized difference vegetation index" + }, + { + "codes": 2529, + "names": "rootlengthProp_0", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 1 (0-3 cm)" + }, + { + "codes": 2530, + "names": "rootlengthProp_1", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 2 (3-10 cm)" + }, + { + "codes": 2531, + "names": "rootlengthProp_2", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 3 (10-30 cm)" + }, + { + "codes": 2532, + "names": "rootlengthProp_3", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 4 (30-60 cm)" + }, + { + "codes": 2533, + "names": "rootlengthProp_4", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 5 (60-90 cm)" + }, + { + "codes": 2534, + "names": "rootlengthProp_5", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 6 (90-120 cm)" + }, + { + "codes": 2535, + "names": "rootlengthProp_6", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 7 (120-150 cm)" + }, + { + "codes": 2536, + "names": "rootlengthProp_7", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 8 (150-200 cm)" + }, + { + "codes": 2537, + "names": "rootlengthProp_8", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 9 (200-400 cm)" + }, + { + "codes": 2538, + "names": "rootlengthProp_9", + "units": "prop", + "descriptions": "Proportion of total root lenght of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2539, + "names": "PSI_0", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 1 (0-3 cm)" + }, + { + "codes": 2540, + "names": "PSI_1", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 2 (3-10 cm)" + }, + { + "codes": 2541, + "names": "PSI_2", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 3 (10-30 cm)" + }, + { + "codes": 2542, + "names": "PSI_3", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 4 (30-60 cm)" + }, + { + "codes": 2543, + "names": "PSI_4", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 5 (60-90 cm)" + }, + { + "codes": 2544, + "names": "PSI_5", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 6 (90-120 cm)" + }, + { + "codes": 2545, + "names": "PSI_6", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 7 (120-150 cm)" + }, + { + "codes": 2546, + "names": "PSI_7", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 8 (150-200 cm)" + }, + { + "codes": 2547, + "names": "PSI_8", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 9 (200-400 cm)" + }, + { + "codes": 2548, + "names": "PSI_9", + "units": "MPa", + "descriptions": "Water potential of soil and leaves of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2549, + "names": "pF_0", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 1 (0-3 cm)" + }, + { + "codes": 2550, + "names": "pF_1", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 2 (3-10 cm)" + }, + { + "codes": 2551, + "names": "pF_2", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 3 (10-30 cm)" + }, + { + "codes": 2552, + "names": "pF_3", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 4 (30-60 cm)" + }, + { + "codes": 2553, + "names": "pF_4", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 5 (60-90 cm)" + }, + { + "codes": 2554, + "names": "pF_5", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 6 (90-120 cm)" + }, + { + "codes": 2555, + "names": "pF_6", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 7 (120-150 cm)" + }, + { + "codes": 2556, + "names": "pF_7", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 8 (150-200 cm)" + }, + { + "codes": 2557, + "names": "pF_8", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 9 (200-400 cm)" + }, + { + "codes": 2558, + "names": "pF_9", + "units": "cm", + "descriptions": "Soil water suction derived from log(soil water potential) of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2559, + "names": "hydrCONDUCTact_0", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2560, + "names": "hydrCONDUCTact_1", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2561, + "names": "hydrCONDUCTact_2", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2562, + "names": "hydrCONDUCTact_3", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2563, + "names": "hydrCONDUCTact_4", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2564, + "names": "hydrCONDUCTact_5", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2565, + "names": "hydrCONDUCTact_6", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2566, + "names": "hydrCONDUCTact_7", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2567, + "names": "hydrCONDUCTact_8", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2568, + "names": "hydrCONDUCTact_9", + "units": "ms-1", + "descriptions": "Hydraulic conductivity on the given day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2569, + "names": "hydrDIFFUSact_0", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 1 (0-3 cm)" + }, + { + "codes": 2570, + "names": "hydrDIFFUSact_1", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 2 (3-10 cm)" + }, + { + "codes": 2571, + "names": "hydrDIFFUSact_2", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 3 (10-30 cm)" + }, + { + "codes": 2572, + "names": "hydrDIFFUSact_3", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 4 (30-60 cm)" + }, + { + "codes": 2573, + "names": "hydrDIFFUSact_4", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 5 (60-90 cm)" + }, + { + "codes": 2574, + "names": "hydrDIFFUSact_5", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 6 (90-120 cm)" + }, + { + "codes": 2575, + "names": "hydrDIFFUSact_6", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 7 (120-150 cm)" + }, + { + "codes": 2576, + "names": "hydrDIFFUSact_7", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 8 (150-200 cm)" + }, + { + "codes": 2577, + "names": "hydrDIFFUSact_8", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 9 (200-400 cm)" + }, + { + "codes": 2578, + "names": "hydrDIFFUSact_9", + "units": "ms-1", + "descriptions": "Hydraulic diffusivity on the given day of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2579, + "names": "rootDepth", + "units": "m", + "descriptions": "Actual depth of the root" + }, + { + "codes": 2580, + "names": "rootDepth_phen_0", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase1" + }, + { + "codes": 2581, + "names": "rootDepth_phen_1", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase2" + }, + { + "codes": 2582, + "names": "rootDepth_phen_2", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase3" + }, + { + "codes": 2583, + "names": "rootDepth_phen_3", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase4" + }, + { + "codes": 2584, + "names": "rootDepth_phen_4", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase5" + }, + { + "codes": 2585, + "names": "rootDepth_phen_5", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase6" + }, + { + "codes": 2586, + "names": "rootDepth_phen_6", + "units": "dimless", + "descriptions": "Rooting depth of the phenphase7" + }, + { + "codes": 2587, + "names": "plantCalloc_CUM", + "units": "kgCm-2", + "descriptions": "Cumulated amount of allocated C" + }, + { + "codes": 2588, + "names": "plantNalloc_CUM", + "units": "kgNm-2", + "descriptions": "Cumulated amount of allocated N" + }, + { + "codes": 2589, + "names": "ts_nitrif_0", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2590, + "names": "ts_nitrif_1", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2591, + "names": "ts_nitrif_2", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2592, + "names": "ts_nitrif_3", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2593, + "names": "ts_nitrif_4", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2594, + "names": "ts_nitrif_5", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2595, + "names": "ts_nitrif_6", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2596, + "names": "ts_nitrif_7", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2597, + "names": "ts_nitrif_8", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2598, + "names": "ts_nitrif_9", + "units": "dimless", + "descriptions": "Nitrification temperature scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2599, + "names": "VWCsat_RZ", + "units": "m3m-3", + "descriptions": "Average value of VWC at saturation (rooting zone)" + }, + { + "codes": 2600, + "names": "VWCfc_RZ", + "units": "m3m-3", + "descriptions": "Average value of VWC at field capacity (rooting zone)" + }, + { + "codes": 2601, + "names": "VWCwp_RZ", + "units": "m3m-3", + "descriptions": "Average value of VWC at wilting point (rooting zone)" + }, + { + "codes": 2602, + "names": "VWChw_RZ", + "units": "m3m-3", + "descriptions": "Average value of hygroscopic VWC (rooting zone)" + }, + { + "codes": 2603, + "names": "VWC_0", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 1 (0-3 cm)" + }, + { + "codes": 2604, + "names": "VWC_1", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 2 (3-10 cm)" + }, + { + "codes": 2605, + "names": "VWC_2", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 3 (10-30 cm)" + }, + { + "codes": 2606, + "names": "VWC_3", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 4 (30-60 cm)" + }, + { + "codes": 2607, + "names": "VWC_4", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 5 (60-90 cm)" + }, + { + "codes": 2608, + "names": "VWC_5", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 6 (90-120 cm)" + }, + { + "codes": 2609, + "names": "VWC_6", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 7 (120-150 cm)" + }, + { + "codes": 2610, + "names": "VWC_7", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 8 (150-200 cm)" + }, + { + "codes": 2611, + "names": "VWC_8", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 9 (200-400 cm)" + }, + { + "codes": 2612, + "names": "VWC_9", + "units": "m3m-3", + "descriptions": "Volumetric water content of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2613, + "names": "relVWCsat_fc_0", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 1 (0-3 cm)" + }, + { + "codes": 2614, + "names": "relVWCsat_fc_1", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 2 (3-10 cm)" + }, + { + "codes": 2615, + "names": "relVWCsat_fc_2", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 3 (10-30 cm)" + }, + { + "codes": 2616, + "names": "relVWCsat_fc_3", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 4 (30-60 cm)" + }, + { + "codes": 2617, + "names": "relVWCsat_fc_4", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 5 (60-90 cm)" + }, + { + "codes": 2618, + "names": "relVWCsat_fc_5", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 6 (90-120 cm)" + }, + { + "codes": 2619, + "names": "relVWCsat_fc_6", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 7 (120-150 cm)" + }, + { + "codes": 2620, + "names": "relVWCsat_fc_7", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 8 (150-200 cm)" + }, + { + "codes": 2621, + "names": "relVWCsat_fc_8", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 9 (200-400 cm)" + }, + { + "codes": 2622, + "names": "relVWCsat_fc_9", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (SAT-FC) of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2623, + "names": "relVWCfc_wp_0", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 1 (0-3 cm)" + }, + { + "codes": 2624, + "names": "relVWCfc_wp_1", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 2 (3-10 cm)" + }, + { + "codes": 2625, + "names": "relVWCfc_wp_2", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 3 (10-30 cm)" + }, + { + "codes": 2626, + "names": "relVWCfc_wp_3", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 4 (30-60 cm)" + }, + { + "codes": 2627, + "names": "relVWCfc_wp_4", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 5 (60-90 cm)" + }, + { + "codes": 2628, + "names": "relVWCfc_wp_5", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 6 (90-120 cm)" + }, + { + "codes": 2629, + "names": "relVWCfc_wp_6", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 7 (120-150 cm)" + }, + { + "codes": 2630, + "names": "relVWCfc_wp_7", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 8 (150-200 cm)" + }, + { + "codes": 2631, + "names": "relVWCfc_wp_8", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 9 (200-400 cm)" + }, + { + "codes": 2632, + "names": "relVWCfc_wp_9", + "units": "m3m-3", + "descriptions": "Relative volumetric water content (FC-WP) of soil layer 10 (400-1000 cm)" + }, + { + "codes": 2633, + "names": "VWC_avg", + "units": "m3m-3", + "descriptions": "Average volumetric water content in active layers" + }, + { + "codes": 2634, + "names": "VWC_RZ", + "units": "m3m-3", + "descriptions": "Average volumetric water content in rootzone (max.soil.depth)" + }, + { + "codes": 2635, + "names": "PSI_RZ", + "units": "MPa", + "descriptions": "Average water potential of soil and leaves" + }, + { + "codes": 2636, + "names": "rootDepth", + "units": "m", + "descriptions": "Actual depth of the rooting zone" + }, + { + "codes": 2637, + "names": "dlmr_area_sun", + "units": "mu$mol$C m-2proj", + "descriptions": "Sunlit leaf MR" + }, + { + "codes": 2638, + "names": "dlmr_area_shade", + "units": "mu$mol$C m-2proj", + "descriptions": "Shaded leaf MR" + }, + { + "codes": 2639, + "names": "gl_t_wv_sun", + "units": "m s-1", + "descriptions": "Sunlit leaf-scale conductance to transpired water" + }, + { + "codes": 2640, + "names": "gl_t_wv_shade", + "units": "m3s-1", + "descriptions": "Shaded leaf-scale conductance to transpired water" + }, + { + "codes": 2641, + "names": "assim_sun", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit assimilation per unit pleaf area index" + }, + { + "codes": 2642, + "names": "assim_shade", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Shaded assimilation per unit pleaf area index" + }, + { + "codes": 2643, + "names": "ts_decomp_0", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2644, + "names": "ts_decomp_1", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2645, + "names": "ts_decomp_2", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2646, + "names": "ts_decomp_3", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2647, + "names": "ts_decomp_4", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2648, + "names": "ts_decomp_5", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2649, + "names": "ts_decomp_6", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2650, + "names": "ts_decomp_7", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2651, + "names": "ts_decomp_8", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2652, + "names": "ts_decomp_9", + "units": "dimless", + "descriptions": "Decomposition temperature scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2653, + "names": "ws_decomp_0", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2654, + "names": "ws_decomp_1", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2655, + "names": "ws_decomp_2", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2656, + "names": "ws_decomp_3", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2657, + "names": "ws_decomp_4", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2658, + "names": "ws_decomp_5", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2659, + "names": "ws_decomp_6", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2660, + "names": "ws_decomp_7", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2661, + "names": "ws_decomp_8", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2662, + "names": "ws_decomp_9", + "units": "dimless", + "descriptions": "Decomposition water scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2663, + "names": "rs_decomp_0", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2664, + "names": "rs_decomp_1", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2665, + "names": "rs_decomp_2", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2666, + "names": "rs_decomp_3", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2667, + "names": "rs_decomp_4", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2668, + "names": "rs_decomp_5", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2669, + "names": "rs_decomp_6", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2670, + "names": "rs_decomp_7", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2671, + "names": "rs_decomp_8", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2672, + "names": "rs_decomp_9", + "units": "dimless", + "descriptions": "Decomposition combined scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2673, + "names": "rs_decomp_avg", + "units": "dimless", + "descriptions": "Decomposition combined and averaged scalar" + }, + { + "codes": 2674, + "names": "annmax_rootDepth", + "units": "m", + "descriptions": "Year-to-date maximum rooting depth" + }, + { + "codes": 2675, + "names": "annmax_plantHeight", + "units": "m", + "descriptions": "Year-to-date maximum plant height" + }, + { + "codes": 2676, + "names": "grossMINER_0", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2677, + "names": "grossMINER_1", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2678, + "names": "grossMINER_2", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2679, + "names": "grossMINER_3", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2680, + "names": "grossMINER_4", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2681, + "names": "grossMINER_5", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2682, + "names": "grossMINER_6", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2683, + "names": "grossMINER_7", + "units": "kgNm-2", + "descriptions": "gross N mineralization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2684, + "names": "potIMMOB_0", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2685, + "names": "potIMMOB_1", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2686, + "names": "potIMMOB_2", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2687, + "names": "potIMMOB_3", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2688, + "names": "potIMMOB_4", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2689, + "names": "potIMMOB_5", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2690, + "names": "potIMMOB_6", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2691, + "names": "potIMMOB_7", + "units": "kgNm-2", + "descriptions": "Potential N immobilization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2692, + "names": "netMINER_0", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 1 (0-3 cm)" + }, + { + "codes": 2693, + "names": "netMINER_1", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 2 (3-10 cm)" + }, + { + "codes": 2694, + "names": "netMINER_2", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 3 (10-30 cm)" + }, + { + "codes": 2695, + "names": "netMINER_3", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 4 (30-60 cm)" + }, + { + "codes": 2696, + "names": "netMINER_4", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 5 (60-90 cm)" + }, + { + "codes": 2697, + "names": "netMINER_5", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 6 (90-120 cm)" + }, + { + "codes": 2698, + "names": "netMINER_6", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 7 (120-150 cm)" + }, + { + "codes": 2699, + "names": "netMINER_7", + "units": "kgNm-2", + "descriptions": "Net N mineralization in soil layer 8 (150-200 cm)" + }, + { + "codes": 2700, + "names": "grossMINER_total", + "units": "kgNm-2", + "descriptions": "Total gross N mineralization" + }, + { + "codes": 2701, + "names": "potIMMOB_total", + "units": "kgNm-2", + "descriptions": "Total potential N immobilization" + }, + { + "codes": 2702, + "names": "netMINER_total", + "units": "kgNm-2", + "descriptions": "Total net N mineralization" + }, + { + "codes": 2703, + "names": "actIMMOB_total", + "units": "kgNm-2", + "descriptions": "Total actual N immobilization" + }, + { + "codes": 2704, + "names": "stomaCONDUCT_max", + "units": "ms-1", + "descriptions": "Maximal stomatal conductance with temperature-pressure correction" + }, + { + "codes": 2705, + "names": "m_Tmin", + "units": "dimless", + "descriptions": "Freezing night temperature multiplier" + }, + { + "codes": 2706, + "names": "m_SWCstress_layer_0", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 1 (0-3 cm)" + }, + { + "codes": 2707, + "names": "m_SWCstress_layer_1", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 2 (3-10 cm)" + }, + { + "codes": 2708, + "names": "m_SWCstress_layer_2", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 3 (10-30 cm)" + }, + { + "codes": 2709, + "names": "m_SWCstress_layer_3", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 4 (30-60 cm)" + }, + { + "codes": 2710, + "names": "m_SWCstress_layer_4", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 5 (60-90 cm)" + }, + { + "codes": 2711, + "names": "m_SWCstress_layer_5", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 6 (90-120 cm)" + }, + { + "codes": 2712, + "names": "m_SWCstress_layer_6", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 7 (120-150 cm)" + }, + { + "codes": 2713, + "names": "m_SWCstress_layer_7", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 8 (150-200 cm)" + }, + { + "codes": 2714, + "names": "m_SWCstress_layer_8", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 9 (200-400 cm)" + }, + { + "codes": 2715, + "names": "m_SWCstress_layer_9", + "units": "dimless", + "descriptions": "Soil water stress multiplier in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2716, + "names": "m_SWCstress", + "units": "dimless", + "descriptions": "Soil water properties multiplier" + }, + { + "codes": 2717, + "names": "m_ppfd_sun", + "units": "dimless", + "descriptions": "Sunlit PAR flux density multiplier" + }, + { + "codes": 2718, + "names": "m_ppfd_shade", + "units": "dimless", + "descriptions": "Sunshade PAR flux density multiplier" + }, + { + "codes": 2719, + "names": "m_vpd", + "units": "dimless", + "descriptions": "Vapor pressure deficit multiplier" + }, + { + "codes": 2720, + "names": "m_final_sun", + "units": "dimless", + "descriptions": "Sunlit product of all other multipliers" + }, + { + "codes": 2721, + "names": "m_final_shade", + "units": "dimless", + "descriptions": "Sunshade product of all other multipliers" + }, + { + "codes": 2722, + "names": "m_SWCstressLENGTH", + "units": "dimless", + "descriptions": "Soil water stress length multiplier" + }, + { + "codes": 2723, + "names": "m_extremT", + "units": "dimless", + "descriptions": "Extrem temperature multiplier" + }, + { + "codes": 2724, + "names": "SMSI", + "units": "prop", + "descriptions": "Soil moisture stress index" + }, + { + "codes": 2725, + "names": "gcorr", + "units": "dimless", + "descriptions": "Temperature and pressure correction factor for conductances" + }, + { + "codes": 2726, + "names": "gl_bl", + "units": "ms-1", + "descriptions": "Leaf boundary layer conductance" + }, + { + "codes": 2727, + "names": "gl_c", + "units": "ms-1", + "descriptions": "Leaf cuticular conductance" + }, + { + "codes": 2728, + "names": "gl_s_sun", + "units": "ms-1", + "descriptions": "Sunlit leaf-scale stomatal conductance" + }, + { + "codes": 2729, + "names": "gl_s_shade", + "units": "ms-1", + "descriptions": "Sunshade leaf-scale stomatal conductance" + }, + { + "codes": 2730, + "names": "gl_e_wv", + "units": "ms-1", + "descriptions": "Leaf conductance to evaporated water" + }, + { + "codes": 2731, + "names": "gl_sh", + "units": "ms-1", + "descriptions": "Leaf conductance to sensible heat" + }, + { + "codes": 2732, + "names": "gc_e_wv", + "units": "ms-1", + "descriptions": "Canopy conductance to evaporated water" + }, + { + "codes": 2733, + "names": "gc_sh", + "units": "ms-1", + "descriptions": "Canopy conductance to sensible heat" + }, + { + "codes": 2734, + "names": "annmax_lai", + "units": "m2m-2", + "descriptions": "Year-to-date maximum projected leaf area index" + }, + { + "codes": 2735, + "names": "IMMOBratio_0", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 1 (0-3 cm)" + }, + { + "codes": 2736, + "names": "IMMOBratio_1", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 2 (3-10 cm)" + }, + { + "codes": 2737, + "names": "IMMOBratio_2", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 3 (10-30 cm)" + }, + { + "codes": 2738, + "names": "IMMOBratio_3", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 4 (30-60 cm)" + }, + { + "codes": 2739, + "names": "IMMOBratio_4", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 5 (60-90 cm)" + }, + { + "codes": 2740, + "names": "IMMOBratio_5", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 6 (90-120 cm)" + }, + { + "codes": 2741, + "names": "IMMOBratio_6", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 7 (120-150 cm)" + }, + { + "codes": 2742, + "names": "IMMOBratio_7", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 8 (150-200 cm)" + }, + { + "codes": 2743, + "names": "IMMOBratio_8", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 9 (200-400 cm)" + }, + { + "codes": 2744, + "names": "IMMOBratio_9", + "units": "flag", + "descriptions": "Immobilization ratio in soil layer 9 (400-1000 cm)" + }, + { + "codes": 2745, + "names": "plantCalloc", + "units": "kgCm-2", + "descriptions": "Amount of allocated C" + }, + { + "codes": 2746, + "names": "plantNalloc", + "units": "kgNm-2", + "descriptions": "Amount of allocated N" + }, + { + "codes": 2747, + "names": "excess_c", + "units": "kgCm-2", + "descriptions": "Difference between available and allocated C" + }, + { + "codes": 2748, + "names": "pnow", + "units": "prop", + "descriptions": "Proportion of growth displayed on current day" + }, + { + "codes": 2749, + "names": "MRdeficit_nw", + "units": "flag", + "descriptions": "Flag of maint.resp.calculation deficit for nw-biomass" + }, + { + "codes": 2750, + "names": "MRdeficit_w", + "units": "flag", + "descriptions": "Flag of maint.resp.calculation deficit for w-biomass" + }, + { + "codes": 2751, + "names": "plantNdemand", + "units": "kgNm-2", + "descriptions": "Amount of plant N demand" + }, + { + "codes": 2752, + "names": "assim_Tcoeff", + "units": "dimless", + "descriptions": "Maximum temperature limitation factor of photosynthesis" + }, + { + "codes": 2753, + "names": "assim_SScoeff", + "units": "dimless", + "descriptions": "Soil moisture stress limitation factor of photosynthesis" + }, + { + "codes": 2754, + "names": "cumNstress", + "units": "n", + "descriptions": "Cumulative soil N stress" + }, + { + "codes": 2755, + "names": "SWCstressLENGTH", + "units": "dimless$C$", + "descriptions": "Limitiation factor of SWC-stress length" + }, + { + "codes": 2756, + "names": "WFPS_0", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 1 (0-3 cm)" + }, + { + "codes": 2757, + "names": "WFPS_1", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 2 (3-10 cm)" + }, + { + "codes": 2758, + "names": "WFPS_2", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 3 (10-30 cm)" + }, + { + "codes": 2759, + "names": "WFPS_3", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 4 (30-60 cm)" + }, + { + "codes": 2760, + "names": "WFPS_4", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 5 (60-90 cm)" + }, + { + "codes": 2761, + "names": "WFPS_5", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 6 (90-120 cm)" + }, + { + "codes": 2762, + "names": "WFPS_6", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 7 (120-150 cm)" + }, + { + "codes": 2763, + "names": "WFPS_7", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 8 (150-200 cm)" + }, + { + "codes": 2764, + "names": "WFPS_8", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 9 (200-400 cm)" + }, + { + "codes": 2765, + "names": "WFPS_9", + "units": "m3m-3", + "descriptions": "Water filled pore spaceof soil layer 10 (400-1000 cm)" + }, + { + "codes": 2766, + "names": "ws_nitrif_0", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 1 (0-3 cm)" + }, + { + "codes": 2767, + "names": "ws_nitrif_1", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 2 (3-10 cm)" + }, + { + "codes": 2768, + "names": "ws_nitrif_2", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 3 (10-30 cm)" + }, + { + "codes": 2769, + "names": "ws_nitrif_3", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 4 (30-60 cm)" + }, + { + "codes": 2770, + "names": "ws_nitrif_4", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 5 (60-90 cm)" + }, + { + "codes": 2771, + "names": "ws_nitrif_5", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 6 (90-120 cm)" + }, + { + "codes": 2772, + "names": "ws_nitrif_6", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 7 (120-150 cm)" + }, + { + "codes": 2773, + "names": "ws_nitrif_7", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 8 (150-200 cm)" + }, + { + "codes": 2774, + "names": "ws_nitrif_8", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 9 (200-400 cm)" + }, + { + "codes": 2775, + "names": "ws_nitrif_9", + "units": "dimless", + "descriptions": "Nitrification water filled pore space scalar in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2776, + "names": "ps_nitrif_0", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 1 (0-3 cm)" + }, + { + "codes": 2777, + "names": "ps_nitrif_1", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 2 (3-10 cm)" + }, + { + "codes": 2778, + "names": "ps_nitrif_2", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 3 (10-30 cm)" + }, + { + "codes": 2779, + "names": "ps_nitrif_3", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 4 (30-60 cm)" + }, + { + "codes": 2780, + "names": "ps_nitrif_4", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 5 (60-90 cm)" + }, + { + "codes": 2781, + "names": "ps_nitrif_5", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 6 (90-120 cm)" + }, + { + "codes": 2782, + "names": "ps_nitrif_6", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 7 (120-150 cm)" + }, + { + "codes": 2783, + "names": "ps_nitrif_7", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 8 (150-200 cm)" + }, + { + "codes": 2784, + "names": "ps_nitrif_8", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 9 (200-400 cm)" + }, + { + "codes": 2785, + "names": "ps_nitrif_9", + "units": "dimless", + "descriptions": "Nitrification pH response function in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2786, + "names": "phenphase_date_0", + "units": "dimless", + "descriptions": "First day of the phenphase1" + }, + { + "codes": 2787, + "names": "phenphase_date_1", + "units": "dimless", + "descriptions": "First day of the phenphase2" + }, + { + "codes": 2788, + "names": "phenphase_date_2", + "units": "dimless", + "descriptions": "First day of the phenphase3" + }, + { + "codes": 2789, + "names": "phenphase_date_3", + "units": "dimless", + "descriptions": "First day of the phenphase4" + }, + { + "codes": 2790, + "names": "phenphase_date_4", + "units": "dimless", + "descriptions": "First day of the phenphase5" + }, + { + "codes": 2791, + "names": "phenphase_date_5", + "units": "dimless", + "descriptions": "First day of the phenphase6" + }, + { + "codes": 2792, + "names": "phenphase_date_6", + "units": "dimless", + "descriptions": "First day of the phenphase7" + }, + { + "codes": 2793, + "names": "WPM", + "units": "dimless", + "descriptions": "Daily whole plant mortality value" + }, + { + "codes": 2794, + "names": "flower_date", + "units": "day of year", + "descriptions": "Start of flowering phenophase" + }, + { + "codes": 2795, + "names": "SCpercent", + "units": "%", + "descriptions": "Percent of soil coverage" + }, + { + "codes": 2796, + "names": "SC_EVPred", + "units": "dimless", + "descriptions": "evaporation reduction of soil cover" + }, + { + "codes": 2797, + "names": "GWlayer", + "units": "dimless", + "descriptions": "Number of layer containing groundwater table" + }, + { + "codes": 2798, + "names": "CFlayer", + "units": "dimless", + "descriptions": "Number of layer containing the upper layer of capillary fringe" + }, + { + "codes": 2799, + "names": "CFD", + "units": "m", + "descriptions": "Depth of upper layer of capillary fringe" + }, + { + "codes": 2800, + "names": "RCN", + "units": "m", + "descriptions": "Runoff curve number" + }, + { + "codes": 2801, + "names": "soilB_0", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 1 (0-3 cm)" + }, + { + "codes": 2802, + "names": "soilB_1", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 2 (3-10 cm)" + }, + { + "codes": 2803, + "names": "soilB_2", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 3 (10-30 cm)" + }, + { + "codes": 2804, + "names": "soilB_3", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 4 (30-60 cm)" + }, + { + "codes": 2805, + "names": "soilB_4", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 5 (60-90 cm)" + }, + { + "codes": 2806, + "names": "soilB_5", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 6 (90-120 cm)" + }, + { + "codes": 2807, + "names": "soilB_6", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 7 (120-150 cm)" + }, + { + "codes": 2808, + "names": "soilB_7", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 8 (150-200 cm)" + }, + { + "codes": 2809, + "names": "soilB_8", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 9 (200-400 cm)" + }, + { + "codes": 2810, + "names": "soilB_9", + "units": "dimless", + "descriptions": "Clapp-Hornberger \"\"b\"\" parameter in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2811, + "names": "BD_0", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 1 (0-3 cm)" + }, + { + "codes": 2812, + "names": "BD_1", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 2 (3-10 cm)" + }, + { + "codes": 2813, + "names": "BD_2", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 3 (10-30 cm)" + }, + { + "codes": 2814, + "names": "BD_3", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 4 (30-60 cm)" + }, + { + "codes": 2815, + "names": "BD_4", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 5 (60-90 cm)" + }, + { + "codes": 2816, + "names": "BD_5", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 6 (90-120 cm)" + }, + { + "codes": 2817, + "names": "BD_6", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 7 (120-150 cm)" + }, + { + "codes": 2818, + "names": "BD_7", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 8 (150-200 cm)" + }, + { + "codes": 2819, + "names": "BD_8", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 9 (200-400 cm)" + }, + { + "codes": 2820, + "names": "BD_9", + "units": "gm-3", + "descriptions": "Bulk density in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2821, + "names": "VWCsat_0", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2822, + "names": "VWCsat_1", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2823, + "names": "VWCsat_2", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2824, + "names": "VWCsat_3", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2825, + "names": "VWCsat_4", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2826, + "names": "VWCsat_5", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2827, + "names": "VWCsat_6", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2828, + "names": "VWCsat_7", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2829, + "names": "VWCsat_8", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2830, + "names": "VWCsat_9", + "units": "m3m-3", + "descriptions": "Volumetric water content at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2831, + "names": "VWCfc_0", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2832, + "names": "VWCfc_1", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2833, + "names": "VWCfc_2", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2834, + "names": "VWCfc_3", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2835, + "names": "VWCfc_4", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2836, + "names": "VWCfc_5", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2837, + "names": "VWCfc_6", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2838, + "names": "VWCfc_7", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2839, + "names": "VWCfc_8", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2840, + "names": "VWCfc_9", + "units": "m3m-3", + "descriptions": "Volumetric water content at field capacity (=-0.033 MPa) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2841, + "names": "VWCwp_0", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2842, + "names": "VWCwp_1", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2843, + "names": "VWCwp_2", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2844, + "names": "VWCwp_3", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2845, + "names": "VWCwp_4", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2846, + "names": "VWCwp_5", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2847, + "names": "VWCwp_6", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2848, + "names": "VWCwp_7", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2849, + "names": "VWCwp_8", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2850, + "names": "VWCwp_9", + "units": "m3m-3", + "descriptions": "Volumetric water content at wilting point (= pF 4.2) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2851, + "names": "VWChw_0", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 1 (0-3 cm)" + }, + { + "codes": 2852, + "names": "VWChw_1", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 2 (3-10 cm)" + }, + { + "codes": 2853, + "names": "VWChw_2", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 3 (10-30 cm)" + }, + { + "codes": 2854, + "names": "VWChw_3", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 4 (30-60 cm)" + }, + { + "codes": 2855, + "names": "VWChw_4", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 5 (60-90 cm)" + }, + { + "codes": 2856, + "names": "VWChw_5", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 6 (90-120 cm)" + }, + { + "codes": 2857, + "names": "VWChw_6", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 7 (120-150 cm)" + }, + { + "codes": 2858, + "names": "VWChw_7", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 8 (150-200 cm)" + }, + { + "codes": 2859, + "names": "VWChw_8", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 9 (200-400 cm)" + }, + { + "codes": 2860, + "names": "VWChw_9", + "units": "m3m-3", + "descriptions": "Volumetric water content at hygroscopic water point (= pF 6.2) in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2861, + "names": "PSIsat_0", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2862, + "names": "PSIsat_1", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2863, + "names": "PSIsat_2", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2864, + "names": "PSIsat_3", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2865, + "names": "PSIsat_4", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2866, + "names": "PSIsat_5", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2867, + "names": "PSIsat_6", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2868, + "names": "PSIsat_7", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2869, + "names": "PSIsat_8", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2870, + "names": "PSIsat_9", + "units": "MPa", + "descriptions": "Soil matric potential at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2871, + "names": "PSIfc_0", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2872, + "names": "PSIfc_1", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2873, + "names": "PSIfc_2", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2874, + "names": "PSIfc_3", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2875, + "names": "PSIfc_4", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2876, + "names": "PSIfc_5", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2877, + "names": "PSIfc_6", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2878, + "names": "PSIfc_7", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2879, + "names": "PSIfc_8", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2880, + "names": "PSIfc_9", + "units": "MPa", + "descriptions": "Soil matric potential at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2881, + "names": "PSIwp_0", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 1 (0-3 cm)" + }, + { + "codes": 2882, + "names": "PSIwp_1", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 2 (3-10 cm)" + }, + { + "codes": 2883, + "names": "PSIwp_2", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 3 (10-30 cm)" + }, + { + "codes": 2884, + "names": "PSIwp_3", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 4 (30-60 cm)" + }, + { + "codes": 2885, + "names": "PSIwp_4", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 5 (60-90 cm)" + }, + { + "codes": 2886, + "names": "PSIwp_5", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 6 (90-120 cm)" + }, + { + "codes": 2887, + "names": "PSIwp_6", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 7 (120-150 cm)" + }, + { + "codes": 2888, + "names": "PSIwp_7", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 8 (150-200 cm)" + }, + { + "codes": 2889, + "names": "PSIwp_8", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 9 (200-400 cm)" + }, + { + "codes": 2890, + "names": "PSIwp_9", + "units": "MPa", + "descriptions": "Soil matric potential at wilting point in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2891, + "names": "hydrCONDUCTsat_0", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2892, + "names": "hydrCONDUCTsat_1", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2893, + "names": "hydrCONDUCTsat_2", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2894, + "names": "hydrCONDUCTsat_3", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2895, + "names": "hydrCONDUCTsat_4", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2896, + "names": "hydrCONDUCTsat_5", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2897, + "names": "hydrCONDUCTsat_6", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2898, + "names": "hydrCONDUCTsat_7", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2899, + "names": "hydrCONDUCTsat_8", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2900, + "names": "hydrCONDUCTsat_9", + "units": "ms-1", + "descriptions": "Hidraulic conductivity at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2901, + "names": "hydrDIFFUSsat_0", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 1 (0-3 cm)" + }, + { + "codes": 2902, + "names": "hydrDIFFUSsat_1", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 2 (3-10 cm)" + }, + { + "codes": 2903, + "names": "hydrDIFFUSsat_2", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 3 (10-30 cm)" + }, + { + "codes": 2904, + "names": "hydrDIFFUSsat_3", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 4 (30-60 cm)" + }, + { + "codes": 2905, + "names": "hydrDIFFUSsat_4", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 5 (60-90 cm)" + }, + { + "codes": 2906, + "names": "hydrDIFFUSsat_5", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 6 (90-120 cm)" + }, + { + "codes": 2907, + "names": "hydrDIFFUSsat_6", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 7 (120-150 cm)" + }, + { + "codes": 2908, + "names": "hydrDIFFUSsat_7", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 8 (150-200 cm)" + }, + { + "codes": 2909, + "names": "hydrDIFFUSsat_8", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 9 (200-400 cm)" + }, + { + "codes": 2910, + "names": "hydrDIFFUSsat_9", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at saturation in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2911, + "names": "hydrCONDUCTfc_0", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2912, + "names": "hydrCONDUCTfc_1", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2913, + "names": "hydrCONDUCTfc_2", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2914, + "names": "hydrCONDUCTfc_3", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2915, + "names": "hydrCONDUCTfc_4", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2916, + "names": "hydrCONDUCTfc_5", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2917, + "names": "hydrCONDUCTfc_6", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2918, + "names": "hydrCONDUCTfc_7", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2919, + "names": "hydrCONDUCTfc_8", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2920, + "names": "hydrCONDUCTfc_9", + "units": "m3s-1", + "descriptions": "Hidraulic conductivity at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2921, + "names": "hydrDIFFUSfc_0", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 1 (0-3 cm)" + }, + { + "codes": 2922, + "names": "hydrDIFFUSfc_1", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 2 (3-10 cm)" + }, + { + "codes": 2923, + "names": "hydrDIFFUSfc_2", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 3 (10-30 cm)" + }, + { + "codes": 2924, + "names": "hydrDIFFUSfc_3", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 4 (30-60 cm)" + }, + { + "codes": 2925, + "names": "hydrDIFFUSfc_4", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 5 (60-90 cm)" + }, + { + "codes": 2926, + "names": "hydrDIFFUSfc_5", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 6 (90-120 cm)" + }, + { + "codes": 2927, + "names": "hydrDIFFUSfc_6", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 7 (120-150 cm)" + }, + { + "codes": 2928, + "names": "hydrDIFFUSfc_7", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 8 (150-200 cm)" + }, + { + "codes": 2929, + "names": "hydrDIFFUSfc_8", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 9 (200-400 cm)" + }, + { + "codes": 2930, + "names": "hydrDIFFUSfc_9", + "units": "m2s-1", + "descriptions": "Hidraulic diffusivity at field capacity in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2931, + "names": "GWeff_0", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 1 (0-3 cm)" + }, + { + "codes": 2932, + "names": "GWeff_1", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 2 (3-10 cm)" + }, + { + "codes": 2933, + "names": "GWeff_2", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 3 (10-30 cm)" + }, + { + "codes": 2934, + "names": "GWeff_3", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 4 (30-60 cm)" + }, + { + "codes": 2935, + "names": "GWeff_4", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 5 (60-90 cm)" + }, + { + "codes": 2936, + "names": "GWeff_5", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 6 (90-120 cm)" + }, + { + "codes": 2937, + "names": "GWeff_6", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 7 (120-150 cm)" + }, + { + "codes": 2938, + "names": "GWeff_7", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 8 (150-200 cm)" + }, + { + "codes": 2939, + "names": "GWeff_8", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 9 (200-400 cm)" + }, + { + "codes": 2940, + "names": "GWeff_9", + "units": "dimless", + "descriptions": "Coefficient of groundwater effect in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2941, + "names": "CFeff_0", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 1 (0-3 cm)" + }, + { + "codes": 2942, + "names": "CFeff_1", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 2 (3-10 cm)" + }, + { + "codes": 2943, + "names": "CFeff_2", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 3 (10-30 cm)" + }, + { + "codes": 2944, + "names": "CFeff_3", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 4 (30-60 cm)" + }, + { + "codes": 2945, + "names": "CFeff_4", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 5 (60-90 cm)" + }, + { + "codes": 2946, + "names": "CFeff_5", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 6 (90-120 cm)" + }, + { + "codes": 2947, + "names": "CFeff_6", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 7 (120-150 cm)" + }, + { + "codes": 2948, + "names": "CFeff_7", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 8 (150-200 cm)" + }, + { + "codes": 2949, + "names": "CFeff_8", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 9 (200-400 cm)" + }, + { + "codes": 2950, + "names": "CFeff_9", + "units": "dimless", + "descriptions": "Coefficient of capillary zone effect in soil layer 10 (400-1000 cm)" + }, + { + "codes": 2951, + "names": "GWD", + "descriptions": "Groundwater depth" + }, + { + "codes": 2952, + "names": "co2", + "units": "ppm", + "descriptions": "Sunlit atmospheric CO2 conc." + }, + { + "codes": 2953, + "names": "co2", + "units": "ppm", + "descriptions": "Sunshade atmospheric CO2 conc." + }, + { + "codes": 2954, + "names": "t", + "units": "Celsius", + "descriptions": "Sunlit temperature" + }, + { + "codes": 2955, + "names": "t", + "units": "Celsius", + "descriptions": "Sunshade temperature" + }, + { + "codes": 2956, + "names": "lnc", + "units": "kgNleafm-2", + "descriptions": "Leaf N per unit sunlit leaf area" + }, + { + "codes": 2957, + "names": "lnc", + "units": "kgNleafm-2", + "descriptions": "Leaf N per unit sunshade area" + }, + { + "codes": 2958, + "names": "flnr", + "units": "kgNRubiscokgNleaf-1", + "descriptions": "Sunlit fraction of leaf N in Rubisco" + }, + { + "codes": 2959, + "names": "flnr", + "units": "kgNRubiscokgNleaf-1", + "descriptions": "Sunshade fraction of leaf N in Rubisco" + }, + { + "codes": 2960, + "names": "flnp", + "units": "kgNPEPkgNleaf-1", + "descriptions": "Sunlit fraction of leaf N in PEP Carboxylase" + }, + { + "codes": 2961, + "names": "flnp", + "units": "kgNPEPkgNleaf-1", + "descriptions": "Sunshade fraction of leaf N in PEP Carboxylase" + }, + { + "codes": 2962, + "names": "ppfd", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit PAR flux per unit sunlit leaf area" + }, + { + "codes": 2963, + "names": "ppfd", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade PAR flux per unit sunlit leaf area" + }, + { + "codes": 2964, + "names": "g", + "units": "mu$mol$ m-2 s-1Pa-1", + "descriptions": "Sunlit conductance to CO2" + }, + { + "codes": 2965, + "names": "g", + "units": "mu$mol$ m-2 s-1Pa-1", + "descriptions": "Sunshade conductance to CO2" + }, + { + "codes": 2966, + "names": "dlmr", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit day leaf maintenance respiration" + }, + { + "codes": 2967, + "names": "dlmr", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade day leaf maintenance respiration" + }, + { + "codes": 2968, + "names": "Ci", + "units": "Pa", + "descriptions": "Sunlit intercellular CO2 concentration" + }, + { + "codes": 2969, + "names": "Ci", + "units": "Pa", + "descriptions": "Sunshade intercellular CO2 concentration" + }, + { + "codes": 2970, + "names": "O2", + "units": "Pa", + "descriptions": "Sunlit atmospheric O2 concentration" + }, + { + "codes": 2971, + "names": "O2", + "units": "Pa", + "descriptions": "Sunshade atmospheric O2 concentration" + }, + { + "codes": 2972, + "names": "Ca", + "units": "Pa", + "descriptions": "Sunlit atmospheric CO2 concentration" + }, + { + "codes": 2973, + "names": "Ca", + "units": "Pa", + "descriptions": "Sunshade atmospheric CO2 concentration" + }, + { + "codes": 2974, + "names": "gamma", + "units": "Pa", + "descriptions": "Sunlit CO2 compensation point" + }, + { + "codes": 2975, + "names": "gamma", + "units": "Pa", + "descriptions": "Sunshade CO2 compensation point" + }, + { + "codes": 2976, + "names": "Kc", + "units": "Pa", + "descriptions": "Sunlit MM constant carboxylation" + }, + { + "codes": 2977, + "names": "Kc", + "units": "Pa", + "descriptions": "Sunshade MM constant carboxylation" + }, + { + "codes": 2978, + "names": "Ko", + "units": "Pa", + "descriptions": "Sunlit MM constant oxygenation" + }, + { + "codes": 2979, + "names": "Ko", + "units": "Pa", + "descriptions": "Sunshade MM constant oxygenation" + }, + { + "codes": 2980, + "names": "Vmax", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit max. rate of carboxylation" + }, + { + "codes": 2981, + "names": "Vmax", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade max. rate of carboxylation" + }, + { + "codes": 2982, + "names": "Jmax", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit max. rate of electron transport" + }, + { + "codes": 2983, + "names": "Jmax", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade max. rate of electron transport" + }, + { + "codes": 2984, + "names": "J", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit rate of RuBP regeneration" + }, + { + "codes": 2985, + "names": "J", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade rate of RuBP regeneration" + }, + { + "codes": 2986, + "names": "Av", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit carboxylation limited assimilation" + }, + { + "codes": 2987, + "names": "Av", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade carboxylation limited assimilation" + }, + { + "codes": 2988, + "names": "Aj", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit RuBP regeneration limited assimilation" + }, + { + "codes": 2989, + "names": "Aj", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade RuBP regeneration limited assimilation" + }, + { + "codes": 2990, + "names": "A", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunlit final assimilation rate" + }, + { + "codes": 2991, + "names": "A", + "units": "mu$mol$ m-2 s-1", + "descriptions": "Sunshade final assimilation rate" + }, + { + "codes": 2992, + "names": "pa", + "units": "Pa", + "descriptions": "Sunlit atmospheric pressure" + }, + { + "codes": 2993, + "names": "pa", + "units": "Pa", + "descriptions": "Sunshade atmospheric pressure" + }, + { + "codes": 3000, + "names": "annprcp", + "units": "mm year-1", + "descriptions": "Annual precipitation" + }, + { + "codes": 3001, + "names": "anntavg", + "units": "Celsius", + "descriptions": "Annual average air temperature" + }, + { + "codes": 3002, + "names": "cumRunoff", + "units": "kgH2Om-2year-1", + "descriptions": "Cumulated SUM of runoff" + }, + { + "codes": 3003, + "names": "cumWleachRZ", + "units": "kgH2Om-2year-1", + "descriptions": "Cumulated SUM of water leaching from rootzone" + }, + { + "codes": 3004, + "names": "N2Oflux", + "units": "kgNm-2 day-1", + "descriptions": "Daily N2O flux" + }, + { + "codes": 3005, + "names": "NEP", + "units": "kgCm-2 day-1", + "descriptions": "Net ecosystem production" + }, + { + "codes": 3006, + "names": "NPP", + "units": "kgCm-2 day-1", + "descriptions": "Net primary production" + }, + { + "codes": 3007, + "names": "NEE", + "units": "kgCm-2 day-1", + "descriptions": "Net ecosystem exchange" + }, + { + "codes": 3008, + "names": "NBP", + "units": "kgCm-2 day-1", + "descriptions": "Net biom production" + }, + { + "codes": 3009, + "names": "GPP", + "units": "kgCm-2 day-1", + "descriptions": "gross primary production" + }, + { + "codes": 3010, + "names": "MR", + "units": "kgCm-2 day-1", + "descriptions": "Maintenance respiration" + }, + { + "codes": 3011, + "names": "GR", + "units": "kgCm-2 day-1", + "descriptions": "growth respiration" + }, + { + "codes": 3012, + "names": "HR", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration" + }, + { + "codes": 3013, + "names": "SR", + "units": "kgCm-2 day-1", + "descriptions": "\"Soil respiration" + }, + { + "codes": 3014, + "names": "TR", + "units": "kgCm-2 day-1", + "descriptions": "\"Total respiration" + }, + { + "codes": 3015, + "names": "fire", + "units": "kgCm-2 day-1", + "descriptions": "Fire losses" + }, + { + "codes": 3016, + "names": "litfallc", + "units": "kgCm-2 day-1", + "descriptions": "Total litterfall" + }, + { + "codes": 3017, + "names": "litfallc_above", + "units": "kgCm-2 day-1", + "descriptions": "Total litterfall aboveground" + }, + { + "codes": 3018, + "names": "litfallc_below", + "units": "kgCm-2 day-1", + "descriptions": "Total litterfall belowground" + }, + { + "codes": 3019, + "names": "litdecomp", + "units": "kgCm-2 day-1", + "descriptions": "Total litter decomposition" + }, + { + "codes": 3020, + "names": "litfire", + "units": "kgCm-2 day-1", + "descriptions": "Total litter fire mortality" + }, + { + "codes": 3021, + "names": "litter", + "units": "kgCm-2", + "descriptions": "Total amount of litter" + }, + { + "codes": 3022, + "names": "cumNPP", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of NPP" + }, + { + "codes": 3023, + "names": "cumNEP", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of NEP" + }, + { + "codes": 3024, + "names": "cumNEE", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of NEE" + }, + { + "codes": 3025, + "names": "cumGPP", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of GPP" + }, + { + "codes": 3026, + "names": "cumMR", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of MR" + }, + { + "codes": 3027, + "names": "cumGR", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of GR" + }, + { + "codes": 3028, + "names": "cumHR", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of HR" + }, + { + "codes": 3029, + "names": "cumTR", + "units": "kgCm-2", + "descriptions": "Cumulative SUM of total ecosystem respiration" + }, + { + "codes": 3030, + "names": "cumN2Oflux", + "units": "kgNm-2", + "descriptions": "Cumulative annual SUM N2O flux" + }, + { + "codes": 3031, + "names": "cumCloss_MGM", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of management C loss" + }, + { + "codes": 3032, + "names": "cumCplus_MGM", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of management C plus" + }, + { + "codes": 3033, + "names": "cumCloss_THN_w", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of thinning woody C loss" + }, + { + "codes": 3034, + "names": "cumCloss_THN_nw", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of thinning non-woody C loss" + }, + { + "codes": 3035, + "names": "cumCloss_MOW", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of mowing C loss" + }, + { + "codes": 3036, + "names": "cumCloss_HRV", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of harvesting C loss" + }, + { + "codes": 3037, + "names": "cumYieldC_HRV", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of harvested yield" + }, + { + "codes": 3038, + "names": "cumCloss_PLG", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of ploughing C loss" + }, + { + "codes": 3039, + "names": "cumCloss_GRZ", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of grazing C loss" + }, + { + "codes": 3040, + "names": "cumCplus_GRZ", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of grazing C plus" + }, + { + "codes": 3041, + "names": "cumCplus_FRZ", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of fertilizing C plus" + }, + { + "codes": 3042, + "names": "cumCplus_PLT", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of planting C plus" + }, + { + "codes": 3043, + "names": "cumNplus_GRZ", + "units": "kgNm-2", + "descriptions": "Cumulative annual SUM of grazing N plus" + }, + { + "codes": 3044, + "names": "cumNplus_FRZ", + "units": "kgNm-2", + "descriptions": "Cumulative annual SUM of fertilizing N plus" + }, + { + "codes": 3045, + "names": "cumCloss_SNSC", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of senescence C loss" + }, + { + "codes": 3046, + "names": "cumCplus_STDB", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of standing dead biome C plus" + }, + { + "codes": 3047, + "names": "cumCplus_CTDB", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of cut-down dead biome C plus" + }, + { + "codes": 3048, + "names": "cumEVP", + "units": "kgH2Om-2", + "descriptions": "Cumulative SUM of evaporation" + }, + { + "codes": 3049, + "names": "cumTRP", + "units": "kgH2Om-2", + "descriptions": "Cumulative SUM of transpiration" + }, + { + "codes": 3050, + "names": "cumET", + "units": "kgH2Om-2", + "descriptions": "Cumulative SUM of evapotranspiration" + }, + { + "codes": 3051, + "names": "leafDM", + "units": "kgDMm-2", + "descriptions": "Dry matter content of leaves" + }, + { + "codes": 3052, + "names": "leaflitrDM", + "units": "kgDMm-2", + "descriptions": "Dry matteC content of leaf litter" + }, + { + "codes": 3053, + "names": "frootDM", + "units": "kgDMm-2", + "descriptions": "Dry matter content of fine roots" + }, + { + "codes": 3054, + "names": "yieldDM", + "units": "kgDMm-2", + "descriptions": "Dry matter content of yields" + }, + { + "codes": 3055, + "names": "softstemDM", + "units": "kgDMm-2", + "descriptions": "Dry matter content of softstems" + }, + { + "codes": 3056, + "names": "livewoodDM", + "units": "kgDMm-2", + "descriptions": "Dry matter content of live wood" + }, + { + "codes": 3057, + "names": "deadwoodDM", + "units": "kgDMm-2", + "descriptions": "Dry matter content of dead wood" + }, + { + "codes": 3058, + "names": "vegC", + "units": "kgCm-2", + "descriptions": "Total vegetation C content" + }, + { + "codes": 3059, + "names": "litrN_total", + "units": "kgNm-2", + "descriptions": "Total Litter N content" + }, + { + "codes": 3060, + "names": "litrC_total", + "units": "kgCm-2", + "descriptions": "Total litter C content" + }, + { + "codes": 3061, + "names": "soilC_total", + "units": "kgCm-2", + "descriptions": "Total soil C content" + }, + { + "codes": 3062, + "names": "soilN_total", + "units": "kgNm-2", + "descriptions": "Total soil N content" + }, + { + "codes": 3063, + "names": "sminN_total", + "units": "kgNm-2", + "descriptions": "Total soil mineralized N content" + }, + { + "codes": 3064, + "names": "totalC", + "units": "kgCm-2", + "descriptions": "Total C content" + }, + { + "codes": 3065, + "names": "stableSOC_top30", + "units": "%", + "descriptions": "C content of stable SOM in soil top 0-30 cm" + }, + { + "codes": 3066, + "names": "SOM_C_top30", + "units": "%", + "descriptions": "Soil organic matter C content in soil top 0-30 cm" + }, + { + "codes": 3067, + "names": "SOM_N_top30", + "units": "%", + "descriptions": "Soil organic matter N content in soil top 0-30 cm" + }, + { + "codes": 3068, + "names": "NH4_top30avail", + "units": "ppm", + "descriptions": "Available soil NH4-N content in soil top 0-30 cm" + }, + { + "codes": 3069, + "names": "NO3_top30avail", + "units": "ppm", + "descriptions": "Available soil NO3-N content in soil top 0-30 cm" + }, + { + "codes": 3070, + "names": "SOM_C_3", + "units": "%", + "descriptions": "Soil organic matter C content in 30-60 cm" + }, + { + "codes": 3071, + "names": "SOM_C_4", + "units": "%", + "descriptions": "Soil organic matter C content in 60-90 cm" + }, + { + "codes": 3072, + "names": "litrCwdC_total", + "units": "kgNm-2", + "descriptions": "Total Litter and cwdc C content" + }, + { + "codes": 3073, + "names": "litrCwdN_total", + "units": "kgCm-2", + "descriptions": "Total litter and cwdc N content" + }, + { + "codes": 3074, + "names": "sminN_top30avail", + "units": "ppm", + "descriptions": "Available mineralized N in soil top 0-30 cm" + }, + { + "codes": 3075, + "names": "leafc_LandD", + "units": "kgCm-2", + "descriptions": "Live and dead leaf C content" + }, + { + "codes": 3076, + "names": "frootc_LandD", + "units": "kgCm-2", + "descriptions": "Live and dead fine root C content" + }, + { + "codes": 3077, + "names": "yield_LandD", + "units": "kgCm-2", + "descriptions": "Live and dead yield C content" + }, + { + "codes": 3078, + "names": "softstemc_LandD", + "units": "kgCm-2", + "descriptions": "Live and dead sofstem C content" + }, + { + "codes": 3079, + "names": "sminNH4_ppm_0", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 1 (0-3 cm)" + }, + { + "codes": 3080, + "names": "sminNH4_ppm_1", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 2 (3-10 cm)" + }, + { + "codes": 3081, + "names": "sminNH4_ppm_2", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 3 (10-30 cm)" + }, + { + "codes": 3082, + "names": "sminNH4_ppm_3", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 4 (30-60 cm)" + }, + { + "codes": 3083, + "names": "sminNH4_ppm_4", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 5 (60-90 cm)" + }, + { + "codes": 3084, + "names": "sminNH4_ppm_5", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 6 (90-120 cm)" + }, + { + "codes": 3085, + "names": "sminNH4_ppm_6", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 7 (120-150 cm)" + }, + { + "codes": 3086, + "names": "sminNH4_ppm_7", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 8 (150-200 cm)" + }, + { + "codes": 3087, + "names": "sminNH4_ppm_8", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 9 (200-400 cm)" + }, + { + "codes": 3088, + "names": "sminNH4_ppm_9", + "units": "ppm", + "descriptions": "Soil NH4-N content in ppm of soil layer 10 (400-1000 cm)" + }, + { + "codes": 3089, + "names": "sminNO3_ppm_0", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 1 (0-3 cm)" + }, + { + "codes": 3090, + "names": "sminNO3_ppm_1", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 2 (3-10 cm)" + }, + { + "codes": 3091, + "names": "sminNO3_ppm_2", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 3 (10-30 cm)" + }, + { + "codes": 3092, + "names": "sminNO3_ppm_3", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 4 (30-60 cm)" + }, + { + "codes": 3093, + "names": "sminNO3_ppm_4", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 5 (60-90 cm)" + }, + { + "codes": 3094, + "names": "sminNO3_ppm_5", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 6 (90-120 cm)" + }, + { + "codes": 3095, + "names": "sminNO3_ppm_6", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 7 (120-150 cm)" + }, + { + "codes": 3096, + "names": "sminNO3_ppm_7", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 8 (150-200 cm)" + }, + { + "codes": 3097, + "names": "sminNO3_ppm_8", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 9 (200-400 cm)" + }, + { + "codes": 3098, + "names": "sminNO3_ppm_9", + "units": "ppm", + "descriptions": "Soil NO3-N content in ppm of soil layer 10 (400-1000 cm)" + }, + { + "codes": 3099, + "names": "CH4flux_total", + "units": "kgCm-2 day-1", + "descriptions": "Estimated total CH4 flux of ecosystem" + }, + { + "codes": 3100, + "names": "NGB", + "units": "kgCm-2day-1", + "descriptions": "Net greenhouse gas balance" + }, + { + "codes": 3101, + "names": "cumNGB", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of NGB" + }, + { + "codes": 3102, + "names": "Cflux_lateral", + "units": "kgCm-2day-1", + "descriptions": "Lateral C flux" + }, + { + "codes": 3103, + "names": "harvestIndex", + "units": "dimless", + "descriptions": "Harvest index" + }, + { + "codes": 3104, + "names": "sminNavail_total", + "units": "kgNm-2", + "descriptions": "Total available soil mineralized N content" + }, + { + "codes": 3105, + "names": "cumNleachRZ", + "units": "kgNm-2", + "descriptions": "Cumulated SUM of N leaching from rootzone" + }, + { + "codes": 3106, + "names": "cumSR", + "units": "kgCm-2", + "descriptions": "Cumulated SUM of soil respiration" + }, + { + "codes": 3107, + "names": "CNlitr_total", + "units": "kgCkgN-1", + "descriptions": "C:N ratio of litter pool" + }, + { + "codes": 3108, + "names": "CNsoil_total", + "units": "kgCkgN-1", + "descriptions": "C:N ratio of soil pool" + }, + { + "codes": 3109, + "names": "litr1HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of labile litter in soil" + }, + { + "codes": 3110, + "names": "litr2HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of unshielded cellulose soil" + }, + { + "codes": 3111, + "names": "litr4HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of lignin portion of litter in soil" + }, + { + "codes": 3112, + "names": "soil1HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (labile) in soil" + }, + { + "codes": 3113, + "names": "soil2HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (fast) in soil" + }, + { + "codes": 3114, + "names": "soil3HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (slow) in soil" + }, + { + "codes": 3115, + "names": "soil4HR_total", + "units": "kgCm-2 day-1", + "descriptions": "Heterotroph respiration of SOM pool (stable) in soil" + }, + { + "codes": 3116, + "names": "yieldDM_HRV", + "units": "kgDMm-2", + "descriptions": "Dry matter content of yield at harvest (annual value)" + }, + { + "codes": 3117, + "names": "cumCloss_PLT", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of planting C loss (standing dead biomass)" + }, + { + "codes": 3118, + "names": "leafCN", + "units": "kgCkgN-1", + "descriptions": "C and N ratio of leaves (live+standind dead)" + }, + { + "codes": 3119, + "names": "frootCN", + "units": "kgCkgN-1", + "descriptions": "C and N ratio of fine roots" + }, + { + "codes": 3120, + "names": "yieldN", + "units": "kgCkgN-1", + "descriptions": "C and N ratio of yields" + }, + { + "codes": 3121, + "names": "softstemCN", + "units": "kgCkgN-1", + "descriptions": "C and N ratio of softstems" + }, + { + "codes": 3122, + "names": "SOM_C_5", + "units": "%", + "descriptions": "Soil organic matter C content in 90-120 cm" + }, + { + "codes": 3123, + "names": "SOM_C_6", + "units": "%", + "descriptions": "Soil organic matter C content in 120-150 cm" + }, + { + "codes": 3124, + "names": "SOM_C_7", + "units": "%", + "descriptions": "Soil organic matter C content in 150-200 cm" + }, + { + "codes": 3125, + "names": "SOM_C_8", + "units": "%", + "descriptions": "Soil organic matter C content in 200-400 cm" + }, + { + "codes": 3126, + "names": "SOM_C_9", + "units": "%", + "descriptions": "Soil organic matter C content in 400-1000 cm" + }, + { + "codes": 3127, + "names": "rootIndex", + "units": "dimless", + "descriptions": "Ratio of fine root C content and vegetation C content on harvest day" + }, + { + "codes": 3128, + "names": "belowground_ratio", + "units": "dimless", + "descriptions": "Ratio of root to vegetation C content" + }, + { + "codes": 3129, + "names": "cumCH4flux", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of total CH4 flux" + }, + { + "codes": 3130, + "names": "cumNBP", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of NBP" + }, + { + "codes": 3131, + "names": "N2OfluxCeq", + "units": "kgCm-2 day-1", + "descriptions": "Daily N2O flux in C eq" + }, + { + "codes": 3132, + "names": "cumN2OfluxCeq", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM N2O fluxn C eq" + }, + { + "codes": 3133, + "names": "cumCflux_lateral", + "units": "kgCm-2", + "descriptions": "Cumulative lateral C flux" + }, + { + "codes": 3134, + "names": "cumAR", + "units": "kgCm-2", + "descriptions": "Cumulative annual SUM of AR" + }, + { + "codes": 3137, + "names": "livingBIOMabove", + "units": "kgCm-2", + "descriptions": "Living aboveground biomass" + }, + { + "codes": 3138, + "names": "livingBIOMbelow", + "units": "kgCm-2", + "descriptions": "Living belowground biomass" + }, + { + "codes": 3139, + "names": "totalBIOMabove", + "units": "kgCm-2", + "descriptions": "Total (living and dead) aboveground biomass" + }, + { + "codes": 3140, + "names": "totalBIOMbelow", + "units": "kgCm-2", + "descriptions": "Total (living and dead) belowground biomass" + }, + { + "codes": 3141, + "names": "annmax_livingBIOMabove", + "units": "kgCm-2", + "descriptions": "Annual maximum of living aboveground biomass" + }, + { + "codes": 3142, + "names": "annmax_livingBIOMbelow", + "units": "kgCm-2", + "descriptions": "Annual maximum of living belowground biomass" + }, + { + "codes": 3143, + "names": "annmax_totalBIOMabove", + "units": "kgCm-2", + "descriptions": "Annual maximum of total living and dead aboveground biomass" + }, + { + "codes": 3144, + "names": "annmax_totalBIOMbelow", + "units": "kgCm-2", + "descriptions": "Annual maximum of total living and dead belowground biomass" + }, + { + "codes": 3145, + "names": "LDbelowC_nw", + "units": "kgCm-2", + "descriptions": "Living+dead belowground non-woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3146, + "names": "LDbelowC_w", + "units": "kgCm-2", + "descriptions": "Living+dead belowground woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3147, + "names": "LDbelowCnsc_nw", + "units": "kgCm-2", + "descriptions": "Living+dead belowground non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3148, + "names": "LDbelowCnsc_w", + "units": "kgCm-2", + "descriptions": "Living+dead belowground woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3149, + "names": "LbelowC_nw", + "units": "kgCm-2", + "descriptions": "Living belowground non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3150, + "names": "LbelowC_w", + "units": "kgCm-2", + "descriptions": "Living belowground woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3151, + "names": "LbelowCnsc_nw", + "units": "kgCm-2", + "descriptions": "Living belowground non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3152, + "names": "LbelowCnsc_w", + "units": "kgCm-2", + "descriptions": "Living belowground woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3153, + "names": "DbelowC_nw", + "units": "kgCm-2", + "descriptions": "Dead belowground non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3154, + "names": "DbelowC_w", + "units": "kgCm-2", + "descriptions": "Dead belowground woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3155, + "names": "DbelowCnsc_nw", + "units": "kgCm-2", + "descriptions": "Dead belowground non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3156, + "names": "DbelowCnsc_w", + "units": "kgCm-2", + "descriptions": "Dead belowground woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3157, + "names": "LDaboveC_nw", + "units": "kgCm-2", + "descriptions": "Living+dead aboveground non-woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3158, + "names": "LDaboveC_w", + "units": "kgCm-2", + "descriptions": "Living+dead aboveground woody biomass C content without non-structured carbohydrate" + }, + { + "codes": 3159, + "names": "LDaboveCnsc_nw", + "units": "kgCm-2", + "descriptions": "Living+dead aboveground non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3160, + "names": "LDaboveCnsc_w", + "units": "kgCm-2", + "descriptions": "Living+dead aboveground woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3161, + "names": "LaboveC_nw", + "units": "kgCm-2", + "descriptions": "Living aboveground non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3162, + "names": "LaboveC_w", + "units": "kgCm-2", + "descriptions": "Living aboveground woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3163, + "names": "LaboveCnsc_nw", + "units": "kgCm-2", + "descriptions": "Living aboveground non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3164, + "names": "LaboveCnsc_w", + "units": "kgCm-2", + "descriptions": "Living aboveground woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3165, + "names": "DaboveC_nw", + "units": "kgCm-2", + "descriptions": "Dead aboveground non-woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3166, + "names": "DaboveC_w", + "units": "kgCm-2", + "descriptions": "Dead aboveground woody biomass C without non-structured carbohydrate" + }, + { + "codes": 3167, + "names": "DaboveCnsc_nw", + "units": "kgCm-2", + "descriptions": "Dead aboveground non-woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3168, + "names": "DaboveCnsc_w", + "units": "kgCm-2", + "descriptions": "Dead aboveground woody biomass C with non-structured carbohydrate" + }, + { + "codes": 3169, + "names": "sminN_maxRZ", + "units": "kgNm-2", + "descriptions": "Soil mineralized N content in maximal rooting zone" + }, + { + "codes": 3170, + "names": "soilC_maxRZ", + "units": "kgCm-2", + "descriptions": "Soil C content in maximal rooting zone" + }, + { + "codes": 3171, + "names": "soilN_maxRZ", + "units": "kgNm-2", + "descriptions": "Soil N content in maximal rooting zone" + }, + { + "codes": 3172, + "names": "litrC_maxRZ", + "units": "kgCm-2", + "descriptions": "Litter C content in maximal rooting zone" + }, + { + "codes": 3173, + "names": "litrN_maxRZ", + "units": "kgNm-2", + "descriptions": "Litter N content in maximal rooting zone" + }, + { + "codes": 3174, + "names": "sminNavail_maxRZ", + "units": "kgNm-2", + "descriptions": "Available soil mineralized N content in maximal rooting zone" + }, + { + "codes": 3175, + "names": "tally1", + "units": "kgCm-2", + "descriptions": "tally of total soil C during successive met cycles (metcyle=1) for comparison" + }, + { + "codes": 3176, + "names": "tally2", + "units": "kgCm-2", + "descriptions": "tally of total soil C during successive met cycles (metcyle=2) for comparison" + }, + { + "codes": 3177, + "names": "steady1", + "units": "flag", + "descriptions": "marker for comparison of soilC change and spinup tolerance in metcyle=1" + }, + { + "codes": 3178, + "names": "steady2", + "units": "flag", + "descriptions": "marker for comparison of soilC change and spinup tolerance in metcyle=2" + }, + { + "codes": 3179, + "names": "metcycle", + "units": "dimless", + "descriptions": "counter for metcyles (0,1 or 2) " + } +] diff --git a/RBBGCMuso/inst/examples/hhs/backup/c3grass_muso7.epc b/RBBGCMuso/inst/examples/hhs/backup/c3grass_muso7.epc new file mode 100644 index 0000000..c06cff3 --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/backup/c3grass_muso7.epc @@ -0,0 +1,142 @@ +ECOPHYS FILE - C3 grass muso6 +---------------------------------------------------------------------------------------- +FLAGS +0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY) +0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS) +1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN) +---------------------------------------------------------------------------------------- +PLANT FUNCTIONING PARAMETERS +0 (yday) yearday to start new growth (when phenology flag = 0) +364 (yday) yearday to end litterfall (when phenology flag = 0) +0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0) +0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0) +0 (Celsius) base temperature +-9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +30 (Celsius) threshold temperature for ET-calculation (line 57 in INI file) using PT-method (-9999: no data - only PM-method) +1.0 (1/yr) annual leaf and fine root turnover fraction +0.00 (1/yr) annual live wood turnover fraction +0.03 (1/yr) annual fire mortality fraction +0.01 (1/vegper) whole-plant mortality fraction in vegetation period +0.2 (prop) dead stem biomass combustion proportion +0.3 (prop) coarse woody biomass combustion proportion +36.6 (kgC/kgN) C:N of leaves +45.0 (kgC/kgN) C:N of leaf litter, after retranslocation +50.0 (kgC/kgN) C:N of fine roots +36.6 *(kgC/kgN) C:N of fruit +36.6 (kgC/kgN) C:N of soft stem +0.0 *(kgC/kgN) C:N of live wood +0.0 *(kgC/kgN) C:N of dead wood +0.4 (kgC/kgDM) dry matter carbon content of leaves +0.4 (kgC/kgDM) dry matter carbon content of leaf litter +0.4 (kgC/kgDM) dry matter carbon content of fine roots +0.4 *(kgC/kgDM) dry matter carbon content of fruit +0.4 (kgC/kgDM) dry matter carbon content of soft stem +0.4 *(kgC/kgDM) dry matter carbon content of live wood +0.4 *(kgC/kgDM) dry matter carbon content of dead wood +0.68 (DIM) leaf litter labile proportion +0.23 (DIM) leaf litter cellulose proportion +0.34 (DIM) fine root labile proportion +0.44 (DIM) fine root cellulose proportion +0.68 *(DIM) fruit litter labile proportion +0.23 *(DIM) fruit litter cellulose proportion +0.68 (DIM) soft stem litter labile proportion +0.23 (DIM) soft stem litter cellulose proportion +0.00 *(DIM) dead wood cellulose proportion +0.01 (1/LAI/d) canopy water interception coefficient +0.63 (DIM) canopy light extinction coefficient +2.0 (g/MJ) potential radiation use efficiency +0.781 (DIM) radiation parameter1 (Jiang et al.2015) +-13.596 (DIM) radiation parameter2 (Jiang et al.2015) +2.0 (DIM) all-sided to projected leaf area ratio +2.0 (DIM) ratio of shaded SLA:sunlit SLA +0.14 (DIM) fraction of leaf N in Rubisco +0.03 (DIM) fraction of leaf N in PEP Carboxylase +0.004 (m/s) maximum stomatal conductance (projected area basis) +0.00006 (m/s) cuticular conductance (projected area basis) +0.04 (m/s) boundary layer conductance (projected area basis) +1.5 (m) maximum height of plant +0.8 (kgC) stem weight corresponding to maximum height +0.5 (dimless) plant height function shape parameter (slope) +4.0 (m) maximum depth of rooting zone +3.67 (DIM) root distribution parameter +0.4 (kgC) root weight corresponding to max root depth +0.5 (dimless) root depth function shape parameter (slope) +1000 (m/kg) root weight to root length conversion factor +0.3 (prop.) growth resp per unit of C grown +0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N +0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates +0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration +0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N +0 (day) time delay for temperature in photosynthesis acclimation +---------------------------------------------------------------------------------------- +CROP SPECIFIC PARAMETERS +0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific) +0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific) +0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination +0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect) +20 (hour) critical photoslow daylength +0.005 (DIM) slope of relative photoslow development rate +0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect) +0 (Celsius) critical vernalization temperature 1 +5 (Celsius) critical vernalization temperature 2 +8 (Celsius) critical vernalization temperature 3 +15 (Celsius) critical vernalization temperature 4 +0.04 (DIM) slope of relative vernalization development rate +50 (n) required vernalization days (in vernalization development rate) +0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect) +35 (Celsius) critical flowering heat stress temperature 1 +40 (Celsius) critical flowering heat stress temperature 2 +0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter +---------------------------------------------------------------------------------------- +STRESS AND SENESCENCE PARAMETERS +0.5 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP) +0.99 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC) +0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value) +1000 (Pa) vapor pressure deficit: start of conductance reduction +4000 (Pa) vapor pressure deficit: complete conductance reduction +0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material +0.001 (prop.) maximum senescence mortality coefficient of belowground plant material +0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material +35 (Celsius) lower limit extreme high temperature effect on senescence mortality +40 (Celsius) upper limit extreme high temperature effect on senescence mortality +0.01 (prop.) turnover rate of wilted standing biomass to litter +0.047 (prop.) turnover rate of non-woody cut-down biomass to litter +0.01 (prop.) turnover rate of woody cut-down biomass to litter +17 (nday) drought tolerance parameter (critical value of DSWS) +0.3 (prop) soil water deficit effect on photosynthesis downregulation +---------------------------------------------------------------------------------------- +GROWING SEASON PARAMETERS +5 (kg/m2) crit. amount of snow limiting photosyn. +20 (Celsius) limit1 (under:full constrained) of HEATSUM index +60 (Celsius) limit2 (above:unconstrained) of HEATSUM index +0 (Celsius) limit1 (under:full constrained) of TMIN index +5 (Celsius) limit2 (above:unconstrained) of TMIN index +4000 (Pa) limit1 (above:full constrained) of VPD index +1000 (Pa) limit2 (under:unconstrained) of VPD index +0 (s) limit1 (under:full constrained) of DAYLENGTH index +0 (s) limit2 (above:unconstrained) of DAYLENGTH index +10 (day) moving average (to avoid the effects of extreme events) +0.10 (dimless) GSI limit1 (greater that limit -> start of vegper) +0.01 (dimless) GSI limit2 (less that limit -> end of vegper) +---------------------------------------------------------------------------------------- +PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases) +phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase +5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD) +0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION +0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION +0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION +0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION +0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION +49 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis) +0.37 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion +10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue diff --git a/RBBGCMuso/inst/examples/hhs/backup/parameters.csv b/RBBGCMuso/inst/examples/hhs/backup/parameters.csv new file mode 100644 index 0000000..012e424 --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/backup/parameters.csv @@ -0,0 +1,17 @@ +ABREVIATION,INDEX,min,max +TRANSFERGROWTHP,11,0.1,1 +T_BASE,13,0,8 +CN_leaf,29,14.3,58.8 +CWIC,52,0.01,0.07 +CLEC,53,0.3,0.8 +FLNR,59,0.1,0.4 +MSTOMACOND,61,0.001,0.007 +BOUNDARYLAYERCOND,63,0.001,0.05 +ROOTDEPTH,67,0.5,3 +ROOTDISTRIB,68,0.2,5 +NFIXATION,76,0.002,0.03 +RELSWCCRIT1,99,0.4,1 +SENESCENCABG,104,0,0.1 +TURNOVEROFDEADBIOMASS,109,0.01,0.4 +SLA1,140.60,20,50 +CURRENTGROWTHPROP1,141.60,0.2,1.0 diff --git a/RBBGCMuso/inst/examples/hhs/backup/parameters2.csv b/RBBGCMuso/inst/examples/hhs/backup/parameters2.csv new file mode 100644 index 0000000..4029c42 --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/backup/parameters2.csv @@ -0,0 +1,22 @@ +ABREVIATION,INDEX,min,max +TRANSFERGROWTHP,11,0.1,1 +T_BASE,13,0,8 +WPM,26,0,0.1 +CN_leaf,29,14.3,58.8 +CWIC,52,0.01,0.07 +CLEC,53,0.3,0.8 +FLNR,59,0.1,0.2 +MSTOMACOND,61,0.001,0.007 +ROOTDEPTH,67,0.5,3 +ROOTDISTRIB,68,0.2,5 +RELSWCCRIT1,99,0.97,1 +RELSWCCRIT2,100,0.4,1 +SENESCENCABG,104,0,0.1 +AllocP_l, 132.60,0,1 +AllocP_fr,133.60,0,1 +AllocP_fr,134.60,0,0 +AllocP_ss,135.60,0,1 +AllocP_ls,136.60,0,0 +AllocP_ds,137.60,0,0 +AllocP_lr,138.60,0,0 +AllocP_dr,139.60,0,0 diff --git a/RBBGCMuso/inst/examples/hhs/c3grass_muso7.epc b/RBBGCMuso/inst/examples/hhs/c3grass_muso7.epc new file mode 100644 index 0000000..479c11a --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/c3grass_muso7.epc @@ -0,0 +1,142 @@ +ECOPHYS FILE - C3 grass muso6 +---------------------------------------------------------------------------------------- +FLAGS +0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY) +0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS) +1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN) +---------------------------------------------------------------------------------------- +PLANT FUNCTIONING PARAMETERS +0 (yday) yearday to start new growth (when phenology flag = 0) +364 (yday) yearday to end litterfall (when phenology flag = 0) +0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0) +0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0) +0 (Celsius) base temperature +-9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation) +-9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation) +-9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation) +30 (Celsius) threshold temperature for ET-calculation (line 57 in INI file) using PT-method (-9999: no data - only PM-method) +1.0 (1/yr) annual leaf and fine root turnover fraction +0.00 (1/yr) annual live wood turnover fraction +0.00 (1/yr) annual fire mortality fraction +0.01 (1/vegper) whole-plant mortality fraction in vegetation period +0.2 (prop) dead stem biomass combustion proportion +0.3 (prop) coarse woody biomass combustion proportion +12. (kgC/kgN) C:N of leaves +45.0 (kgC/kgN) C:N of leaf litter, after retranslocation +50.0 (kgC/kgN) C:N of fine roots +36.6 *(kgC/kgN) C:N of fruit +36.6 (kgC/kgN) C:N of soft stem +0.0 *(kgC/kgN) C:N of live wood +0.0 *(kgC/kgN) C:N of dead wood +0.4 (kgC/kgDM) dry matter carbon content of leaves +0.4 (kgC/kgDM) dry matter carbon content of leaf litter +0.4 (kgC/kgDM) dry matter carbon content of fine roots +0.4 *(kgC/kgDM) dry matter carbon content of fruit +0.4 (kgC/kgDM) dry matter carbon content of soft stem +0.4 *(kgC/kgDM) dry matter carbon content of live wood +0.4 *(kgC/kgDM) dry matter carbon content of dead wood +0.68 (DIM) leaf litter labile proportion +0.23 (DIM) leaf litter cellulose proportion +0.34 (DIM) fine root labile proportion +0.44 (DIM) fine root cellulose proportion +0.68 *(DIM) fruit litter labile proportion +0.23 *(DIM) fruit litter cellulose proportion +0.68 (DIM) soft stem litter labile proportion +0.23 (DIM) soft stem litter cellulose proportion +0.00 *(DIM) dead wood cellulose proportion +0.01 (1/LAI/d) canopy water interception coefficient +0.7 (DIM) canopy light extinction coefficient +2.0 (g/MJ) potential radiation use efficiency +0.781 (DIM) radiation parameter1 (Jiang et al.2015) +-13.596 (DIM) radiation parameter2 (Jiang et al.2015) +2.0 (DIM) all-sided to projected leaf area ratio +2.0 (DIM) ratio of shaded SLA:sunlit SLA +0.3 (DIM) fraction of leaf N in Rubisco +0.03 (DIM) fraction of leaf N in PEP Carboxylase +0.002 (m/s) maximum stomatal conductance (projected area basis) +0.00006 (m/s) cuticular conductance (projected area basis) +0.04 (m/s) boundary layer conductance (projected area basis) +1.5 (m) maximum height of plant +0.8 (kgC) stem weight corresponding to maximum height +0.5 (dimless) plant height function shape parameter (slope) +2.5 (m) maximum depth of rooting zone +1 (DIM) root distribution parameter +0.4 (kgC) root weight corresponding to max root depth +0.5 (dimless) root depth function shape parameter (slope) +1000 (m/kg) root weight to root length conversion factor +0.3 (prop.) growth resp per unit of C grown +0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N +0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates +0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration +0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N +0 (day) time delay for temperature in photosynthesis acclimation +---------------------------------------------------------------------------------------- +CROP SPECIFIC PARAMETERS +0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific) +0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific) +0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination +0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect) +20 (hour) critical photoslow daylength +0.005 (DIM) slope of relative photoslow development rate +0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect) +0 (Celsius) critical vernalization temperature 1 +5 (Celsius) critical vernalization temperature 2 +8 (Celsius) critical vernalization temperature 3 +15 (Celsius) critical vernalization temperature 4 +0.04 (DIM) slope of relative vernalization development rate +50 (n) required vernalization days (in vernalization development rate) +0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect) +35 (Celsius) critical flowering heat stress temperature 1 +40 (Celsius) critical flowering heat stress temperature 2 +0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter +---------------------------------------------------------------------------------------- +STRESS AND SENESCENCE PARAMETERS +0.4 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP) +0.99 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC) +0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value) +1000 (Pa) vapor pressure deficit: start of conductance reduction +4000 (Pa) vapor pressure deficit: complete conductance reduction +0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material +0.001 (prop.) maximum senescence mortality coefficient of belowground plant material +0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material +35 (Celsius) lower limit extreme high temperature effect on senescence mortality +40 (Celsius) upper limit extreme high temperature effect on senescence mortality +0.01 (prop.) turnover rate of wilted standing biomass to litter +0.047 (prop.) turnover rate of non-woody cut-down biomass to litter +0.01 (prop.) turnover rate of woody cut-down biomass to litter +17 (nday) drought tolerance parameter (critical value of DSWS) +0. (prop) soil water deficit effect on photosynthesis downregulation +---------------------------------------------------------------------------------------- +GROWING SEASON PARAMETERS +5 (kg/m2) crit. amount of snow limiting photosyn. +20 (Celsius) limit1 (under:full constrained) of HEATSUM index +60 (Celsius) limit2 (above:unconstrained) of HEATSUM index +0 (Celsius) limit1 (under:full constrained) of TMIN index +5 (Celsius) limit2 (above:unconstrained) of TMIN index +4000 (Pa) limit1 (above:full constrained) of VPD index +1000 (Pa) limit2 (under:unconstrained) of VPD index +0 (s) limit1 (under:full constrained) of DAYLENGTH index +0 (s) limit2 (above:unconstrained) of DAYLENGTH index +10 (day) moving average (to avoid the effects of extreme events) +0.10 (dimless) GSI limit1 (greater that limit -> start of vegper) +0.01 (dimless) GSI limit2 (less that limit -> end of vegper) +---------------------------------------------------------------------------------------- +PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases) +phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase +5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD) +0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION +0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION +0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION +0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION +0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION +0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION +30 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis) +0.5 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion +10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue diff --git a/RBBGCMuso/inst/examples/hhs/hhs_muso7.mgm b/RBBGCMuso/inst/examples/hhs/hhs_muso7.mgm new file mode 100644 index 0000000..1a90157 --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/hhs_muso7.mgm @@ -0,0 +1,41 @@ +MANAGEMENT_INFORMATION MuSo7 +------------------------------------------------------------------------------------------------------------------- +PLANTING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +THINNING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +MOWING +1 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +hhs.mow +------------------------------------------------------------------------------------------------------------------- +GRAZING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +HARVESTING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +PLOUGHING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +FERTILIZING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +IRRIGATING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +MULCHING +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none +------------------------------------------------------------------------------------------------------------------- +CWD-EXTRACT +0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below +none diff --git a/RBBGCMuso/inst/examples/hhs/hhs_muso7.soi b/RBBGCMuso/inst/examples/hhs/hhs_muso7.soi new file mode 100644 index 0000000..3ed4e64 --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/hhs_muso7.soi @@ -0,0 +1,101 @@ +SOILPROP FILE - MuSo6 +-------------------------------------------------------------------------------- +SOIL GENERIC PARAMETERS + 3.000000 (m) depth of soil + 10.000000 (ppm) C:N ratio of labile soil pool (soil1) + 15.000000 (ppm) C:N ratio of medium soil pool (soil2) + 20.000000 (ppm) C:N ratio of slow soil pool (soil3) + 12.000000 (ppm) C:N ratio of passive soil pool (soil4) + 10.000000 (kgC/m2) total SOC content (critical value for spinup run) + 0.100000 (prop) NH4 mobilen proportion + 107.000000 (s/m) aerodynamic resistance (Wallace and Holwill, 1997) +-------------------------------------------------------------------------------- +DECOMPOSITION, NITRIFICATION AND DENITRIFICATION PARAMETERS + 0.100000 (prop) VWC ratio to calc. decomposition limit 1 (prop. to FC-HW) + 1.000000 (prop) VWC ratio to calc. decomposition limit 2 (prop. to SAT-FC) + 1.000000 (dimless) curvature of decomposition limitation function + -9999.000000 (dimless) parameter 1 for tscalar function of decomposition + 308.559998 (dimless) parameter 2 for tscalar function of decomposition + 71.019997 (dimless) parameter 3 for tscalar function of decomposition + 227.130005 (dimless) parameter 4 for tscalar function of decomposition + -5.000000 (Celsius) minimum soil temperature for decomposition + 10.000000 (m) e-folding depth of decomposition rate depth scalar + 0.200000 (prop) net mineralization proportion of nitrification + 0.100000 (1/day) maximum nitrification rate + 0.020000 (prop) coefficient of N2O emission of nitrification + 0.150000 (dimless) parameter 1 for pHscalar function of nitrification + 1.000000 (dimless) parameter 2 for pHscalar function of nitrification + 5.200000 (dimless) parameter 3 for pHscalar function of nitrification + 0.550000 (dimless) parameter 4 for pHscalar function of nitrification + -9999.000000 (dimless) parameter 1 for tscalar function of nitrification + 308.559998 (dimless) parameter 2 for tscalar function of nitrification + 71.019997 (dimless) parameter 3 for tscalar function of nitrification + 227.130005 (dimless) parameter 4 for tscalar function of nitrification + 0.100000 (prop) minimum WFPS for scalar of nitrification calculation + 0.450000 (prop) lower optimum WFPS for scalar of nitrification calculation + 0.550000 (prop) higher optimum WFPS for scalar of nitrification calculation + 0.200000 (prop) minimum value for saturated WFPS scalar of nitrification calculation + 0.050000 (1/gCO2) soil respiration related denitrification rate + 2.000000 (dimless) denitrification related N2/N2O ratio multiplier + 0.550000 (prop) critical WFPS value for denitrification +-------------------------------------------------------------------------------- +RATE SCALARS + 0.390000 (dimless) respiration fractions for fluxes between compartments (11s1) + 0.550000 (dimless) respiration fractions for fluxes between compartments (l2s2) + 0.290000 (dimless) respiration fractions for fluxes between compartments (l4s3) + 0.280000 (dimless) respiration fractions for fluxes between compartments (s1s2) + 0.460000 (dimless) respiration fractions for fluxes between compartments (s2s3) + 0.550000 (dimless) respiration fractions for fluxes between compartments (s3s4) + 0.700000 (1/day) rate constant scalar of labile litter pool + 0.070000 (1/day) rate constant scalar of cellulose litter pool + 0.014000 (1/day) rate constant scalar of lignin litter pool + 0.070000 (1/day) rate constant scalar of fast microbial recycling pool + 0.014000 (1/day) rate constant scalar of medium microbial recycling pool + 0.001400 (1/day) rate constant scalar of slow microbial recycling pool + 0.000100 (1/day) rate constant scalar of recalcitrant SOM pool + 0.001000 (1/day) rate constant scalar of physical fragmentation of coarse woody debris + 0.000000 (1/day) fraction of direct decomposition of labile litter pool + 0.000000 (1/day) fraction of direct decomposition of cellulose litter pool + 0.000000 (1/day) fraction of direct decomposition of lignin litter pool +-------------------------------------------------------------------------------- +SOIL MOISTURE PARAMETERS + 6.000000 (mm) limit of first stage evaporation + 5.000000 (mm) maximum height of pond water + 1.000000 (dimless) curvature of soil stress function + -9999.000000 (dimless) measured runoff curve number (0: no runoff, -9999: model estimation) + 0.002000 (prop) fraction of dissolved part of SOIL1 organic matter + 0.002000 (prop) fraction of dissolved part of SOIL2 organic matter + 0.001000 (prop) fraction of dissolved part of SOIL3 organic matter + 0.001000 (prop) fraction of dissolved part of SOIL4 organic matter + 2.000000 (dimless) mulch parameter: number of layer affected by mulch + 0.000000 (kgC/m2) mulch parameter: critical amount + 100.000000 (dimless) parameter 1 for mulch function + 0.750000 (dimless) parameter 2 for mulch function + 0.750000 (dimless) parameter 3 for mulch function + 0.500000 (prop) mulch parameter: evaporation reduction + 0.880000 (dimless) parameter 1 for diffusion calculation - tipping + 35.400002 (dimless) parameter 2 for diffusion calculation - tipping + 5.000000 (cm/day) limit of assumed diffusivity in tipping calculation +-------------------------------------------------------------------------------- +CH4 PARAMETERS + 212.500000 (dimless) soil CH4 emission bulk density dependence parameter1 + 1.810000 (dimless) soil CH4 emission bulk density dependence parameter2 + -1.353000 (dimless) soil CH4 emission soil water content dependence parameter1 + 0.200000 dimless) soil CH4 emission soil water content dependence parameter2 + 1.781000 (dimless) soil CH4 emission soil water content dependence parameter3 + 6.786000 (dimless) soil CH4 emission soil water content dependence parameter4 + 0.010000 (dimless) soil CH4 emission soil temperature dependence parameter1 +-------------------------------------------------------------------------------- +SOIL COMPOSITION AND CHARACTERISTIC VALUES (-9999: no measured data) + 28.000000 28.000000 28.000000 30.000000 30.000000 41.000000 41.000000 41.000000 41.000000 41.000000 (%) sand percentage by volume in rock-free soil + 49.000000 49.000000 49.000000 41.000000 46.000000 36.000000 36.000000 36.000000 36.000000 36.000000 (%) silt percentage by volume in rock-free soil + 8.200000 8.200000 8.200000 8.500000 8.700000 8.700000 8.700000 8.700000 8.700000 8.700000 (dimless) soil pH + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (dimless) Clapp-Hornberger soilB parameter + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (g/cm3) bulk density + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (m3/m3) SWC at saturation + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (m3/m3) SWC at field capacity + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (m3/m3) SWC at wilting point + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (m3/m3) SWC at hygroscopic water content + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (dimless) drainage coefficient + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (cm/day) hydraulic condictivity at saturation + -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 -9999.000000 (cm) capillary fringe diff --git a/RBBGCMuso/inst/examples/hhs/muso b/RBBGCMuso/inst/examples/hhs/muso old mode 100755 new mode 100644 index 276db81..92f0096 Binary files a/RBBGCMuso/inst/examples/hhs/muso and b/RBBGCMuso/inst/examples/hhs/muso differ diff --git a/RBBGCMuso/inst/examples/hhs/muso.exe b/RBBGCMuso/inst/examples/hhs/muso.exe index 1930717..fb387cf 100644 Binary files a/RBBGCMuso/inst/examples/hhs/muso.exe and b/RBBGCMuso/inst/examples/hhs/muso.exe differ diff --git a/RBBGCMuso/inst/examples/hhs/muso6.1.exe b/RBBGCMuso/inst/examples/hhs/muso6.1.exe deleted file mode 100644 index 1930717..0000000 Binary files a/RBBGCMuso/inst/examples/hhs/muso6.1.exe and /dev/null differ diff --git a/RBBGCMuso/inst/examples/hhs/muso7.0b9.exe b/RBBGCMuso/inst/examples/hhs/muso7.0b9.exe new file mode 100644 index 0000000..fb387cf Binary files /dev/null and b/RBBGCMuso/inst/examples/hhs/muso7.0b9.exe differ diff --git a/RBBGCMuso/inst/examples/hhs/n.ini b/RBBGCMuso/inst/examples/hhs/n.ini index 0c4629b..9654624 100644 --- a/RBBGCMuso/inst/examples/hhs/n.ini +++ b/RBBGCMuso/inst/examples/hhs/n.ini @@ -8,8 +8,8 @@ hhs.mtc43 RESTART 1 (flag) 1 = read restart; 0 = dont read restart 0 (flag) 1 = write restart; 0 = dont write restart -hhs_MuSo6.endpoint (filename) name of the input restart file -hhs_MuSo6.endpoint (filename) name of the output restart file +hhs_MuSo7.endpoint (filename) name of the input restart file +hhs_MuSo7.endpoint (filename) name of the output restart file TIME_DEFINE 9 (int) number of simulation years @@ -24,25 +24,23 @@ CO2.txt NDEP_CONTROL 1 (flag) 0=constant; 1=vary with file -0.001400 (kgN/m2/yr) wet+dry atmospheric deposition of N +0.000200 (kgN/m2/yr) wet+dry atmospheric deposition of N +0.50 (prop.) proprortion of NH4 flux of N-deposition Ndep.txt (filename) name of the N-dep file SITE 248.0 (m) site elevation 46.95 (degrees) site latitude (- for S.Hem.) 0.20 (DIM) site shortwave albedo -9.00 (Celsius) mean annual air temperature -10.15 (Celsius) mean annual air temperature range -0.50 (prop.) proprortion of NH4 flux of N-deposition SOIL_FILE -hhs.soi (filename) SOIL filename +hhs_muso7.soi (filename) SOIL filename EPC_FILE -c3grass_muso6.epc (filename) EPC filename +c3grass_muso7.epc (filename) EPC filename MANAGEMENT_FILE -hhs.mgm (filename) MGM filename (or "none") +hhs_muso7.mgm (filename) MGM filename (or "none") SIMULATION_CONTROL 1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY) @@ -59,6 +57,7 @@ SIMULATION_CONTROL 0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor) 0 (flag) radiation calculation method (0: SWabs, 1: Rn) 0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand) +1 (flag) interception calculation method (0: based on allLAI, 1: based on allLAI) W_STATE 0.0 (kg/m2) water stored in snowpack @@ -103,7 +102,7 @@ CONDITIONAL_MANAGEMENT_STRATEGIES 0.0 (kgH2O/m2) maximum amount of irrigated water OUTPUT_CONTROL -hhs_MuSo6 (filename) output prefix +hhs_MuSo7 (filename) output prefix 1 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) 0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) 0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) diff --git a/RBBGCMuso/inst/examples/hhs/parameters.csv b/RBBGCMuso/inst/examples/hhs/parameters.csv index fd2dee0..012e424 100644 --- a/RBBGCMuso/inst/examples/hhs/parameters.csv +++ b/RBBGCMuso/inst/examples/hhs/parameters.csv @@ -1,15 +1,17 @@ -ABREVIATION,INDEX,min,max MuSo6 +ABREVIATION,INDEX,min,max TRANSFERGROWTHP,11,0.1,1 T_BASE,13,0,8 -WPM,25,0,0.1 -CN_leaf,26,14.3,58.8 -CWIC,49,0.01,0.07 -CLEC,50,0.3,0.8 -FLNR,56,0.1,0.2 -MSTOMACOND,58,0.001,0.007 -ROOTDEPTH,64,0.5,3 -ROOTDISTRIB,65,0.2,5 -RELSWCCRIT1,96,0.97,1 -RELSWCCRIT2,97,0.4,1 -SENESCENCABG,101,0,0.1 -SLA,137.60,10,60 +CN_leaf,29,14.3,58.8 +CWIC,52,0.01,0.07 +CLEC,53,0.3,0.8 +FLNR,59,0.1,0.4 +MSTOMACOND,61,0.001,0.007 +BOUNDARYLAYERCOND,63,0.001,0.05 +ROOTDEPTH,67,0.5,3 +ROOTDISTRIB,68,0.2,5 +NFIXATION,76,0.002,0.03 +RELSWCCRIT1,99,0.4,1 +SENESCENCABG,104,0,0.1 +TURNOVEROFDEADBIOMASS,109,0.01,0.4 +SLA1,140.60,20,50 +CURRENTGROWTHPROP1,141.60,0.2,1.0 diff --git a/RBBGCMuso/inst/examples/hhs/parameters2.csv b/RBBGCMuso/inst/examples/hhs/parameters2.csv new file mode 100644 index 0000000..4029c42 --- /dev/null +++ b/RBBGCMuso/inst/examples/hhs/parameters2.csv @@ -0,0 +1,22 @@ +ABREVIATION,INDEX,min,max +TRANSFERGROWTHP,11,0.1,1 +T_BASE,13,0,8 +WPM,26,0,0.1 +CN_leaf,29,14.3,58.8 +CWIC,52,0.01,0.07 +CLEC,53,0.3,0.8 +FLNR,59,0.1,0.2 +MSTOMACOND,61,0.001,0.007 +ROOTDEPTH,67,0.5,3 +ROOTDISTRIB,68,0.2,5 +RELSWCCRIT1,99,0.97,1 +RELSWCCRIT2,100,0.4,1 +SENESCENCABG,104,0,0.1 +AllocP_l, 132.60,0,1 +AllocP_fr,133.60,0,1 +AllocP_fr,134.60,0,0 +AllocP_ss,135.60,0,1 +AllocP_ls,136.60,0,0 +AllocP_ds,137.60,0,0 +AllocP_lr,138.60,0,0 +AllocP_dr,139.60,0,0 diff --git a/RBBGCMuso/inst/examples/hhs/s.ini b/RBBGCMuso/inst/examples/hhs/s.ini index 996ef2b..8124399 100644 --- a/RBBGCMuso/inst/examples/hhs/s.ini +++ b/RBBGCMuso/inst/examples/hhs/s.ini @@ -8,8 +8,8 @@ hhs.mtc43 RESTART 0 (flag) 1 = read restart; 0 = dont read restart 1 (flag) 1 = write restart; 0 = dont write restart -hhs_MuSo6.endpoint (filename) name of the input restart file -hhs_MuSo6.endpoint (filename) name of the output restart file +hhs_MuSo7.endpoint (filename) name of the input restart file +hhs_MuSo7.endpoint (filename) name of the output restart file TIME_DEFINE 54 (int) number of simulation years @@ -25,21 +25,19 @@ CO2.txt NDEP_CONTROL 1 (flag) 0=constant; 1=vary with file 0.000200 (kgN/m2/yr) wet+dry atmospheric deposition of N +0.50 (prop.) proprortion of NH4 flux of N-deposition Ndep.txt (filename) name of the N-dep file SITE 248.0 (m) site elevation 46.95 (degrees) site latitude (- for S.Hem.) 0.20 (DIM) site shortwave albedo -9.00 (Celsius) mean annual air temperature -10.15 (Celsius) mean annual air temperature range -0.50 (prop.) proprortion of NH4 flux of N-deposition SOIL_FILE -hhs.soi (filename) SOIL filename +hhs_muso7.soi (filename) SOIL filename EPC_FILE -c3grass_muso6.epc (filename) EPC filename +c3grass_muso7.epc (filename) EPC filename MANAGEMENT_FILE none (filename) MGM filename (or "none") @@ -59,6 +57,7 @@ SIMULATION_CONTROL 0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor) 0 (flag) radiation calculation method (0: SWabs, 1: Rn) 0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand) +1 (flag) interception calculation method (0: based on allLAI, 1: based on allLAI) W_STATE 0.0 (kg/m2) water stored in snowpack @@ -103,7 +102,7 @@ CONDITIONAL_MANAGEMENT_STRATEGIES 0.0 (kgH2O/m2) maximum amount of irrigated water OUTPUT_CONTROL -hhs_MuSo6_Spinup (filename) output prefix +hhs_MuSo7_Spinup (filename) output prefix 0 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) 0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) 0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen) diff --git a/RBBGCMuso/man/compareCalibratedWithOriginal.Rd b/RBBGCMuso/man/compareCalibratedWithOriginal.Rd index 1b46fc9..da3fb8f 100644 --- a/RBBGCMuso/man/compareCalibratedWithOriginal.Rd +++ b/RBBGCMuso/man/compareCalibratedWithOriginal.Rd @@ -16,6 +16,9 @@ compareCalibratedWithOriginal( groupFun ) } +\arguments{ +\item{key}{keyword} +} \description{ This functions compareses the likelihood and the RMSE values of the simulations and the measurements } diff --git a/RBBGCMuso/man/createSoilFile.Rd b/RBBGCMuso/man/createSoilFile.Rd index 5eb6bac..21fb73e 100644 --- a/RBBGCMuso/man/createSoilFile.Rd +++ b/RBBGCMuso/man/createSoilFile.Rd @@ -3,6 +3,16 @@ \name{createSoilFile} \alias{createSoilFile} \title{createSoilFile} +\usage{ +createSoilFile( + lat, + lon, + outputFile = "recent.soi", + method = "constant", + apiURL, + template = system.file("examples/hhs/hhs_MuSo7.soi", package = "RBBGCMuso") +) +} \description{ This function collects soil data from a given restapi, de default is soilGrid } diff --git a/RBBGCMuso/man/fixAlloc.Rd b/RBBGCMuso/man/fixAlloc.Rd new file mode 100644 index 0000000..0d51882 --- /dev/null +++ b/RBBGCMuso/man/fixAlloc.Rd @@ -0,0 +1,16 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/otherUsefullFunctions.R +\name{fixAlloc} +\alias{fixAlloc} +\title{fixAlloc} +\usage{ +... +} +\arguments{ +\item{settings}{the base RMuso settings variable} + +\item{type}{normal or spinup depending what you want to modify} +} +\description{ +Fix allocation parameter in the epc file +} diff --git a/RBBGCMuso/man/getSoilDataFull.Rd b/RBBGCMuso/man/getSoilDataFull.Rd index 4442e72..af8f395 100644 --- a/RBBGCMuso/man/getSoilDataFull.Rd +++ b/RBBGCMuso/man/getSoilDataFull.Rd @@ -3,6 +3,9 @@ \name{getSoilDataFull} \alias{getSoilDataFull} \title{getSoilDataFull} +\usage{ +getSoilDataFull(lat, lon, apiURL) +} \description{ This function collects soil data from a given restapi, de default is soilGrid } diff --git a/RBBGCMuso/man/musoDate.Rd b/RBBGCMuso/man/musoDate.Rd index d2d47f6..95a7029 100644 --- a/RBBGCMuso/man/musoDate.Rd +++ b/RBBGCMuso/man/musoDate.Rd @@ -13,6 +13,19 @@ musoDate( prettyOut = FALSE ) } +\arguments{ +\item{startYear}{Start year of the simulations} + +\item{numYears}{Number of the years of the simulation} + +\item{combined}{using separate y m d columns or not?} + +\item{timestep}{timestep of date creation} + +\item{corrigated}{If leapyear ...} + +\item{format}{"the date format"} +} \description{ This function generates MuSo compatibla dates for the data } diff --git a/RBBGCMuso/man/musoQuickEffect.Rd b/RBBGCMuso/man/musoQuickEffect.Rd index 57879e4..8fb6fde 100644 --- a/RBBGCMuso/man/musoQuickEffect.Rd +++ b/RBBGCMuso/man/musoQuickEffect.Rd @@ -15,7 +15,8 @@ musoQuickEffect( outVar, parName = "parVal", yearNum = 1, - year = (settings$startYear + yearNum - 1) + year = (settings$startYear + yearNum - 1), + fixAlloc = FALSE ) } \arguments{ diff --git a/RBBGCMuso/man/paramSweep.Rd b/RBBGCMuso/man/paramSweep.Rd index 8933dce..b2945e5 100644 --- a/RBBGCMuso/man/paramSweep.Rd +++ b/RBBGCMuso/man/paramSweep.Rd @@ -10,7 +10,8 @@ paramSweep( outputDir = NULL, iterations = 10, outVar = "daily_gpp", - htmlOutName = "paramsweep.html" + htmlOutName = "paramsweep.html", + fixAlloc = FALSE ) } \arguments{ diff --git a/RBBGCMuso/man/readValuesFromFile.Rd b/RBBGCMuso/man/readValuesFromFile.Rd new file mode 100644 index 0000000..078087e --- /dev/null +++ b/RBBGCMuso/man/readValuesFromFile.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assistantFunctions.R +\name{readValuesFromFile} +\alias{readValuesFromFile} +\title{readValuesFromFile} +\usage{ +readValuesFromFile(filename, linums) +} +\arguments{ +\item{filename}{The name of the} +} +\description{ +read Muso values from file +} diff --git a/RBBGCMuso/man/setupMuso.Rd b/RBBGCMuso/man/setupMuso.Rd index e2d9502..4b1b3d5 100644 --- a/RBBGCMuso/man/setupMuso.Rd +++ b/RBBGCMuso/man/setupMuso.Rd @@ -42,7 +42,7 @@ nitInput=NULL, iniInput=NULL, epcInput=NULL) \item{plougInput}{Via the plougInput parameter, the user can specify the location of the file that contains the ploughing information. By default the package reads this information from the INI files.} -\item{fertInput}{Via the fertInput parameter, ythe user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files.} +\item{fertInput}{Via the fertInput parameter, the user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files.} \item{irrInput}{Via the irrInput parameter, the user can specify the location of the file that contains the irrigation information. By default the package reads this information from the INI files.} diff --git a/RBBGCMuso/man/tuneMusoUI.Rd b/RBBGCMuso/man/tuneMusoUI.Rd index 25801a9..90a79e5 100644 --- a/RBBGCMuso/man/tuneMusoUI.Rd +++ b/RBBGCMuso/man/tuneMusoUI.Rd @@ -10,5 +10,5 @@ \item{parameterFile}{optional, the parameter csv file} } \description{ -This is a simple parameter tuner function which works great in a flat directory systemj +This is a simple parameter tuner function which works great in a flat directory system } diff --git a/RBBGCMuso/man/updateMusoMapping.Rd b/RBBGCMuso/man/updateMusoMapping.Rd index ecdffc0..b1e4665 100644 --- a/RBBGCMuso/man/updateMusoMapping.Rd +++ b/RBBGCMuso/man/updateMusoMapping.Rd @@ -7,13 +7,13 @@ updateMusoMapping(excelName, dest = "./", version = getOption("RMuso_version")) } \arguments{ -\item{excelName}{Name of the excelfile which contains the parameters} +\item{excelName}{Name of the Excel file which contains the parameters} } \value{ The output code-variable matrix, and also the function changes the global variable } \description{ -This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variablesare marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order! +This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variables are marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order! } \author{ Roland HOLLOS diff --git a/RBBGCMuso_0.7.1.tar.gz b/RBBGCMuso_0.7.1.tar.gz new file mode 100644 index 0000000..5f163f6 Binary files /dev/null and b/RBBGCMuso_0.7.1.tar.gz differ diff --git a/README.org b/README.org index db13b22..ea96e7e 100644 --- a/README.org +++ b/README.org @@ -11,7 +11,7 @@ RBBGCMuso: an R package to support the application of the [[http://nimbus.elte.h *Current version: 0.7.0* -RBBGCMuso is an R package which supports the easy but powerful application of the [[http://nimbus.elte.hu/bbgc/][Biome-BGCMuSo]] biogeochemical model in R environment. It also provides some additional tools for the model such as Biome-BGCMuSo optimized Monte-Carlo simulation and global sensitivity analysis. If you would like to use the framework, please read the following description. Note that we recommend to use [[http://nimbus.elte.hu/bbgc/download.html][Biome-BGCMuSo v6.1]] with RBBGCMuSo. +RBBGCMuso is an R package which supports the easy but powerful application of the [[http://nimbus.elte.hu/bbgc/][Biome-BGCMuSo]] biogeochemical model in R environment. It also provides some additional tools for the model such as Biome-BGCMuSo optimized Monte-Carlo simulation and global sensitivity analysis. If you would like to use the framework, please read the following description. ** Installation You can install the RBBGCMuso package in several ways depending on the operating system you use. Up to now RBBGCMuso was tested only in Linux and MS Windows environment, so Mac OS X compatibility cannot be guaranteed yet. In MS Windows you can install the package from binary or from source installer. In Linux you can only install the software from source. @@ -67,18 +67,19 @@ Once this command is executed in R, it will invoke a small Graphical User Interf Once the copyMusoExampleTo command is finished, the model input dataset and the model executable (called muso.exe and cygwin1.dll) are available in the C:\model folder. The user might check the content of the files using his/her favourite text editor (we propose Editpad Lite as it can handle both Windows and Linux text files). Note that file extension might be hidden by Windows which could cause problems, so we propose to adjust Windows so that file extensions are visible. Visit [[https://www.thewindowsclub.com/show-file-extensions-in-windows][this website]] to learn how to show file extensions in Windows. In this example the C:\model directory will contain the following files: -- muso.exe - this is the Biome-BGCMuSo 6.1 model executable for Windows (version might change in the future) +- muso.exe - this is the Biome-BGCMuSo model executable for Windows (version might change in the future) - cygwin1.dll - a so-called DLL file that supports the model execution under Windows -- c3grass_muso6.epc - ecophysiological constants input file for the model (C3 grass in this case) +- c3grass_muso7.epc - ecophysiological constants input file for the model (C3 grass in this case) - n.ini - initialization file for the model, normal mode (INI file controls the entire simulation) - s.ini - initialization file for the model spinup (also known as self-initialization or equilibrium run) -- hhs.soi - soil file for the Hegyhátsál simulation +- hhs_muso7.soi - soil file for the Hegyhátsál simulation - hhs.mtc43 - meteorology input file -- hhs.mgm - management definition file for the simulation +- hhs_muso7.mgm - management definition file for the simulation - hhs.mow - ancillary management file for mowing - Ndep.txt - Nitrogen deposition file for the simulation - CO2.txt - CO_{2} file for the simulation - parameters.csv - parameter interval file for the sensitivity analysis and optimization +- parameters2.csv - alternative parameter interval file for the optimization that contains allocation parameter intervals - HU-He2_2012_MEASURED.txt - sample observation file for the Hegyhátsál site (eddy covariance data for 2012) In the followings we will demonstrate the usability of RBBGCMuso with the hhs example dataset. If you have your own model input data set, you might need to change the commands accordingly. @@ -177,7 +178,7 @@ DAILY_OUTPUT #+END_SRC Note the number right below the DAILY_OUTPUT line that indicates the number of selected output variables. If you decide to change the number of output variables, the number (currently 12) should be adjusted accordingly. At present the R package handles only daily output data, but the user should acknowledge the optional annual output set in the ini file as well. -Biome-BGCMuSo offers a large number of posible output variables. The full list of variables are available at the website of the model as an Excel file: http://nimbus.elte.hu/bbgc/files/MUSO6.1_variables.xlsx +Biome-BGCMuSo offers a large number of posible output variables. The full list of variables are available at the website of the model as an Excel file: https://nimbus.elte.hu/~bzoli/public/OUTGOING/muso70beta07/Biome-BGCMuSo7.0-b7_outputs.xlsx Selection of output variables is primarily driven by the need of the user: it depends on the process that the user would like to study. We made an effort to provide all possible variables that are comparable with the observations. One might be interested in carbon fluxes like Net Ecosystem Exchange (NEE), Gross Primary Production (GPP), total ecosystem respiation (Reco, all comparable with eddy covariance measurements), evapotransporation (ET), Net Primary Production (NPP), soil organic carbon (SOC) content, leaf area index (LAI), aboveground woody biomass and coarse woody debris in forests, crop yield, rooting depth, aoveground or total biomass for herbaceous vegetation, litter, soil respiration, soil water content for 10 soil layers, soil N2O efflux, etc. @@ -238,25 +239,54 @@ At present musoQuickEffect is not usable for the allocation parameters due to re *** Study the effect of ecophysiological parameters using paramSweep -The paramSweep function is the extension of the musoQuickEffect. It can test the effect of the multiple selected parameters on the model results in once. The result of the paramSweep function is a single HTML file with embedded images. paramSweep needs a csv file called parameters.csv which defines the parameters of interest and the corresponding parameter intervals. In case of the hhs sample dataset there is an example parameters.csv file (please open it and check). The structure of the parameters.csv file is simple. First, parameter name is needed (it can be anything but should refer to the parameter), then the line number of the EPC file is provided, then the possible minimum and maximum value of the parameter is given. Note that there is a tricky part in the parameters.csv as the parameter selection is not straightforward in case of multiple columns (see the end of the EPC file!). The logic is that fractional part of a number is used to select the appropriate parameter from multiple columns. For example, "emergence,127.61,0,1000" means that in the 127th line of the EPC file there are 7 columns (numbering starts from 0, so it is 6), and we would like to adjust the 2nd column (marked by 1), which ends up with 127.61. 0,1000 means that sweep starts at 0 and ends with 1000. Invoke the paramSweep with simply issuing this command: +The paramSweep function is the extension of the musoQuickEffect. It can test the effect of the multiple selected parameters on the model results in once. The result of the paramSweep function is a single HTML file with embedded images. paramSweep needs a csv file called parameters.csv which defines the parameters of interest and the corresponding parameter intervals. In case of the hhs sample dataset there is an example parameters.csv file (please open it and check). The structure of the parameters.csv file is simple. First, parameter name is needed (it can be anything but should refer to the parameter), then the line number of the EPC file is provided, then the possible minimum and maximum value of the parameter is given. Note that there is a tricky part in the parameters.csv as the parameter selection is not straightforward in case of multiple columns (see the end of the EPC file!). The logic is that fractional part of a number is used to select the appropriate parameter from multiple columns. For example, "emergence,132.61,0,1000" means that in the 132nd line of the EPC file there are 7 columns (numbering starts from 0, so it is 6), and we would like to adjust the 2nd column (marked by 1), which ends up with 132.61. 0,1000 means that sweep starts at 0 and ends with 1000. Invoke the paramSweep with simply issuing this command: #+BEGIN_SRC R :eval no paramSweep() #+END_SRC -*IMPORTANT NOTE: After the execution of this command a pop-up window will be opened to select the appropriate parameters.csv file. Due to some R related issues at present the dialog window might appear BEHIND THE MAIN R/Rstudio WINDOW, so it might be hidden from the user. Please check the Windows taskbar and find the dialog window, then select the parameters.csv.* -In advanced mode there is possibility to select the parameters.csv file using the parameters of paramSweep. +The routine uses the provided parameters.csv by default. This can be changed of course and the user can provide an alternative csv file. *** Sensitivity analysis Advanced sensitivity analysis is possible with the musoSensi function of RBBGCMuso. [[http://nimbus.elte.hu/agromo/files/musoSensi_usage.html][Visit this link to read the manual of the sensitivity analysis.]] Note that parameters.csv is provided in the hhs example dataset, so you don't have to create it manually. -*IMPORTANT NOTE: If the result file contains only NAs it means that none of the parameters affected the output variable of interest. In this case you need to adjust the output parameter selection or the EPC parameter list. A simple example for this is soil temperature which is not affected by some of the plant parameters. [[https://github.com/hollorol/RBBGCMuso/issues/3][See this link for further details.]] +In the simplest case the user might issue the following command that can be immediately tested with the provided example: + +#+BEGIN_SRC R :eval no +musoSensi(iterations = 1000, varIndex = 2) +#+END_SRC + +This example runs the analysis with 1000 iterations using the second output variable (that is daily GPP). The results will be provided in a graphical form and also by numeric values. + +IMPORTANT NOTE: If the result file contains only NAs it means that none of the parameters affected the output variable of interest. In this case you need to adjust the output parameter selection or the EPC parameter list. A simple example for this is soil temperature which is not affected by some of the plant parameters. [[https://github.com/hollorol/RBBGCMuso/issues/3][See this link for further details.]] *** Parameter estimation (calibration) -RBBGCMuso supports parameter estimation (also called as model optimization or calibration) based on the so-called GLUE method. GLUE uses observations and the optimization is driven by the parameter intervals file that is described above (parameters.csv). Detailed description of the GLUE based optimization method will be published soon. Please contact the authors of the package for sample R scripts that executes the GLUE-based parameter estimation. +RBBGCMuso supports parameter estimation (also called as model optimization or calibration) based on the so-called GLUE method. GLUE uses observations and the optimization is driven by the parameter intervals file that is described above (parameters.csv). Below we provide a sample R script that executes the GLUE-based parameter estimation using the sample dataset that is provided by the copyMusoExampleTo() command (see above). Note that the content of the EPC file might have been changed as the result of the above-described procedures, which means that the user might want to remove the test folder and recreate it using the copyMusoExampleTo() command. The runMuso(skipSpinup = FALSE) command must be executed prior to testing the provided code if the model folder is newly created: + + +#+BEGIN_SRC R :eval no +md <- data.table::fread("HU-He2_2012_MEASURED.txt") +md[md ==-9999] <- NA +md[,GPP:=GPP/1000] +plotMusoWithData(md, modelVar = 3009, dataVar = "GPP") +plotMuso() + + +likelihoodGPP = list( + GPP = (function(x, y){exp(-sqrt(mean((x-y)^2))) })) +calibrateMuso(measuredData = md, + dataVar = c(GPP=3009), iterations = 100, + likelihood = likelihoodGPP, method="GLUE") +#+END_SRC + +In the script the observed daily GPP is used to construct the likelihood function. Unit conversion takes place since the model provides GPP in kgC/m2/day units while the observations are provided in gC/m2/day units. The result of the calibration is provided by a PDF file that is created in the model folder. The plotMusoWithData command is useful to compare visually the observation and the simulation. + +NOTE: we plan to disseminate a sample script in the future to demonstrate the applicability of the CIRM method in the GLUE context. + + *** Contact diff --git a/docs/sensi_complex_example.R b/docs/sensi_complex_example.R new file mode 100644 index 0000000..a40610c --- /dev/null +++ b/docs/sensi_complex_example.R @@ -0,0 +1,28 @@ +library('RBBGCMuso') + +## This function can be modified, it is a generator function, +## which works like this: +## meanmax_gen(4): meanmax for for the 4th year. + +meanmax_gen <- function(selectedYears=NULL){ + + function(x){ + years <- rep(1:(as.integer(length(x)/365)), each=365) + if(!is.null(selectedYears)){ + x <- x[years %in% selectedYears] + years <- years[years %in% selectedYears] + } + mean(tapply(x, years,function(year){ + max(year) + })) + } +} + +musoSensi(iteration=100,varIndex=2,fun=meanmax_gen()) + +settings <- setupMuso(iniInput=c(spinup="n.ini",normal="n.ini")) +# I would like to do the sensitivity only for maize. +settings$epcInput["normal"] <- "maize.epc" +## Select the 4th,5th year only for sensitivity ,assuming that these are the maize years +## The sensitivity will be calculated for mean of annual maximum values of LAI(varIndex = 2) +musoSensi(iteration=100,varIndex=2,fun=meanmax_gen(c(4,5))) diff --git a/test.R b/test.R deleted file mode 100644 index 88e85f5..0000000 --- a/test.R +++ /dev/null @@ -1,382 +0,0 @@ -parameters <- -getOption("RMuso_constMatrix")[["epc"]][["6"]] - NAME - yearday to start new growth - yearday to end new growth - transfer growth period as fraction of growing season - litterfall as fraction of growing season - base temperature - minimum temperature for growth displayed on current day - optimal1 temperature for growth displayed on current day - optimal2 temperature for growth displayed on current day - maxmimum temperature for growth displayed on current day - minimum temperature for carbon assimilation displayed on current day - optimal1 temperature for carbon assimilation displayed on current day - optimal2 temperature for carbon assimilation displayed on current day - maxmimum temperature for carbon assimilation displayed on current day - annual leaf and fine root turnover fraction - annual live wood turnover fraction - annual fire mortality fraction - whole-plant mortality paramter for vegetation period - C:N of leaves - C:N of leaf litter - C:N of fine roots - C:N of fruit - C:N of softstem - C:N of live wood - C:N of dead wood - dry matter content of leaves - dry matter content of leaf litter - dry matter content of fine roots - dry matter content of fruit - dry matter content of softstem - dry matter content of live wood - dry matter content of dead wood - leaf litter labile proportion - leaf litter cellulose proportion - fine root labile proportion - fine root cellulose proportion - fruit labile proportion - fruit cellulose proportion - softstem labile proportion - softstem cellulose proportion - dead wood cellulose proportion - canopy water interception coefficient - canopy light extinction coefficient - potential radiation use efficiency - radiation parameter1 (Jiang et al.2015) - radiation parameter1 (Jiang et al.2015) - all-sided to projected leaf area ratio - ratio of shaded SLA:sunlit SLA - fraction of leaf N in Rubisco - fraction of leaf N in PeP - maximum stomatal conductance - cuticular conductance - boundary layer conductance - maximum height of plant - stem weight corresponding to maximum height - plant height function shape parameter (slope) - maximum depth of rooting zone - root distribution parameter - root weight corresponding to max root depth - root depth function shape parameter (slope) - root weight to rooth length conversion factor - growth resp per unit of C grown - maintenance respiration in kgC/day per kg of tissue N - theoretical maximum prop. of non-structural and structural carbohydrates - prop. of non-structural carbohydrates available for maintanance resp - symbiotic+asymbiotic fixation of N - time delay for temperature in photosynthesis acclimation - critical VWCratio (prop. to FC-WP) in germination - critical photoslow daylength - slope of relative photoslow development rate - critical vernalization temperature 1 - critical vernalization temperature 2 - critical vernalization temperature 3 - critical vernalization temperature 4 - slope of relative vernalization development rate - required vernalization days (in vernalization development rate) - critical flowering heat stress temperature 1 - critical flowering heat stress temperature 2 - theoretical maximum of flowering thermal stress mortality - VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP) - VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC) - minimum of soil moisture limit2 multiplicator (full anoxic stress value) - vapor pressure deficit: start of conductance reduction - vapor pressure deficit: complete conductance reduction - maximum senescence mortality coefficient of aboveground plant material - maximum senescence mortality coefficient of belowground plant material - maximum senescence mortality coefficient of non-structured plant material - lower limit extreme high temperature effect on senescence mortality - upper limit extreme high temperature effect on senescence mortality - turnover rate of wilted standing biomass to litter - turnover rate of cut-down non-woody biomass to litter - turnover rate of cut-down woody biomass to litter - drought tolerance parameter (critical value of day since water stress) - effect of soilstress factor on photosynthesis - crit. amount of snow limiting photosyn. - limit1 (under:full constrained) of HEATSUM index - limit2 (above:unconstrained) of HEATSUM index - limit1 (under:full constrained) of TMIN index - limit2 (above:unconstrained) of TMIN index - limit1 (above:full constrained) of VPD index - limit2 (under:unconstrained) of VPD index - limit1 (under:full constrained) of DAYLENGTH index - limit2 (above:unconstrained) of DAYLENGTH index - moving average (to avoid the effects of extreme events) - GSI limit1 (greater that limit -> start of vegper) - GSI limit2 (less that limit -> end of vegper) - length of phenophase (GDD)-0 - leaf ALLOCATION -0 - fine root ALLOCATION-0 - fruit ALLOCATION -0 - soft stem ALLOCATION-0 - live woody stem ALLOCATION -0 - dead woody stem ALLOCATION -0 - live coarse root ALLOCATION-0 - dead coarse root ALLOCATION -0 - canopy average specific leaf area-0 - current growth proportion-0 - maximal lifetime of plant tissue-0 - length of phenophase (GDD)-1 - leaf ALLOCATION -1 - fine root ALLOCATION-1 - fruit ALLOCATION -1 - soft stem ALLOCATION-1 - live woody stem ALLOCATION -1 - dead woody stem ALLOCATION -1 - live coarse root ALLOCATION-1 - dead coarse root ALLOCATION -1 - canopy average specific leaf area-1 - current growth proportion-1 - maximal lifetime of plant tissue-1 - length of phenophase (GDD)-2 - leaf ALLOCATION -2 - fine root ALLOCATION-2 - fruit ALLOCATION -2 - soft stem ALLOCATION-2 - live woody stem ALLOCATION -2 - dead woody stem ALLOCATION -2 - live coarse root ALLOCATION-2 - dead coarse root ALLOCATION -2 - canopy average specific leaf area-2 - current growth proportion-2 - maximal lifetime of plant tissue-2 - length of phenophase (GDD)-3 - leaf ALLOCATION -3 - fine root ALLOCATION-3 - fruit ALLOCATION -3 - soft stem ALLOCATION-3 - live woody stem ALLOCATION -3 - dead woody stem ALLOCATION -3 - live coarse root ALLOCATION-3 - dead coarse root ALLOCATION -3 - canopy average specific leaf area-3 - current growth proportion-3 - maximal lifetime of plant tissue-3 - length of phenophase (GDD)-4 - leaf ALLOCATION -4 - fine root ALLOCATION-4 - fruit ALLOCATION -4 - soft stem ALLOCATION-4 - live woody stem ALLOCATION -4 - dead woody stem ALLOCATION -4 - live coarse root ALLOCATION-4 - dead coarse root ALLOCATION -4 - canopy average specific leaf area-4 - current growth proportion-4 - maximal lifetime of plant tissue-4 - length of phenophase (GDD)-5 - leaf ALLOCATION -5 - fine root ALLOCATION-5 - fruit ALLOCATION -5 - soft stem ALLOCATION-5 - live woody stem ALLOCATION -5 - dead woody stem ALLOCATION -5 - live coarse root ALLOCATION-5 - dead coarse root ALLOCATION -5 - canopy average specific leaf area-5 - current growth proportion-5 - maximal lifetime of plant tissue-5 - length of phenophase (GDD)-6 - leaf ALLOCATION -6 - fine root ALLOCATION-6 - fruit ALLOCATION -6 - soft stem ALLOCATION-6 - live woody stem ALLOCATION -6 - dead woody stem ALLOCATION -6 - live coarse root ALLOCATION-6 - dead coarse root ALLOCATION -6 - canopy average specific leaf area-6 - current growth proportion-6 - maximal lifetime of plant tissue-6 - INDEX UNIT DEPENDENCE MIN MAX GROUP TYPE - 9.00 yday NA 0.00000 364.0000 0 0 - 10.00 yday NA 0.00000 364.0000 0 0 - 11.00 prop NA 0.00000 1.0000 0 0 - 12.00 prop NA 0.00000 1.0000 0 0 - 13.00 Celsius NA 0.00000 12.0000 0 0 - 14.00 Celsius 0 0.00000 10.0000 1 1 - 15.00 Celsius 1 10.00000 20.0000 1 1 - 16.00 Celsius 2 20.00000 40.0000 1 1 - 17.00 Celsius 3 30.00000 50.0000 1 1 - 18.00 Celsius 0 0.00000 10.0000 2 1 - 19.00 Celsius 1 10.00000 20.0000 2 1 - 20.00 Celsius 2 20.00000 40.0000 2 1 - 21.00 Celsius 3 30.00000 50.0000 2 1 - 22.00 1/yr NA 0.10000 0.4000 0 0 - 23.00 1/yr NA 0.50000 1.0000 0 0 - 24.00 1/yr NA 0.00000 1.0000 0 0 - 25.00 1/vegper NA 0.00000 0.5000 0 0 - 26.00 kgC/kgN 0 10.00000 100.0000 3 1 - 27.00 kgC/kgN 1 10.00000 60.0000 3 1 - 28.00 kgC/kgN 1 10.00000 60.0000 3 1 - 29.00 kgC/kgN 1 10.00000 60.0000 3 1 - 30.00 kgC/kgN 1 10.00000 60.0000 3 1 - 31.00 kgC/kgN 0 50.00000 100.0000 4 1 - 32.00 kgC/kgN 1 300.00000 800.0000 4 1 - 33.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 34.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 35.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 36.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 37.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 38.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 39.00 kgC/kgDM NA 0.20000 0.6000 0 0 - 40.00 prop 1 0.10000 0.6000 5 2 - 41.00 prop 1 0.10000 0.6000 5 2 - 42.00 prop 1 0.10000 0.6000 6 2 - 43.00 prop 1 0.10000 0.6000 6 2 - 44.00 prop 1 0.10000 0.6000 7 2 - 45.00 prop 1 0.10000 0.6000 7 2 - 46.00 prop 1 0.10000 0.6000 8 2 - 47.00 prop 1 0.10000 0.6000 8 2 - 48.00 prop NA 0.50000 0.9000 0 0 - 49.00 1/LAI/d NA 0.01000 0.1000 0 0 - 50.00 dimless NA 0.20000 0.8000 0 0 - 51.00 g/MJ NA 2.00000 2.0000 0 0 - 52.00 dimless NA 0.78100 0.7810 0 0 - 53.00 dimless NA -13.59600 -13.5960 0 0 - 54.00 dimless NA 2.00000 2.0000 0 0 - 55.00 dimless NA 2.00000 2.0000 0 0 - 56.00 dimless NA 0.01000 0.2000 0 0 - 57.00 dimless NA 0.04240 0.0424 0 0 - 58.00 m/s NA 0.00100 0.1000 0 0 - 59.00 m/s NA 0.00001 0.0001 0 0 - 60.00 m/s NA 0.01000 0.0900 0 0 - 61.00 m NA 0.10000 10.0000 0 0 - 62.00 kgC NA 0.10000 100.0000 0 0 - 63.00 dimless NA 0.50000 0.5000 0 0 - 64.00 m NA 0.10000 10.0000 0 0 - 65.00 prop NA 3.67000 3.6700 0 0 - 66.00 kgC/m2 NA 0.40000 0.4000 0 0 - 67.00 prop NA 0.50000 0.5000 0 0 - 68.00 m/kg NA 1000.00000 1000.0000 0 0 - 69.00 prop NA 0.10000 0.5000 0 0 - 70.00 kgC/kgN/d NA 0.10000 0.5000 0 0 - 71.00 dimless NA 0.00000 1.0000 0 0 - 72.00 dimless NA 0.00000 1.0000 0 0 - 73.00 kgN/m2/yr NA 0.00000 0.0010 0 0 - 74.00 day NA 0.00000 50.0000 0 0 - 79.00 prop NA 0.00000 1.0000 0 0 - 81.00 hour NA 14.00000 18.0000 0 0 - 82.00 dimless NA 0.00500 0.0050 0 0 - 84.00 Celsius 0 -5.00000 5.0000 9 1 - 85.00 Celsius 1 0.00000 10.0000 9 1 - 86.00 Celsius 2 5.00000 15.0000 9 1 - 87.00 Celsius 3 10.00000 20.0000 9 1 - 88.00 dimless NA 0.04000 0.0400 0 0 - 89.00 dimless NA 30.00000 70.0000 0 0 - 91.00 Celsius 0 30.00000 40.0000 10 1 - 92.00 Celsius 1 30.00000 50.0000 10 1 - 93.00 prop NA 0.00000 0.4000 0 0 - 96.00 prop NA 0.50000 1.0000 0 0 - 97.00 prop NA 0.50000 1.0000 0 0 - 98.00 prop NA 0.00000 1.0000 0 0 - 99.00 Pa NA 500.00000 1500.0000 0 0 -100.00 Pa NA 1500.00000 3500.0000 0 0 -101.00 prop 0 0.00000 0.1000 0 0 -102.00 prop 1 0.00000 0.1000 0 0 -103.00 prop NA 0.00000 0.1000 0 0 -104.00 Celsius NA 30.00000 40.0000 0 0 -105.00 Celsius NA 30.00000 50.0000 0 0 -106.00 prop NA 0.00000 0.1000 0 0 -107.00 prop NA 0.00000 0.1000 0 0 -108.00 prop NA 0.00000 0.1000 0 0 -109.00 n_day NA 0.00000 100.0000 0 0 -110.00 dimless NA 0.00000 1.0000 0 0 -113.00 kg/m2 NA 0.00000 20.0000 0 0 -114.00 Celsius 0 0.00000 50.0000 11 1 -115.00 Celsius 1 0.00000 100.0000 11 1 -116.00 Celsius 0 -5.00000 5.0000 12 1 -117.00 Celsius 1 0.00000 10.0000 12 1 -118.00 Pa 0 2000.00000 600.0000 13 1 -119.00 Pa 1 500.00000 1500.0000 13 1 -120.00 s 0 0.00000 0.0000 14 1 -121.00 s 1 0.00000 0.0000 14 1 -122.00 n_day NA 2.00000 20.0000 0 0 -123.00 dimless NA 0.00000 0.2000 0 0 -124.00 dimless NA 0.00000 0.1000 0 0 -128.60 Celsius NA 0.00000 10000.0000 0 0 -129.60 prop 1 0.00000 1.0000 15 -3 -130.60 prop 1 0.00000 1.0000 15 -3 -131.60 prop 1 0.00000 1.0000 15 -3 -132.60 prop 1 0.00000 1.0000 15 -3 -133.60 prop 1 0.00000 1.0000 15 -3 -134.60 prop 1 0.00000 1.0000 15 -3 -135.60 prop 1 0.00000 1.0000 15 -3 -136.60 prop 1 0.00000 1.0000 15 -3 -137.60 m2/kg NA 0.00000 2.0000 0 0 -138.60 prop NA 0.00000 0.0000 0 0 -139.60 Celsius NA 1.00000 20000.0000 0 0 -128.61 Celsius NA 0.00000 10000.0000 0 0 -129.61 prop 1 0.00000 1.0000 16 -3 -130.61 prop 1 0.00000 1.0000 16 -3 -131.61 prop 1 0.00000 1.0000 16 -3 -132.61 prop 1 0.00000 1.0000 16 -3 -133.61 prop 1 0.00000 1.0000 16 -3 -134.61 prop 1 0.00000 1.0000 16 -3 -135.61 prop 1 0.00000 1.0000 16 -3 -136.61 prop 1 0.00000 1.0000 16 -3 -137.61 m2/kg NA 0.00000 2.0000 0 0 -138.61 prop NA 0.00000 0.0000 0 0 -139.61 Celsius NA 1.00000 20000.0000 0 0 -128.62 Celsius NA 0.00000 10000.0000 0 0 -129.62 prop 1 0.00000 1.0000 17 -3 -130.62 prop 1 0.00000 1.0000 17 -3 -131.62 prop 1 0.00000 1.0000 17 -3 -132.62 prop 1 0.00000 1.0000 17 -3 -133.62 prop 1 0.00000 1.0000 17 -3 -134.62 prop 1 0.00000 1.0000 17 -3 -135.62 prop 1 0.00000 1.0000 17 -3 -136.62 prop 1 0.00000 1.0000 17 -3 -137.62 m2/kg NA 0.00000 2.0000 0 0 -138.62 prop NA 0.00000 0.0000 0 0 -139.62 Celsius NA 1.00000 20000.0000 0 0 -128.63 Celsius NA 0.00000 10000.0000 0 0 -129.63 prop 1 0.00000 1.0000 18 -3 -130.63 prop 1 0.00000 1.0000 18 -3 -131.63 prop 1 0.00000 1.0000 18 -3 -132.63 prop 1 0.00000 1.0000 18 -3 -133.63 prop 1 0.00000 1.0000 18 -3 -134.63 prop 1 0.00000 1.0000 18 -3 -135.63 prop 1 0.00000 1.0000 18 -3 -136.63 prop 1 0.00000 1.0000 18 -3 -137.63 m2/kg NA 0.00000 2.0000 0 0 -138.63 prop NA 0.00000 0.0000 0 0 -139.63 Celsius NA 1.00000 20000.0000 0 0 -128.64 Celsius NA 0.00000 10000.0000 0 0 -129.64 prop 1 0.00000 1.0000 19 -3 -130.64 prop 1 0.00000 1.0000 19 -3 -131.64 prop 1 0.00000 1.0000 19 -3 -132.64 prop 1 0.00000 1.0000 19 -3 -133.64 prop 1 0.00000 1.0000 19 -3 -134.64 prop 1 0.00000 1.0000 19 -3 -135.64 prop 1 0.00000 1.0000 19 -3 -136.64 prop 1 0.00000 1.0000 19 -3 -137.64 m2/kg NA 0.00000 2.0000 0 0 -138.64 prop NA 0.00000 0.0000 0 0 -139.64 Celsius NA 1.00000 20000.0000 0 0 -128.65 Celsius NA 0.00000 10000.0000 0 0 -129.65 prop 1 0.00000 1.0000 20 -3 -130.65 prop 1 0.00000 1.0000 20 -3 -131.65 prop 1 0.00000 1.0000 20 -3 -132.65 prop 1 0.00000 1.0000 20 -3 -133.65 prop 1 0.00000 1.0000 20 -3 -134.65 prop 1 0.00000 1.0000 20 -3 -135.65 prop 1 0.00000 1.0000 20 -3 -136.65 prop 1 0.00000 1.0000 20 -3 -137.65 m2/kg NA 0.00000 2.0000 0 0 -138.65 prop NA 0.00000 0.0000 0 0 -139.65 Celsius NA 1.00000 20000.0000 0 0 -128.66 Celsius NA 0.00000 10000.0000 0 0 -129.66 prop 1 0.00000 1.0000 21 -3 -130.66 prop 1 0.00000 1.0000 21 -3 -131.66 prop 1 0.00000 1.0000 21 -3 -132.66 prop 1 0.00000 1.0000 21 -3 -133.66 prop 1 0.00000 1.0000 21 -3 -134.66 prop 1 0.00000 1.0000 21 -3 -135.66 prop 1 0.00000 1.0000 21 -3 -136.66 prop 1 0.00000 1.0000 21 -3 -137.66 m2/kg NA 0.00000 2.0000 0 0 -138.66 prop NA 0.00000 0.0000 0 0 -139.66 Celsius NA 1.00000 20000.0000 0 0